Index: trunk/src/transforms/transforms.nw =================================================================== --- trunk/src/transforms/transforms.nw (revision 8817) +++ trunk/src/transforms/transforms.nw (revision 8818) @@ -1,16316 +1,16319 @@ % -*- ess-noweb-default-code-mode: f90-mode; noweb-default-code-mode: f90-mode; -*- % WHIZARD event transforms and event API %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \chapter{Event Implementation} \includemodulegraph{transforms} With a process object and the associated methods at hand, we can generate events for elementary processes and, by subsequent transformation, for complete physical processes. We have the following modules: \begin{description} \item[event\_transforms] Abstract base type for transforming a physical process with process instance and included evaluators, etc., into a new object. The following modules extend this base type. \item[resonance\_insertion] Insert a resonance history into an event record, based on kinematical and matrix-element information. \item[recoil\_kinematics] Common kinematics routines for the ISR and EPA handlers. \item[isr\_photon\_handler] Transform collinear kinematics, as it results from applying ISR radiation, to non-collinear kinematics with a reasonable transverse-momentum distribution of the radiated photons, and also of the recoiling partonic event. \item[epa\_beam\_handler] For photon-initiated processes where the effective photon approximation is used in integration, to add in beam-particle recoil. Analogous to the ISR handler. \item[decays] Combine the elementary process with elementary decay processes and thus transform the elementary event into a decayed event, still at the parton level. \item[showers] Create QED/QCD showers out of the partons that are emitted by elementary processes. This should be interleaved with showering of radiated particles (structure functions) and multiple interactions. \item[hadrons] (not implemented yet) Apply hadronization to the partonic events, interleaved with hadron decays. (The current setup relies on hadronizing partonic events externally.) \item[tau\_decays] (not implemented yet) Let $\tau$ leptons decay taking full spin correlations into account. \item[evt\_nlo] Handler for fixed-order NLO events. \item[events] Combine all pieces to generate full events. \item[eio\_raw] Raw I/O for complete events. \end{description} @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Abstract Event Transforms} <<[[event_transforms.f90]]>>= <> module event_transforms <> <> use quantum_numbers, only: quantum_numbers_t use interactions use particles use model_data use rng_base use process, only: process_t use instances, only: process_instance_t use process_stacks <> <> <> <> interface <> end interface end module event_transforms @ %def event_transforms @ <<[[event_transforms_sub.f90]]>>= <> submodule (event_transforms) event_transforms_s use io_units use format_utils, only: write_separator use diagnostics use subevents implicit none contains <> end submodule event_transforms_s @ %def event_transforms_s @ \subsection{Abstract base type} Essentially, all methods are abstract, but some get minimal base versions. We know that there will be a random-number generator at top level, and that we will relate to an elementary process. The model is stored separately. It may contain modified settings that differ from the model instance stored in the process object. Each event transform contains a particle set that it can fill for further use. There is a flag that indicates this. We will collect event transforms in a list, therefore we include [[previous]] and [[next]] pointers. <>= public :: evt_t <>= type, abstract :: evt_t type(process_t), pointer :: process => null () type(process_instance_t), pointer :: process_instance => null () class(model_data_t), pointer :: model => null () class(rng_t), allocatable :: rng integer :: rejection_count = 0 logical :: particle_set_exists = .false. type(particle_set_t) :: particle_set class(evt_t), pointer :: previous => null () class(evt_t), pointer :: next => null () logical :: only_weighted_events = .false. contains <> end type evt_t @ %def evt_t @ Finalizer. In any case, we finalize the r.n.g. The process instance is a pointer and should not be finalized here. <>= procedure :: final => evt_final procedure :: base_final => evt_final <>= module subroutine evt_final (evt) class(evt_t), intent(inout) :: evt end subroutine evt_final <>= module subroutine evt_final (evt) class(evt_t), intent(inout) :: evt if (allocated (evt%rng)) call evt%rng%final () if (evt%particle_set_exists) & call evt%particle_set%final () end subroutine evt_final @ %def evt_final @ Print out the type of the [[evt]]. <>= procedure (evt_write_name), deferred :: write_name <>= abstract interface subroutine evt_write_name (evt, unit) import class(evt_t), intent(in) :: evt integer, intent(in), optional :: unit end subroutine evt_write_name end interface @ %def evt_write_name @ <>= procedure (evt_write), deferred :: write <>= abstract interface subroutine evt_write (evt, unit, verbose, more_verbose, testflag) import class(evt_t), intent(in) :: evt integer, intent(in), optional :: unit logical, intent(in), optional :: verbose, more_verbose, testflag end subroutine evt_write end interface @ %def evt_write @ Output. We can print r.n.g. info. <>= procedure :: base_write => evt_base_write <>= module subroutine evt_base_write (evt, unit, testflag, show_set) class(evt_t), intent(in) :: evt integer, intent(in), optional :: unit logical, intent(in), optional :: testflag, show_set end subroutine evt_base_write <>= module subroutine evt_base_write (evt, unit, testflag, show_set) class(evt_t), intent(in) :: evt integer, intent(in), optional :: unit logical, intent(in), optional :: testflag, show_set integer :: u logical :: show u = given_output_unit (unit) show = .true.; if (present (show_set)) show = show_set if (associated (evt%process)) then write (u, "(3x,A,A,A)") "Associated process: '", & char (evt%process%get_id ()), "'" end if if (allocated (evt%rng)) then call evt%rng%write (u, 1) write (u, "(3x,A,I0)") "Number of tries = ", evt%rejection_count end if if (show) then if (evt%particle_set_exists) then call write_separator (u) call evt%particle_set%write (u, testflag = testflag) end if end if end subroutine evt_base_write @ %def evt_base_write @ Connect the transform with a process instance (and thus with the associated process). Use this to allocate the master random-number generator. This is not an initializer; we may initialize the transform by implementation-specific methods. <>= procedure :: connect => evt_connect procedure :: base_connect => evt_connect <>= module subroutine evt_connect (evt, process_instance, model, process_stack) class(evt_t), intent(inout), target :: evt type(process_instance_t), intent(in), target :: process_instance class(model_data_t), intent(in), target :: model type(process_stack_t), intent(in), optional :: process_stack end subroutine evt_connect <>= module subroutine evt_connect (evt, process_instance, model, process_stack) class(evt_t), intent(inout), target :: evt type(process_instance_t), intent(in), target :: process_instance class(model_data_t), intent(in), target :: model type(process_stack_t), intent(in), optional :: process_stack evt%process => process_instance%process evt%process_instance => process_instance evt%model => model call evt%process%make_rng (evt%rng) end subroutine evt_connect @ %def evt_connect @ Reset internal state. <>= procedure :: reset => evt_reset procedure :: base_reset => evt_reset <>= module subroutine evt_reset (evt) class(evt_t), intent(inout) :: evt end subroutine evt_reset <>= module subroutine evt_reset (evt) class(evt_t), intent(inout) :: evt evt%rejection_count = 0 call evt%particle_set%final () evt%particle_set_exists = .false. end subroutine evt_reset @ %def evt_reset @ Prepare for a new event: reset internal state, if necessary. We provide MCI and term index of the parent process. <>= procedure (evt_prepare_new_event), deferred :: prepare_new_event <>= interface subroutine evt_prepare_new_event (evt, i_mci, i_term) import class(evt_t), intent(inout) :: evt integer, intent(in) :: i_mci, i_term end subroutine evt_prepare_new_event end interface @ %def evt_prepare_new_event @ Generate a weighted event, using a valid initiator event in the process instance, and the random-number generator. The returned event probability should be a number between zero and one that we can use for rejection. <>= procedure (evt_generate_weighted), deferred :: generate_weighted <>= abstract interface subroutine evt_generate_weighted (evt, probability) import class(evt_t), intent(inout) :: evt real(default), intent(inout) :: probability end subroutine evt_generate_weighted end interface @ %def evt_generate_weighted @ The unweighted event generation routine is actually implemented. It uses the random-number generator for simple rejection. Of course, the implementation may override this and implement a different way of generating an unweighted event. <>= procedure :: generate_unweighted => evt_generate_unweighted procedure :: base_generate_unweighted => evt_generate_unweighted <>= module subroutine evt_generate_unweighted (evt) class(evt_t), intent(inout) :: evt end subroutine evt_generate_unweighted <>= module subroutine evt_generate_unweighted (evt) class(evt_t), intent(inout) :: evt real(default) :: p, x evt%rejection_count = 0 REJECTION: do evt%rejection_count = evt%rejection_count + 1 call evt%generate_weighted (p) if (signal_is_pending ()) return call evt%rng%generate (x) if (x < p) exit REJECTION end do REJECTION end subroutine evt_generate_unweighted @ %def evt_generate_unweighted @ Make a particle set. This should take the most recent evaluator (or whatever stores the event), factorize the density matrix if necessary, and store as a particle set. If applicable, the factorization should make use of the [[factorization_mode]] and [[keep_correlations]] settings. The values [[r]], if set, should control the factorization in more detail, e.g., bypassing the random-number generator. <>= procedure (evt_make_particle_set), deferred :: make_particle_set <>= interface subroutine evt_make_particle_set & (evt, factorization_mode, keep_correlations, r) import class(evt_t), intent(inout) :: evt integer, intent(in) :: factorization_mode logical, intent(in) :: keep_correlations real(default), dimension(:), intent(in), optional :: r end subroutine evt_make_particle_set end interface @ %def evt_make_particle_set @ Copy an existing particle set into the event record. This bypasses all methods to evaluate the internal state, but may be sufficient for further processing. <>= procedure :: set_particle_set => evt_set_particle_set <>= module subroutine evt_set_particle_set (evt, particle_set, i_mci, i_term) class(evt_t), intent(inout) :: evt type(particle_set_t), intent(in) :: particle_set integer, intent(in) :: i_term, i_mci end subroutine evt_set_particle_set <>= module subroutine evt_set_particle_set (evt, particle_set, i_mci, i_term) class(evt_t), intent(inout) :: evt type(particle_set_t), intent(in) :: particle_set integer, intent(in) :: i_term, i_mci call evt%prepare_new_event (i_mci, i_term) evt%particle_set = particle_set evt%particle_set_exists = .true. end subroutine evt_set_particle_set @ %def evt_set_particle_set @ This procedure can help in the previous task, if the particles are available in the form of an interaction object. We need two interactions, one with color summed over, the [[int_matrix]], and one with the probability distributed among flows, the [[int_flows]]. We use the two values from the random number generator saved in [[r]] for factorizing the state. For testing purposes, we can provide those numbers explicitly. The optional [[qn_select]] allows to limit the number of quantum numbers to choose from when factorizing. If only a single set of quantum numbers is given, it effectively dictates the quantum numbers chosen for the event. <>= procedure :: factorize_interactions => evt_factorize_interactions <>= module subroutine evt_factorize_interactions & (evt, int_matrix, int_flows, factorization_mode, & keep_correlations, r, qn_select) class(evt_t), intent(inout) :: evt type(interaction_t), intent(in), target :: int_matrix, int_flows integer, intent(in) :: factorization_mode logical, intent(in) :: keep_correlations real(default), dimension(:), intent(in), optional :: r type(quantum_numbers_t), dimension(:), intent(in), optional :: qn_select end subroutine evt_factorize_interactions <>= module subroutine evt_factorize_interactions & (evt, int_matrix, int_flows, factorization_mode, & keep_correlations, r, qn_select) class(evt_t), intent(inout) :: evt type(interaction_t), intent(in), target :: int_matrix, int_flows integer, intent(in) :: factorization_mode logical, intent(in) :: keep_correlations real(default), dimension(:), intent(in), optional :: r type(quantum_numbers_t), dimension(:), intent(in), optional :: qn_select real(default), dimension(2) :: x if (present (r)) then if (size (r) == 2) then x = r else call msg_bug ("event factorization: size of r array must be 2") end if else call evt%rng%generate (x) end if call evt%particle_set%init (evt%particle_set_exists, & int_matrix, int_flows, factorization_mode, x, & keep_correlations, keep_virtual=.true., qn_select = qn_select) evt%particle_set_exists = .true. end subroutine evt_factorize_interactions @ %def evt_factorize_interactions @ <>= public :: make_factorized_particle_set <>= module subroutine make_factorized_particle_set (evt, factorization_mode, & keep_correlations, r, ii_term, qn_select) class(evt_t), intent(inout) :: evt integer, intent(in) :: factorization_mode logical, intent(in) :: keep_correlations real(default), dimension(:), intent(in), optional :: r integer, intent(in), optional :: ii_term type(quantum_numbers_t), dimension(:), intent(in), optional :: qn_select end subroutine make_factorized_particle_set <>= module subroutine make_factorized_particle_set (evt, factorization_mode, & keep_correlations, r, ii_term, qn_select) class(evt_t), intent(inout) :: evt integer, intent(in) :: factorization_mode logical, intent(in) :: keep_correlations real(default), dimension(:), intent(in), optional :: r integer, intent(in), optional :: ii_term type(quantum_numbers_t), dimension(:), intent(in), optional :: qn_select integer :: i_term type(interaction_t), pointer :: int_matrix, int_flows if (evt%process_instance%is_complete_event ()) then if (present (ii_term)) then i_term = ii_term else i_term = evt%process_instance%select_i_term () end if int_matrix => evt%process_instance%get_matrix_int_ptr (i_term) int_flows => evt%process_instance%get_flows_int_ptr (i_term) call evt%factorize_interactions (int_matrix, int_flows, & factorization_mode, keep_correlations, r, qn_select) call evt%tag_incoming () else call msg_bug ("Event factorization: event is incomplete") end if end subroutine make_factorized_particle_set @ %def make_factorized_particle_set @ Mark the incoming particles as incoming in the particle set. This is necessary because in the interaction objects they are usually marked as virtual. In the inquiry functions we set the term index to one; the indices of beams and incoming particles should be identical for all process terms. We use the initial elementary process for obtaining the indices. Thus, we implicitly assume that the beam and incoming indices stay the same across event transforms. If this is not true for a transform (say, MPI), it should override this method. <>= procedure :: tag_incoming => evt_tag_incoming <>= module subroutine evt_tag_incoming (evt) class(evt_t), intent(inout) :: evt end subroutine evt_tag_incoming <>= module subroutine evt_tag_incoming (evt) class(evt_t), intent(inout) :: evt integer :: i_term, n_in integer, dimension(:), allocatable :: beam_index, in_index n_in = evt%process%get_n_in () i_term = 1 allocate (beam_index (n_in)) call evt%process_instance%get_beam_index (i_term, beam_index) call evt%particle_set%reset_status (beam_index, PRT_BEAM) allocate (in_index (n_in)) call evt%process_instance%get_in_index (i_term, in_index) call evt%particle_set%reset_status (in_index, PRT_INCOMING) end subroutine evt_tag_incoming @ %def evt_tag_incoming @ \subsection{Implementation: Trivial transform} This transform contains just a pointer to process and process instance. The [[generate]] methods do nothing. <>= public :: evt_trivial_t <>= type, extends (evt_t) :: evt_trivial_t contains <> end type evt_trivial_t @ %def evt_trivial_t @ <>= procedure :: write_name => evt_trivial_write_name <>= module subroutine evt_trivial_write_name (evt, unit) class(evt_trivial_t), intent(in) :: evt integer, intent(in), optional :: unit end subroutine evt_trivial_write_name <>= module subroutine evt_trivial_write_name (evt, unit) class(evt_trivial_t), intent(in) :: evt integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(1x,A)") "Event transform: trivial (hard process)" end subroutine evt_trivial_write_name @ %def evt_trivial_write_name @ The finalizer is trivial. Some output: <>= procedure :: write => evt_trivial_write <>= module subroutine evt_trivial_write & (evt, unit, verbose, more_verbose, testflag) class(evt_trivial_t), intent(in) :: evt integer, intent(in), optional :: unit logical, intent(in), optional :: verbose, more_verbose, testflag end subroutine evt_trivial_write <>= module subroutine evt_trivial_write & (evt, unit, verbose, more_verbose, testflag) class(evt_trivial_t), intent(in) :: evt integer, intent(in), optional :: unit logical, intent(in), optional :: verbose, more_verbose, testflag integer :: u u = given_output_unit (unit) call write_separator (u, 2) call evt%write_name (u) call write_separator (u) call evt%base_write (u, testflag = testflag) !!! More readable but wider output; in line with evt_resonance_write ! if (verbose .and. evt%particle_set_exists) then ! call evt%particle_set%write & ! (u, summary = .true., compressed = .true., testflag = testflag) ! call write_separator (u) ! end if end subroutine evt_trivial_write @ %def evt_trivial_write @ Nothing to do here: <>= procedure :: prepare_new_event => evt_trivial_prepare_new_event <>= module subroutine evt_trivial_prepare_new_event (evt, i_mci, i_term) class(evt_trivial_t), intent(inout) :: evt integer, intent(in) :: i_mci, i_term end subroutine evt_trivial_prepare_new_event <>= module subroutine evt_trivial_prepare_new_event (evt, i_mci, i_term) class(evt_trivial_t), intent(inout) :: evt integer, intent(in) :: i_mci, i_term call evt%reset () end subroutine evt_trivial_prepare_new_event @ %def evt_trivial_prepare_new_event @ The weighted generator is, surprisingly, trivial. <>= procedure :: generate_weighted => evt_trivial_generate_weighted <>= module subroutine evt_trivial_generate_weighted (evt, probability) class(evt_trivial_t), intent(inout) :: evt real(default), intent(inout) :: probability end subroutine evt_trivial_generate_weighted <>= module subroutine evt_trivial_generate_weighted (evt, probability) class(evt_trivial_t), intent(inout) :: evt real(default), intent(inout) :: probability probability = 1 end subroutine evt_trivial_generate_weighted @ %def evt_trivial_generate_weighted @ This routine makes a particle set, using the associated process instance as-is. Note that it is a potential risk to tolerate a non-existent particle set at this point. We should remove it once the flavors are determined correctly in all cases. It is currently neccessary if we are keeping failed events [[?keep_failed_events = .true.]]. For these events, we do not compute the matrix elements, so the factorization fails trying to determine the quantum numbers. Additionally, it is necessary for the trivial event transformation preceeding the event transformations required for POWHEG matching. <>= procedure :: make_particle_set => evt_trivial_make_particle_set <>= module subroutine evt_trivial_make_particle_set & (evt, factorization_mode, keep_correlations, r) class(evt_trivial_t), intent(inout) :: evt integer, intent(in) :: factorization_mode logical, intent(in) :: keep_correlations real(default), dimension(:), intent(in), optional :: r end subroutine evt_trivial_make_particle_set <>= module subroutine evt_trivial_make_particle_set & (evt, factorization_mode, keep_correlations, r) class(evt_trivial_t), intent(inout) :: evt integer, intent(in) :: factorization_mode logical, intent(in) :: keep_correlations real(default), dimension(:), intent(in), optional :: r call make_factorized_particle_set (evt, factorization_mode, & keep_correlations, r) evt%particle_set_exists = .true. end subroutine evt_trivial_make_particle_set @ %def event_trivial_make_particle_set @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[event_transforms_ut.f90]]>>= <> module event_transforms_ut use unit_tests use event_transforms_uti <> <> contains <> end module event_transforms_ut @ %def event_transforms_ut @ <<[[event_transforms_uti.f90]]>>= <> module event_transforms_uti <> <> use format_utils, only: write_separator use os_interface use sm_qcd use models use state_matrices, only: FM_IGNORE_HELICITY use interactions, only: reset_interaction_counter use process_libraries use rng_base use mci_base use mci_midpoint use phs_base use phs_single use prc_core use prc_test, only: prc_test_create_library use process, only: process_t use instances, only: process_instance_t use event_transforms use rng_base_ut, only: rng_test_factory_t <> <> contains <> <> end module event_transforms_uti @ %def event_transforms_uti @ API: driver for the unit tests below. <>= public :: event_transforms_test <>= subroutine event_transforms_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine event_transforms_test @ %def event_transforms_test @ \subsubsection{Test trivial event transform} The trivial transform, as an instance of the abstract transform, does nothing but to trigger event generation for an elementary process. <>= call test (event_transforms_1, "event_transforms_1", & "trivial event transform", & u, results) <>= public :: event_transforms_1 <>= subroutine event_transforms_1 (u) integer, intent(in) :: u type(os_data_t) :: os_data type(model_t), target :: model type(process_library_t), target :: lib type(string_t) :: libname, procname1 class(phs_config_t), allocatable :: phs_config_template real(default) :: sqrts type(process_t), allocatable, target :: process type(process_instance_t), allocatable, target :: process_instance class(evt_t), allocatable :: evt integer :: factorization_mode logical :: keep_correlations write (u, "(A)") "* Test output: event_transforms_1" write (u, "(A)") "* Purpose: handle trivial transform" write (u, "(A)") write (u, "(A)") "* Initialize environment and parent process" write (u, "(A)") call os_data%init () libname = "event_transforms_1_lib" procname1 = "event_transforms_1_p" call prc_test_create_library (libname, lib, & scattering = .true., procname1 = procname1) call reset_interaction_counter () call model%init_test () allocate (process) call process%init (procname1, lib, os_data, model) call process%setup_test_cores () allocate (phs_single_config_t :: phs_config_template) call process%init_components (phs_config_template) sqrts = 1000 call process%setup_beams_sqrts (sqrts, i_core = 1) call process%configure_phs () call process%setup_mci (dispatch_mci_test_midpoint) call process%setup_terms () allocate (process_instance) call process_instance%init (process) call process_instance%integrate (1, n_it=1, n_calls=100) call process%final_integration (1) call process_instance%final () deallocate (process_instance) allocate (process_instance) call process_instance%init (process) call process_instance%setup_event_data () call process_instance%init_simulation (1) write (u, "(A)") "* Initialize trivial event transform" write (u, "(A)") allocate (evt_trivial_t :: evt) call evt%connect (process_instance, process%get_model_ptr ()) write (u, "(A)") "* Generate event and subsequent transform" write (u, "(A)") call process_instance%generate_unweighted_event (1) call process_instance%evaluate_event_data () call evt%prepare_new_event (1, 1) call evt%generate_unweighted () call write_separator (u, 2) call evt%write (u) call write_separator (u, 2) write (u, "(A)") write (u, "(A)") "* Obtain particle set" write (u, "(A)") factorization_mode = FM_IGNORE_HELICITY keep_correlations = .false. call evt%make_particle_set (factorization_mode, keep_correlations) call write_separator (u, 2) call evt%write (u) call write_separator (u, 2) write (u, "(A)") write (u, "(A)") "* Cleanup" call evt%final () call process_instance%final () deallocate (process_instance) write (u, "(A)") write (u, "(A)") "* Test output end: event_transforms_1" end subroutine event_transforms_1 @ %def event_transforms_1 @ MCI record prepared for midpoint integrator. <>= subroutine dispatch_mci_test_midpoint (mci, var_list, process_id, is_nlo) use variables, only: var_list_t 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 allocate (mci_midpoint_t :: mci) end subroutine dispatch_mci_test_midpoint @ %def dispatch_mci_test_midpoint @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Hadronization interface} <<[[hadrons.f90]]>>= <> module hadrons <> <> use event_transforms use lorentz use model_data use models use particles use physics_defs use process, only: process_t use instances, only: process_instance_t use process_stacks use whizard_lha use pythia8 use rng_base, only: rng_t use shower_base use shower_pythia6 use sm_qcd use variables <> <> <> <> <> interface <> end interface end module hadrons @ %def hadrons @ <<[[hadrons_sub.f90]]>>= <> submodule (hadrons) hadrons_s <> use constants use diagnostics use format_utils, only: write_separator use helicities use hep_common use io_units use numeric_utils, only: vanishes use subevents implicit none contains <> end submodule hadrons_s @ %def hadrons_s @ \subsection{Hadronization implementations} <>= public :: HADRONS_UNDEFINED, HADRONS_WHIZARD, HADRONS_PYTHIA6, HADRONS_PYTHIA8 <>= integer, parameter :: HADRONS_UNDEFINED = 0 integer, parameter :: HADRONS_WHIZARD = 1 integer, parameter :: HADRONS_PYTHIA6 = 2 integer, parameter :: HADRONS_PYTHIA8 = 3 @ %def HADRONS_UNDEFINED HADRONS_WHIZARD HADRONS_PYTHIA6 HADRONS_PYTHIA8 @ A dictionary <>= public :: hadrons_method <>= interface hadrons_method module procedure hadrons_method_of_string module procedure hadrons_method_to_string end interface <>= elemental module function hadrons_method_of_string (string) result (i) integer :: i type(string_t), intent(in) :: string end function hadrons_method_of_string elemental module function hadrons_method_to_string (i) result (string) type(string_t) :: string integer, intent(in) :: i end function hadrons_method_to_string <>= elemental module function hadrons_method_of_string (string) result (i) integer :: i type(string_t), intent(in) :: string select case (char(string)) case ("WHIZARD") i = HADRONS_WHIZARD case ("PYTHIA6") i = HADRONS_PYTHIA6 case ("PYTHIA8") i = HADRONS_PYTHIA8 case default i = HADRONS_UNDEFINED end select end function hadrons_method_of_string elemental module function hadrons_method_to_string (i) result (string) type(string_t) :: string integer, intent(in) :: i select case (i) case (HADRONS_WHIZARD) string = "WHIZARD" case (HADRONS_PYTHIA6) string = "PYTHIA6" case (HADRONS_PYTHIA8) string = "PYTHIA8" case default string = "UNDEFINED" end select end function hadrons_method_to_string @ %def hadrons_method @ \subsection{Hadronization settings} These are the general settings and parameters for the different shower methods. <>= public :: hadron_settings_t <>= type :: hadron_settings_t logical :: active = .false. integer :: method = HADRONS_UNDEFINED real(default) :: enhanced_fraction = 0 real(default) :: enhanced_width = 0 contains <> end type hadron_settings_t @ %def hadron_settings_t @ Read in the hadronization settings. <>= procedure :: init => hadron_settings_init <>= module subroutine hadron_settings_init (hadron_settings, var_list) class(hadron_settings_t), intent(out) :: hadron_settings type(var_list_t), intent(in) :: var_list end subroutine hadron_settings_init <>= module subroutine hadron_settings_init (hadron_settings, var_list) class(hadron_settings_t), intent(out) :: hadron_settings type(var_list_t), intent(in) :: var_list hadron_settings%active = & var_list%get_lval (var_str ("?hadronization_active")) hadron_settings%method = hadrons_method_of_string ( & var_list%get_sval (var_str ("$hadronization_method"))) hadron_settings%enhanced_fraction = & var_list%get_rval (var_str ("hadron_enhanced_fraction")) hadron_settings%enhanced_width = & var_list%get_rval (var_str ("hadron_enhanced_width")) end subroutine hadron_settings_init @ %def hadron_settings_init @ <>= procedure :: write => hadron_settings_write <>= module subroutine hadron_settings_write (settings, unit) class(hadron_settings_t), intent(in) :: settings integer, intent(in), optional :: unit end subroutine hadron_settings_write <>= module subroutine hadron_settings_write (settings, unit) class(hadron_settings_t), intent(in) :: settings integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit); if (u < 0) return write (u, "(1x,A)") "Hadronization settings:" call write_separator (u) write (u, "(1x,A)") "Master switches:" write (u, "(3x,A,1x,L1)") & "active = ", settings%active write (u, "(1x,A)") "General settings:" if (settings%active) then write (u, "(3x,A)") & "hadron_method = " // & char (hadrons_method_to_string (settings%method)) else write (u, "(3x,A)") " [Hadronization off]" end if write (u, "(1x,A)") "pT generation parameters" write (u, "(3x,A,1x,ES19.12)") & "enhanced_fraction = ", settings%enhanced_fraction write (u, "(3x,A,1x,ES19.12)") & "enhanced_width = ", settings%enhanced_width end subroutine hadron_settings_write @ %def hadron_settings_write @ \subsection{Abstract Hadronization Type} The [[model]] is the fallback model including all hadrons <>= type, abstract :: hadrons_t class(rng_t), allocatable :: rng type(shower_settings_t) :: shower_settings type(hadron_settings_t) :: hadron_settings type(model_t), pointer :: model => null() contains <> end type hadrons_t @ %def hadrons_t @ <>= procedure (hadrons_init), deferred :: init <>= abstract interface subroutine hadrons_init & (hadrons, shower_settings, hadron_settings, model_hadrons) import class(hadrons_t), intent(out) :: hadrons type(shower_settings_t), intent(in) :: shower_settings type(hadron_settings_t), intent(in) :: hadron_settings type(model_t), target, intent(in) :: model_hadrons end subroutine hadrons_init end interface @ %def hadrons_init @ <>= procedure (hadrons_hadronize), deferred :: hadronize <>= abstract interface subroutine hadrons_hadronize (hadrons, particle_set, valid) import class(hadrons_t), intent(inout) :: hadrons type(particle_set_t), intent(in) :: particle_set logical, intent(out) :: valid end subroutine hadrons_hadronize end interface @ %def hadrons_hadronize @ <>= procedure (hadrons_make_particle_set), deferred :: make_particle_set <>= abstract interface subroutine hadrons_make_particle_set (hadrons, particle_set, & model, valid) import class(hadrons_t), intent(in) :: hadrons type(particle_set_t), intent(inout) :: particle_set class(model_data_t), intent(in), target :: model logical, intent(out) :: valid end subroutine hadrons_make_particle_set end interface @ %def hadrons_make_particle_set @ <>= procedure :: import_rng => hadrons_import_rng <>= pure module subroutine hadrons_import_rng (hadrons, rng) class(hadrons_t), intent(inout) :: hadrons class(rng_t), intent(inout), allocatable :: rng end subroutine hadrons_import_rng <>= pure module subroutine hadrons_import_rng (hadrons, rng) class(hadrons_t), intent(inout) :: hadrons class(rng_t), intent(inout), allocatable :: rng call move_alloc (from = rng, to = hadrons%rng) end subroutine hadrons_import_rng @ %def hadrons_import_rng @ \subsection{[[WHIZARD]] Hadronization Type} Hadronization can be (incompletely) performed through \whizard's internal routine. <>= public :: hadrons_hadrons_t <>= type, extends (hadrons_t) :: hadrons_hadrons_t contains <> end type hadrons_hadrons_t @ %def hadrons_hadrons_t @ <>= procedure :: init => hadrons_hadrons_init <>= module subroutine hadrons_hadrons_init & (hadrons, shower_settings, hadron_settings, model_hadrons) class(hadrons_hadrons_t), intent(out) :: hadrons type(shower_settings_t), intent(in) :: shower_settings type(hadron_settings_t), intent(in) :: hadron_settings type(model_t), intent(in), target :: model_hadrons end subroutine hadrons_hadrons_init <>= module subroutine hadrons_hadrons_init & (hadrons, shower_settings, hadron_settings, model_hadrons) class(hadrons_hadrons_t), intent(out) :: hadrons type(shower_settings_t), intent(in) :: shower_settings type(hadron_settings_t), intent(in) :: hadron_settings type(model_t), intent(in), target :: model_hadrons hadrons%model => model_hadrons hadrons%shower_settings = shower_settings hadrons%hadron_settings = hadron_settings call msg_message & ("Hadronization: WHIZARD model for hadronization and decays") end subroutine hadrons_hadrons_init @ %def hadrons_hadrons_init @ <>= procedure :: hadronize => hadrons_hadrons_hadronize <>= module subroutine hadrons_hadrons_hadronize (hadrons, particle_set, valid) class(hadrons_hadrons_t), intent(inout) :: hadrons type(particle_set_t), intent(in) :: particle_set logical, intent(out) :: valid end subroutine hadrons_hadrons_hadronize <>= module subroutine hadrons_hadrons_hadronize (hadrons, particle_set, valid) class(hadrons_hadrons_t), intent(inout) :: hadrons type(particle_set_t), intent(in) :: particle_set logical, intent(out) :: valid integer, dimension(:), allocatable :: cols, acols, octs integer :: n if (signal_is_pending ()) return if (debug_on) call msg_debug (D_TRANSFORMS, "hadrons_hadrons_hadronize") call particle_set%write (6, compressed=.true.) n = particle_set%get_n_tot () allocate (cols (n), acols (n), octs (n)) call extract_color_systems (particle_set, cols, acols, octs) print *, "size(cols) = ", size (cols) if (size(cols) > 0) then print *, "cols = ", cols end if print *, "size(acols) = ", size(acols) if (size(acols) > 0) then print *, "acols = ", acols end if print *, "size(octs) = ", size(octs) if (size (octs) > 0) then print *, "octs = ", octs end if !!! if all arrays are empty, i.e. zero particles found, nothing to do end subroutine hadrons_hadrons_hadronize @ %def hadrons_hadrons_hadronize @ This type contains a flavor selector for the creation of hadrons, including parameters for the special handling of baryons. <>= public :: had_flav_t <>= type had_flav_t end type had_flav_t @ %def had_flav_t @ This is the type for the ends of Lund strings. <>= public :: lund_end <>= type lund_end logical :: from_pos integer :: i_end integer :: i_max integer :: id_had integer :: i_pos_old integer :: i_neg_old integer :: i_pos_new integer :: i_neg_new real(default) :: px_old real(default) :: py_old real(default) :: px_new real(default) :: py_new real(default) :: px_had real(default) :: py_had real(default) :: m_had real(default) :: mT2_had real(default) :: z_had real(default) :: gamma_old real(default) :: gamma_new real(default) :: x_pos_old real(default) :: x_pos_new real(default) :: x_pos_had real(default) :: x_neg_old real(default) :: x_neg_new real(default) :: x_neg_had type(had_flav_t) :: old_flav type(had_flav_t) :: new_flav type(vector4_t) :: p_had type(vector4_t) :: p_pre end type lund_end @ %def lund_end @ Generator for transverse momentum for the fragmentation. <>= public :: lund_pt_t <>= type lund_pt_t real(default) :: sigma_min real(default) :: sigma_q real(default) :: enhanced_frac real(default) :: enhanced_width real(default) :: sigma_to_had class(rng_t), allocatable :: rng contains <> end type lund_pt_t @ %def lund_pt <>= procedure :: init => lund_pt_init <>= module subroutine lund_pt_init (lund_pt, settings) class (lund_pt_t), intent(out) :: lund_pt type(hadron_settings_t), intent(in) :: settings end subroutine lund_pt_init <>= module subroutine lund_pt_init (lund_pt, settings) class (lund_pt_t), intent(out) :: lund_pt type(hadron_settings_t), intent(in) :: settings end subroutine lund_pt_init @ %def lund_pt_init @ <>= procedure :: make_particle_set => hadrons_hadrons_make_particle_set <>= module subroutine hadrons_hadrons_make_particle_set & (hadrons, particle_set, model, valid) class(hadrons_hadrons_t), intent(in) :: hadrons type(particle_set_t), intent(inout) :: particle_set class(model_data_t), intent(in), target :: model logical, intent(out) :: valid end subroutine hadrons_hadrons_make_particle_set <>= module subroutine hadrons_hadrons_make_particle_set & (hadrons, particle_set, model, valid) class(hadrons_hadrons_t), intent(in) :: hadrons type(particle_set_t), intent(inout) :: particle_set class(model_data_t), intent(in), target :: model logical, intent(out) :: valid if (signal_is_pending ()) return valid = .false. if (valid) then else call msg_fatal ("WHIZARD hadronization not yet implemented") end if end subroutine hadrons_hadrons_make_particle_set @ %def hadrons_hadrons_make_particle_set @ <>= subroutine extract_color_systems (p_set, cols, acols, octs) type(particle_set_t), intent(in) :: p_set integer, dimension(:), allocatable, intent(out) :: cols, acols, octs logical, dimension(:), allocatable :: mask integer :: i, n, n_cols, n_acols, n_octs n = p_set%get_n_tot () allocate (mask (n)) do i = 1, n mask(i) = p_set%prt(i)%col%get_col () /= 0 .and. & p_set%prt(i)%col%get_acl () == 0 .and. & p_set%prt(i)%get_status () == PRT_OUTGOING end do n_cols = count (mask) allocate (cols (n_cols)) cols = p_set%get_indices (mask) do i = 1, n mask(i) = p_set%prt(i)%col%get_col () == 0 .and. & p_set%prt(i)%col%get_acl () /= 0 .and. & p_set%prt(i)%get_status () == PRT_OUTGOING end do n_acols = count (mask) allocate (acols (n_acols)) acols = p_set%get_indices (mask) do i = 1, n mask(i) = p_set%prt(i)%col%get_col () /= 0 .and. & p_set%prt(i)%col%get_acl () /= 0 .and. & p_set%prt(i)%get_status () == PRT_OUTGOING end do n_octs = count (mask) allocate (octs (n_octs)) octs = p_set%get_indices (mask) end subroutine extract_color_systems @ %def extract_color_systems @ \subsection{[[PYTHIA6]] Hadronization Type} Hadronization via [[PYTHIA6]] is at another option for hadronization within \whizard. <>= public :: hadrons_pythia6_t <>= type, extends (hadrons_t) :: hadrons_pythia6_t contains <> end type hadrons_pythia6_t @ %def hadrons_pythia6_t <>= procedure :: init => hadrons_pythia6_init <>= module subroutine hadrons_pythia6_init & (hadrons, shower_settings, hadron_settings, model_hadrons) class(hadrons_pythia6_t), intent(out) :: hadrons type(shower_settings_t), intent(in) :: shower_settings type(hadron_settings_t), intent(in) :: hadron_settings type(model_t), intent(in), target :: model_hadrons end subroutine hadrons_pythia6_init <>= module subroutine hadrons_pythia6_init & (hadrons, shower_settings, hadron_settings, model_hadrons) class(hadrons_pythia6_t), intent(out) :: hadrons type(shower_settings_t), intent(in) :: shower_settings type(hadron_settings_t), intent(in) :: hadron_settings type(model_t), intent(in), target :: model_hadrons logical :: pygive_not_set_by_shower hadrons%model => model_hadrons hadrons%shower_settings = shower_settings hadrons%hadron_settings = hadron_settings pygive_not_set_by_shower = .not. (shower_settings%method == PS_PYTHIA6 & .and. (shower_settings%isr_active .or. shower_settings%fsr_active)) if (pygive_not_set_by_shower) then call pythia6_set_verbose (shower_settings%verbose) call pythia6_set_config (shower_settings%pythia6_pygive) end if call msg_message & ("Hadronization: Using PYTHIA6 interface for hadronization and decays") end subroutine hadrons_pythia6_init @ %def hadrons_pythia6_init @ Assume that the event record is still in the PYTHIA COMMON BLOCKS transferred there by the WHIZARD or PYTHIA6 shower routines. <>= procedure :: hadronize => hadrons_pythia6_hadronize <>= module subroutine hadrons_pythia6_hadronize (hadrons, particle_set, valid) class(hadrons_pythia6_t), intent(inout) :: hadrons type(particle_set_t), intent(in) :: particle_set logical, intent(out) :: valid end subroutine hadrons_pythia6_hadronize <>= module subroutine hadrons_pythia6_hadronize (hadrons, particle_set, valid) class(hadrons_pythia6_t), intent(inout) :: hadrons type(particle_set_t), intent(in) :: particle_set logical, intent(out) :: valid integer :: N, NPAD, K real(double) :: P, V common /PYJETS/ N, NPAD, K(4000,5), P(4000,5), V(4000,5) save /PYJETS/ if (signal_is_pending ()) return if (debug_on) call msg_debug (D_TRANSFORMS, "hadrons_pythia6_hadronize") call pygive ("MSTP(111)=1") !!! Switch on hadronization and decays call pygive ("MSTJ(1)=1") !!! String fragmentation call pygive ("MSTJ(21)=2") !!! String fragmentation keeping resonance momentum call pygive ("MSTJ(28)=0") !!! Switch off tau decays if (debug_active (D_TRANSFORMS)) then call msg_debug (D_TRANSFORMS, "N", N) call pylist(2) print *, ' line 7 : ', k(7,1:5), p(7,1:5) end if call pyedit (12) call pythia6_set_last_treated_line (N) call pyexec () call pyedit (12) valid = .true. end subroutine hadrons_pythia6_hadronize @ %def hadrons_pythia6_hadronize @ <>= procedure :: make_particle_set => hadrons_pythia6_make_particle_set <>= module subroutine hadrons_pythia6_make_particle_set & (hadrons, particle_set, model, valid) class(hadrons_pythia6_t), intent(in) :: hadrons type(particle_set_t), intent(inout) :: particle_set class(model_data_t), intent(in), target :: model logical, intent(out) :: valid end subroutine hadrons_pythia6_make_particle_set <>= module subroutine hadrons_pythia6_make_particle_set & (hadrons, particle_set, model, valid) class(hadrons_pythia6_t), intent(in) :: hadrons type(particle_set_t), intent(inout) :: particle_set class(model_data_t), intent(in), target :: model logical, intent(out) :: valid if (signal_is_pending ()) return valid = pythia6_handle_errors () if (valid) then call pythia6_combine_with_particle_set & (particle_set, model, hadrons%model, hadrons%shower_settings) end if end subroutine hadrons_pythia6_make_particle_set @ %def hadrons_pythia6_make_particle_set @ \subsection{[[PYTHIA8]] Hadronization} @ <>= public :: hadrons_pythia8_t <>= type, extends (hadrons_t) :: hadrons_pythia8_t type(pythia8_t) :: pythia type(whizard_lha_t) :: lhaup logical :: user_process_set = .false. logical :: pythia_initialized = .false., & lhaup_initialized = .false. contains <> end type hadrons_pythia8_t @ %def hadrons_pythia8_t @ <>= procedure :: init => hadrons_pythia8_init <>= module subroutine hadrons_pythia8_init & (hadrons, shower_settings, hadron_settings, model_hadrons) class(hadrons_pythia8_t), intent(out) :: hadrons type(shower_settings_t), intent(in) :: shower_settings type(hadron_settings_t), intent(in) :: hadron_settings type(model_t), intent(in), target :: model_hadrons end subroutine hadrons_pythia8_init <>= module subroutine hadrons_pythia8_init & (hadrons, shower_settings, hadron_settings, model_hadrons) class(hadrons_pythia8_t), intent(out) :: hadrons type(shower_settings_t), intent(in) :: shower_settings type(hadron_settings_t), intent(in) :: hadron_settings type(model_t), intent(in), target :: model_hadrons hadrons%model => model_hadrons hadrons%shower_settings = shower_settings hadrons%hadron_settings = hadron_settings call msg_message ("Hadronization: Using PYTHIA8 interface " // & "for hadronization and decays.") ! TODO sbrass which verbose? call hadrons%pythia%init (verbose = shower_settings%verbose) call hadrons%lhaup%init () end subroutine hadrons_pythia8_init @ %def hadrons_pythia8_init @ Transfer hadron settings to [[PYTHIA8]]. <>= procedure, private :: transfer_settings => hadrons_pythia8_transfer_settings <>= module subroutine hadrons_pythia8_transfer_settings (hadrons) class(hadrons_pythia8_t), intent(inout), target :: hadrons end subroutine hadrons_pythia8_transfer_settings <>= module subroutine hadrons_pythia8_transfer_settings (hadrons) class(hadrons_pythia8_t), intent(inout), target :: hadrons real(default) :: r if (debug_on) call msg_debug & (D_TRANSFORMS, "hadrons_pythia8_transfer_settings") if (debug_on) call msg_debug2 & (D_TRANSFORMS, "pythia_initialized", hadrons%pythia_initialized) if (hadrons%pythia_initialized) return call hadrons%pythia%import_rng (hadrons%rng) call hadrons%pythia%parse_and_set_config & (hadrons%shower_settings%pythia8_config) if (len (hadrons%shower_settings%pythia8_config_file) > 0) & call hadrons%pythia%read_file & (hadrons%shower_settings%pythia8_config_file) call hadrons%pythia%read_string (var_str ("Beams:frameType = 5")) call hadrons%pythia%read_string (var_str ("ProcessLevel:all = off")) if (.not. hadrons%shower_settings%verbose) then call hadrons%pythia%read_string (var_str ("Print:quiet = on")) end if call hadrons%pythia%set_lhaup_ptr (hadrons%lhaup) call hadrons%pythia%init_pythia () hadrons%pythia_initialized = .true. end subroutine hadrons_pythia8_transfer_settings @ %def hadrons_pythia8_transfer_settings @ Set user process for the LHA interface. <>= procedure, private :: set_user_process => hadrons_pythia8_set_user_process <>= module subroutine hadrons_pythia8_set_user_process (hadrons, pset) class(hadrons_pythia8_t), intent(inout) :: hadrons type(particle_set_t), intent(in) :: pset end subroutine hadrons_pythia8_set_user_process <>= module subroutine hadrons_pythia8_set_user_process (hadrons, pset) class(hadrons_pythia8_t), intent(inout) :: hadrons type(particle_set_t), intent(in) :: pset integer, dimension(2) :: beam_pdg real(default), dimension(2) :: beam_energy integer, parameter :: process_id = 0, n_processes = 0 if (debug_on) call msg_debug & (D_TRANSFORMS, "hadrons_pythia8_set_user_process") beam_pdg = [pset%prt(1)%get_pdg (), pset%prt(2)%get_pdg ()] beam_energy = [energy(pset%prt(1)%p), energy(pset%prt(2)%p)] call hadrons%lhaup%set_init (beam_pdg, beam_energy, & n_processes, unweighted = .false., negative_weights = .false.) call hadrons%lhaup%set_process_parameters (process_id = process_id, & cross_section = one, error = one) end subroutine hadrons_pythia8_set_user_process @ %def hadrons_pythia8_set_user_process @ Import particle set. <>= procedure, private :: import_particle_set => & hadrons_pythia8_import_particle_set <>= module subroutine hadrons_pythia8_import_particle_set & (hadrons, particle_set) class(hadrons_pythia8_t), target, intent(inout) :: hadrons type(particle_set_t), intent(in) :: particle_set end subroutine hadrons_pythia8_import_particle_set <>= module subroutine hadrons_pythia8_import_particle_set (hadrons, particle_set) class(hadrons_pythia8_t), target, intent(inout) :: hadrons type(particle_set_t), intent(in) :: particle_set type(particle_set_t) :: pset_reduced integer, parameter :: PROCESS_ID = 1 if (debug_on) call msg_debug & (D_TRANSFORMS, "hadrons_pythia8_import_particle_set") if (.not. hadrons%user_process_set) then call hadrons%set_user_process (particle_set) hadrons%user_process_set = .true. end if call hadrons%lhaup%set_event_process (process_id = PROCESS_ID, & scale = -one, alpha_qcd = -one, alpha_qed = -one, weight = -one) call hadrons%lhaup%set_event (process_id = PROCESS_ID, & particle_set = particle_set, polarization = .true.) if (debug_active (D_TRANSFORMS)) then call hadrons%lhaup%list_init () end if end subroutine hadrons_pythia8_import_particle_set @ %def hadrons_pythia8_import_particle_set @ <>= procedure :: hadronize => hadrons_pythia8_hadronize <>= module subroutine hadrons_pythia8_hadronize (hadrons, particle_set, valid) class(hadrons_pythia8_t), intent(inout) :: hadrons type(particle_set_t), intent(in) :: particle_set logical, intent(out) :: valid end subroutine hadrons_pythia8_hadronize <>= module subroutine hadrons_pythia8_hadronize (hadrons, particle_set, valid) class(hadrons_pythia8_t), intent(inout) :: hadrons type(particle_set_t), intent(in) :: particle_set logical, intent(out) :: valid if (signal_is_pending ()) return call hadrons%import_particle_set (particle_set) if (.not. hadrons%pythia_initialized) & call hadrons%transfer_settings () call hadrons%pythia%next (valid) if (debug_active (D_TRANSFORMS)) then call hadrons%pythia%list_event () call particle_set%write (summary=.true., compressed=.true.) end if end subroutine hadrons_pythia8_hadronize @ %def hadrons_pythia8_hadronize @ <>= procedure :: make_particle_set => hadrons_pythia8_make_particle_set <>= module subroutine hadrons_pythia8_make_particle_set & (hadrons, particle_set, model, valid) class(hadrons_pythia8_t), intent(in) :: hadrons type(particle_set_t), intent(inout) :: particle_set class(model_data_t), intent(in), target :: model logical, intent(out) :: valid end subroutine hadrons_pythia8_make_particle_set <>= module subroutine hadrons_pythia8_make_particle_set & (hadrons, particle_set, model, valid) class(hadrons_pythia8_t), intent(in) :: hadrons type(particle_set_t), intent(inout) :: particle_set class(model_data_t), intent(in), target :: model logical, intent(out) :: valid type(particle_t), dimension(:), allocatable :: beam if (debug_on) call msg_debug & (D_TRANSFORMS, "hadrons_pythia8_make_particle_set") if (signal_is_pending ()) return associate (settings => hadrons%shower_settings) if (debug_active (D_TRANSFORMS)) then call msg_debug (D_TRANSFORMS, 'Combine PYTHIA8 with particle set') call msg_debug (D_TRANSFORMS, 'Particle set before replacing') call particle_set%write (summary=.true., compressed=.true.) call hadrons%pythia%list_event () call msg_debug (D_TRANSFORMS, string = "settings%hadron_collision", & value = settings%hadron_collision) end if call hadrons%pythia%get_hadron_particles (& model, hadrons%model, particle_set, & helicity = PRT_DEFINITE_HELICITY) end associate if (debug_active (D_TRANSFORMS)) then print *, 'Particle set after replacing' call particle_set%write (summary=.true., compressed=.true.) end if valid = .true. end subroutine hadrons_pythia8_make_particle_set @ %def hadrons_pythia8_make_particle_set @ \subsection{Hadronization Event Transform} This is the type for the hadronization event transform. It does not depend on the specific hadronization implementation of [[hadrons_t]]. <>= public :: evt_hadrons_t <>= type, extends (evt_t) :: evt_hadrons_t class(hadrons_t), allocatable :: hadrons type(model_t), pointer :: model_hadrons => null() type(qcd_t) :: qcd logical :: is_first_event contains <> end type evt_hadrons_t @ %def evt_hadrons_t @ Initialize the parameters. The [[model_hadrons]] is supposed to be the SM variant that contains all hadrons that may be generated in the shower. <>= procedure :: init => evt_hadrons_init <>= module subroutine evt_hadrons_init (evt, model_hadrons) class(evt_hadrons_t), intent(out) :: evt type(model_t), intent(in), target :: model_hadrons end subroutine evt_hadrons_init <>= module subroutine evt_hadrons_init (evt, model_hadrons) class(evt_hadrons_t), intent(out) :: evt type(model_t), intent(in), target :: model_hadrons evt%model_hadrons => model_hadrons evt%is_first_event = .true. end subroutine evt_hadrons_init @ %def evt_hadrons_init @ <>= procedure :: write_name => evt_hadrons_write_name <>= module subroutine evt_hadrons_write_name (evt, unit) class(evt_hadrons_t), intent(in) :: evt integer, intent(in), optional :: unit end subroutine evt_hadrons_write_name <>= module subroutine evt_hadrons_write_name (evt, unit) class(evt_hadrons_t), intent(in) :: evt integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(1x,A)") "Event transform: hadronization" end subroutine evt_hadrons_write_name @ %def evt_hadrons_write_name @ Output. <>= procedure :: write => evt_hadrons_write <>= module subroutine evt_hadrons_write & (evt, unit, verbose, more_verbose, testflag) class(evt_hadrons_t), intent(in) :: evt integer, intent(in), optional :: unit logical, intent(in), optional :: verbose, more_verbose, testflag end subroutine evt_hadrons_write <>= module subroutine evt_hadrons_write & (evt, unit, verbose, more_verbose, testflag) class(evt_hadrons_t), intent(in) :: evt integer, intent(in), optional :: unit logical, intent(in), optional :: verbose, more_verbose, testflag integer :: u u = given_output_unit (unit) call write_separator (u, 2) call evt%write_name (u) call write_separator (u) call evt%base_write (u, testflag = testflag, show_set = .false.) if (evt%particle_set_exists) & call evt%particle_set%write & (u, summary = .true., compressed = .true., testflag = testflag) call write_separator (u) call evt%hadrons%shower_settings%write (u) call write_separator (u) call evt%hadrons%hadron_settings%write (u) end subroutine evt_hadrons_write @ %def evt_hadrons_write @ <>= procedure :: first_event => evt_hadrons_first_event <>= module subroutine evt_hadrons_first_event (evt) class(evt_hadrons_t), intent(inout) :: evt end subroutine evt_hadrons_first_event <>= module subroutine evt_hadrons_first_event (evt) class(evt_hadrons_t), intent(inout) :: evt if (debug_on) call msg_debug (D_TRANSFORMS, "evt_hadrons_first_event") associate (settings => evt%hadrons%shower_settings) settings%hadron_collision = .false. if (all (evt%particle_set%prt(1:2)%flv%get_pdg_abs () <= 39)) then settings%hadron_collision = .false. else if (all (evt%particle_set%prt(1:2)%flv%get_pdg_abs () >= 100)) then settings%hadron_collision = .true. else call msg_fatal ("evt_hadrons didn't recognize beams setup") end if if (debug_on) call msg_debug & (D_TRANSFORMS, "hadron_collision", settings%hadron_collision) if (.not. (settings%isr_active .or. settings%fsr_active)) then call msg_fatal ("Hadronization without shower is not supported") end if end associate evt%is_first_event = .false. end subroutine evt_hadrons_first_event @ %def evt_hadrons_first_event @ Here we take the particle set from the previous event transform and apply the hadronization. The result is stored in the [[evt%hadrons]] object. We always return a probability of unity as we don't have the analytic weight of the hadronization. Invalid events have to be discarded by the caller which is why we mark the particle set as invalid. <>= procedure :: generate_weighted => evt_hadrons_generate_weighted <>= module subroutine evt_hadrons_generate_weighted (evt, probability) class(evt_hadrons_t), intent(inout) :: evt real(default), intent(inout) :: probability end subroutine evt_hadrons_generate_weighted <>= module subroutine evt_hadrons_generate_weighted (evt, probability) class(evt_hadrons_t), intent(inout) :: evt real(default), intent(inout) :: probability logical :: valid if (signal_is_pending ()) return evt%particle_set = evt%previous%particle_set if (evt%is_first_event) then call evt%first_event () end if call evt%hadrons%hadronize (evt%particle_set, valid) probability = 1 evt%particle_set_exists = valid end subroutine evt_hadrons_generate_weighted @ %def evt_hadrons_generate_weighted @ The factorization parameters are irrelevant. <>= procedure :: make_particle_set => evt_hadrons_make_particle_set <>= module subroutine evt_hadrons_make_particle_set & (evt, factorization_mode, keep_correlations, r) class(evt_hadrons_t), intent(inout) :: evt integer, intent(in) :: factorization_mode logical, intent(in) :: keep_correlations real(default), dimension(:), intent(in), optional :: r end subroutine evt_hadrons_make_particle_set <>= module subroutine evt_hadrons_make_particle_set & (evt, factorization_mode, keep_correlations, r) class(evt_hadrons_t), intent(inout) :: evt integer, intent(in) :: factorization_mode logical, intent(in) :: keep_correlations real(default), dimension(:), intent(in), optional :: r logical :: valid call evt%hadrons%make_particle_set (evt%particle_set, evt%model, valid) evt%particle_set_exists = evt%particle_set_exists .and. valid end subroutine evt_hadrons_make_particle_set @ %def event_hadrons_make_particle_set @ Connect the process with the hadrons object. <>= procedure :: connect => evt_hadrons_connect <>= module subroutine evt_hadrons_connect & (evt, process_instance, model, process_stack) class(evt_hadrons_t), intent(inout), target :: evt type(process_instance_t), intent(in), target :: process_instance class(model_data_t), intent(in), target :: model type(process_stack_t), intent(in), optional :: process_stack end subroutine evt_hadrons_connect <>= module subroutine evt_hadrons_connect & (evt, process_instance, model, process_stack) class(evt_hadrons_t), intent(inout), target :: evt type(process_instance_t), intent(in), target :: process_instance class(model_data_t), intent(in), target :: model type(process_stack_t), intent(in), optional :: process_stack call evt%base_connect (process_instance, model, process_stack) call evt%make_rng (evt%process) end subroutine evt_hadrons_connect @ %def evt_hadrons_connect @ Create RNG instances, spawned by the process object. <>= procedure :: make_rng => evt_hadrons_make_rng <>= module subroutine evt_hadrons_make_rng (evt, process) class(evt_hadrons_t), intent(inout) :: evt type(process_t), intent(inout) :: process class(rng_t), allocatable :: rng end subroutine evt_hadrons_make_rng <>= module subroutine evt_hadrons_make_rng (evt, process) class(evt_hadrons_t), intent(inout) :: evt type(process_t), intent(inout) :: process class(rng_t), allocatable :: rng call process%make_rng (rng) call evt%hadrons%import_rng (rng) end subroutine evt_hadrons_make_rng @ %def evt_hadrons_make_rng @ <>= procedure :: prepare_new_event => evt_hadrons_prepare_new_event <>= module subroutine evt_hadrons_prepare_new_event (evt, i_mci, i_term) class(evt_hadrons_t), intent(inout) :: evt integer, intent(in) :: i_mci, i_term end subroutine evt_hadrons_prepare_new_event <>= module subroutine evt_hadrons_prepare_new_event (evt, i_mci, i_term) class(evt_hadrons_t), intent(inout) :: evt integer, intent(in) :: i_mci, i_term call evt%reset () end subroutine evt_hadrons_prepare_new_event @ %def evt_hadrons_prepare_new_event @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Resonance Insertion} <<[[resonance_insertion.f90]]>>= <> module resonance_insertion <> <> use rng_base, only: rng_t use selectors, only: selector_t use particles, only: particle_t, particle_set_t use resonances, only: resonance_history_set_t use resonances, only: resonance_tree_t use instances, only: process_instance_ptr_t use event_transforms <> <> <> interface <> end interface end module resonance_insertion @ %def resonance_insertion @ <<[[resonance_insertion_sub.f90]]>>= <> submodule (resonance_insertion) resonance_insertion_s use io_units use format_utils, only: write_separator use format_defs, only: FMT_12 use interactions, only: interaction_t use subevents, only: PRT_RESONANT implicit none contains <> end submodule resonance_insertion_s @ %def resonance_insertion_s @ \subsection{Resonance-Insertion Event Transform} This is the type for the event transform that applies resonance insertion. The resonance history set describe the resonance histories that we may consider. There is a process library with process objects that correspond to the resonance histories. Library creation, compilation etc.\ is done outside the scope of this module. <>= public :: evt_resonance_t <>= type, extends (evt_t) :: evt_resonance_t type(resonance_history_set_t), dimension(:), allocatable :: res_history_set integer, dimension(:), allocatable :: index_offset integer :: selected_component = 0 type(string_t) :: libname type(string_t), dimension(:), allocatable :: proc_id real(default) :: on_shell_limit = 0 real(default) :: on_shell_turnoff = 0 real(default) :: background_factor = 1 logical :: selector_active = .false. type(selector_t) :: selector integer :: selected_history = 0 type(process_instance_ptr_t), dimension(:), allocatable :: instance contains <> end type evt_resonance_t @ %def evt_resonance_t <>= procedure :: write_name => evt_resonance_write_name <>= module subroutine evt_resonance_write_name (evt, unit) class(evt_resonance_t), intent(in) :: evt integer, intent(in), optional :: unit end subroutine evt_resonance_write_name <>= module subroutine evt_resonance_write_name (evt, unit) class(evt_resonance_t), intent(in) :: evt integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(1x,A)") "Event transform: resonance insertion" end subroutine evt_resonance_write_name @ %def evt_resonance_write_name @ Output. <>= procedure :: write => evt_resonance_write <>= module subroutine evt_resonance_write & (evt, unit, verbose, more_verbose, testflag) class(evt_resonance_t), intent(in) :: evt integer, intent(in), optional :: unit logical, intent(in), optional :: verbose, more_verbose, testflag end subroutine evt_resonance_write <>= module subroutine evt_resonance_write & (evt, unit, verbose, more_verbose, testflag) class(evt_resonance_t), intent(in) :: evt integer, intent(in), optional :: unit logical, intent(in), optional :: verbose, more_verbose, testflag integer :: u, i u = given_output_unit (unit) call write_separator (u, 2) call evt%write_name (u) call write_separator (u, 2) write (u, "(1x,A,A,A)") "Process library = '", char (evt%libname), "'" if (allocated (evt%res_history_set)) then do i = 1, size (evt%res_history_set) if (i == evt%selected_component) then write (u, "(1x,A,I0,A)") "Component #", i, ": *" else write (u, "(1x,A,I0,A)") "Component #", i, ":" end if call evt%res_history_set(i)%write (u, indent=1) end do end if call write_separator (u) if (allocated (evt%instance)) then write (u, "(1x,A)") "Subprocess instances: allocated" else write (u, "(1x,A)") "Subprocess instances: not allocated" end if if (evt%particle_set_exists) then if (evt%selected_history > 0) then write (u, "(1x,A,I0)") "Selected: resonance history #", & evt%selected_history else write (u, "(1x,A)") "Selected: no resonance history" end if else write (u, "(1x,A)") "Selected: [none]" end if write (u, "(1x,A,1x," // FMT_12 // ")") & "On-shell limit =", evt%on_shell_limit write (u, "(1x,A,1x," // FMT_12 // ")") & "On-shell turnoff =", evt%on_shell_turnoff write (u, "(1x,A,1x," // FMT_12 // ")") & "Background factor =", evt%background_factor call write_separator (u) if (evt%selector_active) then write (u, "(2x)", advance="no") call evt%selector%write (u, testflag=testflag) call write_separator (u) end if call evt%base_write (u, testflag = testflag, show_set = .false.) call write_separator (u) if (evt%particle_set_exists) then call evt%particle_set%write & (u, summary = .true., compressed = .true., testflag = testflag) call write_separator (u) end if end subroutine evt_resonance_write @ %def evt_resonance_write @ \subsection{Set contained data} Insert the resonance data, in form of a pre-generated resonance history set. Accumulate the number of histories for each set, to initialize an array of index offsets for lookup. <>= procedure :: set_resonance_data => evt_resonance_set_resonance_data <>= module subroutine evt_resonance_set_resonance_data (evt, res_history_set) class(evt_resonance_t), intent(inout) :: evt type(resonance_history_set_t), dimension(:), intent(in) :: res_history_set end subroutine evt_resonance_set_resonance_data <>= module subroutine evt_resonance_set_resonance_data (evt, res_history_set) class(evt_resonance_t), intent(inout) :: evt type(resonance_history_set_t), dimension(:), intent(in) :: res_history_set integer :: i evt%res_history_set = res_history_set allocate (evt%index_offset (size (evt%res_history_set)), source = 0) do i = 2, size (evt%res_history_set) evt%index_offset(i) = & evt%index_offset(i-1) + evt%res_history_set(i-1)%get_n_history () end do end subroutine evt_resonance_set_resonance_data @ %def evt_resonance_set_resonance_data @ Set the library that contains the resonant subprocesses. <>= procedure :: set_library => evt_resonance_set_library <>= module subroutine evt_resonance_set_library (evt, libname) class(evt_resonance_t), intent(inout) :: evt type(string_t), intent(in) :: libname end subroutine evt_resonance_set_library <>= module subroutine evt_resonance_set_library (evt, libname) class(evt_resonance_t), intent(inout) :: evt type(string_t), intent(in) :: libname evt%libname = libname end subroutine evt_resonance_set_library @ %def evt_resonance_set_library @ Assign pointers to subprocess instances. Once a subprocess has been selected, the instance is used for generating the particle set with valid quantum-number assignments, ready for resonance insertion. <>= procedure :: set_subprocess_instances & => evt_resonance_set_subprocess_instances <>= module subroutine evt_resonance_set_subprocess_instances (evt, instance) class(evt_resonance_t), intent(inout) :: evt type(process_instance_ptr_t), dimension(:), intent(in) :: instance end subroutine evt_resonance_set_subprocess_instances <>= module subroutine evt_resonance_set_subprocess_instances (evt, instance) class(evt_resonance_t), intent(inout) :: evt type(process_instance_ptr_t), dimension(:), intent(in) :: instance evt%instance = instance end subroutine evt_resonance_set_subprocess_instances @ %def evt_resonance_set_subprocess_instances @ Set the on-shell limit, the relative distance from a resonance that is still considered to be on-shell. The probability for being considered on-shell can be reduced by the turnoff parameter below. For details, see the [[resonances]] module. <>= procedure :: set_on_shell_limit => evt_resonance_set_on_shell_limit <>= module subroutine evt_resonance_set_on_shell_limit (evt, on_shell_limit) class(evt_resonance_t), intent(inout) :: evt real(default), intent(in) :: on_shell_limit end subroutine evt_resonance_set_on_shell_limit <>= module subroutine evt_resonance_set_on_shell_limit (evt, on_shell_limit) class(evt_resonance_t), intent(inout) :: evt real(default), intent(in) :: on_shell_limit evt%on_shell_limit = on_shell_limit end subroutine evt_resonance_set_on_shell_limit @ %def evt_resonance_set_on_shell_limit @ Set the Gaussian on-shell turnoff parameter, the width of the weighting factor for the resonance squared matrix element. If the resonance is off shell, this factor reduces the weight of the matrix element in the selector, such that the probability for considered resonant is reduced. The factor is applied only if the offshellness is less than the [[on_shell_limit]] above. For details, see the [[resonances]] module. <>= procedure :: set_on_shell_turnoff => evt_resonance_set_on_shell_turnoff <>= module subroutine evt_resonance_set_on_shell_turnoff (evt, on_shell_turnoff) class(evt_resonance_t), intent(inout) :: evt real(default), intent(in) :: on_shell_turnoff end subroutine evt_resonance_set_on_shell_turnoff <>= module subroutine evt_resonance_set_on_shell_turnoff (evt, on_shell_turnoff) class(evt_resonance_t), intent(inout) :: evt real(default), intent(in) :: on_shell_turnoff evt%on_shell_turnoff = on_shell_turnoff end subroutine evt_resonance_set_on_shell_turnoff @ %def evt_resonance_set_on_shell_turnoff @ Reweight (suppress) the background contribution if there is a resonance history that applies. The event will be registered as background if there is no applicable resonance history, or if the background configuration has been selected based on (reweighted) squared matrix elements. <>= procedure :: set_background_factor => evt_resonance_set_background_factor <>= module subroutine evt_resonance_set_background_factor & (evt, background_factor) class(evt_resonance_t), intent(inout) :: evt real(default), intent(in) :: background_factor end subroutine evt_resonance_set_background_factor <>= module subroutine evt_resonance_set_background_factor (evt, background_factor) class(evt_resonance_t), intent(inout) :: evt real(default), intent(in) :: background_factor evt%background_factor = background_factor end subroutine evt_resonance_set_background_factor @ %def evt_resonance_set_background_factor @ \subsection{Selector} Manually import a random-number generator object. This should be done only for testing purposes. The standard procedure is to [[connect]] a process to an event transform; this will create an appropriate [[rng]] from the RNG factory in the process object. <>= procedure :: import_rng => evt_resonance_import_rng <>= module subroutine evt_resonance_import_rng (evt, rng) class(evt_resonance_t), intent(inout) :: evt class(rng_t), allocatable, intent(inout) :: rng end subroutine evt_resonance_import_rng <>= module subroutine evt_resonance_import_rng (evt, rng) class(evt_resonance_t), intent(inout) :: evt class(rng_t), allocatable, intent(inout) :: rng call move_alloc (from = rng, to = evt%rng) end subroutine evt_resonance_import_rng @ %def evt_resonance_import_rng @ We use a standard selector object to choose from the available resonance histories. If the selector is inactive, we do not insert resonances. <>= procedure :: write_selector => evt_resonance_write_selector <>= module subroutine evt_resonance_write_selector (evt, unit, testflag) class(evt_resonance_t), intent(in) :: evt integer, intent(in), optional :: unit logical, intent(in), optional :: testflag end subroutine evt_resonance_write_selector <>= module subroutine evt_resonance_write_selector (evt, unit, testflag) class(evt_resonance_t), intent(in) :: evt integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u u = given_output_unit (unit) if (evt%selector_active) then call evt%selector%write (u, testflag) else write (u, "(1x,A)") "Selector: [inactive]" end if end subroutine evt_resonance_write_selector @ %def evt_resonance_write_selector @ The selector is initialized with relative weights of histories which need not be normalized. Channels with weight zero are ignored. The [[offset]] will normally be $-1$, so we count from zero, and zero is a valid result from the selector. Selecting the zero entry implies no resonance insertion. However, this behavior is not hard-coded here (without offset, no resonance is not possible as a result). <>= procedure :: init_selector => evt_resonance_init_selector <>= module subroutine evt_resonance_init_selector (evt, weight, offset) class(evt_resonance_t), intent(inout) :: evt real(default), dimension(:), intent(in) :: weight integer, intent(in), optional :: offset end subroutine evt_resonance_init_selector <>= module subroutine evt_resonance_init_selector (evt, weight, offset) class(evt_resonance_t), intent(inout) :: evt real(default), dimension(:), intent(in) :: weight integer, intent(in), optional :: offset if (any (weight > 0)) then call evt%selector%init (weight, offset = offset) evt%selector_active = .true. else evt%selector_active = .false. end if end subroutine evt_resonance_init_selector @ %def evt_resonance_init_selector @ Return all selector weights, for inspection. Note that the index counts from zero. <>= procedure :: get_selector_weights => evt_resonance_get_selector_weights <>= module subroutine evt_resonance_get_selector_weights (evt, weight) class(evt_resonance_t), intent(in) :: evt real(default), dimension(0:), intent(out) :: weight end subroutine evt_resonance_get_selector_weights <>= module subroutine evt_resonance_get_selector_weights (evt, weight) class(evt_resonance_t), intent(in) :: evt real(default), dimension(0:), intent(out) :: weight integer :: i do i = 0, ubound (weight,1) weight(i) = evt%selector%get_weight (i) end do end subroutine evt_resonance_get_selector_weights @ %def evt_resonance_get_selector_weights @ \subsection{Runtime calculations} Use the associated master process instance and the subprocess instances to distribute the current momentum set, then compute the squared matrix elements weights for all subprocesses. NOTE: Procedures in this subsection are not covered by unit tests in this module, but by unit tests of the [[restricted_subprocesses]] module. Fill the particle set, so the momentum configuration can be used by the subprocess instances. The standard workflow is to copy from the previous particle set. <>= procedure :: fill_momenta => evt_resonance_fill_momenta <>= module subroutine evt_resonance_fill_momenta (evt) class(evt_resonance_t), intent(inout) :: evt end subroutine evt_resonance_fill_momenta <>= module subroutine evt_resonance_fill_momenta (evt) class(evt_resonance_t), intent(inout) :: evt integer :: i, n if (associated (evt%previous)) then evt%particle_set = evt%previous%particle_set else if (associated (evt%process_instance)) then ! this branch only for unit test call evt%process_instance%get_trace & (evt%particle_set, i_term=1, n_incoming=evt%process%get_n_in ()) end if end subroutine evt_resonance_fill_momenta @ %def evt_resonance_fill_momenta @ Return the indices of those subprocesses which can be considered on-shell. The result depends on the stored particle set (outgoing momenta) and on the on-shell limit value. The index [[evt%selected_component]] identifies the particular history set that corresponds to the given process component. Recall that process components may have different external particles, so they have distinct history sets. <>= procedure :: determine_on_shell_histories & => evt_resonance_determine_on_shell_histories <>= module subroutine evt_resonance_determine_on_shell_histories & (evt, index_array) class(evt_resonance_t), intent(in) :: evt integer, dimension(:), allocatable, intent(out) :: index_array end subroutine evt_resonance_determine_on_shell_histories <>= module subroutine evt_resonance_determine_on_shell_histories & (evt, index_array) class(evt_resonance_t), intent(in) :: evt integer, dimension(:), allocatable, intent(out) :: index_array integer :: i i = evt%selected_component call evt%res_history_set(i)%determine_on_shell_histories & (evt%particle_set%get_outgoing_momenta (), & evt%on_shell_limit, & index_array) end subroutine evt_resonance_determine_on_shell_histories @ %def evt_resonance_determine_on_shell_histories @ Evaluate selected subprocesses. (In actual operation, the ones that have been tagged as on-shell.) We assume that the MCI, term, and channel indices for the subprocesses can all be set to 1. <>= procedure :: evaluate_subprocess => evt_resonance_evaluate_subprocess <>= module subroutine evt_resonance_evaluate_subprocess (evt, index_array) class(evt_resonance_t), intent(inout) :: evt integer, dimension(:), intent(in) :: index_array end subroutine evt_resonance_evaluate_subprocess <>= module subroutine evt_resonance_evaluate_subprocess (evt, index_array) class(evt_resonance_t), intent(inout) :: evt integer, dimension(:), intent(in) :: index_array integer :: k, i if (allocated (evt%instance)) then do k = 1, size (index_array) i = index_array(k) associate (instance => evt%instance(i)%p) call instance%choose_mci (1) call instance%set_trace (evt%particle_set, 1, check_match=.false.) call instance%recover (channel = 1, i_term = 1, & update_sqme = .true., recover_phs = .false.) end associate end do end if end subroutine evt_resonance_evaluate_subprocess @ %def evt_resonance_evaluate_subprocess @ Return the current squared matrix-element value of the master process, and of the selected resonant subprocesses, respectively. <>= procedure :: get_master_sqme => evt_resonance_get_master_sqme procedure :: get_subprocess_sqme => evt_resonance_get_subprocess_sqme <>= module function evt_resonance_get_master_sqme (evt) result (sqme) class(evt_resonance_t), intent(in) :: evt real(default) :: sqme end function evt_resonance_get_master_sqme module subroutine evt_resonance_get_subprocess_sqme (evt, sqme, index_array) class(evt_resonance_t), intent(in) :: evt real(default), dimension(:), intent(out) :: sqme integer, dimension(:), intent(in), optional :: index_array end subroutine evt_resonance_get_subprocess_sqme <>= module function evt_resonance_get_master_sqme (evt) result (sqme) class(evt_resonance_t), intent(in) :: evt real(default) :: sqme sqme = evt%process_instance%get_sqme () end function evt_resonance_get_master_sqme module subroutine evt_resonance_get_subprocess_sqme (evt, sqme, index_array) class(evt_resonance_t), intent(in) :: evt real(default), dimension(:), intent(out) :: sqme integer, dimension(:), intent(in), optional :: index_array integer :: k, i if (present (index_array)) then sqme = 0 do k = 1, size (index_array) call get_sqme (index_array(k)) end do else do i = 1, size (evt%instance) call get_sqme (i) end do end if contains subroutine get_sqme (i) integer, intent(in) :: i associate (instance => evt%instance(i)%p) sqme(i) = instance%get_sqme () end associate end subroutine get_sqme end subroutine evt_resonance_get_subprocess_sqme @ %def evt_resonance_get_master_sqme @ %def evt_resonance_get_subprocess_sqme @ Apply a turnoff factor for off-shell kinematics to the [[sqme]] values. The [[sqme]] array indices are offset from the resonance history set entries. <>= procedure :: apply_turnoff_factor => evt_resonance_apply_turnoff_factor <>= module subroutine evt_resonance_apply_turnoff_factor & (evt, sqme, index_array) class(evt_resonance_t), intent(in) :: evt real(default), dimension(:), intent(inout) :: sqme integer, dimension(:), intent(in) :: index_array end subroutine evt_resonance_apply_turnoff_factor <>= module subroutine evt_resonance_apply_turnoff_factor (evt, sqme, index_array) class(evt_resonance_t), intent(in) :: evt real(default), dimension(:), intent(inout) :: sqme integer, dimension(:), intent(in) :: index_array integer :: k, i_res, i_prc do k = 1, size (index_array) i_res = evt%selected_component i_prc = index_array(k) + evt%index_offset(i_res) sqme(i_prc) = sqme(i_prc) & * evt%res_history_set(i_res)%evaluate_gaussian & & (evt%particle_set%get_outgoing_momenta (), & & evt%on_shell_turnoff, index_array(k)) end do end subroutine evt_resonance_apply_turnoff_factor @ %def evt_resonance_apply_turnoff_factor @ We use the calculations of resonant matrix elements to determine probabilities for all applicable resonance configurations. This method combines the steps implemented above. First, we determine the selected process component. TODO: the version below selects the first component which is found active. This make sense only for standard LO process components, where exactly one component corresponds to a MCI set. For the selected process component, we query the kinematics and determine the applicable resonance histories. We collect squared matrix elements for those resonance histories and compare them to the master-process squared matrix element. The result is the probability for each resonance history together with the probability for non-resonant background (zeroth entry). The latter is defined as the difference between the complete process result and the sum of the resonances, ignoring the possibility for interference. If the complete process result is actually undershooting the sum of resonances, we nevertheless count the background with positive probability. When looking up the subprocess sqme, we must add the [[index_offset]] to the resulting array, since the indices returned by the individual history set all count from one, while the subprocess instances that belong to process components are collected in one flat array. After determining matrix elements and background, we may reduce the weight of the matrix elements in the selector by applying a turnoff factor. The factor [[background_factor]] indicates whether to include the background contribution at all, as long as there is a nonvanishing resonance contribution. Note that instead of setting background to zero, we just multiply it by a very small number. This ensures that indices are assigned correctly, and that background will eventually be selected if smooth turnoff is chosen. <>= procedure :: compute_probabilities => evt_resonance_compute_probabilities <>= module subroutine evt_resonance_compute_probabilities (evt) class(evt_resonance_t), intent(inout) :: evt end subroutine evt_resonance_compute_probabilities <>= module subroutine evt_resonance_compute_probabilities (evt) class(evt_resonance_t), intent(inout) :: evt integer, dimension(:), allocatable :: index_array real(default) :: sqme_master, sqme_sum, sqme_bg real(default), dimension(:), allocatable :: sqme_res integer :: n, ic if (.not. associated (evt%process_instance)) return n = size (evt%instance) call evt%select_component (0) FIND_ACTIVE_COMPONENT: do ic = 1, evt%process%get_n_components () if (evt%process%component_is_selected (ic)) then call evt%select_component (ic) exit FIND_ACTIVE_COMPONENT end if end do FIND_ACTIVE_COMPONENT if (evt%selected_component > 0) then call evt%determine_on_shell_histories (index_array) else allocate (index_array (0)) end if call evt%evaluate_subprocess & (index_array + evt%index_offset(evt%selected_component)) allocate (sqme_res (n), source = 0._default) call evt%get_subprocess_sqme & (sqme_res, index_array + evt%index_offset(evt%selected_component)) sqme_master = evt%get_master_sqme () sqme_sum = sum (sqme_res) sqme_bg = abs (sqme_master - sqme_sum) if (evt%on_shell_turnoff > 0) then call evt%apply_turnoff_factor (sqme_res, index_array) end if if (any (sqme_res > 0)) then sqme_bg = sqme_bg * evt%background_factor end if call evt%init_selector ([sqme_bg, sqme_res], offset = -1) end subroutine evt_resonance_compute_probabilities @ %def evt_resonance_compute_probabilities @ Set the selected component (unit tests). <>= procedure :: select_component => evt_resonance_select_component <>= module subroutine evt_resonance_select_component (evt, i_component) class(evt_resonance_t), intent(inout) :: evt integer, intent(in) :: i_component end subroutine evt_resonance_select_component <>= module subroutine evt_resonance_select_component (evt, i_component) class(evt_resonance_t), intent(inout) :: evt integer, intent(in) :: i_component evt%selected_component = i_component end subroutine evt_resonance_select_component @ %def evt_resonance_select_component @ \subsection{Sanity check} Check the color assignment, which may be wrong for the inserted resonances. Delegated to the particle-set component. Return offending particle indices and, optionally, particles as arrays. This is done in a unit test. The current algorithm, i.e., selecting the color assignment from the resonant-subprocess instance, should not generate invalid color assignments. <>= procedure :: find_prt_invalid_color => evt_resonance_find_prt_invalid_color <>= module subroutine evt_resonance_find_prt_invalid_color (evt, index, prt) class(evt_resonance_t), intent(in) :: evt integer, dimension(:), allocatable, intent(out) :: index type(particle_t), dimension(:), allocatable, intent(out), optional :: prt end subroutine evt_resonance_find_prt_invalid_color <>= module subroutine evt_resonance_find_prt_invalid_color (evt, index, prt) class(evt_resonance_t), intent(in) :: evt integer, dimension(:), allocatable, intent(out) :: index type(particle_t), dimension(:), allocatable, intent(out), optional :: prt if (evt%particle_set_exists) then call evt%particle_set%find_prt_invalid_color (index, prt) else allocate (prt (0)) end if end subroutine evt_resonance_find_prt_invalid_color @ %def evt_resonance_find_prt_invalid_color @ \subsection{API implementation} <>= procedure :: prepare_new_event => evt_resonance_prepare_new_event <>= module subroutine evt_resonance_prepare_new_event (evt, i_mci, i_term) class(evt_resonance_t), intent(inout) :: evt integer, intent(in) :: i_mci, i_term end subroutine evt_resonance_prepare_new_event <>= module subroutine evt_resonance_prepare_new_event (evt, i_mci, i_term) class(evt_resonance_t), intent(inout) :: evt integer, intent(in) :: i_mci, i_term call evt%reset () end subroutine evt_resonance_prepare_new_event @ %def evt_resonance_prepare_new_event @ Select one of the histories, based on the momentum array from the current particle set. Compute the probabilities for all resonant subprocesses and initialize the selector accordingly. Then select one resonance history, or none. <>= procedure :: generate_weighted => evt_resonance_generate_weighted <>= module subroutine evt_resonance_generate_weighted (evt, probability) class(evt_resonance_t), intent(inout) :: evt real(default), intent(inout) :: probability end subroutine evt_resonance_generate_weighted <>= module subroutine evt_resonance_generate_weighted (evt, probability) class(evt_resonance_t), intent(inout) :: evt real(default), intent(inout) :: probability call evt%fill_momenta () call evt%compute_probabilities () call evt%selector%generate (evt%rng, evt%selected_history) probability = 1 end subroutine evt_resonance_generate_weighted @ %def evt_resonance_generate_weighted @ Here take the current particle set and insert resonance intermediate states if applicable. The resonance history has already been chosen by the generator above. If no resonance history applies, just retain the particle set. If a resonance history applies, we factorize the exclusive interaction of the selected (resonance-process) process instance. With a temporary particle set [[prt_set]] as workspace, we the insert the resonances, reinstate parent-child relations and set colors and momenta for the resonances. The temporary is then copied back. Taking the event data from the resonant subprocess instead of the master process, guarantees that all flavor, helicity, and color assignments are valid for the selected resonance history. Note that the transform may thus choose a quantum-number combination that is different from the one chosen by the master process. The [[i_term]] value for the selected subprocess instance is always 1. We support only LO process. For those, the master process may have several terms (= components) that correspond to different external states. The subprocesses are distinct, each one corresponds to a definite master component, and by itself it consists of a single component/term. However, if the selector chooses resonance history \#0, i.e., no resonance, we just copy the particle set from the previous (i.e., trivial) event transform and ignore all subprocess data. <>= procedure :: make_particle_set => evt_resonance_make_particle_set <>= module subroutine evt_resonance_make_particle_set & (evt, factorization_mode, keep_correlations, r) class(evt_resonance_t), intent(inout) :: evt integer, intent(in) :: factorization_mode logical, intent(in) :: keep_correlations real(default), dimension(:), intent(in), optional :: r end subroutine evt_resonance_make_particle_set <>= module subroutine evt_resonance_make_particle_set & (evt, factorization_mode, keep_correlations, r) class(evt_resonance_t), intent(inout) :: evt integer, intent(in) :: factorization_mode logical, intent(in) :: keep_correlations real(default), dimension(:), intent(in), optional :: r type(particle_set_t), target :: prt_set type(particle_t), dimension(:), allocatable :: prt integer :: n_beam, n_in, n_vir, n_res, n_out, i, i_res, i_term, i_tree type(interaction_t), pointer :: int_matrix, int_flows integer, dimension(:), allocatable :: map type(resonance_tree_t) :: res_tree if (associated (evt%previous)) then if (evt%previous%particle_set_exists) then if (evt%selected_history > 0) then if (allocated (evt%instance)) then associate (instance => evt%instance(evt%selected_history)%p) call instance%evaluate_event_data (weight = 1._default) i_term = 1 int_matrix => instance%get_matrix_int_ptr (i_term) int_flows => instance%get_flows_int_ptr (i_term) call evt%factorize_interactions (int_matrix, int_flows, & factorization_mode, keep_correlations, r) call evt%tag_incoming () end associate else ! this branch only for unit test evt%particle_set = evt%previous%particle_set end if i_tree = evt%selected_history & - evt%index_offset(evt%selected_component) call evt%res_history_set(evt%selected_component)%get_tree & (i_tree, res_tree) n_beam = evt%particle_set%get_n_beam () n_in = evt%particle_set%get_n_in () n_vir = evt%particle_set%get_n_vir () n_out = evt%particle_set%get_n_out () n_res = res_tree%get_n_resonances () allocate (map (n_beam + n_in + n_vir + n_out)) map(1:n_beam+n_in+n_vir) & = [(i, i = 1, n_beam+n_in+n_vir)] map(n_beam+n_in+n_vir+1:n_beam+n_in+n_vir+n_out) & = [(i + n_res, & & i = n_beam+n_in+n_vir+1, & & n_beam+n_in+n_vir+n_out)] call prt_set%transfer (evt%particle_set, n_res, map) do i = 1, n_res i_res = n_beam + n_in + n_vir + i call prt_set%insert (i_res, & PRT_RESONANT, & res_tree%get_flv (i), & res_tree%get_children (i, & & n_beam+n_in+n_vir, n_beam+n_in+n_vir+n_res)) end do do i = n_res, 1, -1 i_res = n_beam + n_in + n_vir + i call prt_set%recover_color (i_res) end do call prt_set%set_momentum & (map(:), evt%particle_set%get_momenta (), on_shell = .true.) do i = n_res, 1, -1 i_res = n_beam + n_in + n_vir + i call prt_set%recover_momentum (i_res) end do call evt%particle_set%final () evt%particle_set = prt_set call prt_set%final () evt%particle_set_exists = .true. else ! retain particle set, as copied from previous evt evt%particle_set_exists = .true. end if else evt%particle_set_exists = .false. end if else evt%particle_set_exists = .false. end if end subroutine evt_resonance_make_particle_set @ %def event_resonance_make_particle_set @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[resonance_insertion_ut.f90]]>>= <> module resonance_insertion_ut use unit_tests use resonance_insertion_uti <> <> contains <> end module resonance_insertion_ut @ %def resonance_insertion_ut @ <<[[resonance_insertion_uti.f90]]>>= <> module resonance_insertion_uti <> <> use format_utils, only: write_separator use os_interface use lorentz use rng_base, only: rng_t use flavors, only: flavor_t use colors, only: color_t use models, only: syntax_model_file_init, syntax_model_file_final use models, only: model_list_t, model_t use particles, only: particle_t, particle_set_t use resonances, only: resonance_info_t use resonances, only: resonance_history_t use resonances, only: resonance_history_set_t use event_transforms use resonance_insertion use rng_base_ut, only: rng_test_t <> <> contains <> end module resonance_insertion_uti @ %def resonance_insertion_uti @ API: driver for the unit tests below. <>= public :: resonance_insertion_test <>= subroutine resonance_insertion_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine resonance_insertion_test @ %def resonance_insertion_test @ \subsubsection{Test resonance insertion as event transform} Insert a resonance (W boson) into an event with momentum assignment. <>= call test (resonance_insertion_1, "resonance_insertion_1", & "simple resonance insertion", & u, results) <>= public :: resonance_insertion_1 <>= subroutine resonance_insertion_1 (u) integer, intent(in) :: u type(os_data_t) :: os_data type(particle_set_t) :: pset type(model_list_t) :: model_list type(model_t), pointer :: model type(resonance_info_t) :: res_info type(resonance_history_t) :: res_history type(resonance_history_set_t), dimension(1) :: res_history_set type(evt_trivial_t), target :: evt_trivial type(evt_resonance_t), target :: evt_resonance type(flavor_t) :: fw type(color_t) :: col real(default) :: mw, ew, pw type(vector4_t), dimension(5) :: p class(rng_t), allocatable :: rng real(default) :: probability integer, dimension(:), allocatable :: i_invalid type(particle_t), dimension(:), allocatable :: prt_invalid integer :: i write (u, "(A)") "* Test output: resonance_insertion_1" write (u, "(A)") "* Purpose: apply simple resonance insertion" write (u, "(A)") write (u, "(A)") "* Initialize environment" write (u, "(A)") call syntax_model_file_init () call os_data%init () call model_list%read_model & (var_str ("SM"), var_str ("SM.mdl"), & os_data, model) ! reset slightly in order to avoid a rounding ambiguity call model%set_real (var_str ("mW"), 80.418_default) write (u, "(A)") "* Initialize particle set" write (u, "(A)") call pset%init_direct (n_beam = 0, n_in = 2, n_rem = 0, n_vir = 0, n_out = 3, & pdg = [1, -1, 1, -2, 24], model = model) call fw%init (24, model) mw = fw%get_mass () ew = 200._default pw = sqrt (ew**2 - mw**2) p(1) = vector4_moving (ew, ew, 3) p(2) = vector4_moving (ew,-ew, 3) p(3) = vector4_moving (ew/2, vector3_moving ([pw/2, mw/2, 0._default])) p(4) = vector4_moving (ew/2, vector3_moving ([pw/2,-mw/2, 0._default])) p(5) = vector4_moving (ew, vector3_moving ([-pw, 0._default, 0._default])) call pset%set_momentum (p, on_shell = .true.) call col%init_col_acl (1,0) call pset%set_color (1, col) call col%init_col_acl (0,1) call pset%set_color (2, col) call col%init_col_acl (2,0) call pset%set_color (3, col) call col%init_col_acl (0,2) call pset%set_color (4, col) call col%init_col_acl (0,0) call pset%set_color (5, col) write (u, "(A)") "* Fill trivial event transform" write (u, "(A)") call evt_trivial%reset () call evt_trivial%set_particle_set (pset, 1, 1) call evt_trivial%write (u) call write_separator (u, 2) write (u, "(A)") write (u, "(A)") "* Prepare resonance history set" write (u, "(A)") call res_history_set(1)%init () call res_info%init (3, -24, model, 2) call res_history%add_resonance (res_info) call res_history_set(1)%enter (res_history) call res_history%clear () call res_history_set(1)%freeze () write (u, "(A)") "* Initialize resonance insertion transform" write (u, "(A)") evt_trivial%next => evt_resonance evt_resonance%previous => evt_trivial allocate (rng_test_t :: rng) call evt_resonance%import_rng (rng) call evt_resonance%set_resonance_data (res_history_set) call evt_resonance%select_component (1) call evt_resonance%write (u) write (u, "(A)") write (u, "(A)") "* Fill resonance insertion transform" write (u, "(A)") call evt_resonance%prepare_new_event (1, 1) call evt_resonance%init_selector ([1._default]) call evt_resonance%generate_weighted (probability) call evt_resonance%make_particle_set (0, .false.) call evt_resonance%write (u) write (u, "(A)") write (u, "(A,1x,F8.5)") "Event probability =", probability write (u, "(A)") call evt_resonance%find_prt_invalid_color (i_invalid, prt_invalid) write (u, "(A)") "Particles with invalid color:" select case (size (prt_invalid)) case (0) write (u, "(2x,A)") "[none]" case default do i = 1, size (prt_invalid) write (u, "(1x,A,1x,I0)", advance="no") "Particle", i_invalid(i) call prt_invalid(i)%write (u) end do end select write (u, "(A)") write (u, "(A)") "* Cleanup" call evt_resonance%final () call evt_trivial%final () call syntax_model_file_final () write (u, "(A)") write (u, "(A)") "* Test output end: resonance_insertion_1" end subroutine resonance_insertion_1 @ %def resonance_insertion_1 @ \subsubsection{Resonance insertion with color mismatch} Same as previous test (but no momenta); resonance insertion should fail because of color mismatch: W boson is color-neutral. <>= call test (resonance_insertion_2, "resonance_insertion_2", & "resonance color mismatch", & u, results) <>= public :: resonance_insertion_2 <>= subroutine resonance_insertion_2 (u) integer, intent(in) :: u type(os_data_t) :: os_data type(particle_set_t) :: pset type(model_list_t) :: model_list type(model_t), pointer :: model type(resonance_info_t) :: res_info type(resonance_history_t) :: res_history type(resonance_history_set_t), dimension(1) :: res_history_set type(evt_trivial_t), target :: evt_trivial type(evt_resonance_t), target :: evt_resonance type(color_t) :: col class(rng_t), allocatable :: rng real(default) :: probability type(particle_t), dimension(:), allocatable :: prt_invalid integer, dimension(:), allocatable :: i_invalid integer :: i write (u, "(A)") "* Test output: resonance_insertion_2" write (u, "(A)") "* Purpose: resonance insertion with color mismatch" write (u, "(A)") write (u, "(A)") "* Initialize environment" write (u, "(A)") call syntax_model_file_init () call os_data%init () call model_list%read_model & (var_str ("SM"), var_str ("SM.mdl"), & os_data, model) write (u, "(A)") "* Initialize particle set" write (u, "(A)") call pset%init_direct (n_beam = 0, n_in = 2, n_rem = 0, n_vir = 0, n_out = 3, & pdg = [1, -1, 1, -2, 24], model = model) call col%init_col_acl (1,0) call pset%set_color (1, col) call col%init_col_acl (0,2) call pset%set_color (2, col) call col%init_col_acl (1,0) call pset%set_color (3, col) call col%init_col_acl (0,2) call pset%set_color (4, col) call col%init_col_acl (0,0) call pset%set_color (5, col) write (u, "(A)") "* Fill trivial event transform" write (u, "(A)") call evt_trivial%reset () call evt_trivial%set_particle_set (pset, 1, 1) call evt_trivial%write (u) call write_separator (u, 2) write (u, "(A)") write (u, "(A)") "* Prepare resonance history set" write (u, "(A)") call res_history_set(1)%init () call res_info%init (3, -24, model, 2) call res_history%add_resonance (res_info) call res_history_set(1)%enter (res_history) call res_history%clear () call res_history_set(1)%freeze () write (u, "(A)") "* Initialize resonance insertion transform" write (u, "(A)") evt_trivial%next => evt_resonance evt_resonance%previous => evt_trivial allocate (rng_test_t :: rng) call evt_resonance%import_rng (rng) call evt_resonance%set_resonance_data (res_history_set) call evt_resonance%select_component (1) call evt_resonance%write (u) write (u, "(A)") write (u, "(A)") "* Fill resonance insertion transform" write (u, "(A)") call evt_resonance%prepare_new_event (1, 1) call evt_resonance%init_selector ([1._default]) call evt_resonance%generate_weighted (probability) call evt_resonance%make_particle_set (0, .false.) call evt_resonance%write (u) write (u, "(A)") write (u, "(A,1x,F8.5)") "Event probability =", probability write (u, "(A)") call evt_resonance%find_prt_invalid_color (i_invalid, prt_invalid) write (u, "(A)") "Particles with invalid color:" select case (size (prt_invalid)) case (0) write (u, "(2x,A)") "[none]" case default do i = 1, size (prt_invalid) write (u, "(1x,A,1x,I0)", advance="no") "Particle", i_invalid(i) call prt_invalid(i)%write (u) end do end select write (u, "(A)") write (u, "(A)") "* Cleanup" call evt_resonance%final () call evt_trivial%final () call syntax_model_file_final () write (u, "(A)") write (u, "(A)") "* Test output end: resonance_insertion_2" end subroutine resonance_insertion_2 @ %def resonance_insertion_2 @ \subsubsection{Complex resonance history} This is the resonance history $u\bar u \to (t\to W^+ b) + (\bar t\to (h \to b\bar b) + (\bar t^\ast \to W^-\bar b))$. <>= call test (resonance_insertion_3, "resonance_insertion_3", & "complex resonance history", & u, results) <>= public :: resonance_insertion_3 <>= subroutine resonance_insertion_3 (u) integer, intent(in) :: u type(os_data_t) :: os_data type(particle_set_t) :: pset type(model_list_t) :: model_list type(model_t), pointer :: model type(resonance_info_t) :: res_info type(resonance_history_t) :: res_history type(resonance_history_set_t), dimension(1) :: res_history_set type(evt_trivial_t), target :: evt_trivial type(evt_resonance_t), target :: evt_resonance type(color_t) :: col class(rng_t), allocatable :: rng real(default) :: probability type(particle_t), dimension(:), allocatable :: prt_invalid integer, dimension(:), allocatable :: i_invalid integer :: i write (u, "(A)") "* Test output: resonance_insertion_3" write (u, "(A)") "* Purpose: resonance insertion with color mismatch" write (u, "(A)") write (u, "(A)") "* Initialize environment" write (u, "(A)") call syntax_model_file_init () call os_data%init () call model_list%read_model & (var_str ("SM"), var_str ("SM.mdl"), & os_data, model) write (u, "(A)") "* Initialize particle set" write (u, "(A)") call pset%init_direct (n_beam = 0, n_in = 2, n_rem = 0, n_vir = 0, n_out = 6, & pdg = [2, -2, 24, 5, 5, -5, -24, -5], model = model) call col%init_col_acl (1,0) call pset%set_color (1, col) call col%init_col_acl (0,2) call pset%set_color (2, col) call col%init_col_acl (0,0) call pset%set_color (3, col) call col%init_col_acl (1,0) call pset%set_color (4, col) call col%init_col_acl (3,0) call pset%set_color (5, col) call col%init_col_acl (0,3) call pset%set_color (6, col) call col%init_col_acl (0,0) call pset%set_color (7, col) call col%init_col_acl (0,2) call pset%set_color (8, col) write (u, "(A)") "* Fill trivial event transform" write (u, "(A)") call evt_trivial%reset () call evt_trivial%set_particle_set (pset, 1, 1) call evt_trivial%write (u) call write_separator (u, 2) write (u, "(A)") write (u, "(A)") "* Prepare resonance history set" write (u, "(A)") call res_history_set(1)%init () call res_info%init (3, 6, model, 6) call res_history%add_resonance (res_info) call res_info%init (12, 25, model, 6) call res_history%add_resonance (res_info) call res_info%init (60, -6, model, 6) call res_history%add_resonance (res_info) call res_history_set(1)%enter (res_history) call res_history%clear () call res_history_set(1)%freeze () write (u, "(A)") "* Initialize resonance insertion transform" write (u, "(A)") evt_trivial%next => evt_resonance evt_resonance%previous => evt_trivial allocate (rng_test_t :: rng) call evt_resonance%import_rng (rng) call evt_resonance%set_resonance_data (res_history_set) call evt_resonance%select_component (1) call evt_resonance%write (u) write (u, "(A)") write (u, "(A)") "* Fill resonance insertion transform" write (u, "(A)") call evt_resonance%prepare_new_event (1, 1) call evt_resonance%init_selector ([1._default]) call evt_resonance%generate_weighted (probability) call evt_resonance%make_particle_set (0, .false.) call evt_resonance%write (u) write (u, "(A)") call evt_resonance%find_prt_invalid_color (i_invalid, prt_invalid) write (u, "(A)") "Particles with invalid color:" select case (size (prt_invalid)) case (0) write (u, "(2x,A)") "[none]" case default do i = 1, size (prt_invalid) write (u, "(1x,A,1x,I0)", advance="no") "Particle", i_invalid(i) call prt_invalid(i)%write (u) end do end select write (u, "(A)") write (u, "(A)") "* Cleanup" call evt_resonance%final () call evt_trivial%final () call syntax_model_file_final () write (u, "(A)") write (u, "(A)") "* Test output end: resonance_insertion_3" end subroutine resonance_insertion_3 @ %def resonance_insertion_3 @ \subsubsection{Resonance history selection} Another test with zero momenta: select one of several resonant channels using the selector component. <>= call test (resonance_insertion_4, "resonance_insertion_4", & "resonance history selection", & u, results) <>= public :: resonance_insertion_4 <>= subroutine resonance_insertion_4 (u) integer, intent(in) :: u type(os_data_t) :: os_data type(particle_set_t) :: pset type(model_list_t) :: model_list type(model_t), pointer :: model type(resonance_info_t) :: res_info type(resonance_history_t) :: res_history type(resonance_history_set_t), dimension(1) :: res_history_set type(evt_trivial_t), target :: evt_trivial type(evt_resonance_t), target :: evt_resonance type(color_t) :: col class(rng_t), allocatable :: rng real(default) :: probability integer :: i write (u, "(A)") "* Test output: resonance_insertion_4" write (u, "(A)") "* Purpose: resonance history selection" write (u, "(A)") write (u, "(A)") "* Initialize environment" write (u, "(A)") call syntax_model_file_init () call os_data%init () call model_list%read_model & (var_str ("SM"), var_str ("SM.mdl"), & os_data, model) write (u, "(A)") "* Initialize particle set" write (u, "(A)") call pset%init_direct (n_beam = 0, n_in = 2, n_rem = 0, n_vir = 0, n_out = 4, & pdg = [1, -1, 1, -2, -3, 4], model = model) write (u, "(A)") "* Fill trivial event transform" write (u, "(A)") call evt_trivial%reset () call evt_trivial%set_particle_set (pset, 1, 1) call evt_trivial%write (u) call write_separator (u, 2) write (u, "(A)") write (u, "(A)") "* Prepare resonance history set" write (u, "(A)") call res_history_set(1)%init () call res_info%init (3, -24, model, 4) call res_history%add_resonance (res_info) call res_history_set(1)%enter (res_history) call res_history%clear () call res_info%init (12, 24, model, 4) call res_history%add_resonance (res_info) call res_history_set(1)%enter (res_history) call res_history%clear () call res_info%init (12, 24, model, 4) call res_history%add_resonance (res_info) call res_info%init (15, 25, model, 4) call res_history%add_resonance (res_info) call res_history_set(1)%enter (res_history) call res_history%clear () call res_history_set(1)%freeze () write (u, "(A)") "* Initialize resonance insertion transform" write (u, "(A)") evt_trivial%next => evt_resonance evt_resonance%previous => evt_trivial allocate (rng_test_t :: rng) call evt_resonance%import_rng (rng) call evt_resonance%set_resonance_data (res_history_set) call evt_resonance%select_component (1) call evt_resonance%write (u) write (u, "(A)") write (u, "(A)") "* Fill resonance insertion transform" write (u, "(A)") do i = 1, 6 write (u, "(A,1x,I0)") "* Event #", i write (u, "(A)") call evt_resonance%prepare_new_event (1, 1) call evt_resonance%init_selector ([1._default, 2._default, 1._default]) call evt_resonance%generate_weighted (probability) call evt_resonance%make_particle_set (0, .false.) call evt_resonance%write (u) write (u, "(A)") end do write (u, "(A)") write (u, "(A)") "* Cleanup" call evt_resonance%final () call evt_trivial%final () call syntax_model_file_final () write (u, "(A)") write (u, "(A)") "* Test output end: resonance_insertion_4" end subroutine resonance_insertion_4 @ %def resonance_insertion_4 @ \subsubsection{Resonance history selection} Another test with zero momenta: select either a resonant channel or no resonance. <>= call test (resonance_insertion_5, "resonance_insertion_5", & "resonance history on/off", & u, results) <>= public :: resonance_insertion_5 <>= subroutine resonance_insertion_5 (u) integer, intent(in) :: u type(os_data_t) :: os_data type(particle_set_t) :: pset type(model_list_t) :: model_list type(model_t), pointer :: model type(resonance_info_t) :: res_info type(resonance_history_t) :: res_history type(resonance_history_set_t), dimension(1) :: res_history_set type(evt_trivial_t), target :: evt_trivial type(evt_resonance_t), target :: evt_resonance type(color_t) :: col class(rng_t), allocatable :: rng real(default) :: probability integer :: i write (u, "(A)") "* Test output: resonance_insertion_5" write (u, "(A)") "* Purpose: resonance history selection including no resonance" write (u, "(A)") write (u, "(A)") "* Initialize environment" write (u, "(A)") call syntax_model_file_init () call os_data%init () call model_list%read_model & (var_str ("SM"), var_str ("SM.mdl"), & os_data, model) write (u, "(A)") "* Initialize particle set" write (u, "(A)") call pset%init_direct (n_beam = 0, n_in = 2, n_rem = 0, n_vir = 0, n_out = 4, & pdg = [1, -1, 1, -2, -3, 4], model = model) write (u, "(A)") "* Fill trivial event transform" write (u, "(A)") call evt_trivial%reset () call evt_trivial%set_particle_set (pset, 1, 1) write (u, "(A)") "* Prepare resonance history set" write (u, "(A)") call res_history_set(1)%init () call res_info%init (3, -24, model, 4) call res_history%add_resonance (res_info) call res_history_set(1)%enter (res_history) call res_history%clear () call res_history_set(1)%freeze () write (u, "(A)") "* Initialize resonance insertion transform" write (u, "(A)") evt_trivial%next => evt_resonance evt_resonance%previous => evt_trivial allocate (rng_test_t :: rng) call evt_resonance%import_rng (rng) call evt_resonance%set_resonance_data (res_history_set) call evt_resonance%select_component (1) write (u, "(A)") "* Fill resonance insertion transform" write (u, "(A)") do i = 1, 2 write (u, "(A,1x,I0)") "* Event #", i write (u, "(A)") call evt_resonance%prepare_new_event (1, 1) call evt_resonance%init_selector ([1._default, 3._default], offset = -1) call evt_resonance%generate_weighted (probability) call evt_resonance%make_particle_set (0, .false.) call evt_resonance%write (u) write (u, "(A)") end do write (u, "(A)") write (u, "(A)") "* Cleanup" call evt_resonance%final () call evt_trivial%final () call syntax_model_file_final () write (u, "(A)") write (u, "(A)") "* Test output end: resonance_insertion_5" end subroutine resonance_insertion_5 @ %def resonance_insertion_5 @ \subsubsection{Resonance insertion with structured beams} Insert a resonance (W boson) into an event with beam and virtual particles. <>= call test (resonance_insertion_6, "resonance_insertion_6", & "resonance insertion with beam structure", & u, results) <>= public :: resonance_insertion_6 <>= subroutine resonance_insertion_6 (u) integer, intent(in) :: u type(os_data_t) :: os_data type(model_list_t) :: model_list type(particle_set_t) :: pset type(model_t), pointer :: model type(resonance_info_t) :: res_info type(resonance_history_t) :: res_history type(resonance_history_set_t), dimension(1) :: res_history_set type(evt_trivial_t), target :: evt_trivial type(evt_resonance_t), target :: evt_resonance class(rng_t), allocatable :: rng real(default) :: probability write (u, "(A)") "* Test output: resonance_insertion_6" write (u, "(A)") "* Purpose: resonance insertion with structured beams" write (u, "(A)") write (u, "(A)") "* Initialize environment" write (u, "(A)") call syntax_model_file_init () call os_data%init () call model_list%read_model & (var_str ("SM"), var_str ("SM.mdl"), & os_data, model) write (u, "(A)") "* Initialize particle set" write (u, "(A)") call pset%init_direct (n_beam = 2, n_in = 2, n_rem = 2, n_vir = 0, n_out = 2, & pdg = [11, -11, 11, -11, 22, 22, 13, -13], model = model) write (u, "(A)") "* Fill trivial event transform" write (u, "(A)") call evt_trivial%reset () call evt_trivial%set_particle_set (pset, 1, 1) call evt_trivial%write (u) call write_separator (u, 2) write (u, "(A)") write (u, "(A)") "* Prepare resonance history set" write (u, "(A)") call res_history_set(1)%init () call res_info%init (3, 23, model, 2) call res_history%add_resonance (res_info) call res_history_set(1)%enter (res_history) call res_history%clear () call res_history_set(1)%freeze () write (u, "(A)") "* Initialize resonance insertion transform" write (u, "(A)") evt_trivial%next => evt_resonance evt_resonance%previous => evt_trivial allocate (rng_test_t :: rng) call evt_resonance%import_rng (rng) call evt_resonance%set_resonance_data (res_history_set) call evt_resonance%select_component (1) call evt_resonance%write (u) write (u, "(A)") write (u, "(A)") "* Fill resonance insertion transform" write (u, "(A)") call evt_resonance%prepare_new_event (1, 1) call evt_resonance%init_selector ([1._default]) call evt_resonance%generate_weighted (probability) call evt_resonance%make_particle_set (0, .false.) call evt_resonance%write (u) write (u, "(A)") write (u, "(A,1x,F8.5)") "Event probability =", probability write (u, "(A)") write (u, "(A)") "* Cleanup" call evt_resonance%final () call evt_trivial%final () call syntax_model_file_final () write (u, "(A)") write (u, "(A)") "* Test output end: resonance_insertion_6" end subroutine resonance_insertion_6 @ %def resonance_insertion_6 @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Recoil kinematics} <<[[recoil_kinematics.f90]]>>= <> module recoil_kinematics <> use lorentz, only: vector4_t use lorentz, only: vector4_null use lorentz, only: vector4_moving use lorentz, only: vector3_moving use lorentz, only: transverse_part use lorentz, only: lorentz_transformation_t use lorentz, only: inverse use lorentz, only: boost use lorentz, only: transformation use lorentz, only: operator(+) use lorentz, only: operator(-) use lorentz, only: operator(*) use lorentz, only: operator(**) use lorentz, only: lambda <> <> <> <> interface <> end interface end module recoil_kinematics @ %def recoil_kinematics @ <<[[recoil_kinematics_sub.f90]]>>= <> submodule (recoil_kinematics) recoil_kinematics_s use constants, only: twopi implicit none contains <> end submodule recoil_kinematics_s @ %def recoil_kinematics_s @ \subsection{$\phi$ sampler} This is trivial. Generate an azimuthal angle, given a $(0,1)$ RNG parameter. <>= elemental subroutine generate_phi_recoil (r, phi) real(default), intent(in) :: r real(default), intent(out) :: phi phi = r * twopi end subroutine generate_phi_recoil @ %def generate_phi_recoil @ \subsection{$Q^2$ sampler} The dynamics of factorization suggests to generate a flat $Q^2$ distribution from a (random) number, event by event. At the lowest momentum transfer values, the particle (electron) mass sets a smooth cutoff. The formula can produce $Q$ values below the electron mass, down to zero, but with a power distribution that eventually evolves into the expected logarithmic distribution for $Q^2 > m^2$. We are talking about the absolute value here, so all $Q^2$ values are positive. For the actual momentum transfer, $q^2=-Q^2$. <>= public :: generate_q2_recoil <>= elemental module subroutine generate_q2_recoil (s, x_bar, q2_max, m2, r, q2) real(default), intent(in) :: s real(default), intent(in) :: q2_max real(default), intent(in) :: x_bar real(default), intent(in) :: m2 real(default), intent(in) :: r real(default), intent(out) :: q2 end subroutine generate_q2_recoil <>= elemental module subroutine generate_q2_recoil (s, x_bar, q2_max, m2, r, q2) real(default), intent(in) :: s real(default), intent(in) :: q2_max real(default), intent(in) :: x_bar real(default), intent(in) :: m2 real(default), intent(in) :: r real(default), intent(out) :: q2 real(default) :: q2_max_evt q2_max_evt = q2_max_event (s, x_bar, q2_max) q2 = m2 * (exp (r * log (1 + (q2_max_evt / m2))) - 1) end subroutine generate_q2_recoil @ %def generate_q_recoil @ The $Q$ distribution is cut off from above by the kinematic limit, which depends on the energy that is available for the radiated photon, or by a user-defined cutoff -- whichever is less. The kinematic limit fits the formulas for recoil momenta (see below), and it also implicitly enters the ISR collinear structure function, so the normalization of the distribution should be correct. <>= elemental function q2_max_event (s, x_bar, q2_max) result (q2) real(default), intent(in) :: s real(default), intent(in) :: x_bar real(default), intent(in) :: q2_max real(default) :: q2 q2 = min (x_bar * s, q2_max) end function q2_max_event @ %def q2_max_event @ \subsection{Kinematics functions} Given values for energies, $Q_{1,2}^2$, azimuthal angle, compute the matching polar angle of the radiating particle. The subroutine returns $\sin\theta$ and $\cos\theta$. <>= subroutine polar_angles (s, xb, rho, ee, q2, sin_th, cos_th, ok) real(default), intent(in) :: s real(default), intent(in) :: xb real(default), intent(in) :: rho real(default), dimension(2), intent(in) :: ee real(default), dimension(2), intent(in) :: q2 real(default), dimension(2), intent(out) :: sin_th real(default), dimension(2), intent(out) :: cos_th logical, intent(out) :: ok real(default), dimension(2) :: sin2_th_2 sin2_th_2 = q2 / (ee * rho * xb * s) if (all (sin2_th_2 <= 1)) then sin_th = 2 * sqrt (sin2_th_2 * (1 - sin2_th_2)) cos_th = 1 - 2 * sin2_th_2 ok = .true. else sin_th = 0 cos_th = 1 ok = .false. end if end subroutine polar_angles @ %def polar_angles @ Compute the acollinearity parameter $\lambda$ from azimuthal and polar angles. The result is a number between $0$ and $1$. <>= function lambda_factor (sin_th, cos_th, cphi) result (lambda) real(default), dimension(2), intent(in) :: sin_th real(default), dimension(2), intent(in) :: cos_th real(default), intent(in) :: cphi real(default) :: lambda lambda = (1 - cos_th(1) * cos_th(2) - cphi * sin_th(1) * sin_th(2)) / 2 end function lambda_factor @ %def lambda_factor @ Compute the factor that rescales photon energies, such that the radiation angles match the kinematics parameters. For small values of $\bar x/\cosh\eta$, we have to use the Taylor expansion if we do not want to lose precision. The optional argument allows for a unit test that compares exact and approximate. <>= function scale_factor (che, lambda, xb0, approximate) result (rho) real(default), intent(in) :: che real(default), intent(in) :: lambda real(default), intent(in) :: xb0 logical, intent(in), optional :: approximate real(default) :: rho real(default), parameter :: & e0 = (100 * epsilon (1._default)) ** (0.3_default) logical :: approx if (present (approximate)) then approx = approximate else approx = (xb0/che) < e0 end if if (approx) then rho = 1 - lambda * (xb0/(2*che)) * (1 + (1-lambda) * (xb0/che)) else rho = (che / ((1-lambda)*xb0)) & * (1 - sqrt (1 - 2 * (1-lambda) * (xb0/che) & & + (1-lambda) * (xb0 / che)**2)) end if end function scale_factor @ %def scale_factor @ The code snippet below is not used anywhere, but may be manually inserted in a unit test to numerically verify the approximation above. <>= write (u, "(A)") write (u, "(A)") "*** Table: scale factor calculation" write (u, "(A)") lambda = 0.25_default write (u, FMT1) "lambda =", lambda che = 4._default write (u, FMT1) "che =", che write (u, "(A)") " x0 rho(exact) rho(approx) rho(chosen)" xb0 = 1._default do i = 1, 30 xb0 = xb0 / 10 write (u, FMT4) xb0, & scale_factor (che, lambda, xb0, approximate=.false.), & scale_factor (che, lambda, xb0, approximate=.true.), & scale_factor (che, lambda, xb0) end do @ Compute the current values for the $x_{1,2}$ parameters, given the updated scale factor $\rho$ and the collinear parameters. <>= subroutine scaled_x (rho, ee, xb0, x, xb) real(default), intent(in) :: rho real(default), dimension(2), intent(in) :: ee real(default), intent(in) :: xb0 real(default), dimension(2), intent(out) :: x real(default), dimension(2), intent(out) :: xb xb = rho * ee * xb0 x = 1 - xb end subroutine scaled_x @ %def scaled_x @ \subsection{Iterative solution of kinematics constraints} Find a solution of the kinematics constraints. We know the parameters appropriate for collinear kinematics $\sqrt{s}$, $x^c_{1,2}$. We have picked values vor the momentum transfer $Q_{1,2}$ and the azimuthal angles $\phi_{1,2}$. The solution consists of modified energy fractions $x_{1,2}$ and polar angles $\theta_{1,2}$. If the computation fails, which can happen for large momentum transfer, the flag [[ok]] will indicate this. <>= public :: solve_recoil <>= module subroutine solve_recoil & (sqrts, xc, xcb, phi, q2, x, xb, cos_th, sin_th, ok) real(default), intent(in) :: sqrts real(default), dimension(2), intent(in) :: xc real(default), dimension(2), intent(in) :: xcb real(default), dimension(2), intent(in) :: phi real(default), dimension(2), intent(in) :: q2 real(default), dimension(2), intent(out) :: x real(default), dimension(2), intent(out) :: xb real(default), dimension(2), intent(out) :: cos_th real(default), dimension(2), intent(out) :: sin_th logical, intent(out) :: ok end subroutine solve_recoil <>= module subroutine solve_recoil & (sqrts, xc, xcb, phi, q2, x, xb, cos_th, sin_th, ok) real(default), intent(in) :: sqrts real(default), dimension(2), intent(in) :: xc real(default), dimension(2), intent(in) :: xcb real(default), dimension(2), intent(in) :: phi real(default), dimension(2), intent(in) :: q2 real(default), dimension(2), intent(out) :: x real(default), dimension(2), intent(out) :: xb real(default), dimension(2), intent(out) :: cos_th real(default), dimension(2), intent(out) :: sin_th logical, intent(out) :: ok real(default) :: s real(default), dimension(2) :: ee real(default), dimension(2) :: th real(default) :: xb0, cphi real(default) :: che, lambda real(default) :: rho_new, rho, rho_old real(default) :: dr_old, dr_new real(default), parameter :: dr_limit = 100 * epsilon (1._default) integer, parameter :: n_it_max = 20 integer :: i ok = .true. s = sqrts**2 ee = sqrt ([xcb(1)/xcb(2), xcb(2)/xcb(1)]) che = sum (ee) / 2 xb0 = sqrt (xcb(1) * xcb(2)) cphi = cos (phi(1) - phi(2)) rho_old = 10 rho = 1 th = 0 sin_th = sin (th) cos_th = cos (th) lambda = lambda_factor (sin_th, cos_th, cphi) call scaled_x (rho, ee, xb0, x, xb) iterate_loop: do i = 1, n_it_max call polar_angles (s, xb0, rho, ee, q2, sin_th, cos_th, ok) if (.not. ok) return th = atan2 (sin_th, cos_th) lambda = lambda_factor (sin_th, cos_th, cphi) rho_new = scale_factor (che, lambda, xb0) call scaled_x (rho_new, ee, xb0, x, xb) dr_old = abs (rho - rho_old) dr_new = abs (rho_new - rho) rho_old = rho rho = rho_new if (dr_new < dr_limit .or. dr_new >= dr_old) exit iterate_loop end do iterate_loop end subroutine solve_recoil @ %def solve_recoil @ With all kinematics parameters known, construct actual four-vectors for the recoil momenta, the off-shell (spacelike) parton momenta, and on-shell projected parton momenta. <>= public :: recoil_momenta <>= module subroutine recoil_momenta (sqrts, xc, xb, cos_th, sin_th, phi, mo, & km, qm, qo, ok) real(default), intent(in) :: sqrts real(default), dimension(2), intent(in) :: xc real(default), dimension(2), intent(in) :: xb real(default), dimension(2), intent(in) :: cos_th real(default), dimension(2), intent(in) :: sin_th real(default), dimension(2), intent(in) :: phi real(default), dimension(2), intent(in) :: mo type(vector4_t), dimension(2), intent(out) :: km type(vector4_t), dimension(2), intent(out) :: qm type(vector4_t), dimension(2), intent(out) :: qo logical, intent(out) :: ok end subroutine recoil_momenta <>= module subroutine recoil_momenta (sqrts, xc, xb, cos_th, sin_th, phi, mo, & km, qm, qo, ok) real(default), intent(in) :: sqrts real(default), dimension(2), intent(in) :: xc real(default), dimension(2), intent(in) :: xb real(default), dimension(2), intent(in) :: cos_th real(default), dimension(2), intent(in) :: sin_th real(default), dimension(2), intent(in) :: phi real(default), dimension(2), intent(in) :: mo type(vector4_t), dimension(2), intent(out) :: km type(vector4_t), dimension(2), intent(out) :: qm type(vector4_t), dimension(2), intent(out) :: qo logical, intent(out) :: ok type(vector4_t), dimension(2) :: pm type(lorentz_transformation_t) :: lt real(default) :: sqsh real(default) :: po4, po2 real(default), dimension(2) :: p0, p3 pm(1) = & vector4_moving (sqrts/2, & vector3_moving ([0._default, 0._default, sqrts/2])) pm(2) = & vector4_moving (sqrts/2, & vector3_moving ([0._default, 0._default,-sqrts/2])) km(1) = xb(1) * (sqrts/2) * vector4_moving ( & 1._default, & vector3_moving ([ & & sin_th(1) * cos (phi(1)), & & sin_th(1) * sin (phi(1)), & & cos_th(1)]) & ) km(2) = xb(2) * (sqrts/2) * vector4_moving ( & 1._default, & vector3_moving ([ & & -sin_th(2) * cos (phi(2)), & & -sin_th(2) * sin (phi(2)), & & -cos_th(2)]) & ) qm(1) = pm(1) - km(1) qm(2) = pm(2) - km(2) sqsh = sqrt (xc(1)*xc(2)) * sqrts lt = transformation (3, qm(1), qm(2), sqsh) po4 = lambda (sqsh**2, mo(1)**2, mo(2)**2) ok = po4 > 0 if (ok) then po2 = sqrt (po4)/4 p0 = sqrt (po2 + mo**2) p3 = [sqrt (po2), -sqrt (po2)] qo = lt * vector4_moving (p0, p3, 3) else qo = vector4_null end if end subroutine recoil_momenta @ %def recoil_momenta @ Compute the Lorentz transformation that we can use to transform any outgoing momenta into the new c.m.\ system of the incoming partons. Not relying on the previous calculations, we determine the transformation that transforms the original collinear partons into their c.m.\ system, and then transform this to the new c.m.\ system. <>= public :: recoil_transformation <>= module subroutine recoil_transformation (sqrts, xc, qo, lt) real(default), intent(in) :: sqrts real(default), dimension(2), intent(in) :: xc type(vector4_t), dimension(2), intent(in) :: qo type(lorentz_transformation_t), intent(out) :: lt end subroutine recoil_transformation <>= module subroutine recoil_transformation (sqrts, xc, qo, lt) real(default), intent(in) :: sqrts real(default), dimension(2), intent(in) :: xc type(vector4_t), dimension(2), intent(in) :: qo type(lorentz_transformation_t), intent(out) :: lt real(default) :: sqsh type(vector4_t), dimension(2) :: qc type(lorentz_transformation_t) :: ltc, lto qc(1) = xc(1) * vector4_moving (sqrts/2, sqrts/2, 3) qc(2) = xc(2) * vector4_moving (sqrts/2,-sqrts/2, 3) sqsh = sqrt (xc(1) * xc(2)) * sqrts ltc = transformation (3, qc(1), qc(2), sqsh) lto = transformation (3, qo(1), qo(2), sqsh) lt = lto * inverse (ltc) end subroutine recoil_transformation @ %def recoil_transformation @ Compute the Lorentz boost that transforms the c.m.\ frame of the momenta into the lab frame where they are given. Also return their common invariant mass, $\sqrt{s}$. If the initial momenta are not collinear, [[ok]] is set false. <>= public :: initial_transformation <>= module subroutine initial_transformation (p, sqrts, lt, ok) type(vector4_t), dimension(2), intent(in) :: p real(default), intent(out) :: sqrts type(lorentz_transformation_t), intent(out) :: lt logical, intent(out) :: ok end subroutine initial_transformation <>= module subroutine initial_transformation (p, sqrts, lt, ok) type(vector4_t), dimension(2), intent(in) :: p real(default), intent(out) :: sqrts type(lorentz_transformation_t), intent(out) :: lt logical, intent(out) :: ok ok = all (transverse_part (p) == 0) sqrts = (p(1) + p(2)) ** 1 lt = boost (p(1) + p(2), sqrts) end subroutine initial_transformation @ %def initial_transformation @ \subsection{Generate recoil event} Combine the above kinematics calculations. First generate azimuthal angles and momentum transfer, solve kinematics and compute momenta for the radiated photons and the on-shell projected, recoiling partons. The [[mo]] masses are used for the on-shell projection of the partons after radiation. They may be equal to [[m]], or set to zero. If [[ok]] is false, the data point has failed and we should repeat the procedure for a new set of RNG parameters [[r]]. <>= public :: generate_recoil <>= module subroutine generate_recoil & (sqrts, q_max, m, mo, xc, xcb, r, km, qm, qo, ok) real(default), intent(in) :: sqrts real(default), intent(in), dimension(2) :: q_max real(default), intent(in), dimension(2) :: m real(default), intent(in), dimension(2) :: mo real(default), intent(in), dimension(2) :: xc real(default), intent(in), dimension(2) :: xcb real(default), intent(in), dimension(4) :: r type(vector4_t), dimension(2), intent(out) :: km type(vector4_t), dimension(2), intent(out) :: qm type(vector4_t), dimension(2), intent(out) :: qo logical, intent(out) :: ok end subroutine generate_recoil <>= module subroutine generate_recoil & (sqrts, q_max, m, mo, xc, xcb, r, km, qm, qo, ok) real(default), intent(in) :: sqrts real(default), intent(in), dimension(2) :: q_max real(default), intent(in), dimension(2) :: m real(default), intent(in), dimension(2) :: mo real(default), intent(in), dimension(2) :: xc real(default), intent(in), dimension(2) :: xcb real(default), intent(in), dimension(4) :: r type(vector4_t), dimension(2), intent(out) :: km type(vector4_t), dimension(2), intent(out) :: qm type(vector4_t), dimension(2), intent(out) :: qo logical, intent(out) :: ok real(default), dimension(2) :: q2 real(default), dimension(2) :: phi real(default), dimension(2) :: x real(default), dimension(2) :: xb real(default), dimension(2) :: cos_th real(default), dimension(2) :: sin_th call generate_q2_recoil (sqrts**2, xcb, q_max**2, m**2, r(1:2), q2) call generate_phi_recoil (r(3:4), phi) call solve_recoil (sqrts, xc, xcb, phi, q2, x, xb, cos_th, sin_th, ok) if (ok) then call recoil_momenta & (sqrts, xc, xb, cos_th, sin_th, phi, mo, km, qm, qo, ok) end if end subroutine generate_recoil @ %def generate_recoil @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[recoil_kinematics_ut.f90]]>>= <> module recoil_kinematics_ut use unit_tests use recoil_kinematics_uti <> <> contains <> end module recoil_kinematics_ut @ %def recoil_kinematics_ut @ <<[[recoil_kinematics_uti.f90]]>>= <> module recoil_kinematics_uti <> use constants, only: twopi use constants, only: degree use lorentz, only: vector4_t use lorentz, only: vector4_moving use lorentz, only: lorentz_transformation_t use lorentz, only: inverse use lorentz, only: operator(+) use lorentz, only: operator(*) use lorentz, only: operator(**) use lorentz, only: pacify use recoil_kinematics, only: solve_recoil use recoil_kinematics, only: recoil_momenta use recoil_kinematics, only: recoil_transformation use recoil_kinematics, only: initial_transformation use recoil_kinematics, only: generate_q2_recoil use recoil_kinematics, only: generate_recoil <> <> contains <> end module recoil_kinematics_uti @ %def recoil_kinematics_uti @ API: driver for the unit tests below. <>= public :: recoil_kinematics_test <>= subroutine recoil_kinematics_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine recoil_kinematics_test @ %def recoil_kinematics_test @ \subsubsection{Recoil kinematics} For a set of input data, solve the kinematics constraints and generate momenta accordingly. <>= call test (recoil_kinematics_1, "recoil_kinematics_1", & "iterative solution of non-collinear kinematics", & u, results) <>= public :: recoil_kinematics_1 <>= subroutine recoil_kinematics_1 (u) integer, intent(in) :: u real(default) :: sqrts real(default), dimension(2) :: xc, xcb real(default), dimension(2) :: q real(default), dimension(2) :: phi real(default), dimension(2) :: mo real(default), dimension(2) :: cos_th, sin_th real(default), dimension(2) :: x real(default), dimension(2) :: xb type(vector4_t), dimension(2) :: km type(vector4_t), dimension(2) :: qm type(vector4_t), dimension(2) :: qo integer :: i logical :: ok character(*), parameter :: FMT1 = "(1x,A,9(1x,F15.10))" character(*), parameter :: FMT2 = "(1x,A,9(1x,F10.5))" character(*), parameter :: FMT4 = "(3x,ES8.1,9(1x,ES19.12))" write (u, "(A)") "* Test output: recoil_kinematics_1" write (u, "(A)") "* Purpose: compute kinematics for various input data" write (u, "(A)") sqrts = 100 write (u, FMT1) "sqrts =", sqrts write (u, "(A)") write (u, "(A)") "*** collinear data set" write (u, "(A)") xc = [0.6_default, 0.9_default] xcb = 1 - xc phi = [0.1_default, 0.2_default] * twopi q = 0 mo = 0 call show_data call solve_recoil (sqrts, xc, xcb, phi, q**2, x, xb, cos_th, sin_th, ok) call show_results call recoil_momenta (sqrts, xc, xb, cos_th, sin_th, phi, mo, km, qm, qo, ok) call show_momenta write (u, "(A)") write (u, "(A)") "*** moderate data set" write (u, "(A)") xc = [0.6_default, 0.9_default] xcb = 1 - xc phi = [0.1_default, 0.2_default] * twopi q = [0.2_default, 0.05_default] * sqrts call show_data call solve_recoil (sqrts, xc, xcb, phi, q**2, x, xb, cos_th, sin_th, ok) call show_results call recoil_momenta (sqrts, xc, xb, cos_th, sin_th, phi, mo, km, qm, qo, ok) call show_momenta write (u, "(A)") write (u, "(A)") "*** semi-soft data set" write (u, "(A)") xcb= [0.1_default, 0.0001_default] xc = 1 - xcb phi = [0.1_default, 0.2_default] * twopi q = [0.2_default, 0.00001_default] * sqrts call show_data call solve_recoil (sqrts, xc, xcb, phi, q**2, x, xb, cos_th, sin_th, ok) call show_results call recoil_momenta (sqrts, xc, xb, cos_th, sin_th, phi, mo, km, qm, qo, ok) call show_momenta write (u, "(A)") write (u, "(A)") "*** hard-soft data set" write (u, "(A)") xcb= [0.1_default, 1.e-30_default] xc = 1 - xcb phi = [0.1_default, 0.2_default] * twopi q = [0.2_default, 1.e-35_default] * sqrts call show_data call solve_recoil (sqrts, xc, xcb, phi, q**2, x, xb, cos_th, sin_th, ok) call show_results call recoil_momenta (sqrts, xc, xb, cos_th, sin_th, phi, mo, km, qm, qo, ok) call show_momenta write (u, "(A)") write (u, "(A)") "*** hard data set" write (u, "(A)") xc = [0.2_default, 0.4_default] xcb = 1 - xc phi = [0.1_default, 0.8_default] * twopi q = [0.74_default, 0.3_default] * sqrts call show_data call solve_recoil (sqrts, xc, xcb, phi, q**2, x, xb, cos_th, sin_th, ok) call show_results call recoil_momenta (sqrts, xc, xb, cos_th, sin_th, phi, mo, km, qm, qo, ok) call show_momenta write (u, "(A)") write (u, "(A)") "*** failing data set" write (u, "(A)") xc = [0.2_default, 0.4_default] xcb = 1 - xc phi = [0.1_default, 0.8_default] * twopi q = [0.9_default, 0.3_default] * sqrts call show_data call solve_recoil (sqrts, xc, xcb, phi, q**2, x, xb, cos_th, sin_th, ok) if (.not. ok) then write (u, "(A)") write (u, "(A)") "Failed as expected." end if write (u, "(A)") write (u, "(A)") "* Test output end: recoil_kinematics_1" contains subroutine show_data write (u, FMT1) "sqs_h =", sqrt (xc(1) * xc(2)) * sqrts write (u, FMT1) "xc =", xc write (u, FMT1) "xcb =", xcb write (u, FMT1) "Q =", Q write (u, FMT1) "phi/D =", phi / degree end subroutine show_data subroutine show_results write (u, "(A)") write (u, "(A)") "Result:" write (u, FMT1) "th/D =", atan2 (sin_th, cos_th) / degree write (u, FMT1) "x =", x write (u, "(A)") end subroutine show_results subroutine show_momenta type(vector4_t) :: qm0, qo0 real(default), parameter :: tol = 1.e-7_default call pacify (km, tol) call pacify (qm, tol) call pacify (qo, tol) write (u, "(A)") "Momenta: k" call km(1)%write (u, testflag=.true.) call km(2)%write (u, testflag=.true.) write (u, FMT1) "k^2 =", abs (km(1)**2), abs (km(2)**2) write (u, "(A)") write (u, "(A)") "Momenta: q" call qm(1)%write (u, testflag=.true.) call qm(2)%write (u, testflag=.true.) write (u, "(A)") write (u, "(A)") "Momenta: q(os)" call qo(1)%write (u, testflag=.true.) call qo(2)%write (u, testflag=.true.) write (u, "(A)") write (u, "(A)") "Check: parton momentum sum: q vs q(os)" qm0 = qm(1) + qm(2) call qm0%write (u, testflag=.true.) qo0 = qo(1) + qo(2) call qo0%write (u, testflag=.true.) write (u, "(A)") write (u, "(A)") "* Check: momentum transfer (off-shell/on-shell)" write (u, FMT2) "|q| =", abs (qm(1)**1), abs (qm(2)**1) write (u, FMT2) "Q =", q write (u, FMT2) "|qo|=", abs (qo(1)**1), abs (qo(2)**1) write (u, "(A)") write (u, "(A)") "* Check: sqrts, sqrts_hat" write (u, FMT1) "|p| =", (km(1)+km(2)+qm(1)+qm(2))**1, (qm(1)+qm(2))**1 write (u, FMT1) "sqs =", sqrts, sqrt (product (xc)) * sqrts write (u, FMT1) "|po|=", abs ((km(1)+km(2)+qo(1)+qo(2))**1), abs ((qo(1)+qo(2))**1) end subroutine show_momenta end subroutine recoil_kinematics_1 @ %def recoil_kinematics_1 @ \subsubsection{Recoil $Q$ distribution} Sample the $Q$ distribution for equidistant bins in the input variable. <>= call test (recoil_kinematics_2, "recoil_kinematics_2", & "Q distribution", & u, results) <>= public :: recoil_kinematics_2 <>= subroutine recoil_kinematics_2 (u) integer, intent(in) :: u real(default) :: sqrts real(default) :: q_max real(default) :: m real(default) :: x_bar real(default) :: r real(default) :: q2, q2_old integer :: i integer :: n_bin character(*), parameter :: FMT1 = "(1x,A,9(1x,F15.10))" character(*), parameter :: FMT3 = "(2x,9(1x,F10.5))" write (u, "(A)") "* Test output: recoil_kinematics_2" write (u, "(A)") "* Purpose: compute Q distribution" write (u, "(A)") n_bin = 20 write (u, "(A)") "* No Q cutoff, xbar = 1" write (u, "(A)") sqrts = 100 q_max = sqrts m = 0.511e-3_default x_bar = 1._default call show_table write (u, "(A)") write (u, "(A)") "* With Q cutoff, xbar = 1" write (u, "(A)") q_max = 10 call show_table write (u, "(A)") write (u, "(A)") "* No Q cutoff, xbar = 0.01" write (u, "(A)") q_max = sqrts x_bar = 0.01_default call show_table write (u, "(A)") write (u, "(A)") "* Test output end: recoil_kinematics_2" contains subroutine show_table write (u, FMT1) "sqrts =", sqrts write (u, FMT1) "q_max =", q_max write (u, FMT1) "m =", m write (u, FMT1) "x_bar =", x_bar write (u, "(A)") write (u, "(1x,A)") "Table: r |Q| |Q_i/Q_(i-1)|" q2_old = 0 do i = 0, n_bin r = real (i, default) / n_bin call generate_q2_recoil (sqrts**2, x_bar, q_max**2, m**2, r, q2) if (q2_old > 0) then write (u, FMT3) r, sqrt (q2), sqrt (q2 / q2_old) else write (u, FMT3) r, sqrt (q2) end if q2_old = q2 end do end subroutine show_table end subroutine recoil_kinematics_2 @ %def recoil_kinematics_2 @ \subsubsection{Generate recoil event} Combine $Q^2$ sampling with momentum generation. <>= call test (recoil_kinematics_3, "recoil_kinematics_3", & "generate recoil event", & u, results) <>= public :: recoil_kinematics_3 <>= subroutine recoil_kinematics_3 (u) integer, intent(in) :: u real(default) :: sqrts real(default), dimension(2) :: q_max real(default), dimension(2) :: m, mo real(default), dimension(2) :: xc, xcb real(default), dimension(4) :: r type(vector4_t), dimension(2) :: km type(vector4_t), dimension(2) :: qm type(vector4_t), dimension(2) :: qo logical :: ok character(*), parameter :: FMT1 = "(1x,A,9(1x,F15.10))" character(*), parameter :: FMT2 = "(1x,A,9(1x,F10.5))" write (u, "(A)") "* Test output: recoil_kinematics_3" write (u, "(A)") "* Purpose: generate momenta from RNG parameters" write (u, "(A)") write (u, "(A)") "*** collinear data set" write (u, "(A)") sqrts = 100 q_max = sqrts m = 0.511e-3_default mo = 0 xc = [0.6_default, 0.9_default] xcb = 1 - xc r = [0._default, 0._default, 0._default, 0._default] call show_data call generate_recoil (sqrts, q_max, m, mo, xc, xcb, r, km, qm, qo, ok) call show_momenta write (u, "(A)") write (u, "(A)") "*** moderate data set" write (u, "(A)") xc = [0.6_default, 0.9_default] xcb = 1 - xc r = [0.8_default, 0.2_default, 0.1_default, 0.2_default] call show_data call generate_recoil (sqrts, q_max, m, mo, xc, xcb, r, km, qm, qo, ok) call show_momenta write (u, "(A)") write (u, "(A)") "*** failing data set" write (u, "(A)") xc = [0.2_default, 0.4_default] xcb = 1 - xc r = [0.9999_default, 0.3_default, 0.1_default, 0.8_default] call show_data call generate_recoil (sqrts, q_max, m, mo, xc, xcb, r, km, qm, qo, ok) if (.not. ok) then write (u, "(A)") write (u, "(A)") "Failed as expected." else call show_momenta end if contains subroutine show_data write (u, FMT1) "sqrts =", sqrts write (u, FMT1) "q_max =", q_max write (u, FMT1) "m =", m write (u, FMT1) "xc =", xc write (u, FMT1) "xcb =", xcb write (u, FMT1) "r =", r end subroutine show_data subroutine show_momenta real(default), parameter :: tol = 1.e-7_default call pacify (km, tol) call pacify (qo, tol) write (u, "(A)") write (u, "(A)") "* Momenta: k" call km(1)%write (u, testflag=.true.) call km(2)%write (u, testflag=.true.) write (u, FMT1) "k^2 =", abs (km(1)**2), abs (km(2)**2) write (u, "(A)") write (u, "(A)") "* Momenta: q(os)" call qo(1)%write (u, testflag=.true.) call qo(2)%write (u, testflag=.true.) write (u, FMT1) "q^2 =", abs (qo(1)**2), abs (qo(2)**2) write (u, "(A)") write (u, "(A)") "* Check: momentum transfer (off-shell/on-shell)" write (u, FMT2) "Q =", q_check (1), q_check (2) write (u, FMT2) "|q| =", abs (qm(1)**1), abs (qm(2)**1) write (u, "(A)") write (u, "(A)") "* Check: sqrts, sqrts_hat" write (u, FMT1) "sqs =", sqrts, sqrt (product (xc)) * sqrts write (u, FMT1) "|po|=", abs ((km(1)+km(2)+qo(1)+qo(2))**1), abs ((qo(1)+qo(2))**1) end subroutine show_momenta function q_check (i) result (q) integer, intent(in) :: i real(default) :: q real(default) :: q2 call generate_q2_recoil (sqrts**2, xcb(i), q_max(i)**2, m(i)**2, r(i), q2) q = sqrt (q2) end function q_check end subroutine recoil_kinematics_3 @ %def recoil_kinematics_3 @ \subsubsection{Transformation after recoil} Given a solution to recoil kinematics, compute the Lorentz transformation that transforms the old collinear parton momenta into the new parton momenta. <>= call test (recoil_kinematics_4, "recoil_kinematics_4", & "reference frame", & u, results) <>= public :: recoil_kinematics_4 <>= subroutine recoil_kinematics_4 (u) integer, intent(in) :: u real(default) :: sqrts real(default), dimension(2) :: xc, xcb real(default), dimension(2) :: q real(default), dimension(2) :: phi real(default), dimension(2) :: cos_th, sin_th real(default), dimension(2) :: mo real(default), dimension(2) :: x real(default), dimension(2) :: xb type(vector4_t), dimension(2) :: km type(vector4_t), dimension(2) :: qm type(vector4_t), dimension(2) :: qo type(lorentz_transformation_t) :: lt logical :: ok character(*), parameter :: FMT1 = "(1x,A,9(1x,F15.10))" character(*), parameter :: FMT2 = "(1x,A,9(1x,F10.5))" write (u, "(A)") "* Test output: recoil_kinematics_4" write (u, "(A)") "* Purpose: check Lorentz transformation for recoil" write (u, "(A)") sqrts = 100 write (u, FMT1) "sqrts =", sqrts write (u, "(A)") write (u, "(A)") "*** collinear data set" write (u, "(A)") xc = [0.6_default, 0.9_default] xcb = 1 - xc phi = [0.1_default, 0.2_default] * twopi q = 0 mo = 0 call show_data call solve_recoil (sqrts, xc, xcb, phi, q**2, x, xb, cos_th, sin_th, ok) call recoil_momenta (sqrts, xc, xb, cos_th, sin_th, phi, mo, km, qm, qo, ok) call recoil_transformation (sqrts, xc, qo, lt) call show_transformation write (u, "(A)") write (u, "(A)") "*** moderate data set" write (u, "(A)") xc = [0.6_default, 0.9_default] xcb = 1 - xc phi = [0.1_default, 0.2_default] * twopi q = [0.2_default, 0.05_default] * sqrts call show_data call solve_recoil (sqrts, xc, xcb, phi, q**2, x, xb, cos_th, sin_th, ok) call recoil_momenta (sqrts, xc, xb, cos_th, sin_th, phi, mo, km, qm, qo, ok) call recoil_transformation (sqrts, xc, qo, lt) call show_transformation write (u, "(A)") write (u, "(A)") "* Test output end: recoil_kinematics_4" contains subroutine show_data write (u, FMT1) "sqs_h =", sqrt (xc(1) * xc(2)) * sqrts write (u, FMT1) "xc =", xc write (u, FMT1) "xcb =", xcb write (u, FMT1) "Q =", Q write (u, FMT1) "phi/D =", phi / degree end subroutine show_data subroutine show_transformation type(vector4_t), dimension(2) :: qc type(vector4_t), dimension(2) :: qct real(default), parameter :: tol = 1.e-7_default qc(1) = xc(1) * vector4_moving (sqrts/2, sqrts/2, 3) qc(2) = xc(2) * vector4_moving (sqrts/2,-sqrts/2, 3) qct = lt * qc call pacify (qct, tol) write (u, "(A)") write (u, "(A)") "Momenta: q(os)" call qo(1)%write (u, testflag=.true.) call qo(2)%write (u, testflag=.true.) write (u, "(A)") write (u, "(A)") "Momenta: LT * qc" call qct(1)%write (u, testflag=.true.) call qct(2)%write (u, testflag=.true.) end subroutine show_transformation end subroutine recoil_kinematics_4 @ %def recoil_kinematics_4 @ \subsubsection{Transformation before recoil} Given a pair of incoming `beam' partons (i.e., before ISR splitting), compute the transformation that transforms their common c.m.\ frame into the lab frame. <>= call test (recoil_kinematics_5, "recoil_kinematics_5", & "initial reference frame", & u, results) <>= public :: recoil_kinematics_5 <>= subroutine recoil_kinematics_5 (u) integer, intent(in) :: u real(default) :: sqrts real(default) :: sqrtsi real(default), dimension(2) :: x type(vector4_t), dimension(2) :: p type(vector4_t), dimension(2) :: pi type(vector4_t), dimension(2) :: p0 type(lorentz_transformation_t) :: lt logical :: ok character(*), parameter :: FMT1 = "(1x,A,9(1x,F15.10))" character(*), parameter :: FMT2 = "(1x,A,9(1x,F10.5))" write (u, "(A)") "* Test output: recoil_kinematics_5" write (u, "(A)") "* Purpose: determine initial Lorentz transformation" write (u, "(A)") sqrts = 100 write (u, FMT1) "sqrts =", sqrts x = [0.6_default, 0.9_default] p(1) = x(1) * vector4_moving (sqrts/2, sqrts/2, 3) p(2) = x(2) * vector4_moving (sqrts/2,-sqrts/2, 3) call show_data call initial_transformation (p, sqrtsi, lt, ok) pi(1) = vector4_moving (sqrtsi/2, sqrtsi/2, 3) pi(2) = vector4_moving (sqrtsi/2,-sqrtsi/2, 3) p0 = inverse (lt) * p call show_momenta write (u, "(A)") write (u, "(A)") "* Test output end: recoil_kinematics_5" contains subroutine show_data write (u, FMT1) "sqrts =", sqrts write (u, FMT1) "x =", x end subroutine show_data subroutine show_momenta real(default), parameter :: tol = 1.e-7_default write (u, "(A)") write (u, "(A)") "* Momenta: p_in(c.m.)" call pi(1)%write (u, testflag=.true.) call pi(2)%write (u, testflag=.true.) write (u, "(A)") write (u, "(A)") "* Momenta: inv(LT) * p_in(lab)" call p0(1)%write (u, testflag=.true.) call p0(2)%write (u, testflag=.true.) end subroutine show_momenta end subroutine recoil_kinematics_5 @ %def recoil_kinematics_5 @ \subsubsection{Transformation after recoil with on-shell momenta} Given a solution to recoil kinematics, compute the Lorentz transformation that transforms the old collinear parton momenta into the new parton momenta. Compare the results for massless and massive on-shell projection. <>= call test (recoil_kinematics_6, "recoil_kinematics_6", & "massless/massive on-shell projection", & u, results) <>= public :: recoil_kinematics_6 <>= subroutine recoil_kinematics_6 (u) integer, intent(in) :: u real(default) :: sqrts real(default), dimension(2) :: xc, xcb real(default), dimension(2) :: q real(default), dimension(2) :: phi real(default), dimension(2) :: cos_th, sin_th real(default), dimension(2) :: x real(default), dimension(2) :: xb real(default), dimension(2) :: mo, z type(vector4_t), dimension(2) :: km type(vector4_t), dimension(2) :: qm type(vector4_t), dimension(2) :: qo type(lorentz_transformation_t) :: lt logical :: ok character(*), parameter :: FMT1 = "(1x,A,9(1x,F15.10))" character(*), parameter :: FMT2 = "(1x,A,9(1x,F11.6))" write (u, "(A)") "* Test output: recoil_kinematics_6" write (u, "(A)") "* Purpose: check effect of mass in on-shell projection" write (u, "(A)") sqrts = 10 write (u, FMT1) "sqrts =", sqrts z = 0 mo = 0.511e-3 write (u, FMT1) "mass =", mo write (u, "(A)") write (u, "(A)") "*** collinear data set" write (u, "(A)") xc = [0.6_default, 0.9_default] xcb = 1 - xc phi = [0.1_default, 0.2_default] * twopi q = 0 call show_data call solve_recoil (sqrts, xc, xcb, phi, q**2, x, xb, cos_th, sin_th, ok) call recoil_momenta (sqrts, xc, xb, cos_th, sin_th, phi, z, km, qm, qo, ok) call recoil_transformation (sqrts, xc, qo, lt) write (u, "(A)") write (u, "(A)") "Massless projection:" call show_momenta call recoil_momenta (sqrts, xc, xb, cos_th, sin_th, phi, mo, km, qm, qo, ok) call recoil_transformation (sqrts, xc, qo, lt) write (u, "(A)") write (u, "(A)") "Massive projection:" call show_momenta write (u, "(A)") write (u, "(A)") "*** moderate data set" write (u, "(A)") xc = [0.6_default, 0.9_default] xcb = 1 - xc phi = [0.1_default, 0.2_default] * twopi q = [0.2_default, 0.05_default] * sqrts call show_data call solve_recoil (sqrts, xc, xcb, phi, q**2, x, xb, cos_th, sin_th, ok) call recoil_momenta (sqrts, xc, xb, cos_th, sin_th, phi, z, km, qm, qo, ok) call recoil_transformation (sqrts, xc, qo, lt) write (u, "(A)") write (u, "(A)") "Massless projection:" call show_momenta call recoil_momenta (sqrts, xc, xb, cos_th, sin_th, phi, mo, km, qm, qo, ok) call recoil_transformation (sqrts, xc, qo, lt) write (u, "(A)") write (u, "(A)") "Massive projection:" call show_momenta write (u, "(A)") write (u, "(A)") "* Test output end: recoil_kinematics_6" contains subroutine show_data write (u, FMT1) "sqs_h =", sqrt (xc(1) * xc(2)) * sqrts write (u, FMT1) "xc =", xc write (u, FMT1) "xcb =", xcb write (u, FMT1) "Q =", Q write (u, FMT1) "phi/D =", phi / degree end subroutine show_data subroutine show_momenta write (u, "(A)") "Momenta: q(os)" call qo(1)%write (u, testflag=.true.) write (u, FMT2) "m = ", abs (qo(1)**1) call qo(2)%write (u, testflag=.true.) write (u, FMT2) "m = ", abs (qo(2)**1) end subroutine show_momenta end subroutine recoil_kinematics_6 @ %def recoil_kinematics_6 @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Transverse momentum for the ISR and EPA approximations} The ISR and EPA handler takes an event with a single radiated collinear particle (photon for ISR, beam particle for EPA) for each beam, respectively, and inserts transverse momentum for both. The four-particle kinematics allows us to generate $Q^2$ and azimuthal angles independently, without violating energy-momentum conservation. The $Q^2$ distribution is logarithmic, as required by the effective particle approximation, and reflected in the inclusive ISR/EPA structure functions. We also conserve the invariant mass of the partonic systm after radiation. The total transverse-momentum kick is applied in form of a Lorentz transformation to the elementary process, both in- and out-particles. In fact, the incoming partons (beam particle for ISR, photon for EPA) which would be virtual space-like in the exact kinematics configuration, are replaced by on-shell incoming partons, such that energy, momentum, and invariant mass $\sqrt{\hat s}$ are conserved. Regarding kinematics, we treat all particles as massless. The beam-particle mass only appears as the parameter [[isr_mass]] or [[epa_mass]], respectively, and cuts off the logarithmic distribution. The upper cutoff is [[isr_q_max]] ([[epa_q_max]]), which defaults to the available energy $\sqrt{s}$. The only differences between ISR and EPA, in this context, are the particle types, and an extra $\bar x$ factor in the lower cutoff for EPA, see below. <<[[isr_epa_handler.f90]]>>= <> module isr_epa_handler <> <> use lorentz, only: vector4_t use lorentz, only: energy use lorentz, only: lorentz_transformation_t use lorentz, only: identity use lorentz, only: inverse use lorentz, only: operator(*) use flavors, only: flavor_t use particles, only: particle_t use rng_base, only: rng_t use event_transforms <> <> <> <> interface <> end interface end module isr_epa_handler @ %def isr_epa_handler @ <<[[isr_epa_handler_sub.f90]]>>= <> submodule (isr_epa_handler) isr_epa_handler_s use diagnostics, only: msg_fatal use diagnostics, only: msg_bug use io_units use format_defs, only: FMT_12, FMT_19 use format_utils, only: write_separator use format_utils, only: pac_fmt use physics_defs, only: PHOTON use recoil_kinematics, only: initial_transformation use recoil_kinematics, only: generate_recoil use recoil_kinematics, only: recoil_transformation implicit none contains <> end submodule isr_epa_handler_s @ %def isr_epa_handler_s @ \subsection{Event transform type} Convention: [[beam]] are the incoming partons before ISR -- not necessarily the actual beams, need not be in c.m.\ frame. [[radiated]] are the radiated particles (photon for ISR), and [[parton]] are the remainders which initiate the elementary process. These particles are copied verbatim from the event record, and must be collinear. The kinematical parameters are [[sqrts]] = invariant mass of the [[beam]] particles, [[q_max]] and [[m]] determining the $Q^2$ distribution, and [[xc]]/[[xcb]] as the energy fraction (complement) of the partons, relative to the beams. Transformations: [[lti]] is the Lorentz transformation that would boosts [[pi]] (c.m. frame) back to the original [[beam]] momenta (lab frame). [[lto]] is the recoil transformation, transforming the partons after ISR from the collinear frame to the recoiling frame. [[lt]] is the combination of both, which is to be applied to all particles after the hard interaction. Momenta: [[pi]] are the beams transformed to their common c.m.\ frame. [[ki]] and [[qi]] are the photon/parton momenta in the [[pi]] c.m.\ frame. [[km]] and [[qm]] are the photon/parton momenta with the $Q$ distribution applied, and finally [[qo]] are the partons [[qm]] projected on-shell. <>= public :: evt_isr_epa_t <>= type, extends (evt_t) :: evt_isr_epa_t private integer :: mode = ISR_TRIVIAL_COLLINEAR logical :: isr_active = .false. logical :: epa_active = .false. real(default) :: isr_q_max = 0 real(default) :: epa_q_max = 0 real(default) :: isr_mass = 0 real(default) :: epa_mass = 0 logical :: isr_keep_mass = .true. real(default) :: sqrts = 0 integer, dimension(2) :: rad_mode = BEAM_RAD_NONE real(default), dimension(2) :: q_max = 0 real(default), dimension(2) :: m = 0 real(default), dimension(2) :: xc = 0 real(default), dimension(2) :: xcb = 0 type(lorentz_transformation_t) :: lti = identity type(lorentz_transformation_t) :: lto = identity type(lorentz_transformation_t) :: lt = identity integer, dimension(2) :: i_beam = 0 type(particle_t), dimension(2) :: beam type(vector4_t), dimension(2) :: pi integer, dimension(2) :: i_radiated = 0 type(particle_t), dimension(2) :: radiated type(vector4_t), dimension(2) :: ki type(vector4_t), dimension(2) :: km integer, dimension(2) :: i_parton = 0 type(particle_t), dimension(2) :: parton type(vector4_t), dimension(2) :: qi type(vector4_t), dimension(2) :: qm type(vector4_t), dimension(2) :: qo contains <> end type evt_isr_epa_t @ %def evt_isr_epa_t @ \subsection{ISR/EPA distinction} <>= integer, parameter, public :: BEAM_RAD_NONE = 0 integer, parameter, public :: BEAM_RAD_ISR = 1 integer, parameter, public :: BEAM_RAD_EPA = 2 @ %def BEAM_RAD_NONE @ %def BEAM_RAD_ISR @ %def BEAM_RAD_EPA <>= function rad_mode_string (mode) result (string) type(string_t) :: string integer, intent(in) :: mode select case (mode) case (BEAM_RAD_NONE); string = "---" case (BEAM_RAD_ISR); string = "ISR" case (BEAM_RAD_EPA); string = "EPA" case default; string = "???" end select end function rad_mode_string @ %def rad_mode_string @ \subsection{Photon insertion modes} <>= integer, parameter, public :: ISR_TRIVIAL_COLLINEAR = 0 integer, parameter, public :: ISR_PAIR_RECOIL = 1 @ %def ISR_TRIVIAL_COLLINEAR ISR_PAIR_RECOIL @ <>= procedure :: get_mode_string => evt_isr_epa_get_mode_string <>= module function evt_isr_epa_get_mode_string (evt) result (string) type(string_t) :: string class(evt_isr_epa_t), intent(in) :: evt end function evt_isr_epa_get_mode_string <>= module function evt_isr_epa_get_mode_string (evt) result (string) type(string_t) :: string class(evt_isr_epa_t), intent(in) :: evt select case (evt%mode) case (ISR_TRIVIAL_COLLINEAR) string = "trivial, collinear" case (ISR_PAIR_RECOIL) string = "pair recoil" case default string = "[undefined]" end select end function evt_isr_epa_get_mode_string @ %def evt_isr_epa_get_mode_string @ Set the numerical mode ID from a user-level string representation. <>= procedure :: set_mode_string => evt_isr_epa_set_mode_string <>= module subroutine evt_isr_epa_set_mode_string (evt, string) class(evt_isr_epa_t), intent(inout) :: evt type(string_t), intent(in) :: string end subroutine evt_isr_epa_set_mode_string <>= module subroutine evt_isr_epa_set_mode_string (evt, string) class(evt_isr_epa_t), intent(inout) :: evt type(string_t), intent(in) :: string select case (char (string)) case ("trivial") evt%mode = ISR_TRIVIAL_COLLINEAR case ("recoil") evt%mode = ISR_PAIR_RECOIL case default call msg_fatal ("ISR handler: mode '" // char (string) & // "' is undefined") end select end subroutine evt_isr_epa_set_mode_string @ %def evt_isr_epa_set_mode_string @ \subsection{Output} <>= procedure :: write_name => evt_isr_epa_write_name <>= module subroutine evt_isr_epa_write_name (evt, unit) class(evt_isr_epa_t), intent(in) :: evt integer, intent(in), optional :: unit end subroutine evt_isr_epa_write_name <>= module subroutine evt_isr_epa_write_name (evt, unit) class(evt_isr_epa_t), intent(in) :: evt integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(1x,A)") "Event transform: ISR/EPA handler" end subroutine evt_isr_epa_write_name @ %def evt_isr_epa_write_name @ The overall recoil-handling mode. <>= procedure :: write_mode => evt_isr_epa_write_mode <>= module subroutine evt_isr_epa_write_mode (evt, unit) class(evt_isr_epa_t), intent(in) :: evt integer, intent(in), optional :: unit end subroutine evt_isr_epa_write_mode <>= module subroutine evt_isr_epa_write_mode (evt, unit) class(evt_isr_epa_t), intent(in) :: evt integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(1x,A,1x,I0,':',1x,A)") "Insertion mode =", evt%mode, & char (evt%get_mode_string ()) end subroutine evt_isr_epa_write_mode @ %def evt_isr_epa_write_mode @ The input data for ISR and EPA, respectively. <>= procedure :: write_input => evt_isr_epa_write_input <>= module subroutine evt_isr_epa_write_input (evt, unit, testflag) class(evt_isr_epa_t), intent(in) :: evt integer, intent(in), optional :: unit logical, intent(in), optional :: testflag end subroutine evt_isr_epa_write_input <>= module subroutine evt_isr_epa_write_input (evt, unit, testflag) class(evt_isr_epa_t), intent(in) :: evt integer, intent(in), optional :: unit logical, intent(in), optional :: testflag character(len=7) :: fmt integer :: u u = given_output_unit (unit) call pac_fmt (fmt, FMT_19, FMT_12, testflag) if (evt%isr_active) then write (u, "(3x,A,1x," // fmt // ")") "ISR: Q_max =", evt%isr_q_max write (u, "(3x,A,1x," // fmt // ")") " m =", evt%isr_mass write (u, "(3x,A,1x,L1)") " keep m=", evt%isr_keep_mass else write (u, "(3x,A)") "ISR: [inactive]" end if if (evt%epa_active) then write (u, "(3x,A,1x," // fmt // ")") "EPA: Q_max =", evt%epa_q_max write (u, "(3x,A,1x," // fmt // ")") " m =", evt%epa_mass else write (u, "(3x,A)") "EPA: [inactive]" end if end subroutine evt_isr_epa_write_input @ %def evt_isr_epa_write_input @ The trivial mode does not depend on any data, since it does nothing to the event. <>= procedure :: write_data => evt_isr_epa_write_data <>= module subroutine evt_isr_epa_write_data (evt, unit, testflag) class(evt_isr_epa_t), intent(in) :: evt integer, intent(in), optional :: unit logical, intent(in), optional :: testflag end subroutine evt_isr_epa_write_data <>= module subroutine evt_isr_epa_write_data (evt, unit, testflag) class(evt_isr_epa_t), intent(in) :: evt integer, intent(in), optional :: unit logical, intent(in), optional :: testflag character(len=7), parameter :: FMTL_19 = "A3,16x" character(len=7), parameter :: FMTL_12 = "A3,9x" character(len=7) :: fmt, fmtl integer :: u u = given_output_unit (unit) call pac_fmt (fmt, FMT_19, FMT_12, testflag) call pac_fmt (fmtl, FMTL_19, FMTL_12, testflag) select case (evt%mode) case (ISR_PAIR_RECOIL) write (u, "(1x,A)") "Event:" write (u, "(3x,A,2(1x," // fmtl // "))") & "mode = ", & char (rad_mode_string (evt%rad_mode(1))), & char (rad_mode_string (evt%rad_mode(2))) write (u, "(3x,A,2(1x," // fmt // "))") "Q_max =", evt%q_max write (u, "(3x,A,2(1x," // fmt // "))") "m =", evt%m write (u, "(3x,A,2(1x," // fmt // "))") "x =", evt%xc write (u, "(3x,A,2(1x," // fmt // "))") "xb =", evt%xcb write (u, "(3x,A,1x," // fmt // ")") "sqrts =", evt%sqrts call write_separator (u) write (u, "(A)") "Lorentz boost (partons before radiation & &c.m. -> lab) =" call evt%lti%write (u, testflag) write (u, "(A)") "Lorentz transformation (collinear partons & &-> partons with recoil in c.m.) =" call evt%lto%write (u, testflag) write (u, "(A)") "Combined transformation (partons & &-> partons with recoil in lab frame) =" call evt%lt%write (u, testflag) end select end subroutine evt_isr_epa_write_data @ %def evt_isr_epa_write_data @ Output method. <>= procedure :: write => evt_isr_epa_write <>= module subroutine evt_isr_epa_write & (evt, unit, verbose, more_verbose, testflag) class(evt_isr_epa_t), intent(in) :: evt integer, intent(in), optional :: unit logical, intent(in), optional :: verbose, more_verbose, testflag end subroutine evt_isr_epa_write <>= module subroutine evt_isr_epa_write & (evt, unit, verbose, more_verbose, testflag) class(evt_isr_epa_t), intent(in) :: evt integer, intent(in), optional :: unit logical, intent(in), optional :: verbose, more_verbose, testflag logical :: show_mass integer :: u, i u = given_output_unit (unit) if (present (testflag)) then show_mass = .not. testflag else show_mass = .true. end if call write_separator (u, 2) call evt%write_name (u) call write_separator (u, 2) call evt%write_mode (u) call evt%write_input (u, testflag=testflag) call evt%write_data (u, testflag=testflag) call write_separator (u) call evt%base_write (u, testflag = testflag, show_set = .false.) if (all (evt%i_beam > 0)) then call write_separator (u) write (u, "(A,2(1x,I0))") "Partons before radiation:", evt%i_beam do i = 1, 2 call evt%beam(i)%write (u, testflag=testflag) end do call write_separator (u) write (u, "(A)") "... boosted to c.m.:" do i = 1, 2 call evt%pi(i)%write (u, show_mass=show_mass, testflag=testflag) end do end if if (all (evt%i_radiated > 0)) then call write_separator (u) write (u, "(A,2(1x,I0))") "Radiated particles, collinear:", & evt%i_radiated do i = 1, 2 call evt%radiated(i)%write (u, testflag=testflag) end do call write_separator (u) write (u, "(A)") "... boosted to c.m.:" do i = 1, 2 call evt%ki(i)%write (u, show_mass=show_mass, testflag=testflag) end do call write_separator (u) write (u, "(A)") "... with kT:" do i = 1, 2 call evt%km(i)%write (u, show_mass=show_mass, testflag=testflag) end do end if if (all (evt%i_parton > 0)) then call write_separator (u) write (u, "(A,2(1x,I0))") "Partons after radiation, collinear:", & evt%i_parton do i = 1, 2 call evt%parton(i)%write (u, testflag=testflag) end do call write_separator (u) write (u, "(A)") "... boosted to c.m.:" do i = 1, 2 call evt%qi(i)%write (u, show_mass=show_mass, testflag=testflag) end do call write_separator (u) write (u, "(A)") "... with qT, off-shell:" do i = 1, 2 call evt%qm(i)%write (u, show_mass=show_mass, testflag=testflag) end do call write_separator (u) write (u, "(A)") "... projected on-shell:" do i = 1, 2 call evt%qo(i)%write (u, show_mass=show_mass, testflag=testflag) end do call write_separator (u) end if if (evt%particle_set_exists) & call evt%particle_set%write & (u, summary = .true., compressed = .true., testflag = testflag) call write_separator (u) end subroutine evt_isr_epa_write @ %def evt_isr_epa_write @ \subsection{Initialization} Manually import a random-number generator object. This should be done only for testing purposes. The standard procedure is to [[connect]] a process to an event transform; this will create an appropriate [[rng]] from the RNG factory in the process object. <>= procedure :: import_rng => evt_isr_epa_import_rng <>= module subroutine evt_isr_epa_import_rng (evt, rng) class(evt_isr_epa_t), intent(inout) :: evt class(rng_t), allocatable, intent(inout) :: rng end subroutine evt_isr_epa_import_rng <>= module subroutine evt_isr_epa_import_rng (evt, rng) class(evt_isr_epa_t), intent(inout) :: evt class(rng_t), allocatable, intent(inout) :: rng call move_alloc (from = rng, to = evt%rng) end subroutine evt_isr_epa_import_rng @ %def evt_isr_epa_import_rng @ Set constant kinematics limits and initialize for ISR. Note that [[sqrts]] is used only as the fallback value for [[q_max]]. The actual [[sqrts]] value for the transform object is inferred from the incoming particles, event by event. <>= procedure :: set_data_isr => evt_isr_epa_set_data_isr <>= module subroutine evt_isr_epa_set_data_isr (evt, sqrts, q_max, m, keep_mass) class(evt_isr_epa_t), intent(inout) :: evt real(default), intent(in) :: sqrts real(default), intent(in) :: q_max real(default), intent(in) :: m logical, intent(in) :: keep_mass end subroutine evt_isr_epa_set_data_isr <>= module subroutine evt_isr_epa_set_data_isr (evt, sqrts, q_max, m, keep_mass) class(evt_isr_epa_t), intent(inout) :: evt real(default), intent(in) :: sqrts real(default), intent(in) :: q_max real(default), intent(in) :: m logical, intent(in) :: keep_mass if (sqrts <= 0) then call msg_fatal ("ISR handler: sqrts value must be positive") end if if (q_max <= 0 .or. q_max > sqrts) then evt%isr_q_max = sqrts else evt%isr_q_max = q_max end if if (m > 0) then evt%isr_mass = m else call msg_fatal ("ISR handler: ISR_mass value must be positive") end if evt%isr_active = .true. evt%isr_keep_mass = keep_mass end subroutine evt_isr_epa_set_data_isr @ %def evt_isr_epa_set_data_isr @ Set constant kinematics limits and initialize for EPA. Note that [[sqrts]] is used only as the fallback value for [[q_max]]. The actual [[sqrts]] value for the transform object is inferred from the incoming particles, event by event. <>= procedure :: set_data_epa => evt_isr_epa_set_data_epa <>= module subroutine evt_isr_epa_set_data_epa (evt, sqrts, q_max, m) class(evt_isr_epa_t), intent(inout) :: evt real(default), intent(in) :: sqrts real(default), intent(in) :: q_max real(default), intent(in) :: m end subroutine evt_isr_epa_set_data_epa <>= module subroutine evt_isr_epa_set_data_epa (evt, sqrts, q_max, m) class(evt_isr_epa_t), intent(inout) :: evt real(default), intent(in) :: sqrts real(default), intent(in) :: q_max real(default), intent(in) :: m if (sqrts <= 0) then call msg_fatal ("EPA handler: sqrts value must be positive") end if if (q_max <= 0 .or. q_max > sqrts) then evt%epa_q_max = sqrts else evt%epa_q_max = q_max end if if (m > 0) then evt%epa_mass = m else call msg_fatal ("EPA handler: EPA_mass value must be positive") end if evt%epa_active = .true. end subroutine evt_isr_epa_set_data_epa @ %def evt_isr_epa_set_data_epa @ \subsection{Fetch event data} Identify the radiated particles and the recoil momenta in the particle set. Without much sophistication, start from the end and find particles with the ``remnant'' status. Their parents should point to the recoiling parton. If successful, set the particle indices in the [[evt]] object, for further processing. <>= procedure, private :: identify_radiated <>= module subroutine identify_radiated (evt) class(evt_isr_epa_t), intent(inout) :: evt end subroutine identify_radiated <>= module subroutine identify_radiated (evt) class(evt_isr_epa_t), intent(inout) :: evt integer :: i, k k = 2 FIND_LAST_RADIATED: do i = evt%particle_set%get_n_tot (), 1, -1 associate (prt => evt%particle_set%prt(i)) if (prt%is_beam_remnant ()) then evt%i_radiated(k) = i evt%radiated(k) = prt k = k - 1 if (k == 0) exit FIND_LAST_RADIATED end if end associate end do FIND_LAST_RADIATED if (k /= 0) call err_count contains subroutine err_count call evt%particle_set%write () call msg_fatal ("ISR/EPA handler: & &event does not contain two radiated particles") end subroutine err_count end subroutine identify_radiated @ %def identify_radiated @ When the radiated particles are known, we can fetch their parent particles and ask for the other child, the incoming parton. <>= procedure, private :: identify_partons <>= module subroutine identify_partons (evt) class(evt_isr_epa_t), intent(inout) :: evt end subroutine identify_partons <>= module subroutine identify_partons (evt) class(evt_isr_epa_t), intent(inout) :: evt integer, dimension(:), allocatable :: parent, child integer :: i, j if (all (evt%i_radiated > 0)) then do i = 1, 2 parent = evt%radiated(i)%get_parents () if (size (parent) /= 1) call err_mismatch evt%i_beam(i) = parent(1) evt%beam(i) = evt%particle_set%prt(parent(1)) associate (prt => evt%beam(i)) child = prt%get_children () if (size (child) /= 2) call err_mismatch do j = 1, 2 if (child(j) /= evt%i_radiated(i)) then evt%i_parton(i) = child(j) evt%parton(i) = evt%particle_set%prt(child(j)) end if end do end associate end do end if contains subroutine err_mismatch call evt%particle_set%write () call msg_bug ("ISR/EPA handler: mismatch in parent-child relations") end subroutine err_mismatch end subroutine identify_partons @ %def identify_partons @ Check whether the radiated particle is a photon, or the incoming parton is a photon. Then set the ISR/EPA switch appropriately, for each beam. <>= procedure :: check_radiation => evt_isr_epa_check_radiation <>= module subroutine evt_isr_epa_check_radiation (evt) class(evt_isr_epa_t), intent(inout) :: evt end subroutine evt_isr_epa_check_radiation <>= module subroutine evt_isr_epa_check_radiation (evt) class(evt_isr_epa_t), intent(inout) :: evt type(flavor_t) :: flv integer :: i do i = 1, 2 flv = evt%radiated(i)%get_flv () if (flv%get_pdg () == PHOTON) then if (evt%isr_active) then evt%rad_mode(i) = BEAM_RAD_ISR else call err_isr_init end if else flv = evt%parton(i)%get_flv () if (flv%get_pdg () == PHOTON) then if (evt%epa_active) then evt%rad_mode(i) = BEAM_RAD_EPA else call err_epa_init end if else call err_no_photon end if end if end do contains subroutine err_isr_init call evt%particle_set%write () call msg_fatal ("ISR/EPA handler: & &event contains radiated photon, but ISR is not initialized") end subroutine err_isr_init subroutine err_epa_init call evt%particle_set%write () call msg_fatal ("ISR/EPA handler: & &event contains incoming photon, but EPA is not initialized") end subroutine err_epa_init subroutine err_no_photon call evt%particle_set%write () call msg_fatal ("ISR/EPA handler: & &event does not appear to be ISR or EPA - missing photon") end subroutine err_no_photon end subroutine evt_isr_epa_check_radiation @ %def evt_isr_epa_check_radiation @ Internally set the appropriate parameters (ISR/EPA) for the two beams in the recoil mode. <>= procedure :: set_recoil_parameters => evt_isr_epa_set_recoil_parameters <>= module subroutine evt_isr_epa_set_recoil_parameters (evt) class(evt_isr_epa_t), intent(inout) :: evt end subroutine evt_isr_epa_set_recoil_parameters <>= module subroutine evt_isr_epa_set_recoil_parameters (evt) class(evt_isr_epa_t), intent(inout) :: evt integer :: i do i = 1, 2 select case (evt%rad_mode(i)) case (BEAM_RAD_ISR) evt%q_max(i) = evt%isr_q_max evt%m(i) = evt%isr_mass case (BEAM_RAD_EPA) evt%q_max(i) = evt%epa_q_max evt%m(i) = evt%epa_mass end select end do end subroutine evt_isr_epa_set_recoil_parameters @ %def evt_isr_epa_set_recoil_parameters @ Boost the particles that participate in ISR to their proper c.m.\ frame, copying the momenta to [[pi]], [[ki]], [[qi]]. Also assign [[sqrts]] properly. <>= procedure, private :: boost_to_cm <>= module subroutine boost_to_cm (evt) class(evt_isr_epa_t), intent(inout) :: evt end subroutine boost_to_cm <>= module subroutine boost_to_cm (evt) class(evt_isr_epa_t), intent(inout) :: evt type(vector4_t), dimension(2) :: p type(vector4_t), dimension(2) :: k type(vector4_t), dimension(2) :: q logical :: ok p = evt%beam%get_momentum () k = evt%radiated%get_momentum () q = evt%parton%get_momentum () call initial_transformation (p, evt%sqrts, evt%lti, ok) if (.not. ok) call err_non_collinear evt%pi = inverse (evt%lti) * p evt%ki = inverse (evt%lti) * k evt%qi = inverse (evt%lti) * q contains subroutine err_non_collinear call evt%particle_set%write () call msg_fatal ("ISR/EPA handler: & &partons before radiation are not collinear") end subroutine err_non_collinear end subroutine boost_to_cm @ %def boost_to_cm @ We can infer the $x$ and $\bar x$ values of the event by looking at the energy fractions of the radiated particles and incoming partons, respectively, relative to their parents. Of course, we must assume that they are all collinear, and that energy is conserved. <>= procedure, private :: infer_x <>= module subroutine infer_x (evt) class(evt_isr_epa_t), intent(inout) :: evt end subroutine infer_x <>= module subroutine infer_x (evt) class(evt_isr_epa_t), intent(inout) :: evt real(default) :: E_parent, E_radiated, E_parton integer :: i if (all (evt%i_radiated > 0)) then do i = 1, 2 E_parent = energy (evt%pi(i)) E_radiated = energy (evt%ki(i)) E_parton = energy (evt%qi(i)) if (E_parent > 0) then evt%xc(i) = E_parton / E_parent evt%xcb(i)= E_radiated / E_parent else call err_energy end if end do end if contains subroutine err_energy call evt%particle_set%write () call msg_bug ("ISR/EPA handler: non-positive energy in splitting") end subroutine err_energy end subroutine infer_x @ %def infer_x @ \subsection{Two-parton recoil} For transforming partons into recoil momenta, we make use of the routines in the [[recoil_kinematics]] module. In addition to the collinear momenta, we use the $x$ energy fractions, and four numbers from the RNG. There is one subtle difference w.r.t.\ ISR case: the EPA mass parameter is multiplied by the energy fraction $x$, separately for each beam. This is the effective lower $Q$ cutoff. For certain kinematics, close to the $Q_\text{max}$ endpoint, this may fail, and [[ok]] is set to false. In that case, we should generate new recoil momenta for the same event. This is handled by the generic unweighting procedure. <>= procedure, private :: generate_recoil => evt_generate_recoil <>= module subroutine evt_generate_recoil (evt, ok) class(evt_isr_epa_t), intent(inout) :: evt logical, intent(out) :: ok end subroutine evt_generate_recoil <>= module subroutine evt_generate_recoil (evt, ok) class(evt_isr_epa_t), intent(inout) :: evt logical, intent(out) :: ok real(default), dimension(4) :: r real(default), dimension(2) :: m, mo integer :: i call evt%rng%generate (r) m = 0 mo = 0 do i = 1, 2 select case (evt%rad_mode(i)) case (BEAM_RAD_ISR) m(i) = evt%m(i) if (evt%isr_keep_mass) mo(i) = m(i) case (BEAM_RAD_EPA) m(i) = evt%xc(i) * evt%m(i) end select end do call generate_recoil (evt%sqrts, evt%q_max, m, mo, evt%xc, evt%xcb, r, & evt%km, evt%qm, evt%qo, ok) end subroutine evt_generate_recoil @ %def evt_generate_recoil @ Replace the collinear radiated (incoming) parton momenta by the momenta that we have generated, respectively. Recall that the recoil has been applied in the c.m.\ system of the partons before ISR, so we apply the stored Lorentz transformation to boost them to the lab frame. <>= procedure, private :: replace_radiated procedure, private :: replace_partons <>= module subroutine replace_radiated (evt) class(evt_isr_epa_t), intent(inout) :: evt end subroutine replace_radiated module subroutine replace_partons (evt) class(evt_isr_epa_t), intent(inout) :: evt end subroutine replace_partons <>= module subroutine replace_radiated (evt) class(evt_isr_epa_t), intent(inout) :: evt integer :: i do i = 1, 2 associate (prt => evt%particle_set%prt(evt%i_radiated(i))) call prt%set_momentum (evt%lti * evt%km(i)) end associate end do end subroutine replace_radiated module subroutine replace_partons (evt) class(evt_isr_epa_t), intent(inout) :: evt integer :: i do i = 1, 2 associate (prt => evt%particle_set%prt(evt%i_parton(i))) call prt%set_momentum (evt%lti * evt%qo(i)) end associate end do end subroutine replace_partons @ %def replace_radiated @ %def replace_partons @ \subsection{Transform the event} Knowing the new incoming partons for the elementary process, we can make use of another procedure in [[recoil_kinematics]] to determine the Lorentz transformation that transforms the collinear frame into the frame with transverse momentum. We apply this transformation, recursively, to all particles that originate from those incoming partons in the original particle set. We have to allow for the pre-ISR partons being not in their common c.m.\ frame. Taking into account non-commutativity, we actually have to first transform the outgoing particles to that c.m.\ frame, then apply the recoil transformation, then boost back to the lab frame. The [[mask]] keep track of particles that we transform, just in case the parent-child tree is multiply connected. <>= procedure :: transform_outgoing => evt_transform_outgoing <>= module subroutine evt_transform_outgoing (evt) class(evt_isr_epa_t), intent(inout) :: evt end subroutine evt_transform_outgoing <>= module subroutine evt_transform_outgoing (evt) class(evt_isr_epa_t), intent(inout) :: evt logical, dimension(:), allocatable :: mask call recoil_transformation (evt%sqrts, evt%xc, evt%qo, evt%lto) evt%lt = evt%lti * evt%lto * inverse (evt%lti) allocate (mask (evt%particle_set%get_n_tot ()), source=.false.) call transform_children (evt%i_parton(1)) contains recursive subroutine transform_children (i) integer, intent(in) :: i integer :: j, n_child, c integer, dimension(:), allocatable :: child child = evt%particle_set%prt(i)%get_children () do j = 1, size (child) c = child(j) if (.not. mask(c)) then associate (prt => evt%particle_set%prt(c)) call prt%set_momentum (evt%lt * prt%get_momentum ()) mask(c) = .true. call transform_children (c) end associate end if end do end subroutine transform_children end subroutine evt_transform_outgoing @ %def evt_transform_outgoing @ \subsection{Implemented methods} Here we take the particle set from the previous event transform and copy it, then generate the transverse momentum for the radiated particles and for the incoming partons. If this fails (rarely, for large $p_T$), return zero for the probability, to trigger another try. NOTE: The boost for the initial partonic system, if not in the c.m.\ frame, has not been implemented yet. <>= procedure :: generate_weighted => & evt_isr_epa_generate_weighted <>= module subroutine evt_isr_epa_generate_weighted (evt, probability) class(evt_isr_epa_t), intent(inout) :: evt real(default), intent(inout) :: probability end subroutine evt_isr_epa_generate_weighted <>= module subroutine evt_isr_epa_generate_weighted (evt, probability) class(evt_isr_epa_t), intent(inout) :: evt real(default), intent(inout) :: probability logical :: valid call evt%particle_set%final () evt%particle_set = evt%previous%particle_set evt%particle_set_exists = .true. select case (evt%mode) case (ISR_TRIVIAL_COLLINEAR) probability = 1 valid = .true. case (ISR_PAIR_RECOIL) call evt%identify_radiated () call evt%identify_partons () call evt%check_radiation () call evt%set_recoil_parameters () call evt%boost_to_cm () call evt%infer_x () call evt%generate_recoil (valid) if (valid) then probability = 1 else probability = 0 end if case default call msg_bug ("ISR/EPA handler: generate weighted: unsupported mode") end select evt%particle_set_exists = .false. end subroutine evt_isr_epa_generate_weighted @ %def evt_isr_epa_generate_weighted @ Insert the generated radiated particles and incoming partons with $p_T$ in their respective places. The factorization parameters are irrelevant. <>= procedure :: make_particle_set => & evt_isr_epa_make_particle_set <>= module subroutine evt_isr_epa_make_particle_set & (evt, factorization_mode, keep_correlations, r) class(evt_isr_epa_t), intent(inout) :: evt integer, intent(in) :: factorization_mode logical, intent(in) :: keep_correlations real(default), dimension(:), intent(in), optional :: r end subroutine evt_isr_epa_make_particle_set <>= module subroutine evt_isr_epa_make_particle_set & (evt, factorization_mode, keep_correlations, r) class(evt_isr_epa_t), intent(inout) :: evt integer, intent(in) :: factorization_mode logical, intent(in) :: keep_correlations real(default), dimension(:), intent(in), optional :: r select case (evt%mode) case (ISR_TRIVIAL_COLLINEAR) case (ISR_PAIR_RECOIL) call evt%replace_radiated () call evt%replace_partons () call evt%transform_outgoing () case default call msg_bug ("ISR/EPA handler: make particle set: unsupported mode") end select evt%particle_set_exists = .true. end subroutine evt_isr_epa_make_particle_set @ %def event_isr_epa_handler_make_particle_set @ <>= procedure :: prepare_new_event => & evt_isr_epa_prepare_new_event <>= module subroutine evt_isr_epa_prepare_new_event (evt, i_mci, i_term) class(evt_isr_epa_t), intent(inout) :: evt integer, intent(in) :: i_mci, i_term end subroutine evt_isr_epa_prepare_new_event <>= module subroutine evt_isr_epa_prepare_new_event (evt, i_mci, i_term) class(evt_isr_epa_t), intent(inout) :: evt integer, intent(in) :: i_mci, i_term call evt%reset () end subroutine evt_isr_epa_prepare_new_event @ %def evt_isr_epa_prepare_new_event @ \subsection{Unit tests: ISR} Test module, followed by the corresponding implementation module. This test module differs from most of the other test modules, since it contains two test subroutines: one for ISR and one for EPA below. <<[[isr_epa_handler_ut.f90]]>>= <> module isr_epa_handler_ut use unit_tests use isr_epa_handler_uti <> <> contains <> end module isr_epa_handler_ut @ %def isr_epa_handler_ut @ <<[[isr_epa_handler_uti.f90]]>>= <> module isr_epa_handler_uti <> <> use format_utils, only: write_separator use os_interface use lorentz, only: vector4_t, vector4_moving, operator(*) use rng_base, only: rng_t use models, only: syntax_model_file_init, syntax_model_file_final use models, only: model_list_t, model_t use particles, only: particle_set_t use event_transforms use isr_epa_handler, only: evt_isr_epa_t use rng_base_ut, only: rng_test_t <> <> contains <> end module isr_epa_handler_uti @ %def isr_epa_handler_uti @ API: driver for the unit tests below. <>= public :: isr_handler_test <>= subroutine isr_handler_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine isr_handler_test @ %def isr_handler_test @ \subsubsection{Trivial case} Handle photons resulting from ISR radiation. This test is for the trivial case where the event is kept collinear. <>= call test (isr_handler_1, "isr_handler_1", & "collinear case, no modification", & u, results) <>= public :: isr_handler_1 <>= subroutine isr_handler_1 (u) integer, intent(in) :: u type(os_data_t) :: os_data type(particle_set_t) :: pset type(model_list_t) :: model_list type(model_t), pointer :: model type(evt_trivial_t), target :: evt_trivial type(evt_isr_epa_t), target :: evt_isr_epa type(vector4_t), dimension(8) :: p real(default) :: sqrts real(default), dimension(2) :: x, xb real(default) :: probability write (u, "(A)") "* Test output: isr_handler_1" write (u, "(A)") "* Purpose: apply photon handler trivially (no-op)" write (u, "(A)") write (u, "(A)") "* Initialize environment" write (u, "(A)") call syntax_model_file_init () call os_data%init () call model_list%read_model & (var_str ("SM"), var_str ("SM.mdl"), & os_data, model) write (u, "(A)") "* Initialize particle set" write (u, "(A)") call pset%init_direct (n_beam = 2, n_in = 2, n_rem = 2, n_vir = 0, n_out = 2, & pdg = [11, -11, 11, -11, 22, 22, 13, -13], model = model) sqrts = 100._default x = [0.6_default, 0.9_default] xb= 1 - x p(1) = vector4_moving (sqrts/2, sqrts/2, 3) p(2) = vector4_moving (sqrts/2,-sqrts/2, 3) p(3:4) = x * p(1:2) p(5:6) = xb * p(1:2) p(7:8) = p(3:4) call pset%set_momentum (p, on_shell = .false.) write (u, "(A)") "* Fill trivial event transform" write (u, "(A)") call evt_trivial%reset () call evt_trivial%set_particle_set (pset, 1, 1) call evt_trivial%write (u) call write_separator (u, 2) write (u, "(A)") write (u, "(A)") "* Initialize ISR handler transform" write (u, "(A)") evt_trivial%next => evt_isr_epa evt_isr_epa%previous => evt_trivial call evt_isr_epa%write (u) write (u, "(A)") write (u, "(A)") "* Fill ISR handler transform" write (u, "(A)") call evt_isr_epa%prepare_new_event (1, 1) call evt_isr_epa%generate_weighted (probability) call evt_isr_epa%make_particle_set (0, .false.) call evt_isr_epa%write (u) write (u, "(A)") write (u, "(A,1x,F8.5)") "Event probability =", probability write (u, "(A)") write (u, "(A)") "* Cleanup" call evt_isr_epa%final () call evt_trivial%final () call syntax_model_file_final () write (u, "(A)") write (u, "(A)") "* Test output end: isr_handler_1" end subroutine isr_handler_1 @ %def isr_handler_1 @ \subsubsection{Photon pair with recoil} Handle photons resulting from ISR radiation. This test invokes the two-photon recoil mechanism. Both photons acquire transverse momentum, the parton momenta recoil, such that total energy-momentum is conserved, and all outgoing photons and partons are on-shell (massless). <>= call test (isr_handler_2, "isr_handler_2", & "two-photon recoil", & u, results) <>= public :: isr_handler_2 <>= subroutine isr_handler_2 (u) integer, intent(in) :: u type(os_data_t) :: os_data type(particle_set_t) :: pset type(model_list_t) :: model_list type(model_t), pointer :: model type(evt_trivial_t), target :: evt_trivial type(evt_isr_epa_t), target :: evt_isr_epa type(vector4_t), dimension(8) :: p real(default) :: sqrts real(default), dimension(2) :: x, xb class(rng_t), allocatable :: rng real(default) :: probability write (u, "(A)") "* Test output: isr_handler_2" write (u, "(A)") "* Purpose: apply photon handler with two-photon recoil" write (u, "(A)") write (u, "(A)") "* Initialize environment" write (u, "(A)") call syntax_model_file_init () call os_data%init () call model_list%read_model & (var_str ("SM"), var_str ("SM.mdl"), & os_data, model) write (u, "(A)") "* Initialize particle set" write (u, "(A)") call pset%init_direct (n_beam = 2, n_in = 2, n_rem = 2, n_vir = 0, n_out = 2, & pdg = [11, -11, 11, -11, 22, 22, 13, -13], model = model) sqrts = 100._default x = [0.6_default, 0.9_default] xb= 1 - x p(1) = vector4_moving (sqrts/2, sqrts/2, 3) p(2) = vector4_moving (sqrts/2,-sqrts/2, 3) p(3:4) = x * p(1:2) p(5:6) = xb * p(1:2) p(7:8) = p(3:4) call pset%set_momentum (p, on_shell = .false.) write (u, "(A)") "* Fill trivial event transform" write (u, "(A)") call evt_trivial%reset () call evt_trivial%set_particle_set (pset, 1, 1) call evt_trivial%write (u) call write_separator (u, 2) write (u, "(A)") write (u, "(A)") "* Initialize ISR handler transform" write (u, "(A)") evt_trivial%next => evt_isr_epa evt_isr_epa%previous => evt_trivial call evt_isr_epa%set_mode_string (var_str ("recoil")) call evt_isr_epa%set_data_isr ( & sqrts = sqrts, & q_max = sqrts, & m = 511.e-3_default, & keep_mass = .false. & ) allocate (rng_test_t :: rng) call rng%init (3) ! default would produce pi for azimuthal angle call evt_isr_epa%import_rng (rng) call evt_isr_epa%write (u, testflag=.true.) write (u, "(A)") write (u, "(A)") "* Fill ISR handler transform" write (u, "(A)") call evt_isr_epa%prepare_new_event (1, 1) call evt_isr_epa%generate_weighted (probability) call evt_isr_epa%make_particle_set (0, .false.) call evt_isr_epa%write (u, testflag=.true.) write (u, "(A)") write (u, "(A,1x,F8.5)") "Event probability =", probability write (u, "(A)") write (u, "(A)") "* Cleanup" call evt_isr_epa%final () call evt_trivial%final () call syntax_model_file_final () write (u, "(A)") write (u, "(A)") "* Test output end: isr_handler_2" end subroutine isr_handler_2 @ %def isr_handler_2 @ \subsubsection{Boosted beams} Handle photons resulting from ISR radiation. This test invokes the two-photon recoil mechanism, in the case that the partons before ISR are not in their c.m.\ frame (but collinear). <>= call test (isr_handler_3, "isr_handler_3", & "two-photon recoil with boost", & u, results) <>= public :: isr_handler_3 <>= subroutine isr_handler_3 (u) integer, intent(in) :: u type(os_data_t) :: os_data type(particle_set_t) :: pset type(model_list_t) :: model_list type(model_t), pointer :: model type(evt_trivial_t), target :: evt_trivial type(evt_isr_epa_t), target :: evt_isr_epa type(vector4_t), dimension(8) :: p real(default) :: sqrts real(default), dimension(2) :: x0 real(default), dimension(2) :: x, xb class(rng_t), allocatable :: rng real(default) :: probability write (u, "(A)") "* Test output: isr_handler_3" write (u, "(A)") "* Purpose: apply photon handler for boosted beams & &and two-photon recoil" write (u, "(A)") write (u, "(A)") "* Initialize environment" write (u, "(A)") call syntax_model_file_init () call os_data%init () call model_list%read_model & (var_str ("SM"), var_str ("SM.mdl"), & os_data, model) write (u, "(A)") "* Initialize particle set" write (u, "(A)") call pset%init_direct (n_beam = 2, n_in = 2, n_rem = 2, n_vir = 0, n_out = 2, & pdg = [11, -11, 11, -11, 22, 22, 13, -13], model = model) write (u, "(A)") "* Event data" write (u, "(A)") sqrts = 100._default write (u, "(A,2(1x,F12.7))") "sqrts =", sqrts x0 = [0.9_default, 0.4_default] write (u, "(A,2(1x,F12.7))") "x0 =", x0 write (u, "(A)") write (u, "(A,2(1x,F12.7))") "sqs_hat =", sqrts * sqrt (product (x0)) x = [0.6_default, 0.9_default] xb= 1 - x write (u, "(A,2(1x,F12.7))") "x =", x write (u, "(A)") write (u, "(A,2(1x,F12.7))") "x0 * x =", x0 * x p(1) = x0(1) * vector4_moving (sqrts/2, sqrts/2, 3) p(2) = x0(2) * vector4_moving (sqrts/2,-sqrts/2, 3) p(3:4) = x * p(1:2) p(5:6) = xb * p(1:2) p(7:8) = p(3:4) call pset%set_momentum (p, on_shell = .false.) write (u, "(A)") write (u, "(A)") "* Fill trivial event transform" write (u, "(A)") call evt_trivial%reset () call evt_trivial%set_particle_set (pset, 1, 1) call evt_trivial%write (u) call write_separator (u, 2) write (u, "(A)") write (u, "(A)") "* Initialize ISR handler transform" write (u, "(A)") evt_trivial%next => evt_isr_epa evt_isr_epa%previous => evt_trivial call evt_isr_epa%set_mode_string (var_str ("recoil")) call evt_isr_epa%set_data_isr ( & sqrts = sqrts, & q_max = sqrts, & m = 511.e-3_default, & keep_mass = .false. & ) allocate (rng_test_t :: rng) call rng%init (3) ! default would produce pi for azimuthal angle call evt_isr_epa%import_rng (rng) call evt_isr_epa%write (u, testflag=.true.) write (u, "(A)") write (u, "(A)") "* Fill ISR handler transform" write (u, "(A)") call evt_isr_epa%prepare_new_event (1, 1) call evt_isr_epa%generate_weighted (probability) call evt_isr_epa%make_particle_set (0, .false.) call evt_isr_epa%write (u, testflag=.true.) write (u, "(A)") write (u, "(A,1x,F8.5)") "Event probability =", probability write (u, "(A)") write (u, "(A)") "* Cleanup" call evt_isr_epa%final () call evt_trivial%final () call syntax_model_file_final () write (u, "(A)") write (u, "(A)") "* Test output end: isr_handler_3" end subroutine isr_handler_3 @ %def isr_handler_3 @ \subsection{Unit tests: EPA} API: Extra driver for the unit tests below. <>= public :: epa_handler_test <>= subroutine epa_handler_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine epa_handler_test @ %def epa_handler_test @ \subsubsection{Trivial case} Handle events resulting from the EPA approximation. This test is for the trivial case where the event is kept collinear. <>= call test (epa_handler_1, "epa_handler_1", & "collinear case, no modification", & u, results) <>= public :: epa_handler_1 <>= subroutine epa_handler_1 (u) integer, intent(in) :: u type(os_data_t) :: os_data type(particle_set_t) :: pset type(model_list_t) :: model_list type(model_t), pointer :: model type(evt_trivial_t), target :: evt_trivial type(evt_isr_epa_t), target :: evt_isr_epa type(vector4_t), dimension(8) :: p real(default) :: sqrts real(default), dimension(2) :: x, xb real(default) :: probability write (u, "(A)") "* Test output: epa_handler_1" write (u, "(A)") "* Purpose: apply beam handler trivially (no-op)" write (u, "(A)") write (u, "(A)") "* Initialize environment" write (u, "(A)") call syntax_model_file_init () call os_data%init () call model_list%read_model & (var_str ("SM"), var_str ("SM.mdl"), & os_data, model) write (u, "(A)") "* Initialize particle set" write (u, "(A)") call pset%init_direct & (n_beam = 2, n_in = 2, n_rem = 2, n_vir = 0, n_out = 2, & pdg = [11, -11, 22, 22, 11, -11, 13, -13], & model = model) sqrts = 100._default x = [0.6_default, 0.9_default] xb= 1 - x p(1) = vector4_moving (sqrts/2, sqrts/2, 3) p(2) = vector4_moving (sqrts/2,-sqrts/2, 3) p(3:4) = x * p(1:2) p(5:6) = xb * p(1:2) p(7:8) = p(3:4) call pset%set_momentum (p, on_shell = .false.) write (u, "(A)") "* Fill trivial event transform" write (u, "(A)") call evt_trivial%reset () call evt_trivial%set_particle_set (pset, 1, 1) call evt_trivial%write (u) call write_separator (u, 2) write (u, "(A)") write (u, "(A)") "* Initialize EPA handler transform" write (u, "(A)") evt_trivial%next => evt_isr_epa evt_isr_epa%previous => evt_trivial call evt_isr_epa%write (u) write (u, "(A)") write (u, "(A)") "* Fill EPA handler transform" write (u, "(A)") call evt_isr_epa%prepare_new_event (1, 1) call evt_isr_epa%generate_weighted (probability) call evt_isr_epa%make_particle_set (0, .false.) call evt_isr_epa%write (u) write (u, "(A)") write (u, "(A,1x,F8.5)") "Event probability =", probability write (u, "(A)") write (u, "(A)") "* Cleanup" call evt_isr_epa%final () call evt_trivial%final () call syntax_model_file_final () write (u, "(A)") write (u, "(A)") "* Test output end: epa_handler_1" end subroutine epa_handler_1 @ %def epa_handler_1 @ \subsubsection{Beam pair with recoil} Handle beams resulting from the EPA approximation. This test invokes the two-beam recoil mechanism. Both beam remnants acquire transverse momentum, the photon momenta recoil, such that total energy-momentum is conserved, and all outgoing beam remnants and photons are on-shell (massless). <>= call test (epa_handler_2, "epa_handler_2", & "two-beam recoil", & u, results) <>= public :: epa_handler_2 <>= subroutine epa_handler_2 (u) integer, intent(in) :: u type(os_data_t) :: os_data type(particle_set_t) :: pset type(model_list_t) :: model_list type(model_t), pointer :: model type(evt_trivial_t), target :: evt_trivial type(evt_isr_epa_t), target :: evt_isr_epa type(vector4_t), dimension(8) :: p real(default) :: sqrts real(default), dimension(2) :: x, xb class(rng_t), allocatable :: rng real(default) :: probability write (u, "(A)") "* Test output: epa_handler_2" write (u, "(A)") "* Purpose: apply beam handler with two-beam recoil" write (u, "(A)") write (u, "(A)") "* Initialize environment" write (u, "(A)") call syntax_model_file_init () call os_data%init () call model_list%read_model & (var_str ("SM"), var_str ("SM.mdl"), & os_data, model) write (u, "(A)") "* Initialize particle set" write (u, "(A)") call pset%init_direct (n_beam = 2, n_in = 2, n_rem = 2, n_vir = 0, n_out = 2, & pdg = [11, -11, 22, 22, 11, -11, 13, -13], model = model) sqrts = 100._default x = [0.6_default, 0.9_default] xb= 1 - x p(1) = vector4_moving (sqrts/2, sqrts/2, 3) p(2) = vector4_moving (sqrts/2,-sqrts/2, 3) p(3:4) = x * p(1:2) p(5:6) = xb * p(1:2) p(7:8) = p(3:4) call pset%set_momentum (p, on_shell = .false.) write (u, "(A)") "* Fill trivial event transform" write (u, "(A)") call evt_trivial%reset () call evt_trivial%set_particle_set (pset, 1, 1) call evt_trivial%write (u) call write_separator (u, 2) write (u, "(A)") write (u, "(A)") "* Initialize EPA handler transform" write (u, "(A)") evt_trivial%next => evt_isr_epa evt_isr_epa%previous => evt_trivial call evt_isr_epa%set_mode_string (var_str ("recoil")) call evt_isr_epa%set_data_epa ( & sqrts = sqrts, & q_max = sqrts, & m = 511.e-3_default & ) allocate (rng_test_t :: rng) call rng%init (3) ! default would produce pi for azimuthal angle call evt_isr_epa%import_rng (rng) call evt_isr_epa%write (u, testflag=.true.) write (u, "(A)") write (u, "(A)") "* Fill EPA handler transform" write (u, "(A)") call evt_isr_epa%prepare_new_event (1, 1) call evt_isr_epa%generate_weighted (probability) call evt_isr_epa%make_particle_set (0, .false.) call evt_isr_epa%write (u, testflag=.true.) write (u, "(A)") write (u, "(A,1x,F8.5)") "Event probability =", probability write (u, "(A)") write (u, "(A)") "* Cleanup" call evt_isr_epa%final () call evt_trivial%final () call syntax_model_file_final () write (u, "(A)") write (u, "(A)") "* Test output end: epa_handler_2" end subroutine epa_handler_2 @ %def epa_handler_2 @ \subsubsection{Boosted beams} Handle radiated beam remnants resulting from EPA radiation. This test invokes the two-beam recoil mechanism, in the case that the partons before EPA are not in their c.m.\ frame (but collinear). <>= call test (epa_handler_3, "epa_handler_3", & "two-beam recoil with boost", & u, results) <>= public :: epa_handler_3 <>= subroutine epa_handler_3 (u) integer, intent(in) :: u type(os_data_t) :: os_data type(particle_set_t) :: pset type(model_list_t) :: model_list type(model_t), pointer :: model type(evt_trivial_t), target :: evt_trivial type(evt_isr_epa_t), target :: evt_isr_epa type(vector4_t), dimension(8) :: p real(default) :: sqrts real(default), dimension(2) :: x0 real(default), dimension(2) :: x, xb class(rng_t), allocatable :: rng real(default) :: probability write (u, "(A)") "* Test output: epa_handler_3" write (u, "(A)") "* Purpose: apply beam handler for boosted beams & &and two-beam recoil" write (u, "(A)") write (u, "(A)") "* Initialize environment" write (u, "(A)") call syntax_model_file_init () call os_data%init () call model_list%read_model & (var_str ("SM"), var_str ("SM.mdl"), & os_data, model) write (u, "(A)") "* Initialize particle set" write (u, "(A)") call pset%init_direct (n_beam = 2, n_in = 2, n_rem = 2, n_vir = 0, n_out = 2, & pdg = [11, -11, 22, 22, 11, -11, 13, -13], model = model) write (u, "(A)") "* Event data" write (u, "(A)") sqrts = 100._default write (u, "(A,2(1x,F12.7))") "sqrts =", sqrts x0 = [0.9_default, 0.4_default] write (u, "(A,2(1x,F12.7))") "x0 =", x0 write (u, "(A)") write (u, "(A,2(1x,F12.7))") "sqs_hat =", sqrts * sqrt (product (x0)) x = [0.6_default, 0.9_default] xb= 1 - x write (u, "(A,2(1x,F12.7))") "x =", x write (u, "(A)") write (u, "(A,2(1x,F12.7))") "x0 * x =", x0 * x p(1) = x0(1) * vector4_moving (sqrts/2, sqrts/2, 3) p(2) = x0(2) * vector4_moving (sqrts/2,-sqrts/2, 3) p(3:4) = x * p(1:2) p(5:6) = xb * p(1:2) p(7:8) = p(3:4) call pset%set_momentum (p, on_shell = .false.) write (u, "(A)") write (u, "(A)") "* Fill trivial event transform" write (u, "(A)") call evt_trivial%reset () call evt_trivial%set_particle_set (pset, 1, 1) call evt_trivial%write (u) call write_separator (u, 2) write (u, "(A)") write (u, "(A)") "* Initialize EPA handler transform" write (u, "(A)") evt_trivial%next => evt_isr_epa evt_isr_epa%previous => evt_trivial call evt_isr_epa%set_mode_string (var_str ("recoil")) call evt_isr_epa%set_data_epa ( & sqrts = sqrts, & q_max = sqrts, & m = 511.e-3_default & ) allocate (rng_test_t :: rng) call rng%init (3) ! default would produce pi for azimuthal angle call evt_isr_epa%import_rng (rng) call evt_isr_epa%write (u, testflag=.true.) write (u, "(A)") write (u, "(A)") "* Fill EPA handler transform" write (u, "(A)") call evt_isr_epa%prepare_new_event (1, 1) call evt_isr_epa%generate_weighted (probability) call evt_isr_epa%make_particle_set (0, .false.) call evt_isr_epa%write (u, testflag=.true.) write (u, "(A)") write (u, "(A,1x,F8.5)") "Event probability =", probability write (u, "(A)") write (u, "(A)") "* Cleanup" call evt_isr_epa%final () call evt_trivial%final () call syntax_model_file_final () write (u, "(A)") write (u, "(A)") "* Test output end: epa_handler_3" end subroutine epa_handler_3 @ %def epa_handler_3 @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Decays} <<[[decays.f90]]>>= <> module decays <> <> use diagnostics use flavors use interactions use evaluators use variables, only: var_list_t use model_data use rng_base use selectors use parton_states use process, only: process_t use instances, only: process_instance_t, pacify use process_stacks use event_transforms <> <> <> <> interface <> end interface contains <> end module decays @ %def decays @ <<[[decays_sub.f90]]>>= <> submodule (decays) decays_s use io_units use format_utils, only: write_indent, write_separator use format_defs, only: FMT_15 use numeric_utils use helicities use quantum_numbers implicit none contains <> end submodule decays_s @ %def decays_s @ \subsection{Final-State Particle Configuration} A final-state particle may be either stable or unstable. Here is an empty abstract type as the parent of both, with holds just the flavor information. <>= type, abstract :: any_config_t private contains <> end type any_config_t @ %def any_config_t @ Finalizer, depends on the implementation. <>= procedure (any_config_final), deferred :: final <>= interface subroutine any_config_final (object) import class(any_config_t), intent(inout) :: object end subroutine any_config_final end interface @ %def any_config_final @ The output is also deferred: <>= procedure (any_config_write), deferred :: write <>= interface subroutine any_config_write (object, unit, indent, verbose) import class(any_config_t), intent(in) :: object integer, intent(in), optional :: unit, indent logical, intent(in), optional :: verbose end subroutine any_config_write end interface @ %def any_config_write @ This is a container for a stable or unstable particle configurator. We need this wrapper for preparing arrays that mix stable and unstable particles. <>= type :: particle_config_t private class(any_config_t), allocatable :: c end type particle_config_t @ %def particle_config_t @ \subsection{Final-State Particle} In theory, for the particle instance we only need to consider the unstable case. However, it is more straightforward to treat configuration and instance on the same footing, and to introduce a wrapper for particle objects as above. <>= type, abstract :: any_t private contains <> end type any_t @ %def any_t @ Finalizer, depends on the implementation. <>= procedure (any_final), deferred :: final <>= interface subroutine any_final (object) import class(any_t), intent(inout) :: object end subroutine any_final end interface @ %def any_final @ The output is also deferred: <>= procedure (any_write), deferred :: write <>= interface subroutine any_write (object, unit, indent) import class(any_t), intent(in) :: object integer, intent(in), optional :: unit, indent end subroutine any_write end interface @ %def any_write @ This is a container for a stable or unstable outgoing particle. We need this wrapper for preparing arrays that mix stable and unstable particles. <>= type :: particle_out_t private class(any_t), allocatable :: c end type particle_out_t @ %def particle_config_t @ \subsection{Decay Term Configuration} A decay term is a distinct final state, corresponding to a process term. Each decay process may give rise to several terms with, possibly, differing flavor content. <>= type :: decay_term_config_t private type(particle_config_t), dimension(:), allocatable :: prt contains <> end type decay_term_config_t @ %def decay_term_config_t @ Finalizer, recursive. <>= procedure :: final => decay_term_config_final <>= recursive module subroutine decay_term_config_final (object) class(decay_term_config_t), intent(inout) :: object end subroutine decay_term_config_final <>= recursive module subroutine decay_term_config_final (object) class(decay_term_config_t), intent(inout) :: object integer :: i if (allocated (object%prt)) then do i = 1, size (object%prt) if (allocated (object%prt(i)%c)) call object%prt(i)%c%final () end do end if end subroutine decay_term_config_final @ %def decay_term_config_final @ Output, with optional indentation <>= procedure :: write => decay_term_config_write <>= recursive module subroutine decay_term_config_write & (object, unit, indent, verbose) class(decay_term_config_t), intent(in) :: object integer, intent(in), optional :: unit, indent logical, intent(in), optional :: verbose end subroutine decay_term_config_write <>= recursive module subroutine decay_term_config_write & (object, unit, indent, verbose) class(decay_term_config_t), intent(in) :: object integer, intent(in), optional :: unit, indent logical, intent(in), optional :: verbose integer :: i, j, u, ind logical :: verb u = given_output_unit (unit) ind = 0; if (present (indent)) ind = indent verb = .true.; if (present (verbose)) verb = verbose call write_indent (u, ind) write (u, "(1x,A)", advance="no") "Final state:" do i = 1, size (object%prt) select type (prt_config => object%prt(i)%c) type is (stable_config_t) write (u, "(1x,A)", advance="no") & char (prt_config%flv(1)%get_name ()) do j = 2, size (prt_config%flv) write (u, "(':',A)", advance="no") & char (prt_config%flv(j)%get_name ()) end do type is (unstable_config_t) write (u, "(1x,A)", advance="no") & char (prt_config%flv%get_name ()) end select end do write (u, *) if (verb) then do i = 1, size (object%prt) call object%prt(i)%c%write (u, ind) end do end if end subroutine decay_term_config_write @ %def decay_term_config_write @ Initialize, given a set of flavors. For each flavor, we must indicate whether the particle is stable. The second index of the flavor array runs over alternatives for each decay product; alternatives are allowed only if the decay product is itself stable. Gfortran 7/8/9 bug, has to remain in the main module: <>= procedure :: init => decay_term_config_init <>= recursive subroutine decay_term_config_init & (term, flv, stable, model, process_stack, var_list) class(decay_term_config_t), intent(out) :: term type(flavor_t), dimension(:,:), intent(in) :: flv logical, dimension(:), intent(in) :: stable class(model_data_t), intent(in), target :: model type(process_stack_t), intent(in), optional :: process_stack type(var_list_t), intent(in), optional :: var_list type(string_t), dimension(:), allocatable :: decay integer :: i allocate (term%prt (size (flv, 1))) do i = 1, size (flv, 1) associate (prt => term%prt(i)) if (stable(i)) then allocate (stable_config_t :: prt%c) else allocate (unstable_config_t :: prt%c) end if select type (prt_config => prt%c) type is (stable_config_t) call prt_config%init (flv(i,:)) type is (unstable_config_t) if (all (flv(i,:) == flv(i,1))) then call prt_config%init (flv(i,1)) call flv(i,1)%get_decays (decay) call prt_config%init_decays & (decay, model, process_stack, var_list) else call prt_config%write () call msg_fatal ("Decay configuration: & &unstable product must be unique") end if end select end associate end do end subroutine decay_term_config_init @ %def decay_term_config_init @ Recursively compute widths and branching ratios for all unstable particles. <>= procedure :: compute => decay_term_config_compute <>= recursive module subroutine decay_term_config_compute (term) class(decay_term_config_t), intent(inout) :: term end subroutine decay_term_config_compute <>= recursive module subroutine decay_term_config_compute (term) class(decay_term_config_t), intent(inout) :: term integer :: i do i = 1, size (term%prt) select type (unstable_config => term%prt(i)%c) type is (unstable_config_t) call unstable_config%compute () end select end do end subroutine decay_term_config_compute @ %def decay_term_config_compute @ \subsection{Decay Term} A decay term instance is selected when we generate an event for the associated process instance. When evaluated, it triggers further decays down the chain. Only unstable products are allocated as child particles. <>= type :: decay_term_t private type(decay_term_config_t), pointer :: config => null () type(particle_out_t), dimension(:), allocatable :: particle_out contains <> end type decay_term_t @ %def decay_term_t @ Finalizer. <>= procedure :: final => decay_term_final <>= recursive module subroutine decay_term_final (object) class(decay_term_t), intent(inout) :: object end subroutine decay_term_final <>= recursive module subroutine decay_term_final (object) class(decay_term_t), intent(inout) :: object integer :: i if (allocated (object%particle_out)) then do i = 1, size (object%particle_out) call object%particle_out(i)%c%final () end do end if end subroutine decay_term_final @ %def decay_term_final @ Output. <>= procedure :: write => decay_term_write <>= recursive module subroutine decay_term_write (object, unit, indent) class(decay_term_t), intent(in) :: object integer, intent(in), optional :: unit, indent end subroutine decay_term_write <>= recursive module subroutine decay_term_write (object, unit, indent) class(decay_term_t), intent(in) :: object integer, intent(in), optional :: unit, indent integer :: i, u, ind u = given_output_unit (unit) ind = 0; if (present (indent)) ind = indent call object%config%write (u, ind, verbose = .false.) do i = 1, size (object%particle_out) call object%particle_out(i)%c%write (u, ind) end do end subroutine decay_term_write @ %def decay_term_write @ Recursively write the embedded process instances. <>= procedure :: write_process_instances => decay_term_write_process_instances <>= recursive module subroutine decay_term_write_process_instances & (term, unit, verbose) class(decay_term_t), intent(in) :: term integer, intent(in), optional :: unit logical, intent(in), optional :: verbose end subroutine decay_term_write_process_instances <>= recursive module subroutine decay_term_write_process_instances & (term, unit, verbose) class(decay_term_t), intent(in) :: term integer, intent(in), optional :: unit logical, intent(in), optional :: verbose integer :: i do i = 1, size (term%particle_out) select type (unstable => term%particle_out(i)%c) type is (unstable_t) call unstable%write_process_instances (unit, verbose) end select end do end subroutine decay_term_write_process_instances @ %def decay_term_write_process_instances @ Initialization, using the configuration object. We allocate particle objects in parallel to the particle configuration objects which we use to initialize them, one at a time. Gfortran 7/8/9 bug, has to remain in the main module: <>= procedure :: init => decay_term_init <>= recursive subroutine decay_term_init (term, config) class(decay_term_t), intent(out) :: term type(decay_term_config_t), intent(in), target :: config integer :: i term%config => config allocate (term%particle_out (size (config%prt))) do i = 1, size (config%prt) select type (prt_config => config%prt(i)%c) type is (stable_config_t) allocate (stable_t :: term%particle_out(i)%c) select type (stable => term%particle_out(i)%c) type is (stable_t) call stable%init (prt_config) end select type is (unstable_config_t) allocate (unstable_t :: term%particle_out(i)%c) select type (unstable => term%particle_out(i)%c) type is (unstable_t) call unstable%init (prt_config) end select end select end do end subroutine decay_term_init @ %def decay_term_init @ Implement a RNG instance, spawned by the process object. <>= procedure :: make_rng => decay_term_make_rng <>= module subroutine decay_term_make_rng (term, process) class(decay_term_t), intent(inout) :: term type(process_t), intent(inout) :: process class(rng_t), allocatable :: rng end subroutine decay_term_make_rng <>= module subroutine decay_term_make_rng (term, process) class(decay_term_t), intent(inout) :: term type(process_t), intent(inout) :: process class(rng_t), allocatable :: rng integer :: i do i = 1, size (term%particle_out) select type (unstable => term%particle_out(i)%c) type is (unstable_t) call process%make_rng (rng) call unstable%import_rng (rng) end select end do end subroutine decay_term_make_rng @ %def decay_term_make_rng @ Link the interactions for unstable decay products to the interaction of the parent process. <>= procedure :: link_interactions => decay_term_link_interactions <>= recursive module subroutine decay_term_link_interactions (term, trace) class(decay_term_t), intent(inout) :: term type(interaction_t), intent(in), target :: trace end subroutine decay_term_link_interactions <>= recursive module subroutine decay_term_link_interactions (term, trace) class(decay_term_t), intent(inout) :: term type(interaction_t), intent(in), target :: trace integer :: i do i = 1, size (term%particle_out) select type (unstable => term%particle_out(i)%c) type is (unstable_t) call unstable%link_interactions (i, trace) end select end do end subroutine decay_term_link_interactions @ %def decay_term_link_interactions @ Recursively generate a decay chain, for each of the unstable particles in the final state. <>= procedure :: select_chain => decay_term_select_chain <>= recursive module subroutine decay_term_select_chain (term) class(decay_term_t), intent(inout) :: term end subroutine decay_term_select_chain <>= recursive module subroutine decay_term_select_chain (term) class(decay_term_t), intent(inout) :: term integer :: i do i = 1, size (term%particle_out) select type (unstable => term%particle_out(i)%c) type is (unstable_t) call unstable%select_chain () end select end do end subroutine decay_term_select_chain @ %def decay_term_select_chain @ Recursively generate a decay event, for each of the unstable particles in the final state. <>= procedure :: generate => decay_term_generate <>= recursive module subroutine decay_term_generate (term) class(decay_term_t), intent(inout) :: term end subroutine decay_term_generate <>= recursive module subroutine decay_term_generate (term) class(decay_term_t), intent(inout) :: term integer :: i do i = 1, size (term%particle_out) select type (unstable => term%particle_out(i)%c) type is (unstable_t) call unstable%generate () end select end do end subroutine decay_term_generate @ %def decay_term_generate @ \subsection{Decay Root Configuration} At the root of a decay chain, there is a parent process. The decay root stores a pointer to the parent process and the set of decay configurations. <>= public :: decay_root_config_t <>= type :: decay_root_config_t private type(string_t) :: process_id type(process_t), pointer :: process => null () class(model_data_t), pointer :: model => null () type(decay_term_config_t), dimension(:), allocatable :: term_config contains <> end type decay_root_config_t @ %def decay_root_config_t @ The finalizer is recursive since there may be cascade decays. <>= procedure :: final => decay_root_config_final <>= recursive module subroutine decay_root_config_final (object) class(decay_root_config_t), intent(inout) :: object end subroutine decay_root_config_final <>= recursive module subroutine decay_root_config_final (object) class(decay_root_config_t), intent(inout) :: object integer :: i if (allocated (object%term_config)) then do i = 1, size (object%term_config) call object%term_config(i)%final () end do end if end subroutine decay_root_config_final @ %def decay_root_config_final @ The output routine is also recursive, and it contains an adjustable indentation. <>= procedure :: write => decay_root_config_write procedure :: write_header => decay_root_config_write_header procedure :: write_terms => decay_root_config_write_terms <>= recursive module subroutine decay_root_config_write & (object, unit, indent, verbose) class(decay_root_config_t), intent(in) :: object integer, intent(in), optional :: unit, indent logical, intent(in), optional :: verbose end subroutine decay_root_config_write module subroutine decay_root_config_write_header (object, unit, indent) class(decay_root_config_t), intent(in) :: object integer, intent(in), optional :: unit, indent end subroutine decay_root_config_write_header module recursive subroutine decay_root_config_write_terms & (object, unit, indent, verbose) class(decay_root_config_t), intent(in) :: object integer, intent(in), optional :: unit, indent logical, intent(in), optional :: verbose end subroutine decay_root_config_write_terms <>= recursive module subroutine decay_root_config_write & (object, unit, indent, verbose) class(decay_root_config_t), intent(in) :: object integer, intent(in), optional :: unit, indent logical, intent(in), optional :: verbose integer :: u, ind u = given_output_unit (unit) ind = 0; if (present (indent)) ind = indent call write_indent (u, ind) write (u, "(1x,A)") "Final-state decay tree:" call object%write_header (unit, indent) call object%write_terms (unit, indent, verbose) end subroutine decay_root_config_write module subroutine decay_root_config_write_header (object, unit, indent) class(decay_root_config_t), intent(in) :: object integer, intent(in), optional :: unit, indent integer :: u, ind u = given_output_unit (unit) ind = 0; if (present (indent)) ind = indent call write_indent (u, ind) if (associated (object%process)) then write (u, 3) "process ID =", char (object%process_id), "*" else write (u, 3) "process ID =", char (object%process_id) end if 3 format (3x,A,2(1x,A)) end subroutine decay_root_config_write_header module recursive subroutine decay_root_config_write_terms & (object, unit, indent, verbose) class(decay_root_config_t), intent(in) :: object integer, intent(in), optional :: unit, indent logical, intent(in), optional :: verbose integer :: i, u, ind logical :: verb u = given_output_unit (unit) ind = 0; if (present (indent)) ind = indent verb = .true.; if (present (verbose)) verb = verbose if (verb .and. allocated (object%term_config)) then do i = 1, size (object%term_config) call object%term_config(i)%write (u, ind + 1) end do end if end subroutine decay_root_config_write_terms @ %def decay_root_config_write @ Initialize for a named process and (optionally) a pre-determined number of terms. <>= procedure :: init => decay_root_config_init <>= module subroutine decay_root_config_init (decay, model, process_id, n_terms) class(decay_root_config_t), intent(out) :: decay class(model_data_t), intent(in), target :: model type(string_t), intent(in) :: process_id integer, intent(in), optional :: n_terms end subroutine decay_root_config_init <>= module subroutine decay_root_config_init (decay, model, process_id, n_terms) class(decay_root_config_t), intent(out) :: decay class(model_data_t), intent(in), target :: model type(string_t), intent(in) :: process_id integer, intent(in), optional :: n_terms decay%model => model decay%process_id = process_id if (present (n_terms)) then allocate (decay%term_config (n_terms)) end if end subroutine decay_root_config_init @ %def decay_root_config_init @ Declare a decay term, given an array of flavors. <>= procedure :: init_term => decay_root_config_init_term <>= recursive module subroutine decay_root_config_init_term & (decay, i, flv, stable, model, process_stack, var_list) class(decay_root_config_t), intent(inout) :: decay integer, intent(in) :: i type(flavor_t), dimension(:,:), intent(in) :: flv logical, dimension(:), intent(in) :: stable class(model_data_t), intent(in), target :: model type(process_stack_t), intent(in), optional :: process_stack type(var_list_t), intent(in), optional, target :: var_list end subroutine decay_root_config_init_term <>= recursive module subroutine decay_root_config_init_term & (decay, i, flv, stable, model, process_stack, var_list) class(decay_root_config_t), intent(inout) :: decay integer, intent(in) :: i type(flavor_t), dimension(:,:), intent(in) :: flv logical, dimension(:), intent(in) :: stable class(model_data_t), intent(in), target :: model type(process_stack_t), intent(in), optional :: process_stack type(var_list_t), intent(in), optional, target :: var_list call decay%term_config(i)%init (flv, stable, model, process_stack, var_list) end subroutine decay_root_config_init_term @ %def decay_root_config_init_term @ Connect the decay root configuration with a process object (which should represent the parent process). This includes initialization, therefore intent(out). The flavor state is retrieved from the process term object. However, we have to be careful: the flavor object points to the model instance that is stored in the process object. This model instance may not contain the current setting for unstable particles and decay. Therefore, we assign the model directly. If the [[process_instance]] argument is provided, we use this for the flavor state. This applies to the decay root only, where the process can be entangled with a beam setup, and the latter contains beam remnants as further outgoing particles. These must be included in the set of outgoing flavors, since the decay application is also done on the connected state. Infer stability from the particle properties, using the first row in the set of flavor states. For unstable particles, we look for decays, recursively, available from the process stack (if present). For the unstable particles, we have to check whether their masses match between the production and the decay. Fortunately, both versions are available for comparison. The optional [[var_list]] argument may override integral/error values for decay processes. <>= procedure :: connect => decay_root_config_connect <>= recursive module subroutine decay_root_config_connect & (decay, process, model, process_stack, process_instance, var_list) class(decay_root_config_t), intent(out) :: decay type(process_t), intent(in), target :: process class(model_data_t), intent(in), target :: model type(process_stack_t), intent(in), optional :: process_stack type(process_instance_t), intent(in), optional, target :: process_instance type(var_list_t), intent(in), optional, target :: var_list end subroutine decay_root_config_connect <>= recursive module subroutine decay_root_config_connect & (decay, process, model, process_stack, process_instance, var_list) class(decay_root_config_t), intent(out) :: decay type(process_t), intent(in), target :: process class(model_data_t), intent(in), target :: model type(process_stack_t), intent(in), optional :: process_stack type(process_instance_t), intent(in), optional, target :: process_instance type(var_list_t), intent(in), optional, target :: var_list type(connected_state_t), pointer :: connected_state type(interaction_t), pointer :: int type(flavor_t), dimension(:,:), allocatable :: flv logical, dimension(:), allocatable :: stable real(default), dimension(:), allocatable :: m_prod, m_dec integer :: i call decay%init (model, process%get_id (), process%get_n_terms ()) do i = 1, size (decay%term_config) if (present (process_instance)) then connected_state => process_instance%get_connected_state_ptr (i) int => connected_state%get_matrix_int_ptr () call int%get_flv_out (flv) else call process%get_term_flv_out (i, flv) end if allocate (m_prod (size (flv(:,1)%get_mass ()))) m_prod = flv(:,1)%get_mass () call flv%set_model (model) allocate (m_dec (size (flv(:,1)%get_mass ()))) m_dec = flv(:,1)%get_mass () allocate (stable (size (flv, 1))) stable = flv(:,1)%is_stable () call check_masses () call decay%init_term (i, flv, stable, model, process_stack, var_list) deallocate (flv, stable, m_prod, m_dec) end do decay%process => process contains subroutine check_masses () integer :: i logical :: ok ok = .true. do i = 1, size (m_prod) if (.not. stable(i)) then if (.not. nearly_equal (m_prod(i), m_dec(i))) then write (msg_buffer, "(A,A,A)") "particle '", & char (flv(i,1)%get_name ()), "':" call msg_message write (msg_buffer, & "(2x,A,1x," // FMT_15 // ",3x,A,1x," // FMT_15 // ")") & "m_prod =", m_prod(i), "m_dec =", m_dec(i) call msg_message ok = .false. end if end if end do if (.not. ok) call msg_fatal & ("Particle mass mismatch between production and decay") end subroutine check_masses end subroutine decay_root_config_connect @ %def decay_root_config_connect @ Recursively compute widths, errors, and branching ratios. <>= procedure :: compute => decay_root_config_compute <>= recursive module subroutine decay_root_config_compute (decay) class(decay_root_config_t), intent(inout) :: decay end subroutine decay_root_config_compute <>= recursive module subroutine decay_root_config_compute (decay) class(decay_root_config_t), intent(inout) :: decay integer :: i do i = 1, size (decay%term_config) call decay%term_config(i)%compute () end do end subroutine decay_root_config_compute @ %def decay_root_config_compute @ \subsection{Decay Root Instance} This is the common parent type for decay and decay root. The process instance points to the parent process. The model pointer is separate because particle settings may be updated w.r.t.\ the parent process object. <>= type, abstract :: decay_gen_t private type(decay_term_t), dimension(:), allocatable :: term type(process_instance_t), pointer :: process_instance => null () integer :: selected_mci = 0 integer :: selected_term = 0 contains <> end type decay_gen_t @ %def decay_gen_t @ The decay root represents the parent process. When an event is generated, the generator selects the term to which the decay chain applies (if possible). The process instance is just a pointer. <>= public :: decay_root_t <>= type, extends (decay_gen_t) :: decay_root_t private type(decay_root_config_t), pointer :: config => null () contains <> end type decay_root_t @ %def decay_root_t @ The finalizer has to recursively finalize the terms, but we can skip the process instance which is not explicitly allocated. <>= procedure :: base_final => decay_gen_final <>= recursive module subroutine decay_gen_final (object) class(decay_gen_t), intent(inout) :: object end subroutine decay_gen_final <>= recursive module subroutine decay_gen_final (object) class(decay_gen_t), intent(inout) :: object integer :: i if (allocated (object%term)) then do i = 1, size (object%term) call object%term(i)%final () end do end if end subroutine decay_gen_final @ %def decay_gen_final @ No extra finalization for the decay root. <>= procedure :: final => decay_root_final <>= module subroutine decay_root_final (object) class(decay_root_t), intent(inout) :: object end subroutine decay_root_final <>= module subroutine decay_root_final (object) class(decay_root_t), intent(inout) :: object call object%base_final () end subroutine decay_root_final @ %def decay_gen_final @ Output. <>= procedure :: write => decay_root_write <>= module subroutine decay_root_write (object, unit) class(decay_root_t), intent(in) :: object integer, intent(in), optional :: unit end subroutine decay_root_write <>= module subroutine decay_root_write (object, unit) class(decay_root_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) if (associated (object%config)) then call object%config%write (unit, verbose = .false.) else write (u, "(1x,A)") "Final-state decay tree: [not configured]" end if if (object%selected_mci > 0) then write (u, "(3x,A,I0)") "Selected MCI = ", object%selected_mci else write (u, "(3x,A)") "Selected MCI = [undefined]" end if if (object%selected_term > 0) then write (u, "(3x,A,I0)") "Selected term = ", object%selected_term call object%term(object%selected_term)%write (u, 1) else write (u, "(3x,A)") "Selected term = [undefined]" end if end subroutine decay_root_write @ %def decay_root_write @ Write the process instances, recursively. <>= procedure :: write_process_instances => decay_gen_write_process_instances <>= recursive module subroutine decay_gen_write_process_instances & (decay, unit, verbose) class(decay_gen_t), intent(in) :: decay integer, intent(in), optional :: unit logical, intent(in), optional :: verbose end subroutine decay_gen_write_process_instances <>= recursive module subroutine decay_gen_write_process_instances & (decay, unit, verbose) class(decay_gen_t), intent(in) :: decay integer, intent(in), optional :: unit logical, intent(in), optional :: verbose logical :: verb verb = .true.; if (present (verbose)) verb = verbose if (associated (decay%process_instance)) then if (verb) then call decay%process_instance%write (unit) else call decay%process_instance%write_header (unit) end if end if if (decay%selected_term > 0) then call decay%term(decay%selected_term)%write_process_instances (unit, verb) end if end subroutine decay_gen_write_process_instances @ %def decay_gen_write_process_instances @ Generic initializer. All can be done recursively. <>= procedure :: base_init => decay_gen_init <>= recursive module subroutine decay_gen_init (decay, term_config) class(decay_gen_t), intent(out) :: decay type(decay_term_config_t), dimension(:), intent(in), target :: term_config end subroutine decay_gen_init <>= recursive module subroutine decay_gen_init (decay, term_config) class(decay_gen_t), intent(out) :: decay type(decay_term_config_t), dimension(:), intent(in), target :: term_config integer :: i allocate (decay%term (size (term_config))) do i = 1, size (decay%term) call decay%term(i)%init (term_config(i)) end do end subroutine decay_gen_init @ %def decay_gen_init @ Specific initializer. We assign the configuration object, which should correspond to a completely initialized decay configuration tree. We also connect to an existing process instance. Then, we recursively link the child interactions to the parent process. <>= procedure :: init => decay_root_init <>= module subroutine decay_root_init (decay_root, config, process_instance) class(decay_root_t), intent(out) :: decay_root type(decay_root_config_t), intent(in), target :: config type(process_instance_t), intent(in), target :: process_instance end subroutine decay_root_init <>= module subroutine decay_root_init (decay_root, config, process_instance) class(decay_root_t), intent(out) :: decay_root type(decay_root_config_t), intent(in), target :: config type(process_instance_t), intent(in), target :: process_instance call decay_root%base_init (config%term_config) decay_root%config => config decay_root%process_instance => process_instance call decay_root%make_term_rng (config%process) call decay_root%link_term_interactions () end subroutine decay_root_init @ %def decay_root_init @ Explicitly set/get mci and term indices. (Used in unit test.) <>= procedure :: set_mci => decay_gen_set_mci procedure :: set_term => decay_gen_set_term procedure :: get_mci => decay_gen_get_mci procedure :: get_term => decay_gen_get_term <>= module subroutine decay_gen_set_mci (decay, i) class(decay_gen_t), intent(inout) :: decay integer, intent(in) :: i end subroutine decay_gen_set_mci module subroutine decay_gen_set_term (decay, i) class(decay_gen_t), intent(inout) :: decay integer, intent(in) :: i end subroutine decay_gen_set_term module function decay_gen_get_mci (decay) result (i) class(decay_gen_t), intent(inout) :: decay integer :: i end function decay_gen_get_mci module function decay_gen_get_term (decay) result (i) class(decay_gen_t), intent(inout) :: decay integer :: i end function decay_gen_get_term <>= module subroutine decay_gen_set_mci (decay, i) class(decay_gen_t), intent(inout) :: decay integer, intent(in) :: i decay%selected_mci = i end subroutine decay_gen_set_mci module subroutine decay_gen_set_term (decay, i) class(decay_gen_t), intent(inout) :: decay integer, intent(in) :: i decay%selected_term = i end subroutine decay_gen_set_term module function decay_gen_get_mci (decay) result (i) class(decay_gen_t), intent(inout) :: decay integer :: i i = decay%selected_mci end function decay_gen_get_mci module function decay_gen_get_term (decay) result (i) class(decay_gen_t), intent(inout) :: decay integer :: i i = decay%selected_term end function decay_gen_get_term @ %def decay_gen_set_mci @ %def decay_gen_set_term @ %def decay_gen_get_mci @ %def decay_gen_get_term @ Implement random-number generators for unstable decay selection in all terms. This is not recursive. We also make use of the fact that [[process]] is a pointer; the (state of the RNG factory inside the) target process will be modified by the rng-spawning method, but not the pointer. <>= procedure :: make_term_rng => decay_gen_make_term_rng <>= module subroutine decay_gen_make_term_rng (decay, process) class(decay_gen_t), intent(inout) :: decay type(process_t), intent(in), pointer :: process end subroutine decay_gen_make_term_rng <>= module subroutine decay_gen_make_term_rng (decay, process) class(decay_gen_t), intent(inout) :: decay type(process_t), intent(in), pointer :: process integer :: i do i = 1, size (decay%term) call decay%term(i)%make_rng (process) end do end subroutine decay_gen_make_term_rng @ %def decay_gen_make_term_rng @ Recursively link interactions of the enclosed decay terms to the corresponding terms in the current process instance. <>= procedure :: link_term_interactions => decay_gen_link_term_interactions <>= recursive module subroutine decay_gen_link_term_interactions (decay) class(decay_gen_t), intent(inout) :: decay end subroutine decay_gen_link_term_interactions <>= recursive module subroutine decay_gen_link_term_interactions (decay) class(decay_gen_t), intent(inout) :: decay integer :: i type(interaction_t), pointer :: trace associate (instance => decay%process_instance) do i = 1, size (decay%term) trace => instance%get_trace_int_ptr (i) call decay%term(i)%link_interactions (trace) end do end associate end subroutine decay_gen_link_term_interactions @ %def decay_gen_link_term_interactions @ Select a decay chain: decay modes and process components. <>= procedure :: select_chain => decay_root_select_chain <>= module subroutine decay_root_select_chain (decay_root) class(decay_root_t), intent(inout) :: decay_root end subroutine decay_root_select_chain <>= module subroutine decay_root_select_chain (decay_root) class(decay_root_t), intent(inout) :: decay_root if (decay_root%selected_term > 0) then call decay_root%term(decay_root%selected_term)%select_chain () else call msg_bug ("Decays: no term selected for parent process") end if end subroutine decay_root_select_chain @ %def decay_root_select_chain @ Generate a decay tree, i.e., for the selected term in the parent process, recursively generate a decay event for all unstable particles. Factor out the trace of the connected state of the parent process. This trace should not be taken into account for unweighting the decay chain, since it was already used for unweighting the parent event, or it determines the overall event weight. <>= procedure :: generate => decay_root_generate <>= module subroutine decay_root_generate (decay_root) class(decay_root_t), intent(inout) :: decay_root end subroutine decay_root_generate <>= module subroutine decay_root_generate (decay_root) class(decay_root_t), intent(inout) :: decay_root type(connected_state_t), pointer :: connected_state if (decay_root%selected_term > 0) then connected_state => decay_root%process_instance%get_connected_state_ptr & (decay_root%selected_term) call connected_state%normalize_matrix_by_trace () call decay_root%term(decay_root%selected_term)%generate () else call msg_bug ("Decays: no term selected for parent process") end if end subroutine decay_root_generate @ %def decay_root_generate @ \subsection{Decay Configuration} A decay configuration describes a distinct decay mode of a particle. Each decay mode may include several terms, which correspond to the terms in the associated process. In addition to the base type, the decay configuration object contains the integral of the parent process and the selector for the MCI group inside this process. The flavor component should be identical to the flavor component of the parent particle ([[unstable]] object). <>= type, extends (decay_root_config_t) :: decay_config_t private type(flavor_t) :: flv real(default) :: weight = 0 real(default) :: integral = 0 real(default) :: abs_error = 0 real(default) :: rel_error = 0 type(selector_t) :: mci_selector contains <> end type decay_config_t @ %def decay_config_t @ The output routine extends the decay-root writer by listing numerical component values. <>= procedure :: write => decay_config_write <>= recursive module subroutine decay_config_write & (object, unit, indent, verbose) class(decay_config_t), intent(in) :: object integer, intent(in), optional :: unit, indent logical, intent(in), optional :: verbose end subroutine decay_config_write <>= recursive module subroutine decay_config_write (object, unit, indent, verbose) class(decay_config_t), intent(in) :: object integer, intent(in), optional :: unit, indent logical, intent(in), optional :: verbose integer :: u, ind u = given_output_unit (unit) ind = 0; if (present (indent)) ind = indent call write_indent (u, ind) write (u, "(1x,A)") "Decay:" call object%write_header (unit, indent) call write_indent (u, ind) write (u, 2) "branching ratio =", object%weight * 100 call write_indent (u, ind) write (u, 1) "partial width =", object%integral call write_indent (u, ind) write (u, 1) "error (abs) =", object%abs_error call write_indent (u, ind) write (u, 1) "error (rel) =", object%rel_error 1 format (3x,A,ES19.12) 2 format (3x,A,F11.6,1x,'%') call object%write_terms (unit, indent, verbose) end subroutine decay_config_write @ %def decay_config_write @ Connect a decay configuration with a process object (which should represent the decay). This includes initialization, therefore intent(out). We first connect the process itself, then do initializations that are specific for this decay. Infer stability from the particle properties, using the first row in the set of flavor states. Once we can deal with predetermined decay chains, they should be used instead. If there is an optional [[var_list]], check if the stored values for the decay partial width and error have been overridden there. <>= procedure :: connect => decay_config_connect <>= recursive module subroutine decay_config_connect & (decay, process, model, process_stack, process_instance, var_list) class(decay_config_t), intent(out) :: decay type(process_t), intent(in), target :: process class(model_data_t), intent(in), target :: model type(process_stack_t), intent(in), optional :: process_stack type(process_instance_t), intent(in), optional, target :: process_instance type(var_list_t), intent(in), optional, target :: var_list end subroutine decay_config_connect <>= recursive module subroutine decay_config_connect & (decay, process, model, process_stack, process_instance, var_list) class(decay_config_t), intent(out) :: decay type(process_t), intent(in), target :: process class(model_data_t), intent(in), target :: model type(process_stack_t), intent(in), optional :: process_stack type(process_instance_t), intent(in), optional, target :: process_instance type(var_list_t), intent(in), optional, target :: var_list real(default), dimension(:), allocatable :: integral_mci type(string_t) :: process_id integer :: i, n_mci call decay%decay_root_config_t%connect & (process, model, process_stack, var_list=var_list) process_id = process%get_id () if (process%lab_is_cm ()) then call msg_fatal ("Decay process " // char (process_id) & // ": unusable because rest frame is fixed.") end if decay%integral = process%get_integral () decay%abs_error = process%get_error () if (present (var_list)) then call update (decay%integral, "integral(" // process_id // ")") call update (decay%abs_error, "error(" // process_id // ")") end if n_mci = process%get_n_mci () allocate (integral_mci (n_mci)) do i = 1, n_mci integral_mci(i) = process%get_integral_mci (i) end do call decay%mci_selector%init (integral_mci) contains subroutine update (var, var_name) real(default), intent(inout) :: var type(string_t), intent(in) :: var_name if (var_list%contains (var_name)) then var = var_list%get_rval (var_name) end if end subroutine update end subroutine decay_config_connect @ %def decay_config_connect @ Set the flavor entry, which repeats the flavor of the parent unstable particle. <>= procedure :: set_flv => decay_config_set_flv <>= module subroutine decay_config_set_flv (decay, flv) class(decay_config_t), intent(inout) :: decay type(flavor_t), intent(in) :: flv end subroutine decay_config_set_flv <>= module subroutine decay_config_set_flv (decay, flv) class(decay_config_t), intent(inout) :: decay type(flavor_t), intent(in) :: flv decay%flv = flv end subroutine decay_config_set_flv @ %def decay_config_set_flv @ Compute embedded branchings and the relative error. This method does not apply to the decay root. <>= procedure :: compute => decay_config_compute <>= recursive module subroutine decay_config_compute (decay) class(decay_config_t), intent(inout) :: decay end subroutine decay_config_compute <>= recursive module subroutine decay_config_compute (decay) class(decay_config_t), intent(inout) :: decay call decay%decay_root_config_t%compute () if (.not. vanishes (decay%integral)) then decay%rel_error = decay%abs_error / decay%integral else decay%rel_error = 0 end if end subroutine decay_config_compute @ %def decay_config_compute @ \subsection{Decay Instance} The decay contains a collection of terms. One of them is selected when the decay is evaluated. This is similar to the decay root, but we implement it independently. The process instance object is allocated via a pointer, so it automatically behaves as a target. <>= type, extends (decay_gen_t) :: decay_t private type(decay_config_t), pointer :: config => null () class(rng_t), allocatable :: rng contains <> end type decay_t @ %def decay_t @ The finalizer is recursive. <>= procedure :: final => decay_final <>= recursive module subroutine decay_final (object) class(decay_t), intent(inout) :: object end subroutine decay_final <>= recursive module subroutine decay_final (object) class(decay_t), intent(inout) :: object integer :: i call object%base_final () do i = 1, object%config%process%get_n_mci () call object%process_instance%final_simulation (i) end do call object%process_instance%final () deallocate (object%process_instance) end subroutine decay_final @ %def decay_final @ Output. <>= procedure :: write => decay_write <>= recursive module subroutine decay_write (object, unit, indent, recursive) class(decay_t), intent(in) :: object integer, intent(in), optional :: unit, indent, recursive end subroutine decay_write <>= recursive module subroutine decay_write (object, unit, indent, recursive) class(decay_t), intent(in) :: object integer, intent(in), optional :: unit, indent, recursive integer :: u, ind u = given_output_unit (unit) ind = 0; if (present (indent)) ind = indent call object%config%write (unit, indent, verbose = .false.) if (allocated (object%rng)) then call object%rng%write (u, ind + 1) end if call write_indent (u, ind) if (object%selected_mci > 0) then write (u, "(3x,A,I0)") "Selected MCI = ", object%selected_mci else write (u, "(3x,A)") "Selected MCI = [undefined]" end if call write_indent (u, ind) if (object%selected_term > 0) then write (u, "(3x,A,I0)") "Selected term = ", object%selected_term call object%term(object%selected_term)%write (u, ind + 1) else write (u, "(3x,A)") "Selected term = [undefined]" end if end subroutine decay_write @ %def decay_write @ Initializer. Base initialization is done recursively. Then, we prepare the current process instance and allocate a random-number generator for term selection. For all unstable particles, we also allocate a r.n.g. as spawned by the current process. <>= procedure :: init => decay_init <>= recursive module subroutine decay_init (decay, config) class(decay_t), intent(out) :: decay type(decay_config_t), intent(in), target :: config end subroutine decay_init <>= recursive module subroutine decay_init (decay, config) class(decay_t), intent(out) :: decay type(decay_config_t), intent(in), target :: config integer :: i call decay%base_init (config%term_config) decay%config => config allocate (decay%process_instance) call decay%process_instance%init (decay%config%process) call decay%process_instance%setup_event_data (decay%config%model) do i = 1, decay%config%process%get_n_mci () call decay%process_instance%init_simulation (i) end do call decay%config%process%make_rng (decay%rng) call decay%make_term_rng (decay%config%process) end subroutine decay_init @ %def decay_init @ Link interactions to the parent process. [[i_prt]] is the index of the current outgoing particle in the parent interaction, for which we take the trace evaluator. We link it to the beam particle in the beam interaction of the decay process instance. Then, repeat the procedure for the outgoing particles. <>= procedure :: link_interactions => decay_link_interactions <>= recursive module subroutine decay_link_interactions (decay, i_prt, trace) class(decay_t), intent(inout) :: decay integer, intent(in) :: i_prt type(interaction_t), intent(in), target :: trace end subroutine decay_link_interactions <>= recursive module subroutine decay_link_interactions (decay, i_prt, trace) class(decay_t), intent(inout) :: decay integer, intent(in) :: i_prt type(interaction_t), intent(in), target :: trace type(interaction_t), pointer :: beam_int integer :: n_in, n_vir beam_int => decay%process_instance%get_beam_int_ptr () n_in = trace%get_n_in () n_vir = trace%get_n_vir () call beam_int%set_source_link (1, trace, & n_in + n_vir + i_prt) call decay%link_term_interactions () end subroutine decay_link_interactions @ %def decay_link_interactions @ Determine a decay chain. For each unstable particle we select one of the possible decay modes, and for each decay process we select one of the possible decay MCI components, calling the random-number generators. We do not generate momenta, yet. <>= procedure :: select_chain => decay_select_chain <>= recursive module subroutine decay_select_chain (decay) class(decay_t), intent(inout) :: decay end subroutine decay_select_chain <>= recursive module subroutine decay_select_chain (decay) class(decay_t), intent(inout) :: decay real(default) :: x integer :: i call decay%rng%generate (x) decay%selected_mci = decay%config%mci_selector%select (x) call decay%process_instance%choose_mci (decay%selected_mci) decay%selected_term = decay%process_instance%select_i_term () do i = 1, size (decay%term) call decay%term(i)%select_chain () end do end subroutine decay_select_chain @ %def decay_select_chain @ Generate a decay. We first receive the beam momenta from the parent process (assuming that this is properly linked), then call the associated process object for a new event. Factor out the trace of the helicity density matrix of the isolated state (the one that will be used for the decay chain). The trace is taken into account for unweighting the individual decay event and should therefore be ignored for unweighting the correlated decay chain afterwards. <>= procedure :: generate => decay_generate <>= recursive module subroutine decay_generate (decay) class(decay_t), intent(inout) :: decay end subroutine decay_generate <>= recursive module subroutine decay_generate (decay) class(decay_t), intent(inout) :: decay type(isolated_state_t), pointer :: isolated_state integer :: i call decay%process_instance%receive_beam_momenta () call decay%process_instance%generate_unweighted_event (decay%selected_mci) if (signal_is_pending ()) return call decay%process_instance%evaluate_event_data () isolated_state => & decay%process_instance%get_isolated_state_ptr (decay%selected_term) call isolated_state%normalize_matrix_by_trace () do i = 1, size (decay%term) call decay%term(i)%generate () if (signal_is_pending ()) return end do end subroutine decay_generate @ %def decay_generate @ \subsection{Stable Particles} This is a stable particle. The flavor can be ambiguous (e.g., partons). <>= type, extends (any_config_t) :: stable_config_t private type(flavor_t), dimension(:), allocatable :: flv contains <> end type stable_config_t @ %def stable_config_t @ The finalizer is empty: <>= procedure :: final => stable_config_final <>= module subroutine stable_config_final (object) class(stable_config_t), intent(inout) :: object end subroutine stable_config_final <>= module subroutine stable_config_final (object) class(stable_config_t), intent(inout) :: object end subroutine stable_config_final @ %def stable_config_final @ Output. <>= procedure :: write => stable_config_write <>= recursive module subroutine stable_config_write & (object, unit, indent, verbose) class(stable_config_t), intent(in) :: object integer, intent(in), optional :: unit, indent logical, intent(in), optional :: verbose end subroutine stable_config_write <>= recursive module subroutine stable_config_write & (object, unit, indent, verbose) class(stable_config_t), intent(in) :: object integer, intent(in), optional :: unit, indent logical, intent(in), optional :: verbose integer :: u, i, ind u = given_output_unit (unit) ind = 0; if (present (indent)) ind = indent call write_indent (u, ind) write (u, "(1x,'+',1x,A)", advance = "no") "Stable:" write (u, "(1x,A)", advance = "no") char (object%flv(1)%get_name ()) do i = 2, size (object%flv) write (u, "(':',A)", advance = "no") & char (object%flv(i)%get_name ()) end do write (u, *) end subroutine stable_config_write @ %def stable_config_write @ Initializer. We are presented with an array of flavors, but there may be double entries which we remove, so we store only the distinct flavors. <>= procedure :: init => stable_config_init <>= module subroutine stable_config_init (config, flv) class(stable_config_t), intent(out) :: config type(flavor_t), dimension(:), intent(in) :: flv end subroutine stable_config_init <>= module subroutine stable_config_init (config, flv) class(stable_config_t), intent(out) :: config type(flavor_t), dimension(:), intent(in) :: flv integer, dimension (size (flv)) :: pdg logical, dimension (size (flv)) :: mask integer :: i pdg = flv%get_pdg () mask(1) = .true. forall (i = 2 : size (pdg)) mask(i) = all (pdg(i) /= pdg(1:i-1)) end forall allocate (config%flv (count (mask))) config%flv = pack (flv, mask) end subroutine stable_config_init @ %def stable_config_init @ Here is the corresponding object instance. Except for the pointer to the configuration, there is no content. <>= type, extends (any_t) :: stable_t private type(stable_config_t), pointer :: config => null () contains <> end type stable_t @ %def stable_t @ The finalizer does nothing. <>= procedure :: final => stable_final <>= module subroutine stable_final (object) class(stable_t), intent(inout) :: object end subroutine stable_final <>= module subroutine stable_final (object) class(stable_t), intent(inout) :: object end subroutine stable_final @ %def stable_final @ We can delegate output to the configuration object. <>= procedure :: write => stable_write <>= module subroutine stable_write (object, unit, indent) class(stable_t), intent(in) :: object integer, intent(in), optional :: unit, indent end subroutine stable_write <>= module subroutine stable_write (object, unit, indent) class(stable_t), intent(in) :: object integer, intent(in), optional :: unit, indent call object%config%write (unit, indent) end subroutine stable_write @ %def stable_write @ Initializer: just assign the configuration. <>= procedure :: init => stable_init <>= module subroutine stable_init (stable, config) class(stable_t), intent(out) :: stable type(stable_config_t), intent(in), target :: config end subroutine stable_init <>= module subroutine stable_init (stable, config) class(stable_t), intent(out) :: stable type(stable_config_t), intent(in), target :: config stable%config => config end subroutine stable_init @ %def stable_init @ \subsection{Unstable Particles} A branching configuration enables us to select among distinct decay modes of a particle. We store the particle flavor (with its implicit link to a model), an array of decay configurations, and a selector object. The total width, absolute and relative error are stored as [[integral]], [[abs_error]], and [[rel_error]], respectively. The flavor must be unique in this case. <>= public :: unstable_config_t <>= type, extends (any_config_t) :: unstable_config_t private type(flavor_t) :: flv real(default) :: integral = 0 real(default) :: abs_error = 0 real(default) :: rel_error = 0 type(selector_t) :: selector type(decay_config_t), dimension(:), allocatable :: decay_config contains <> end type unstable_config_t @ %def unstable_config_t @ Finalizer. The branching configuration can be a recursive structure. <>= procedure :: final => unstable_config_final <>= recursive module subroutine unstable_config_final (object) class(unstable_config_t), intent(inout) :: object end subroutine unstable_config_final <>= recursive module subroutine unstable_config_final (object) class(unstable_config_t), intent(inout) :: object integer :: i if (allocated (object%decay_config)) then do i = 1, size (object%decay_config) call object%decay_config(i)%final () end do end if end subroutine unstable_config_final @ %def unstable_config_final @ Output. Since this may be recursive, we include indentation. <>= procedure :: write => unstable_config_write <>= recursive module subroutine unstable_config_write & (object, unit, indent, verbose) class(unstable_config_t), intent(in) :: object integer, intent(in), optional :: unit, indent logical, intent(in), optional :: verbose end subroutine unstable_config_write <>= recursive module subroutine unstable_config_write & (object, unit, indent, verbose) class(unstable_config_t), intent(in) :: object integer, intent(in), optional :: unit, indent logical, intent(in), optional :: verbose integer :: u, i, ind logical :: verb u = given_output_unit (unit) ind = 0; if (present (indent)) ind = indent verb = .true.; if (present (verbose)) verb = verbose call write_indent (u, ind) write (u, "(1x,'+',1x,A,1x,A)") "Unstable:", & char (object%flv%get_name ()) call write_indent (u, ind) write (u, 1) "total width =", object%integral call write_indent (u, ind) write (u, 1) "error (abs) =", object%abs_error call write_indent (u, ind) write (u, 1) "error (rel) =", object%rel_error 1 format (5x,A,ES19.12) if (verb .and. allocated (object%decay_config)) then do i = 1, size (object%decay_config) call object%decay_config(i)%write (u, ind + 1) end do end if end subroutine unstable_config_write @ %def unstable_config_write @ Initializer. For the unstable particle, the flavor is unique. <>= procedure :: init => unstable_config_init <>= module subroutine unstable_config_init (unstable, flv, set_decays, model) class(unstable_config_t), intent(out) :: unstable type(flavor_t), intent(in) :: flv logical, intent(in), optional :: set_decays class(model_data_t), intent(in), optional, target :: model end subroutine unstable_config_init <>= module subroutine unstable_config_init (unstable, flv, set_decays, model) class(unstable_config_t), intent(out) :: unstable type(flavor_t), intent(in) :: flv logical, intent(in), optional :: set_decays class(model_data_t), intent(in), optional, target :: model type(string_t), dimension(:), allocatable :: decay unstable%flv = flv if (present (set_decays)) then call unstable%flv%get_decays (decay) call unstable%init_decays (decay, model) end if end subroutine unstable_config_init @ %def unstable_config_init @ Further initialization: determine the number of decay modes. We can assume that the flavor of the particle has been set already. If the process stack is given, we can delve recursively into actually assigning decay processes. Otherwise, we just initialize with decay process names. <>= procedure :: init_decays => unstable_config_init_decays <>= recursive module subroutine unstable_config_init_decays & (unstable, decay_id, model, process_stack, var_list) class(unstable_config_t), intent(inout) :: unstable type(string_t), dimension(:), intent(in) :: decay_id class(model_data_t), intent(in), target :: model type(process_stack_t), intent(in), optional :: process_stack type(var_list_t), intent(in), optional :: var_list end subroutine unstable_config_init_decays <>= recursive module subroutine unstable_config_init_decays & (unstable, decay_id, model, process_stack, var_list) class(unstable_config_t), intent(inout) :: unstable type(string_t), dimension(:), intent(in) :: decay_id class(model_data_t), intent(in), target :: model type(process_stack_t), intent(in), optional :: process_stack type(var_list_t), intent(in), optional :: var_list integer :: i allocate (unstable%decay_config (size (decay_id))) do i = 1, size (decay_id) associate (decay => unstable%decay_config(i)) if (present (process_stack)) then call decay%connect (process_stack%get_process_ptr (decay_id(i)), & model, process_stack, var_list=var_list) else call decay%init (model, decay_id(i)) end if call decay%set_flv (unstable%flv) end associate end do end subroutine unstable_config_init_decays @ %def unstable_config_init_decays @ Explicitly connect a specific decay with a process. This is used only in unit tests. <>= procedure :: connect_decay => unstable_config_connect_decay <>= module subroutine unstable_config_connect_decay & (unstable, i, process, model) class(unstable_config_t), intent(inout) :: unstable integer, intent(in) :: i type(process_t), intent(in), target :: process class(model_data_t), intent(in), target :: model end subroutine unstable_config_connect_decay <>= module subroutine unstable_config_connect_decay (unstable, i, process, model) class(unstable_config_t), intent(inout) :: unstable integer, intent(in) :: i type(process_t), intent(in), target :: process class(model_data_t), intent(in), target :: model associate (decay => unstable%decay_config(i)) call decay%connect (process, model) end associate end subroutine unstable_config_connect_decay @ %def unstable_config_connect_decay @ Compute the total width and branching ratios, initializing the decay selector. <>= procedure :: compute => unstable_config_compute <>= recursive module subroutine unstable_config_compute (unstable) class(unstable_config_t), intent(inout) :: unstable end subroutine unstable_config_compute <>= recursive module subroutine unstable_config_compute (unstable) class(unstable_config_t), intent(inout) :: unstable integer :: i do i = 1, size (unstable%decay_config) call unstable%decay_config(i)%compute () end do unstable%integral = sum (unstable%decay_config%integral) if (unstable%integral <= 0) then call unstable%write () call msg_fatal ("Decay configuration: computed total width is zero") end if unstable%abs_error = sqrt (sum (unstable%decay_config%abs_error ** 2)) unstable%rel_error = unstable%abs_error / unstable%integral call unstable%selector%init (unstable%decay_config%integral) do i = 1, size (unstable%decay_config) unstable%decay_config(i)%weight & = unstable%selector%get_weight (i) end do end subroutine unstable_config_compute @ %def unstable_config_compute @ Now we define the instance of an unstable particle. <>= public :: unstable_t <>= type, extends (any_t) :: unstable_t private type(unstable_config_t), pointer :: config => null () class(rng_t), allocatable :: rng integer :: selected_decay = 0 type(decay_t), dimension(:), allocatable :: decay contains <> end type unstable_t @ %def unstable_t @ Recursive finalizer. <>= procedure :: final => unstable_final <>= recursive module subroutine unstable_final (object) class(unstable_t), intent(inout) :: object end subroutine unstable_final <>= recursive module subroutine unstable_final (object) class(unstable_t), intent(inout) :: object integer :: i if (allocated (object%decay)) then do i = 1, size (object%decay) call object%decay(i)%final () end do end if end subroutine unstable_final @ %def unstable_final @ Output. <>= procedure :: write => unstable_write <>= recursive module subroutine unstable_write (object, unit, indent) class(unstable_t), intent(in) :: object integer, intent(in), optional :: unit, indent end subroutine unstable_write <>= recursive module subroutine unstable_write (object, unit, indent) class(unstable_t), intent(in) :: object integer, intent(in), optional :: unit, indent integer :: u, ind u = given_output_unit (unit) ind = 0; if (present (indent)) ind = indent call object%config%write (u, ind, verbose=.false.) if (allocated (object%rng)) then call object%rng%write (u, ind + 2) end if call write_indent (u, ind) if (object%selected_decay > 0) then write (u, "(5x,A,I0)") "Sel. decay = ", object%selected_decay call object%decay(object%selected_decay)%write (u, ind + 1) else write (u, "(5x,A)") "Sel. decay = [undefined]" end if end subroutine unstable_write @ %def unstable_write @ Write the embedded process instances. <>= procedure :: write_process_instances => unstable_write_process_instances <>= recursive module subroutine unstable_write_process_instances & (unstable, unit, verbose) class(unstable_t), intent(in) :: unstable integer, intent(in), optional :: unit logical, intent(in), optional :: verbose end subroutine unstable_write_process_instances <>= recursive module subroutine unstable_write_process_instances & (unstable, unit, verbose) class(unstable_t), intent(in) :: unstable integer, intent(in), optional :: unit logical, intent(in), optional :: verbose if (unstable%selected_decay > 0) then call unstable%decay(unstable%selected_decay)% & write_process_instances (unit, verbose) end if end subroutine unstable_write_process_instances @ %def unstable_write_process_instances @ Initialization, using the configuration object. <>= procedure :: init => unstable_init <>= recursive module subroutine unstable_init (unstable, config) class(unstable_t), intent(out) :: unstable type(unstable_config_t), intent(in), target :: config end subroutine unstable_init <>= recursive module subroutine unstable_init (unstable, config) class(unstable_t), intent(out) :: unstable type(unstable_config_t), intent(in), target :: config integer :: i unstable%config => config allocate (unstable%decay (size (config%decay_config))) do i = 1, size (config%decay_config) call unstable%decay(i)%init (config%decay_config(i)) end do end subroutine unstable_init @ %def unstable_init @ Recursively link interactions to the parent process. [[i_prt]] is the index of the current outgoing particle in the parent interaction. <>= procedure :: link_interactions => unstable_link_interactions <>= recursive module subroutine unstable_link_interactions & (unstable, i_prt, trace) class(unstable_t), intent(inout) :: unstable integer, intent(in) :: i_prt type(interaction_t), intent(in), target :: trace end subroutine unstable_link_interactions <>= recursive module subroutine unstable_link_interactions & (unstable, i_prt, trace) class(unstable_t), intent(inout) :: unstable integer, intent(in) :: i_prt type(interaction_t), intent(in), target :: trace integer :: i do i = 1, size (unstable%decay) call unstable%decay(i)%link_interactions (i_prt, trace) end do end subroutine unstable_link_interactions @ %def unstable_link_interactions @ Import the random-number generator state. <>= procedure :: import_rng => unstable_import_rng <>= module subroutine unstable_import_rng (unstable, rng) class(unstable_t), intent(inout) :: unstable class(rng_t), intent(inout), allocatable :: rng end subroutine unstable_import_rng <>= module subroutine unstable_import_rng (unstable, rng) class(unstable_t), intent(inout) :: unstable class(rng_t), intent(inout), allocatable :: rng call move_alloc (from = rng, to = unstable%rng) end subroutine unstable_import_rng @ %def unstable_import_rng @ Generate a decay chain. First select a decay mode, then call the [[select_chain]] method of the selected mode. <>= procedure :: select_chain => unstable_select_chain <>= recursive module subroutine unstable_select_chain (unstable) class(unstable_t), intent(inout) :: unstable end subroutine unstable_select_chain <>= recursive module subroutine unstable_select_chain (unstable) class(unstable_t), intent(inout) :: unstable real(default) :: x call unstable%rng%generate (x) unstable%selected_decay = unstable%config%selector%select (x) call unstable%decay(unstable%selected_decay)%select_chain () end subroutine unstable_select_chain @ %def unstable_select_chain @ Generate a decay event. <>= procedure :: generate => unstable_generate <>= recursive module subroutine unstable_generate (unstable) class(unstable_t), intent(inout) :: unstable end subroutine unstable_generate <>= recursive module subroutine unstable_generate (unstable) class(unstable_t), intent(inout) :: unstable call unstable%decay(unstable%selected_decay)%generate () end subroutine unstable_generate @ %def unstable_generate @ \subsection{Decay Chain} While the decay configuration tree and the decay tree are static entities (during a simulation run), the decay chain is dynamically generated for each event. The reason is that with the possibility of several decay modes for each particle, and several terms for each process, the total number of distinct decay chains is not under control. Each entry in the decay chain is a connected parton state. The origin of the chain is a connected state in the parent process (not part of the chain itself). For each decay, mode and term chosen, we convolute this with the isolated (!) state of the current decay, to generate a new connected state. We accumulate this chain by recursively traversing the allocated decay tree. Whenever a particle decays, it becomes virtual and is replaced by its decay product, while all other particles stay in the parton state as spectators. Technically, we implement the decay chain as a stack structure and include information from the associated decay object for easier debugging. This is a decay chain entry: <>= type, extends (connected_state_t) :: decay_chain_entry_t private integer :: index = 0 type(decay_config_t), pointer :: config => null () integer :: selected_mci = 0 integer :: selected_term = 0 type(decay_chain_entry_t), pointer :: previous => null () end type decay_chain_entry_t @ %def decay_chain_entry_t @ This is the complete chain; we need just a pointer to the last entry. We also include a pointer to the master process instance, which serves as the seed for the decay chain. The evaluator [[correlated_trace]] traces over all quantum numbers for the final spin-correlated (but color-summed) evaluator of the decay chain. This allows us to compute the probability for a momentum configuration, given that all individual density matrices (of the initial process and the subsequent decays) have been normalized to one. Note: This trace is summed over color, so color is treated exactly when computing spin correlations. However, we do not keep non-diagonal color correlations. When an event is accepted, we compute probabilities for all color states and can choose one of them. <>= public :: decay_chain_t <>= type :: decay_chain_t private type(process_instance_t), pointer :: process_instance => null () integer :: selected_term = 0 type(evaluator_t) :: correlated_trace type(decay_chain_entry_t), pointer :: last => null () contains <> end type decay_chain_t @ %def decay_chain_t @ The finalizer recursively deletes and deallocates the entries. <>= procedure :: final => decay_chain_final <>= module subroutine decay_chain_final (object) class(decay_chain_t), intent(inout) :: object end subroutine decay_chain_final <>= module subroutine decay_chain_final (object) class(decay_chain_t), intent(inout) :: object type(decay_chain_entry_t), pointer :: entry do while (associated (object%last)) entry => object%last object%last => entry%previous call entry%final () deallocate (entry) end do call object%correlated_trace%final () end subroutine decay_chain_final @ %def decay_chain_final @ Doing output recursively allows us to display the chain in chronological order. <>= procedure :: write => decay_chain_write <>= module subroutine decay_chain_write (object, unit) class(decay_chain_t), intent(in) :: object integer, intent(in), optional :: unit end subroutine decay_chain_write <>= module subroutine decay_chain_write (object, unit) class(decay_chain_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) call write_separator (u, 2) write (u, "(1x,A)") "Decay chain:" call write_entries (object%last) call write_separator (u, 2) write (u, "(1x,A)") "Evaluator (correlated trace of the decay chain):" call write_separator (u) call object%correlated_trace%write (u) call write_separator (u, 2) contains recursive subroutine write_entries (entry) type(decay_chain_entry_t), intent(in), pointer :: entry if (associated (entry)) then call write_entries (entry%previous) call write_separator (u, 2) write (u, "(1x,A,I0)") "Decay #", entry%index call entry%config%write_header (u) write (u, "(3x,A,I0)") "Selected MCI = ", entry%selected_mci write (u, "(3x,A,I0)") "Selected term = ", entry%selected_term call entry%config%term_config(entry%selected_term)%write (u, indent=1) call entry%write (u) end if end subroutine write_entries end subroutine decay_chain_write @ %def decay_chain_write @ Build a decay chain, recursively following the selected decays and terms in a decay tree. Before start, we finalize the chain, deleting any previous contents. <>= procedure :: build => decay_chain_build <>= module subroutine decay_chain_build (chain, decay_root) class(decay_chain_t), intent(inout), target :: chain type(decay_root_t), intent(in) :: decay_root end subroutine decay_chain_build <>= module subroutine decay_chain_build (chain, decay_root) class(decay_chain_t), intent(inout), target :: chain type(decay_root_t), intent(in) :: decay_root type(quantum_numbers_mask_t), dimension(:), allocatable :: qn_mask type(interaction_t), pointer :: int_last_decay call chain%final () if (decay_root%selected_term > 0) then chain%process_instance => decay_root%process_instance chain%selected_term = decay_root%selected_term call chain%build_term_entries (decay_root%term(decay_root%selected_term)) end if int_last_decay => chain%last%get_matrix_int_ptr () allocate (qn_mask (int_last_decay%get_n_tot ())) call qn_mask%init (mask_f = .true., mask_c = .true., mask_h = .true.) call chain%correlated_trace%init_qn_sum (int_last_decay, qn_mask) end subroutine decay_chain_build @ %def decay_chain_build @ Build the entries that correspond to a decay term. We have to scan all unstable particles. <>= procedure :: build_term_entries => decay_chain_build_term_entries <>= recursive module subroutine decay_chain_build_term_entries (chain, term) class(decay_chain_t), intent(inout) :: chain type(decay_term_t), intent(in) :: term end subroutine decay_chain_build_term_entries <>= recursive module subroutine decay_chain_build_term_entries (chain, term) class(decay_chain_t), intent(inout) :: chain type(decay_term_t), intent(in) :: term integer :: i do i = 1, size (term%particle_out) select type (unstable => term%particle_out(i)%c) type is (unstable_t) if (unstable%selected_decay > 0) then call chain%build_decay_entries & (unstable%decay(unstable%selected_decay)) end if end select end do end subroutine decay_chain_build_term_entries @ %def decay_chain_build_term_entries @ Build the entries that correspond to a specific decay. The decay term should have been determined, so we allocate a decay chain entry and fill it, then proceed to child decays. For the first entry, we convolute the connected state of the parent process instance with the isolated state of the current decay (which does not contain an extra beam entry for the parent). For subsequent entries, we take the previous entry as first factor. In principle, each chain entry (as a parton state) is capable of holding a subevent object and associated expressions. We currently do not make use of that feature. Before generating the decays, factor out the trace of the helicity density matrix of the parent parton state. This trace has been used for unweighting the original event (unweighted case) or it determines the overall weight, so it should not be taken into account in the decay chain generation. <>= procedure :: build_decay_entries => decay_chain_build_decay_entries <>= recursive module subroutine decay_chain_build_decay_entries (chain, decay) class(decay_chain_t), intent(inout) :: chain type(decay_t), intent(in) :: decay end subroutine decay_chain_build_decay_entries <>= recursive module subroutine decay_chain_build_decay_entries (chain, decay) class(decay_chain_t), intent(inout) :: chain type(decay_t), intent(in) :: decay type(decay_chain_entry_t), pointer :: entry type(connected_state_t), pointer :: previous_state type(isolated_state_t), pointer :: current_decay type(helicity_t) :: hel type(quantum_numbers_t) :: qn_filter_conn allocate (entry) if (associated (chain%last)) then entry%previous => chain%last entry%index = entry%previous%index + 1 previous_state => entry%previous%connected_state_t else entry%index = 1 previous_state => & chain%process_instance%get_connected_state_ptr (chain%selected_term) end if entry%config => decay%config entry%selected_mci = decay%selected_mci entry%selected_term = decay%selected_term current_decay => decay%process_instance%get_isolated_state_ptr & (decay%selected_term) call entry%setup_connected_trace & (current_decay, previous_state%get_trace_int_ptr (), resonant=.true.) if (entry%config%flv%has_decay_helicity ()) then call hel%init (entry%config%flv%get_decay_helicity ()) call qn_filter_conn%init (hel) call entry%setup_connected_matrix & (current_decay, previous_state%get_matrix_int_ptr (), & resonant=.true., qn_filter_conn = qn_filter_conn) call entry%setup_connected_flows & (current_decay, previous_state%get_flows_int_ptr (), & resonant=.true., qn_filter_conn = qn_filter_conn) else call entry%setup_connected_matrix & (current_decay, previous_state%get_matrix_int_ptr (), & resonant=.true.) call entry%setup_connected_flows & (current_decay, previous_state%get_flows_int_ptr (), & resonant=.true.) end if chain%last => entry call chain%build_term_entries (decay%term(decay%selected_term)) end subroutine decay_chain_build_decay_entries @ %def decay_chain_build_decay_entries @ Recursively fill the decay chain with momenta and evaluate the matrix elements. Since all evaluators should have correct source entries at this point, momenta are automatically retrieved from the appropriate process instance. Like we did above for the parent process, factor out the trace for each subsequent decay (the helicity density matrix in the isolated state, which is taken for the convolution). <>= procedure :: evaluate => decay_chain_evaluate <>= module subroutine decay_chain_evaluate (chain) class(decay_chain_t), intent(inout) :: chain end subroutine decay_chain_evaluate <>= module subroutine decay_chain_evaluate (chain) class(decay_chain_t), intent(inout) :: chain call evaluate (chain%last) call chain%correlated_trace%receive_momenta () call chain%correlated_trace%evaluate () contains recursive subroutine evaluate (entry) type(decay_chain_entry_t), intent(inout), pointer :: entry if (associated (entry)) then call evaluate (entry%previous) call entry%receive_kinematics () call entry%evaluate_trace () call entry%evaluate_event_data () end if end subroutine evaluate end subroutine decay_chain_evaluate @ %def decay_chain_evaluate @ Return the probability of a decay chain. This is given as the trace of the density matrix with intermediate helicity correlations, normalized by the product of the uncorrelated density matrix traces. This works only if an event has been evaluated and the [[correlated_trace]] evaluator is filled. By definition, this evaluator has only one matrix element, and this must be real. <>= procedure :: get_probability => decay_chain_get_probability <>= module function decay_chain_get_probability (chain) result (x) class(decay_chain_t), intent(in) :: chain real(default) :: x end function decay_chain_get_probability <>= module function decay_chain_get_probability (chain) result (x) class(decay_chain_t), intent(in) :: chain real(default) :: x x = real (chain%correlated_trace%get_matrix_element (1)) end function decay_chain_get_probability @ %def decay_chain_get_probability @ \subsection{Decay as Event Transform} The [[evt_decay]] object combines decay configuration, decay tree, and chain in a single object, as an implementation of the [[evt]] (event transform) abstract type. The [[var_list]] may be a pointer to the user variable list, which could contain overridden parameters for the decay processes. <>= public :: evt_decay_t <>= type, extends (evt_t) :: evt_decay_t private type(decay_root_config_t) :: decay_root_config type(decay_root_t) :: decay_root type(decay_chain_t) :: decay_chain type(var_list_t), pointer :: var_list => null () contains <> end type evt_decay_t @ %def evt_decay_t @ <>= procedure :: write_name => evt_decay_write_name <>= module subroutine evt_decay_write_name (evt, unit) class(evt_decay_t), intent(in) :: evt integer, intent(in), optional :: unit end subroutine evt_decay_write_name <>= module subroutine evt_decay_write_name (evt, unit) class(evt_decay_t), intent(in) :: evt integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(1x,A)") "Event transform: partonic decays" end subroutine evt_decay_write_name @ %def evt_decay_write_name @ Output. We display the currently selected decay tree, which includes configuration data, and the decay chain, i.e., the evaluators. <>= procedure :: write => evt_decay_write <>= module subroutine evt_decay_write & (evt, unit, verbose, more_verbose, testflag) class(evt_decay_t), intent(in) :: evt integer, intent(in), optional :: unit logical, intent(in), optional :: verbose, more_verbose, testflag end subroutine evt_decay_write <>= module subroutine evt_decay_write (evt, unit, verbose, more_verbose, testflag) class(evt_decay_t), intent(in) :: evt integer, intent(in), optional :: unit logical, intent(in), optional :: verbose, more_verbose, testflag logical :: verb, verb2 integer :: u u = given_output_unit (unit) verb = .true.; if (present (verbose)) verb = verbose verb2 = .false.; if (present (more_verbose)) verb2 = more_verbose call write_separator (u, 2) call evt%write_name (u) call write_separator (u, 2) call evt%base_write (u, testflag = testflag) if (associated (evt%var_list)) then call write_separator (u) write (u, "(1x,A)") "Variable list for simulation: & &[associated, not shown]" end if if (verb) then call write_separator (u) call evt%decay_root%write (u) if (verb2) then call evt%decay_chain%write (u) call evt%decay_root%write_process_instances (u, verb) end if else call write_separator (u, 2) end if end subroutine evt_decay_write @ %def evt_decay_write @ Set the pointer to a user variable list. <>= procedure :: set_var_list => evt_decay_set_var_list <>= module subroutine evt_decay_set_var_list (evt, var_list) class(evt_decay_t), intent(inout) :: evt type(var_list_t), intent(in), target :: var_list end subroutine evt_decay_set_var_list <>= module subroutine evt_decay_set_var_list (evt, var_list) class(evt_decay_t), intent(inout) :: evt type(var_list_t), intent(in), target :: var_list evt%var_list => var_list end subroutine evt_decay_set_var_list @ %def evt_decay_set_var_list @ Connect with a process instance and process. This initializes the decay configuration. The process stack is used to look for process objects that implement daughter decays. When all processes are assigned, configure the decay tree instance, using the decay tree configuration. First obtain the branching ratios, then allocate the decay tree. This is done once for all events. <>= procedure :: connect => evt_decay_connect <>= module subroutine evt_decay_connect & (evt, process_instance, model, process_stack) class(evt_decay_t), intent(inout), target :: evt type(process_instance_t), intent(in), target :: process_instance class(model_data_t), intent(in), target :: model type(process_stack_t), intent(in), optional :: process_stack end subroutine evt_decay_connect <>= module subroutine evt_decay_connect & (evt, process_instance, model, process_stack) class(evt_decay_t), intent(inout), target :: evt type(process_instance_t), intent(in), target :: process_instance class(model_data_t), intent(in), target :: model type(process_stack_t), intent(in), optional :: process_stack call evt%base_connect (process_instance, model) if (associated (evt%var_list)) then call evt%decay_root_config%connect (process_instance%process, & model, process_stack, process_instance, evt%var_list) else call evt%decay_root_config%connect (process_instance%process, & model, process_stack, process_instance) end if call evt%decay_root_config%compute () call evt%decay_root%init (evt%decay_root_config, evt%process_instance) end subroutine evt_decay_connect @ %def evt_decay_connect @ Prepare a new event: Select a decay chain and build the corresponding chain object. <>= procedure :: prepare_new_event => evt_decay_prepare_new_event <>= module subroutine evt_decay_prepare_new_event (evt, i_mci, i_term) class(evt_decay_t), intent(inout) :: evt integer, intent(in) :: i_mci, i_term end subroutine evt_decay_prepare_new_event <>= module subroutine evt_decay_prepare_new_event (evt, i_mci, i_term) class(evt_decay_t), intent(inout) :: evt integer, intent(in) :: i_mci, i_term call evt%reset () evt%decay_root%selected_mci = i_mci evt%decay_root%selected_term = i_term call evt%decay_root%select_chain () call evt%decay_chain%build (evt%decay_root) end subroutine evt_decay_prepare_new_event @ %def evt_decay_prepare_new_event @ Generate a weighted event and assign the resulting weight (probability). We use a chain initialized by the preceding subroutine, fill it with momenta and evaluate. <>= procedure :: generate_weighted => evt_decay_generate_weighted <>= module subroutine evt_decay_generate_weighted (evt, probability) class(evt_decay_t), intent(inout) :: evt real(default), intent(inout) :: probability end subroutine evt_decay_generate_weighted <>= module subroutine evt_decay_generate_weighted (evt, probability) class(evt_decay_t), intent(inout) :: evt real(default), intent(inout) :: probability call evt%decay_root%generate () if (signal_is_pending ()) return call evt%decay_chain%evaluate () probability = evt%decay_chain%get_probability () end subroutine evt_decay_generate_weighted @ %def evt_decay_generate_weighted @ To create a usable event, we have to transform the interaction into a particle set; this requires factorization for the correlated density matrix, according to the factorization mode. <>= procedure :: make_particle_set => evt_decay_make_particle_set <>= module subroutine evt_decay_make_particle_set & (evt, factorization_mode, keep_correlations, r) class(evt_decay_t), intent(inout) :: evt integer, intent(in) :: factorization_mode logical, intent(in) :: keep_correlations real(default), dimension(:), intent(in), optional :: r end subroutine evt_decay_make_particle_set <>= module subroutine evt_decay_make_particle_set & (evt, factorization_mode, keep_correlations, r) class(evt_decay_t), intent(inout) :: evt integer, intent(in) :: factorization_mode logical, intent(in) :: keep_correlations real(default), dimension(:), intent(in), optional :: r type(interaction_t), pointer :: int_matrix, int_flows type(decay_chain_entry_t), pointer :: last_entry last_entry => evt%decay_chain%last int_matrix => last_entry%get_matrix_int_ptr () int_flows => last_entry%get_flows_int_ptr () call evt%factorize_interactions (int_matrix, int_flows, & factorization_mode, keep_correlations, r) call evt%tag_incoming () end subroutine evt_decay_make_particle_set @ %def event_decay_make_particle_set @ \subsubsection{Auxiliary} Eliminate numerical noise for the associated process instances. <>= public :: pacify <>= interface pacify module procedure pacify_decay module procedure pacify_decay_gen module procedure pacify_term module procedure pacify_unstable end interface pacify <>= module subroutine pacify_decay (evt) class(evt_decay_t), intent(inout) :: evt end subroutine pacify_decay recursive module subroutine pacify_decay_gen (decay) class(decay_gen_t), intent(inout) :: decay end subroutine pacify_decay_gen recursive module subroutine pacify_term (term) class(decay_term_t), intent(inout) :: term end subroutine pacify_term recursive module subroutine pacify_unstable (unstable) class(unstable_t), intent(inout) :: unstable end subroutine pacify_unstable <>= module subroutine pacify_decay (evt) class(evt_decay_t), intent(inout) :: evt call pacify_decay_gen (evt%decay_root) end subroutine pacify_decay recursive module subroutine pacify_decay_gen (decay) class(decay_gen_t), intent(inout) :: decay if (associated (decay%process_instance)) then call pacify (decay%process_instance) end if if (decay%selected_term > 0) then call pacify_term (decay%term(decay%selected_term)) end if end subroutine pacify_decay_gen recursive module subroutine pacify_term (term) class(decay_term_t), intent(inout) :: term integer :: i do i = 1, size (term%particle_out) select type (unstable => term%particle_out(i)%c) type is (unstable_t); call pacify_unstable (unstable) end select end do end subroutine pacify_term recursive module subroutine pacify_unstable (unstable) class(unstable_t), intent(inout) :: unstable if (unstable%selected_decay > 0) then call pacify_decay_gen (unstable%decay(unstable%selected_decay)) end if end subroutine pacify_unstable @ %def pacify @ Prepare specific configurations for use in unit tests. <>= procedure :: init_test_case1 procedure :: init_test_case2 <>= module subroutine init_test_case1 & (unstable, i, flv, integral, relerr, model) class(unstable_config_t), intent(inout) :: unstable integer, intent(in) :: i type(flavor_t), dimension(:,:), intent(in) :: flv real(default), intent(in) :: integral real(default), intent(in) :: relerr class(model_data_t), intent(in), target :: model end subroutine init_test_case1 module subroutine init_test_case2 (unstable, flv1, flv21, flv22, model) class(unstable_config_t), intent(inout) :: unstable type(flavor_t), dimension(:,:), intent(in) :: flv1, flv21, flv22 class(model_data_t), intent(in), target :: model end subroutine init_test_case2 <>= module subroutine init_test_case1 (unstable, i, flv, integral, relerr, model) class(unstable_config_t), intent(inout) :: unstable integer, intent(in) :: i type(flavor_t), dimension(:,:), intent(in) :: flv real(default), intent(in) :: integral real(default), intent(in) :: relerr class(model_data_t), intent(in), target :: model associate (decay => unstable%decay_config(i)) allocate (decay%term_config (1)) call decay%init_term (1, flv, stable = [.true., .true.], model=model) decay%integral = integral decay%abs_error = integral * relerr end associate end subroutine init_test_case1 module subroutine init_test_case2 (unstable, flv1, flv21, flv22, model) class(unstable_config_t), intent(inout) :: unstable type(flavor_t), dimension(:,:), intent(in) :: flv1, flv21, flv22 class(model_data_t), intent(in), target :: model associate (decay => unstable%decay_config(1)) decay%integral = 1.e-3_default decay%abs_error = decay%integral * .01_default allocate (decay%term_config (1)) call decay%init_term (1, flv1, stable = [.false., .true.], model=model) select type (w => decay%term_config(1)%prt(1)%c) type is (unstable_config_t) associate (w_decay => w%decay_config(1)) w_decay%integral = 2._default allocate (w_decay%term_config (1)) call w_decay%init_term (1, flv21, stable = [.true., .true.], & model=model) end associate associate (w_decay => w%decay_config(2)) w_decay%integral = 1._default allocate (w_decay%term_config (1)) call w_decay%init_term (1, flv22, stable = [.true., .true.], & model=model) end associate call w%compute () end select end associate end subroutine init_test_case2 @ %def init_test_case1 @ %def init_test_case2 @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[decays_ut.f90]]>>= <> module decays_ut use unit_tests use decays_uti <> <> <> contains <> end module decays_ut @ %def decays_ut @ <<[[decays_uti.f90]]>>= <> module decays_uti <> <> use os_interface use sm_qcd use model_data use models use state_matrices, only: FM_IGNORE_HELICITY use interactions, only: reset_interaction_counter use flavors use process_libraries use rng_base use mci_base use mci_midpoint use phs_base use phs_single use prc_core use prc_test, only: prc_test_create_library use process, only: process_t use instances, only: process_instance_t use process_stacks use decays use rng_base_ut, only: rng_test_t, rng_test_factory_t <> <> <> contains <> <> end module decays_uti @ %def decays_uti @ API: driver for the unit tests below. <>= public :: decays_test <>= subroutine decays_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine decays_test @ %def decays_test @ \subsubsection{Testbed} As a variation of the [[prepare_test_process]] routine used elsewhere, we define here a routine that creates two processes (scattering $ss\to ss$ and decay $s\to f\bar f$), compiles and integrates them and prepares for event generation. <>= public :: prepare_testbed <>= subroutine prepare_testbed & (lib, process_stack, prefix, os_data, & scattering, decay, decay_rest_frame) type(process_library_t), intent(out), target :: lib type(process_stack_t), intent(out) :: process_stack type(string_t), intent(in) :: prefix type(os_data_t), intent(in) :: os_data logical, intent(in) :: scattering, decay logical, intent(in), optional :: decay_rest_frame type(model_t), target :: model type(model_t), target :: model_copy type(string_t) :: libname, procname1, procname2 type(process_entry_t), pointer :: process type(process_instance_t), allocatable, target :: process_instance class(phs_config_t), allocatable :: phs_config_template type(field_data_t), pointer :: field_data real(default) :: sqrts libname = prefix // "_lib" procname1 = prefix // "_p" procname2 = prefix // "_d" call model%init_test () call model%set_par (var_str ("ff"), 0.4_default) call model%set_par (var_str ("mf"), & model%get_real (var_str ("ff")) * model%get_real (var_str ("ms"))) if (scattering .and. decay) then field_data => model%get_field_ptr (25) call field_data%set (p_is_stable = .false.) end if call prc_test_create_library (libname, lib, & scattering = .true., decay = .true., & procname1 = procname1, procname2 = procname2) call reset_interaction_counter () allocate (phs_single_config_t :: phs_config_template) if (scattering) then call model_copy%init (model%get_name (), & model%get_n_real (), & model%get_n_complex (), & model%get_n_field (), & model%get_n_vtx ()) call model_copy%copy_from (model) allocate (process) call process%init (procname1, lib, os_data, model_copy) call process%setup_test_cores () call process%init_components (phs_config_template) sqrts = 1000 call process%setup_beams_sqrts (sqrts, i_core = 1) call process%configure_phs () call process%setup_mci (dispatch_mci_test_midpoint) call process%setup_terms () allocate (process_instance) call process_instance%init (process%process_t) call process_instance%integrate (1, n_it = 1, n_calls = 100) call process%final_integration (1) call process_instance%final () deallocate (process_instance) call process%prepare_simulation (1) call process_stack%push (process) end if if (decay) then call model_copy%init (model%get_name (), & model%get_n_real (), & model%get_n_complex (), & model%get_n_field (), & model%get_n_vtx ()) call model_copy%copy_from (model) allocate (process) call process%init (procname2, lib, os_data, model_copy) call process%setup_test_cores () call process%init_components (phs_config_template) if (present (decay_rest_frame)) then call process%setup_beams_decay (rest_frame = decay_rest_frame, i_core = 1) else call process%setup_beams_decay (rest_frame = .not. scattering, i_core = 1) end if call process%configure_phs () call process%setup_mci (dispatch_mci_test_midpoint) call process%setup_terms () allocate (process_instance) call process_instance%init (process%process_t) call process_instance%integrate (1, n_it=1, n_calls=100) call process%final_integration (1) call process_instance%final () deallocate (process_instance) call process%prepare_simulation (1) call process_stack%push (process) end if call model%final () call model_copy%final () end subroutine prepare_testbed @ %def prepare_testbed @ MCI record prepared for midpoint integrator. <>= subroutine dispatch_mci_test_midpoint (mci, var_list, process_id, is_nlo) use variables, only: var_list_t 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 allocate (mci_midpoint_t :: mci) end subroutine dispatch_mci_test_midpoint @ %def dispatch_mci_test_midpoint @ \subsubsection{Simple decay configuration} We define a branching configuration with two decay modes. We set the integral values by hand, so we do not need to evaluate processes, yet. <>= call test (decays_1, "decays_1", & "branching and decay configuration", & u, results) <>= public :: decays_1 <>= subroutine decays_1 (u) integer, intent(in) :: u type(os_data_t) :: os_data type(model_data_t), target :: model type(flavor_t) :: flv_h type(flavor_t), dimension(2,1) :: flv_hbb, flv_hgg type(unstable_config_t), allocatable :: unstable write (u, "(A)") "* Test output: decays_1" write (u, "(A)") "* Purpose: Set up branching and decay configuration" write (u, "(A)") write (u, "(A)") "* Initialize environment" write (u, "(A)") call os_data%init () call model%init_sm_test () call flv_h%init (25, model) call flv_hbb(:,1)%init ([5, -5], model) call flv_hgg(:,1)%init ([22, 22], model) write (u, "(A)") "* Set up branching and decay" write (u, "(A)") allocate (unstable) call unstable%init (flv_h) call unstable%init_decays ([var_str ("h_bb"), var_str ("h_gg")], model) call unstable%init_test_case1 & (1, flv_hbb, 1.234e-3_default, .02_default, model) call unstable%init_test_case1 & (2, flv_hgg, 3.085e-4_default, .08_default, model) call unstable%compute () call unstable%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call unstable%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: decays_1" end subroutine decays_1 @ %def decays_1 @ \subsubsection{Cascade decay configuration} We define a branching configuration with one decay, which is followed by another branching. <>= call test (decays_2, "decays_2", & "cascade decay configuration", & u, results) <>= public :: decays_2 <>= subroutine decays_2 (u) integer, intent(in) :: u type(os_data_t) :: os_data type(model_data_t), target :: model type(flavor_t) :: flv_h, flv_wp, flv_wm type(flavor_t), dimension(2,1) :: flv_hww, flv_wud, flv_wen type(unstable_config_t), allocatable :: unstable write (u, "(A)") "* Test output: decays_2" write (u, "(A)") "* Purpose: Set up cascade branching" write (u, "(A)") write (u, "(A)") "* Initialize environment" write (u, "(A)") call os_data%init () call model%init_sm_test () call model%set_unstable (25, [var_str ("h_ww")]) call model%set_unstable (24, [var_str ("w_ud"), var_str ("w_en")]) call flv_h%init (25, model) call flv_hww(:,1)%init ([24, -24], model) call flv_wp%init (24, model) call flv_wm%init (-24, model) call flv_wud(:,1)%init ([2, -1], model) call flv_wen(:,1)%init ([-11, 12], model) write (u, "(A)") "* Set up branching and decay" write (u, "(A)") allocate (unstable) call unstable%init (flv_h, set_decays=.true., model=model) call unstable%init_test_case2 (flv_hww, flv_wud, flv_wen, model) call unstable%compute () call unstable%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call unstable%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: decays_2" end subroutine decays_2 @ %def decays_2 @ \subsubsection{Decay and Process Object} We define a branching configuration with one decay and connect this with an actual process object. <>= call test (decays_3, "decays_3", & "associate process", & u, results) <>= public :: decays_3 <>= subroutine decays_3 (u) integer, intent(in) :: u type(os_data_t) :: os_data class(model_data_t), pointer :: model type(process_library_t), target :: lib type(string_t) :: prefix type(string_t) :: procname2 type(process_stack_t) :: process_stack type(process_t), pointer :: process type(unstable_config_t), allocatable :: unstable type(flavor_t) :: flv write (u, "(A)") "* Test output: decays_3" write (u, "(A)") "* Purpose: Connect a decay configuration & &with a process" write (u, "(A)") write (u, "(A)") "* Initialize environment and integrate process" write (u, "(A)") call os_data%init () prefix = "decays_3" call prepare_testbed & (lib, process_stack, prefix, os_data, & scattering=.false., decay=.true., decay_rest_frame=.false.) procname2 = prefix // "_d" process => process_stack%get_process_ptr (procname2) model => process%get_model_ptr () call process%write (.false., u) write (u, "(A)") write (u, "(A)") "* Set up branching and decay" write (u, "(A)") call flv%init (25, model) allocate (unstable) call unstable%init (flv) call unstable%init_decays ([procname2], model) write (u, "(A)") "* Connect decay with process object" write (u, "(A)") call unstable%connect_decay (1, process, model) call unstable%compute () call unstable%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call unstable%final () call process_stack%final () write (u, "(A)") write (u, "(A)") "* Test output end: decays_3" end subroutine decays_3 @ %def decays_3 @ \subsubsection{Decay and Process Object} Building upon the previous test, we set up a decay instance and generate a decay event. <>= call test (decays_4, "decays_4", & "decay instance", & u, results) <>= public :: decays_4 <>= subroutine decays_4 (u) integer, intent(in) :: u type(os_data_t) :: os_data class(model_data_t), pointer :: model type(process_library_t), target :: lib type(string_t) :: prefix, procname2 class(rng_t), allocatable :: rng type(process_stack_t) :: process_stack type(process_t), pointer :: process type(unstable_config_t), allocatable, target :: unstable type(flavor_t) :: flv type(unstable_t), allocatable :: instance write (u, "(A)") "* Test output: decays_4" write (u, "(A)") "* Purpose: Create a decay process and evaluate & &an instance" write (u, "(A)") write (u, "(A)") "* Initialize environment, process, & &and decay configuration" write (u, "(A)") call os_data%init () prefix = "decays_4" call prepare_testbed & (lib, process_stack, prefix, os_data, & scattering=.false., decay=.true., decay_rest_frame = .false.) procname2 = prefix // "_d" process => process_stack%get_process_ptr (procname2) model => process%get_model_ptr () call flv%init (25, model) allocate (unstable) call unstable%init (flv) call unstable%init_decays ([procname2], model) call model%set_unstable (25, [procname2]) call unstable%connect_decay (1, process, model) call unstable%compute () allocate (rng_test_t :: rng) allocate (instance) call instance%init (unstable) call instance%import_rng (rng) call instance%select_chain () call instance%generate () call instance%write (u) write (u, *) call instance%write_process_instances (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call instance%final () call process_stack%final () call unstable%final () write (u, "(A)") write (u, "(A)") "* Test output end: decays_4" end subroutine decays_4 @ %def decays_4 @ \subsubsection{Decay with Parent Process} We define a scattering process $ss\to ss$ and subsequent decays $s\to f\bar f$. <>= call test (decays_5, "decays_5", & "parent process and decay", & u, results) <>= public :: decays_5 <>= subroutine decays_5 (u) integer, intent(in) :: u type(os_data_t) :: os_data class(model_data_t), pointer :: model type(process_library_t), target :: lib type(string_t) :: prefix, procname1, procname2 type(process_stack_t) :: process_stack type(process_t), pointer :: process type(process_instance_t), allocatable, target :: process_instance type(decay_root_config_t), target :: decay_root_config type(decay_root_t) :: decay_root type(decay_chain_t) :: decay_chain write (u, "(A)") "* Test output: decays_5" write (u, "(A)") "* Purpose: Handle a process with subsequent decays" write (u, "(A)") write (u, "(A)") "* Initialize environment and parent process" write (u, "(A)") call os_data%init () prefix = "decays_5" procname1 = prefix // "_p" procname2 = prefix // "_d" call prepare_testbed & (lib, process_stack, prefix, os_data, & scattering=.true., decay=.true.) write (u, "(A)") "* Initialize decay process" write (u, "(A)") process => process_stack%get_process_ptr (procname1) model => process%get_model_ptr () call model%set_unstable (25, [procname2]) write (u, "(A)") "* Initialize decay tree configuration" write (u, "(A)") call decay_root_config%connect (process, model, process_stack) call decay_root_config%compute () call decay_root_config%write (u) write (u, "(A)") write (u, "(A)") "* Initialize decay tree" allocate (process_instance) call process_instance%init (process) call process_instance%setup_event_data () call process_instance%init_simulation (1) call decay_root%init (decay_root_config, process_instance) write (u, "(A)") write (u, "(A)") "* Select decay chain" write (u, "(A)") call decay_root%set_mci (1) !!! Not yet implemented; there is only one term anyway: ! call process_instance%select_i_term (decay_root%selected_term) call decay_root%set_term (1) call decay_root%select_chain () call decay_chain%build (decay_root) call decay_root%write (u) write (u, "(A)") write (u, "(A)") "* Generate event" write (u, "(A)") call process_instance%generate_unweighted_event (decay_root%get_mci ()) call process_instance%evaluate_event_data () call decay_root%generate () call pacify (decay_root) write (u, "(A)") "* Process instances" write (u, "(A)") call decay_root%write_process_instances (u) write (u, "(A)") write (u, "(A)") "* Generate decay chain" write (u, "(A)") call decay_chain%evaluate () call decay_chain%write (u) write (u, *) write (u, "(A,ES19.12)") "chain probability =", & decay_chain%get_probability () write (u, "(A)") write (u, "(A)") "* Cleanup" call decay_chain%final () call decay_root%final () call decay_root_config%final () call process_instance%final () deallocate (process_instance) call process_stack%final () write (u, "(A)") write (u, "(A)") "* Test output end: decays_5" end subroutine decays_5 @ %def decays_5 @ \subsubsection{Decay as Event Transform} Again, we define a scattering process $ss\to ss$ and subsequent decays $s\to f\bar f$. <>= call test (decays_6, "decays_6", & "evt_decay object", & u, results) <>= public :: decays_6 <>= subroutine decays_6 (u) integer, intent(in) :: u type(os_data_t) :: os_data class(model_data_t), pointer :: model type(process_library_t), target :: lib type(string_t) :: prefix, procname1, procname2 type(process_stack_t) :: process_stack type(process_t), pointer :: process type(process_instance_t), allocatable, target :: process_instance type(evt_decay_t), target :: evt_decay integer :: factorization_mode logical :: keep_correlations write (u, "(A)") "* Test output: decays_6" write (u, "(A)") "* Purpose: Handle a process with subsequent decays" write (u, "(A)") write (u, "(A)") "* Initialize environment and parent process" write (u, "(A)") call os_data%init () prefix = "decays_6" procname1 = prefix // "_p" procname2 = prefix // "_d" call prepare_testbed & (lib, process_stack, prefix, os_data, & scattering=.true., decay=.true.) write (u, "(A)") "* Initialize decay process" process => process_stack%get_process_ptr (procname1) model => process%get_model_ptr () call model%set_unstable (25, [procname2]) allocate (process_instance) call process_instance%init (process) call process_instance%setup_event_data () call process_instance%init_simulation (1) write (u, "(A)") write (u, "(A)") "* Initialize decay object" call evt_decay%connect (process_instance, model, process_stack) write (u, "(A)") write (u, "(A)") "* Generate scattering event" call process_instance%generate_unweighted_event (1) call process_instance%evaluate_event_data () write (u, "(A)") write (u, "(A)") "* Select decay chain and generate event" write (u, "(A)") call evt_decay%prepare_new_event (1, 1) call evt_decay%generate_unweighted () factorization_mode = FM_IGNORE_HELICITY keep_correlations = .false. call evt_decay%make_particle_set (factorization_mode, keep_correlations) call evt_decay%write (u, verbose = .true.) write (u, "(A)") write (u, "(A)") "* Cleanup" call evt_decay%final () call process_instance%final () deallocate (process_instance) call process_stack%final () write (u, "(A)") write (u, "(A)") "* Test output end: decays_6" end subroutine decays_6 @ %def decays_6 @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Tau decays} <<[[tau_decays.f90]]>>= <> module tau_decays <> use sm_qcd use model_data use models use event_transforms <> <> <> interface <> end interface end module tau_decays @ <<[[tau_decays_sub.f90]]>>= <> submodule (tau_decays) tau_decays_s use io_units use format_utils, only: write_separator implicit none contains <> end submodule tau_decays_s @ %def tau_decays_s @ @ %def tau_decays \subsection{Tau Decays Event Transform} This is the type for the tau decay event transform. <>= public :: evt_tau_decays_t <>= type, extends (evt_t) :: evt_tau_decays_t type(model_t), pointer :: model_hadrons => null() type(qcd_t) :: qcd contains <> end type evt_tau_decays_t @ %def evt_tau_decays_t <>= procedure :: write_name => evt_tau_decays_write_name <>= module subroutine evt_tau_decays_write_name (evt, unit) class(evt_tau_decays_t), intent(in) :: evt integer, intent(in), optional :: unit end subroutine evt_tau_decays_write_name <>= module subroutine evt_tau_decays_write_name (evt, unit) class(evt_tau_decays_t), intent(in) :: evt integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(1x,A)") "Event transform: tau decays" end subroutine evt_tau_decays_write_name @ %def evt_tau_decays_write_name @ Output. <>= procedure :: write => evt_tau_decays_write <>= module subroutine evt_tau_decays_write & (evt, unit, verbose, more_verbose, testflag) class(evt_tau_decays_t), intent(in) :: evt integer, intent(in), optional :: unit logical, intent(in), optional :: verbose, more_verbose, testflag end subroutine evt_tau_decays_write <>= module subroutine evt_tau_decays_write & (evt, unit, verbose, more_verbose, testflag) class(evt_tau_decays_t), intent(in) :: evt integer, intent(in), optional :: unit logical, intent(in), optional :: verbose, more_verbose, testflag integer :: u u = given_output_unit (unit) call write_separator (u, 2) call evt%write_name (u) call write_separator (u) call evt%base_write (u, testflag = testflag, show_set = .false.) if (evt%particle_set_exists) & call evt%particle_set%write & (u, summary = .true., compressed = .true., testflag = testflag) call write_separator (u) end subroutine evt_tau_decays_write @ %def evt_tau_decays_write @ Here we take the particle set from the previous event transform and apply the tau decays. What probability should be given back, the product of branching ratios of the corresponding tau decays? <>= procedure :: generate_weighted => evt_tau_decays_generate_weighted <>= module subroutine evt_tau_decays_generate_weighted (evt, probability) class(evt_tau_decays_t), intent(inout) :: evt real(default), intent(inout) :: probability end subroutine evt_tau_decays_generate_weighted <>= module subroutine evt_tau_decays_generate_weighted (evt, probability) class(evt_tau_decays_t), intent(inout) :: evt real(default), intent(inout) :: probability logical :: valid evt%particle_set = evt%previous%particle_set !!! To be checked or expanded probability = 1 valid = .true. evt%particle_set_exists = valid end subroutine evt_tau_decays_generate_weighted @ %def evt_tau_decays_generate_weighted @ The factorization parameters are irrelevant. <>= procedure :: make_particle_set => evt_tau_decays_make_particle_set <>= module subroutine evt_tau_decays_make_particle_set & (evt, factorization_mode, keep_correlations, r) class(evt_tau_decays_t), intent(inout) :: evt integer, intent(in) :: factorization_mode logical, intent(in) :: keep_correlations real(default), dimension(:), intent(in), optional :: r end subroutine evt_tau_decays_make_particle_set <>= module subroutine evt_tau_decays_make_particle_set & (evt, factorization_mode, keep_correlations, r) class(evt_tau_decays_t), intent(inout) :: evt integer, intent(in) :: factorization_mode logical, intent(in) :: keep_correlations real(default), dimension(:), intent(in), optional :: r logical :: valid !!! to be checked and expanded valid = .true. evt%particle_set_exists = evt%particle_set_exists .and. valid end subroutine evt_tau_decays_make_particle_set @ %def event_tau_decays_make_particle_set @ <>= procedure :: prepare_new_event => evt_tau_decays_prepare_new_event <>= module subroutine evt_tau_decays_prepare_new_event (evt, i_mci, i_term) class(evt_tau_decays_t), intent(inout) :: evt integer, intent(in) :: i_mci, i_term end subroutine evt_tau_decays_prepare_new_event <>= module subroutine evt_tau_decays_prepare_new_event (evt, i_mci, i_term) class(evt_tau_decays_t), intent(inout) :: evt integer, intent(in) :: i_mci, i_term call evt%reset () end subroutine evt_tau_decays_prepare_new_event @ %def evt_tau_decays_prepare_new_event @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Shower} We might use matrix elements of LO and NLO to increase the accuracy of the shower in the sense of matching as well as merging. <<[[shower.f90]]>>= <> module shower <> <> use os_interface use pdf use shower_base use matching_base use sm_qcd use model_data use event_transforms use models use process, only: process_t use instances, only: process_instance_t use process_stacks <> <> <> <> interface <> end interface end module shower @ %def shower @ <<[[shower_sub.f90]]>>= <> submodule (shower) shower_s <> use io_units use format_utils, only: write_separator use system_defs, only: LF use diagnostics use lorentz use subevents, only: PRT_BEAM_REMNANT, PRT_INCOMING, PRT_OUTGOING use powheg_matching, only: powheg_matching_t use rng_base use hep_common implicit none contains <> end submodule shower_s @ %def shower_s @ \subsection{Configuration Parameters} [[POWHEG_TESTING]] allows to disable the parton shower for validation and testing of the POWHEG procedure. <>= logical, parameter :: POWHEG_TESTING = .true. @ %def POWHEG_TESTING @ \subsection{Event Transform} The event transforms can do more than mere showering. Especially, it may reweight showered events to fixed-order matrix elements. The [[model_hadrons]] is supposed to be the SM variant that contains all hadrons that can be generated in the shower. <>= public :: evt_shower_t <>= type, extends (evt_t) :: evt_shower_t class(shower_base_t), allocatable :: shower class(matching_t), allocatable :: matching type(model_t), pointer :: model_hadrons => null () type(qcd_t) :: qcd type(pdf_data_t) :: pdf_data type(os_data_t) :: os_data logical :: is_first_event contains <> end type evt_shower_t @ %def evt_shower_t @ <>= procedure :: write_name => evt_shower_write_name <>= module subroutine evt_shower_write_name (evt, unit) class(evt_shower_t), intent(in) :: evt integer, intent(in), optional :: unit end subroutine evt_shower_write_name <>= module subroutine evt_shower_write_name (evt, unit) class(evt_shower_t), intent(in) :: evt integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(1x,A)") "Event transform: shower" end subroutine evt_shower_write_name @ %def evt_shower_write_name @ Output. <>= procedure :: write => evt_shower_write <>= module subroutine evt_shower_write & (evt, unit, verbose, more_verbose, testflag) class(evt_shower_t), intent(in) :: evt integer, intent(in), optional :: unit logical, intent(in), optional :: verbose, more_verbose, testflag end subroutine evt_shower_write <>= module subroutine evt_shower_write & (evt, unit, verbose, more_verbose, testflag) class(evt_shower_t), intent(in) :: evt integer, intent(in), optional :: unit logical, intent(in), optional :: verbose, more_verbose, testflag integer :: u u = given_output_unit (unit) call write_separator (u, 2) call evt%write_name (u) call write_separator (u) call evt%base_write (u, testflag = testflag, show_set = .false.) if (evt%particle_set_exists) call evt%particle_set%write & (u, summary = .true., compressed = .true., testflag = testflag) call write_separator (u) call evt%shower%settings%write (u) end subroutine evt_shower_write @ %def evt_shower_write <>= procedure :: connect => evt_shower_connect <>= module subroutine evt_shower_connect & (evt, process_instance, model, process_stack) class(evt_shower_t), intent(inout), target :: evt type(process_instance_t), intent(in), target :: process_instance class(model_data_t), intent(in), target :: model type(process_stack_t), intent(in), optional :: process_stack end subroutine evt_shower_connect <>= module subroutine evt_shower_connect & (evt, process_instance, model, process_stack) class(evt_shower_t), intent(inout), target :: evt type(process_instance_t), intent(in), target :: process_instance class(model_data_t), intent(in), target :: model type(process_stack_t), intent(in), optional :: process_stack call evt%base_connect (process_instance, model, process_stack) call evt%make_rng (evt%process) if (allocated (evt%matching)) then call evt%matching%connect (process_instance, model, evt%shower) end if end subroutine evt_shower_connect @ %def evt_shower_connect @ Initialize the event transformation. This will be executed once during dispatching. The [[model_hadrons]] is supposed to be the SM variant that contains all hadrons that may be generated in the shower. <>= procedure :: init => evt_shower_init <>= module subroutine evt_shower_init (evt, model_hadrons, os_data) class(evt_shower_t), intent(out) :: evt type(model_t), intent(in), target :: model_hadrons type(os_data_t), intent(in) :: os_data end subroutine evt_shower_init <>= module subroutine evt_shower_init (evt, model_hadrons, os_data) class(evt_shower_t), intent(out) :: evt type(model_t), intent(in), target :: model_hadrons type(os_data_t), intent(in) :: os_data evt%os_data = os_data evt%model_hadrons => model_hadrons evt%is_first_event = .true. end subroutine evt_shower_init @ %def evt_shower_init @ Create RNG instances, spawned by the process object. <>= procedure :: make_rng => evt_shower_make_rng <>= module subroutine evt_shower_make_rng (evt, process) class(evt_shower_t), intent(inout) :: evt type(process_t), intent(inout) :: process end subroutine evt_shower_make_rng <>= module subroutine evt_shower_make_rng (evt, process) class(evt_shower_t), intent(inout) :: evt type(process_t), intent(inout) :: process class(rng_t), allocatable :: rng call process%make_rng (rng) call evt%shower%import_rng (rng) if (allocated (evt%matching)) then call process%make_rng (rng) call evt%matching%import_rng (rng) end if end subroutine evt_shower_make_rng @ %def evt_shower_make_rng @ Things we want to do for a new event before the whole event transformation chain is evaluated. <>= procedure :: prepare_new_event => evt_shower_prepare_new_event <>= module subroutine evt_shower_prepare_new_event (evt, i_mci, i_term) class(evt_shower_t), intent(inout) :: evt integer, intent(in) :: i_mci, i_term end subroutine evt_shower_prepare_new_event <>= module subroutine evt_shower_prepare_new_event (evt, i_mci, i_term) class(evt_shower_t), intent(inout) :: evt integer, intent(in) :: i_mci, i_term real(default) :: fac_scale, alpha_s fac_scale = evt%process_instance%get_fac_scale (i_term) alpha_s = evt%process_instance%get_alpha_s (i_term) call evt%reset () call evt%shower%prepare_new_event (fac_scale, alpha_s) end subroutine evt_shower_prepare_new_event @ %def evt_shower_prepare_new_event @ <>= procedure :: first_event => evt_shower_first_event <>= module subroutine evt_shower_first_event (evt) class(evt_shower_t), intent(inout) :: evt end subroutine evt_shower_first_event <>= module subroutine evt_shower_first_event (evt) class(evt_shower_t), intent(inout) :: evt double precision :: pdftest if (debug_on) call msg_debug (D_TRANSFORMS, "evt_shower_first_event") associate (settings => evt%shower%settings) settings%hadron_collision = .false. !!! !!! !!! Workaround for PGF90 v16.1 !!! if (all (evt%particle_set%prt(1:2)%flv%get_pdg_abs () <= 39)) then if (evt%particle_set%prt(1)%flv%get_pdg_abs () <= 39 .and. & evt%particle_set%prt(2)%flv%get_pdg_abs () <= 39) then settings%hadron_collision = .false. !!! else if (all (evt%particle_set%prt(1:2)%flv%get_pdg_abs () >= 100)) then else if (evt%particle_set%prt(1)%flv%get_pdg_abs () >= 100 .and. & evt%particle_set%prt(2)%flv%get_pdg_abs () >= 100) then settings%hadron_collision = .true. else call msg_fatal ("evt_shower didn't recognize beams setup") end if if (debug_on) call msg_debug (D_TRANSFORMS, "hadron_collision", settings%hadron_collision) if (allocated (evt%matching)) then evt%matching%is_hadron_collision = settings%hadron_collision call evt%matching%first_event () end if if (.not. settings%hadron_collision .and. settings%isr_active) then call msg_fatal ("?ps_isr_active is only intended for hadron-collisions") end if if (evt%pdf_data%type == STRF_LHAPDF5) then if (settings%isr_active .and. settings%hadron_collision) then call GetQ2max (0, pdftest) if (pdftest < epsilon (pdftest)) then call msg_bug ("ISR QCD shower enabled, but LHAPDF not " // & "initialized," // LF // " aborting simulation") return end if end if else if (evt%pdf_data%type == STRF_PDF_BUILTIN .and. & settings%method == PS_PYTHIA6) then call msg_fatal ("Builtin PDFs cannot be used for PYTHIA showers," & // LF // " aborting simulation") return end if end associate evt%is_first_event = .false. end subroutine evt_shower_first_event @ %def evt_shower_first_event @ Here we take the particle set from the previous event transform (assuming that there is always one) and apply the shower algorithm. The result is stored in the event transform of the current object. We always return a probability of unity as we don't have the analytic weight of the combination of shower, MLM matching and hadronization. A subdivision into multiple event transformations is under construction. Invalid or vetoed events have to be discarded by the caller which is why we mark the particle set as invalid. This procedure directly takes the (MLM) matching into account. <>= procedure :: generate_weighted => evt_shower_generate_weighted <>= module subroutine evt_shower_generate_weighted (evt, probability) class(evt_shower_t), intent(inout) :: evt real(default), intent(inout) :: probability end subroutine evt_shower_generate_weighted <>= module subroutine evt_shower_generate_weighted (evt, probability) class(evt_shower_t), intent(inout) :: evt real(default), intent(inout) :: probability logical :: valid, vetoed, is_powheg_matching if (debug_on) call msg_debug (D_TRANSFORMS, "evt_shower_generate_weighted") if (signal_is_pending ()) return evt%particle_set = evt%previous%particle_set valid = .true.; vetoed = .false.; is_powheg_matching = .false. if (evt%is_first_event) call evt%first_event () call evt%shower%import_particle_set (evt%particle_set) if (allocated (evt%matching)) then call evt%matching%before_shower (evt%particle_set, vetoed) if (msg_level(D_TRANSFORMS) >= DEBUG) then if (debug_on) call msg_debug & (D_TRANSFORMS, "Matching before generate emissions") call evt%matching%write () end if end if if (allocated (evt%matching)) then select type (matching => evt%matching) type is (powheg_matching_t) is_powheg_matching = .true. end select end if if (.not. vetoed) then if (.not. POWHEG_TESTING .or. .not. is_powheg_matching) then if (evt%shower%settings%method == PS_PYTHIA6 .or. & evt%shower%settings%hadronization_active) then call assure_heprup (evt%particle_set) end if call evt%shower%generate_emissions (valid) end if end if probability = 1 evt%particle_set_exists = valid .and. .not. vetoed end subroutine evt_shower_generate_weighted @ %def evt_shower_generate_weighted @ Here, we fill the particle set with the partons from the shower. The factorization parameters are irrelevant. We make a sanity check that the initial energy lands either in the outgoing particles or add to the beam remnant. <>= procedure :: make_particle_set => evt_shower_make_particle_set <>= module subroutine evt_shower_make_particle_set & (evt, factorization_mode, keep_correlations, r) class(evt_shower_t), intent(inout) :: evt integer, intent(in) :: factorization_mode logical, intent(in) :: keep_correlations real(default), dimension(:), intent(in), optional :: r end subroutine evt_shower_make_particle_set <>= module subroutine evt_shower_make_particle_set & (evt, factorization_mode, keep_correlations, r) class(evt_shower_t), intent(inout) :: evt integer, intent(in) :: factorization_mode logical, intent(in) :: keep_correlations real(default), dimension(:), intent(in), optional :: r type(vector4_t) :: sum_vec_in, sum_vec_out, sum_vec_beamrem, & sum_vec_beamrem_before logical :: vetoed, sane if (evt%particle_set_exists) then vetoed = .false. sum_vec_beamrem_before = sum (evt%particle_set%prt%p, & mask=evt%particle_set%prt%get_status () == PRT_BEAM_REMNANT) call evt%shower%make_particle_set (evt%particle_set, & evt%model, evt%model_hadrons) if (allocated (evt%matching)) then call evt%matching%after_shower (evt%particle_set, vetoed) end if if (debug_active (D_TRANSFORMS)) then call msg_debug (D_TRANSFORMS, & "Shower: obtained particle set after shower + matching") call evt%particle_set%write (summary = .true., compressed = .true.) end if sum_vec_in = sum (evt%particle_set%prt%p, & mask=evt%particle_set%prt%get_status () == PRT_INCOMING) sum_vec_out = sum (evt%particle_set%prt%p, & mask=evt%particle_set%prt%get_status () == PRT_OUTGOING) sum_vec_beamrem = sum (evt%particle_set%prt%p, & mask=evt%particle_set%prt%get_status () == PRT_BEAM_REMNANT) sum_vec_beamrem = sum_vec_beamrem - sum_vec_beamrem_before sane = abs(sum_vec_out%p(0) - sum_vec_in%p(0)) < & sum_vec_in%p(0) / 10 .or. & abs((sum_vec_out%p(0) + sum_vec_beamrem%p(0)) - sum_vec_in%p(0)) < & sum_vec_in%p(0) / 10 sane = .true. evt%particle_set_exists = .not. vetoed .and. sane end if end subroutine evt_shower_make_particle_set @ %def event_shower_make_particle_set @ <>= procedure :: contains_powheg_matching => evt_shower_contains_powheg_matching <>= module function evt_shower_contains_powheg_matching (evt) result (val) logical :: val class(evt_shower_t), intent(in) :: evt end function evt_shower_contains_powheg_matching <>= module function evt_shower_contains_powheg_matching (evt) result (val) logical :: val class(evt_shower_t), intent(in) :: evt val = .false. if (allocated (evt%matching)) & val = evt%matching%get_method () == "POWHEG" end function evt_shower_contains_powheg_matching @ %def evt_shower_contains_powheg_matching @ <>= procedure :: disable_powheg_matching => evt_shower_disable_powheg_matching <>= module subroutine evt_shower_disable_powheg_matching (evt) class(evt_shower_t), intent(inout) :: evt end subroutine evt_shower_disable_powheg_matching <>= module subroutine evt_shower_disable_powheg_matching (evt) class(evt_shower_t), intent(inout) :: evt select type (matching => evt%matching) type is (powheg_matching_t) matching%active = .false. class default call msg_fatal ("Trying to disable powheg but " // & "no powheg matching is allocated!") end select end subroutine evt_shower_disable_powheg_matching @ %def evt_shower_disable_powheg_matching @ <>= procedure :: enable_powheg_matching => evt_shower_enable_powheg_matching <>= module subroutine evt_shower_enable_powheg_matching (evt) class(evt_shower_t), intent(inout) :: evt end subroutine evt_shower_enable_powheg_matching <>= module subroutine evt_shower_enable_powheg_matching (evt) class(evt_shower_t), intent(inout) :: evt select type (matching => evt%matching) type is (powheg_matching_t) matching%active = .true. class default call msg_fatal & ("Trying to enable powheg but no powheg matching is allocated!") end select end subroutine evt_shower_enable_powheg_matching @ %def evt_shower_enable_powheg_matching @ <>= procedure :: final => evt_shower_final <>= module subroutine evt_shower_final (evt) class(evt_shower_t), intent(inout) :: evt end subroutine evt_shower_final <>= module subroutine evt_shower_final (evt) class(evt_shower_t), intent(inout) :: evt call evt%base_final () if (allocated (evt%matching)) call evt%matching%final () end subroutine evt_shower_final @ %def evt_shower_final @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[shower_ut.f90]]>>= <> module shower_ut use unit_tests use shower_uti <> <> contains <> end module shower_ut @ %def shower_ut @ <<[[shower_uti.f90]]>>= <> module shower_uti <> <> use format_utils, only: write_separator use os_interface use sm_qcd use physics_defs, only: BORN use model_data use models use state_matrices, only: FM_IGNORE_HELICITY use process_libraries use rng_base use rng_tao use dispatch_rng, only: dispatch_rng_factory_fallback use mci_base use mci_midpoint use phs_base use phs_single use prc_core_def, only: prc_core_def_t use prc_core use prc_omega use variables use event_transforms use tauola_interface !NODEP! use process, only: process_t use instances, only: process_instance_t use pdf use shower_base use shower_core use dispatch_rng_ut, only: dispatch_rng_factory_tao use shower <> <> contains <> end module shower_uti @ %def shower_uti @ API: driver for the unit tests below. <>= public :: shower_test <>= subroutine shower_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine shower_test @ %def shower_test @ \subsubsection{Testbed} This sequence sets up a two-jet process, ready for generating events. <>= <> @ <>= subroutine setup_testbed & (prefix, os_data, lib, model_list, process, process_instance) type(string_t), intent(in) :: prefix type(os_data_t), intent(out) :: os_data type(process_library_t), intent(out), target :: lib type(model_list_t), intent(out) :: model_list type(model_t), pointer :: model type(model_t), pointer :: model_tmp type(process_t), target, intent(out) :: process type(process_instance_t), target, intent(out) :: process_instance type(var_list_t), pointer :: model_vars type(string_t) :: model_name, libname, procname type(process_def_entry_t), pointer :: entry type(string_t), dimension(:), allocatable :: prt_in, prt_out class(prc_core_t), allocatable :: core_template class(phs_config_t), allocatable :: phs_config_template real(default) :: sqrts model_name = "SM" libname = prefix // "_lib" procname = prefix // "p" call os_data%init () dispatch_rng_factory_fallback => dispatch_rng_factory_tao allocate (model_tmp) call model_list%read_model (model_name, model_name // ".mdl", & os_data, model_tmp) model_vars => model_tmp%get_var_list_ptr () call model_vars%set_real (var_str ("me"), 0._default, & is_known = .true.) model => model_tmp call lib%init (libname) allocate (prt_in (2), source = [var_str ("e-"), var_str ("e+")]) allocate (prt_out (2), source = [var_str ("d"), var_str ("dbar")]) allocate (entry) call entry%init (procname, model, n_in = 2, n_components = 1) call omega_make_process_component (entry, 1, & model_name, prt_in, prt_out, & report_progress=.true.) call lib%append (entry) call lib%configure (os_data) call lib%write_makefile (os_data, force = .true., verbose = .false.) call lib%clean (os_data, distclean = .false.) call lib%write_driver (force = .true.) call lib%load (os_data) call process%init (procname, lib, os_data, model) allocate (prc_omega_t :: core_template) allocate (phs_single_config_t :: phs_config_template) call process%setup_cores (dispatch_core_omega_test) call process%init_components (phs_config_template) sqrts = 1000 call process%setup_beams_sqrts (sqrts, i_core = 1) call process%configure_phs () call process%setup_mci (dispatch_mci_test_midpoint) call process%setup_terms () call process_instance%init (process) call process_instance%integrate (1, 1, 1000) call process%final_integration (1) call process_instance%setup_event_data (i_core = 1) call process_instance%init_simulation (1) call process_instance%generate_weighted_event (1) call process_instance%evaluate_event_data () end subroutine setup_testbed @ %def setup_testbed @ A minimal dispatcher version that allocates the core object for testing. <>= subroutine dispatch_core_omega_test (core, core_def, model, & helicity_selection, qcd, use_color_factors, has_beam_pol) class(prc_core_t), allocatable, intent(inout) :: core class(prc_core_def_t), intent(in) :: core_def class(model_data_t), intent(in), target, optional :: model type(helicity_selection_t), intent(in), optional :: helicity_selection type(qcd_t), intent(in), optional :: qcd logical, intent(in), optional :: use_color_factors logical, intent(in), optional :: has_beam_pol allocate (prc_omega_t :: core) select type (core) type is (prc_omega_t) call core%set_parameters (model) end select end subroutine dispatch_core_omega_test @ %def dispatch_core_omega_test @ MCI record prepared for midpoint integrator. <>= subroutine dispatch_mci_test_midpoint (mci, var_list, process_id, is_nlo) use variables, only: var_list_t 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 allocate (mci_midpoint_t :: mci) end subroutine dispatch_mci_test_midpoint @ %def dispatch_mci_test_midpoint @ \subsubsection{Trivial Test} We generate a two-jet event and shower it using default settings, i.e. in disabled mode. <>= call test (shower_1, "shower_1", & "disabled shower", & u, results) <>= public :: shower_1 <>= subroutine shower_1 (u) integer, intent(in) :: u type(os_data_t) :: os_data type(process_library_t), target :: lib type(model_list_t) :: model_list class(model_data_t), pointer :: model type(model_t), pointer :: model_hadrons type(process_t), target :: process type(process_instance_t), target :: process_instance type(pdf_data_t) :: pdf_data integer :: factorization_mode logical :: keep_correlations class(evt_t), allocatable, target :: evt_trivial class(evt_t), allocatable, target :: evt_shower type(shower_settings_t) :: settings type(taudec_settings_t) :: taudec_settings write (u, "(A)") "* Test output: shower_1" write (u, "(A)") "* Purpose: Two-jet event with disabled shower" write (u, "(A)") write (u, "(A)") "* Initialize environment" write (u, "(A)") call syntax_model_file_init () call os_data%init () call model_list%read_model & (var_str ("SM_hadrons"), var_str ("SM_hadrons.mdl"), & os_data, model_hadrons) call setup_testbed (var_str ("shower_1"), & os_data, lib, model_list, process, process_instance) write (u, "(A)") "* Set up trivial transform" write (u, "(A)") allocate (evt_trivial_t :: evt_trivial) model => process%get_model_ptr () call evt_trivial%connect (process_instance, model) call evt_trivial%prepare_new_event (1, 1) call evt_trivial%generate_unweighted () factorization_mode = FM_IGNORE_HELICITY keep_correlations = .false. call evt_trivial%make_particle_set (factorization_mode, keep_correlations) select type (evt_trivial) type is (evt_trivial_t) call evt_trivial%write (u) call write_separator (u, 2) end select write (u, "(A)") write (u, "(A)") "* Set up shower event transform" write (u, "(A)") allocate (evt_shower_t :: evt_shower) select type (evt_shower) type is (evt_shower_t) call evt_shower%init (model_hadrons, os_data) allocate (shower_t :: evt_shower%shower) call evt_shower%shower%init (settings, taudec_settings, pdf_data, os_data) call evt_shower%connect (process_instance, model) end select evt_trivial%next => evt_shower evt_shower%previous => evt_trivial call evt_shower%prepare_new_event (1, 1) call evt_shower%generate_unweighted () call evt_shower%make_particle_set (factorization_mode, keep_correlations) select type (evt_shower) type is (evt_shower_t) call evt_shower%write (u) call write_separator (u, 2) end select write (u, "(A)") write (u, "(A)") "* Cleanup" call evt_shower%final () call evt_trivial%final () call process_instance%final () call process%final () call lib%final () call model_hadrons%final () deallocate (model_hadrons) call syntax_model_file_final () write (u, "(A)") write (u, "(A)") "* Test output end: shower_1" end subroutine shower_1 @ %def shower_1 @ \subsubsection{FSR Shower} We generate a two-jet event and shower it with the Whizard FSR shower. <>= call test (shower_2, "shower_2", & "final-state shower", & u, results) <>= public :: shower_2 <>= subroutine shower_2 (u) integer, intent(in) :: u type(os_data_t) :: os_data type(process_library_t), target :: lib type(model_list_t) :: model_list type(model_t), pointer :: model_hadrons class(model_data_t), pointer :: model type(process_t), target :: process type(process_instance_t), target :: process_instance integer :: factorization_mode logical :: keep_correlations type(pdf_data_t) :: pdf_data class(evt_t), allocatable, target :: evt_trivial class(evt_t), allocatable, target :: evt_shower type(shower_settings_t) :: settings type(taudec_settings_t) :: taudec_settings write (u, "(A)") "* Test output: shower_2" write (u, "(A)") "* Purpose: Two-jet event with FSR shower" write (u, "(A)") write (u, "(A)") "* Initialize environment" write (u, "(A)") call syntax_model_file_init () call os_data%init () call model_list%read_model & (var_str ("SM_hadrons"), var_str ("SM_hadrons.mdl"), & os_data, model_hadrons) call setup_testbed (var_str ("shower_2"), & os_data, lib, model_list, process, process_instance) model => process%get_model_ptr () write (u, "(A)") "* Set up trivial transform" write (u, "(A)") allocate (evt_trivial_t :: evt_trivial) call evt_trivial%connect (process_instance, model) call evt_trivial%prepare_new_event (1, 1) call evt_trivial%generate_unweighted () factorization_mode = FM_IGNORE_HELICITY keep_correlations = .false. call evt_trivial%make_particle_set (factorization_mode, keep_correlations) select type (evt_trivial) type is (evt_trivial_t) call evt_trivial%write (u) call write_separator (u, 2) end select write (u, "(A)") write (u, "(A)") "* Set up shower event transform" write (u, "(A)") settings%fsr_active = .true. allocate (evt_shower_t :: evt_shower) select type (evt_shower) type is (evt_shower_t) call evt_shower%init (model_hadrons, os_data) allocate (shower_t :: evt_shower%shower) call evt_shower%shower%init (settings, taudec_settings, pdf_data, os_data) call evt_shower%connect (process_instance, model) end select evt_trivial%next => evt_shower evt_shower%previous => evt_trivial call evt_shower%prepare_new_event (1, 1) call evt_shower%generate_unweighted () call evt_shower%make_particle_set (factorization_mode, keep_correlations) select type (evt_shower) type is (evt_shower_t) call evt_shower%write (u, testflag = .true.) call write_separator (u, 2) end select write (u, "(A)") write (u, "(A)") "* Cleanup" call evt_shower%final () call evt_trivial%final () call process_instance%final () call process%final () call lib%final () call model_hadrons%final () deallocate (model_hadrons) call syntax_model_file_final () write (u, "(A)") write (u, "(A)") "* Test output end: shower_2" end subroutine shower_2 @ %def shower_2 @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Fixed Order NLO Events} This section deals with the generation of weighted event samples which take into account next-to-leading order corrections. An approach generating unweighted events is not possible here, because negative weights might occur due to subtraction. Note that the events produced this way are not physical in the sense that they will not keep NLO-accuracy when interfaced to a parton shower. They are rather useful for theoretical consistency checks and a fast estimate of NLO effects.\\ We generate NLO events in the following way: First, the integration is carried out using the complete divergence-subtracted NLO matrix element. In the subsequent simulation, $N$-particle kinematics are generated using $\mathcal{B}+\mathcal{V}+\mathcal{C}$ as weight. After that, the program loops over all singular regions and for each of them generates an event with $N+1$-particle kinematics. The weight for those events corresponds to the real matrix element $\mathcal{R}^\alpha$ evaluated at the $\alpha$-region's emitter's phase space point, multiplied with $S_\alpha$. This procedure is implemented using the [[evt_nlo]] transform. <<[[evt_nlo.f90]]>>= <> module evt_nlo <> <> use constants use phs_points, only: phs_point_t use phs_points, only: assignment(=), operator(*), size use sm_qcd use model_data use particles use instances, only: process_instance_t use process_stacks use event_transforms use quantum_numbers, only: quantum_numbers_t use phs_fks, only: phs_fks_t, phs_fks_generator_t use phs_fks, only: phs_identifier_t, phs_point_set_t use resonances, only: resonance_contributors_t use fks_regions, only: region_data_t <> <> <> <> interface <> end interface end module evt_nlo @ %def evt_nlo @ <<[[evt_nlo_sub.f90]]>>= <> submodule (evt_nlo) evt_nlo_s <> use io_units, only: given_output_unit use diagnostics use format_utils, only: write_separator use numeric_utils, only: nearly_equal use physics_defs, only: BORN, NLO_REAL use lorentz use interactions, only: interaction_t use pcm, only: pcm_nlo_t, pcm_nlo_workspace_t use prc_core, only: prc_core_t use prc_external, only: prc_external_t implicit none contains <> end submodule evt_nlo_s @ %def evt_nlo_s @ <>= type :: nlo_event_deps_t logical :: lab_is_cm = .true. type(phs_point_set_t) :: p_born_cms type(phs_point_set_t) :: p_born_lab type(phs_point_set_t) :: p_real_cms type(phs_point_set_t) :: p_real_lab type(resonance_contributors_t), dimension(:), allocatable :: contributors type(phs_identifier_t), dimension(:), allocatable :: phs_identifiers integer, dimension(:), allocatable :: alr_to_i_con integer :: n_phs = 0 end type nlo_event_deps_t @ %def nlo_event_deps_t @ This event transformation is for the generation of fixed-order NLO events. It takes an event with Born kinematics and creates $N_\alpha + 1$ modified weighted events. The first one has Born kinematics and its weight is the sum of Born, virtual, subtraction and, if present, also DGLAP matrix elements. The other $N_\alpha$ events have a weight which is equal to the real matrix element, evaluated with the phase space corresponding to the emitter of the $\alpha$-region. As the NLO event transforms have different kinematics, they also differ in their [[particle_set]]s. The NLO [[event_t]] object carries a single pointer to a [[particle_set]]. To avoid interference between the different NLO [[particle_set]]s, we save the [[particle_set]] of the current $\alpha$-region in the array [[particle_set_nlo]]. Otherwise it would be unretrievable if the usual particle set of the event object was used. <>= integer, parameter, public :: EVT_NLO_UNDEFINED = 0 integer, parameter, public :: EVT_NLO_SEPARATE_BORNLIKE = 1 integer, parameter, public :: EVT_NLO_SEPARATE_REAL = 2 integer, parameter, public :: EVT_NLO_COMBINED = 3 <>= public :: evt_nlo_t <>= type, extends (evt_t) :: evt_nlo_t type(phs_fks_generator_t) :: phs_fks_generator real(default) :: sqme_rad = zero integer :: i_evaluation = 0 type(particle_set_t), dimension(:), allocatable :: particle_set_nlo type(qcd_t) :: qcd type(nlo_event_deps_t) :: event_deps integer :: mode = EVT_NLO_UNDEFINED integer, dimension(:), allocatable :: & i_evaluation_to_i_phs, i_evaluation_to_emitter, & i_evaluation_to_i_term logical :: keep_failed_events = .false. integer :: selected_i_flv = 0 contains <> end type evt_nlo_t @ %def evt_nlo_t @ <>= procedure :: write_name => evt_nlo_write_name <>= module subroutine evt_nlo_write_name (evt, unit) class(evt_nlo_t), intent(in) :: evt integer, intent(in), optional :: unit end subroutine evt_nlo_write_name <>= module subroutine evt_nlo_write_name (evt, unit) class(evt_nlo_t), intent(in) :: evt integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(1x,A)") "Event transform: NLO" end subroutine evt_nlo_write_name @ %def evt_nlo_write_name @ <>= procedure :: write => evt_nlo_write <>= module subroutine evt_nlo_write (evt, unit, verbose, more_verbose, testflag) class(evt_nlo_t), intent(in) :: evt integer, intent(in), optional :: unit logical, intent(in), optional :: verbose, more_verbose, testflag end subroutine evt_nlo_write <>= module subroutine evt_nlo_write (evt, unit, verbose, more_verbose, testflag) class(evt_nlo_t), intent(in) :: evt integer, intent(in), optional :: unit logical, intent(in), optional :: verbose, more_verbose, testflag integer :: u, i u = given_output_unit (unit) call write_separator (u, 2) call evt%write_name (u) call write_separator (u) call evt%base_write (u, testflag = testflag, show_set = .true.) write (u,'(A,ES16.9)') "sqme_rad = ", evt%sqme_rad write (u, "(3x,A,I0)") "i_evaluation = ", evt%i_evaluation call write_separator (u) write (u, "(1x,A)") "Radiated particle sets:" do i = 1, size (evt%particle_set_nlo) call evt%particle_set_nlo(i)%write (u, testflag = testflag) call write_separator (u) end do end subroutine evt_nlo_write @ %def evt_nlo_write @ Connects the event transform to the process. Here also the phase space is set up by making [[real_kinematics]] point to the corresponding object in the [[pcm_instance]]. <>= procedure :: connect => evt_nlo_connect <>= module subroutine evt_nlo_connect & (evt, process_instance, model, process_stack) class(evt_nlo_t), intent(inout), target :: evt type(process_instance_t), intent(in), target :: process_instance class(model_data_t), intent(in), target :: model type(process_stack_t), intent(in), optional :: process_stack end subroutine evt_nlo_connect <>= module subroutine evt_nlo_connect & (evt, process_instance, model, process_stack) class(evt_nlo_t), intent(inout), target :: evt type(process_instance_t), intent(in), target :: process_instance class(model_data_t), intent(in), target :: model type(process_stack_t), intent(in), optional :: process_stack if (debug_on) call msg_debug (D_TRANSFORMS, "evt_nlo_connect") call evt%base_connect (process_instance, model, process_stack) select type (pcm_work => process_instance%pcm_work) class is (pcm_nlo_workspace_t) select type (pcm => process_instance%pcm) type is (pcm_nlo_t) call pcm%setup_phs_generator (pcm_work, evt%phs_fks_generator, & process_instance%get_sqrts ()) call evt%set_i_evaluation_mappings (pcm%region_data, & pcm_work%real_kinematics%alr_to_i_phs) end select end select call evt%set_mode (process_instance) call evt%setup_general_event_kinematics (process_instance) if (evt%mode > EVT_NLO_SEPARATE_BORNLIKE) & call evt%setup_real_event_kinematics (process_instance) if (debug_on) call msg_debug2 (D_TRANSFORMS, "evt_nlo_connect: success") end subroutine evt_nlo_connect @ %def evt_nlo_connect @ <>= procedure :: set_i_evaluation_mappings => evt_nlo_set_i_evaluation_mappings <>= module subroutine evt_nlo_set_i_evaluation_mappings & (evt, reg_data, alr_to_i_phs) class(evt_nlo_t), intent(inout) :: evt type(region_data_t), intent(in) :: reg_data integer, intent(in), dimension(:) :: alr_to_i_phs end subroutine evt_nlo_set_i_evaluation_mappings <>= type :: registered_triple_t integer, dimension(2) :: phs_em type(registered_triple_t), pointer :: next => null () end type registered_triple_t <>= module subroutine evt_nlo_set_i_evaluation_mappings & (evt, reg_data, alr_to_i_phs) class(evt_nlo_t), intent(inout) :: evt type(region_data_t), intent(in) :: reg_data integer, intent(in), dimension(:) :: alr_to_i_phs integer :: n_phs, alr integer :: i_evaluation, i_phs, emitter logical :: checked type(registered_triple_t), allocatable, target :: check_list i_evaluation = 1 n_phs = reg_data%n_phs allocate (evt%i_evaluation_to_i_phs (n_phs), source = 0) allocate (evt%i_evaluation_to_emitter (n_phs), source = -1) allocate (evt%i_evaluation_to_i_term (0 : n_phs), source = 0) do alr = 1, reg_data%n_regions i_phs = alr_to_i_phs (alr) emitter = reg_data%regions(alr)%emitter call search_check_list (checked) if (.not. checked) then evt%i_evaluation_to_i_phs (i_evaluation) = i_phs evt%i_evaluation_to_emitter (i_evaluation) = emitter i_evaluation = i_evaluation + 1 end if end do call fill_i_evaluation_to_i_term () if (.not. (all (evt%i_evaluation_to_i_phs > 0) & .and. all (evt%i_evaluation_to_emitter > -1))) then call msg_fatal ("evt_nlo: Inconsistent mappings!") else if (debug2_active (D_TRANSFORMS)) then print *, 'evt_nlo Mappings, i_evaluation -> ' print *, 'i_phs: ', evt%i_evaluation_to_i_phs print *, 'emitter: ', evt%i_evaluation_to_emitter end if end if contains subroutine fill_i_evaluation_to_i_term () integer :: i_term, i_evaluation, term_emitter !!! First find subtraction component i_evaluation = 1 do i_term = 1, evt%process%get_n_terms () if (evt%process_instance%term(i_term)%nlo_type /= NLO_REAL) cycle term_emitter = evt%process_instance%kin(i_term)%emitter if (term_emitter < 0) then evt%i_evaluation_to_i_term (0) = i_term else if (evt%i_evaluation_to_emitter(i_evaluation) == term_emitter) then evt%i_evaluation_to_i_term (i_evaluation) = i_term i_evaluation = i_evaluation + 1 end if end do end subroutine fill_i_evaluation_to_i_term subroutine search_check_list (found) logical, intent(out) :: found type(registered_triple_t), pointer :: current_triple => null () if (allocated (check_list)) then current_triple => check_list do if (all (current_triple%phs_em == [i_phs, emitter])) then found = .true. exit end if if (.not. associated (current_triple%next)) then allocate (current_triple%next) current_triple%next%phs_em = [i_phs, emitter] found = .false. exit else current_triple => current_triple%next end if end do else allocate (check_list) check_list%phs_em = [i_phs, emitter] found = .false. end if end subroutine search_check_list end subroutine evt_nlo_set_i_evaluation_mappings @ %def evt_nlo_set_i_evaluation_mappings @ <>= procedure :: get_i_phs => evt_nlo_get_i_phs <>= module function evt_nlo_get_i_phs (evt) result (i_phs) integer :: i_phs class(evt_nlo_t), intent(in) :: evt end function evt_nlo_get_i_phs <>= module function evt_nlo_get_i_phs (evt) result (i_phs) integer :: i_phs class(evt_nlo_t), intent(in) :: evt i_phs = evt%i_evaluation_to_i_phs (evt%i_evaluation) end function evt_nlo_get_i_phs @ %def evt_nlo_get_i_phs @ <>= procedure :: get_emitter => evt_nlo_get_emitter <>= module function evt_nlo_get_emitter (evt) result (emitter) integer :: emitter class(evt_nlo_t), intent(in) :: evt end function evt_nlo_get_emitter <>= module function evt_nlo_get_emitter (evt) result (emitter) integer :: emitter class(evt_nlo_t), intent(in) :: evt emitter = evt%i_evaluation_to_emitter (evt%i_evaluation) end function evt_nlo_get_emitter @ %def evt_nlo_get_emitter @ <>= procedure :: get_i_term => evt_nlo_get_i_term <>= module function evt_nlo_get_i_term (evt) result (i_term) integer :: i_term class(evt_nlo_t), intent(in) :: evt end function evt_nlo_get_i_term <>= module function evt_nlo_get_i_term (evt) result (i_term) integer :: i_term class(evt_nlo_t), intent(in) :: evt if (evt%mode >= EVT_NLO_SEPARATE_REAL) then i_term = evt%i_evaluation_to_i_term (evt%i_evaluation) else i_term = evt%process_instance%get_first_active_i_term () end if end function evt_nlo_get_i_term @ %def evt_nlo_get_i_term @ The event transform has a variable which counts the number of times it has already been called for one generation point. If this variable, [[i_evaluation]], is zero, this means that [[evt_nlo_generate_weighted]] is called for the first time, so that the generation of an $N$-particle event is required. In all other cases, emission events are generated. During a separate integration of the real component, the first event of each event group will become the counterevent. In this case, we return the sum of all subtraction matrix elements. During a combined integration, the first event will be a combination of all Born-like events. To get the sum of their matrix elements, we subtract the sum of all real emissions from the sum of all matrix elements as the real contribution is the only non-Born contribution. Note that the argument named [[probablity]], the use of the routine [[generate_weighted]] and the procedure we use to generate NLO events via an event transformation is an abuse of the interface which should be refactored. <>= procedure :: generate_weighted => evt_nlo_generate_weighted <>= module subroutine evt_nlo_generate_weighted (evt, probability) class(evt_nlo_t), intent(inout) :: evt real(default), intent(inout) :: probability end subroutine evt_nlo_generate_weighted <>= module subroutine evt_nlo_generate_weighted (evt, probability) class(evt_nlo_t), intent(inout) :: evt real(default), intent(inout) :: probability real(default) :: sqme call print_debug_info () sqme = probability if (evt%mode > EVT_NLO_SEPARATE_BORNLIKE) then if (evt%i_evaluation == 0) then call evt%reset_phs_identifiers () call evt%evaluate_real_kinematics () if (evt%mode == EVT_NLO_SEPARATE_REAL) then sqme = evt%compute_subtraction_sqmes () else sqme = sqme - evt%compute_all_sqme_rad () end if else call evt%compute_real () sqme = evt%sqme_rad end if end if probability = sqme if (debug_on) call msg_debug & (D_TRANSFORMS, "probability (after)", probability) contains function status_code_to_string (mode) result (smode) type(string_t) :: smode integer, intent(in) :: mode select case (mode) case (EVT_NLO_UNDEFINED) smode = var_str ("Undefined") case (EVT_NLO_SEPARATE_BORNLIKE) smode = var_str ("Born-like") case (EVT_NLO_SEPARATE_REAL) smode = var_str ("Real") case (EVT_NLO_COMBINED) smode = var_str ("Combined") end select end function status_code_to_string subroutine print_debug_info () if (debug_on) call msg_debug (D_TRANSFORMS, "evt_nlo_generate_weighted") if (debug_on) call msg_debug & (D_TRANSFORMS, char ("mode: " // status_code_to_string (evt%mode))) if (debug_on) call msg_debug & (D_TRANSFORMS, "probability (before)", probability) if (debug_on) call msg_debug & (D_TRANSFORMS, "evt%i_evaluation", evt%i_evaluation) if (debug2_active (D_TRANSFORMS)) then if (evt%mode > EVT_NLO_SEPARATE_BORNLIKE) then if (evt%i_evaluation == 0) then print *, 'Evaluate subtraction component' else print *, 'Evaluate radiation component' end if end if end if end subroutine print_debug_info end subroutine evt_nlo_generate_weighted @ %def evt_nlo_generate_weighted @ <>= procedure :: reset_phs_identifiers => evt_nlo_reset_phs_identifiers <>= module subroutine evt_nlo_reset_phs_identifiers (evt) class(evt_nlo_t), intent(inout) :: evt end subroutine evt_nlo_reset_phs_identifiers <>= module subroutine evt_nlo_reset_phs_identifiers (evt) class(evt_nlo_t), intent(inout) :: evt evt%event_deps%phs_identifiers%evaluated = .false. end subroutine evt_nlo_reset_phs_identifiers @ %def evt_nlo_reset_phs_identifiers @ The routine [[make_factorized_particle_set]] will setup the subevent momenta from the [[connected%matrix]]. Its initial state momenta correspond to the Born process without IS splitting and thus need to be updated with the real momenta from the [[int_hard]] to get correct momenta in the events with real radiation. Ideally the [[int_hard]] and the [[connected]] would be setup with correct [[source_link]]s to real momenta so that we would not need to replace momenta of the [[connected]] here. The parameter [[n_in]] from the [[int_matrix]] is still $0$ as it has been shifted to [[n_vir]]. We thus take [[n_in]] from the [[particle_set]]. <>= procedure :: connected_set_real_IS_momenta => & evt_nlo_connected_set_real_IS_momenta <>= module subroutine evt_nlo_connected_set_real_IS_momenta (evt) class(evt_nlo_t), intent(inout) :: evt end subroutine evt_nlo_connected_set_real_IS_momenta <>= module subroutine evt_nlo_connected_set_real_IS_momenta (evt) class(evt_nlo_t), intent(inout) :: evt type(vector4_t) :: p_hard, p_beam, p_remn type(interaction_t), pointer :: int_matrix integer :: i, i_term, n_in, i_in_beam, i_in_hard, i_in_remn i_term = evt%get_i_term () int_matrix => evt%process_instance%get_matrix_int_ptr (i_term) n_in = evt%particle_set%get_n_in () do i = 1, n_in i_in_beam = i i_in_hard = n_in + i i_in_remn = 2 * n_in + i p_hard = evt%process_instance%term(i_term)%int_hard%get_momentum (i) p_beam = int_matrix%get_momentum (i_in_beam) p_remn = p_beam - p_hard call int_matrix%set_momentum (p_hard , i_in_hard) call int_matrix%set_momentum (p_remn , i_in_remn) end do end subroutine evt_nlo_connected_set_real_IS_momenta @ %def evt_nlo_connected_set_real_IS_momenta @ <>= procedure :: make_particle_set => evt_nlo_make_particle_set <>= module subroutine evt_nlo_make_particle_set & (evt, factorization_mode, keep_correlations, r) class(evt_nlo_t), intent(inout) :: evt integer, intent(in) :: factorization_mode logical, intent(in) :: keep_correlations real(default), dimension(:), intent(in), optional :: r end subroutine evt_nlo_make_particle_set <>= module subroutine evt_nlo_make_particle_set & (evt, factorization_mode, keep_correlations, r) class(evt_nlo_t), intent(inout) :: evt integer, intent(in) :: factorization_mode logical, intent(in) :: keep_correlations real(default), dimension(:), intent(in), optional :: r if (evt%mode >= EVT_NLO_SEPARATE_BORNLIKE) then call make_factorized_particle_set (evt, factorization_mode, & keep_correlations, r, evt%get_i_term (), & evt%get_selected_quantum_numbers (evt%selected_i_flv)) else call make_factorized_particle_set (evt, factorization_mode, & keep_correlations, r) end if end subroutine evt_nlo_make_particle_set @ %def evt_nlo_make_particle_set @ <>= procedure :: evaluate_real_kinematics => evt_nlo_evaluate_real_kinematics <>= module subroutine evt_nlo_evaluate_real_kinematics (evt) class(evt_nlo_t), intent(inout) :: evt end subroutine evt_nlo_evaluate_real_kinematics <>= module subroutine evt_nlo_evaluate_real_kinematics (evt) class(evt_nlo_t), intent(inout) :: evt integer :: alr, i_phs, i_con, emitter real(default), dimension(3) :: x_rad logical :: use_contributors integer :: n_regions integer :: i_term type(vector4_t), dimension(:), allocatable :: p_real select type (pcm_work => evt%process_instance%pcm_work) class is (pcm_nlo_workspace_t) x_rad = pcm_work%real_kinematics%x_rad associate (event_deps => evt%event_deps) i_term = evt%get_i_term () event_deps%p_born_lab%phs_point(1) = & evt%process_instance%term(i_term)%p_seed event_deps%p_born_cms%phs_point(1) & = evt%boost_to_cms (event_deps%p_born_lab%phs_point(1)) call evt%phs_fks_generator%set_sqrts_hat & (event_deps%p_born_cms%get_energy (1, 1)) use_contributors = allocated (event_deps%contributors) select type (pcm => evt%process_instance%pcm) type is (pcm_nlo_t) n_regions = pcm%region_data%n_regions end select do alr = 1, n_regions i_phs = pcm_work%real_kinematics%alr_to_i_phs(alr) if (event_deps%phs_identifiers(i_phs)%evaluated) cycle emitter = event_deps%phs_identifiers(i_phs)%emitter associate (generator => evt%phs_fks_generator) if (emitter <= evt%process%get_n_in ()) then call generator%prepare_generation (x_rad, i_phs, emitter, & event_deps%p_born_cms%phs_point(1)%get (), & event_deps%phs_identifiers) ! TODO wk 19-02-28: intent of p_real (also below)? p_real = event_deps%p_real_lab%phs_point(i_phs) call generator%generate_isr (i_phs, & event_deps%p_born_lab%phs_point(1)%get (), & p_real) event_deps%p_real_lab%phs_point(i_phs) = p_real event_deps%p_real_cms%phs_point(i_phs) & = evt%boost_to_cms (event_deps%p_real_lab%phs_point(i_phs)) else if (use_contributors) then i_con = event_deps%alr_to_i_con(alr) call generator%prepare_generation (x_rad, i_phs, emitter, & event_deps%p_born_cms%phs_point(1)%get (), & event_deps%phs_identifiers, event_deps%contributors, i_con) p_real = event_deps%p_real_cms%phs_point(i_phs) call generator%generate_fsr (emitter, i_phs, i_con, & event_deps%p_born_cms%phs_point(1)%get (), & p_real) event_deps%p_real_cms%phs_point(i_phs) = p_real else call generator%prepare_generation (x_rad, i_phs, emitter, & event_deps%p_born_cms%phs_point(1)%get (), & event_deps%phs_identifiers) p_real = event_deps%p_real_cms%phs_point(i_phs) call generator%generate_fsr (emitter, i_phs, & event_deps%p_born_cms%phs_point(1)%get (), & p_real) event_deps%p_real_cms%phs_point(i_phs) = p_real end if event_deps%p_real_lab%phs_point(i_phs) & = evt%boost_to_lab (event_deps%p_real_cms%phs_point(i_phs)) end if end associate call pcm_work%set_momenta & (event_deps%p_born_lab%phs_point(1)%get (), & event_deps%p_real_lab%phs_point(i_phs)%get (), & i_phs) call pcm_work%set_momenta & (event_deps%p_born_cms%phs_point(1)%get (), & event_deps%p_real_cms%phs_point(i_phs)%get (), & i_phs, cms = .true.) event_deps%phs_identifiers(i_phs)%evaluated = .true. end do end associate end select end subroutine evt_nlo_evaluate_real_kinematics @ %def evt_nlo_evaluate_real_kinematics @ This routine calls the evaluation of the singular regions only for the subtraction terms. <>= procedure :: compute_subtraction_sqmes => evt_nlo_compute_subtraction_sqmes <>= module function evt_nlo_compute_subtraction_sqmes (evt) result (sqme) class(evt_nlo_t), intent(inout) :: evt real(default) :: sqme end function evt_nlo_compute_subtraction_sqmes <>= module function evt_nlo_compute_subtraction_sqmes (evt) result (sqme) class(evt_nlo_t), intent(inout) :: evt real(default) :: sqme integer :: i_phs, i_term if (debug_on) call msg_debug & (D_TRANSFORMS, "evt_nlo_compute_subtraction_sqmes") sqme = zero associate (event_deps => evt%event_deps) i_phs = 1; i_term = evt%i_evaluation_to_i_term(0) call evt%process_instance%compute_sqme_rad & (i_term, i_phs, is_subtraction = .true.) sqme = sqme + evt%process_instance%get_sqme (i_term) end associate end function evt_nlo_compute_subtraction_sqmes @ %def evt_nlo_compute_subtraction_sqmes @ This routine calls the evaluation of the singular regions only for emission matrix elements. <>= procedure :: compute_real => evt_nlo_compute_real <>= module subroutine evt_nlo_compute_real (evt) class(evt_nlo_t), intent(inout) :: evt end subroutine evt_nlo_compute_real <>= module subroutine evt_nlo_compute_real (evt) class(evt_nlo_t), intent(inout) :: evt integer :: i_phs, i_term if (debug_on) call msg_debug (D_TRANSFORMS, "evt_nlo_compute_real") i_phs = evt%get_i_phs () i_term = evt%i_evaluation_to_i_term (evt%i_evaluation) associate (event_deps => evt%event_deps) call evt%process_instance%compute_sqme_rad (i_term, i_phs, & is_subtraction = .false.) evt%sqme_rad = evt%process_instance%get_sqme (i_term) end associate end subroutine evt_nlo_compute_real @ %def evt_nlo_compute_real @ This routine calls the evaluation of the singular regions only for all emission matrix elements. This is needed for the combined mode. It returns the sum of all valid real matrix elements. <>= procedure :: compute_all_sqme_rad => evt_nlo_compute_all_sqme_rad <>= module function evt_nlo_compute_all_sqme_rad (evt) result (sqme) class(evt_nlo_t), intent(inout) :: evt real(default) :: sqme end function evt_nlo_compute_all_sqme_rad <>= module function evt_nlo_compute_all_sqme_rad (evt) result (sqme) class(evt_nlo_t), intent(inout) :: evt real(default) :: sqme integer :: i_phs, i_term if (debug_on) call msg_debug (D_TRANSFORMS, "evt_nlo_compute_all_sqme_rad") sqme = zero do i_term = 1, size (evt%process_instance%term) if (evt%is_valid_event (i_term)) then associate (term => evt%process_instance%term(i_term)) if (term%nlo_type == NLO_REAL .and. & .not. term%is_subtraction ()) then i_phs = evt%process_instance%kin(i_term)%i_phs call evt%process_instance%compute_sqme_rad ( & i_term, i_phs, is_subtraction = .false.) sqme = sqme + evt%process_instance%get_sqme (i_term) end if end associate end if end do end function evt_nlo_compute_all_sqme_rad @ %def evt_nlo_compute_all_sqme_rad @ Boosts the given four vector [[p_lab]] to the Born or real CMS depending on the number of given momenta. Unfortunately, all boosts available via [[get_boost_to_cms]] are Born-like, so we need to compute the boost to the real CMS here manually. We cannot rely on [[i_term]] in order to determine whether to apply a Born-like or a real boost as we also need a real boost to compute the weights of the Born-like subevents as implemented in [[evt_nlo_generate_weighted]]. <>= procedure :: boost_to_cms => evt_nlo_boost_to_cms <>= module function evt_nlo_boost_to_cms (evt, p_lab) result (p_cms) type(phs_point_t), intent(in) :: p_lab class(evt_nlo_t), intent(in) :: evt type(phs_point_t) :: p_cms end function evt_nlo_boost_to_cms <>= module function evt_nlo_boost_to_cms (evt, p_lab) result (p_cms) type(phs_point_t), intent(in) :: p_lab class(evt_nlo_t), intent(in) :: evt type(phs_point_t) :: p_cms type(vector4_t) :: p0, p1 type(lorentz_transformation_t) :: lt_lab_to_cms, lt real(default) :: sqrts_hat integer :: i_boost, n_legs_born if (evt%event_deps%lab_is_cm) then lt_lab_to_cms = identity else n_legs_born = size (evt%event_deps%p_born_lab%phs_point(1)) if (size (p_lab) == n_legs_born) then i_boost = evt%get_i_term () lt_lab_to_cms = evt%process_instance%get_boost_to_cms (i_boost) else sqrts_hat = (p_lab%select (1) + p_lab%select (2))**1 p0 = p_lab%select (1) + p_lab%select (2) lt = boost (p0, sqrts_hat) p1 = inverse(lt) * p_lab%select (1) lt_lab_to_cms = inverse (lt * rotation_to_2nd (3, space_part (p1))) end if end if p_cms = lt_lab_to_cms * p_lab end function evt_nlo_boost_to_cms @ %def evt_nlo_boost_to_cms @ Boosts the given four vector [[p_cms]] from the Born CMS to the lab system. It should not be called for ISR as in this case, the Born CMS and the real CMS differ. <>= procedure :: boost_to_lab => evt_nlo_boost_to_lab <>= module function evt_nlo_boost_to_lab (evt, p_cms) result (p_lab) type(phs_point_t) :: p_lab class(evt_nlo_t), intent(in) :: evt type(phs_point_t), intent(in) :: p_cms end function evt_nlo_boost_to_lab <>= module function evt_nlo_boost_to_lab (evt, p_cms) result (p_lab) type(phs_point_t) :: p_lab class(evt_nlo_t), intent(in) :: evt type(phs_point_t), intent(in) :: p_cms type(lorentz_transformation_t) :: lt_cms_to_lab integer :: i_boost if (evt%event_deps%lab_is_cm) then lt_cms_to_lab = identity else i_boost = evt%get_i_term () lt_cms_to_lab = evt%process_instance%get_boost_to_lab (i_boost) end if p_lab = lt_cms_to_lab * p_cms end function evt_nlo_boost_to_lab @ %def evt_nlo_boost_to_lab @ <>= procedure :: setup_general_event_kinematics => & evt_nlo_setup_general_event_kinematics <>= module subroutine evt_nlo_setup_general_event_kinematics & (evt, process_instance) class(evt_nlo_t), intent(inout) :: evt type(process_instance_t), intent(in) :: process_instance end subroutine evt_nlo_setup_general_event_kinematics <>= module subroutine evt_nlo_setup_general_event_kinematics & (evt, process_instance) class(evt_nlo_t), intent(inout) :: evt type(process_instance_t), intent(in) :: process_instance integer :: n_born associate (event_deps => evt%event_deps) event_deps%lab_is_cm = process_instance%lab_is_cm (1) select type (pcm => process_instance%pcm) type is (pcm_nlo_t) n_born = pcm%region_data%n_legs_born end select call event_deps%p_born_cms%init (n_born, 1) call event_deps%p_born_lab%init (n_born, 1) end associate end subroutine evt_nlo_setup_general_event_kinematics @ %def evt_nlo_setup_general_event_kinematics @ <>= procedure :: setup_real_event_kinematics => & evt_nlo_setup_real_event_kinematics <>= module subroutine evt_nlo_setup_real_event_kinematics & (evt, process_instance) class(evt_nlo_t), intent(inout) :: evt type(process_instance_t), intent(in) :: process_instance end subroutine evt_nlo_setup_real_event_kinematics <>= module subroutine evt_nlo_setup_real_event_kinematics (evt, process_instance) class(evt_nlo_t), intent(inout) :: evt type(process_instance_t), intent(in) :: process_instance integer :: n_real, n_phs integer :: i_real associate (event_deps => evt%event_deps) select type (pcm => process_instance%pcm) class is (pcm_nlo_t) n_real = pcm%region_data%n_legs_real end select i_real = evt%process%get_first_real_term () select type (phs => process_instance%kin(i_real)%phs) type is (phs_fks_t) event_deps%phs_identifiers = phs%phs_identifiers end select n_phs = size (event_deps%phs_identifiers) call event_deps%p_real_cms%init (n_real, n_phs) call event_deps%p_real_lab%init (n_real, n_phs) select type (pcm => process_instance%pcm) type is (pcm_nlo_t) if (allocated (pcm%region_data%alr_contributors)) then allocate (event_deps%contributors & (size (pcm%region_data%alr_contributors))) event_deps%contributors = pcm%region_data%alr_contributors end if if (allocated (pcm%region_data%alr_to_i_contributor)) then allocate (event_deps%alr_to_i_con & (size (pcm%region_data%alr_to_i_contributor))) event_deps%alr_to_i_con = pcm%region_data%alr_to_i_contributor end if end select end associate end subroutine evt_nlo_setup_real_event_kinematics @ %def evt_nlo_setup_real_event_kinematics @ <>= procedure :: set_mode => evt_nlo_set_mode <>= module subroutine evt_nlo_set_mode (evt, process_instance) class(evt_nlo_t), intent(inout) :: evt type(process_instance_t), intent(in) :: process_instance end subroutine evt_nlo_set_mode <>= module subroutine evt_nlo_set_mode (evt, process_instance) class(evt_nlo_t), intent(inout) :: evt type(process_instance_t), intent(in) :: process_instance integer :: i_real select type (pcm => process_instance%pcm) type is (pcm_nlo_t) if (pcm%settings%combined_integration) then evt%mode = EVT_NLO_COMBINED else i_real = evt%process%get_first_real_component () if (i_real == evt%process%extract_active_component_mci ()) then evt%mode = EVT_NLO_SEPARATE_REAL else evt%mode = EVT_NLO_SEPARATE_BORNLIKE end if end if end select end subroutine evt_nlo_set_mode @ %def evt_nlo_set_mode @ <>= procedure :: is_valid_event => evt_nlo_is_valid_event <>= module function evt_nlo_is_valid_event (evt, i_term) result (valid) logical :: valid class(evt_nlo_t), intent(in) :: evt integer, intent(in) :: i_term end function evt_nlo_is_valid_event <>= module function evt_nlo_is_valid_event (evt, i_term) result (valid) logical :: valid class(evt_nlo_t), intent(in) :: evt integer, intent(in) :: i_term valid = evt%process_instance%term(i_term)%passed end function evt_nlo_is_valid_event @ %def evt_nlo_is_valid_event @ Retrieves the actual quantum numbers chosen in [[evt_nlo_prepare_new_event]]. <>= procedure :: get_selected_quantum_numbers => & evt_nlo_get_selected_quantum_numbers <>= module function evt_nlo_get_selected_quantum_numbers & (evt, i_flv) result (qn_select) class(evt_nlo_t), intent(in) :: evt integer, intent(in) :: i_flv type(quantum_numbers_t), dimension(:), allocatable :: qn_select end function evt_nlo_get_selected_quantum_numbers <>= module function evt_nlo_get_selected_quantum_numbers & (evt, i_flv) result (qn_select) class(evt_nlo_t), intent(in) :: evt integer, intent(in) :: i_flv type(quantum_numbers_t), dimension(:), allocatable :: qn_select integer :: i_term, index i_term = evt%get_i_term () associate (term => evt%process_instance%term(i_term)) index = term%connected%matrix%get_qn_index (i_flv, i_sub = 0) qn_select = term%connected%matrix%get_quantum_numbers (index) end associate end function evt_nlo_get_selected_quantum_numbers @ %def evt_nlo_get_selected_quantum_numbers @ Selects a flavor structure for Born subevents, such that each possible flavor structure is as probable as its portion of the sum of Born matrix elements over all flavors. For non-Born Born-like subevents, no Born matrix elements are available. We always choose [[i_flv = 1]] in this case. If all terms are active, i.e. in a full NLO calculation, the flavors of Born-like subevents will be distributed according to the Born matrix elements only, to avoid issues with matrix elements of different sign and assure a LO flavor distribution. Likewise, the real-like event flavors are distributed according to the real matrix elements. Here, we need to make sure to not mix matrix elements from different real terms and instead determine the flavor for each subevent based on just the matrix elements for one of the terms. The implementation below assumes that in the sequence of NLO terms, the Born term is immediately followed by all the real terms which are again followed by the subtraction, the virtual and the DGLAP term. Both flavor structures can be determined without correlation as the flavors will only become important for events to be matched to a parton shower and in this case we will only generate either a single Born-like or a single real-like event which are not part of an event group. In case all subevents failed the cuts, all [[sqme]]s were set to $0$ so we cannot determine the flavor in this way. In this case, we always choose the first flavor structure given by the matrix-element generator with [[i_flv = 1]]. Ideally, having to choose a particle set here would not be necessary as it is also chosen in [[particle_set_init_interaction]] which in the current approach is disabled by supplying [[qn_select]] explicitly based on the flavors chosen here. <>= procedure :: prepare_new_event => evt_nlo_prepare_new_event <>= module subroutine evt_nlo_prepare_new_event (evt, i_mci, i_term) class(evt_nlo_t), intent(inout) :: evt integer, intent(in) :: i_mci, i_term end subroutine evt_nlo_prepare_new_event <>= module subroutine evt_nlo_prepare_new_event (evt, i_mci, i_term) class(evt_nlo_t), intent(inout) :: evt integer, intent(in) :: i_mci, i_term real(default) :: s, x real(default) :: sqme_total real(default), dimension(:), allocatable :: sqme_flv integer :: i, i_flv, i_core, emitter, n_in logical, save :: warn_once = .true. class(prc_core_t), pointer :: core => null () call evt%reset () call evt%rng%generate (x) do i = 1, size (evt%process_instance%term) associate (term => evt%process_instance%term(i)) if (evt%i_evaluation == 0) then if (term%nlo_type == BORN) then allocate (sqme_flv (term%config%data%n_flv)) exit end if else if (term%nlo_type == NLO_REAL .and. .not. term%is_subtraction()) then allocate (sqme_flv (term%config%data%n_flv)) exit end if end if end associate end do sqme_total = zero sqme_flv = zero i_core = evt%process%get_i_core (i_term) core => evt%process%get_core_ptr (i_core) do i = 1, size (evt%process_instance%term) associate (term => evt%process_instance%term(i)) if (i == evt%i_evaluation + 1 .and. (term%nlo_type == BORN .or. & (term%nlo_type == NLO_REAL .and. .not. term%is_subtraction())) ) then sqme_total = sqme_total + real (sum ( term%connected%matrix%get_matrix_element ())) !!! TODO (VR 2020-02-19) figure out why this select type is needed for prc_omega_t !!! For NLO and prc_omega_t the connected trace seems to be set up incorrectly! !!! (PS 2020-11-05) This leads to real events of processes with structure functions !!! having a wrong flavor distribution if computed with O'Mega. !!! The flavor distributions are identical with and also without the special case !!! for O'Mega and wrong in both cases. !!! However, this case it is not critical as long as O'Mega does not provide matrix elements !!! exclusive in coupling orders and is thus only rarely used for NLO applications anyways select type (core) class is (prc_external_t) do i_flv = 1, size (sqme_flv) + if (allocated (term%passed_array)) then + if (term%passed .and. .not. term%passed_array(i_flv)) cycle + end if sqme_flv(i_flv) = sqme_flv(i_flv) & + real (term%connected%matrix%get_matrix_element ( & term%connected%matrix%get_qn_index (i_flv, i_sub = 0))) end do class default sqme_flv = sqme_flv & + real (term%connected%matrix%get_matrix_element ()) emitter = evt%process_instance%kin(i)%emitter n_in = evt%process_instance%kin(i)%n_in if (warn_once .and. term%nlo_type == NLO_REAL .and. emitter <= n_in) then warn_once = .false. call msg_warning("evt_nlo_prepare_new_event: fNLO flavor& & distributions with O'Mega are wrong.") end if end select end if end associate end do if (debug2_active (D_TRANSFORMS)) then if (.not. nearly_equal(sqme_total, sum (sqme_flv))) then call msg_warning ("evt_nlo_prepare_new_event: & &sum over flavored sqmes does not match total sqme.") end if end if !!! Need absolute values to take into account negative weights x = x * abs (sqme_total) s = abs (sqme_flv (1)) evt%selected_i_flv = 1 if (s < x) then do i_flv = 2, size (sqme_flv) s = s + abs (sqme_flv (i_flv)) if (s > x) then evt%selected_i_flv = i_flv exit end if end do end if if (debug2_active (D_TRANSFORMS)) then call msg_print_color ("Selected i_flv: ", COL_GREEN) print *, evt%selected_i_flv end if end subroutine evt_nlo_prepare_new_event @ %def evt_nlo_prepare_new_event @ \section{Complete Events} This module combines hard processes with decay chains, shower, and hadronization (not implemented yet) to complete events. It also manages the input and output of event records in various formats. <<[[events.f90]]>>= <> module events <> <> use diagnostics use variables use expr_base use model_data use state_matrices, only: FM_IGNORE_HELICITY, & FM_SELECT_HELICITY, FM_FACTOR_HELICITY, FM_CORRELATED_HELICITY use particles use subevt_expr use rng_base use process, only: process_t use instances, only: process_instance_t use process_stacks use event_base use event_transforms <> <> <> <> interface <> end interface contains <> end module events @ %def events @ <<[[events_sub.f90]]>>= <> submodule (events) events_s <> use constants, only: one use io_units use format_utils, only: pac_fmt, write_separator use format_defs, only: FMT_12, FMT_19 use numeric_utils use pcm, only: pcm_nlo_workspace_t use decays use evt_nlo implicit none contains <> end submodule events_s @ %def events_s @ \subsection{Event configuration} The parameters govern the transformation of an event to a particle set. The [[safety_factor]] reduces the acceptance probability for unweighting. If greater than one, excess events become less likely, but the reweighting efficiency also drops. The [[sigma]] and [[n]] values, if nontrivial, allow for reweighting the events according to the requested [[norm_mode]]. Various [[parse_node_t]] objects are taken from the SINDARIN input. They encode expressions that apply to the current event. The workspaces for evaluating those expressions are set up in the [[event_expr_t]] objects. Note that these are really pointers, so the actual nodes are not stored inside the event object. <>= type :: event_config_t logical :: unweighted = .false. integer :: norm_mode = NORM_UNDEFINED integer :: factorization_mode = FM_IGNORE_HELICITY logical :: keep_correlations = .false. logical :: colorize_subevt = .false. real(default) :: sigma = 1 integer :: n = 1 real(default) :: safety_factor = 1 class(expr_factory_t), allocatable :: ef_selection class(expr_factory_t), allocatable :: ef_reweight class(expr_factory_t), allocatable :: ef_analysis contains <> end type event_config_t @ %def event_config_t @ Output. <>= procedure :: write => event_config_write <>= module subroutine event_config_write (object, unit, show_expressions) class(event_config_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: show_expressions end subroutine event_config_write <>= module subroutine event_config_write (object, unit, show_expressions) class(event_config_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: show_expressions integer :: u u = given_output_unit (unit) write (u, "(3x,A,L1)") "Unweighted = ", object%unweighted write (u, "(3x,A,A)") "Normalization = ", & char (event_normalization_string (object%norm_mode)) write (u, "(3x,A)", advance="no") "Helicity handling = " select case (object%factorization_mode) case (FM_IGNORE_HELICITY) write (u, "(A)") "drop" case (FM_SELECT_HELICITY) write (u, "(A)") "select" case (FM_FACTOR_HELICITY) write (u, "(A)") "factorize" end select write (u, "(3x,A,L1)") "Keep correlations = ", object%keep_correlations if (object%colorize_subevt) then write (u, "(3x,A,L1)") "Colorize subevent = ", object%colorize_subevt end if if (.not. nearly_equal (object%safety_factor, one)) then write (u, "(3x,A," // FMT_12 // ")") & "Safety factor = ", object%safety_factor end if if (present (show_expressions)) then if (show_expressions) then if (allocated (object%ef_selection)) then call write_separator (u) write (u, "(3x,A)") "Event selection expression:" call object%ef_selection%write (u) end if if (allocated (object%ef_reweight)) then call write_separator (u) write (u, "(3x,A)") "Event reweighting expression:" call object%ef_reweight%write (u) end if if (allocated (object%ef_analysis)) then call write_separator (u) write (u, "(3x,A)") "Analysis expression:" call object%ef_analysis%write (u) end if end if end if end subroutine event_config_write @ %def event_config_write @ \subsection{The event type} This is the concrete implementation of the [[generic_event_t]] core that is defined above in the [[event_base]] module. The core manages the main (dressed) particle set pointer and the current values for weights and sqme. The implementation adds configuration data, expressions, process references, and event transforms. Each event refers to a single elementary process. This process may be dressed by a shower, a decay chain etc. We maintain pointers to a process instance. A list of event transforms (class [[evt_t]]) transform the connected interactions of the process instance into the final particle set. In this list, the first transform is always the trivial one, which just factorizes the process instance. Subsequent transforms may apply decays, etc. The [[particle_set]] pointer identifies the particle set that we want to be analyzed and returned by the event, usually the last one. Squared matrix element and weight values: when reading events from file, the [[ref]] value is the number in the file, while the [[prc]] value is the number that we calculate from the momenta in the file, possibly with different parameters. When generating events the first time, or if we do not recalculate, the numbers should coincide. Furthermore, the array of [[alt]] values is copied from an array of alternative event records. These values should represent calculated values. The [[sqme]] and [[weight]] values mirror corresponding values in the [[expr]] subobject. The idea is that when generating or reading events, the event record is filled first, then the [[expr]] object acquires copies. These copies are used for writing events and as targets for pointer variables in the analysis expression. All data that involve user-provided expressions (selection, reweighting, analysis) are handled by the [[expr]] subobject. In particular, evaluating the event-selection expression sets the [[passed]] flag. Furthermore, the [[expr]] subobject collects data that can be used in the analysis and should be written to file, including copies of [[sqme]] and [[weight]]. <>= public :: event_t <>= type, extends (generic_event_t) :: event_t type(event_config_t) :: config type(process_t), pointer :: process => null () type(process_instance_t), pointer :: instance => null () class(rng_t), allocatable :: rng integer :: selected_i_mci = 0 integer :: selected_i_term = 0 integer :: selected_channel = 0 logical :: is_complete = .false. class(evt_t), pointer :: transform_first => null () class(evt_t), pointer :: transform_last => null () type(event_expr_t) :: expr logical :: selection_evaluated = .false. logical :: passed = .false. real(default), allocatable :: alpha_qcd_forced real(default), allocatable :: scale_forced real(default) :: reweight = 1 logical :: analysis_flag = .false. integer :: i_event = 0 contains <> end type event_t @ %def event_t @ <>= procedure :: clone => event_clone <>= module subroutine event_clone (event, event_new) class(event_t), intent(in), target :: event class(event_t), intent(out), target:: event_new end subroutine event_clone <>= module subroutine event_clone (event, event_new) class(event_t), intent(in), target :: event class(event_t), intent(out), target:: event_new type(string_t) :: id integer :: num_id event_new%config = event%config event_new%process => event%process event_new%instance => event%instance if (allocated (event%rng)) & allocate(event_new%rng, source=event%rng) event_new%selected_i_mci = event%selected_i_mci event_new%selected_i_term = event%selected_i_term event_new%selected_channel = event%selected_channel event_new%is_complete = event%is_complete event_new%transform_first => event%transform_first event_new%transform_last => event%transform_last event_new%selection_evaluated = event%selection_evaluated event_new%passed = event%passed if (allocated (event%alpha_qcd_forced)) & allocate(event_new%alpha_qcd_forced, source=event%alpha_qcd_forced) if (allocated (event%scale_forced)) & allocate(event_new%scale_forced, source=event%scale_forced) event_new%reweight = event%reweight event_new%analysis_flag = event%analysis_flag event_new%i_event = event%i_event id = event_new%process%get_id () if (id /= "") call event_new%expr%set_process_id (id) num_id = event_new%process%get_num_id () if (num_id /= 0) call event_new%expr%set_process_num_id (num_id) call event_new%expr%setup_vars (event_new%process%get_sqrts ()) call event_new%expr%link_var_list (event_new%process%get_var_list_ptr ()) end subroutine event_clone @ %def event_clone @ Finalizer: the list of event transforms is deleted iteratively. <>= procedure :: final => event_final <>= module subroutine event_final (object) class(event_t), intent(inout) :: object end subroutine event_final <>= module subroutine event_final (object) class(event_t), intent(inout) :: object class(evt_t), pointer :: evt if (allocated (object%rng)) call object%rng%final () call object%expr%final () do while (associated (object%transform_first)) evt => object%transform_first object%transform_first => evt%next call evt%final () deallocate (evt) end do end subroutine event_final @ %def event_final @ Output. The event index is written in the header, it should coincide with the [[event_index]] variable that can be used in selection and analysis. Particle set: this is a pointer to one of the event transforms, so it should suffice to print the latter. <>= procedure :: write => event_write <>= module subroutine event_write (object, unit, show_process, & show_transforms, show_decay, verbose, testflag) class(event_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: show_process, show_transforms, show_decay logical, intent(in), optional :: verbose logical, intent(in), optional :: testflag end subroutine event_write <>= module subroutine event_write (object, unit, show_process, & show_transforms, show_decay, verbose, testflag) class(event_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: show_process, show_transforms, show_decay logical, intent(in), optional :: verbose logical, intent(in), optional :: testflag logical :: prc, trans, dec, verb class(evt_t), pointer :: evt character(len=7) :: fmt integer :: u, i call pac_fmt (fmt, FMT_19, FMT_12, testflag) u = given_output_unit (unit) prc = .true.; if (present (show_process)) prc = show_process trans = .true.; if (present (show_transforms)) trans = show_transforms dec = .true.; if (present (show_decay)) dec = show_decay verb = .false.; if (present (verbose)) verb = verbose call write_separator (u, 2) write (u, "(1x,A)", advance="no") "Event" if (object%has_index ()) then write (u, "(1x,'#',I0)", advance="no") object%get_index () end if if (object%is_complete) then write (u, *) else write (u, "(1x,A)") "[incomplete]" end if call write_separator (u) call object%config%write (u) if (object%sqme_ref_is_known () .or. object%weight_ref_is_known ()) then call write_separator (u) end if if (object%sqme_ref_is_known ()) then write (u, "(3x,A," // fmt // ")") & "Squared matrix el. (ref) = ", object%get_sqme_ref () if (object%sqme_alt_is_known ()) then do i = 1, object%get_n_alt () write (u, "(5x,A," // fmt // ",1x,I0)") & "alternate sqme = ", object%get_sqme_alt(i), i end do end if end if if (object%sqme_prc_is_known ()) & write (u, "(3x,A," // fmt // ")") & "Squared matrix el. (prc) = ", object%get_sqme_prc () if (object%weight_ref_is_known ()) then write (u, "(3x,A," // fmt // ")") & "Event weight (ref) = ", object%get_weight_ref () if (object%weight_alt_is_known ()) then do i = 1, object%get_n_alt () write (u, "(5x,A," // fmt // ",1x,I0)") & "alternate weight = ", object%get_weight_alt(i), i end do end if end if if (object%weight_prc_is_known ()) & write (u, "(3x,A," // fmt // ")") & "Event weight (prc) = ", object%get_weight_prc () if (object%selected_i_mci /= 0) then call write_separator (u) write (u, "(3x,A,I0)") "Selected MCI group = ", object%selected_i_mci write (u, "(3x,A,I0)") "Selected term = ", object%selected_i_term write (u, "(3x,A,I0)") "Selected channel = ", object%selected_channel end if if (object%selection_evaluated) then call write_separator (u) write (u, "(3x,A,L1)") "Passed selection = ", object%passed if (object%passed) then write (u, "(3x,A," // fmt // ")") & "Reweighting factor = ", object%reweight write (u, "(3x,A,L1)") & "Analysis flag = ", object%analysis_flag end if end if if (associated (object%instance)) then if (prc) then if (verb) then call object%instance%write (u, testflag) else call object%instance%write_header (u) end if end if if (trans) then evt => object%transform_first do while (associated (evt)) select type (evt) type is (evt_decay_t) call evt%write (u, verbose = dec, more_verbose = verb, & testflag = testflag) class default call evt%write (u, verbose = verb, testflag = testflag) end select call write_separator (u, 2) evt => evt%next end do else call write_separator (u, 2) end if if (object%expr%subevt_filled) then call object%expr%write (u, pacified = testflag) call write_separator (u, 2) end if else call write_separator (u, 2) write (u, "(1x,A)") "Process instance: [undefined]" call write_separator (u, 2) end if end subroutine event_write @ %def event_write @ \subsection{Initialization} Initialize: set configuration parameters, using a variable list. We do not call this [[init]], because this method name will be used by a type extension. The default normalization is [[NORM_SIGMA]], since the default generation mode is weighted. For unweighted events, we may want to a apply a safety factor to event rejection. (By default, this factor is unity and can be ignored.) We also allocate the trivial event transform, which is always the first one. Gfortran 7/8/9 bug, has to remain in the main module: <>= procedure :: basic_init => event_init <>= subroutine event_init (event, var_list, n_alt) class(event_t), intent(out) :: event type(var_list_t), intent(in), optional :: var_list integer, intent(in), optional :: n_alt type(string_t) :: norm_string, mode_string logical :: polarized_events if (present (n_alt)) then call event%base_init (n_alt) call event%expr%init (n_alt) else call event%base_init (0) end if if (present (var_list)) then event%config%unweighted = var_list%get_lval (& var_str ("?unweighted")) norm_string = var_list%get_sval (& var_str ("$sample_normalization")) event%config%norm_mode = & event_normalization_mode (norm_string, event%config%unweighted) polarized_events = & var_list%get_lval (var_str ("?polarized_events")) if (polarized_events) then mode_string = & var_list%get_sval (var_str ("$polarization_mode")) select case (char (mode_string)) case ("ignore") event%config%factorization_mode = FM_IGNORE_HELICITY case ("helicity") event%config%factorization_mode = FM_SELECT_HELICITY case ("factorized") event%config%factorization_mode = FM_FACTOR_HELICITY case ("correlated") event%config%factorization_mode = FM_CORRELATED_HELICITY case default call msg_fatal ("Polarization mode " & // char (mode_string) // " is undefined") end select else event%config%factorization_mode = FM_IGNORE_HELICITY end if event%config%colorize_subevt = & var_list%get_lval (var_str ("?colorize_subevt")) if (event%config%unweighted) then event%config%safety_factor = var_list%get_rval (& var_str ("safety_factor")) end if else event%config%norm_mode = NORM_SIGMA end if allocate (evt_trivial_t :: event%transform_first) event%transform_last => event%transform_first end subroutine event_init @ %def event_init @ Set the [[sigma]] and [[n]] values in the configuration record that determine non-standard event normalizations. If these numbers are not set explicitly, the default value for both is unity, and event renormalization has no effect. <>= procedure :: set_sigma => event_set_sigma procedure :: set_n => event_set_n <>= elemental module subroutine event_set_sigma (event, sigma) class(event_t), intent(inout) :: event real(default), intent(in) :: sigma end subroutine event_set_sigma elemental module subroutine event_set_n (event, n) class(event_t), intent(inout) :: event integer, intent(in) :: n end subroutine event_set_n <>= elemental module subroutine event_set_sigma (event, sigma) class(event_t), intent(inout) :: event real(default), intent(in) :: sigma event%config%sigma = sigma end subroutine event_set_sigma elemental module subroutine event_set_n (event, n) class(event_t), intent(inout) :: event integer, intent(in) :: n event%config%n = n end subroutine event_set_n @ %def event_set_n @ Append an event transform (decays, etc.). The transform is not yet connected to a process. The transform is then considered to belong to the event object, and will be finalized together with it. The original pointer is removed. We can assume that the trivial transform is already present in the event object, at least. <>= procedure :: import_transform => event_import_transform <>= module subroutine event_import_transform (event, evt) class(event_t), intent(inout) :: event class(evt_t), intent(inout), pointer :: evt end subroutine event_import_transform <>= module subroutine event_import_transform (event, evt) class(event_t), intent(inout) :: event class(evt_t), intent(inout), pointer :: evt event%transform_last%next => evt evt%previous => event%transform_last event%transform_last => evt evt => null () end subroutine event_import_transform @ %def event_import_transform @ We link the event to an existing process instance. This includes the variable list, which is linked to the process variable list. Note that this is not necessarily identical to the variable list used for event initialization. The variable list will contain pointers to [[event]] subobjects, therefore the [[target]] attribute. Once we have a process connected, we can use it to obtain an event generator instance. The model and process stack may be needed by event transforms. The current model setting may be different from the model in the process (regarding unstable particles, etc.). The process stack can be used for assigning extra processes that we need for the event transforms. <>= procedure :: connect => event_connect <>= module subroutine event_connect & (event, process_instance, model, process_stack) class(event_t), intent(inout), target :: event type(process_instance_t), intent(in), target :: process_instance class(model_data_t), intent(in), target :: model type(process_stack_t), intent(in), optional :: process_stack end subroutine event_connect <>= module subroutine event_connect & (event, process_instance, model, process_stack) class(event_t), intent(inout), target :: event type(process_instance_t), intent(in), target :: process_instance class(model_data_t), intent(in), target :: model type(process_stack_t), intent(in), optional :: process_stack type(string_t) :: id integer :: num_id class(evt_t), pointer :: evt event%process => process_instance%process event%instance => process_instance id = event%process%get_id () if (id /= "") call event%expr%set_process_id (id) num_id = event%process%get_num_id () if (num_id /= 0) call event%expr%set_process_num_id (num_id) call event%expr%setup_vars (event%process%get_sqrts ()) call event%expr%link_var_list (event%process%get_var_list_ptr ()) call event%process%make_rng (event%rng) evt => event%transform_first do while (associated (evt)) call evt%connect (process_instance, model, process_stack) evt => evt%next end do end subroutine event_connect @ %def event_connect @ Set the parse nodes for the associated expressions, individually. The parse-node pointers may be null. <>= procedure :: set_selection => event_set_selection procedure :: set_reweight => event_set_reweight procedure :: set_analysis => event_set_analysis <>= module subroutine event_set_selection (event, ef_selection) class(event_t), intent(inout) :: event class(expr_factory_t), intent(in) :: ef_selection end subroutine event_set_selection module subroutine event_set_reweight (event, ef_reweight) class(event_t), intent(inout) :: event class(expr_factory_t), intent(in) :: ef_reweight end subroutine event_set_reweight module subroutine event_set_analysis (event, ef_analysis) class(event_t), intent(inout) :: event class(expr_factory_t), intent(in) :: ef_analysis end subroutine event_set_analysis <>= module subroutine event_set_selection (event, ef_selection) class(event_t), intent(inout) :: event class(expr_factory_t), intent(in) :: ef_selection allocate (event%config%ef_selection, source = ef_selection) end subroutine event_set_selection module subroutine event_set_reweight (event, ef_reweight) class(event_t), intent(inout) :: event class(expr_factory_t), intent(in) :: ef_reweight allocate (event%config%ef_reweight, source = ef_reweight) end subroutine event_set_reweight module subroutine event_set_analysis (event, ef_analysis) class(event_t), intent(inout) :: event class(expr_factory_t), intent(in) :: ef_analysis allocate (event%config%ef_analysis, source = ef_analysis) end subroutine event_set_analysis @ %def event_set_selection @ %def event_set_reweight @ %def event_set_analysis @ Create evaluation trees from the parse trees. The [[target]] attribute is required because the expressions contain pointers to event subobjects. <>= procedure :: setup_expressions => event_setup_expressions <>= module subroutine event_setup_expressions (event) class(event_t), intent(inout), target :: event end subroutine event_setup_expressions <>= module subroutine event_setup_expressions (event) class(event_t), intent(inout), target :: event call event%expr%setup_selection (event%config%ef_selection) call event%expr%setup_analysis (event%config%ef_analysis) call event%expr%setup_reweight (event%config%ef_reweight) call event%expr%colorize (event%config%colorize_subevt) end subroutine event_setup_expressions @ %def event_setup_expressions @ \subsection{Evaluation} To fill the [[particle_set]], i.e., the event record proper, we have to apply all event transforms in order. The last transform should fill its associated particle set, factorizing the state matrix according to the current settings. There are several parameters in the event configuration that control this. We always fill the particle set for the first transform (the hard process) and the last transform, if different from the first (the fully dressed process). Each event transform is an event generator of its own. We choose to generate an \emph{unweighted} event for each of them, even if the master event is assumed to be weighted. Thus, the overall event weight is the one of the hard process only. (There may be more options in future extensions.) We can generate the two random numbers that the factorization needs. For testing purpose, we allow for providing them explicitly, as an option. <>= procedure :: evaluate_transforms => event_evaluate_transforms <>= module subroutine event_evaluate_transforms (event, r) class(event_t), intent(inout) :: event real(default), dimension(:), intent(in), optional :: r end subroutine event_evaluate_transforms <>= module subroutine event_evaluate_transforms (event, r) class(event_t), intent(inout) :: event real(default), dimension(:), intent(in), optional :: r class(evt_t), pointer :: evt real(default) :: weight_over_sqme integer :: i_term, emitter, n_in logical :: failed_but_keep failed_but_keep = .false. if (debug_on) call msg_debug (D_TRANSFORMS, "event_evaluate_transforms") call event%discard_particle_set () call event%check () if (event%instance%is_complete_event ()) then i_term = event%instance%select_i_term () event%selected_i_term = i_term evt => event%transform_first do while (associated (evt)) call evt%prepare_new_event & (event%selected_i_mci, event%selected_i_term) evt => evt%next end do if (debug_on) call msg_debug & (D_TRANSFORMS, "Before event transformations") if (debug_on) call msg_debug & (D_TRANSFORMS, "event%weight_prc", event%weight_prc) if (debug_on) call msg_debug & (D_TRANSFORMS, "event%sqme_prc", event%sqme_prc) evt => event%transform_first do while (associated (evt)) call print_transform_name_if_debug () if (evt%only_weighted_events) then select type (evt) type is (evt_nlo_t) i_term = evt%get_i_term () failed_but_keep = .not. evt%is_valid_event (i_term) & .and. evt%keep_failed_events if (.not. any(evt%process_instance%term%passed .and. evt%process_instance%term%active) & .and. .not. evt%keep_failed_events) return end select if (abs (event%weight_prc) > 0._default) then weight_over_sqme = event%weight_prc / event%sqme_prc call evt%generate_weighted (event%sqme_prc) event%weight_prc = weight_over_sqme * event%sqme_prc select type (evt) type is (evt_nlo_t) if (.not. evt%is_valid_event (i_term)) event%weight_prc = 0 end select else if (.not. failed_but_keep) exit end if else call evt%generate_unweighted () end if if (signal_is_pending ()) return select type (evt) type is (evt_nlo_t) if (evt%i_evaluation > 0) then emitter = evt%process_instance%kin(i_term)%emitter n_in = evt%process_instance%kin(i_term)%n_in if (emitter <= n_in) then call evt%connected_set_real_IS_momenta () end if end if end select call evt%make_particle_set (event%config%factorization_mode, & event%config%keep_correlations) if (signal_is_pending ()) return if (.not. evt%particle_set_exists) exit evt => evt%next end do evt => event%transform_last if ((associated (evt) .and. evt%particle_set_exists) .or. failed_but_keep) then if (event%is_nlo ()) then select type (evt) type is (evt_nlo_t) evt%particle_set_nlo (event%i_event + 1) = evt%particle_set evt%i_evaluation = evt%i_evaluation + 1 call event%link_particle_set & (evt%particle_set_nlo(event%i_event + 1)) end select else call event%link_particle_set (evt%particle_set) end if end if if (debug_on) call msg_debug & (D_TRANSFORMS, "After event transformations") if (debug_on) call msg_debug & (D_TRANSFORMS, "event%weight_prc", event%weight_prc) if (debug_on) call msg_debug & (D_TRANSFORMS, "event%sqme_prc", event%sqme_prc) if (debug_on) call msg_debug & (D_TRANSFORMS, "evt%particle_set_exists", evt%particle_set_exists) end if contains subroutine print_transform_name_if_debug () if (debug_active (D_TRANSFORMS)) then print *, 'Current event transform: ' call evt%write_name () end if end subroutine print_transform_name_if_debug end subroutine event_evaluate_transforms @ %def event_evaluate_transforms @ Set / increment the event index for the current event. There is no condition for this to happen. The event index is actually stored in the subevent expression, because this allows us to access it in subevent expressions as a variable. <>= procedure :: set_index => event_set_index procedure :: increment_index => event_increment_index <>= module subroutine event_set_index (event, index) class(event_t), intent(inout) :: event integer, intent(in) :: index end subroutine event_set_index module subroutine event_increment_index (event, offset) class(event_t), intent(inout) :: event integer, intent(in), optional :: offset end subroutine event_increment_index <>= module subroutine event_set_index (event, index) class(event_t), intent(inout) :: event integer, intent(in) :: index call event%expr%set_event_index (index) end subroutine event_set_index module subroutine event_increment_index (event, offset) class(event_t), intent(inout) :: event integer, intent(in), optional :: offset call event%expr%increment_event_index (offset) end subroutine event_increment_index @ %def event_set_index @ %def event_increment_index @ Evaluate the event-related expressions, given a valid [[particle_set]]. If [[update_sqme]] is set, we use the process instance for the [[sqme_prc]] value. The [[sqme_ref]] value is always taken from the event record. <>= procedure :: evaluate_expressions => event_evaluate_expressions <>= module subroutine event_evaluate_expressions (event) class(event_t), intent(inout) :: event end subroutine event_evaluate_expressions <>= module subroutine event_evaluate_expressions (event) class(event_t), intent(inout) :: event if (event%has_valid_particle_set ()) then call event%expr%fill_subevt (event%get_particle_set_ptr ()) end if if (event%weight_ref_is_known ()) then call event%expr%set (weight_ref = event%get_weight_ref ()) end if if (event%weight_prc_is_known ()) then call event%expr%set (weight_prc = event%get_weight_prc ()) end if if (event%excess_prc_is_known ()) then call event%expr%set (excess_prc = event%get_excess_prc ()) end if if (event%sqme_ref_is_known ()) then call event%expr%set (sqme_ref = event%get_sqme_ref ()) end if if (event%sqme_prc_is_known ()) then call event%expr%set (sqme_prc = event%get_sqme_prc ()) end if if (event%has_valid_particle_set ()) then call event%expr%evaluate & (event%passed, event%reweight, event%analysis_flag) event%selection_evaluated = .true. end if end subroutine event_evaluate_expressions @ %def event_evaluate_expressions @ Report the result of the [[selection]] evaluation. <>= procedure :: passed_selection => event_passed_selection <>= module function event_passed_selection (event) result (flag) class(event_t), intent(in) :: event logical :: flag end function event_passed_selection <>= module function event_passed_selection (event) result (flag) class(event_t), intent(in) :: event logical :: flag flag = event%passed end function event_passed_selection @ %def event_passed_selection @ Set alternate sqme and weight arrays. This should be merged with the previous routine, if the expressions are allowed to refer to these values. <>= procedure :: store_alt_values => event_store_alt_values <>= module subroutine event_store_alt_values (event) class(event_t), intent(inout) :: event end subroutine event_store_alt_values <>= module subroutine event_store_alt_values (event) class(event_t), intent(inout) :: event if (event%weight_alt_is_known ()) then call event%expr%set (weight_alt = event%get_weight_alt ()) end if if (event%sqme_alt_is_known ()) then call event%expr%set (sqme_alt = event%get_sqme_alt ()) end if end subroutine event_store_alt_values @ %def event_store_alt_values @ <>= procedure :: is_nlo => event_is_nlo <>= module function event_is_nlo (event) result (is_nlo) logical :: is_nlo class(event_t), intent(in) :: event end function event_is_nlo <>= module function event_is_nlo (event) result (is_nlo) logical :: is_nlo class(event_t), intent(in) :: event if (associated (event%instance)) then select type (pcm_work => event%instance%pcm_work) type is (pcm_nlo_workspace_t) is_nlo = pcm_work%is_fixed_order_nlo_events () class default is_nlo = .false. end select else is_nlo = .false. end if end function event_is_nlo @ %def event_is_nlo @ \subsection{Reset to empty state} Applying this, current event contents are marked as incomplete but are not deleted. In particular, the initialization is kept. The event index is also kept, this can be reset separately. <>= procedure :: reset_contents => event_reset_contents procedure :: reset_index => event_reset_index <>= module subroutine event_reset_contents (event) class(event_t), intent(inout) :: event end subroutine event_reset_contents module subroutine event_reset_index (event) class(event_t), intent(inout) :: event end subroutine event_reset_index <>= module subroutine event_reset_contents (event) class(event_t), intent(inout) :: event class(evt_t), pointer :: evt call event%base_reset_contents () event%selected_i_mci = 0 event%selected_i_term = 0 event%selected_channel = 0 event%is_complete = .false. call event%expr%reset_contents () event%selection_evaluated = .false. event%passed = .false. event%analysis_flag = .false. if (associated (event%instance)) then call event%instance%reset (reset_mci = .true.) end if if (allocated (event%alpha_qcd_forced)) deallocate (event%alpha_qcd_forced) if (allocated (event%scale_forced)) deallocate (event%scale_forced) evt => event%transform_first do while (associated (evt)) call evt%reset () evt => evt%next end do end subroutine event_reset_contents module subroutine event_reset_index (event) class(event_t), intent(inout) :: event call event%expr%reset_event_index () end subroutine event_reset_index @ %def event_reset_contents @ %def event_reset_index @ \subsection{Squared Matrix Element and Weight} Transfer the result of the process instance calculation to the event record header. <>= procedure :: import_instance_results => event_import_instance_results <>= module subroutine event_import_instance_results (event) class(event_t), intent(inout) :: event end subroutine event_import_instance_results <>= module subroutine event_import_instance_results (event) class(event_t), intent(inout) :: event if (associated (event%instance)) then if (event%instance%has_evaluated_trace ()) then call event%set ( & sqme_prc = event%instance%get_sqme (), & weight_prc = event%instance%get_weight (), & excess_prc = event%instance%get_excess (), & n_dropped = event%instance%get_n_dropped () & ) end if end if end subroutine event_import_instance_results @ %def event_import_instance_results @ Duplicate the instance result / the reference result in the event record. <>= procedure :: accept_sqme_ref => event_accept_sqme_ref procedure :: accept_sqme_prc => event_accept_sqme_prc procedure :: accept_weight_ref => event_accept_weight_ref procedure :: accept_weight_prc => event_accept_weight_prc <>= module subroutine event_accept_sqme_ref (event) class(event_t), intent(inout) :: event end subroutine event_accept_sqme_ref module subroutine event_accept_sqme_prc (event) class(event_t), intent(inout) :: event end subroutine event_accept_sqme_prc module subroutine event_accept_weight_ref (event) class(event_t), intent(inout) :: event end subroutine event_accept_weight_ref module subroutine event_accept_weight_prc (event) class(event_t), intent(inout) :: event end subroutine event_accept_weight_prc <>= module subroutine event_accept_sqme_ref (event) class(event_t), intent(inout) :: event if (event%sqme_ref_is_known ()) then call event%set (sqme_prc = event%get_sqme_ref ()) end if end subroutine event_accept_sqme_ref module subroutine event_accept_sqme_prc (event) class(event_t), intent(inout) :: event if (event%sqme_prc_is_known ()) then call event%set (sqme_ref = event%get_sqme_prc ()) end if end subroutine event_accept_sqme_prc module subroutine event_accept_weight_ref (event) class(event_t), intent(inout) :: event if (event%weight_ref_is_known ()) then call event%set (weight_prc = event%get_weight_ref ()) end if end subroutine event_accept_weight_ref module subroutine event_accept_weight_prc (event) class(event_t), intent(inout) :: event if (event%weight_prc_is_known ()) then call event%set (weight_ref = event%get_weight_prc ()) end if end subroutine event_accept_weight_prc @ %def event_accept_sqme_ref @ %def event_accept_sqme_prc @ %def event_accept_weight_ref @ %def event_accept_weight_prc @ Update the weight normalization, just after generation. Unweighted and weighted events are generated with a different default normalization. The intended normalization is stored in the configuration record. <>= procedure :: update_normalization => event_update_normalization <>= module subroutine event_update_normalization (event, mode_ref) class(event_t), intent(inout) :: event integer, intent(in), optional :: mode_ref end subroutine event_update_normalization <>= module subroutine event_update_normalization (event, mode_ref) class(event_t), intent(inout) :: event integer, intent(in), optional :: mode_ref integer :: mode_old real(default) :: weight, excess if (present (mode_ref)) then mode_old = mode_ref else if (event%config%unweighted) then mode_old = NORM_UNIT else mode_old = NORM_SIGMA end if weight = event%get_weight_prc () call event_normalization_update (weight, & event%config%sigma, event%config%n, & mode_new = event%config%norm_mode, & mode_old = mode_old) call event%set_weight_prc (weight) excess = event%get_excess_prc () call event_normalization_update (excess, & event%config%sigma, event%config%n, & mode_new = event%config%norm_mode, & mode_old = mode_old) call event%set_excess_prc (excess) end subroutine event_update_normalization @ %def event_update_normalization @ The event is complete if it has a particle set plus valid entries for the sqme and weight values. <>= procedure :: check => event_check <>= module subroutine event_check (event) class(event_t), intent(inout) :: event end subroutine event_check <>= module subroutine event_check (event) class(event_t), intent(inout) :: event event%is_complete = event%has_valid_particle_set () & .and. event%sqme_ref_is_known () & .and. event%sqme_prc_is_known () & .and. event%weight_ref_is_known () & .and. event%weight_prc_is_known () if (event%get_n_alt () /= 0) then event%is_complete = event%is_complete & .and. event%sqme_alt_is_known () & .and. event%weight_alt_is_known () end if end subroutine event_check @ %def event_check @ @ \subsection{Generation} Assuming that we have a valid process associated to the event, we generate an event. We complete the event data, then factorize the spin density matrix and transfer it to the particle set. When done, we retrieve squared matrix element and weight. In case of explicit generation, the reference values coincide with the process values, so we [[accept]] the latter. The explicit random number argument [[r]] should be generated by a random-number generator. It is taken for the factorization algorithm, bypassing the event-specific random-number generator. This is useful for deterministic testing. <>= procedure :: generate => event_generate <>= module subroutine event_generate (event, i_mci, r, i_nlo) class(event_t), intent(inout) :: event integer, intent(in) :: i_mci real(default), dimension(:), intent(in), optional :: r integer, intent(in), optional :: i_nlo end subroutine event_generate <>= module subroutine event_generate (event, i_mci, r, i_nlo) class(event_t), intent(inout) :: event integer, intent(in) :: i_mci real(default), dimension(:), intent(in), optional :: r integer, intent(in), optional :: i_nlo logical :: generate_new generate_new = .true. if (present (i_nlo)) generate_new = (i_nlo == 1) if (generate_new) call event%reset_contents () event%selected_i_mci = i_mci if (event%config%unweighted) then call event%instance%generate_unweighted_event (i_mci) if (signal_is_pending ()) return call event%instance%evaluate_event_data () call event%instance%normalize_weight () else if (generate_new) & call event%instance%generate_weighted_event (i_mci) if (signal_is_pending ()) return call event%instance%evaluate_event_data () end if event%selected_channel = event%instance%get_channel () call event%import_instance_results () call event%accept_sqme_prc () call event%update_normalization () call event%accept_weight_prc () call event%evaluate_transforms (r) if (signal_is_pending ()) return call event%check () end subroutine event_generate @ %def event_generate @ Get a copy of the particle set belonging to the hard process. <>= procedure :: get_hard_particle_set => event_get_hard_particle_set <>= module subroutine event_get_hard_particle_set (event, pset) class(event_t), intent(in) :: event type(particle_set_t), intent(out) :: pset end subroutine event_get_hard_particle_set <>= module subroutine event_get_hard_particle_set (event, pset) class(event_t), intent(in) :: event type(particle_set_t), intent(out) :: pset class(evt_t), pointer :: evt evt => event%transform_first pset = evt%particle_set end subroutine event_get_hard_particle_set @ %def event_get_hard_particle_set @ \subsection{Recovering an event} Select MC group, term, and integration channel. <>= procedure :: select => event_select <>= module subroutine event_select (event, i_mci, i_term, channel) class(event_t), intent(inout) :: event integer, intent(in) :: i_mci, i_term, channel end subroutine event_select <>= module subroutine event_select (event, i_mci, i_term, channel) class(event_t), intent(inout) :: event integer, intent(in) :: i_mci, i_term, channel if (associated (event%instance)) then event%selected_i_mci = i_mci event%selected_i_term = i_term event%selected_channel = channel else event%selected_i_mci = 0 event%selected_i_term = 0 event%selected_channel = 0 end if end subroutine event_select @ %def event_select @ Copy a particle set into the event record. We deliberately use the first (the trivial) transform for this, i.e., the hard process. The event reader may either read in the transformed event separately, or apply all event transforms to the hard particle set to (re)generate a fully dressed event. Since this makes all subsequent event transforms invalid, we call [[reset]] on them. <>= procedure :: set_hard_particle_set => event_set_hard_particle_set <>= module subroutine event_set_hard_particle_set (event, particle_set) class(event_t), intent(inout) :: event type(particle_set_t), intent(in) :: particle_set end subroutine event_set_hard_particle_set <>= module subroutine event_set_hard_particle_set (event, particle_set) class(event_t), intent(inout) :: event type(particle_set_t), intent(in) :: particle_set class(evt_t), pointer :: evt evt => event%transform_first call evt%set_particle_set (particle_set, & event%selected_i_mci, event%selected_i_term) call event%link_particle_set (evt%particle_set) evt => evt%next do while (associated (evt)) call evt%reset () evt => evt%next end do end subroutine event_set_hard_particle_set @ %def event_set_hard_particle_set @ Set the $\alpha_s$ value that should be used in a recalculation. This should be called only if we explicitly want to override the QCD setting of the process core. <>= procedure :: set_alpha_qcd_forced => event_set_alpha_qcd_forced <>= module subroutine event_set_alpha_qcd_forced (event, alpha_qcd) class(event_t), intent(inout) :: event real(default), intent(in) :: alpha_qcd end subroutine event_set_alpha_qcd_forced <>= module subroutine event_set_alpha_qcd_forced (event, alpha_qcd) class(event_t), intent(inout) :: event real(default), intent(in) :: alpha_qcd if (allocated (event%alpha_qcd_forced)) then event%alpha_qcd_forced = alpha_qcd else allocate (event%alpha_qcd_forced, source = alpha_qcd) end if end subroutine event_set_alpha_qcd_forced @ %def event_set_alpha_qcd_forced @ Analogously, for the common scale. This forces also renormalization and factorization scale. <>= procedure :: set_scale_forced => event_set_scale_forced <>= module subroutine event_set_scale_forced (event, scale) class(event_t), intent(inout) :: event real(default), intent(in) :: scale end subroutine event_set_scale_forced <>= module subroutine event_set_scale_forced (event, scale) class(event_t), intent(inout) :: event real(default), intent(in) :: scale if (allocated (event%scale_forced)) then event%scale_forced = scale else allocate (event%scale_forced, source = scale) end if end subroutine event_set_scale_forced @ %def event_set_scale_forced @ Here we try to recover an event from the [[particle_set]] subobject and recalculate the structure functions and matrix elements. We have the appropriate [[process]] object and an initialized [[process_instance]] at hand, so beam and configuration data are known. From the [[particle_set]], we get the momenta. The quantum-number information may be incomplete, e.g., helicity information may be partial or absent. We recover the event just from the momentum configuration. We do not transfer the matrix element from the process instance to the event record, as we do when generating an event. The event record may contain the matrix element as read from file, and the current calculation may use different parameters. We thus can compare old and new values. The event [[weight]] may also be known already. If yes, we pass it to the [[evaluate_event_data]] procedure. It should already be normalized. If we have a [[weight_factor]] value, we obtain the event weight by multiplying the computed [[sqme]] by this factor. Otherwise, we make use of the MCI setup (which should be valid then) to compute the event weight, and we should normalize the result just as when generating events. Evaluating event expressions must also be done separately. If [[recover_phs]] is set (and false), do not attempt any phase-space calculation, including MCI evaluation. Useful if we need only matrix elements. <>= procedure :: recalculate => event_recalculate <>= module subroutine event_recalculate (event, update_sqme, weight_factor, & recover_beams, recover_phs, check_match, success) class(event_t), intent(inout) :: event logical, intent(in) :: update_sqme real(default), intent(in), optional :: weight_factor logical, intent(in), optional :: recover_beams logical, intent(in), optional :: recover_phs logical, intent(in), optional :: check_match logical, intent(out), optional :: success end subroutine event_recalculate <>= module subroutine event_recalculate (event, update_sqme, weight_factor, & recover_beams, recover_phs, check_match, success) class(event_t), intent(inout) :: event logical, intent(in) :: update_sqme real(default), intent(in), optional :: weight_factor logical, intent(in), optional :: recover_beams logical, intent(in), optional :: recover_phs logical, intent(in), optional :: check_match logical, intent(out), optional :: success type(particle_set_t), pointer :: particle_set integer :: i_mci, i_term, channel logical :: rec_phs_mci rec_phs_mci = .true.; if (present (recover_phs)) rec_phs_mci = recover_phs if (present (success)) success = .false. if (event%has_valid_particle_set ()) then particle_set => event%get_particle_set_ptr () i_mci = event%selected_i_mci i_term = event%selected_i_term channel = event%selected_channel if (i_mci == 0 .or. i_term == 0 .or. channel == 0) then call msg_bug ("Event: recalculate: undefined selection parameters") end if call event%instance%choose_mci (i_mci) call event%instance%set_trace & (particle_set, i_term, recover_beams, check_match, success) if (present (success)) then if (.not. success) return end if if (allocated (event%alpha_qcd_forced)) then call event%instance%set_alpha_qcd_forced & (i_term, event%alpha_qcd_forced) end if call event%instance%recover (channel, i_term, & update_sqme, rec_phs_mci, event%scale_forced) if (signal_is_pending ()) return if (update_sqme .and. present (weight_factor)) then call event%instance%evaluate_event_data & (weight = event%instance%get_sqme () * weight_factor) else if (event%weight_ref_is_known ()) then call event%instance%evaluate_event_data & (weight = event%get_weight_ref ()) else if (rec_phs_mci) then call event%instance%recover_event () if (signal_is_pending ()) return call event%instance%evaluate_event_data () if (event%config%unweighted) then call event%instance%normalize_weight () end if end if if (signal_is_pending ()) return if (update_sqme) then call event%import_instance_results () else call event%accept_sqme_ref () call event%accept_weight_ref () end if else call msg_bug ("Event: can't recalculate, particle set is undefined") end if end subroutine event_recalculate @ %def event_recalculate @ \subsection{Access content} Pointer to the associated process object (the associated model). <>= procedure :: get_process_ptr => event_get_process_ptr procedure :: get_process_instance_ptr => event_get_process_instance_ptr procedure :: get_model_ptr => event_get_model_ptr <>= module function event_get_process_ptr (event) result (ptr) class(event_t), intent(in) :: event type(process_t), pointer :: ptr end function event_get_process_ptr module function event_get_process_instance_ptr (event) result (ptr) class(event_t), intent(in) :: event type(process_instance_t), pointer :: ptr end function event_get_process_instance_ptr module function event_get_model_ptr (event) result (model) class(event_t), intent(in) :: event class(model_data_t), pointer :: model end function event_get_model_ptr <>= module function event_get_process_ptr (event) result (ptr) class(event_t), intent(in) :: event type(process_t), pointer :: ptr ptr => event%process end function event_get_process_ptr module function event_get_process_instance_ptr (event) result (ptr) class(event_t), intent(in) :: event type(process_instance_t), pointer :: ptr ptr => event%instance end function event_get_process_instance_ptr module function event_get_model_ptr (event) result (model) class(event_t), intent(in) :: event class(model_data_t), pointer :: model if (associated (event%process)) then model => event%process%get_model_ptr () else model => null () end if end function event_get_model_ptr @ %def event_get_process_ptr @ %def event_get_process_instance_ptr @ %def event_get_model_ptr @ Return the current values of indices: the MCI group of components, the term index (different terms corresponding, potentially, to different effective kinematics), and the MC integration channel. The [[i_mci]] call is delegated to the current process instance. <>= procedure :: get_i_mci => event_get_i_mci procedure :: get_i_term => event_get_i_term procedure :: get_channel => event_get_channel <>= module function event_get_i_mci (event) result (i_mci) class(event_t), intent(in) :: event integer :: i_mci end function event_get_i_mci module function event_get_i_term (event) result (i_term) class(event_t), intent(in) :: event integer :: i_term end function event_get_i_term module function event_get_channel (event) result (channel) class(event_t), intent(in) :: event integer :: channel end function event_get_channel <>= module function event_get_i_mci (event) result (i_mci) class(event_t), intent(in) :: event integer :: i_mci i_mci = event%selected_i_mci end function event_get_i_mci module function event_get_i_term (event) result (i_term) class(event_t), intent(in) :: event integer :: i_term i_term = event%selected_i_term end function event_get_i_term module function event_get_channel (event) result (channel) class(event_t), intent(in) :: event integer :: channel channel = event%selected_channel end function event_get_channel @ %def event_get_i_mci @ %def event_get_i_term @ %def event_get_channel @ This flag tells us whether the event consists just of a hard process (i.e., holds at most the first, trivial transform), or is a dressed events with additional transforms. <>= procedure :: has_transform => event_has_transform <>= module function event_has_transform (event) result (flag) class(event_t), intent(in) :: event logical :: flag end function event_has_transform <>= module function event_has_transform (event) result (flag) class(event_t), intent(in) :: event logical :: flag if (associated (event%transform_first)) then flag = associated (event%transform_first%next) else flag = .false. end if end function event_has_transform @ %def event_has_transform @ Return the currently selected normalization mode, or alternate normalization mode. <>= procedure :: get_norm_mode => event_get_norm_mode <>= elemental module function event_get_norm_mode (event) result (norm_mode) class(event_t), intent(in) :: event integer :: norm_mode end function event_get_norm_mode <>= elemental module function event_get_norm_mode (event) result (norm_mode) class(event_t), intent(in) :: event integer :: norm_mode norm_mode = event%config%norm_mode end function event_get_norm_mode @ %def event_get_norm_mode @ Return the kinematical weight, defined as the ratio of event weight and squared matrix element. <>= procedure :: get_kinematical_weight => event_get_kinematical_weight <>= module function event_get_kinematical_weight (event) result (f) class(event_t), intent(in) :: event real(default) :: f end function event_get_kinematical_weight <>= module function event_get_kinematical_weight (event) result (f) class(event_t), intent(in) :: event real(default) :: f if (event%sqme_ref_is_known () .and. event%weight_ref_is_known () & .and. abs (event%get_sqme_ref ()) > 0) then f = event%get_weight_ref () / event%get_sqme_ref () else f = 0 end if end function event_get_kinematical_weight @ %def event_get_kinematical_weight @ Return data used by external event formats. <>= procedure :: has_index => event_has_index procedure :: get_index => event_get_index procedure :: get_fac_scale => event_get_fac_scale procedure :: get_alpha_s => event_get_alpha_s procedure :: get_sqrts => event_get_sqrts procedure :: get_polarization => event_get_polarization procedure :: get_beam_file => event_get_beam_file procedure :: get_process_name => event_get_process_name <>= module function event_has_index (event) result (flag) class(event_t), intent(in) :: event logical :: flag end function event_has_index module function event_get_index (event) result (index) class(event_t), intent(in) :: event integer :: index end function event_get_index module function event_get_fac_scale (event) result (fac_scale) class(event_t), intent(in) :: event real(default) :: fac_scale end function event_get_fac_scale module function event_get_alpha_s (event) result (alpha_s) class(event_t), intent(in) :: event real(default) :: alpha_s end function event_get_alpha_s module function event_get_sqrts (event) result (sqrts) class(event_t), intent(in) :: event real(default) :: sqrts end function event_get_sqrts module function event_get_polarization (event) result (pol) class(event_t), intent(in) :: event real(default), dimension(:), allocatable :: pol end function event_get_polarization module function event_get_beam_file (event) result (file) class(event_t), intent(in) :: event type(string_t) :: file end function event_get_beam_file module function event_get_process_name (event) result (name) class(event_t), intent(in) :: event type(string_t) :: name end function event_get_process_name <>= module function event_has_index (event) result (flag) class(event_t), intent(in) :: event logical :: flag flag = event%expr%has_event_index () end function event_has_index module function event_get_index (event) result (index) class(event_t), intent(in) :: event integer :: index index = event%expr%get_event_index () end function event_get_index module function event_get_fac_scale (event) result (fac_scale) class(event_t), intent(in) :: event real(default) :: fac_scale fac_scale = event%instance%get_fac_scale (event%selected_i_term) end function event_get_fac_scale module function event_get_alpha_s (event) result (alpha_s) class(event_t), intent(in) :: event real(default) :: alpha_s alpha_s = event%instance%get_alpha_s (event%selected_i_term) end function event_get_alpha_s module function event_get_sqrts (event) result (sqrts) class(event_t), intent(in) :: event real(default) :: sqrts sqrts = event%instance%get_sqrts () end function event_get_sqrts module function event_get_polarization (event) result (pol) class(event_t), intent(in) :: event real(default), dimension(:), allocatable :: pol pol = event%instance%get_polarization () end function event_get_polarization module function event_get_beam_file (event) result (file) class(event_t), intent(in) :: event type(string_t) :: file file = event%instance%get_beam_file () end function event_get_beam_file module function event_get_process_name (event) result (name) class(event_t), intent(in) :: event type(string_t) :: name name = event%instance%get_process_name () end function event_get_process_name @ %def event_get_index @ %def event_get_fac_scale @ %def event_get_alpha_s @ %def event_get_sqrts @ %def event_get_polarization @ %def event_get_beam_file @ %def event_get_process_name @ Return the actual number of calls, as stored in the process instance. <>= procedure :: get_actual_calls_total => event_get_actual_calls_total <>= elemental module function event_get_actual_calls_total (event) result (n) class(event_t), intent(in) :: event integer :: n end function event_get_actual_calls_total <>= elemental module function event_get_actual_calls_total (event) result (n) class(event_t), intent(in) :: event integer :: n if (associated (event%instance)) then n = event%instance%get_actual_calls_total () else n = 0 end if end function event_get_actual_calls_total @ %def event_get_actual_calls_total @ Eliminate numerical noise in the [[subevt]] expression and in the event transforms (which includes associated process instances). <>= public :: pacify <>= interface pacify module procedure pacify_event end interface pacify <>= module subroutine pacify_event (event) class(event_t), intent(inout) :: event class(evt_t), pointer :: evt end subroutine pacify_event <>= module subroutine pacify_event (event) class(event_t), intent(inout) :: event class(evt_t), pointer :: evt call event%pacify_particle_set () if (event%expr%subevt_filled) call pacify (event%expr) evt => event%transform_first do while (associated (evt)) select type (evt) type is (evt_decay_t); call pacify (evt) end select evt => evt%next end do end subroutine pacify_event @ %def pacify @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[events_ut.f90]]>>= <> module events_ut use unit_tests use events_uti <> <> contains <> end module events_ut @ %def events_ut @ <<[[events_uti.f90]]>>= <> module events_uti <> <> use os_interface use model_data use particles use process_libraries use process_stacks use event_transforms use decays use decays_ut, only: prepare_testbed use process, only: process_t use instances, only: process_instance_t use events <> <> contains <> end module events_uti @ %def events_uti @ API: driver for the unit tests below. <>= public :: events_test <>= subroutine events_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine events_test @ %def events_test @ \subsubsection{Empty event record} <>= call test (events_1, "events_1", & "empty event record", & u, results) <>= public :: events_1 <>= subroutine events_1 (u) integer, intent(in) :: u type(event_t), target :: event write (u, "(A)") "* Test output: events_1" write (u, "(A)") "* Purpose: display an empty event object" write (u, "(A)") call event%write (u) write (u, "(A)") write (u, "(A)") "* Test output end: events_1" end subroutine events_1 @ %def events_1 @ \subsubsection{Simple event} <>= call test (events_2, "events_2", & "generate event", & u, results) <>= public :: events_2 <>= subroutine events_2 (u) use processes_ut, only: prepare_test_process, cleanup_test_process integer, intent(in) :: u type(event_t), allocatable, target :: event type(process_t), allocatable, target :: process type(process_instance_t), allocatable, target :: process_instance type(model_data_t), target :: model write (u, "(A)") "* Test output: events_2" write (u, "(A)") "* Purpose: generate and display an event" write (u, "(A)") call model%init_test () write (u, "(A)") "* Generate test process event" allocate (process) allocate (process_instance) call prepare_test_process (process, process_instance, model) call process_instance%setup_event_data () write (u, "(A)") write (u, "(A)") "* Initialize event object" allocate (event) call event%basic_init () call event%connect (process_instance, process%get_model_ptr ()) write (u, "(A)") write (u, "(A)") "* Generate test process event" call process_instance%generate_weighted_event (1) write (u, "(A)") write (u, "(A)") "* Fill event object" write (u, "(A)") call event%generate (1, [0.4_default, 0.4_default]) call event%increment_index () call event%evaluate_expressions () call event%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call event%final () deallocate (event) call cleanup_test_process (process, process_instance) deallocate (process_instance) deallocate (process) call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: events_2" end subroutine events_2 @ %def events_2 @ \subsubsection{Recovering an event} Generate an event and store the particle set. Then reset the event record, recall the particle set, and recover the event from that. <>= call test (events_4, "events_4", & "recover event", & u, results) <>= public :: events_4 <>= subroutine events_4 (u) use processes_ut, only: prepare_test_process, cleanup_test_process integer, intent(in) :: u type(event_t), allocatable, target :: event type(process_t), allocatable, target :: process type(process_instance_t), allocatable, target :: process_instance type(process_t), allocatable, target :: process2 type(process_instance_t), allocatable, target :: process2_instance type(particle_set_t) :: particle_set type(model_data_t), target :: model write (u, "(A)") "* Test output: events_4" write (u, "(A)") "* Purpose: generate and recover an event" write (u, "(A)") call model%init_test () write (u, "(A)") "* Generate test process event and save particle set" write (u, "(A)") allocate (process) allocate (process_instance) call prepare_test_process (process, process_instance, model) call process_instance%setup_event_data () allocate (event) call event%basic_init () call event%connect (process_instance, process%get_model_ptr ()) call event%generate (1, [0.4_default, 0.4_default]) call event%increment_index () call event%evaluate_expressions () call event%write (u) particle_set = event%get_particle_set_ptr () ! NB: 'particle_set' contains pointers to the model within 'process' call event%final () deallocate (event) write (u, "(A)") write (u, "(A)") "* Recover event from particle set" write (u, "(A)") allocate (process2) allocate (process2_instance) call prepare_test_process (process2, process2_instance, model) call process2_instance%setup_event_data () allocate (event) call event%basic_init () call event%connect (process2_instance, process2%get_model_ptr ()) call event%select (1, 1, 1) call event%set_hard_particle_set (particle_set) call event%recalculate (update_sqme = .true.) call event%write (u) write (u, "(A)") write (u, "(A)") "* Transfer sqme and evaluate expressions" write (u, "(A)") call event%accept_sqme_prc () call event%accept_weight_prc () call event%check () call event%set_index (1) call event%evaluate_expressions () call event%write (u) write (u, "(A)") write (u, "(A)") "* Reset contents" write (u, "(A)") call event%reset_contents () call event%reset_index () event%transform_first%particle_set_exists = .false. call event%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call particle_set%final () call event%final () deallocate (event) call cleanup_test_process (process2, process2_instance) deallocate (process2_instance) deallocate (process2) call cleanup_test_process (process, process_instance) deallocate (process_instance) deallocate (process) call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: events_4" end subroutine events_4 @ %def events_4 @ \subsubsection{Partially Recovering an event} Generate an event and store the particle set. Then reset the event record, recall the particle set, and recover the event as far as possible without recomputing the squared matrix element. <>= call test (events_5, "events_5", & "partially recover event", & u, results) <>= public :: events_5 <>= subroutine events_5 (u) use processes_ut, only: prepare_test_process, cleanup_test_process integer, intent(in) :: u type(event_t), allocatable, target :: event type(process_t), allocatable, target :: process type(process_instance_t), allocatable, target :: process_instance type(process_t), allocatable, target :: process2 type(process_instance_t), allocatable, target :: process2_instance type(particle_set_t) :: particle_set real(default) :: sqme, weight type(model_data_t), target :: model write (u, "(A)") "* Test output: events_5" write (u, "(A)") "* Purpose: generate and recover an event" write (u, "(A)") call model%init_test () write (u, "(A)") "* Generate test process event and save particle set" write (u, "(A)") allocate (process) allocate (process_instance) call prepare_test_process (process, process_instance, model) call process_instance%setup_event_data () allocate (event) call event%basic_init () call event%connect (process_instance, process%get_model_ptr ()) call event%generate (1, [0.4_default, 0.4_default]) call event%increment_index () call event%evaluate_expressions () call event%write (u) particle_set = event%get_particle_set_ptr () sqme = event%get_sqme_ref () weight = event%get_weight_ref () call event%final () deallocate (event) write (u, "(A)") write (u, "(A)") "* Recover event from particle set" write (u, "(A)") allocate (process2) allocate (process2_instance) call prepare_test_process (process2, process2_instance, model) call process2_instance%setup_event_data () allocate (event) call event%basic_init () call event%connect (process2_instance, process2%get_model_ptr ()) call event%select (1, 1, 1) call event%set_hard_particle_set (particle_set) call event%recalculate (update_sqme = .false.) call event%write (u) write (u, "(A)") write (u, "(A)") "* Manually set sqme and evaluate expressions" write (u, "(A)") call event%set (sqme_ref = sqme, weight_ref = weight) call event%accept_sqme_ref () call event%accept_weight_ref () call event%set_index (1) call event%evaluate_expressions () call event%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call particle_set%final () call event%final () deallocate (event) call cleanup_test_process (process2, process2_instance) deallocate (process2_instance) deallocate (process2) call cleanup_test_process (process, process_instance) deallocate (process_instance) deallocate (process) call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: events_5" end subroutine events_5 @ %def events_5 @ \subsubsection{Decays} Generate an event with subsequent decays. <>= call test (events_6, "events_6", & "decays", & u, results) <>= public :: events_6 <>= subroutine events_6 (u) integer, intent(in) :: u type(os_data_t) :: os_data class(model_data_t), pointer :: model type(string_t) :: prefix, procname1, procname2 type(process_library_t), target :: lib type(process_stack_t) :: process_stack class(evt_t), pointer :: evt_decay type(event_t), allocatable, target :: event type(process_t), pointer :: process type(process_instance_t), allocatable, target :: process_instance write (u, "(A)") "* Test output: events_6" write (u, "(A)") "* Purpose: generate an event with subsequent decays" write (u, "(A)") write (u, "(A)") "* Generate test process and decay" write (u, "(A)") call os_data%init () prefix = "events_6" procname1 = prefix // "_p" procname2 = prefix // "_d" call prepare_testbed & (lib, process_stack, prefix, os_data, & scattering=.true., decay=.true.) write (u, "(A)") "* Initialize decay process" process => process_stack%get_process_ptr (procname1) model => process%get_model_ptr () call model%set_unstable (25, [procname2]) allocate (process_instance) call process_instance%init (process) call process_instance%setup_event_data () call process_instance%init_simulation (1) write (u, "(A)") write (u, "(A)") "* Initialize event transform: decay" allocate (evt_decay_t :: evt_decay) call evt_decay%connect (process_instance, model, process_stack) write (u, "(A)") write (u, "(A)") "* Initialize event object" write (u, "(A)") allocate (event) call event%basic_init () call event%connect (process_instance, model) call event%import_transform (evt_decay) call event%write (u, show_decay = .true.) write (u, "(A)") write (u, "(A)") "* Generate event" write (u, "(A)") call event%generate (1, [0.4_default, 0.4_default]) call event%increment_index () call event%evaluate_expressions () call event%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call event%final () deallocate (event) call process_instance%final () deallocate (process_instance) call process_stack%final () write (u, "(A)") write (u, "(A)") "* Test output end: events_6" end subroutine events_6 @ %def events_6 @ \subsubsection{Decays} Generate a decay event with varying options. <>= call test (events_7, "events_7", & "decay options", & u, results) <>= public :: events_7 <>= subroutine events_7 (u) integer, intent(in) :: u type(os_data_t) :: os_data class(model_data_t), pointer :: model type(string_t) :: prefix, procname2 type(process_library_t), target :: lib type(process_stack_t) :: process_stack type(process_t), pointer :: process type(process_instance_t), allocatable, target :: process_instance write (u, "(A)") "* Test output: events_7" write (u, "(A)") "* Purpose: check decay options" write (u, "(A)") write (u, "(A)") "* Prepare test process" write (u, "(A)") call os_data%init () prefix = "events_7" procname2 = prefix // "_d" call prepare_testbed & (lib, process_stack, prefix, os_data, & scattering=.false., decay=.true.) write (u, "(A)") "* Generate decay event, default options" write (u, "(A)") process => process_stack%get_process_ptr (procname2) model => process%get_model_ptr () call model%set_unstable (25, [procname2]) allocate (process_instance) call process_instance%init (process) call process_instance%setup_event_data (model) call process_instance%init_simulation (1) call process_instance%generate_weighted_event (1) call process_instance%write (u) call process_instance%final () deallocate (process_instance) write (u, "(A)") write (u, "(A)") "* Generate decay event, helicity-diagonal decay" write (u, "(A)") process => process_stack%get_process_ptr (procname2) model => process%get_model_ptr () call model%set_unstable (25, [procname2], diagonal = .true.) allocate (process_instance) call process_instance%init (process) call process_instance%setup_event_data (model) call process_instance%init_simulation (1) call process_instance%generate_weighted_event (1) call process_instance%write (u) call process_instance%final () deallocate (process_instance) write (u, "(A)") write (u, "(A)") "* Generate decay event, isotropic decay, & &polarized final state" write (u, "(A)") process => process_stack%get_process_ptr (procname2) model => process%get_model_ptr () call model%set_unstable (25, [procname2], isotropic = .true.) call model%set_polarized (6) call model%set_polarized (-6) allocate (process_instance) call process_instance%init (process) call process_instance%setup_event_data (model) call process_instance%init_simulation (1) call process_instance%generate_weighted_event (1) call process_instance%write (u) call process_instance%final () deallocate (process_instance) write (u, "(A)") write (u, "(A)") "* Cleanup" call process_stack%final () write (u, "(A)") write (u, "(A)") "* Test output end: events_7" end subroutine events_7 @ %def events_7 @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Raw Event I/O} The raw format is for internal use only. All data are stored unformatted, so they can be efficiently be re-read on the same machine, but not necessarily on another machine. This module explicitly depends on the [[events]] module which provides the concrete implementation of [[event_base]]. The other I/O formats access only the methods that are defined in [[event_base]]. <<[[eio_raw.f90]]>>= <> module eio_raw <> <> use event_base use event_handles, only: event_handle_t use eio_data use eio_base use events <> <> <> <> interface <> end interface end module eio_raw @ %def eio_raw @ <<[[eio_raw_sub.f90]]>>= <> submodule (eio_raw) eio_raw_s use io_units use diagnostics use model_data use particles implicit none contains <> end submodule eio_raw_s @ %def eio_raw_s @ \subsection{File Format Version} This is the current default file version. <>= integer, parameter :: CURRENT_FILE_VERSION = 2 @ %def CURRENT_FILE_VERSION @ The user may change this number; this should force some compatibility mode for reading and writing. In any case, the file version stored in a event file that we read has to match the expected file version. History of version numbers: \begin{enumerate} \item Format for WHIZARD 2.2.0 to 2.2.3. No version number stored in the raw file. \item Format from 2.2.4 on. File contains version number. The file contains the transformed particle set (if applicable) after the hard-process particle set. \end{enumerate} @ \subsection{Type} Note the file version number. The default may be reset during initialization, which should enforce some compatibility mode. <>= public :: eio_raw_t <>= type, extends (eio_t) :: eio_raw_t logical :: reading = .false. logical :: writing = .false. integer :: unit = 0 integer :: norm_mode = NORM_UNDEFINED real(default) :: sigma = 1 integer :: n = 1 integer :: n_alt = 0 logical :: check = .false. logical :: use_alphas_from_file = .false. logical :: use_scale_from_file = .false. logical :: fixed_order_nlo = .false. integer :: file_version = CURRENT_FILE_VERSION contains <> end type eio_raw_t @ %def eio_raw_t @ Output. This is not the actual event format, but a readable account of the current object status. <>= procedure :: write => eio_raw_write <>= module subroutine eio_raw_write (object, unit) class(eio_raw_t), intent(in) :: object integer, intent(in), optional :: unit end subroutine eio_raw_write <>= module subroutine eio_raw_write (object, unit) class(eio_raw_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(1x,A)") "Raw event stream:" write (u, "(3x,A,L1)") "Check MD5 sum = ", object%check if (object%n_alt > 0) then write (u, "(3x,A,I0)") "Alternate weights = ", object%n_alt end if write (u, "(3x,A,L1)") "Alpha_s from file = ", & object%use_alphas_from_file write (u, "(3x,A,L1)") "Scale from file = ", & object%use_scale_from_file write (u, "(3x,A,L1)") "Events for fNLO = ", & object%fixed_order_nlo if (object%reading) then write (u, "(3x,A,A)") "Reading from file = ", char (object%filename) else if (object%writing) then write (u, "(3x,A,A)") "Writing to file = ", char (object%filename) else write (u, "(3x,A)") "[closed]" end if end subroutine eio_raw_write @ %def eio_raw_write @ Finalizer: close any open file. <>= procedure :: final => eio_raw_final <>= module subroutine eio_raw_final (object) class(eio_raw_t), intent(inout) :: object end subroutine eio_raw_final <>= module subroutine eio_raw_final (object) class(eio_raw_t), intent(inout) :: object if (object%reading .or. object%writing) then write (msg_buffer, "(A,A,A)") "Events: closing raw file '", & char (object%filename), "'" call msg_message () close (object%unit) object%reading = .false. object%writing = .false. end if end subroutine eio_raw_final @ %def eio_raw_final @ Set the [[check]] flag which determines whether we compare checksums on input. <>= procedure :: set_parameters => eio_raw_set_parameters <>= module subroutine eio_raw_set_parameters (eio, check, & use_alphas_from_file, use_scale_from_file, fixed_order_nlo, & version_string, extension) class(eio_raw_t), intent(inout) :: eio logical, intent(in), optional :: check, use_alphas_from_file, & use_scale_from_file, fixed_order_nlo type(string_t), intent(in), optional :: version_string type(string_t), intent(in), optional :: extension end subroutine eio_raw_set_parameters <>= module subroutine eio_raw_set_parameters (eio, check, use_alphas_from_file, & use_scale_from_file, fixed_order_nlo, version_string, extension) class(eio_raw_t), intent(inout) :: eio logical, intent(in), optional :: check, use_alphas_from_file, & use_scale_from_file, fixed_order_nlo type(string_t), intent(in), optional :: version_string type(string_t), intent(in), optional :: extension if (present (check)) eio%check = check if (present (use_alphas_from_file)) eio%use_alphas_from_file = & use_alphas_from_file if (present (use_scale_from_file)) eio%use_scale_from_file = & use_scale_from_file if (present (fixed_order_nlo)) eio%fixed_order_nlo = & fixed_order_nlo if (present (version_string)) then select case (char (version_string)) case ("", "2.2.4") eio%file_version = CURRENT_FILE_VERSION case ("2.2") eio%file_version = 1 case default call msg_fatal ("Raw event I/O: unsupported version '" & // char (version_string) // "'") eio%file_version = 0 end select end if if (present (extension)) then eio%extension = extension else eio%extension = "evx" end if end subroutine eio_raw_set_parameters @ %def eio_raw_set_parameters @ Initialize event writing. <>= procedure :: init_out => eio_raw_init_out <>= module subroutine eio_raw_init_out (eio, sample, data, success, extension) class(eio_raw_t), intent(inout) :: eio type(string_t), intent(in) :: sample type(event_sample_data_t), intent(in), optional :: data logical, intent(out), optional :: success type(string_t), intent(in), optional :: extension end subroutine eio_raw_init_out <>= module subroutine eio_raw_init_out (eio, sample, data, success, extension) class(eio_raw_t), intent(inout) :: eio type(string_t), intent(in) :: sample type(event_sample_data_t), intent(in), optional :: data logical, intent(out), optional :: success type(string_t), intent(in), optional :: extension character(32) :: md5sum_prc, md5sum_cfg character(32), dimension(:), allocatable :: md5sum_alt integer :: i if (present (extension)) then eio%extension = extension else eio%extension = "evx" end if eio%filename = sample // "." // eio%extension eio%unit = free_unit () write (msg_buffer, "(A,A,A)") "Events: writing to raw file '", & char (eio%filename), "'" call msg_message () eio%writing = .true. if (present (data)) then md5sum_prc = data%md5sum_prc md5sum_cfg = data%md5sum_cfg eio%norm_mode = data%norm_mode eio%sigma = data%total_cross_section eio%n = data%n_evt eio%n_alt = data%n_alt if (eio%n_alt > 0) then !!! !!! !!! Workaround for gfortran 5.0 ICE allocate (md5sum_alt (data%n_alt)) md5sum_alt = data%md5sum_alt !!! allocate (md5sum_alt (data%n_alt), source = data%md5sum_alt) end if else md5sum_prc = "" md5sum_cfg = "" end if open (eio%unit, file = char (eio%filename), form = "unformatted", & action = "write", status = "replace") select case (eio%file_version) case (2:); write (eio%unit) eio%file_version end select write (eio%unit) md5sum_prc write (eio%unit) md5sum_cfg write (eio%unit) eio%norm_mode write (eio%unit) eio%n_alt if (allocated (md5sum_alt)) then do i = 1, eio%n_alt write (eio%unit) md5sum_alt(i) end do end if if (present (success)) success = .true. end subroutine eio_raw_init_out @ %def eio_raw_init_out @ Initialize event reading. <>= procedure :: init_in => eio_raw_init_in <>= module subroutine eio_raw_init_in (eio, sample, data, success, extension) class(eio_raw_t), intent(inout) :: eio type(string_t), intent(in) :: sample type(event_sample_data_t), intent(inout), optional :: data logical, intent(out), optional :: success type(string_t), intent(in), optional :: extension end subroutine eio_raw_init_in <>= module subroutine eio_raw_init_in (eio, sample, data, success, extension) class(eio_raw_t), intent(inout) :: eio type(string_t), intent(in) :: sample type(event_sample_data_t), intent(inout), optional :: data logical, intent(out), optional :: success type(string_t), intent(in), optional :: extension character(32) :: md5sum_prc, md5sum_cfg character(32), dimension(:), allocatable :: md5sum_alt integer :: i, file_version if (present (success)) success = .true. if (present (extension)) then eio%extension = extension else eio%extension = "evx" end if eio%filename = sample // "." // eio%extension eio%unit = free_unit () if (present (data)) then eio%sigma = data%total_cross_section eio%n = data%n_evt end if write (msg_buffer, "(A,A,A)") "Events: reading from raw file '", & char (eio%filename), "'" call msg_message () eio%reading = .true. open (eio%unit, file = char (eio%filename), form = "unformatted", & action = "read", status = "old") select case (eio%file_version) case (2:); read (eio%unit) file_version case default; file_version = 1 end select if (file_version /= eio%file_version) then call msg_error ("Reading event file: raw-file version mismatch.") if (present (success)) success = .false. return else if (file_version /= CURRENT_FILE_VERSION) then call msg_warning ("Reading event file: compatibility mode.") end if read (eio%unit) md5sum_prc read (eio%unit) md5sum_cfg read (eio%unit) eio%norm_mode read (eio%unit) eio%n_alt if (present (data)) then if (eio%n_alt /= data%n_alt) then if (present (success)) success = .false. return end if end if allocate (md5sum_alt (eio%n_alt)) do i = 1, eio%n_alt read (eio%unit) md5sum_alt(i) end do if (present (success)) then if (present (data)) then if (eio%check) then if (data%md5sum_prc /= "") then success = success .and. md5sum_prc == data%md5sum_prc end if if (data%md5sum_cfg /= "") then success = success .and. md5sum_cfg == data%md5sum_cfg end if do i = 1, eio%n_alt if (data%md5sum_alt(i) /= "") then success = success .and. md5sum_alt(i) == data%md5sum_alt(i) end if end do else call msg_warning ("Reading event file: MD5 sum check disabled") end if end if end if end subroutine eio_raw_init_in @ %def eio_raw_init_in @ Switch from input to output: reopen the file for reading. <>= procedure :: switch_inout => eio_raw_switch_inout <>= module subroutine eio_raw_switch_inout (eio, success) class(eio_raw_t), intent(inout) :: eio logical, intent(out), optional :: success end subroutine eio_raw_switch_inout <>= module subroutine eio_raw_switch_inout (eio, success) class(eio_raw_t), intent(inout) :: eio logical, intent(out), optional :: success write (msg_buffer, "(A,A,A)") "Events: appending to raw file '", & char (eio%filename), "'" call msg_message () close (eio%unit, status = "keep") eio%reading = .false. open (eio%unit, file = char (eio%filename), form = "unformatted", & action = "write", position = "append", status = "old") eio%writing = .true. if (present (success)) success = .true. end subroutine eio_raw_switch_inout @ %def eio_raw_switch_inout @ Output an event. Write first the event indices, then weight and squared matrix element, then the particle set. We always write the particle set of the hard process. (Note: this should be reconsidered.) We do make a physical copy. On output, we write the [[prc]] values for weight and sqme, since these are the values just computed. On input, we store the values as [[ref]] values. The caller can then decide whether to recompute values and thus obtain distinct [[prc]] values, or just accept them. The [[passed]] flag is not written. This allow us to apply different selection criteria upon rereading. <>= procedure :: output => eio_raw_output <>= module subroutine eio_raw_output & (eio, event, i_prc, reading, passed, pacify, event_handle) class(eio_raw_t), intent(inout) :: eio class(generic_event_t), intent(in), target :: event logical, intent(in), optional :: reading, passed, pacify class(event_handle_t), intent(inout), optional :: event_handle integer, intent(in) :: i_prc end subroutine eio_raw_output <>= module subroutine eio_raw_output & (eio, event, i_prc, reading, passed, pacify, event_handle) class(eio_raw_t), intent(inout) :: eio class(generic_event_t), intent(in), target :: event logical, intent(in), optional :: reading, passed, pacify class(event_handle_t), intent(inout), optional :: event_handle integer, intent(in) :: i_prc type(particle_set_t), pointer :: pset integer :: i if (eio%writing) then if (event%has_valid_particle_set ()) then select type (event) type is (event_t) write (eio%unit) i_prc write (eio%unit) event%get_index () write (eio%unit) event%get_i_mci () write (eio%unit) event%get_i_term () write (eio%unit) event%get_channel () write (eio%unit) event%expr%weight_prc write (eio%unit) event%expr%excess_prc write (eio%unit) event%get_n_dropped () write (eio%unit) event%expr%sqme_prc do i = 1, eio%n_alt write (eio%unit) event%expr%weight_alt(i) write (eio%unit) event%expr%sqme_alt(i) end do allocate (pset) call event%get_hard_particle_set (pset) call pset%write_raw (eio%unit) call pset%final () deallocate (pset) select case (eio%file_version) case (2:) if (event%has_transform ()) then write (eio%unit) .true. pset => event%get_particle_set_ptr () call pset%write_raw (eio%unit) else write (eio%unit) .false. end if end select class default call msg_bug ("Event: write raw: defined only for full event_t") end select else call msg_bug ("Event: write raw: particle set is undefined") end if else call eio%write () call msg_fatal ("Raw event file is not open for writing") end if end subroutine eio_raw_output @ %def eio_raw_output @ Input an event. Note: the particle set is physically copied. If there is a performance issue, we might choose to pointer-assign it instead, with a different version of [[event%set_hard_particle_set]]. <>= procedure :: input_i_prc => eio_raw_input_i_prc procedure :: input_event => eio_raw_input_event <>= module subroutine eio_raw_input_i_prc (eio, i_prc, iostat) class(eio_raw_t), intent(inout) :: eio integer, intent(out) :: i_prc integer, intent(out) :: iostat end subroutine eio_raw_input_i_prc module subroutine eio_raw_input_event (eio, event, iostat, event_handle) class(eio_raw_t), intent(inout) :: eio class(generic_event_t), intent(inout), target :: event integer, intent(out) :: iostat class(event_handle_t), intent(inout), optional :: event_handle end subroutine eio_raw_input_event <>= module subroutine eio_raw_input_i_prc (eio, i_prc, iostat) class(eio_raw_t), intent(inout) :: eio integer, intent(out) :: i_prc integer, intent(out) :: iostat if (eio%reading) then read (eio%unit, iostat = iostat) i_prc else call eio%write () call msg_fatal ("Raw event file is not open for reading") end if end subroutine eio_raw_input_i_prc module subroutine eio_raw_input_event (eio, event, iostat, event_handle) class(eio_raw_t), intent(inout) :: eio class(generic_event_t), intent(inout), target :: event integer, intent(out) :: iostat class(event_handle_t), intent(inout), optional :: event_handle integer :: event_index, i_mci, i_term, channel, i real(default) :: weight, excess, sqme integer :: n_dropped real(default), dimension(:), allocatable :: weight_alt, sqme_alt logical :: has_transform type(particle_set_t), pointer :: pset class(model_data_t), pointer :: model if (eio%reading) then select type (event) type is (event_t) read (eio%unit, iostat = iostat) event_index if (iostat /= 0) return read (eio%unit, iostat = iostat) i_mci if (iostat /= 0) return read (eio%unit, iostat = iostat) i_term if (iostat /= 0) return read (eio%unit, iostat = iostat) channel if (iostat /= 0) return read (eio%unit, iostat = iostat) weight if (iostat /= 0) return read (eio%unit, iostat = iostat) excess if (iostat /= 0) return read (eio%unit, iostat = iostat) n_dropped if (iostat /= 0) return read (eio%unit, iostat = iostat) sqme if (iostat /= 0) return call event%reset_contents () call event%set_index (event_index) call event%select (i_mci, i_term, channel) if (eio%norm_mode /= NORM_UNDEFINED) then call event_normalization_update (weight, & eio%sigma, eio%n, event%get_norm_mode (), eio%norm_mode) call event_normalization_update (excess, & eio%sigma, eio%n, event%get_norm_mode (), eio%norm_mode) end if call event%set (sqme_ref = sqme, weight_ref = weight, & excess_prc = excess, & n_dropped = n_dropped) if (eio%n_alt /= 0) then allocate (sqme_alt (eio%n_alt), weight_alt (eio%n_alt)) do i = 1, eio%n_alt read (eio%unit, iostat = iostat) weight_alt(i) if (iostat /= 0) return read (eio%unit, iostat = iostat) sqme_alt(i) if (iostat /= 0) return end do call event%set (sqme_alt = sqme_alt, weight_alt = weight_alt) end if model => null () if (associated (event%process)) then model => event%process%get_model_ptr () end if allocate (pset) call pset%read_raw (eio%unit, iostat) if (iostat /= 0) return if (associated (model)) call pset%set_model (model) call event%set_hard_particle_set (pset) if (eio%use_alphas_from_file .or. eio%use_scale_from_file) then call event%recalculate (update_sqme = .true.) if (eio%fixed_order_nlo) then if (event%weight_prc /= event%weight_ref .and. & event%weight_prc == 0) then event%weight_prc = event%weight_ref end if end if end if call pset%final () deallocate (pset) select case (eio%file_version) case (2:) read (eio%unit, iostat = iostat) has_transform if (iostat /= 0) return if (has_transform) then allocate (pset) call pset%read_raw (eio%unit, iostat) if (iostat /= 0) return if (associated (model)) & call pset%set_model (model) call event%link_particle_set (pset) end if end select class default call msg_bug ("Event: read raw: defined only for full event_t") end select else call eio%write () call msg_fatal ("Raw event file is not open for reading") end if end subroutine eio_raw_input_event @ %def eio_raw_input_i_prc @ %def eio_raw_input_event @ <>= procedure :: skip => eio_raw_skip <>= module subroutine eio_raw_skip (eio, iostat) class(eio_raw_t), intent(inout) :: eio integer, intent(out) :: iostat end subroutine eio_raw_skip <>= module subroutine eio_raw_skip (eio, iostat) class(eio_raw_t), intent(inout) :: eio integer, intent(out) :: iostat if (eio%reading) then read (eio%unit, iostat = iostat) else call eio%write () call msg_fatal ("Raw event file is not open for reading") end if end subroutine eio_raw_skip @ %def eio_raw_skip @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[eio_raw_ut.f90]]>>= <> module eio_raw_ut use unit_tests use eio_raw_uti <> <> contains <> end module eio_raw_ut @ %def eio_raw_ut @ <<[[eio_raw_uti.f90]]>>= <> module eio_raw_uti <> <> use model_data use variables use events use eio_data use eio_base use eio_raw use process, only: process_t use instances, only: process_instance_t <> <> contains <> end module eio_raw_uti @ %def eio_raw_uti @ API: driver for the unit tests below. <>= public :: eio_raw_test <>= subroutine eio_raw_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine eio_raw_test @ %def eio_raw_test @ \subsubsection{Test I/O methods} We test the implementation of all I/O methods. <>= call test (eio_raw_1, "eio_raw_1", & "read and write event contents", & u, results) <>= public :: eio_raw_1 <>= subroutine eio_raw_1 (u) use processes_ut, only: prepare_test_process, cleanup_test_process integer, intent(in) :: u type(model_data_t), target :: model type(event_t), allocatable, target :: event type(process_t), allocatable, target :: process type(process_instance_t), allocatable, target :: process_instance class(eio_t), allocatable :: eio integer :: i_prc, iostat type(string_t) :: sample write (u, "(A)") "* Test output: eio_raw_1" write (u, "(A)") "* Purpose: generate and read/write an event" write (u, "(A)") write (u, "(A)") "* Initialize test process" call model%init_test () allocate (process) allocate (process_instance) call prepare_test_process (process, process_instance, model, & run_id = var_str ("run_test")) call process_instance%setup_event_data () allocate (event) call event%basic_init () call event%connect (process_instance, process%get_model_ptr ()) write (u, "(A)") write (u, "(A)") "* Generate and write an event" write (u, "(A)") sample = "eio_raw_1" allocate (eio_raw_t :: eio) call eio%init_out (sample) call event%generate (1, [0._default, 0._default]) call event%increment_index () call event%evaluate_expressions () call event%write (u) write (u, "(A)") call eio%output (event, i_prc = 42) call eio%write (u) call eio%final () call event%final () deallocate (event) call process_instance%final () deallocate (process_instance) write (u, "(A)") write (u, "(A)") "* Re-read the event" write (u, "(A)") call eio%init_in (sample) allocate (process_instance) call process_instance%init (process) call process_instance%setup_event_data () allocate (event) call event%basic_init () call event%connect (process_instance, process%get_model_ptr ()) call eio%input_i_prc (i_prc, iostat) if (iostat /= 0) write (u, "(A,I0)") "I/O error (i_prc):", iostat call eio%input_event (event, iostat) if (iostat /= 0) write (u, "(A,I0)") "I/O error (event):", iostat call eio%write (u) write (u, "(A)") write (u, "(1x,A,I0)") "i_prc = ", i_prc write (u, "(A)") call event%write (u) write (u, "(A)") write (u, "(A)") "* Generate and append another event" write (u, "(A)") call eio%switch_inout () call event%generate (1, [0._default, 0._default]) call event%increment_index () call event%evaluate_expressions () call event%write (u) write (u, "(A)") call eio%output (event, i_prc = 5) call eio%write (u) call eio%final () call event%final () deallocate (event) call process_instance%final () deallocate (process_instance) write (u, "(A)") write (u, "(A)") "* Re-read both events" write (u, "(A)") call eio%init_in (sample) allocate (process_instance) call process_instance%init (process) call process_instance%setup_event_data () allocate (event) call event%basic_init () call event%connect (process_instance, process%get_model_ptr ()) call eio%input_i_prc (i_prc, iostat) if (iostat /= 0) write (u, "(A,I0)") "I/O error (i_prc/1):", iostat call eio%input_event (event, iostat) if (iostat /= 0) write (u, "(A,I0)") "I/O error (event/1):", iostat call eio%input_i_prc (i_prc, iostat) if (iostat /= 0) write (u, "(A,I0)") "I/O error (i_prc/2):", iostat call eio%input_event (event, iostat) if (iostat /= 0) write (u, "(A,I0)") "I/O error (event/2):", iostat call eio%write (u) write (u, "(A)") write (u, "(1x,A,I0)") "i_prc = ", i_prc write (u, "(A)") call event%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call eio%final () deallocate (eio) call event%final () deallocate (event) call cleanup_test_process (process, process_instance) deallocate (process_instance) deallocate (process) call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: eio_raw_1" end subroutine eio_raw_1 @ %def eio_raw_1 @ \subsubsection{Test I/O methods} We test the implementation of all I/O methods. <>= call test (eio_raw_2, "eio_raw_2", & "handle multiple weights", & u, results) <>= public :: eio_raw_2 <>= subroutine eio_raw_2 (u) use processes_ut, only: prepare_test_process, cleanup_test_process integer, intent(in) :: u type(model_data_t), target :: model type(var_list_t) :: var_list type(event_t), allocatable, target :: event type(process_t), allocatable, target :: process type(process_instance_t), allocatable, target :: process_instance type(event_sample_data_t) :: data class(eio_t), allocatable :: eio integer :: i_prc, iostat type(string_t) :: sample write (u, "(A)") "* Test output: eio_raw_2" write (u, "(A)") "* Purpose: generate and read/write an event" write (u, "(A)") "* with multiple weights" write (u, "(A)") call model%init_test () write (u, "(A)") "* Initialize test process" allocate (process) allocate (process_instance) call prepare_test_process (process, process_instance, model, & run_id = var_str ("run_test")) call process_instance%setup_event_data () call data%init (n_proc = 1, n_alt = 2) call var_list%append_log (var_str ("?unweighted"), .false., & intrinsic = .true.) call var_list%append_string (var_str ("$sample_normalization"), & var_str ("auto"), intrinsic = .true.) call var_list%append_real (var_str ("safety_factor"), & 1._default, intrinsic = .true.) allocate (event) call event%basic_init (var_list, n_alt = 2) call event%connect (process_instance, process%get_model_ptr ()) write (u, "(A)") write (u, "(A)") "* Generate and write an event" write (u, "(A)") sample = "eio_raw_2" allocate (eio_raw_t :: eio) call eio%init_out (sample, data) call event%generate (1, [0._default, 0._default]) call event%increment_index () call event%evaluate_expressions () call event%set (sqme_alt = [2._default, 3._default]) call event%set (weight_alt = & [2 * event%get_weight_ref (), 3 * event%get_weight_ref ()]) call event%store_alt_values () call event%check () call event%write (u) write (u, "(A)") call eio%output (event, i_prc = 42) call eio%write (u) call eio%final () call event%final () deallocate (event) call process_instance%final () deallocate (process_instance) write (u, "(A)") write (u, "(A)") "* Re-read the event" write (u, "(A)") call eio%init_in (sample, data) allocate (process_instance) call process_instance%init (process) call process_instance%setup_event_data () allocate (event) call event%basic_init (var_list, n_alt = 2) call event%connect (process_instance, process%get_model_ptr ()) call eio%input_i_prc (i_prc, iostat) if (iostat /= 0) write (u, "(A,I0)") "I/O error (i_prc):", iostat call eio%input_event (event, iostat) if (iostat /= 0) write (u, "(A,I0)") "I/O error (event):", iostat call eio%write (u) write (u, "(A)") write (u, "(1x,A,I0)") "i_prc = ", i_prc write (u, "(A)") call event%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call eio%final () deallocate (eio) call event%final () deallocate (event) call cleanup_test_process (process, process_instance) deallocate (process_instance) deallocate (process) call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: eio_raw_2" end subroutine eio_raw_2 @ %def eio_raw_2 @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Dispatch} An event transform is responsible for dressing a partonic event. Since event transforms are not mutually exclusive but are concatenated, we provide individual dispatchers for each of them. Due to the gfortran 7/8/9 bug that leads to segmentation violation if polymorphic user-defined derived types are allocated in routines within submodules, this module remains without submodule until we can switch to gfortran v10 or newer. <<[[dispatch_transforms.f90]]>>= <> module dispatch_transforms <> <> use process use variables use system_defs, only: LF use system_dependencies, only: LHAPDF6_AVAILABLE use sf_lhapdf, only: lhapdf_initialize use pdf, only: pdf_data_t use diagnostics use models use os_interface use beam_structures use resonances, only: resonance_history_set_t use instances, only: process_instance_t, process_instance_hook_t use event_base, only: event_callback_t, event_callback_nop_t use hepmc_interface, only: HEPMC3_MODE_HEPMC2, HEPMC3_MODE_HEPMC3 use hepmc_interface, only: HEPMC3_MODE_ROOT, HEPMC3_MODE_ROOTTREE use hepmc_interface, only: HEPMC3_MODE_HEPEVT use eio_base use eio_raw use eio_checkpoints use eio_callback use eio_lhef use eio_hepmc use eio_lcio use eio_stdhep use eio_ascii use eio_weights use eio_dump use event_transforms use resonance_insertion use isr_epa_handler use decays use shower_base use shower_core use shower use shower_pythia6 use shower_pythia8 use hadrons use mlm_matching use powheg_matching use ckkw_matching use tauola_interface !NODEP! use evt_nlo <> <> contains <> end module dispatch_transforms @ %def dispatch_transforms @ <>= public :: dispatch_evt_nlo <>= subroutine dispatch_evt_nlo (evt, keep_failed_events) class(evt_t), intent(out), pointer :: evt logical, intent(in) :: keep_failed_events call msg_message ("Simulate: activating fixed-order NLO events") allocate (evt_nlo_t :: evt) evt%only_weighted_events = .true. select type (evt) type is (evt_nlo_t) evt%i_evaluation = 0 evt%keep_failed_events = keep_failed_events end select end subroutine dispatch_evt_nlo @ %def dispatch_evt_nlo @ <>= public :: dispatch_evt_resonance <>= subroutine dispatch_evt_resonance (evt, var_list, res_history_set, libname) class(evt_t), intent(out), pointer :: evt type(var_list_t), intent(in) :: var_list type(resonance_history_set_t), dimension(:), intent(in) :: res_history_set type(string_t), intent(in) :: libname logical :: resonance_history resonance_history = var_list%get_lval (var_str ("?resonance_history")) if (resonance_history) then allocate (evt_resonance_t :: evt) call msg_message ("Simulate: activating resonance insertion") select type (evt) type is (evt_resonance_t) call evt%set_resonance_data (res_history_set) call evt%set_library (libname) end select else evt => null () end if end subroutine dispatch_evt_resonance @ %def dispatch_evt_resonance @ Initialize the ISR/EPA handler, depending on active settings. The activation is independent for both handlers, since only one may be needed at a time. However, if both handlers are active, the current implementation requires the handler modes of ISR and EPA to coincide. <>= public :: dispatch_evt_isr_epa_handler <>= subroutine dispatch_evt_isr_epa_handler (evt, var_list) class(evt_t), intent(out), pointer :: evt type(var_list_t), intent(in) :: var_list logical :: isr_recoil logical :: epa_recoil logical :: isr_handler_active logical :: epa_handler_active type(string_t) :: isr_handler_mode type(string_t) :: epa_handler_mode logical :: isr_keep_mass real(default) :: sqrts real(default) :: isr_q_max real(default) :: epa_q_max real(default) :: isr_mass real(default) :: epa_mass isr_handler_active = var_list%get_lval (var_str ("?isr_handler")) if (isr_handler_active) then call msg_message ("Simulate: activating ISR handler") isr_recoil = & var_list%get_lval (var_str ("?isr_recoil")) isr_handler_mode = & var_list%get_sval (var_str ("$isr_handler_mode")) isr_keep_mass = & var_list%get_lval (var_str ("?isr_handler_keep_mass")) if (isr_recoil) then call msg_fatal ("Simulate: ISR handler is incompatible & &with ?isr_recoil=true") end if end if epa_handler_active = var_list%get_lval (var_str ("?epa_handler")) if (epa_handler_active) then call msg_message ("Simulate: activating EPA handler") epa_recoil = var_list%get_lval (var_str ("?epa_recoil")) epa_handler_mode = var_list%get_sval (var_str ("$epa_handler_mode")) if (epa_recoil) then call msg_fatal ("Simulate: EPA handler is incompatible & &with ?epa_recoil=true") end if end if if (isr_handler_active .and. epa_handler_active) then if (isr_handler_mode /= epa_handler_mode) then call msg_fatal ("Simulate: ISR/EPA handler: modes must coincide") end if end if if (isr_handler_active .or. epa_handler_active) then allocate (evt_isr_epa_t :: evt) select type (evt) type is (evt_isr_epa_t) if (isr_handler_active) then call evt%set_mode_string (isr_handler_mode) else call evt%set_mode_string (epa_handler_mode) end if sqrts = var_list%get_rval (var_str ("sqrts")) if (isr_handler_active) then isr_q_max = var_list%get_rval (var_str ("isr_q_max")) isr_mass = var_list%get_rval (var_str ("isr_mass")) call evt%set_data_isr (sqrts, isr_q_max, isr_mass, isr_keep_mass) end if if (epa_handler_active) then epa_q_max = var_list%get_rval (var_str ("epa_q_max")) epa_mass = var_list%get_rval (var_str ("epa_mass")) call evt%set_data_epa (sqrts, epa_q_max, epa_mass) end if call msg_message ("Simulate: ISR/EPA handler mode: " & // char (evt%get_mode_string ())) end select else evt => null () end if end subroutine dispatch_evt_isr_epa_handler @ %def dispatch_evt_isr_epa_handler @ <>= public :: dispatch_evt_decay <>= subroutine dispatch_evt_decay (evt, var_list) class(evt_t), intent(out), pointer :: evt type(var_list_t), intent(in), target :: var_list logical :: allow_decays allow_decays = var_list%get_lval (var_str ("?allow_decays")) if (allow_decays) then allocate (evt_decay_t :: evt) call msg_message ("Simulate: activating decays") select type (evt) type is (evt_decay_t) call evt%set_var_list (var_list) end select else evt => null () end if end subroutine dispatch_evt_decay @ %def dispatch_evt_decay @ <>= public :: dispatch_evt_shower <>= subroutine dispatch_evt_shower (evt, var_list, model, fallback_model, & os_data, beam_structure, process) class(evt_t), intent(out), pointer :: evt type(var_list_t), intent(in) :: var_list type(model_t), pointer, intent(in) :: model, fallback_model type(os_data_t), intent(in) :: os_data type(beam_structure_t), intent(in) :: beam_structure type(process_t), intent(in), optional :: process type(string_t) :: lhapdf_file, lhapdf_dir, process_name integer :: lhapdf_member type(shower_settings_t) :: settings type(taudec_settings_t) :: taudec_settings call msg_message ("Simulate: activating parton shower") allocate (evt_shower_t :: evt) call settings%init (var_list) if (associated (model)) then call taudec_settings%init (var_list, model) else call taudec_settings%init (var_list, fallback_model) end if if (present (process)) then process_name = process%get_id () else process_name = 'dispatch_testing' end if select type (evt) type is (evt_shower_t) call evt%init (fallback_model, os_data) lhapdf_member = & var_list%get_ival (var_str ("lhapdf_member")) if (LHAPDF6_AVAILABLE) then lhapdf_dir = & var_list%get_sval (var_str ("$lhapdf_dir")) lhapdf_file = & var_list%get_sval (var_str ("$lhapdf_file")) call lhapdf_initialize & (1, lhapdf_dir, lhapdf_file, lhapdf_member, evt%pdf_data%pdf) end if if (present (process)) call evt%pdf_data%setup ("Shower", & beam_structure, lhapdf_member, process%get_pdf_set ()) select case (settings%method) case (PS_WHIZARD) allocate (shower_t :: evt%shower) case (PS_PYTHIA6) allocate (shower_pythia6_t :: evt%shower) case (PS_PYTHIA8) allocate (shower_pythia8_t :: evt%shower) case default call msg_fatal ('Shower: Method ' // & char (var_list%get_sval (var_str ("$shower_method"))) // & 'not implemented!') end select call evt%shower%init (settings, taudec_settings, evt%pdf_data, os_data) call dispatch_matching (evt, settings, var_list, process_name, evt%pdf_data) class default call dispatch_matching (evt, settings, var_list, process_name) end select end subroutine dispatch_evt_shower @ %def dispatch_evt_shower @ <>= public :: dispatch_evt_shower_hook <>= subroutine dispatch_evt_shower_hook (hook, var_list, process_instance, beam_structure, pdf_set) class(process_instance_hook_t), pointer, intent(out) :: hook type(var_list_t), intent(in) :: var_list class(process_instance_t), intent(in), target :: process_instance type(beam_structure_t), intent(in) :: beam_structure integer, intent(in) :: pdf_set type(pdf_data_t) :: pdf_data type(string_t) :: lhapdf_file, lhapdf_dir integer :: lhapdf_member if (var_list%get_lval (var_str ('?powheg_matching'))) then call msg_message ("Integration hook: add POWHEG hook") allocate (powheg_matching_hook_t :: hook) select type (hook) type is (powheg_matching_hook_t) lhapdf_member = var_list%get_ival (var_str ("lhapdf_member")) if (LHAPDF6_AVAILABLE) then lhapdf_dir = var_list%get_sval (var_str ("$lhapdf_dir")) lhapdf_file = var_list%get_sval (var_str ("$lhapdf_file")) call lhapdf_initialize (1, lhapdf_dir, lhapdf_file, lhapdf_member, pdf_data%pdf) end if call pdf_data%setup ("Shower", beam_structure, lhapdf_member, pdf_set) call hook%init (var_list, process_instance, pdf_data) end select else hook => null () end if end subroutine dispatch_evt_shower_hook @ %def dispatch_evt_shower_hook @ <>= public :: dispatch_matching <>= subroutine dispatch_matching (evt, settings, var_list, process_name, pdf_data) class(evt_t), intent(inout) :: evt type(shower_settings_t), intent(in) :: settings type(var_list_t), intent(in) :: var_list type(string_t), intent(in) :: process_name type(pdf_data_t), intent(in), optional :: pdf_data select type (evt) type is (evt_shower_t) if (settings%mlm_matching .and. settings%ckkw_matching) then call msg_fatal ("Both MLM and CKKW matching activated," // & LF // " aborting simulation") end if if (settings%powheg_matching) then call msg_message ("Simulate: applying POWHEG matching") allocate (powheg_matching_t :: evt%matching) end if if (settings%mlm_matching) then call msg_message ("Simulate: applying MLM matching") allocate (mlm_matching_t :: evt%matching) end if if (settings%ckkw_matching) then call msg_warning ("Simulate: CKKW(-L) matching not yet supported") allocate (ckkw_matching_t :: evt%matching) end if if (allocated (evt%matching)) then call evt%matching%init (var_list, process_name) if (present(pdf_data)) then select type (matching => evt%matching) type is (powheg_matching_t) matching%process_deps%pdf_data = pdf_data end select end if end if end select end subroutine dispatch_matching @ %def dispatch_matching @ <>= public :: dispatch_evt_hadrons <>= subroutine dispatch_evt_hadrons (evt, var_list, fallback_model) class(evt_t), intent(out), pointer :: evt type(var_list_t), intent(in) :: var_list type(model_t), pointer, intent(in) :: fallback_model type(shower_settings_t) :: shower_settings type(hadron_settings_t) :: hadron_settings allocate (evt_hadrons_t :: evt) call msg_message ("Simulate: activating hadronization") call shower_settings%init (var_list) call hadron_settings%init (var_list) select type (evt) type is (evt_hadrons_t) call evt%init (fallback_model) select case (hadron_settings%method) case (HADRONS_WHIZARD) allocate (hadrons_hadrons_t :: evt%hadrons) case (HADRONS_PYTHIA6) allocate (hadrons_pythia6_t :: evt%hadrons) case (HADRONS_PYTHIA8) allocate (hadrons_pythia8_t :: evt%hadrons) case default call msg_fatal ('Hadronization: Method ' // & char (var_list%get_sval (var_str ("hadronization_method"))) // & 'not implemented!') end select call evt%hadrons%init & (shower_settings, hadron_settings, fallback_model) end select end subroutine dispatch_evt_hadrons @ %def dispatch_evt_hadrons @ We cannot put this in the [[events]] subdir due to [[eio_raw_t]], which is defined here. <>= public :: dispatch_eio <>= subroutine dispatch_eio (eio, method, var_list, fallback_model, & event_callback) class(eio_t), allocatable, intent(inout) :: eio type(string_t), intent(in) :: method type(var_list_t), intent(in) :: var_list type(model_t), target, intent(in) :: fallback_model class(event_callback_t), allocatable, intent(in) :: event_callback logical :: check, keep_beams, keep_remnants, recover_beams logical :: use_alphas_from_file, use_scale_from_file logical :: fixed_order_nlo_events logical :: write_sqme_prc, write_sqme_ref, write_sqme_alt logical :: output_cross_section, ensure_order type(string_t) :: lhef_version, lhef_extension, raw_version type(string_t) :: extension_default, debug_extension, dump_extension, & extension_hepmc, & extension_lha, extension_hepevt, extension_ascii_short, & extension_ascii_long, extension_athena, extension_mokka, & extension_stdhep, extension_stdhep_up, extension_stdhep_ev4, & extension_raw, extension_hepevt_verb, extension_lha_verb, & extension_lcio integer :: checkpoint integer :: lcio_run_id, hepmc3_mode logical :: show_process, show_transforms, show_decay, verbose, pacified logical :: dump_weights, dump_compressed, dump_summary, dump_screen logical :: proc_as_run_id, hepmc3_write_flows keep_beams = & var_list%get_lval (var_str ("?keep_beams")) keep_remnants = & var_list%get_lval (var_str ("?keep_remnants")) ensure_order = & var_list%get_lval (var_str ("?hepevt_ensure_order")) recover_beams = & var_list%get_lval (var_str ("?recover_beams")) use_alphas_from_file = & var_list%get_lval (var_str ("?use_alphas_from_file")) use_scale_from_file = & var_list%get_lval (var_str ("?use_scale_from_file")) fixed_order_nlo_events = & var_list%get_lval (var_str ("?fixed_order_nlo_events")) select case (char (method)) case ("raw") allocate (eio_raw_t :: eio) select type (eio) type is (eio_raw_t) check = & var_list%get_lval (var_str ("?check_event_file")) raw_version = & var_list%get_sval (var_str ("$event_file_version")) extension_raw = & var_list%get_sval (var_str ("$extension_raw")) call eio%set_parameters (check, use_alphas_from_file, & use_scale_from_file, fixed_order_nlo_events, & raw_version, extension_raw) end select case ("checkpoint") allocate (eio_checkpoints_t :: eio) select type (eio) type is (eio_checkpoints_t) checkpoint = & var_list%get_ival (var_str ("checkpoint")) pacified = & var_list%get_lval (var_str ("?pacify")) call eio%set_parameters (checkpoint, blank = pacified) end select case ("callback") allocate (eio_callback_t :: eio) select type (eio) type is (eio_callback_t) checkpoint = & var_list%get_ival (var_str ("event_callback_interval")) if (allocated (event_callback)) then call eio%set_parameters (event_callback, checkpoint) else call eio%set_parameters (event_callback_nop_t (), 0) end if end select case ("lhef") allocate (eio_lhef_t :: eio) select type (eio) type is (eio_lhef_t) lhef_version = & var_list%get_sval (var_str ("$lhef_version")) lhef_extension = & var_list%get_sval (var_str ("$lhef_extension")) write_sqme_prc = & var_list%get_lval (var_str ("?lhef_write_sqme_prc")) write_sqme_ref = & var_list%get_lval (var_str ("?lhef_write_sqme_ref")) write_sqme_alt = & var_list%get_lval (var_str ("?lhef_write_sqme_alt")) call eio%set_parameters ( & keep_beams, keep_remnants, recover_beams, & use_alphas_from_file, use_scale_from_file, & char (lhef_version), lhef_extension, & write_sqme_ref, write_sqme_prc, write_sqme_alt) end select case ("hepmc") allocate (eio_hepmc_t :: eio) select type (eio) type is (eio_hepmc_t) output_cross_section = & var_list%get_lval (var_str ("?hepmc_output_cross_section")) extension_hepmc = & var_list%get_sval (var_str ("$extension_hepmc")) hepmc3_write_flows = & var_list%get_lval (var_str ("?hepmc3_write_flows")) select case (char (var_list%get_sval (var_str ("$hepmc3_mode")))) case ("HepMC2") hepmc3_mode = HEPMC3_MODE_HEPMC2 case ("HepMC3") hepmc3_mode = HEPMC3_MODE_HEPMC3 case ("Root") hepmc3_mode = HEPMC3_MODE_ROOT if (extension_hepmc /= "root") then call msg_message ("Events: HepMC3 Root mode, using " // & "event sample extension 'root'") extension_hepmc = "root" end if case ("RootTree") hepmc3_mode = HEPMC3_MODE_ROOTTREE if (extension_hepmc /= "root") then call msg_message ("Events: HepMC3 RootTree mode, using " // & "event sample extension 'root'") extension_hepmc = "root" end if case ("HepEVT") hepmc3_mode = HEPMC3_MODE_HEPEVT case default call msg_fatal ("Only supported HepMC3 modes are: 'HepMC2', " // & "'HepMC3', 'HepEVT', 'Root', and 'RootTree'.") end select call eio%set_parameters (recover_beams, & use_alphas_from_file, use_scale_from_file, & extension = extension_hepmc, & output_cross_section = output_cross_section, & hepmc3_mode = hepmc3_mode, & hepmc3_write_flows = hepmc3_write_flows) end select case ("lcio") allocate (eio_lcio_t :: eio) select type (eio) type is (eio_lcio_t) extension_lcio = & var_list%get_sval (var_str ("$extension_lcio")) proc_as_run_id = & var_list%get_lval (var_str ("?proc_as_run_id")) lcio_run_id = & var_list%get_ival (var_str ("lcio_run_id")) call eio%set_parameters (recover_beams, & use_alphas_from_file, use_scale_from_file, & extension_lcio, proc_as_run_id = proc_as_run_id, & lcio_run_id = lcio_run_id) end select case ("stdhep") allocate (eio_stdhep_hepevt_t :: eio) select type (eio) type is (eio_stdhep_hepevt_t) extension_stdhep = & var_list%get_sval (var_str ("$extension_stdhep")) call eio%set_parameters & (keep_beams, keep_remnants, ensure_order, recover_beams, & use_alphas_from_file, use_scale_from_file, extension_stdhep) end select case ("stdhep_up") allocate (eio_stdhep_hepeup_t :: eio) select type (eio) type is (eio_stdhep_hepeup_t) extension_stdhep_up = & var_list%get_sval (var_str ("$extension_stdhep_up")) call eio%set_parameters (keep_beams, keep_remnants, ensure_order, & recover_beams, use_alphas_from_file, & use_scale_from_file, extension_stdhep_up) end select case ("stdhep_ev4") allocate (eio_stdhep_hepev4_t :: eio) select type (eio) type is (eio_stdhep_hepev4_t) extension_stdhep_ev4 = & var_list%get_sval (var_str ("$extension_stdhep_ev4")) call eio%set_parameters & (keep_beams, keep_remnants, ensure_order, recover_beams, & use_alphas_from_file, use_scale_from_file, extension_stdhep_ev4) end select case ("ascii") allocate (eio_ascii_ascii_t :: eio) select type (eio) type is (eio_ascii_ascii_t) extension_default = & var_list%get_sval (var_str ("$extension_default")) call eio%set_parameters & (keep_beams, keep_remnants, ensure_order, extension_default) end select case ("athena") allocate (eio_ascii_athena_t :: eio) select type (eio) type is (eio_ascii_athena_t) extension_athena = & var_list%get_sval (var_str ("$extension_athena")) call eio%set_parameters & (keep_beams, keep_remnants, ensure_order, extension_athena) end select case ("debug") allocate (eio_ascii_debug_t :: eio) select type (eio) type is (eio_ascii_debug_t) debug_extension = & var_list%get_sval (var_str ("$debug_extension")) show_process = & var_list%get_lval (var_str ("?debug_process")) show_transforms = & var_list%get_lval (var_str ("?debug_transforms")) show_decay = & var_list%get_lval (var_str ("?debug_decay")) verbose = & var_list%get_lval (var_str ("?debug_verbose")) call eio%set_parameters ( & extension = debug_extension, & show_process = show_process, & show_transforms = show_transforms, & show_decay = show_decay, & verbose = verbose) end select case ("dump") allocate (eio_dump_t :: eio) select type (eio) type is (eio_dump_t) dump_extension = & var_list%get_sval (var_str ("$dump_extension")) pacified = & var_list%get_lval (var_str ("?pacify")) dump_weights = & var_list%get_lval (var_str ("?dump_weights")) dump_compressed = & var_list%get_lval (var_str ("?dump_compressed")) dump_summary = & var_list%get_lval (var_str ("?dump_summary")) dump_screen = & var_list%get_lval (var_str ("?dump_screen")) call eio%set_parameters ( & extension = dump_extension, & pacify = pacified, & weights = dump_weights, & compressed = dump_compressed, & summary = dump_summary, & screen = dump_screen) end select case ("hepevt") allocate (eio_ascii_hepevt_t :: eio) select type (eio) type is (eio_ascii_hepevt_t) extension_hepevt = & var_list%get_sval (var_str ("$extension_hepevt")) call eio%set_parameters & (keep_beams, keep_remnants, ensure_order, extension_hepevt) end select case ("hepevt_verb") allocate (eio_ascii_hepevt_verb_t :: eio) select type (eio) type is (eio_ascii_hepevt_verb_t) extension_hepevt_verb = & var_list%get_sval (var_str ("$extension_hepevt_verb")) call eio%set_parameters & (keep_beams, keep_remnants, ensure_order, extension_hepevt_verb) end select case ("lha") allocate (eio_ascii_lha_t :: eio) select type (eio) type is (eio_ascii_lha_t) extension_lha = & var_list%get_sval (var_str ("$extension_lha")) call eio%set_parameters & (keep_beams, keep_remnants, ensure_order, extension_lha) end select case ("lha_verb") allocate (eio_ascii_lha_verb_t :: eio) select type (eio) type is (eio_ascii_lha_verb_t) extension_lha_verb = var_list%get_sval ( & var_str ("$extension_lha_verb")) call eio%set_parameters & (keep_beams, keep_remnants, ensure_order, extension_lha_verb) end select case ("long") allocate (eio_ascii_long_t :: eio) select type (eio) type is (eio_ascii_long_t) extension_ascii_long = & var_list%get_sval (var_str ("$extension_ascii_long")) call eio%set_parameters & (keep_beams, keep_remnants, ensure_order, extension_ascii_long) end select case ("mokka") allocate (eio_ascii_mokka_t :: eio) select type (eio) type is (eio_ascii_mokka_t) extension_mokka = & var_list%get_sval (var_str ("$extension_mokka")) call eio%set_parameters & (keep_beams, keep_remnants, ensure_order, extension_mokka) end select case ("short") allocate (eio_ascii_short_t :: eio) select type (eio) type is (eio_ascii_short_t) extension_ascii_short = & var_list%get_sval (var_str ("$extension_ascii_short")) call eio%set_parameters & (keep_beams, keep_remnants, ensure_order, extension_ascii_short) end select case ("weight_stream") allocate (eio_weights_t :: eio) select type (eio) type is (eio_weights_t) pacified = & var_list%get_lval (var_str ("?pacify")) call eio%set_parameters (pacify = pacified) end select case default call msg_fatal ("Event I/O method '" // char (method) & // "' not implemented") end select call eio%set_fallback_model (fallback_model) end subroutine dispatch_eio @ %def dispatch_eio @ @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[dispatch_transforms_ut.f90]]>>= <> module dispatch_transforms_ut use unit_tests use dispatch_transforms_uti <> <> contains <> end module dispatch_transforms_ut @ %def dispatch_transforms_ut @ <<[[dispatch_transforms_uti.f90]]>>= <> module dispatch_transforms_uti <> <> use format_utils, only: write_separator use variables use event_base, only: event_callback_t use models, only: model_t, model_list_t use models, only: syntax_model_file_init, syntax_model_file_final use resonances, only: resonance_history_set_t use beam_structures, only: beam_structure_t use eio_base, only: eio_t use os_interface, only: os_data_t use event_transforms, only: evt_t use dispatch_transforms <> <> contains <> end module dispatch_transforms_uti @ %def dispatch_transforms_uti @ API: driver for the unit tests below. <>= public ::dispatch_transforms_test <>= subroutine dispatch_transforms_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine dispatch_transforms_test @ %def dispatch_transforms_test @ \subsubsection{Event I/O} <>= call test (dispatch_transforms_1, "dispatch_transforms_1", & "event I/O", & u, results) <>= public :: dispatch_transforms_1 <>= subroutine dispatch_transforms_1 (u) integer, intent(in) :: u type(var_list_t) :: var_list type(model_list_t) :: model_list type(model_t), pointer :: model type(os_data_t) :: os_data class(event_callback_t), allocatable :: event_callback class(eio_t), allocatable :: eio write (u, "(A)") "* Test output: dispatch_transforms_1" write (u, "(A)") "* Purpose: allocate an event I/O (eio) stream" write (u, "(A)") call var_list%init_defaults (0) call os_data%init () call syntax_model_file_init () call model_list%read_model (var_str ("SM_hadrons"), & var_str ("SM_hadrons.mdl"), os_data, model) write (u, "(A)") "* Allocate as raw" write (u, "(A)") call dispatch_eio (eio, var_str ("raw"), var_list, & model, event_callback) call eio%write (u) call eio%final () deallocate (eio) write (u, "(A)") write (u, "(A)") "* Allocate as checkpoints:" write (u, "(A)") call dispatch_eio (eio, var_str ("checkpoint"), var_list, & model, event_callback) call eio%write (u) call eio%final () deallocate (eio) write (u, "(A)") write (u, "(A)") "* Allocate as LHEF:" write (u, "(A)") call var_list%set_string (var_str ("$lhef_extension"), & var_str ("lhe_custom"), is_known = .true.) call dispatch_eio (eio, var_str ("lhef"), var_list, & model, event_callback) call eio%write (u) call eio%final () deallocate (eio) write (u, "(A)") write (u, "(A)") "* Allocate as HepMC:" write (u, "(A)") call dispatch_eio (eio, var_str ("hepmc"), var_list, & model, event_callback) call eio%write (u) call eio%final () deallocate (eio) write (u, "(A)") write (u, "(A)") "* Allocate as weight_stream" write (u, "(A)") call dispatch_eio (eio, var_str ("weight_stream"), var_list, & model, event_callback) call eio%write (u) call eio%final () deallocate (eio) write (u, "(A)") write (u, "(A)") "* Allocate as debug format" write (u, "(A)") call var_list%set_log (var_str ("?debug_verbose"), & .false., is_known = .true.) call dispatch_eio (eio, var_str ("debug"), var_list, & model, event_callback) call eio%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call eio%final () call var_list%final () call syntax_model_file_final () write (u, "(A)") write (u, "(A)") "* Test output end: dispatch_transforms_1" end subroutine dispatch_transforms_1 @ %def dispatch_transforms_1 @ \subsubsection{Event transforms} This test dispatches [[evt]] (event transform) objects. <>= call test (dispatch_transforms_2, "dispatch_transforms_2", & "event transforms", & u, results) <>= public :: dispatch_transforms_2 <>= subroutine dispatch_transforms_2 (u) integer, intent(in) :: u type(var_list_t), target :: var_list type(model_list_t) :: model_list type(model_t), pointer :: model type(os_data_t) :: os_data type(resonance_history_set_t), dimension(1) :: res_history_set type(beam_structure_t) :: beam_structure class(evt_t), pointer :: evt write (u, "(A)") "* Test output: dispatch_transforms_2" write (u, "(A)") "* Purpose: configure event transform" write (u, "(A)") call syntax_model_file_init () call var_list%init_defaults (0) call os_data%init () call model_list%read_model (var_str ("SM_hadrons"), & var_str ("SM_hadrons.mdl"), os_data, model) write (u, "(A)") "* Resonance insertion" write (u, "(A)") call var_list%set_log (var_str ("?resonance_history"), .true., & is_known = .true.) call dispatch_evt_resonance (evt, var_list, & res_history_set, & var_str ("foo_R")) call evt%write (u, verbose = .true., more_verbose = .true.) call evt%final () deallocate (evt) write (u, "(A)") write (u, "(A)") "* ISR handler" write (u, "(A)") call var_list%set_log (var_str ("?isr_handler"), .true., & is_known = .true.) call var_list%set_log (var_str ("?epa_handler"), .false., & is_known = .true.) call var_list%set_string (var_str ("$isr_handler_mode"), & var_str ("recoil"), & is_known = .true.) call var_list%set_real (var_str ("sqrts"), 100._default, & is_known = .true.) call var_list%set_real (var_str ("isr_mass"), 511.e-6_default, & is_known = .true.) call dispatch_evt_isr_epa_handler (evt, var_list) call evt%write (u, verbose = .true., more_verbose = .true.) call evt%final () deallocate (evt) write (u, "(A)") write (u, "(A)") "* EPA handler" write (u, "(A)") call var_list%set_log (var_str ("?isr_handler"), .false., & is_known = .true.) call var_list%set_log (var_str ("?epa_handler"), .true., & is_known = .true.) call var_list%set_string (var_str ("$epa_handler_mode"), & var_str ("recoil"), & is_known = .true.) call var_list%set_real (var_str ("sqrts"), 100._default, & is_known = .true.) call var_list%set_real (var_str ("epa_mass"), 511.e-6_default, & is_known = .true.) call dispatch_evt_isr_epa_handler (evt, var_list) call evt%write (u, verbose = .true., more_verbose = .true.) call evt%final () deallocate (evt) write (u, "(A)") write (u, "(A)") "* Partonic decays" write (u, "(A)") call dispatch_evt_decay (evt, var_list) call evt%write (u, verbose = .true., more_verbose = .true.) call evt%final () deallocate (evt) write (u, "(A)") write (u, "(A)") "* Shower" write (u, "(A)") call var_list%set_log (var_str ("?allow_shower"), .true., & is_known = .true.) call var_list%set_string (var_str ("$shower_method"), & var_str ("WHIZARD"), is_known = .true.) call dispatch_evt_shower (evt, var_list, model, & model, os_data, beam_structure) call evt%write (u) call write_separator (u, 2) call evt%final () deallocate (evt) call var_list%final () call syntax_model_file_final () write (u, "(A)") write (u, "(A)") "* Test output end: dispatch_transforms_2" end subroutine dispatch_transforms_2 @ %def dispatch_transforms_2 Index: trunk/src/process_integration/process_integration.nw =================================================================== --- trunk/src/process_integration/process_integration.nw (revision 8817) +++ trunk/src/process_integration/process_integration.nw (revision 8818) @@ -1,23616 +1,23889 @@ % -*- ess-noweb-default-code-mode: f90-mode; noweb-default-code-mode: f90-mode; -*- % WHIZARD code as NOWEB source: integration and process objects and such %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \chapter{Integration and Process Objects} \includemodulegraph{process_integration} This is the central part of the \whizard\ package. It provides the functionality for evaluating structure functions, kinematics and matrix elements, integration and event generation. It combines the various parts that deal with those tasks individually and organizes the data transfer between them. \begin{description} \item[subevt\_expr] This enables process observables as (abstract) expressions, to be evaluated for each process call. \item[parton\_states] A [[parton_state_t]] object represents an elementary partonic interaction. There are two versions: one for the isolated elementary process, one for the elementary process convoluted with the structure-function chain. The parton state is an effective state. It needs not coincide with the seed-kinematics state which is used in evaluating phase space. \item[process] Here, all pieces are combined for the purpose of evaluating the elementary processes. The whole algorithm is coded in terms of abstract data types as defined in the appropriate modules: [[prc_core]] for matrix-element evaluation, [[prc_core_def]] for the associated configuration and driver, [[sf_base]] for beams and structure-functions, [[phs_base]] for phase space, and [[mci_base]] for integration and event generation. \item[process\_config] \item[process\_counter] Very simple object for statistics \item[process\_mci] \item[pcm] \item[kinematics] \item[instances] While the above modules set up all static information, the instances have the changing event data. There are term and process instances but no component instances. \item[process\_stacks] Process stacks collect process objects. \end{description} We combine here hard interactions, phase space, and (for scatterings) structure functions and interfaces them to the integration module. The process object implements the combination of a fixed beam and structure-function setup with a number of elementary processes. The latter are called process components. The process object represents an entity which is supposedly observable. It should be meaningful to talk about the cross section of a process. The individual components of a process are, technically, processes themselves, but they may have unphysical cross sections which have to be added for a physical result. Process components may be exclusive tree-level elementary processes, dipole subtraction term, loop corrections, etc. The beam and structure function setup is common to all process components. Thus, there is only one instance of this part. The process may be a scattering process or a decay process. In the latter case, there are no structure functions, and the beam setup consists of a single particle. Otherwise, the two classes are treated on the same footing. Once a sampling point has been chosen, a process determines a set of partons with a correlated density matrix of quantum numbers. In general, each sampling point will generate, for each process component, one or more distinct parton configurations. This is the [[computed]] state. The computed state is the subject of the multi-channel integration algorithm. For NLO computations, it is necessary to project the computed states onto another set of parton configurations (e.g., by recombining certain pairs). This is the [[observed]] state. When computing partonic observables, the information is taken from the observed state. For the purpose of event generation, we will later select one parton configuration from the observed state and collapse the correlated quantum state. This configuration is then dressed by applying parton shower, decays and hadronization. The decay chain, in particular, combines a scattering process with possible subsequent decay processes on the parton level, which are full-fledged process objects themselves. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Process observables} We define an abstract [[subevt_expr_t]] object as an extension of the [[subevt_t]] type. The object contains a local variable list, variable instances (as targets for pointers in the variable list), and evaluation trees. The evaluation trees reference both the variables and the [[subevt]]. There are two instances of the abstract type: one for process instances, one for physical events. Both have a common logical expression [[selection]] which determines whether the object passes user-defined cuts. The intention is that we fill the [[subevt_t]] base object and compute the variables once we have evaluated a kinematical phase space point (or a complete event). We then evaluate the expressions and can use the results in further calculations. The [[process_expr_t]] extension contains furthermore scale and weight expressions. The [[event_expr_t]] extension contains a reweighting-factor expression and a logical expression for event analysis. In practice, we will link the variable list of the [[event_obs]] object to the variable list of the currently active [[process_obs]] object, such that the process variables are available to both objects. Event variables are meaningful only for physical events. Note that there are unit tests, but they are deferred to the [[expr_tests]] module. <<[[subevt_expr.f90]]>>= <> module subevt_expr <> <> use lorentz use subevents use variables use flavors use quantum_numbers use interactions use particles use expr_base <> <> <> <> interface <> end interface end module subevt_expr @ %def subevt_expr @ <<[[subevt_expr_sub.f90]]>>= <> submodule (subevt_expr) subevt_expr_s use constants, only: zero, one use io_units use format_utils, only: write_separator use diagnostics implicit none contains <> end submodule subevt_expr_s @ %def subevt_expr_s @ \subsection{Abstract base type} <>= type, extends (subevt_t), abstract :: subevt_expr_t logical :: subevt_filled = .false. type(var_list_t) :: var_list real(default) :: sqrts_hat = 0 integer :: n_in = 0 integer :: n_out = 0 integer :: n_tot = 0 logical :: has_selection = .false. class(expr_t), allocatable :: selection logical :: colorize_subevt = .false. contains <> end type subevt_expr_t @ %def subevt_expr_t @ Output: Base and extended version. We already have a [[write]] routine for the [[subevt_t]] parent type. <>= procedure :: base_write => subevt_expr_write <>= module subroutine subevt_expr_write (object, unit, pacified) class(subevt_expr_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: pacified end subroutine subevt_expr_write <>= module subroutine subevt_expr_write (object, unit, pacified) class(subevt_expr_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: pacified integer :: u u = given_output_unit (unit) write (u, "(1x,A)") "Local variables:" call write_separator (u) call object%var_list%write (u, follow_link=.false., & pacified = pacified) call write_separator (u) if (object%subevt_filled) then call object%subevt_t%write (u, pacified = pacified) if (object%has_selection) then call write_separator (u) write (u, "(1x,A)") "Selection expression:" call write_separator (u) call object%selection%write (u) end if else write (u, "(1x,A)") "subevt: [undefined]" end if end subroutine subevt_expr_write @ %def subevt_expr_write @ Finalizer. <>= procedure (subevt_expr_final), deferred :: final procedure :: base_final => subevt_expr_final <>= module subroutine subevt_expr_final (object) class(subevt_expr_t), intent(inout) :: object end subroutine subevt_expr_final <>= module subroutine subevt_expr_final (object) class(subevt_expr_t), intent(inout) :: object call object%var_list%final () if (object%has_selection) then call object%selection%final () end if end subroutine subevt_expr_final @ %def subevt_expr_final @ \subsection{Initialization} Initialization: define local variables and establish pointers. The common variables are [[sqrts]] (the nominal beam energy, fixed), [[sqrts_hat]] (the actual energy), [[n_in]], [[n_out]], and [[n_tot]] for the [[subevt]]. With the exception of [[sqrts]], all are implemented as pointers to subobjects. <>= procedure (subevt_expr_setup_vars), deferred :: setup_vars procedure :: base_setup_vars => subevt_expr_setup_vars <>= module subroutine subevt_expr_setup_vars (expr, sqrts) class(subevt_expr_t), intent(inout), target :: expr real(default), intent(in) :: sqrts end subroutine subevt_expr_setup_vars <>= module subroutine subevt_expr_setup_vars (expr, sqrts) class(subevt_expr_t), intent(inout), target :: expr real(default), intent(in) :: sqrts call expr%var_list%final () call expr%var_list%append_real (var_str ("sqrts"), sqrts, & locked = .true., verbose = .false., intrinsic = .true.) call expr%var_list%append_real_ptr (var_str ("sqrts_hat"), & expr%sqrts_hat, is_known = expr%subevt_filled, & locked = .true., verbose = .false., intrinsic = .true.) call expr%var_list%append_int_ptr (var_str ("n_in"), expr%n_in, & is_known = expr%subevt_filled, & locked = .true., verbose = .false., intrinsic = .true.) call expr%var_list%append_int_ptr (var_str ("n_out"), expr%n_out, & is_known = expr%subevt_filled, & locked = .true., verbose = .false., intrinsic = .true.) call expr%var_list%append_int_ptr (var_str ("n_tot"), expr%n_tot, & is_known = expr%subevt_filled, & locked = .true., verbose = .false., intrinsic = .true.) end subroutine subevt_expr_setup_vars @ %def subevt_expr_setup_vars @ Append the subevent expr (its base-type core) itself to the variable list, if it is not yet present. <>= procedure :: setup_var_self => subevt_expr_setup_var_self <>= module subroutine subevt_expr_setup_var_self (expr) class(subevt_expr_t), intent(inout), target :: expr end subroutine subevt_expr_setup_var_self <>= module subroutine subevt_expr_setup_var_self (expr) class(subevt_expr_t), intent(inout), target :: expr if (.not. expr%var_list%contains (var_str ("@evt"))) then call expr%var_list%append_subevt_ptr & (var_str ("@evt"), expr%subevt_t, & is_known = expr%subevt_filled, & locked = .true., verbose = .false., intrinsic=.true.) end if end subroutine subevt_expr_setup_var_self @ %def subevt_expr_setup_var_self @ Link a variable list to the local one. This could be done event by event, but before evaluating expressions. <>= procedure :: link_var_list => subevt_expr_link_var_list <>= module subroutine subevt_expr_link_var_list (expr, var_list) class(subevt_expr_t), intent(inout) :: expr type(var_list_t), intent(in), target :: var_list end subroutine subevt_expr_link_var_list <>= module subroutine subevt_expr_link_var_list (expr, var_list) class(subevt_expr_t), intent(inout) :: expr type(var_list_t), intent(in), target :: var_list call expr%var_list%link (var_list) end subroutine subevt_expr_link_var_list @ %def subevt_expr_link_var_list @ Compile the selection expression. If there is no expression, the build method will not allocate the expression object. <>= procedure :: setup_selection => subevt_expr_setup_selection <>= module subroutine subevt_expr_setup_selection (expr, ef_cuts) class(subevt_expr_t), intent(inout), target :: expr class(expr_factory_t), intent(in) :: ef_cuts end subroutine subevt_expr_setup_selection <>= module subroutine subevt_expr_setup_selection (expr, ef_cuts) class(subevt_expr_t), intent(inout), target :: expr class(expr_factory_t), intent(in) :: ef_cuts call ef_cuts%build (expr%selection) if (allocated (expr%selection)) then call expr%setup_var_self () call expr%selection%setup_lexpr (expr%var_list) expr%has_selection = .true. end if end subroutine subevt_expr_setup_selection @ %def subevt_expr_setup_selection @ (De)activate color storage and evaluation for the expression. The subevent particles will have color information. <>= procedure :: colorize => subevt_expr_colorize <>= module subroutine subevt_expr_colorize (expr, colorize_subevt) class(subevt_expr_t), intent(inout), target :: expr logical, intent(in) :: colorize_subevt end subroutine subevt_expr_colorize <>= module subroutine subevt_expr_colorize (expr, colorize_subevt) class(subevt_expr_t), intent(inout), target :: expr logical, intent(in) :: colorize_subevt expr%colorize_subevt = colorize_subevt end subroutine subevt_expr_colorize @ %def subevt_expr_colorize @ \subsection{Evaluation} Reset to initial state, i.e., mark the [[subevt]] as invalid. <>= procedure :: reset_contents => subevt_expr_reset_contents procedure :: base_reset_contents => subevt_expr_reset_contents <>= module subroutine subevt_expr_reset_contents (expr) class(subevt_expr_t), intent(inout) :: expr end subroutine subevt_expr_reset_contents <>= module subroutine subevt_expr_reset_contents (expr) class(subevt_expr_t), intent(inout) :: expr expr%subevt_filled = .false. end subroutine subevt_expr_reset_contents @ %def subevt_expr_reset_contents @ Evaluate the selection expression and return the result. There is also a deferred version: this should evaluate the remaining expressions if the event has passed. <>= procedure :: base_evaluate => subevt_expr_evaluate <>= module subroutine subevt_expr_evaluate (expr, passed) class(subevt_expr_t), intent(inout) :: expr logical, intent(out) :: passed end subroutine subevt_expr_evaluate <>= module subroutine subevt_expr_evaluate (expr, passed) class(subevt_expr_t), intent(inout) :: expr logical, intent(out) :: passed if (expr%has_selection) then call expr%selection%evaluate () if (expr%selection%is_known ()) then passed = expr%selection%get_log () else call msg_error ("Evaluate selection expression: result undefined") passed = .false. end if else passed = .true. end if end subroutine subevt_expr_evaluate @ %def subevt_expr_evaluate @ \subsection{Implementation for partonic events} This implementation contains the expressions that we can evaluate for the partonic process during integration. <>= public :: parton_expr_t <>= type, extends (subevt_expr_t) :: parton_expr_t integer, dimension(:), allocatable :: i_beam integer, dimension(:), allocatable :: i_in integer, dimension(:), allocatable :: i_out logical :: has_scale = .false. logical :: has_fac_scale = .false. logical :: has_ren_scale = .false. logical :: has_weight = .false. class(expr_t), allocatable :: scale class(expr_t), allocatable :: fac_scale class(expr_t), allocatable :: ren_scale class(expr_t), allocatable :: weight contains <> end type parton_expr_t @ %def parton_expr_t @ Finalizer. <>= procedure :: final => parton_expr_final <>= module subroutine parton_expr_final (object) class(parton_expr_t), intent(inout) :: object end subroutine parton_expr_final <>= module subroutine parton_expr_final (object) class(parton_expr_t), intent(inout) :: object call object%base_final () if (object%has_scale) then call object%scale%final () end if if (object%has_fac_scale) then call object%fac_scale%final () end if if (object%has_ren_scale) then call object%ren_scale%final () end if if (object%has_weight) then call object%weight%final () end if end subroutine parton_expr_final @ %def parton_expr_final @ Output: continue writing the active expressions, after the common selection expression. Note: the [[prefix]] argument is declared in the [[write]] method of the [[subevt_t]] base type. Here, it is unused. <>= procedure :: write => parton_expr_write <>= module subroutine parton_expr_write (object, unit, prefix, pacified) class(parton_expr_t), intent(in) :: object integer, intent(in), optional :: unit character(*), intent(in), optional :: prefix logical, intent(in), optional :: pacified end subroutine parton_expr_write <>= module subroutine parton_expr_write (object, unit, prefix, pacified) class(parton_expr_t), intent(in) :: object integer, intent(in), optional :: unit character(*), intent(in), optional :: prefix logical, intent(in), optional :: pacified integer :: u u = given_output_unit (unit) call object%base_write (u, pacified = pacified) if (object%subevt_filled) then if (object%has_scale) then call write_separator (u) write (u, "(1x,A)") "Scale expression:" call write_separator (u) call object%scale%write (u) end if if (object%has_fac_scale) then call write_separator (u) write (u, "(1x,A)") "Factorization scale expression:" call write_separator (u) call object%fac_scale%write (u) end if if (object%has_ren_scale) then call write_separator (u) write (u, "(1x,A)") "Renormalization scale expression:" call write_separator (u) call object%ren_scale%write (u) end if if (object%has_weight) then call write_separator (u) write (u, "(1x,A)") "Weight expression:" call write_separator (u) call object%weight%write (u) end if end if end subroutine parton_expr_write @ %def parton_expr_write @ Define variables. <>= procedure :: setup_vars => parton_expr_setup_vars <>= module subroutine parton_expr_setup_vars (expr, sqrts) class(parton_expr_t), intent(inout), target :: expr real(default), intent(in) :: sqrts end subroutine parton_expr_setup_vars <>= module subroutine parton_expr_setup_vars (expr, sqrts) class(parton_expr_t), intent(inout), target :: expr real(default), intent(in) :: sqrts call expr%base_setup_vars (sqrts) end subroutine parton_expr_setup_vars @ %def parton_expr_setup_vars @ Compile the scale expressions. If a pointer is disassociated, there is no expression. <>= procedure :: setup_scale => parton_expr_setup_scale procedure :: setup_fac_scale => parton_expr_setup_fac_scale procedure :: setup_ren_scale => parton_expr_setup_ren_scale <>= module subroutine parton_expr_setup_scale (expr, ef_scale) class(parton_expr_t), intent(inout), target :: expr class(expr_factory_t), intent(in) :: ef_scale end subroutine parton_expr_setup_scale module subroutine parton_expr_setup_fac_scale (expr, ef_fac_scale) class(parton_expr_t), intent(inout), target :: expr class(expr_factory_t), intent(in) :: ef_fac_scale end subroutine parton_expr_setup_fac_scale module subroutine parton_expr_setup_ren_scale (expr, ef_ren_scale) class(parton_expr_t), intent(inout), target :: expr class(expr_factory_t), intent(in) :: ef_ren_scale end subroutine parton_expr_setup_ren_scale <>= module subroutine parton_expr_setup_scale (expr, ef_scale) class(parton_expr_t), intent(inout), target :: expr class(expr_factory_t), intent(in) :: ef_scale call ef_scale%build (expr%scale) if (allocated (expr%scale)) then call expr%setup_var_self () call expr%scale%setup_expr (expr%var_list) expr%has_scale = .true. end if end subroutine parton_expr_setup_scale module subroutine parton_expr_setup_fac_scale (expr, ef_fac_scale) class(parton_expr_t), intent(inout), target :: expr class(expr_factory_t), intent(in) :: ef_fac_scale call ef_fac_scale%build (expr%fac_scale) if (allocated (expr%fac_scale)) then call expr%setup_var_self () call expr%fac_scale%setup_expr (expr%var_list) expr%has_fac_scale = .true. end if end subroutine parton_expr_setup_fac_scale module subroutine parton_expr_setup_ren_scale (expr, ef_ren_scale) class(parton_expr_t), intent(inout), target :: expr class(expr_factory_t), intent(in) :: ef_ren_scale call ef_ren_scale%build (expr%ren_scale) if (allocated (expr%ren_scale)) then call expr%setup_var_self () call expr%ren_scale%setup_expr (expr%var_list) expr%has_ren_scale = .true. end if end subroutine parton_expr_setup_ren_scale @ %def parton_expr_setup_scale @ %def parton_expr_setup_fac_scale @ %def parton_expr_setup_ren_scale @ Compile the weight expression. <>= procedure :: setup_weight => parton_expr_setup_weight <>= module subroutine parton_expr_setup_weight (expr, ef_weight) class(parton_expr_t), intent(inout), target :: expr class(expr_factory_t), intent(in) :: ef_weight end subroutine parton_expr_setup_weight <>= module subroutine parton_expr_setup_weight (expr, ef_weight) class(parton_expr_t), intent(inout), target :: expr class(expr_factory_t), intent(in) :: ef_weight call ef_weight%build (expr%weight) if (allocated (expr%weight)) then call expr%setup_var_self () call expr%weight%setup_expr (expr%var_list) expr%has_weight = .true. end if end subroutine parton_expr_setup_weight @ %def parton_expr_setup_weight @ Filling the partonic state consists of two parts. The first routine prepares the subevt without assigning momenta. It takes the particles from an [[interaction_t]]. It needs the indices and flavors for the beam, incoming, and outgoing particles. We can assume that the particle content of the subevt does not change. Therefore, we set the event variables [[n_in]], [[n_out]], [[n_tot]] already in this initialization step. <>= procedure :: setup_subevt => parton_expr_setup_subevt <>= module subroutine parton_expr_setup_subevt (expr, int, & i_beam, i_in, i_out, f_beam, f_in, f_out) class(parton_expr_t), intent(inout) :: expr type(interaction_t), intent(in), target :: int integer, dimension(:), intent(in) :: i_beam, i_in, i_out type(flavor_t), dimension(:), intent(in) :: f_beam, f_in, f_out end subroutine parton_expr_setup_subevt <>= module subroutine parton_expr_setup_subevt (expr, int, & i_beam, i_in, i_out, f_beam, f_in, f_out) class(parton_expr_t), intent(inout) :: expr type(interaction_t), intent(in), target :: int integer, dimension(:), intent(in) :: i_beam, i_in, i_out type(flavor_t), dimension(:), intent(in) :: f_beam, f_in, f_out allocate (expr%i_beam (size (i_beam))) allocate (expr%i_in (size (i_in))) allocate (expr%i_out (size (i_out))) expr%i_beam = i_beam expr%i_in = i_in expr%i_out = i_out call interaction_to_subevt (int, & expr%i_beam, expr%i_in, expr%i_out, expr%subevt_t) call expr%set_pdg_beam (f_beam%get_pdg ()) call expr%set_pdg_incoming (f_in%get_pdg ()) call expr%set_pdg_outgoing (f_out%get_pdg ()) call expr%set_p2_beam (f_beam%get_mass () ** 2) call expr%set_p2_incoming (f_in%get_mass () ** 2) call expr%set_p2_outgoing (f_out%get_mass () ** 2) expr%n_in = size (i_in) expr%n_out = size (i_out) expr%n_tot = expr%n_in + expr%n_out end subroutine parton_expr_setup_subevt @ %def parton_expr_setup_subevt +<>= + procedure :: renew_flv_content_subevt => parton_expr_renew_flv_content_subevt +<>= + module subroutine parton_expr_renew_flv_content_subevt (expr, int, & + i_beam, i_in, i_out, f_beam, f_in, f_out) + class(parton_expr_t), intent(inout) :: expr + type(interaction_t), intent(in), target :: int + integer, dimension(:), intent(in) :: i_beam, i_in, i_out + type(flavor_t), dimension(:), intent(in) :: f_beam, f_in, f_out + end subroutine parton_expr_renew_flv_content_subevt +<>= + module subroutine parton_expr_renew_flv_content_subevt (expr, int, & + i_beam, i_in, i_out, f_beam, f_in, f_out) + class(parton_expr_t), intent(inout) :: expr + type(interaction_t), intent(in), target :: int + integer, dimension(:), intent(in) :: i_beam, i_in, i_out + type(flavor_t), dimension(:), intent(in) :: f_beam, f_in, f_out + expr%i_beam = i_beam + expr%i_in = i_in + expr%i_out = i_out + call expr%set_pdg_beam (f_beam%get_pdg ()) + call expr%set_pdg_incoming (f_in%get_pdg ()) + call expr%set_pdg_outgoing (f_out%get_pdg ()) + expr%n_in = size (i_in) + expr%n_out = size (i_out) + expr%n_tot = expr%n_in + expr%n_out + end subroutine parton_expr_renew_flv_content_subevt + +@ %def parton_expr_renew_flv_content_subevt @ Transfer PDG codes, masses (initalization) and momenta to a predefined subevent. We use the flavor assignment of the first branch in the interaction state matrix. Only incoming and outgoing particles are transferred. Switch momentum sign for incoming particles. <>= interface interaction_momenta_to_subevt module procedure interaction_momenta_to_subevt_id module procedure interaction_momenta_to_subevt_tr end interface <>= module subroutine interaction_momenta_to_subevt_id & (int, j_beam, j_in, j_out, subevt) type(interaction_t), intent(in) :: int integer, dimension(:), intent(in) :: j_beam, j_in, j_out type(subevt_t), intent(inout) :: subevt end subroutine interaction_momenta_to_subevt_id module subroutine interaction_momenta_to_subevt_tr & (int, j_beam, j_in, j_out, lt, subevt) type(interaction_t), intent(in) :: int integer, dimension(:), intent(in) :: j_beam, j_in, j_out type(subevt_t), intent(inout) :: subevt type(lorentz_transformation_t), intent(in) :: lt end subroutine interaction_momenta_to_subevt_tr <>= subroutine interaction_to_subevt (int, j_beam, j_in, j_out, subevt) type(interaction_t), intent(in), target :: int integer, dimension(:), intent(in) :: j_beam, j_in, j_out type(subevt_t), intent(out) :: subevt type(flavor_t), dimension(:), allocatable :: flv integer :: n_beam, n_in, n_out, i, j allocate (flv (int%get_n_tot ())) flv = quantum_numbers_get_flavor (int%get_quantum_numbers (1)) n_beam = size (j_beam) n_in = size (j_in) n_out = size (j_out) call subevt_init (subevt, n_beam + n_in + n_out) do i = 1, n_beam j = j_beam(i) call subevt%set_beam (i, flv(j)%get_pdg (), & vector4_null, flv(j)%get_mass () ** 2) end do do i = 1, n_in j = j_in(i) call subevt%set_incoming (n_beam + i, flv(j)%get_pdg (), & vector4_null, flv(j)%get_mass () ** 2) end do do i = 1, n_out j = j_out(i) call subevt%set_outgoing (n_beam + n_in + i, & flv(j)%get_pdg (), vector4_null, & flv(j)%get_mass () ** 2) end do end subroutine interaction_to_subevt module subroutine interaction_momenta_to_subevt_id & (int, j_beam, j_in, j_out, subevt) type(interaction_t), intent(in) :: int integer, dimension(:), intent(in) :: j_beam, j_in, j_out type(subevt_t), intent(inout) :: subevt call subevt%set_p_beam (- int%get_momenta (j_beam)) call subevt%set_p_incoming (- int%get_momenta (j_in)) call subevt%set_p_outgoing (int%get_momenta (j_out)) end subroutine interaction_momenta_to_subevt_id module subroutine interaction_momenta_to_subevt_tr & (int, j_beam, j_in, j_out, lt, subevt) type(interaction_t), intent(in) :: int integer, dimension(:), intent(in) :: j_beam, j_in, j_out type(subevt_t), intent(inout) :: subevt type(lorentz_transformation_t), intent(in) :: lt call subevt%set_p_beam (- lt * int%get_momenta (j_beam)) call subevt%set_p_incoming (- lt * int%get_momenta (j_in)) call subevt%set_p_outgoing (lt * int%get_momenta (j_out)) end subroutine interaction_momenta_to_subevt_tr @ %def interaction_momenta_to_subevt @ The second part takes the momenta from the interaction object and thus completes the subevt. The partonic energy can then be computed. <>= procedure :: fill_subevt => parton_expr_fill_subevt <>= module subroutine parton_expr_fill_subevt (expr, int) class(parton_expr_t), intent(inout) :: expr type(interaction_t), intent(in), target :: int end subroutine parton_expr_fill_subevt <>= module subroutine parton_expr_fill_subevt (expr, int) class(parton_expr_t), intent(inout) :: expr type(interaction_t), intent(in), target :: int call interaction_momenta_to_subevt (int, & expr%i_beam, expr%i_in, expr%i_out, expr%subevt_t) expr%sqrts_hat = expr%get_sqrts_hat () expr%subevt_filled = .true. end subroutine parton_expr_fill_subevt @ %def parton_expr_fill_subevt @ Evaluate, if the event passes the selection. For absent expressions we take default values. <>= procedure :: evaluate => parton_expr_evaluate <>= module subroutine parton_expr_evaluate (expr, passed, scale, fac_scale, & ren_scale, weight, scale_forced, force_evaluation) class(parton_expr_t), intent(inout) :: expr logical, intent(out) :: passed real(default), intent(out) :: scale real(default), allocatable, intent(out) :: fac_scale real(default), allocatable, intent(out) :: ren_scale real(default), intent(out) :: weight real(default), intent(in), allocatable, optional :: scale_forced logical, intent(in), optional :: force_evaluation end subroutine parton_expr_evaluate <>= module subroutine parton_expr_evaluate (expr, passed, scale, fac_scale, & ren_scale, weight, scale_forced, force_evaluation) class(parton_expr_t), intent(inout) :: expr logical, intent(out) :: passed real(default), intent(out) :: scale real(default), allocatable, intent(out) :: fac_scale real(default), allocatable, intent(out) :: ren_scale real(default), intent(out) :: weight real(default), intent(in), allocatable, optional :: scale_forced logical, intent(in), optional :: force_evaluation logical :: force_scale, force_eval force_scale = .false.; force_eval = .false. if (present (scale_forced)) force_scale = allocated (scale_forced) if (present (force_evaluation)) force_eval = force_evaluation call expr%base_evaluate (passed) if (passed .or. force_eval) then if (force_scale) then scale = scale_forced else if (expr%has_scale) then call expr%scale%evaluate () if (expr%scale%is_known ()) then scale = expr%scale%get_real () else call msg_error ("Evaluate scale expression: result undefined") scale = zero end if else scale = expr%sqrts_hat end if if (expr%has_fac_scale) then call expr%fac_scale%evaluate () if (expr%fac_scale%is_known ()) then if (.not. allocated (fac_scale)) then allocate (fac_scale, source = expr%fac_scale%get_real ()) else fac_scale = expr%fac_scale%get_real () end if else call msg_error ("Evaluate factorization scale expression: & &result undefined") end if end if if (expr%has_ren_scale) then call expr%ren_scale%evaluate () if (expr%ren_scale%is_known ()) then if (.not. allocated (ren_scale)) then allocate (ren_scale, source = expr%ren_scale%get_real ()) else ren_scale = expr%ren_scale%get_real () end if else call msg_error ("Evaluate renormalization scale expression: & &result undefined") end if end if if (expr%has_weight) then call expr%weight%evaluate () if (expr%weight%is_known ()) then weight = expr%weight%get_real () else call msg_error ("Evaluate weight expression: result undefined") weight = zero end if else weight = one end if else weight = zero end if end subroutine parton_expr_evaluate @ %def parton_expr_evaluate @ Return the beam/incoming parton indices. <>= procedure :: get_beam_index => parton_expr_get_beam_index procedure :: get_in_index => parton_expr_get_in_index <>= module subroutine parton_expr_get_beam_index (expr, i_beam) class(parton_expr_t), intent(in) :: expr integer, dimension(:), intent(out) :: i_beam end subroutine parton_expr_get_beam_index module subroutine parton_expr_get_in_index (expr, i_in) class(parton_expr_t), intent(in) :: expr integer, dimension(:), intent(out) :: i_in end subroutine parton_expr_get_in_index <>= module subroutine parton_expr_get_beam_index (expr, i_beam) class(parton_expr_t), intent(in) :: expr integer, dimension(:), intent(out) :: i_beam i_beam = expr%i_beam end subroutine parton_expr_get_beam_index module subroutine parton_expr_get_in_index (expr, i_in) class(parton_expr_t), intent(in) :: expr integer, dimension(:), intent(out) :: i_in i_in = expr%i_in end subroutine parton_expr_get_in_index @ %def parton_expr_get_beam_index @ %def parton_expr_get_in_index @ \subsection{Implementation for full events} This implementation contains the expressions that we can evaluate for the full event. It also contains data that pertain to the event, suitable for communication with external event formats. These data simultaneously serve as pointer targets for the variable lists hidden in the expressions (eval trees). Squared matrix element and weight values: when reading events from file, the [[ref]] value is the number in the file, while the [[prc]] value is the number that we calculate from the momenta in the file, possibly with different parameters. When generating events the first time, or if we do not recalculate, the numbers should coincide. Furthermore, the array of [[alt]] values is copied from an array of alternative event records. These values should represent calculated values. <>= public :: event_expr_t <>= type, extends (subevt_expr_t) :: event_expr_t logical :: has_reweight = .false. logical :: has_analysis = .false. class(expr_t), allocatable :: reweight class(expr_t), allocatable :: analysis logical :: has_id = .false. type(string_t) :: id logical :: has_num_id = .false. integer :: num_id = 0 logical :: has_index = .false. integer :: index = 0 logical :: has_sqme_ref = .false. real(default) :: sqme_ref = 0 logical :: has_sqme_prc = .false. real(default) :: sqme_prc = 0 logical :: has_weight_ref = .false. real(default) :: weight_ref = 0 logical :: has_weight_prc = .false. real(default) :: weight_prc = 0 logical :: has_excess_prc = .false. real(default) :: excess_prc = 0 integer :: n_alt = 0 logical :: has_sqme_alt = .false. real(default), dimension(:), allocatable :: sqme_alt logical :: has_weight_alt = .false. real(default), dimension(:), allocatable :: weight_alt contains <> end type event_expr_t @ %def event_expr_t @ Finalizer for the expressions. <>= procedure :: final => event_expr_final <>= module subroutine event_expr_final (object) class(event_expr_t), intent(inout) :: object end subroutine event_expr_final <>= module subroutine event_expr_final (object) class(event_expr_t), intent(inout) :: object call object%base_final () if (object%has_reweight) then call object%reweight%final () end if if (object%has_analysis) then call object%analysis%final () end if end subroutine event_expr_final @ %def event_expr_final @ Output: continue writing the active expressions, after the common selection expression. Note: the [[prefix]] argument is declared in the [[write]] method of the [[subevt_t]] base type. Here, it is unused. <>= procedure :: write => event_expr_write <>= module subroutine event_expr_write (object, unit, prefix, pacified) class(event_expr_t), intent(in) :: object integer, intent(in), optional :: unit character(*), intent(in), optional :: prefix logical, intent(in), optional :: pacified end subroutine event_expr_write <>= module subroutine event_expr_write (object, unit, prefix, pacified) class(event_expr_t), intent(in) :: object integer, intent(in), optional :: unit character(*), intent(in), optional :: prefix logical, intent(in), optional :: pacified integer :: u u = given_output_unit (unit) call object%base_write (u, pacified = pacified) if (object%subevt_filled) then if (object%has_reweight) then call write_separator (u) write (u, "(1x,A)") "Reweighting expression:" call write_separator (u) call object%reweight%write (u) end if if (object%has_analysis) then call write_separator (u) write (u, "(1x,A)") "Analysis expression:" call write_separator (u) call object%analysis%write (u) end if end if end subroutine event_expr_write @ %def event_expr_write @ Initializer. This is required only for the [[sqme_alt]] and [[weight_alt]] arrays. <>= procedure :: init => event_expr_init <>= module subroutine event_expr_init (expr, n_alt) class(event_expr_t), intent(out) :: expr integer, intent(in), optional :: n_alt end subroutine event_expr_init <>= module subroutine event_expr_init (expr, n_alt) class(event_expr_t), intent(out) :: expr integer, intent(in), optional :: n_alt if (present (n_alt)) then expr%n_alt = n_alt allocate (expr%sqme_alt (n_alt), source = 0._default) allocate (expr%weight_alt (n_alt), source = 0._default) end if end subroutine event_expr_init @ %def event_expr_init @ Define variables. We have the variables of the base type plus specific variables for full events. There is the event index. <>= procedure :: setup_vars => event_expr_setup_vars <>= module subroutine event_expr_setup_vars (expr, sqrts) class(event_expr_t), intent(inout), target :: expr real(default), intent(in) :: sqrts end subroutine event_expr_setup_vars <>= module subroutine event_expr_setup_vars (expr, sqrts) class(event_expr_t), intent(inout), target :: expr real(default), intent(in) :: sqrts call expr%base_setup_vars (sqrts) call expr%var_list%append_string_ptr (var_str ("$process_id"), & expr%id, is_known = expr%has_id, & locked = .true., verbose = .false., intrinsic = .true.) call expr%var_list%append_int_ptr (var_str ("process_num_id"), & expr%num_id, is_known = expr%has_num_id, & locked = .true., verbose = .false., intrinsic = .true.) call expr%var_list%append_real_ptr (var_str ("sqme"), & expr%sqme_prc, is_known = expr%has_sqme_prc, & locked = .true., verbose = .false., intrinsic = .true.) call expr%var_list%append_real_ptr (var_str ("sqme_ref"), & expr%sqme_ref, is_known = expr%has_sqme_ref, & locked = .true., verbose = .false., intrinsic = .true.) call expr%var_list%append_int_ptr (var_str ("event_index"), & expr%index, is_known = expr%has_index, & locked = .true., verbose = .false., intrinsic = .true.) call expr%var_list%append_real_ptr (var_str ("event_weight"), & expr%weight_prc, is_known = expr%has_weight_prc, & locked = .true., verbose = .false., intrinsic = .true.) call expr%var_list%append_real_ptr (var_str ("event_weight_ref"), & expr%weight_ref, is_known = expr%has_weight_ref, & locked = .true., verbose = .false., intrinsic = .true.) call expr%var_list%append_real_ptr (var_str ("event_excess"), & expr%excess_prc, is_known = expr%has_excess_prc, & locked = .true., verbose = .false., intrinsic = .true.) end subroutine event_expr_setup_vars @ %def event_expr_setup_vars @ Compile the analysis expression. If the pointer is disassociated, there is no expression. <>= procedure :: setup_analysis => event_expr_setup_analysis <>= module subroutine event_expr_setup_analysis (expr, ef_analysis) class(event_expr_t), intent(inout), target :: expr class(expr_factory_t), intent(in) :: ef_analysis end subroutine event_expr_setup_analysis <>= module subroutine event_expr_setup_analysis (expr, ef_analysis) class(event_expr_t), intent(inout), target :: expr class(expr_factory_t), intent(in) :: ef_analysis call ef_analysis%build (expr%analysis) if (allocated (expr%analysis)) then call expr%setup_var_self () call expr%analysis%setup_lexpr (expr%var_list) expr%has_analysis = .true. end if end subroutine event_expr_setup_analysis @ %def event_expr_setup_analysis @ Compile the reweight expression. <>= procedure :: setup_reweight => event_expr_setup_reweight <>= module subroutine event_expr_setup_reweight (expr, ef_reweight) class(event_expr_t), intent(inout), target :: expr class(expr_factory_t), intent(in) :: ef_reweight end subroutine event_expr_setup_reweight <>= module subroutine event_expr_setup_reweight (expr, ef_reweight) class(event_expr_t), intent(inout), target :: expr class(expr_factory_t), intent(in) :: ef_reweight call ef_reweight%build (expr%reweight) if (allocated (expr%reweight)) then call expr%setup_var_self () call expr%reweight%setup_expr (expr%var_list) expr%has_reweight = .true. end if end subroutine event_expr_setup_reweight @ %def event_expr_setup_reweight @ Store the string or numeric process ID. This should be done during initialization. <>= procedure :: set_process_id => event_expr_set_process_id procedure :: set_process_num_id => event_expr_set_process_num_id <>= module subroutine event_expr_set_process_id (expr, id) class(event_expr_t), intent(inout) :: expr type(string_t), intent(in) :: id end subroutine event_expr_set_process_id module subroutine event_expr_set_process_num_id (expr, num_id) class(event_expr_t), intent(inout) :: expr integer, intent(in) :: num_id end subroutine event_expr_set_process_num_id <>= module subroutine event_expr_set_process_id (expr, id) class(event_expr_t), intent(inout) :: expr type(string_t), intent(in) :: id expr%id = id expr%has_id = .true. end subroutine event_expr_set_process_id module subroutine event_expr_set_process_num_id (expr, num_id) class(event_expr_t), intent(inout) :: expr integer, intent(in) :: num_id expr%num_id = num_id expr%has_num_id = .true. end subroutine event_expr_set_process_num_id @ %def event_expr_set_process_id @ %def event_expr_set_process_num_id @ Reset / set the data that pertain to a particular event. The event index is reset unless explicitly told to keep it. <>= procedure :: reset_contents => event_expr_reset_contents procedure :: set => event_expr_set <>= module subroutine event_expr_reset_contents (expr) class(event_expr_t), intent(inout) :: expr end subroutine event_expr_reset_contents module subroutine event_expr_set (expr, & weight_ref, weight_prc, weight_alt, & excess_prc, & sqme_ref, sqme_prc, sqme_alt) class(event_expr_t), intent(inout) :: expr real(default), intent(in), optional :: weight_ref, weight_prc real(default), intent(in), optional :: excess_prc real(default), intent(in), optional :: sqme_ref, sqme_prc real(default), dimension(:), intent(in), optional :: sqme_alt, weight_alt end subroutine event_expr_set <>= module subroutine event_expr_reset_contents (expr) class(event_expr_t), intent(inout) :: expr call expr%base_reset_contents () expr%has_sqme_ref = .false. expr%has_sqme_prc = .false. expr%has_sqme_alt = .false. expr%has_weight_ref = .false. expr%has_weight_prc = .false. expr%has_weight_alt = .false. expr%has_excess_prc = .false. end subroutine event_expr_reset_contents module subroutine event_expr_set (expr, & weight_ref, weight_prc, weight_alt, & excess_prc, & sqme_ref, sqme_prc, sqme_alt) class(event_expr_t), intent(inout) :: expr real(default), intent(in), optional :: weight_ref, weight_prc real(default), intent(in), optional :: excess_prc real(default), intent(in), optional :: sqme_ref, sqme_prc real(default), dimension(:), intent(in), optional :: sqme_alt, weight_alt if (present (sqme_ref)) then expr%has_sqme_ref = .true. expr%sqme_ref = sqme_ref end if if (present (sqme_prc)) then expr%has_sqme_prc = .true. expr%sqme_prc = sqme_prc end if if (present (sqme_alt)) then expr%has_sqme_alt = .true. expr%sqme_alt = sqme_alt end if if (present (weight_ref)) then expr%has_weight_ref = .true. expr%weight_ref = weight_ref end if if (present (weight_prc)) then expr%has_weight_prc = .true. expr%weight_prc = weight_prc end if if (present (weight_alt)) then expr%has_weight_alt = .true. expr%weight_alt = weight_alt end if if (present (excess_prc)) then expr%has_excess_prc = .true. expr%excess_prc = excess_prc end if end subroutine event_expr_set @ %def event_expr_reset_contents event_expr_set @ Access the subevent index. <>= procedure :: has_event_index => event_expr_has_event_index procedure :: get_event_index => event_expr_get_event_index <>= module function event_expr_has_event_index (expr) result (flag) class(event_expr_t), intent(in) :: expr logical :: flag end function event_expr_has_event_index module function event_expr_get_event_index (expr) result (index) class(event_expr_t), intent(in) :: expr integer :: index end function event_expr_get_event_index <>= module function event_expr_has_event_index (expr) result (flag) class(event_expr_t), intent(in) :: expr logical :: flag flag = expr%has_index end function event_expr_has_event_index module function event_expr_get_event_index (expr) result (index) class(event_expr_t), intent(in) :: expr integer :: index if (expr%has_index) then index = expr%index else index = 0 end if end function event_expr_get_event_index @ %def event_expr_has_event_index @ %def event_expr_get_event_index @ Set/increment the subevent index. Initialize it if necessary. <>= procedure :: set_event_index => event_expr_set_event_index procedure :: reset_event_index => event_expr_reset_event_index procedure :: increment_event_index => event_expr_increment_event_index <>= module subroutine event_expr_set_event_index (expr, index) class(event_expr_t), intent(inout) :: expr integer, intent(in) :: index end subroutine event_expr_set_event_index module subroutine event_expr_reset_event_index (expr) class(event_expr_t), intent(inout) :: expr end subroutine event_expr_reset_event_index module subroutine event_expr_increment_event_index (expr, offset) class(event_expr_t), intent(inout) :: expr integer, intent(in), optional :: offset end subroutine event_expr_increment_event_index <>= module subroutine event_expr_set_event_index (expr, index) class(event_expr_t), intent(inout) :: expr integer, intent(in) :: index expr%index = index expr%has_index = .true. end subroutine event_expr_set_event_index module subroutine event_expr_reset_event_index (expr) class(event_expr_t), intent(inout) :: expr expr%has_index = .false. end subroutine event_expr_reset_event_index module subroutine event_expr_increment_event_index (expr, offset) class(event_expr_t), intent(inout) :: expr integer, intent(in), optional :: offset if (expr%has_index) then expr%index = expr%index + 1 else if (present (offset)) then call expr%set_event_index (offset + 1) else call expr%set_event_index (1) end if end subroutine event_expr_increment_event_index @ %def event_expr_set_event_index @ %def event_expr_increment_event_index @ Fill the event expression: take the particle data and kinematics from a [[particle_set]] object. We allow the particle content to change for each event. Therefore, we set the event variables each time. Also increment the event index; initialize it if necessary. <>= procedure :: fill_subevt => event_expr_fill_subevt <>= module subroutine event_expr_fill_subevt (expr, particle_set) class(event_expr_t), intent(inout) :: expr type(particle_set_t), intent(in) :: particle_set end subroutine event_expr_fill_subevt <>= module subroutine event_expr_fill_subevt (expr, particle_set) class(event_expr_t), intent(inout) :: expr type(particle_set_t), intent(in) :: particle_set call particle_set%to_subevt (expr%subevt_t, expr%colorize_subevt) expr%sqrts_hat = expr%get_sqrts_hat () expr%n_in = expr%get_n_in () expr%n_out = expr%get_n_out () expr%n_tot = expr%n_in + expr%n_out expr%subevt_filled = .true. end subroutine event_expr_fill_subevt @ %def event_expr_fill_subevt @ Evaluate, if the event passes the selection. For absent expressions we take default values. <>= procedure :: evaluate => event_expr_evaluate <>= module subroutine event_expr_evaluate & (expr, passed, reweight, analysis_flag) class(event_expr_t), intent(inout) :: expr logical, intent(out) :: passed real(default), intent(out) :: reweight logical, intent(out) :: analysis_flag end subroutine event_expr_evaluate <>= module subroutine event_expr_evaluate (expr, passed, reweight, analysis_flag) class(event_expr_t), intent(inout) :: expr logical, intent(out) :: passed real(default), intent(out) :: reweight logical, intent(out) :: analysis_flag call expr%base_evaluate (passed) if (passed) then if (expr%has_reweight) then call expr%reweight%evaluate () if (expr%reweight%is_known ()) then reweight = expr%reweight%get_real () else call msg_error ("Evaluate reweight expression: & &result undefined") reweight = 0 end if else reweight = 1 end if if (expr%has_analysis) then call expr%analysis%evaluate () if (expr%analysis%is_known ()) then analysis_flag = expr%analysis%get_log () else call msg_error ("Evaluate analysis expression: & &result undefined") analysis_flag = .false. end if else analysis_flag = .true. end if end if end subroutine event_expr_evaluate @ %def event_expr_evaluate @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Parton states} A [[parton_state_t]] object contains the effective kinematics and dynamics of an elementary partonic interaction, with or without the beam/structure function state included. The type is abstract and has two distinct extensions. The [[isolated_state_t]] extension describes the isolated elementary interaction where the [[int_eff]] subobject contains the complex transition amplitude, exclusive in all quantum numbers. The particle content and kinematics describe the effective partonic state. The [[connected_state_t]] extension contains the partonic [[subevt]] and the expressions for cuts and scales which use it. In the isolated state, the effective partonic interaction may either be identical to the hard interaction, in which case it is just a pointer to the latter. Or it may involve a rearrangement of partons, in which case we allocate it explicitly and flag this by [[int_is_allocated]]. The [[trace]] evaluator contains the absolute square of the effective transition amplitude matrix, summed over final states. It is also summed over initial states, depending on the the beam setup allows. The result is used for integration. The [[matrix]] evaluator is the counterpart of [[trace]] which is kept exclusive in all observable quantum numbers. The [[flows]] evaluator is furthermore exclusive in colors, but neglecting all color interference. The [[matrix]] and [[flows]] evaluators are filled only for sampling points that become part of physical events. Note: It would be natural to make the evaluators allocatable. The extra [[has_XXX]] flags indicate whether evaluators are active, instead. This module contains no unit tests. The tests are covered by the [[processes]] module below. <<[[parton_states.f90]]>>= <> module parton_states <> use variables use expr_base use model_data use flavors use quantum_numbers use state_matrices use interactions use evaluators use beams use sf_base use prc_core use subevt_expr <> <> <> interface <> end interface end module parton_states @ %def parton_states @ <<[[parton_states_sub.f90]]>>= <> submodule (parton_states) parton_states_s <> use io_units use format_utils, only: write_separator use diagnostics use lorentz use subevents use helicities use colors use polarizations use process_constants implicit none contains <> end submodule parton_states_s @ %def parton_states_s @ \subsection{Abstract base type} The common part are the evaluators, one for the trace (summed over all quantum numbers), one for the transition matrix (summed only over unobservable quantum numbers), and one for the flow distribution (transition matrix without interferences, exclusive in color flow). <>= type, abstract :: parton_state_t logical :: has_trace = .false. logical :: has_matrix = .false. logical :: has_flows = .false. type(evaluator_t) :: trace type(evaluator_t) :: matrix type(evaluator_t) :: flows contains <> end type parton_state_t @ %def parton_state_t @ The [[isolated_state_t]] extension contains the [[sf_chain_eff]] object and the (hard) effective interaction [[int_eff]], separately, both are implemented as a pointer. The evaluators (trace, matrix, flows) apply to the hard interaction only. If the effective interaction differs from the hard interaction, the pointer is allocated explicitly. Analogously for [[sf_chain_eff]]. <>= public :: isolated_state_t <>= type, extends (parton_state_t) :: isolated_state_t logical :: sf_chain_is_allocated = .false. type(sf_chain_instance_t), pointer :: sf_chain_eff => null () logical :: int_is_allocated = .false. type(interaction_t), pointer :: int_eff => null () contains <> end type isolated_state_t @ %def isolated_state_t @ The [[connected_state_t]] extension contains all data that enable the evaluation of observables for the effective connected state. The evaluators connect the (effective) structure-function chain and hard interaction that were kept separate in the [[isolated_state_t]]. The [[flows_sf]] evaluator is an extended copy of the structure-function The [[expr]] subobject consists of the [[subevt]], a simple event record, expressions for cuts etc.\ which refer to this record, and a [[var_list]] which contains event-specific variables, linked to the process variable list. Variables used within the expressions are looked up in [[var_list]]. <>= public :: connected_state_t <>= type, extends (parton_state_t) :: connected_state_t type(state_flv_content_t) :: state_flv logical :: has_flows_sf = .false. type(evaluator_t) :: flows_sf logical :: has_expr = .false. type(parton_expr_t) :: expr contains <> end type connected_state_t @ %def connected_state_t @ Output: each evaluator is written only when it is active. The [[sf_chain]] is only written if it is explicitly allocated. <>= procedure :: write => parton_state_write <>= module subroutine parton_state_write (state, unit, testflag) class(parton_state_t), intent(in) :: state integer, intent(in), optional :: unit logical, intent(in), optional :: testflag end subroutine parton_state_write <>= module subroutine parton_state_write (state, unit, testflag) class(parton_state_t), intent(in) :: state integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u u = given_output_unit (unit) select type (state) class is (isolated_state_t) if (state%sf_chain_is_allocated) then call write_separator (u) call state%sf_chain_eff%write (u) end if if (state%int_is_allocated) then call write_separator (u) write (u, "(1x,A)") & "Effective interaction:" call write_separator (u) call state%int_eff%basic_write (u, testflag = testflag) end if class is (connected_state_t) if (state%has_flows_sf) then call write_separator (u) write (u, "(1x,A)") & "Evaluator (extension of the beam evaluator & &with color contractions):" call write_separator (u) call state%flows_sf%write (u, testflag = testflag) end if end select if (state%has_trace) then call write_separator (u) write (u, "(1x,A)") & "Evaluator (trace of the squared transition matrix):" call write_separator (u) call state%trace%write (u, testflag = testflag) end if if (state%has_matrix) then call write_separator (u) write (u, "(1x,A)") & "Evaluator (squared transition matrix):" call write_separator (u) call state%matrix%write (u, testflag = testflag) end if if (state%has_flows) then call write_separator (u) write (u, "(1x,A)") & "Evaluator (squared color-flow matrix):" call write_separator (u) call state%flows%write (u, testflag = testflag) end if select type (state) class is (connected_state_t) if (state%has_expr) then call write_separator (u) call state%expr%write (u) end if end select end subroutine parton_state_write @ %def parton_state_write @ Finalize interaction and evaluators, but only if allocated. <>= procedure :: final => parton_state_final <>= module subroutine parton_state_final (state) class(parton_state_t), intent(inout) :: state end subroutine parton_state_final <>= module subroutine parton_state_final (state) class(parton_state_t), intent(inout) :: state if (state%has_flows) then call state%flows%final () state%has_flows = .false. end if if (state%has_matrix) then call state%matrix%final () state%has_matrix = .false. end if if (state%has_trace) then call state%trace%final () state%has_trace = .false. end if select type (state) class is (connected_state_t) if (state%has_flows_sf) then call state%flows_sf%final () state%has_flows_sf = .false. end if call state%expr%final () class is (isolated_state_t) if (state%int_is_allocated) then call state%int_eff%final () deallocate (state%int_eff) state%int_is_allocated = .false. end if if (state%sf_chain_is_allocated) then call state%sf_chain_eff%final () end if end select end subroutine parton_state_final @ %def parton_state_final @ \subsection{Common Initialization} Initialize the isolated parton state. In this version, the effective structure-function chain [[sf_chain_eff]] and the effective interaction [[int_eff]] both are trivial pointers to the seed structure-function chain and to the hard interaction, respectively. <>= procedure :: init => isolated_state_init <>= module subroutine isolated_state_init (state, sf_chain, int) class(isolated_state_t), intent(out) :: state type(sf_chain_instance_t), intent(in), target :: sf_chain type(interaction_t), intent(in), target :: int end subroutine isolated_state_init <>= module subroutine isolated_state_init (state, sf_chain, int) class(isolated_state_t), intent(out) :: state type(sf_chain_instance_t), intent(in), target :: sf_chain type(interaction_t), intent(in), target :: int state%sf_chain_eff => sf_chain state%int_eff => int end subroutine isolated_state_init @ %def isolated_state_init @ \subsection{Evaluator initialization: isolated state} Create an evaluator for the trace of the squared transition matrix. The trace goes over all outgoing quantum numbers. Whether we trace over incoming quantum numbers other than color, depends on the given [[qn_mask_in]]. There are two options: explicitly computing the color factor table ([[use_cf]] false; [[nc]] defined), or taking the color factor table from the hard matrix element data. <>= procedure :: setup_square_trace => isolated_state_setup_square_trace <>= module subroutine isolated_state_setup_square_trace (state, core, & qn_mask_in, col, keep_fs_flavor) class(isolated_state_t), intent(inout), target :: state class(prc_core_t), intent(in) :: core type(quantum_numbers_mask_t), intent(in), dimension(:) :: qn_mask_in integer, intent(in), dimension(:), allocatable :: col logical, intent(in) :: keep_fs_flavor end subroutine isolated_state_setup_square_trace <>= module subroutine isolated_state_setup_square_trace (state, core, & qn_mask_in, col, keep_fs_flavor) class(isolated_state_t), intent(inout), target :: state class(prc_core_t), intent(in) :: core type(quantum_numbers_mask_t), intent(in), dimension(:) :: qn_mask_in !!! Actually need allocatable attribute here for once because col might !!! enter the subroutine non-allocated. integer, intent(in), dimension(:), allocatable :: col logical, intent(in) :: keep_fs_flavor type(quantum_numbers_mask_t), dimension(:), allocatable :: qn_mask associate (data => core%data) allocate (qn_mask (data%n_in + data%n_out)) qn_mask( : data%n_in) = & quantum_numbers_mask (.false., .true., .false.) & .or. qn_mask_in qn_mask(data%n_in + 1 : ) = & quantum_numbers_mask (.not. keep_fs_flavor, .true., .true.) if (core%use_color_factors) then call state%trace%init_square (state%int_eff, qn_mask, & col_flow_index = data%cf_index, & col_factor = data%color_factors, & col_index_hi = col, & nc = core%nc) else call state%trace%init_square (state%int_eff, qn_mask, nc = core%nc) end if end associate state%has_trace = .true. end subroutine isolated_state_setup_square_trace @ %def isolated_state_setup_square_trace @ Set up an identity-evaluator for the trace. This implies that [[me]] is considered to be a squared amplitude, as for example for BLHA matrix elements. <>= procedure :: setup_identity_trace => isolated_state_setup_identity_trace <>= module subroutine isolated_state_setup_identity_trace (state, core, & qn_mask_in, keep_fs_flavors, keep_colors) class(isolated_state_t), intent(inout), target :: state class(prc_core_t), intent(in) :: core type(quantum_numbers_mask_t), intent(in), dimension(:) :: qn_mask_in logical, intent(in), optional :: keep_fs_flavors, keep_colors end subroutine isolated_state_setup_identity_trace <>= module subroutine isolated_state_setup_identity_trace (state, core, & qn_mask_in, keep_fs_flavors, keep_colors) class(isolated_state_t), intent(inout), target :: state class(prc_core_t), intent(in) :: core type(quantum_numbers_mask_t), intent(in), dimension(:) :: qn_mask_in logical, intent(in), optional :: keep_fs_flavors, keep_colors type(quantum_numbers_mask_t), dimension(:), allocatable :: qn_mask logical :: fs_flv_flag, col_flag fs_flv_flag = .true.; col_flag = .true. if (present(keep_fs_flavors)) fs_flv_flag = .not. keep_fs_flavors if (present(keep_colors)) col_flag = .not. keep_colors associate (data => core%data) allocate (qn_mask (data%n_in + data%n_out)) qn_mask( : data%n_in) = & quantum_numbers_mask (.false., col_flag, .false.) .or. qn_mask_in qn_mask(data%n_in + 1 : ) = & quantum_numbers_mask (fs_flv_flag, col_flag, .true.) end associate call state%int_eff%set_mask (qn_mask) call state%trace%init_identity (state%int_eff) state%has_trace = .true. end subroutine isolated_state_setup_identity_trace @ %def isolated_state_setup_identity_trace @ Set up the evaluator for the transition matrix, exclusive in helicities where this is requested. For all unstable final-state particles we keep polarization according to the applicable decay options. If the process is a decay itself, this applies also to the initial state. For all polarized final-state particles, we keep polarization including off-diagonal entries. We drop helicity completely for unpolarized final-state particles. For the initial state, if the particle has not been handled yet, we apply the provided [[qn_mask_in]] which communicates the beam properties. <>= procedure :: setup_square_matrix => isolated_state_setup_square_matrix <>= module subroutine isolated_state_setup_square_matrix & (state, core, model, qn_mask_in, col) class(isolated_state_t), intent(inout), target :: state class(prc_core_t), intent(in) :: core class(model_data_t), intent(in), target :: model type(quantum_numbers_mask_t), dimension(:), intent(in) :: qn_mask_in integer, dimension(:), intent(in) :: col end subroutine isolated_state_setup_square_matrix <>= module subroutine isolated_state_setup_square_matrix & (state, core, model, qn_mask_in, col) class(isolated_state_t), intent(inout), target :: state class(prc_core_t), intent(in) :: core class(model_data_t), intent(in), target :: model type(quantum_numbers_mask_t), dimension(:), intent(in) :: qn_mask_in integer, dimension(:), intent(in) :: col type(quantum_numbers_mask_t), dimension(:), allocatable :: qn_mask type(flavor_t), dimension(:), allocatable :: flv integer :: i logical :: helmask, helmask_hd associate (data => core%data) allocate (qn_mask (data%n_in + data%n_out)) allocate (flv (data%n_flv)) do i = 1, data%n_in + data%n_out call flv%init (data%flv_state(i,:), model) if ((data%n_in == 1 .or. i > data%n_in) & .and. any (.not. flv%is_stable ())) then helmask = all (flv%decays_isotropically ()) helmask_hd = all (flv%decays_diagonal ()) qn_mask(i) = quantum_numbers_mask (.false., .true., helmask, & mask_hd = helmask_hd) else if (i > data%n_in) then helmask = all (.not. flv%is_polarized ()) qn_mask(i) = quantum_numbers_mask (.false., .true., helmask) else qn_mask(i) = quantum_numbers_mask (.false., .true., .false.) & .or. qn_mask_in(i) end if end do if (core%use_color_factors) then call state%matrix%init_square (state%int_eff, qn_mask, & col_flow_index = data%cf_index, & col_factor = data%color_factors, & col_index_hi = col, & nc = core%nc) else call state%matrix%init_square (state%int_eff, & qn_mask, & nc = core%nc) end if end associate state%has_matrix = .true. end subroutine isolated_state_setup_square_matrix @ %def isolated_state_setup_square_matrix @ This procedure initializes the evaluator that computes the contributions to color flows, neglecting color interference. The incoming-particle mask can be used to sum over incoming flavor. Helicity handling: see above. <>= procedure :: setup_square_flows => isolated_state_setup_square_flows <>= module subroutine isolated_state_setup_square_flows & (state, core, model, qn_mask_in) class(isolated_state_t), intent(inout), target :: state class(prc_core_t), intent(in) :: core class(model_data_t), intent(in), target :: model type(quantum_numbers_mask_t), dimension(:), intent(in) :: qn_mask_in end subroutine isolated_state_setup_square_flows <>= module subroutine isolated_state_setup_square_flows & (state, core, model, qn_mask_in) class(isolated_state_t), intent(inout), target :: state class(prc_core_t), intent(in) :: core class(model_data_t), intent(in), target :: model type(quantum_numbers_mask_t), dimension(:), intent(in) :: qn_mask_in type(quantum_numbers_mask_t), dimension(:), allocatable :: qn_mask type(flavor_t), dimension(:), allocatable :: flv integer :: i logical :: helmask, helmask_hd associate (data => core%data) allocate (qn_mask (data%n_in + data%n_out)) allocate (flv (data%n_flv)) do i = 1, data%n_in + data%n_out call flv%init (data%flv_state(i,:), model) if ((data%n_in == 1 .or. i > data%n_in) & .and. any (.not. flv%is_stable ())) then helmask = all (flv%decays_isotropically ()) helmask_hd = all (flv%decays_diagonal ()) qn_mask(i) = quantum_numbers_mask (.false., .false., helmask, & mask_hd = helmask_hd) else if (i > data%n_in) then helmask = all (.not. flv%is_polarized ()) qn_mask(i) = quantum_numbers_mask (.false., .false., helmask) else qn_mask(i) = quantum_numbers_mask (.false., .false., .false.) & .or. qn_mask_in(i) end if end do call state%flows%init_square (state%int_eff, qn_mask, & expand_color_flows = .true.) end associate state%has_flows = .true. end subroutine isolated_state_setup_square_flows @ %def isolated_state_setup_square_flows @ \subsection{Evaluator initialization: connected state} Set up a trace evaluator as a product of two evaluators (incoming state, effective interaction). In the result, all quantum numbers are summed over. If the optional [[int]] interaction is provided, use this for the first factor in the convolution. Otherwise, use the final interaction of the stored [[sf_chain]]. The [[resonant]] flag applies if we want to construct a decay chain. The resonance property can propagate to the final event output. If an extended structure function is required [[requires_extended_sf]], we have to not consider [[sub]] as a quantum number. <>= procedure :: setup_connected_trace => connected_state_setup_connected_trace <>= module subroutine connected_state_setup_connected_trace & (state, isolated, int, resonant, undo_helicities, & keep_fs_flavors, requires_extended_sf) class(connected_state_t), intent(inout), target :: state type(isolated_state_t), intent(in), target :: isolated type(interaction_t), intent(in), optional, target :: int logical, intent(in), optional :: resonant logical, intent(in), optional :: undo_helicities logical, intent(in), optional :: keep_fs_flavors logical, intent(in), optional :: requires_extended_sf end subroutine connected_state_setup_connected_trace <>= module subroutine connected_state_setup_connected_trace & (state, isolated, int, resonant, undo_helicities, & keep_fs_flavors, requires_extended_sf) class(connected_state_t), intent(inout), target :: state type(isolated_state_t), intent(in), target :: isolated type(interaction_t), intent(in), optional, target :: int logical, intent(in), optional :: resonant logical, intent(in), optional :: undo_helicities logical, intent(in), optional :: keep_fs_flavors logical, intent(in), optional :: requires_extended_sf type(quantum_numbers_mask_t) :: mask type(interaction_t), pointer :: src_int, beam_int logical :: reduce, fs_flv_flag if (debug_on) call msg_debug (D_PROCESS_INTEGRATION, & "connected_state_setup_connected_trace") reduce = .false.; fs_flv_flag = .true. if (present (undo_helicities)) reduce = undo_helicities if (present (keep_fs_flavors)) fs_flv_flag = .not. keep_fs_flavors mask = quantum_numbers_mask (fs_flv_flag, .true., .true.) if (present (int)) then src_int => int else src_int => isolated%sf_chain_eff%get_out_int_ptr () end if if (debug2_active (D_PROCESS_INTEGRATION)) then call src_int%basic_write () end if call state%trace%init_product (src_int, isolated%trace, & qn_mask_conn = mask, & qn_mask_rest = mask, & connections_are_resonant = resonant, & ignore_sub_for_qn = requires_extended_sf) if (reduce) then beam_int => isolated%sf_chain_eff%get_beam_int_ptr () call undo_qn_hel (beam_int, mask, beam_int%get_n_tot ()) call undo_qn_hel (src_int, mask, src_int%get_n_tot ()) call beam_int%set_matrix_element (cmplx (1, 0, default)) call src_int%set_matrix_element (cmplx (1, 0, default)) end if state%has_trace = .true. contains subroutine undo_qn_hel (int_in, mask, n_tot) type(interaction_t), intent(inout) :: int_in type(quantum_numbers_mask_t), intent(in) :: mask integer, intent(in) :: n_tot type(quantum_numbers_mask_t), dimension(n_tot) :: mask_in mask_in = mask call int_in%set_mask (mask_in) end subroutine undo_qn_hel end subroutine connected_state_setup_connected_trace @ %def connected_state_setup_connected_trace @ Set up a matrix evaluator as a product of two evaluators (incoming state, effective interation). In the intermediate state, color and helicity is summed over. In the final state, we keep the quantum numbers which are present in the original evaluators. <>= procedure :: setup_connected_matrix => connected_state_setup_connected_matrix <>= module subroutine connected_state_setup_connected_matrix & (state, isolated, int, resonant, qn_filter_conn) class(connected_state_t), intent(inout), target :: state type(isolated_state_t), intent(in), target :: isolated type(interaction_t), intent(in), optional, target :: int logical, intent(in), optional :: resonant type(quantum_numbers_t), intent(in), optional :: qn_filter_conn end subroutine connected_state_setup_connected_matrix <>= module subroutine connected_state_setup_connected_matrix & (state, isolated, int, resonant, qn_filter_conn) class(connected_state_t), intent(inout), target :: state type(isolated_state_t), intent(in), target :: isolated type(interaction_t), intent(in), optional, target :: int logical, intent(in), optional :: resonant type(quantum_numbers_t), intent(in), optional :: qn_filter_conn type(quantum_numbers_mask_t) :: mask type(interaction_t), pointer :: src_int mask = quantum_numbers_mask (.false., .true., .true.) if (present (int)) then src_int => int else src_int => isolated%sf_chain_eff%get_out_int_ptr () end if call state%matrix%init_product & (src_int, isolated%matrix, mask, & qn_filter_conn = qn_filter_conn, & connections_are_resonant = resonant) state%has_matrix = .true. end subroutine connected_state_setup_connected_matrix @ %def connected_state_setup_connected_matrix @ Set up a matrix evaluator as a product of two evaluators (incoming state, effective interation). In the intermediate state, only helicity is summed over. In the final state, we keep the quantum numbers which are present in the original evaluators. If the optional [[int]] interaction is provided, use this for the first factor in the convolution. Otherwise, use the final interaction of the stored [[sf_chain]], after creating an intermediate interaction that includes a correlated color state. We assume that for a caller-provided [[int]], this is not necessary. For fixed-order NLO differential distribution, we are interested at the partonic level, no parton showering takes place as this would demand for a proper matching. So, the flows in the [[connected_state]] are not needed, and the color part will be masked for the interaction coming from the [[sf_chain]]. The squared matrix elements coming from the OLP provider at the moment do not come with flows anyhow. This needs to be revised once the matching to the shower is completed. <>= procedure :: setup_connected_flows => connected_state_setup_connected_flows <>= module subroutine connected_state_setup_connected_flows & (state, isolated, int, resonant, qn_filter_conn, mask_color) class(connected_state_t), intent(inout), target :: state type(isolated_state_t), intent(in), target :: isolated type(interaction_t), intent(in), optional, target :: int logical, intent(in), optional :: resonant, mask_color type(quantum_numbers_t), intent(in), optional :: qn_filter_conn end subroutine connected_state_setup_connected_flows <>= module subroutine connected_state_setup_connected_flows & (state, isolated, int, resonant, qn_filter_conn, mask_color) class(connected_state_t), intent(inout), target :: state type(isolated_state_t), intent(in), target :: isolated type(interaction_t), intent(in), optional, target :: int logical, intent(in), optional :: resonant, mask_color type(quantum_numbers_t), intent(in), optional :: qn_filter_conn type(quantum_numbers_mask_t) :: mask type(quantum_numbers_mask_t), dimension(:), allocatable :: mask_sf type(interaction_t), pointer :: src_int logical :: mask_c mask_c = .false. if (present (mask_color)) mask_c = mask_color mask = quantum_numbers_mask (.false., .false., .true.) if (present (int)) then src_int => int else src_int => isolated%sf_chain_eff%get_out_int_ptr () call state%flows_sf%init_color_contractions (src_int) state%has_flows_sf = .true. src_int => state%flows_sf%interaction_t if (mask_c) then allocate (mask_sf (src_int%get_n_tot ())) mask_sf = quantum_numbers_mask (.false., .true., .false.) call src_int%reduce_state_matrix (mask_sf, keep_order = .true.) end if end if call state%flows%init_product (src_int, isolated%flows, mask, & qn_filter_conn = qn_filter_conn, & connections_are_resonant = resonant) state%has_flows = .true. end subroutine connected_state_setup_connected_flows @ %def connected_state_setup_connected_flows @ Determine and store the flavor content for the connected state. This queries the [[matrix]] evaluator component, which should hold the requested flavor information. <>= procedure :: setup_state_flv => connected_state_setup_state_flv <>= module subroutine connected_state_setup_state_flv (state, n_out_hard) class(connected_state_t), intent(inout), target :: state integer, intent(in) :: n_out_hard end subroutine connected_state_setup_state_flv <>= module subroutine connected_state_setup_state_flv (state, n_out_hard) class(connected_state_t), intent(inout), target :: state integer, intent(in) :: n_out_hard call state%matrix%get_flv_content (state%state_flv, n_out_hard) end subroutine connected_state_setup_state_flv @ %def connected_state_setup_state_flv @ Return the current flavor state object. <>= procedure :: get_state_flv => connected_state_get_state_flv <>= module function connected_state_get_state_flv (state) result (state_flv) class(connected_state_t), intent(in) :: state type(state_flv_content_t) :: state_flv end function connected_state_get_state_flv <>= module function connected_state_get_state_flv (state) result (state_flv) class(connected_state_t), intent(in) :: state type(state_flv_content_t) :: state_flv state_flv = state%state_flv end function connected_state_get_state_flv @ %def connected_state_get_state_flv @ \subsection{Cuts and expressions} Set up the [[subevt]] that corresponds to the connected interaction. The index arrays refer to the interaction. We assign the particles as follows: the beam particles are the first two (decay process: one) entries in the trace evaluator. The incoming partons are identified by their link to the outgoing partons of the structure-function chain. The outgoing partons are those of the trace evaluator, which include radiated partons during the structure-function chain. <>= procedure :: setup_subevt => connected_state_setup_subevt <>= module subroutine connected_state_setup_subevt & (state, sf_chain, f_beam, f_in, f_out) class(connected_state_t), intent(inout), target :: state type(sf_chain_instance_t), intent(in), target :: sf_chain type(flavor_t), dimension(:), intent(in) :: f_beam, f_in, f_out end subroutine connected_state_setup_subevt <>= module subroutine connected_state_setup_subevt & (state, sf_chain, f_beam, f_in, f_out) class(connected_state_t), intent(inout), target :: state type(sf_chain_instance_t), intent(in), target :: sf_chain type(flavor_t), dimension(:), intent(in) :: f_beam, f_in, f_out integer :: n_beam, n_in, n_out, n_vir, n_tot, i, j integer, dimension(:), allocatable :: i_beam, i_in, i_out integer :: sf_out_i type(interaction_t), pointer :: sf_int sf_int => sf_chain%get_out_int_ptr () n_beam = size (f_beam) n_in = size (f_in) n_out = size (f_out) n_vir = state%trace%get_n_vir () n_tot = state%trace%get_n_tot () allocate (i_beam (n_beam), i_in (n_in), i_out (n_out)) i_beam = [(i, i = 1, n_beam)] do j = 1, n_in sf_out_i = sf_chain%get_out_i (j) i_in(j) = interaction_find_link & (state%trace%interaction_t, sf_int, sf_out_i) end do i_out = [(i, i = n_vir + 1, n_tot)] call state%expr%setup_subevt (state%trace%interaction_t, & i_beam, i_in, i_out, f_beam, f_in, f_out) state%has_expr = .true. end subroutine connected_state_setup_subevt @ %def connected_state_setup_subevt +<>= + procedure :: renew_flv_content_subevt => & + connected_state_renew_flv_content_subevt +<>= + module subroutine connected_state_renew_flv_content_subevt & + (state, sf_chain, f_beam, f_in, f_out) + class(connected_state_t), intent(inout), target :: state + type(sf_chain_instance_t), intent(in), target :: sf_chain + type(flavor_t), dimension(:), intent(in) :: f_beam, f_in, f_out + end subroutine connected_state_renew_flv_content_subevt +<>= + module subroutine connected_state_renew_flv_content_subevt & + (state, sf_chain, f_beam, f_in, f_out) + class(connected_state_t), intent(inout), target :: state + type(sf_chain_instance_t), intent(in), target :: sf_chain + type(flavor_t), dimension(:), intent(in) :: f_beam, f_in, f_out + integer :: n_beam, n_in, n_out, n_vir, n_tot, i, j + integer, dimension(:), allocatable :: i_beam, i_in, i_out + integer :: sf_out_i + type(interaction_t), pointer :: sf_int + sf_int => sf_chain%get_out_int_ptr () + n_beam = size (f_beam) + n_in = size (f_in) + n_out = size (f_out) + n_vir = state%trace%get_n_vir () + n_tot = state%trace%get_n_tot () + allocate (i_beam (n_beam), i_in (n_in), i_out (n_out)) + i_beam = [(i, i = 1, n_beam)] + do j = 1, n_in + sf_out_i = sf_chain%get_out_i (j) + i_in(j) = interaction_find_link & + (state%trace%interaction_t, sf_int, sf_out_i) + end do + i_out = [(i, i = n_vir + 1, n_tot)] + call state%expr%renew_flv_content_subevt (state%trace%interaction_t, & + i_beam, i_in, i_out, f_beam, f_in, f_out) + state%has_expr = .true. + end subroutine connected_state_renew_flv_content_subevt + +@ %def connected_state_setup_subevt @ Initialize the variable list specific for this state/term. We insert event variables ([[sqrts_hat]]) and link the process variable list. The variable list acquires pointers to subobjects of [[state]], which must therefore have a [[target]] attribute. <>= procedure :: setup_var_list => connected_state_setup_var_list <>= module subroutine connected_state_setup_var_list & (state, process_var_list, beam_data) class(connected_state_t), intent(inout), target :: state type(var_list_t), intent(in), target :: process_var_list type(beam_data_t), intent(in) :: beam_data end subroutine connected_state_setup_var_list <>= module subroutine connected_state_setup_var_list & (state, process_var_list, beam_data) class(connected_state_t), intent(inout), target :: state type(var_list_t), intent(in), target :: process_var_list type(beam_data_t), intent(in) :: beam_data call state%expr%setup_vars (beam_data%get_sqrts ()) call state%expr%link_var_list (process_var_list) end subroutine connected_state_setup_var_list @ %def connected_state_setup_var_list @ Allocate the cut expression etc. <>= procedure :: setup_cuts => connected_state_setup_cuts procedure :: setup_scale => connected_state_setup_scale procedure :: setup_fac_scale => connected_state_setup_fac_scale procedure :: setup_ren_scale => connected_state_setup_ren_scale procedure :: setup_weight => connected_state_setup_weight <>= module subroutine connected_state_setup_cuts (state, ef_cuts) class(connected_state_t), intent(inout), target :: state class(expr_factory_t), intent(in) :: ef_cuts end subroutine connected_state_setup_cuts module subroutine connected_state_setup_scale (state, ef_scale) class(connected_state_t), intent(inout), target :: state class(expr_factory_t), intent(in) :: ef_scale end subroutine connected_state_setup_scale module subroutine connected_state_setup_fac_scale (state, ef_fac_scale) class(connected_state_t), intent(inout), target :: state class(expr_factory_t), intent(in) :: ef_fac_scale end subroutine connected_state_setup_fac_scale module subroutine connected_state_setup_ren_scale (state, ef_ren_scale) class(connected_state_t), intent(inout), target :: state class(expr_factory_t), intent(in) :: ef_ren_scale end subroutine connected_state_setup_ren_scale module subroutine connected_state_setup_weight (state, ef_weight) class(connected_state_t), intent(inout), target :: state class(expr_factory_t), intent(in) :: ef_weight end subroutine connected_state_setup_weight <>= module subroutine connected_state_setup_cuts (state, ef_cuts) class(connected_state_t), intent(inout), target :: state class(expr_factory_t), intent(in) :: ef_cuts call state%expr%setup_selection (ef_cuts) end subroutine connected_state_setup_cuts module subroutine connected_state_setup_scale (state, ef_scale) class(connected_state_t), intent(inout), target :: state class(expr_factory_t), intent(in) :: ef_scale call state%expr%setup_scale (ef_scale) end subroutine connected_state_setup_scale module subroutine connected_state_setup_fac_scale (state, ef_fac_scale) class(connected_state_t), intent(inout), target :: state class(expr_factory_t), intent(in) :: ef_fac_scale call state%expr%setup_fac_scale (ef_fac_scale) end subroutine connected_state_setup_fac_scale module subroutine connected_state_setup_ren_scale (state, ef_ren_scale) class(connected_state_t), intent(inout), target :: state class(expr_factory_t), intent(in) :: ef_ren_scale call state%expr%setup_ren_scale (ef_ren_scale) end subroutine connected_state_setup_ren_scale module subroutine connected_state_setup_weight (state, ef_weight) class(connected_state_t), intent(inout), target :: state class(expr_factory_t), intent(in) :: ef_weight call state%expr%setup_weight (ef_weight) end subroutine connected_state_setup_weight @ %def connected_state_setup_expressions @ Reset the expression object: invalidate the subevt. <>= procedure :: reset_expressions => connected_state_reset_expressions <>= module subroutine connected_state_reset_expressions (state) class(connected_state_t), intent(inout) :: state end subroutine connected_state_reset_expressions <>= module subroutine connected_state_reset_expressions (state) class(connected_state_t), intent(inout) :: state if (state%has_expr) call state%expr%reset_contents () end subroutine connected_state_reset_expressions @ %def connected_state_reset_expressions @ \subsection{Evaluation} Transfer momenta to the trace evaluator and fill the [[subevt]] with this effective kinematics, if applicable. Note: we may want to apply a boost for the [[subevt]]. <>= procedure :: receive_kinematics => parton_state_receive_kinematics <>= module subroutine parton_state_receive_kinematics (state) class(parton_state_t), intent(inout), target :: state end subroutine parton_state_receive_kinematics <>= module subroutine parton_state_receive_kinematics (state) class(parton_state_t), intent(inout), target :: state if (state%has_trace) then call state%trace%receive_momenta () select type (state) class is (connected_state_t) if (state%has_expr) then call state%expr%fill_subevt (state%trace%interaction_t) end if end select end if end subroutine parton_state_receive_kinematics @ %def parton_state_receive_kinematics @ Recover kinematics: We assume that the trace evaluator is filled with momenta. Send those momenta back to the sources, then fill the variables and subevent as above. The incoming momenta of the connected state are not connected to the isolated state but to the beam interaction. Therefore, the incoming momenta within the isolated state do not become defined, yet. Instead, we reconstruct the beam (and ISR) momentum configuration. <>= procedure :: send_kinematics => parton_state_send_kinematics <>= module subroutine parton_state_send_kinematics (state) class(parton_state_t), intent(inout), target :: state end subroutine parton_state_send_kinematics <>= module subroutine parton_state_send_kinematics (state) class(parton_state_t), intent(inout), target :: state if (state%has_trace) then call state%trace%send_momenta () select type (state) class is (connected_state_t) call state%expr%fill_subevt (state%trace%interaction_t) end select end if end subroutine parton_state_send_kinematics @ %def parton_state_send_kinematics @ Evaluate the expressions. The routine evaluates first the cut expression. If the event passes, it evaluates the other expressions. Where no expressions are defined, default values are inserted. <>= procedure :: evaluate_expressions => connected_state_evaluate_expressions <>= module subroutine connected_state_evaluate_expressions (state, passed, & scale, fac_scale, ren_scale, weight, scale_forced, force_evaluation) class(connected_state_t), intent(inout) :: state logical, intent(out) :: passed real(default), intent(out) :: scale, weight real(default), intent(out), allocatable :: fac_scale, ren_scale real(default), intent(in), allocatable, optional :: scale_forced logical, intent(in), optional :: force_evaluation end subroutine connected_state_evaluate_expressions <>= module subroutine connected_state_evaluate_expressions (state, passed, & scale, fac_scale, ren_scale, weight, scale_forced, force_evaluation) class(connected_state_t), intent(inout) :: state logical, intent(out) :: passed real(default), intent(out) :: scale, weight real(default), intent(out), allocatable :: fac_scale, ren_scale real(default), intent(in), allocatable, optional :: scale_forced logical, intent(in), optional :: force_evaluation if (state%has_expr) then call state%expr%evaluate (passed, scale, fac_scale, ren_scale, weight, & scale_forced, force_evaluation) end if end subroutine connected_state_evaluate_expressions @ %def connected_state_evaluate_expressions @ Evaluate the structure-function chain, if it is allocated explicitly. The argument is the factorization scale. If the chain is merely a pointer, the chain should already be evaluated at this point. <>= procedure :: evaluate_sf_chain => isolated_state_evaluate_sf_chain <>= module subroutine isolated_state_evaluate_sf_chain (state, fac_scale) class(isolated_state_t), intent(inout) :: state real(default), intent(in) :: fac_scale end subroutine isolated_state_evaluate_sf_chain <>= module subroutine isolated_state_evaluate_sf_chain (state, fac_scale) class(isolated_state_t), intent(inout) :: state real(default), intent(in) :: fac_scale if (state%sf_chain_is_allocated) & call state%sf_chain_eff%evaluate (fac_scale) end subroutine isolated_state_evaluate_sf_chain @ %def isolated_state_evaluate_sf_chain @ Evaluate the trace. <>= procedure :: evaluate_trace => parton_state_evaluate_trace <>= module subroutine parton_state_evaluate_trace (state) class(parton_state_t), intent(inout) :: state end subroutine parton_state_evaluate_trace <>= module subroutine parton_state_evaluate_trace (state) class(parton_state_t), intent(inout) :: state if (state%has_trace) call state%trace%evaluate () end subroutine parton_state_evaluate_trace @ %def parton_state_evaluate_trace <>= procedure :: evaluate_matrix => parton_state_evaluate_matrix <>= module subroutine parton_state_evaluate_matrix (state) class(parton_state_t), intent(inout) :: state end subroutine parton_state_evaluate_matrix <>= module subroutine parton_state_evaluate_matrix (state) class(parton_state_t), intent(inout) :: state if (state%has_matrix) call state%matrix%evaluate () end subroutine parton_state_evaluate_matrix @ %def parton_state_evaluate_matrix @ Evaluate the extra evaluators that we need for physical events. <>= procedure :: evaluate_event_data => parton_state_evaluate_event_data <>= module subroutine parton_state_evaluate_event_data (state, only_momenta) class(parton_state_t), intent(inout) :: state logical, intent(in), optional :: only_momenta end subroutine parton_state_evaluate_event_data <>= module subroutine parton_state_evaluate_event_data (state, only_momenta) class(parton_state_t), intent(inout) :: state logical, intent(in), optional :: only_momenta logical :: only_mom only_mom = .false.; if (present (only_momenta)) only_mom = only_momenta select type (state) type is (connected_state_t) if (state%has_flows_sf) then call state%flows_sf%receive_momenta () if (.not. only_mom) call state%flows_sf%evaluate () end if end select if (state%has_matrix) then call state%matrix%receive_momenta () if (.not. only_mom) call state%matrix%evaluate () end if if (state%has_flows) then call state%flows%receive_momenta () if (.not. only_mom) call state%flows%evaluate () end if end subroutine parton_state_evaluate_event_data @ %def parton_state_evaluate_event_data @ Normalize the helicity density matrix by its trace, i.e., factor out the trace and put it into an overall normalization factor. The trace and flow evaluators are unchanged. <>= procedure :: normalize_matrix_by_trace => & parton_state_normalize_matrix_by_trace <>= module subroutine parton_state_normalize_matrix_by_trace (state) class(parton_state_t), intent(inout) :: state end subroutine parton_state_normalize_matrix_by_trace <>= module subroutine parton_state_normalize_matrix_by_trace (state) class(parton_state_t), intent(inout) :: state if (state%has_matrix) call state%matrix%normalize_by_trace () end subroutine parton_state_normalize_matrix_by_trace @ %def parton_state_normalize_matrix_by_trace @ \subsection{Accessing the state} Three functions return a pointer to the event-relevant interactions. <>= procedure :: get_trace_int_ptr => parton_state_get_trace_int_ptr procedure :: get_matrix_int_ptr => parton_state_get_matrix_int_ptr procedure :: get_flows_int_ptr => parton_state_get_flows_int_ptr <>= module function parton_state_get_trace_int_ptr (state) result (ptr) class(parton_state_t), intent(in), target :: state type(interaction_t), pointer :: ptr end function parton_state_get_trace_int_ptr module function parton_state_get_matrix_int_ptr (state) result (ptr) class(parton_state_t), intent(in), target :: state type(interaction_t), pointer :: ptr end function parton_state_get_matrix_int_ptr module function parton_state_get_flows_int_ptr (state) result (ptr) class(parton_state_t), intent(in), target :: state type(interaction_t), pointer :: ptr end function parton_state_get_flows_int_ptr <>= module function parton_state_get_trace_int_ptr (state) result (ptr) class(parton_state_t), intent(in), target :: state type(interaction_t), pointer :: ptr if (state%has_trace) then ptr => state%trace%interaction_t else ptr => null () end if end function parton_state_get_trace_int_ptr module function parton_state_get_matrix_int_ptr (state) result (ptr) class(parton_state_t), intent(in), target :: state type(interaction_t), pointer :: ptr if (state%has_matrix) then ptr => state%matrix%interaction_t else ptr => null () end if end function parton_state_get_matrix_int_ptr module function parton_state_get_flows_int_ptr (state) result (ptr) class(parton_state_t), intent(in), target :: state type(interaction_t), pointer :: ptr if (state%has_flows) then ptr => state%flows%interaction_t else ptr => null () end if end function parton_state_get_flows_int_ptr @ %def parton_state_get_trace_int_ptr @ %def parton_state_get_matrix_int_ptr @ %def parton_state_get_flows_int_ptr @ Return the indices of the beam particles and the outgoing particles within the trace (and thus, matrix and flows) evaluator, respectively. <>= procedure :: get_beam_index => connected_state_get_beam_index procedure :: get_in_index => connected_state_get_in_index <>= module subroutine connected_state_get_beam_index (state, i_beam) class(connected_state_t), intent(in) :: state integer, dimension(:), intent(out) :: i_beam end subroutine connected_state_get_beam_index module subroutine connected_state_get_in_index (state, i_in) class(connected_state_t), intent(in) :: state integer, dimension(:), intent(out) :: i_in end subroutine connected_state_get_in_index <>= module subroutine connected_state_get_beam_index (state, i_beam) class(connected_state_t), intent(in) :: state integer, dimension(:), intent(out) :: i_beam call state%expr%get_beam_index (i_beam) end subroutine connected_state_get_beam_index module subroutine connected_state_get_in_index (state, i_in) class(connected_state_t), intent(in) :: state integer, dimension(:), intent(out) :: i_in call state%expr%get_in_index (i_in) end subroutine connected_state_get_in_index @ %def connected_state_get_beam_index @ %def connected_state_get_in_index @ <>= public :: refill_evaluator <>= module subroutine refill_evaluator (sqme, qn, flv_index, evaluator) complex(default), intent(in), dimension(:) :: sqme type(quantum_numbers_t), intent(in), dimension(:,:) :: qn integer, intent(in), dimension(:), optional :: flv_index type(evaluator_t), intent(inout) :: evaluator end subroutine refill_evaluator <>= module subroutine refill_evaluator (sqme, qn, flv_index, evaluator) complex(default), intent(in), dimension(:) :: sqme type(quantum_numbers_t), intent(in), dimension(:,:) :: qn integer, intent(in), dimension(:), optional :: flv_index type(evaluator_t), intent(inout) :: evaluator integer :: i, i_flv do i = 1, size (sqme) if (present (flv_index)) then i_flv = flv_index(i) else i_flv = i end if call evaluator%add_to_matrix_element (qn(:,i_flv), sqme(i), & match_only_flavor = .true.) end do end subroutine refill_evaluator @ %def refill_evaluator @ Return the number of outgoing (hard) particles for the state. <>= procedure :: get_n_out => parton_state_get_n_out <>= module function parton_state_get_n_out (state) result (n) class(parton_state_t), intent(in), target :: state integer :: n end function parton_state_get_n_out <>= module function parton_state_get_n_out (state) result (n) class(parton_state_t), intent(in), target :: state integer :: n n = state%trace%get_n_out () end function parton_state_get_n_out @ %def parton_state_get_n_out @ \subsection{Unit tests} <<[[parton_states_ut.f90]]>>= <> module parton_states_ut use unit_tests use parton_states_uti <> <> contains <> end module parton_states_ut @ %def parton_states_ut <<[[parton_states_uti.f90]]>>= <> module parton_states_uti <> <> use constants, only: zero use numeric_utils use flavors use colors use helicities use quantum_numbers use sf_base, only: sf_chain_instance_t use state_matrices, only: state_matrix_t use prc_template_me, only: prc_template_me_t use interactions, only: interaction_t use models, only: model_t, create_test_model use parton_states <> <> contains <> end module parton_states_uti @ %def parton_states_uti @ <>= public :: parton_states_test <>= subroutine parton_states_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine parton_states_test @ %def parton_states_test @ \subsubsection{Test a simple isolated state} <>= call test (parton_states_1, "parton_states_1", & "Create a 2 -> 2 isolated state and compute trace", & u, results) <>= public :: parton_states_1 <>= subroutine parton_states_1 (u) integer, intent(in) :: u type(state_matrix_t), allocatable :: state type(flavor_t), dimension(2) :: flv_in type(flavor_t), dimension(2) :: flv_out1, flv_out2 type(flavor_t), dimension(4) :: flv_tot type(helicity_t), dimension(4) :: hel type(color_t), dimension(4) :: col integer :: h1, h2, h3, h4 integer :: f integer :: i type(quantum_numbers_t), dimension(4) :: qn type(prc_template_me_t) :: core type(sf_chain_instance_t), target :: sf_chain type(interaction_t), target :: int type(isolated_state_t) :: isolated_state integer :: n_states = 0 integer, dimension(:), allocatable :: col_flow_index type(quantum_numbers_mask_t), dimension(2) :: qn_mask integer, dimension(8) :: i_allowed_states complex(default), dimension(8) :: me complex(default) :: me_check_tot, me_check_1, me_check_2, me2 logical :: tmp1, tmp2 type(model_t), pointer :: test_model => null () write (u, "(A)") "* Test output: parton_states_1" write (u, "(A)") "* Purpose: Test the standard parton states" write (u, "(A)") call flv_in%init ([11, -11]) call flv_out1%init ([1, -1]) call flv_out2%init ([2, -2]) write (u, "(A)") "* Using incoming flavors: " call flavor_write_array (flv_in, u) write (u, "(A)") "* Two outgoing flavor structures: " call flavor_write_array (flv_out1, u) call flavor_write_array (flv_out2, u) write (u, "(A)") "* Initialize state matrix" allocate (state) call state%init () write (u, "(A)") "* Fill state matrix" call col(3)%init ([1]) call col(4)%init ([-1]) do f = 1, 2 do h1 = -1, 1, 2 do h2 = -1, 1, 2 do h3 = -1, 1, 2 do h4 = -1, 1, 2 n_states = n_states + 1 call hel%init ([h1, h2, h3, h4], [h1, h2, h3, h4]) if (f == 1) then flv_tot = [flv_in, flv_out1] else flv_tot = [flv_in, flv_out2] end if call qn%init (flv_tot, col, hel) call state%add_state (qn) end do end do end do end do end do !!! Two flavors, one color flow, 2 x 2 x 2 x 2 helicity configurations !!! -> 32 states. write (u, "(A)") write (u, "(A,I2)") "* Generated number of states: ", n_states call state%freeze () !!! Indices of the helicity configurations which are non-zero i_allowed_states = [6, 7, 10, 11, 22, 23, 26, 27] me = [cmplx (-1.89448E-5_default, 9.94456E-7_default, default), & cmplx (-8.37887E-2_default, 4.30842E-3_default, default), & cmplx (-1.99997E-1_default, -1.01985E-2_default, default), & cmplx ( 1.79717E-5_default, 9.27038E-7_default, default), & cmplx (-1.74859E-5_default, 8.78819E-7_default, default), & cmplx ( 1.67577E-1_default, -8.61683E-3_default, default), & cmplx ( 2.41331E-1_default, 1.23306E-2_default, default), & cmplx (-3.59435E-5_default, -1.85407E-6_default, default)] me_check_tot = cmplx (zero, zero, default) me_check_1 = cmplx (zero, zero, default) me_check_2 = cmplx (zero, zero, default) do i = 1, 8 me2 = me(i) * conjg (me(i)) me_check_tot = me_check_tot + me2 if (i < 5) then me_check_1 = me_check_1 + me2 else me_check_2 = me_check_2 + me2 end if call state%set_matrix_element (i_allowed_states(i), me(i)) end do !!! Do not forget the color factor me_check_tot = 3._default * me_check_tot me_check_1 = 3._default * me_check_1 me_check_2 = 3._default * me_check_2 write (u, "(A)") write (u, "(A)") "* Setup interaction" call int%basic_init (2, 0, 2, set_relations = .true.) call int%set_state_matrix (state) core%data%n_in = 2; core%data%n_out = 2 core%data%n_flv = 2 allocate (core%data%flv_state (4, 2)) core%data%flv_state (1, :) = [11, 11] core%data%flv_state (2, :) = [-11, -11] core%data%flv_state (3, :) = [1, 2] core%data%flv_state (4, :) = [-1, -2] core%use_color_factors = .false. core%nc = 3 write (u, "(A)") "* Init isolated state" call isolated_state%init (sf_chain, int) !!! There is only one color flow. allocate (col_flow_index (n_states)); col_flow_index = 1 call qn_mask%init (.false., .false., .true., mask_cg = .false.) write (u, "(A)") "* Give a trace to the isolated state" call isolated_state%setup_square_trace (core, qn_mask, col_flow_index, .false.) call isolated_state%evaluate_trace () write (u, "(A)") write (u, "(A)", advance = "no") "* Squared matrix element correct: " write (u, "(L1)") nearly_equal (me_check_tot, & isolated_state%trace%get_matrix_element (1), rel_smallness = 0.00001_default) write (u, "(A)") "* Give a matrix to the isolated state" call create_test_model (var_str ("SM"), test_model) call isolated_state%setup_square_matrix (core, test_model, qn_mask, col_flow_index) call isolated_state%evaluate_matrix () write (u, "(A)") "* Sub-matrixelements correct: " tmp1 = nearly_equal (me_check_1, & isolated_state%matrix%get_matrix_element (1), rel_smallness = 0.00001_default) tmp2 = nearly_equal (me_check_2, & isolated_state%matrix%get_matrix_element (2), rel_smallness = 0.00001_default) write (u, "(A,L1,A,L1)") "* 1: ", tmp1, ", 2: ", tmp2 write (u, "(A)") "* Test output end: parton_states_1" end subroutine parton_states_1 @ %def parton_states_1 @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Process component management} This module contains tools for managing and combining process components and matrix-element code and values, acting at a level below the actual process definition. \subsection{Abstract base type} The types introduced here are abstract base types. <<[[pcm_base.f90]]>>= <> module pcm_base <> <> use os_interface, only: os_data_t use process_libraries, only: process_library_t use prc_core_def use prc_core use variables, only: var_list_t use mappings, only: mapping_defaults_t use phs_base, only: phs_config_t use phs_forests, only: phs_parameters_t use mci_base, only: mci_t use model_data, only: model_data_t use models, only: model_t use blha_config, only: blha_master_t use blha_olp_interfaces, only: blha_template_t use process_config use process_mci, only: process_mci_entry_t <> <> <> <> <> interface <> end interface end module pcm_base @ %def pcm_base @ <<[[pcm_base_sub.f90]]>>= <> submodule (pcm_base) pcm_base_s use io_units use diagnostics use format_utils, only: write_integer_array use format_utils, only: write_separator use physics_defs, only: BORN, NLO_REAL implicit none contains <> end submodule pcm_base_s @ %def pcm_base_s @ \subsection{Core management} This object holds information about the cores used by the components and allocates the corresponding manager instance. [[i_component]] is the index of the process component which this core belongs to. The pointer to the core definition is a convenient help in configuring the core itself. We allow for a [[blha_config]] configuration object that covers BLHA cores. The BLHA standard is suitable generic to warrant support outside of specific type extension (i.e., applies to LO and NLO if requested). The BLHA configuration is allocated only if the core requires it. <>= public :: core_entry_t <>= type :: core_entry_t integer :: i_component = 0 logical :: active = .false. class(prc_core_def_t), pointer :: core_def => null () type(blha_template_t), allocatable :: blha_config class(prc_core_t), allocatable :: core contains <> end type core_entry_t @ %def core_entry_t @ <>= procedure :: get_core_ptr => core_entry_get_core_ptr <>= module function core_entry_get_core_ptr (core_entry) result (core) class(core_entry_t), intent(in), target :: core_entry class(prc_core_t), pointer :: core end function core_entry_get_core_ptr <>= module function core_entry_get_core_ptr (core_entry) result (core) class(core_entry_t), intent(in), target :: core_entry class(prc_core_t), pointer :: core if (allocated (core_entry%core)) then core => core_entry%core else core => null () end if end function core_entry_get_core_ptr @ %def core_entry_get_core_ptr @ Configure the core object after allocation with correct type. The [[core_def]] object pointer and the index [[i_component]] of the associated process component are already there. <>= procedure :: configure => core_entry_configure <>= module subroutine core_entry_configure (core_entry, lib, id) class(core_entry_t), intent(inout) :: core_entry type(process_library_t), intent(in), target :: lib type(string_t), intent(in) :: id end subroutine core_entry_configure <>= module subroutine core_entry_configure (core_entry, lib, id) class(core_entry_t), intent(inout) :: core_entry type(process_library_t), intent(in), target :: lib type(string_t), intent(in) :: id call core_entry%core%init & (core_entry%core_def, lib, id, core_entry%i_component) end subroutine core_entry_configure @ %def core_entry_configure @ \subsection{Process component manager} The process-component manager [[pcm]] is the master component of the [[process_t]] object. It serves two purposes: \begin{enumerate} \item It holds configuration data which allow us to centrally manage the components, terms, etc.\ of the process object. \item It implements the methods that realize the algorithm for constructing the process object and computing an integral. This algorithm makes use of the data stored within [[pcm]]. \end{enumerate} To this end, the object is abstract and polymorphic. The two extensions that we support, implement (a) default tree-level calculation, optionally including a sum over sub-processes with different particle content, or (b) the FKS-NLO subtraction algorithm for QCD-corrected processes. In both cases, the type extensions may hold suitable further data. Data included in the base type: The number of components determines the [[component_selected]] array. [[i_phs_config]] is a lookup table that holds the PHS configuration index for a given component index. [[i_core]] is a lookup table that holds the core-entry index for a given component index. [[i_mci]] is a lookup table that holds the integrator (MCI) index for a given component index. <>= public :: pcm_t <>= type, abstract :: pcm_t logical :: initialized = .false. logical :: has_pdfs = .false. integer :: n_components = 0 integer :: n_cores = 0 integer :: n_mci = 0 logical, dimension(:), allocatable :: component_selected logical, dimension(:), allocatable :: component_active integer, dimension(:), allocatable :: i_phs_config integer, dimension(:), allocatable :: i_core integer, dimension(:), allocatable :: i_mci type(blha_template_t) :: blha_defaults logical :: uses_blha = .false. type(os_data_t) :: os_data contains <> end type pcm_t @ %def pcm_t @ The factory method. We use the [[inout]] intent, so calling this again is an error. <>= procedure(pcm_allocate_workspace), deferred :: allocate_workspace <>= abstract interface subroutine pcm_allocate_workspace (pcm, work) import class(pcm_t), intent(in) :: pcm class(pcm_workspace_t), intent(inout), allocatable :: work end subroutine pcm_allocate_workspace end interface @ %def pcm_allocate_workspace @ <>= procedure(pcm_is_nlo), deferred :: is_nlo <>= abstract interface function pcm_is_nlo (pcm) result (is_nlo) import logical :: is_nlo class(pcm_t), intent(in) :: pcm end function pcm_is_nlo end interface @ %def pcm_is_nlo @ <>= procedure(pcm_final), deferred :: final <>= abstract interface subroutine pcm_final (pcm) import class(pcm_t), intent(inout) :: pcm end subroutine pcm_final end interface @ %def pcm_final @ \subsection{Initialization methods} The PCM has the duty to coordinate and configure the process-object components. Initialize the PCM configuration itself, using environment data. <>= procedure(pcm_init), deferred :: init <>= abstract interface subroutine pcm_init (pcm, env, meta) import class(pcm_t), intent(out) :: pcm type(process_environment_t), intent(in) :: env type(process_metadata_t), intent(in) :: meta end subroutine pcm_init end interface @ %def pcm_init @ Initialize the BLHA configuration block, the component-independent default settings. This is to be called by [[pcm_init]]. We use the provided variable list. This block is filled regardless of whether BLHA is actually used, because why not? We use a default value for the scheme (not set in unit tests). <>= procedure :: set_blha_defaults => pcm_set_blha_defaults <>= module subroutine pcm_set_blha_defaults (pcm, polarized_beams, var_list) class(pcm_t), intent(inout) :: pcm type(var_list_t), intent(in) :: var_list logical, intent(in) :: polarized_beams end subroutine pcm_set_blha_defaults <>= module subroutine pcm_set_blha_defaults (pcm, polarized_beams, var_list) class(pcm_t), intent(inout) :: pcm type(var_list_t), intent(in) :: var_list logical, intent(in) :: polarized_beams logical :: muon_yukawa_off real(default) :: top_yukawa type(string_t) :: ew_scheme muon_yukawa_off = & var_list%get_lval (var_str ("?openloops_switch_off_muon_yukawa")) top_yukawa = & var_list%get_rval (var_str ("blha_top_yukawa")) ew_scheme = & var_list%get_sval (var_str ("$blha_ew_scheme")) if (ew_scheme == "") ew_scheme = "Gmu" call pcm%blha_defaults%init & (polarized_beams, muon_yukawa_off, top_yukawa, ew_scheme) end subroutine pcm_set_blha_defaults @ %def pcm_set_blha_defaults @ Read the method settings from the variable list and store them in the BLHA master. The details depend on the [[pcm]] concrete type. <>= procedure(pcm_set_blha_methods), deferred :: set_blha_methods <>= abstract interface subroutine pcm_set_blha_methods (pcm, blha_master, var_list) import class(pcm_t), intent(inout) :: pcm type(blha_master_t), intent(inout) :: blha_master type(var_list_t), intent(in) :: var_list end subroutine pcm_set_blha_methods end interface @ %def pcm_set_blha_methods @ Produce the LO and NLO flavor-state tables (as far as available), as appropriate for BLHA configuration. We may inspect either the PCM itself or the array of process cores. <>= procedure(pcm_get_blha_flv_states), deferred :: get_blha_flv_states <>= abstract interface subroutine pcm_get_blha_flv_states (pcm, core_entry, flv_born, flv_real) import class(pcm_t), intent(in) :: pcm type(core_entry_t), dimension(:), intent(in) :: core_entry integer, dimension(:,:), allocatable, intent(out) :: flv_born integer, dimension(:,:), allocatable, intent(out) :: flv_real end subroutine pcm_get_blha_flv_states end interface @ %def pcm_get_blha_flv_states @ Allocate the right number of process components. The number is also stored in the process meta. Initially, all components are active but none are selected. <>= procedure :: allocate_components => pcm_allocate_components <>= module subroutine pcm_allocate_components (pcm, comp, meta) class(pcm_t), intent(inout) :: pcm type(process_component_t), dimension(:), allocatable, intent(out) :: comp type(process_metadata_t), intent(in) :: meta end subroutine pcm_allocate_components <>= module subroutine pcm_allocate_components (pcm, comp, meta) class(pcm_t), intent(inout) :: pcm type(process_component_t), dimension(:), allocatable, intent(out) :: comp type(process_metadata_t), intent(in) :: meta pcm%n_components = meta%n_components allocate (comp (pcm%n_components)) allocate (pcm%component_selected (pcm%n_components), source = .false.) allocate (pcm%component_active (pcm%n_components), source = .true.) end subroutine pcm_allocate_components @ %def pcm_allocate_components @ Each process component belongs to a category/type, which we identify by a universal integer constant. The categories can be taken from the process definition. For easy lookup, we store the categories in an array. <>= procedure(pcm_categorize_components), deferred :: categorize_components <>= abstract interface subroutine pcm_categorize_components (pcm, config) import class(pcm_t), intent(inout) :: pcm type(process_config_data_t), intent(in) :: config end subroutine pcm_categorize_components end interface @ %def pcm_categorize_components @ Allocate the right number and type(s) of process-core objects, i.e., the interface object between the process and matrix-element code. Within the [[pcm]] block, also associate cores with components and store relevant configuration data, including the [[i_core]] lookup table. <>= procedure(pcm_allocate_cores), deferred :: allocate_cores <>= abstract interface subroutine pcm_allocate_cores (pcm, config, core_entry) import class(pcm_t), intent(inout) :: pcm type(process_config_data_t), intent(in) :: config type(core_entry_t), dimension(:), allocatable, intent(out) :: core_entry end subroutine pcm_allocate_cores end interface @ %def pcm_allocate_cores @ Generate and interface external code for a single core, if this is required. <>= procedure(pcm_prepare_any_external_code), deferred :: & prepare_any_external_code <>= abstract interface subroutine pcm_prepare_any_external_code & (pcm, core_entry, i_core, libname, model, var_list) import class(pcm_t), intent(in) :: pcm type(core_entry_t), intent(inout) :: core_entry integer, intent(in) :: i_core type(string_t), intent(in) :: libname type(model_data_t), intent(in), target :: model type(var_list_t), intent(in) :: var_list end subroutine pcm_prepare_any_external_code end interface @ %def pcm_prepare_any_external_code @ Prepare the BLHA configuration for a core object that requires it. This does not affect the core object, which may not yet be allocated. <>= procedure(pcm_setup_blha), deferred :: setup_blha <>= abstract interface subroutine pcm_setup_blha (pcm, core_entry) import class(pcm_t), intent(in) :: pcm type(core_entry_t), intent(inout) :: core_entry end subroutine pcm_setup_blha end interface @ %def pcm_setup_blha @ Configure the BLHA interface for a core object that requires it. This is separate from the previous method, assuming that the [[pcm]] has to allocate the actual cores and acquire some data in-between. <>= procedure(pcm_prepare_blha_core), deferred :: prepare_blha_core <>= abstract interface subroutine pcm_prepare_blha_core (pcm, core_entry, model) import class(pcm_t), intent(in) :: pcm type(core_entry_t), intent(inout) :: core_entry class(model_data_t), intent(in), target :: model end subroutine pcm_prepare_blha_core end interface @ %def pcm_prepare_blha_core @ Allocate and configure the MCI (multi-channel integrator) records and their relation to process components, appropriate for the algorithm implemented by [[pcm]]. Create a [[mci_t]] template: the procedure [[dispatch_mci]] is called as a factory method for allocating the [[mci_t]] object with a specific concrete type. The call may depend on the concrete [[pcm]] type. <>= public :: dispatch_mci_proc <>= abstract interface subroutine dispatch_mci_proc (mci, var_list, process_id, is_nlo) import 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 end subroutine dispatch_mci_proc end interface @ %def dispatch_mci_proc <>= procedure(pcm_setup_mci), deferred :: setup_mci procedure(pcm_call_dispatch_mci), deferred :: call_dispatch_mci <>= abstract interface subroutine pcm_setup_mci (pcm, mci_entry) import class(pcm_t), intent(inout) :: pcm type(process_mci_entry_t), & dimension(:), allocatable, intent(out) :: mci_entry end subroutine pcm_setup_mci end interface abstract interface subroutine pcm_call_dispatch_mci (pcm, & dispatch_mci, var_list, process_id, mci_template) import class(pcm_t), intent(inout) :: pcm procedure(dispatch_mci_proc) :: dispatch_mci type(var_list_t), intent(in) :: var_list type(string_t), intent(in) :: process_id class(mci_t), intent(out), allocatable :: mci_template end subroutine pcm_call_dispatch_mci end interface @ %def pcm_setup_mci @ %def pcm_call_dispatch_mci @ Proceed with PCM configuration based on the core and component configuration data. Base version is empty. <>= procedure(pcm_complete_setup), deferred :: complete_setup <>= abstract interface subroutine pcm_complete_setup (pcm, core_entry, component, model) import class(pcm_t), intent(inout) :: pcm type(core_entry_t), dimension(:), intent(in) :: core_entry type(process_component_t), dimension(:), intent(inout) :: component type(model_t), intent(in), target :: model end subroutine pcm_complete_setup end interface @ %def pcm_complete_setup @ \subsubsection{Retrieve information} Return the core index that belongs to a particular component. <>= procedure :: get_i_core => pcm_get_i_core <>= module function pcm_get_i_core (pcm, i_component) result (i_core) class(pcm_t), intent(in) :: pcm integer, intent(in) :: i_component integer :: i_core end function pcm_get_i_core <>= module function pcm_get_i_core (pcm, i_component) result (i_core) class(pcm_t), intent(in) :: pcm integer, intent(in) :: i_component integer :: i_core if (allocated (pcm%i_core)) then i_core = pcm%i_core(i_component) else i_core = 0 end if end function pcm_get_i_core @ %def pcm_get_i_core @ \subsubsection{Phase-space configuration} Allocate and initialize the right number and type(s) of phase-space configuration entries. The [[i_phs_config]] lookup table must be set accordingly. <>= procedure(pcm_init_phs_config), deferred :: init_phs_config <>= abstract interface subroutine pcm_init_phs_config & (pcm, phs_entry, meta, env, phs_par, mapping_defs) import class(pcm_t), intent(inout) :: pcm type(process_phs_config_t), & dimension(:), allocatable, intent(out) :: phs_entry type(process_metadata_t), intent(in) :: meta type(process_environment_t), intent(in) :: env type(mapping_defaults_t), intent(in) :: mapping_defs type(phs_parameters_t), intent(in) :: phs_par end subroutine pcm_init_phs_config end interface @ %def pcm_init_phs_config @ Initialize a single component. We require all process-configuration blocks, and specific templates for the phase-space and integrator configuration. We also provide the current component index [[i]] and the [[active]] flag. <>= procedure(pcm_init_component), deferred :: init_component <>= abstract interface subroutine pcm_init_component & (pcm, component, i, active, phs_config, env, meta, config) import class(pcm_t), intent(in) :: pcm type(process_component_t), intent(out) :: component integer, intent(in) :: i logical, intent(in) :: active class(phs_config_t), allocatable, intent(in) :: phs_config type(process_environment_t), intent(in) :: env type(process_metadata_t), intent(in) :: meta type(process_config_data_t), intent(in) :: config end subroutine pcm_init_component end interface @ %def pcm_init_component @ Record components in the process [[meta]] data if they have turned out to be inactive. <>= procedure :: record_inactive_components => pcm_record_inactive_components <>= module subroutine pcm_record_inactive_components (pcm, component, meta) class(pcm_t), intent(inout) :: pcm type(process_component_t), dimension(:), intent(in) :: component type(process_metadata_t), intent(inout) :: meta end subroutine pcm_record_inactive_components <>= module subroutine pcm_record_inactive_components (pcm, component, meta) class(pcm_t), intent(inout) :: pcm type(process_component_t), dimension(:), intent(in) :: component type(process_metadata_t), intent(inout) :: meta integer :: i pcm%component_active = component%active do i = 1, pcm%n_components if (.not. component(i)%active) call meta%deactivate_component (i) end do end subroutine pcm_record_inactive_components @ %def pcm_record_inactive_components @ \subsection{Manager workspace} This object deals with the actual (squared) matrix element values. It holds any central data that are generated and/or used when calculating a particular phase-space point. Since phase-space points are associated with an integrator, we expect the instances of this type to correspond to MCI instances. <>= public :: pcm_workspace_t <>= type, abstract :: pcm_workspace_t ! class(pcm_t), pointer :: config => null () logical :: bad_point = .false. contains <> end type pcm_workspace_t @ %def pcm_workspace_t @ <>= procedure(pcm_work_final), deferred :: final <>= abstract interface subroutine pcm_work_final (pcm_work) import class(pcm_workspace_t), intent(inout) :: pcm_work end subroutine pcm_work_final end interface @ %def pcm_work_final @ <>= procedure(pcm_work_is_nlo), deferred :: is_nlo <>= abstract interface function pcm_work_is_nlo (pcm_work) result (is_nlo) import logical :: is_nlo class(pcm_workspace_t), intent(inout) :: pcm_work end function pcm_work_is_nlo end interface @ %def pcm_work_is_nlo @ <>= procedure :: link_config => pcm_work_link_config <>= subroutine pcm_work_link_config (pcm_work, config) class(pcm_workspace_t), intent(inout) :: pcm_work class(pcm_t), intent(in), target :: config pcm_work%config => config end subroutine pcm_work_link_config @ %def pcm_work_link_config @ <>= procedure :: is_valid => pcm_work_is_valid <>= module function pcm_work_is_valid (pcm_work) result (valid) logical :: valid class(pcm_workspace_t), intent(in) :: pcm_work end function pcm_work_is_valid <>= module function pcm_work_is_valid (pcm_work) result (valid) logical :: valid class(pcm_workspace_t), intent(in) :: pcm_work valid = .not. pcm_work%bad_point end function pcm_work_is_valid @ %def pcm_work_is_valid @ <>= procedure :: set_bad_point => pcm_work_set_bad_point <>= pure module subroutine pcm_work_set_bad_point (pcm_work, bad_point) class(pcm_workspace_t), intent(inout) :: pcm_work logical, intent(in) :: bad_point end subroutine pcm_work_set_bad_point <>= pure module subroutine pcm_work_set_bad_point (pcm_work, bad_point) class(pcm_workspace_t), intent(inout) :: pcm_work logical, intent(in) :: bad_point pcm_work%bad_point = pcm_work%bad_point .or. bad_point end subroutine pcm_work_set_bad_point @ %def pcm_work_set_bad_point @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{The process object} <<[[process.f90]]>>= <> module process <> <> <> use diagnostics use lorentz use rng_base use dispatch_rng, only: dispatch_rng_factory use dispatch_rng, only: update_rng_seed_in_var_list use os_interface use sm_qcd use mci_base use flavors use model_data use models use process_libraries use process_constants use variables use beam_structures use beams use pdg_arrays use expr_base use sf_base use sf_mappings use resonances, only: resonance_history_t, resonance_history_set_t use prc_test_core, only: test_t use prc_core_def, only: prc_core_def_t use prc_core, only: prc_core_t, helicity_selection_t use phs_base use parton_states, only: connected_state_t use pcm_base use pcm use process_counter use process_config use process_mci <> <> <> <> interface <> end interface contains <> end module process @ %def process @ <<[[process_sub.f90]]>>= <> submodule (process) process_s use io_units use format_utils, only: write_separator use constants use numeric_utils use cputime use md5 use integration_results use physics_defs use interactions use particles use dispatch_phase_space, only: dispatch_phs use prc_external, only: prc_external_t use prc_recola, only: prc_recola_t use blha_olp_interfaces, only: prc_blha_t, blha_template_t use prc_threshold, only: prc_threshold_t use phs_fks, only: phs_fks_config_t use mappings, only: mapping_defaults_t use phs_forests, only: phs_parameters_t use phs_wood, only: phs_wood_config_t use blha_config, only: blha_master_t implicit none contains <> end submodule process_s @ %def process_s @ \subsection{Process status} Store counter and status information in a process object. <>= type :: process_status_t private end type process_status_t @ %def process_status_t @ \subsection{Process status} Store integration results in a process object. <>= type :: process_results_t private end type process_results_t @ %def process_results_t @ \subsection{The process type} NOTE: The description below represents the intended structure after refactoring and disentangling the FKS-NLO vs. LO algorithm dependencies. A [[process]] object is the internal representation of integration-run methods and data, as they are controlled by the user via a Sindarin script. The process object provides access to matrix elements (the actual ``process'' definitions that the user has provided before), it defines the separation into individually integrable components, and it manages phase-space construction, the actual integration over phase space, and the accumulation of results. As a workspace for individual sampling calls, we introduce an associated [[process_instance]] object type elsewhere. The [[process]] object contains data that either define the configuration or accumulate results from a complete integration pass. After successful phase-space integration, subsequent event generation is not actually represented by the [[process]] object. However, any event generation refers to an existing [[process]] object which represents a specific integration pass, and it uses a fresh [[process_instance]] workspace for calculations. The process object consists of several subobjects with their specific purposes. The corresponding types are defined below. (Technically, the subobject type definitions have to come before the process type definition, but with NOWEB magic we reverse this order here.) The [[meta]] object describes the process globally. All contents become fixed when the object is initialized. Similarly, the [[env]] component captures the (Sindarin) environment at the point where the process object is initialized. The [[config]] object holds physical and technical configuration data that are collected and derived from the environment during process initialization, and which are common to all process components. The [[pcm]] object (process-component manager) is polymorphic. This is an object which holds data which represent the process-object structure and breakdown, and it contains the methods that implement the algorithm of managing this structure, accumulating partial results, and finally collecting the pieces. Depending on the generic process type, the contents of [[pcm]] do vary. In particular, there is some base-type data content and a simple (default) extension which is designed for traditional \oMega\ matrix elements and tree-level integration, possibly with several sub-processes to sum over. The second extension is designed for the FKS phase-space and subtraction algorithm for NLO QCD, which interfaces external one-loop providers. The [[component]] subobjects are, first of all, interfaces to the original process-component definitions that have been provided by the user, which the program has already taken to produce matrix-element code and interfaces. The management of those components is deferred by [[pcm]], which contains the information that defines the role of each component. In particular, in the default (LO) version, process components correspond to distinct particle combinations which have been included in the original process definition. In the FKS-NLO version, the breakdown of a NLO process into Born, real, virtual, etc.\ components determines the setup. The [[phs_config]] subobjects hold data that allow and implement the construction of phase-space configurations. The type [[process_phs_config_t]] is a wrapper type around the concrete polymorphic [[phs_config_t]] object type, which manages phase-space construction, including some bookkeeping required for setting up multi-channel integration. In the LO case, we expect a separate entry for each independent sub-process. For the FKS-NLO algorithm, we expect several entries: a default-type entry which implements the underlying Born phase space, and additional entries which enable the construction of various real-radiation and subtraction kinematics configurations. A [[core_entry]] is the interface to existing matrix-element and interaction code. Depending on the process and its components, there may be various distinct matrix elements to compute. The [[mci_entry]] objects configure distinct MC input parameter sets and their associated (multi-channel) integrators. The [[rng_factory]] object is a single objects which constructs individual random-number generators for various tasks, in a uniform and well-defined way. The [[beam_config]] object describes the incoming particles, either the decay mother or the scattering beams. It also contains the spectrum- and structure-function setup, which has to interact with the phase-space and integrator facilities. The [[term]] subobjects break down the process in its smallest parts which appear in the calculation. For LO processes, the correspondence between terms and components is one-to-one. The FKS-NLO algorithm requires not just separation of Born, real, and virtual components but also subtraction terms, and a decomposition of the real phase space into singular regions. The general idea is that the integration results of distinct sets of terms are summed over to provide the results of individual components. This is also controlled by the [[pcm]] subobject. The [[process_status]] object is a bookkeeping device that allows us to query the status of an ongoing calculation. The [[process_results]] object collects the integration results for external use, including integration history information. <>= public :: process_t <>= type :: process_t private type(process_metadata_t) :: & meta type(process_environment_t) :: & env type(process_config_data_t) :: & config class(pcm_t), allocatable :: & pcm type(process_component_t), dimension(:), allocatable :: & component type(process_phs_config_t), dimension(:), allocatable :: & phs_entry type(core_entry_t), dimension(:), allocatable :: & core_entry type(process_mci_entry_t), dimension(:), allocatable :: & mci_entry class(rng_factory_t), allocatable :: & rng_factory type(process_beam_config_t) :: & beam_config type(process_term_t), dimension(:), allocatable :: & term type(process_status_t) :: & status type(process_results_t) :: & result contains <> end type process_t @ %def process_t @ \subsection{Process pointer} Wrapper type for storing pointers to process objects in arrays. <>= public :: process_ptr_t <>= type :: process_ptr_t type(process_t), pointer :: p => null () end type process_ptr_t @ %def process_ptr_t @ \subsection{Output} This procedure is an important debugging and inspection tool; it is not used during normal operation. The process object is written to a file (identified by unit, which may also be standard output). Optional flags determine whether we show everything or just the interesting parts. The shorthand as a traditional TBP. <>= procedure :: write => process_write <>= module subroutine process_write (process, screen, unit, & show_os_data, show_var_list, show_rng, show_expressions, pacify) class(process_t), intent(in) :: process logical, intent(in) :: screen integer, intent(in), optional :: unit logical, intent(in), optional :: show_os_data logical, intent(in), optional :: show_var_list logical, intent(in), optional :: show_rng logical, intent(in), optional :: show_expressions logical, intent(in), optional :: pacify end subroutine process_write <>= module subroutine process_write (process, screen, unit, & show_os_data, show_var_list, show_rng, show_expressions, pacify) class(process_t), intent(in) :: process logical, intent(in) :: screen integer, intent(in), optional :: unit logical, intent(in), optional :: show_os_data logical, intent(in), optional :: show_var_list logical, intent(in), optional :: show_rng logical, intent(in), optional :: show_expressions logical, intent(in), optional :: pacify integer :: u, iostat character(0) :: iomsg integer, dimension(:), allocatable :: v_list u = given_output_unit (unit) allocate (v_list (0)) call set_flag (v_list, F_SHOW_OS_DATA, show_os_data) call set_flag (v_list, F_SHOW_VAR_LIST, show_var_list) call set_flag (v_list, F_SHOW_RNG, show_rng) call set_flag (v_list, F_SHOW_EXPRESSIONS, show_expressions) call set_flag (v_list, F_PACIFY, pacify) if (screen) then call process%write_formatted (u, "LISTDIRECTED", v_list, iostat, iomsg) else call process%write_formatted (u, "DT", v_list, iostat, iomsg) end if end subroutine process_write @ %def process_write @ Standard DTIO procedure with binding. For the particular application, the screen format is triggered by the [[LISTDIRECTED]] option for the [[iotype]] format editor string. The other options activate when the particular parameter value is found in [[v_list]]. NOTE: The DTIO [[generic]] binding is supported by gfortran since 7.0. TODO wk 2018: The default could be to show everything, and we should have separate switches for all major parts. Currently, there are only a few. <>= ! generic :: write (formatted) => write_formatted procedure :: write_formatted => process_write_formatted <>= module subroutine process_write_formatted (dtv, unit, iotype, & v_list, iostat, iomsg) class(process_t), intent(in) :: dtv integer, intent(in) :: unit character(*), intent(in) :: iotype integer, dimension(:), intent(in) :: v_list integer, intent(out) :: iostat character(*), intent(inout) :: iomsg end subroutine process_write_formatted <>= module subroutine process_write_formatted (dtv, unit, iotype, & v_list, iostat, iomsg) class(process_t), intent(in) :: dtv integer, intent(in) :: unit character(*), intent(in) :: iotype integer, dimension(:), intent(in) :: v_list integer, intent(out) :: iostat character(*), intent(inout) :: iomsg integer :: u logical :: screen logical :: var_list logical :: rng_factory logical :: expressions logical :: counters logical :: os_data logical :: model logical :: pacify integer :: i u = unit select case (iotype) case ("LISTDIRECTED") screen = .true. case default screen = .false. end select var_list = flagged (v_list, F_SHOW_VAR_LIST) rng_factory = flagged (v_list, F_SHOW_RNG, .true.) expressions = flagged (v_list, F_SHOW_EXPRESSIONS) counters = .true. os_data = flagged (v_list, F_SHOW_OS_DATA) model = .false. pacify = flagged (v_list, F_PACIFY) associate (process => dtv) if (screen) then write (msg_buffer, "(A)") repeat ("-", 72) call msg_message () else call write_separator (u, 2) end if call process%meta%write (u, screen) if (var_list) then call process%env%write (u, show_var_list=var_list, & show_model=.false., show_lib=.false., & show_os_data=os_data) else if (.not. screen) then write (u, "(1x,A)") "Variable list: [not shown]" end if if (process%meta%type == PRC_UNKNOWN) then call write_separator (u, 2) return else if (screen) then return end if call write_separator (u) call process%config%write (u, counters, model, expressions) if (rng_factory) then if (allocated (process%rng_factory)) then call write_separator (u) call process%rng_factory%write (u) end if end if call write_separator (u, 2) if (allocated (process%component)) then write (u, "(1x,A)") "Process component configuration:" do i = 1, size (process%component) call write_separator (u) call process%component(i)%write (u) end do else write (u, "(1x,A)") "Process component configuration: [undefined]" end if call write_separator (u, 2) if (allocated (process%term)) then write (u, "(1x,A)") "Process term configuration:" do i = 1, size (process%term) call write_separator (u) call process%term(i)%write (u) end do else write (u, "(1x,A)") "Process term configuration: [undefined]" end if call write_separator (u, 2) call process%beam_config%write (u) call write_separator (u, 2) if (allocated (process%mci_entry)) then write (u, "(1x,A)") "Multi-channel integrator configurations:" do i = 1, size (process%mci_entry) call write_separator (u) write (u, "(1x,A,I0,A)") "MCI #", i, ":" call process%mci_entry(i)%write (u, pacify) end do end if call write_separator (u, 2) end associate iostat = 0 iomsg = "" end subroutine process_write_formatted @ %def process_write_formatted @ <>= procedure :: write_meta => process_write_meta <>= module subroutine process_write_meta (process, unit, testflag) class(process_t), intent(in) :: process integer, intent(in), optional :: unit logical, intent(in), optional :: testflag end subroutine process_write_meta <>= module subroutine process_write_meta (process, unit, testflag) class(process_t), intent(in) :: process integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u, i u = given_output_unit (unit) select case (process%meta%type) case (PRC_UNKNOWN) write (u, "(1x,A)") "Process instance [undefined]" return case (PRC_DECAY) write (u, "(1x,A)", advance="no") "Process instance [decay]:" case (PRC_SCATTERING) write (u, "(1x,A)", advance="no") "Process instance [scattering]:" case default call msg_bug ("process_instance_write: undefined process type") end select write (u, "(1x,A,A,A)") "'", char (process%meta%id), "'" write (u, "(3x,A,A,A)") "Run ID = '", char (process%meta%run_id), "'" if (allocated (process%meta%component_id)) then write (u, "(3x,A)") "Process components:" do i = 1, size (process%meta%component_id) if (process%pcm%component_selected(i)) then write (u, "(3x,'*')", advance="no") else write (u, "(4x)", advance="no") end if write (u, "(1x,I0,9A)") i, ": '", & char (process%meta%component_id (i)), "': ", & char (process%meta%component_description (i)) end do end if end subroutine process_write_meta @ %def process_write_meta @ Screen output. Write a short account of the process configuration and the current results. The verbose version lists the components, the short version just the results. <>= procedure :: show => process_show <>= module subroutine process_show (object, unit, verbose) class(process_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: verbose end subroutine process_show <>= module subroutine process_show (object, unit, verbose) class(process_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: verbose integer :: u logical :: verb real(default) :: err_percent u = given_output_unit (unit) verb = .true.; if (present (verbose)) verb = verbose if (verb) then call object%meta%show (u, object%config%model%get_name ()) select case (object%meta%type) case (PRC_DECAY) write (u, "(2x,A)", advance="no") "Computed width =" case (PRC_SCATTERING) write (u, "(2x,A)", advance="no") "Computed cross section =" case default; return end select else if (object%meta%run_id /= "") then write (u, "('Run',1x,A,':',1x)", advance="no") & char (object%meta%run_id) end if write (u, "(A)", advance="no") char (object%meta%id) select case (object%meta%num_id) case (0) write (u, "(':')") case default write (u, "(1x,'(',I0,')',':')") object%meta%num_id end select write (u, "(2x)", advance="no") end if if (object%has_integral_tot ()) then write (u, "(ES14.7,1x,'+-',ES9.2)", advance="no") & object%get_integral_tot (), object%get_error_tot () select case (object%meta%type) case (PRC_DECAY) write (u, "(1x,A)", advance="no") "GeV" case (PRC_SCATTERING) write (u, "(1x,A)", advance="no") "fb " case default write (u, "(1x,A)", advance="no") " " end select if (object%get_integral_tot () /= 0) then err_percent = abs (100 & * object%get_error_tot () / object%get_integral_tot ()) else err_percent = 0 end if if (err_percent == 0) then write (u, "(1x,'(',F4.0,4x,'%)')") err_percent else if (err_percent < 0.1) then write (u, "(1x,'(',F7.3,1x,'%)')") err_percent else if (err_percent < 1) then write (u, "(1x,'(',F6.2,2x,'%)')") err_percent else if (err_percent < 10) then write (u, "(1x,'(',F5.1,3x,'%)')") err_percent else write (u, "(1x,'(',F4.0,4x,'%)')") err_percent end if else write (u, "(A)") "[integral undefined]" end if end subroutine process_show @ %def process_show @ Finalizer. Explicitly iterate over all subobjects that may contain allocated pointers. TODO wk 2018 (workaround): The finalizer for the [[config_data]] component is not called. The reason is that this deletes model data local to the process, but these could be referenced by pointers (flavor objects) from some persistent event record. Obviously, such side effects should be avoided, but this requires refactoring the event-handling procedures. <>= procedure :: final => process_final <>= module subroutine process_final (process) class(process_t), intent(inout) :: process end subroutine process_final <>= module subroutine process_final (process) class(process_t), intent(inout) :: process integer :: i ! call process%meta%final () call process%env%final () ! call process%config%final () if (allocated (process%component)) then do i = 1, size (process%component) call process%component(i)%final () end do end if if (allocated (process%term)) then do i = 1, size (process%term) call process%term(i)%final () end do end if call process%beam_config%final () if (allocated (process%mci_entry)) then do i = 1, size (process%mci_entry) call process%mci_entry(i)%final () end do end if if (allocated (process%pcm)) then call process%pcm%final () deallocate (process%pcm) end if end subroutine process_final @ %def process_final @ \subsubsection{Process setup} Initialize a process. We need a process library [[lib]] and the process identifier [[proc_id]] (string). We will fetch the current run ID from the variable list [[var_list]]. We collect all important data from the environment and store them in the appropriate places. OS data, model, and variable list are copied into [[env]] (true snapshot), also the process library (pointer only). The [[meta]] subobject is initialized with process ID and attributes taken from the process library. We initialize the [[config]] subobject with all data that are relevant for this run, using the settings from [[env]]. These data determine the MD5 sum for this run, which allows us to identify the setup and possibly skips in a later re-run. We also allocate and initialize the embedded RNG factory. We take the seed from the [[var_list]], and we should return the [[var_list]] to the caller with a new seed. Finally, we allocate the process component manager [[pcm]], which implements the chosen algorithm for process integration. The first task of the manager is to allocate the component array and to determine the component categories (e.g., Born/Virtual etc.). TODO wk 2018: The [[pcm]] dispatcher should be provided by the caller, if we eventually want to eliminate dependencies on concrete [[pcm_t]] extensions. Gfortran 7/8/9 bug, has to remain in the main module: <>= procedure :: init => process_init <>= subroutine process_init & (process, proc_id, lib, os_data, model, var_list, beam_structure) class(process_t), intent(out) :: process type(string_t), intent(in) :: proc_id type(process_library_t), intent(in), target :: lib type(os_data_t), intent(in) :: os_data class(model_t), intent(in), target :: model type(var_list_t), intent(inout), target, optional :: var_list type(beam_structure_t), intent(in), optional :: beam_structure integer :: next_rng_seed if (debug_on) call msg_debug (D_PROCESS_INTEGRATION, "process_init") associate & (meta => process%meta, env => process%env, config => process%config) call env%init & (model, lib, os_data, var_list, beam_structure) call meta%init & (proc_id, lib, env%get_var_list_ptr ()) call config%init & (meta, env) call dispatch_rng_factory & (process%rng_factory, env%get_var_list_ptr (), next_rng_seed) call update_rng_seed_in_var_list (var_list, next_rng_seed) call dispatch_pcm & (process%pcm, config%process_def%is_nlo ()) associate (pcm => process%pcm) call pcm%init (env, meta) call pcm%allocate_components (process%component, meta) call pcm%categorize_components (config) end associate end associate end subroutine process_init @ %def process_init @ \subsection{Process component manager} The [[pcm]] (read: process-component manager) takes the responsibility of steering the actual algorithm of configuration and integration. Depending on the concrete type, different algorithms can be implemented. The first version of this supports just two implementations: leading-order (tree-level) integration and event generation, and NLO (QCD/FKS subtraction). We thus can start with a single logical for steering the dispatcher. TODO wk 2018: Eventually, we may eliminate all references to the extensions of [[pcm_t]] from this module and therefore move this outside the module as well. Gfortran 7/8/9 bug, has to be in the main module: <>= subroutine dispatch_pcm (pcm, is_nlo) class(pcm_t), allocatable, intent(out) :: pcm logical, intent(in) :: is_nlo if (.not. is_nlo) then allocate (pcm_default_t :: pcm) else allocate (pcm_nlo_t :: pcm) end if end subroutine dispatch_pcm @ %def dispatch_pcm @ This step is performed after phase-space and core objects are done: collect all missing information and prepare the process component manager for the appropriate integration algorithm. <>= procedure :: complete_pcm_setup => process_complete_pcm_setup <>= module subroutine process_complete_pcm_setup (process) class(process_t), intent(inout) :: process end subroutine process_complete_pcm_setup <>= module subroutine process_complete_pcm_setup (process) class(process_t), intent(inout) :: process call process%pcm%complete_setup & (process%core_entry, process%component, process%env%get_model_ptr ()) end subroutine process_complete_pcm_setup @ %def process_complete_pcm_setup @ \subsection{Core management} Allocate cores (interface objects to matrix-element code). The [[dispatch_core]] procedure is taken as an argument, so we do not depend on the implementation, and thus on the specific core types. The [[helicity_selection]] object collects data that the matrix-element code needs for configuring the appropriate behavior. After the cores have been allocated, and assuming the phs initial configuration has been done before, we proceed with computing the [[pcm]] internal data. <>= procedure :: setup_cores => process_setup_cores <>= module subroutine process_setup_cores (process, dispatch_core, & helicity_selection, use_color_factors, has_beam_pol) class(process_t), intent(inout) :: process procedure(dispatch_core_proc) :: dispatch_core type(helicity_selection_t), intent(in), optional :: helicity_selection logical, intent(in), optional :: use_color_factors logical, intent(in), optional :: has_beam_pol end subroutine process_setup_cores <>= module subroutine process_setup_cores (process, dispatch_core, & helicity_selection, use_color_factors, has_beam_pol) class(process_t), intent(inout) :: process procedure(dispatch_core_proc) :: dispatch_core type(helicity_selection_t), intent(in), optional :: helicity_selection logical, intent(in), optional :: use_color_factors logical, intent(in), optional :: has_beam_pol integer :: i associate (pcm => process%pcm) call pcm%allocate_cores (process%config, process%core_entry) do i = 1, size (process%core_entry) call dispatch_core (process%core_entry(i)%core, & process%core_entry(i)%core_def, & process%config%model, & helicity_selection, & process%config%qcd, & use_color_factors, & has_beam_pol) call process%core_entry(i)%configure & (process%env%get_lib_ptr (), process%meta%id) if (process%core_entry(i)%core%uses_blha ()) then call pcm%setup_blha (process%core_entry(i)) end if end do end associate end subroutine process_setup_cores @ %def process_setup_cores <>= abstract interface subroutine dispatch_core_proc (core, core_def, model, & helicity_selection, qcd, use_color_factors, has_beam_pol) import class(prc_core_t), allocatable, intent(inout) :: core class(prc_core_def_t), intent(in) :: core_def class(model_data_t), intent(in), target, optional :: model type(helicity_selection_t), intent(in), optional :: helicity_selection type(qcd_t), intent(in), optional :: qcd logical, intent(in), optional :: use_color_factors logical, intent(in), optional :: has_beam_pol end subroutine dispatch_core_proc end interface @ %def dispatch_core_proc @ Use the [[pcm]] to initialize the BLHA interface for each core which requires it. <>= procedure :: prepare_blha_cores => process_prepare_blha_cores <>= module subroutine process_prepare_blha_cores (process) class(process_t), intent(inout), target :: process end subroutine process_prepare_blha_cores <>= module subroutine process_prepare_blha_cores (process) class(process_t), intent(inout), target :: process integer :: i associate (pcm => process%pcm) do i = 1, size (process%core_entry) associate (core_entry => process%core_entry(i)) if (core_entry%core%uses_blha ()) then pcm%uses_blha = .true. call pcm%prepare_blha_core (core_entry, process%config%model) end if end associate end do end associate end subroutine process_prepare_blha_cores @ %def process_prepare_blha_cores @ Create the BLHA interface data, using PCM for specific data, and write the BLHA contract file(s). We take various configuration data and copy them to the [[blha_master]] record, which then creates and writes the contracts. For assigning the QCD/EW coupling powers, we inspect the first process component only. The other parameters are taken as-is from the process environment variables. <>= procedure :: create_blha_interface => process_create_blha_interface <>= module subroutine process_create_blha_interface (process) class(process_t), intent(inout) :: process end subroutine process_create_blha_interface <>= module subroutine process_create_blha_interface (process) class(process_t), intent(inout) :: process integer :: alpha_power, alphas_power integer :: openloops_phs_tolerance, openloops_stability_log logical :: use_cms type(string_t) :: ew_scheme, correction_type type(string_t) :: openloops_extra_cmd type(blha_master_t) :: blha_master integer, dimension(:,:), allocatable :: flv_born, flv_real if (process%pcm%uses_blha) then call collect_configuration_parameters (process%get_var_list_ptr ()) call process%component(1)%config%get_coupling_powers & (alpha_power, alphas_power) associate (pcm => process%pcm) call pcm%set_blha_methods (blha_master, process%get_var_list_ptr ()) call blha_master%set_ew_scheme (ew_scheme) call blha_master%allocate_config_files () call blha_master%set_correction_type (correction_type) call blha_master%setup_additional_features ( & openloops_phs_tolerance, & use_cms, & openloops_stability_log, & extra_cmd = openloops_extra_cmd, & beam_structure = process%env%get_beam_structure ()) call pcm%get_blha_flv_states (process%core_entry, flv_born, flv_real) call blha_master%set_photon_characteristics (flv_born, process%config%n_in) call blha_master%generate (process%meta%id, & process%config%model, process%config%n_in, & alpha_power, alphas_power, & flv_born, flv_real) call blha_master%write_olp (process%meta%id) end associate end if contains subroutine collect_configuration_parameters (var_list) type(var_list_t), intent(in) :: var_list openloops_phs_tolerance = & var_list%get_ival (var_str ("openloops_phs_tolerance")) openloops_stability_log = & var_list%get_ival (var_str ("openloops_stability_log")) use_cms = & var_list%get_lval (var_str ("?openloops_use_cms")) ew_scheme = & var_list%get_sval (var_str ("$blha_ew_scheme")) correction_type = & var_list%get_sval (var_str ("$nlo_correction_type")) openloops_extra_cmd = & var_list%get_sval (var_str ("$openloops_extra_cmd")) end subroutine collect_configuration_parameters end subroutine process_create_blha_interface @ %def process_create_blha_interface @ Initialize the process components, one by one. We require templates for the [[mci]] (integrator) and [[phs_config]] (phase-space) configuration data. The [[active]] flag is set if the component has an associated matrix element, so we can compute it. The case of no core is a unit-test case. The specifics depend on the algorithm and are delegated to the [[pcm]] process-component manager. The optional [[phs_config]] overrides a pre-generated config array (for unit test). <>= procedure :: init_components => process_init_components <>= module subroutine process_init_components (process, phs_config) class(process_t), intent(inout), target :: process class(phs_config_t), allocatable, intent(in), optional :: phs_config end subroutine process_init_components <>= module subroutine process_init_components (process, phs_config) class(process_t), intent(inout), target :: process class(phs_config_t), allocatable, intent(in), optional :: phs_config integer :: i, i_core class(prc_core_t), pointer :: core logical :: active associate (pcm => process%pcm) do i = 1, pcm%n_components i_core = pcm%get_i_core(i) if (i_core > 0) then core => process%get_core_ptr (i_core) active = core%has_matrix_element () else active = .true. end if select type (pcm => process%pcm) type is (pcm_nlo_t) if (pcm%use_real_partition .and. .not. pcm%use_real_singular) then if (pcm%component_type(i) == COMP_REAL_SING) then active = .false. end if end if end select if (present (phs_config)) then call pcm%init_component (process%component(i), & i, & active, & phs_config, & process%env, process%meta, process%config) else call pcm%init_component (process%component(i), & i, & active, & process%phs_entry(pcm%i_phs_config(i))%phs_config, & process%env, process%meta, process%config) end if end do end associate end subroutine process_init_components @ %def process_init_components @ If process components have turned out to be inactive, this has to be recorded in the [[meta]] block. Delegate to the [[pcm]]. <>= procedure :: record_inactive_components => process_record_inactive_components <>= module subroutine process_record_inactive_components (process) class(process_t), intent(inout) :: process end subroutine process_record_inactive_components <>= module subroutine process_record_inactive_components (process) class(process_t), intent(inout) :: process associate (pcm => process%pcm) call pcm%record_inactive_components (process%component, process%meta) end associate end subroutine process_record_inactive_components @ %def process_record_inactive_components @ Determine the process terms for each process component. <>= procedure :: setup_terms => process_setup_terms <>= module subroutine process_setup_terms (process, with_beams) class(process_t), intent(inout), target :: process logical, intent(in), optional :: with_beams end subroutine process_setup_terms <>= module subroutine process_setup_terms (process, with_beams) class(process_t), intent(inout), target :: process logical, intent(in), optional :: with_beams class(model_data_t), pointer :: model integer :: i, j, k, i_term integer, dimension(:), allocatable :: n_entry integer :: n_components, n_tot integer :: i_sub type(string_t) :: subtraction_method class(prc_core_t), pointer :: core => null () logical :: setup_subtraction_component, singular_real logical :: requires_spin_correlations integer :: nlo_type_to_fetch, n_emitters i_sub = 0 model => process%config%model n_components = process%meta%n_components allocate (n_entry (n_components), source = 0) do i = 1, n_components associate (component => process%component(i)) if (component%active) then n_entry(i) = 1 if (component%get_nlo_type () == NLO_REAL) then select type (pcm => process%pcm) type is (pcm_nlo_t) if (pcm%component_type(i) /= COMP_REAL_FIN) & n_entry(i) = n_entry(i) + pcm%region_data%get_n_phs () end select end if end if end associate end do n_tot = sum (n_entry) allocate (process%term (n_tot)) k = 0 if (process%is_nlo_calculation ()) then i_sub = process%component(1)%config%get_associated_subtraction () subtraction_method = process%component(i_sub)%config%get_me_method () if (debug_on) call msg_debug2 & (D_PROCESS_INTEGRATION, "process_setup_terms: ", subtraction_method) end if do i = 1, n_components associate (component => process%component(i)) if (.not. component%active) cycle allocate (component%i_term (n_entry(i))) do j = 1, n_entry(i) select type (pcm => process%pcm) type is (pcm_nlo_t) singular_real = component%get_nlo_type () == NLO_REAL & .and. pcm%component_type(i) /= COMP_REAL_FIN class default singular_real = .false. end select setup_subtraction_component = singular_real .and. j == n_entry(i) i_term = k + j component%i_term(j) = i_term if (singular_real) then process%term(i_term)%i_sub = k + n_entry(i) else process%term(i_term)%i_sub = 0 end if if (setup_subtraction_component) then select type (pcm => process%pcm) class is (pcm_nlo_t) process%term(i_term)%i_core = pcm%i_core(pcm%i_sub) end select else process%term(i_term)%i_core = process%pcm%get_i_core(i) end if if (process%term(i_term)%i_core == 0) then call msg_bug ("Process '" // char (process%get_id ()) & // "': core not found!") end if core => process%get_core_term (i_term) if (i_sub > 0) then select type (pcm => process%pcm) type is (pcm_nlo_t) requires_spin_correlations = & pcm%region_data%requires_spin_correlations () n_emitters = pcm%region_data%get_n_emitters_sc () class default requires_spin_correlations = .false. n_emitters = 0 end select if (requires_spin_correlations) then call process%term(i_term)%init ( & i_term, i, j, core, model, & nlo_type = component%config%get_nlo_type (), & use_beam_pol = with_beams, & subtraction_method = subtraction_method, & has_pdfs = process%pcm%has_pdfs, & n_emitters = n_emitters) else call process%term(i_term)%init ( & i_term, i, j, core, model, & nlo_type = component%config%get_nlo_type (), & use_beam_pol = with_beams, & subtraction_method = subtraction_method, & has_pdfs = process%pcm%has_pdfs) end if else call process%term(i_term)%init ( & i_term, i, j, core, model, & nlo_type = component%config%get_nlo_type (), & use_beam_pol = with_beams, & has_pdfs = process%pcm%has_pdfs) end if end do end associate k = k + n_entry(i) end do process%config%n_terms = n_tot end subroutine process_setup_terms @ %def process_setup_terms @ Initialize the beam setup. This is the trivial version where the incoming state of the matrix element coincides with the initial state of the process. For a scattering process, we need the c.m. energy, all other variables are set to their default values (no polarization, lab frame and c.m.\ frame coincide, etc.) We assume that all components consistently describe a scattering process, i.e., two incoming particles. Note: The current layout of the [[beam_data_t]] record requires that the flavor for each beam is unique. For processes with multiple flavors in the initial state, one has to set up beams explicitly. This restriction could be removed by extending the code in the [[beams]] module. <>= procedure :: setup_beams_sqrts => process_setup_beams_sqrts <>= module subroutine process_setup_beams_sqrts & (process, sqrts, beam_structure, i_core) class(process_t), intent(inout) :: process real(default), intent(in) :: sqrts type(beam_structure_t), intent(in), optional :: beam_structure integer, intent(in), optional :: i_core end subroutine process_setup_beams_sqrts <>= module subroutine process_setup_beams_sqrts & (process, sqrts, beam_structure, i_core) class(process_t), intent(inout) :: process real(default), intent(in) :: sqrts type(beam_structure_t), intent(in), optional :: beam_structure integer, intent(in), optional :: i_core type(pdg_array_t), dimension(:,:), allocatable :: pdg_in integer, dimension(2) :: pdg_scattering type(flavor_t), dimension(2) :: flv_in integer :: i, i0, ic allocate (pdg_in (2, process%meta%n_components)) i0 = 0 do i = 1, process%meta%n_components if (process%component(i)%active) then if (present (i_core)) then ic = i_core else ic = process%pcm%get_i_core (i) end if associate (core => process%core_entry(ic)%core) pdg_in(:,i) = core%data%get_pdg_in () end associate if (i0 == 0) i0 = i end if end do do i = 1, process%meta%n_components if (.not. process%component(i)%active) then pdg_in(:,i) = pdg_in(:,i0) end if end do if (all (pdg_in%get_length () == 1) .and. & all (pdg_in(1,:) == pdg_in(1,i0)) .and. & all (pdg_in(2,:) == pdg_in(2,i0))) then pdg_scattering(:) = pdg_in(:,i0)%get (1) call flv_in%init (pdg_scattering, process%config%model) call process%beam_config%init_scattering (flv_in, sqrts, beam_structure) else call msg_fatal ("Setting up process '" // char (process%meta%id) // "':", & [var_str (" --------------------------------------------"), & var_str ("Inconsistent initial state. This happens if either "), & var_str ("several processes with non-matching initial states "), & var_str ("have been added, or for a single process with an "), & var_str ("initial state flavor sum. In that case, please set beams "), & var_str ("explicitly [singling out a flavor / structure function.]")]) end if end subroutine process_setup_beams_sqrts @ %def process_setup_beams_sqrts @ This is the version that applies to decay processes. The energy is the particle mass, hence no extra argument. <>= procedure :: setup_beams_decay => process_setup_beams_decay <>= module subroutine process_setup_beams_decay & (process, rest_frame, beam_structure, i_core) class(process_t), intent(inout), target :: process logical, intent(in), optional :: rest_frame type(beam_structure_t), intent(in), optional :: beam_structure integer, intent(in), optional :: i_core end subroutine process_setup_beams_decay <>= module subroutine process_setup_beams_decay & (process, rest_frame, beam_structure, i_core) class(process_t), intent(inout), target :: process logical, intent(in), optional :: rest_frame type(beam_structure_t), intent(in), optional :: beam_structure integer, intent(in), optional :: i_core type(pdg_array_t), dimension(:,:), allocatable :: pdg_in integer, dimension(1) :: pdg_decay type(flavor_t), dimension(1) :: flv_in integer :: i, i0, ic allocate (pdg_in (1, process%meta%n_components)) i0 = 0 do i = 1, process%meta%n_components if (process%component(i)%active) then if (present (i_core)) then ic = i_core else ic = process%pcm%get_i_core (i) end if associate (core => process%core_entry(ic)%core) pdg_in(:,i) = core%data%get_pdg_in () end associate if (i0 == 0) i0 = i end if end do do i = 1, process%meta%n_components if (.not. process%component(i)%active) then pdg_in(:,i) = pdg_in(:,i0) end if end do if (all (pdg_in%get_length () == 1) & .and. all (pdg_in(1,:) == pdg_in(1,i0))) then pdg_decay(:) = pdg_in(:,i0)%get (1) call flv_in%init (pdg_decay, process%config%model) call process%beam_config%init_decay (flv_in, rest_frame, beam_structure) else call msg_fatal ("Setting up decay '" & // char (process%meta%id) // "': decaying particle not unique") end if end subroutine process_setup_beams_decay @ %def process_setup_beams_decay @ We have to make sure that the masses of the various flavors in a given position in the particle string coincide. <>= procedure :: check_masses => process_check_masses <>= module subroutine process_check_masses (process) class(process_t), intent(in) :: process end subroutine process_check_masses <>= module subroutine process_check_masses (process) class(process_t), intent(in) :: process type(flavor_t), dimension(:), allocatable :: flv real(default), dimension(:), allocatable :: mass integer :: i, j integer :: i_component class(prc_core_t), pointer :: core do i = 1, process%get_n_terms () i_component = process%term(i)%i_component if (.not. process%component(i_component)%active) cycle core => process%get_core_term (i) associate (data => core%data) allocate (flv (data%n_flv), mass (data%n_flv)) do j = 1, data%n_in + data%n_out call flv%init (data%flv_state(j,:), process%config%model) mass = flv%get_mass () if (any (.not. nearly_equal(mass, mass(1)))) then call msg_fatal ("Process '" // char (process%meta%id) // "': " & // "mass values in flavor combination do not coincide. ") end if end do deallocate (flv, mass) end associate end do end subroutine process_check_masses @ %def process_check_masses @ Set up index mapping for [[region_data]] for singular regions equivalent w.r.t. their amplitudes. Has to be called after [[region_data]] AND the [[core]] are fully set up. For processes with structure function, subprocesses which lead to the same amplitude for the hard interaction can differ if structure functions are applied. In this case we remap flavor structures to themselves if the eqvivalent hard interaction flavor structure has no identical initial state. <>= procedure :: optimize_nlo_singular_regions => & process_optimize_nlo_singular_regions <>= module subroutine process_optimize_nlo_singular_regions (process) class(process_t), intent(inout) :: process end subroutine process_optimize_nlo_singular_regions <>= module subroutine process_optimize_nlo_singular_regions (process) class(process_t), intent(inout) :: process class(prc_core_t), pointer :: core, core_sub integer, dimension(:), allocatable :: eqv_flv_index_born integer, dimension(:), allocatable :: eqv_flv_index_real integer, dimension(:,:), allocatable :: flv_born, flv_real integer :: i_flv, i_flv2, n_in, i integer :: i_component, i_core, i_core_sub logical :: fetched_born, fetched_real logical :: optimize fetched_born = .false.; fetched_real = .false. select type (pcm => process%pcm) type is (pcm_nlo_t) optimize = pcm%settings%reuse_amplitudes_fks if (optimize) then do i_component = 1, pcm%n_components i_core = pcm%get_i_core(i_component) core => process%get_core_ptr (i_core) if (.not. core%data_known) cycle associate (data => core%data) if (pcm%nlo_type_core(i_core) == NLO_REAL .and. & .not. pcm%component_type(i_component) == COMP_SUB) then if (allocated (core%data%eqv_flv_index)) then eqv_flv_index_real = core%get_equivalent_flv_index () fetched_real = .true. end if i_core_sub = pcm%get_i_core (pcm%i_sub) core_sub => process%get_core_ptr (i_core_sub) if (allocated (core_sub%data%eqv_flv_index)) then eqv_flv_index_born = core_sub%get_equivalent_flv_index () fetched_born = .true. end if if (fetched_born .and. fetched_real) exit end if end associate end do if (.not. fetched_born .or. .not. fetched_real) then call msg_warning('Failed to fetch flavor equivalence indices. & &Disabling singular region optimization') optimize = .false. eqv_flv_index_born = [(i, i = 1, pcm%region_data%n_flv_born)] eqv_flv_index_real = [(i, i = 1, pcm%region_data%n_flv_real)] end if if (optimize .and. pcm%has_pdfs) then flv_born = pcm%region_data%get_flv_states_born () flv_real = pcm%region_data%get_flv_states_real () n_in = pcm%region_data%n_in do i_flv = 1, size (eqv_flv_index_born) do i_flv2 = 1, i_flv if (any (flv_born(1:n_in, eqv_flv_index_born(i_flv)) /= & flv_born(1:n_in, i_flv))) then eqv_flv_index_born(i_flv) = i_flv exit end if end do end do do i_flv = 1, size (eqv_flv_index_real) do i_flv2 = 1, i_flv if (any (flv_real(1:n_in, eqv_flv_index_real(i_flv)) /= & flv_real(1:n_in, i_flv))) then eqv_flv_index_real(i_flv) = i_flv exit end if end do end do end if else eqv_flv_index_born = [(i, i = 1, pcm%region_data%n_flv_born)] eqv_flv_index_real = [(i, i = 1, pcm%region_data%n_flv_real)] end if pcm%region_data%eqv_flv_index_born = eqv_flv_index_born pcm%region_data%eqv_flv_index_real = eqv_flv_index_real call pcm%region_data%find_eqv_regions (optimize) end select end subroutine process_optimize_nlo_singular_regions @ %def process_optimize_nlo_singular_regions @ For some structure functions we need to get the list of initial state flavors. This is a two-dimensional array. The first index is the beam index, the second index is the component index. Each array element is itself a PDG array object, which consists of the list of incoming PDG values for this beam and component. <>= procedure :: get_pdg_in => process_get_pdg_in <>= module subroutine process_get_pdg_in (process, pdg_in) class(process_t), intent(in), target :: process type(pdg_array_t), dimension(:,:), allocatable, intent(out) :: pdg_in end subroutine process_get_pdg_in <>= module subroutine process_get_pdg_in (process, pdg_in) class(process_t), intent(in), target :: process type(pdg_array_t), dimension(:,:), allocatable, intent(out) :: pdg_in integer :: i, i_core allocate (pdg_in (process%config%n_in, process%meta%n_components)) do i = 1, process%meta%n_components if (process%component(i)%active) then i_core = process%pcm%get_i_core (i) associate (core => process%core_entry(i_core)%core) pdg_in(:,i) = core%data%get_pdg_in () end associate end if end do end subroutine process_get_pdg_in @ %def process_get_pdg_in @ The phase-space configuration object, in case we need it separately. <>= procedure :: get_phs_config => process_get_phs_config <>= module function process_get_phs_config & (process, i_component) result (phs_config) class(phs_config_t), pointer :: phs_config class(process_t), intent(in), target :: process integer, intent(in) :: i_component end function process_get_phs_config <>= module function process_get_phs_config & (process, i_component) result (phs_config) class(phs_config_t), pointer :: phs_config class(process_t), intent(in), target :: process integer, intent(in) :: i_component if (allocated (process%component)) then phs_config => process%component(i_component)%phs_config else phs_config => null () end if end function process_get_phs_config @ %def process_get_phs_config @ The resonance history set can be extracted from the phase-space configuration. However, this is only possible if the default phase-space method (wood) has been chosen. If [[include_trivial]] is set, we include the resonance history with no resonances in the set. <>= procedure :: extract_resonance_history_set & => process_extract_resonance_history_set <>= module subroutine process_extract_resonance_history_set & (process, res_set, include_trivial, i_component) class(process_t), intent(in), target :: process type(resonance_history_set_t), intent(out) :: res_set logical, intent(in), optional :: include_trivial integer, intent(in), optional :: i_component end subroutine process_extract_resonance_history_set <>= module subroutine process_extract_resonance_history_set & (process, res_set, include_trivial, i_component) class(process_t), intent(in), target :: process type(resonance_history_set_t), intent(out) :: res_set logical, intent(in), optional :: include_trivial integer, intent(in), optional :: i_component integer :: i i = 1; if (present (i_component)) i = i_component select type (phs_config => process%get_phs_config (i)) class is (phs_wood_config_t) call phs_config%extract_resonance_history_set (res_set, include_trivial) class default call msg_error ("process '" // char (process%get_id ()) & // "': extract resonance histories: phase-space method must be & &'wood'. No resonances can be determined.") end select end subroutine process_extract_resonance_history_set @ %def process_extract_resonance_history_set @ Initialize from a complete beam setup. If the beam setup does not apply directly to the process, choose a fallback option as a straight scattering or decay process. <>= procedure :: setup_beams_beam_structure => process_setup_beams_beam_structure <>= module subroutine process_setup_beams_beam_structure & (process, beam_structure, sqrts, decay_rest_frame) class(process_t), intent(inout) :: process type(beam_structure_t), intent(in) :: beam_structure real(default), intent(in) :: sqrts logical, intent(in), optional :: decay_rest_frame end subroutine process_setup_beams_beam_structure <>= module subroutine process_setup_beams_beam_structure & (process, beam_structure, sqrts, decay_rest_frame) class(process_t), intent(inout) :: process type(beam_structure_t), intent(in) :: beam_structure real(default), intent(in) :: sqrts logical, intent(in), optional :: decay_rest_frame integer :: n_in logical :: applies n_in = process%get_n_in () call beam_structure%check_against_n_in (process%get_n_in (), applies) if (applies) then call process%beam_config%init_beam_structure & (beam_structure, sqrts, process%get_model_ptr (), decay_rest_frame) else if (n_in == 2) then call process%setup_beams_sqrts (sqrts, beam_structure) else call process%setup_beams_decay (decay_rest_frame, beam_structure) end if end subroutine process_setup_beams_beam_structure @ %def process_setup_beams_beam_structure @ Notify the user about beam setup. <>= procedure :: beams_startup_message => process_beams_startup_message <>= module subroutine process_beams_startup_message & (process, unit, beam_structure) class(process_t), intent(in) :: process integer, intent(in), optional :: unit type(beam_structure_t), intent(in), optional :: beam_structure end subroutine process_beams_startup_message <>= module subroutine process_beams_startup_message & (process, unit, beam_structure) class(process_t), intent(in) :: process integer, intent(in), optional :: unit type(beam_structure_t), intent(in), optional :: beam_structure call process%beam_config%startup_message (unit, beam_structure) end subroutine process_beams_startup_message @ %def process_beams_startup_message @ Initialize phase-space configuration by reading out the environment variables. We return the rebuild flags and store parameters in the blocks [[phs_par]] and [[mapping_defs]]. The phase-space configuration object(s) are allocated by [[pcm]]. <>= procedure :: init_phs_config => process_init_phs_config <>= module subroutine process_init_phs_config (process) class(process_t), intent(inout) :: process end subroutine process_init_phs_config <>= module subroutine process_init_phs_config (process) class(process_t), intent(inout) :: process type(var_list_t), pointer :: var_list type(phs_parameters_t) :: phs_par type(mapping_defaults_t) :: mapping_defs var_list => process%env%get_var_list_ptr () phs_par%m_threshold_s = & var_list%get_rval (var_str ("phs_threshold_s")) phs_par%m_threshold_t = & var_list%get_rval (var_str ("phs_threshold_t")) phs_par%off_shell = & var_list%get_ival (var_str ("phs_off_shell")) phs_par%keep_nonresonant = & var_list%get_lval (var_str ("?phs_keep_nonresonant")) phs_par%t_channel = & var_list%get_ival (var_str ("phs_t_channel")) mapping_defs%energy_scale = & var_list%get_rval (var_str ("phs_e_scale")) mapping_defs%invariant_mass_scale = & var_list%get_rval (var_str ("phs_m_scale")) mapping_defs%momentum_transfer_scale = & var_list%get_rval (var_str ("phs_q_scale")) mapping_defs%step_mapping = & var_list%get_lval (var_str ("?phs_step_mapping")) mapping_defs%step_mapping_exp = & var_list%get_lval (var_str ("?phs_step_mapping_exp")) mapping_defs%enable_s_mapping = & var_list%get_lval (var_str ("?phs_s_mapping")) associate (pcm => process%pcm) call pcm%init_phs_config (process%phs_entry, & process%meta, process%env, phs_par, mapping_defs) end associate end subroutine process_init_phs_config @ %def process_init_phs_config @ We complete the kinematics configuration after the beam setup, but before we configure the chain of structure functions. The reason is that we need the total energy [[sqrts]] for the kinematics, but the structure-function setup requires the number of channels, which depends on the kinematics configuration. For instance, the kinematics module may return the need for parameterizing an s-channel resonance. <>= procedure :: configure_phs => process_configure_phs <>= module subroutine process_configure_phs (process, rebuild, & ignore_mismatch, combined_integration, subdir) class(process_t), intent(inout) :: process logical, intent(in), optional :: rebuild logical, intent(in), optional :: ignore_mismatch logical, intent(in), optional :: combined_integration type(string_t), intent(in), optional :: subdir end subroutine process_configure_phs <>= module subroutine process_configure_phs (process, rebuild, & ignore_mismatch, combined_integration, subdir) class(process_t), intent(inout) :: process logical, intent(in), optional :: rebuild logical, intent(in), optional :: ignore_mismatch logical, intent(in), optional :: combined_integration type(string_t), intent(in), optional :: subdir real(default) :: sqrts integer :: i, i_born, nlo_type class(phs_config_t), pointer :: phs_config_born sqrts = process%get_sqrts () do i = 1, process%meta%n_components associate (component => process%component(i)) if (component%active) then select type (pcm => process%pcm) type is (pcm_default_t) call component%configure_phs (sqrts, process%beam_config, & rebuild, ignore_mismatch, subdir) class is (pcm_nlo_t) nlo_type = component%config%get_nlo_type () select case (nlo_type) case (BORN, NLO_VIRTUAL, NLO_SUBTRACTION) call component%configure_phs (sqrts, process%beam_config, & rebuild, ignore_mismatch, subdir) call check_and_extend_phs (component) case (NLO_REAL, NLO_MISMATCH, NLO_DGLAP) i_born = component%config%get_associated_born () if (pcm%component_type(i) /= COMP_REAL_FIN) & call check_and_extend_phs (component) call process%component(i_born)%get_phs_config & (phs_config_born) select type (config => component%phs_config) type is (phs_fks_config_t) select type (phs_config_born) type is (phs_wood_config_t) config%md5sum_born_config = & phs_config_born%md5sum_phs_config call config%set_born_config (phs_config_born) call config%set_mode (component%config%get_nlo_type ()) end select end select call component%configure_phs (sqrts, & process%beam_config, rebuild, ignore_mismatch, subdir) end select class default call msg_bug ("process_configure_phs: unsupported PCM type") end select end if end associate end do contains subroutine check_and_extend_phs (component) type(process_component_t), intent(inout) :: component if (combined_integration) then select type (phs_config => component%phs_config) class is (phs_wood_config_t) phs_config%is_combined_integration = .true. call phs_config%increase_n_par () end select end if end subroutine check_and_extend_phs end subroutine process_configure_phs @ %def process_configure_phs @ <>= procedure :: print_phs_startup_message => process_print_phs_startup_message <>= module subroutine process_print_phs_startup_message (process) class(process_t), intent(in) :: process end subroutine process_print_phs_startup_message <>= module subroutine process_print_phs_startup_message (process) class(process_t), intent(in) :: process integer :: i_component do i_component = 1, process%meta%n_components associate (component => process%component(i_component)) if (component%active) then call component%phs_config%startup_message () end if end associate end do end subroutine process_print_phs_startup_message @ %def process_print_phs_startup_message @ Insert the structure-function configuration data. First allocate the storage, then insert data one by one. The third procedure declares a mapping (of the MC input parameters) for a specific channel and structure-function combination. We take the number of channels from the corresponding entry in the [[config_data]] section. Otherwise, these a simple wrapper routines. The extra level in the call tree may allow for simple addressing of multiple concurrent beam configurations, not implemented currently. If we do not want structure functions, we simply do not call those procedures. <>= procedure :: init_sf_chain => process_init_sf_chain generic :: set_sf_channel => set_sf_channel_single procedure :: set_sf_channel_single => process_set_sf_channel generic :: set_sf_channel => set_sf_channel_array procedure :: set_sf_channel_array => process_set_sf_channel_array <>= module subroutine process_init_sf_chain (process, sf_config, sf_trace_file) class(process_t), intent(inout) :: process type(sf_config_t), dimension(:), intent(in) :: sf_config type(string_t), intent(in), optional :: sf_trace_file end subroutine process_init_sf_chain module subroutine process_set_sf_channel (process, c, sf_channel) class(process_t), intent(inout) :: process integer, intent(in) :: c type(sf_channel_t), intent(in) :: sf_channel end subroutine process_set_sf_channel module subroutine process_set_sf_channel_array (process, sf_channel) class(process_t), intent(inout) :: process type(sf_channel_t), dimension(:), intent(in) :: sf_channel end subroutine process_set_sf_channel_array <>= module subroutine process_init_sf_chain (process, sf_config, sf_trace_file) class(process_t), intent(inout) :: process type(sf_config_t), dimension(:), intent(in) :: sf_config type(string_t), intent(in), optional :: sf_trace_file type(string_t) :: file if (present (sf_trace_file)) then if (sf_trace_file /= "") then file = sf_trace_file else file = process%get_id () // "_sftrace.dat" end if call process%beam_config%init_sf_chain (sf_config, file) else call process%beam_config%init_sf_chain (sf_config) end if end subroutine process_init_sf_chain module subroutine process_set_sf_channel (process, c, sf_channel) class(process_t), intent(inout) :: process integer, intent(in) :: c type(sf_channel_t), intent(in) :: sf_channel call process%beam_config%set_sf_channel (c, sf_channel) end subroutine process_set_sf_channel module subroutine process_set_sf_channel_array (process, sf_channel) class(process_t), intent(inout) :: process type(sf_channel_t), dimension(:), intent(in) :: sf_channel integer :: c call process%beam_config%allocate_sf_channels (size (sf_channel)) do c = 1, size (sf_channel) call process%beam_config%set_sf_channel (c, sf_channel(c)) end do end subroutine process_set_sf_channel_array @ %def process_init_sf_chain @ %def process_set_sf_channel @ Notify about the structure-function setup. <>= procedure :: sf_startup_message => process_sf_startup_message <>= module subroutine process_sf_startup_message (process, sf_string, unit) class(process_t), intent(in) :: process type(string_t), intent(in) :: sf_string integer, intent(in), optional :: unit end subroutine process_sf_startup_message <>= module subroutine process_sf_startup_message (process, sf_string, unit) class(process_t), intent(in) :: process type(string_t), intent(in) :: sf_string integer, intent(in), optional :: unit call process%beam_config%sf_startup_message (sf_string, unit) end subroutine process_sf_startup_message @ %def process_sf_startup_message @ As soon as both the kinematics configuration and the structure-function setup are complete, we match parameterizations (channels) for both. The matching entries are (re)set in the [[component]] phase-space configuration, while the structure-function configuration is left intact. <>= procedure :: collect_channels => process_collect_channels <>= module subroutine process_collect_channels (process, coll) class(process_t), intent(inout) :: process type(phs_channel_collection_t), intent(inout) :: coll end subroutine process_collect_channels <>= module subroutine process_collect_channels (process, coll) class(process_t), intent(inout) :: process type(phs_channel_collection_t), intent(inout) :: coll integer :: i do i = 1, process%meta%n_components associate (component => process%component(i)) if (component%active) & call component%collect_channels (coll) end associate end do end subroutine process_collect_channels @ %def process_collect_channels @ Independently, we should be able to check if any component does not contain phase-space parameters. Such a process can only be integrated if there are structure functions. <>= procedure :: contains_trivial_component => process_contains_trivial_component <>= module function process_contains_trivial_component (process) result (flag) class(process_t), intent(in) :: process logical :: flag end function process_contains_trivial_component <>= module function process_contains_trivial_component (process) result (flag) class(process_t), intent(in) :: process logical :: flag integer :: i flag = .true. do i = 1, process%meta%n_components associate (component => process%component(i)) if (component%active) then if (component%get_n_phs_par () == 0) return end if end associate end do flag = .false. end function process_contains_trivial_component @ %def process_contains_trivial_component @ <>= procedure :: get_master_component => process_get_master_component <>= module function process_get_master_component & (process, i_mci) result (i_component) integer :: i_component class(process_t), intent(in) :: process integer, intent(in) :: i_mci end function process_get_master_component <>= module function process_get_master_component & (process, i_mci) result (i_component) integer :: i_component class(process_t), intent(in) :: process integer, intent(in) :: i_mci integer :: i i_component = 0 do i = 1, size (process%component) if (process%component(i)%i_mci == i_mci) then i_component = i return end if end do end function process_get_master_component @ %def process_get_master_component @ Determine the MC parameter set structure and the MCI configuration for each process component. We need data from the structure-function and phase-space setup, so those should be complete before this is called. We also make a random-number generator instance for each MCI group. <>= procedure :: setup_mci => process_setup_mci <>= module subroutine process_setup_mci (process, dispatch_mci) class(process_t), intent(inout) :: process procedure(dispatch_mci_proc) :: dispatch_mci end subroutine process_setup_mci <>= module subroutine process_setup_mci (process, dispatch_mci) class(process_t), intent(inout) :: process procedure(dispatch_mci_proc) :: dispatch_mci class(mci_t), allocatable :: mci_template integer :: i, i_mci if (debug_on) call msg_debug (D_PROCESS_INTEGRATION, "process_setup_mci") associate (pcm => process%pcm) call pcm%call_dispatch_mci (dispatch_mci, & process%get_var_list_ptr (), process%meta%id, mci_template) call pcm%setup_mci (process%mci_entry) process%config%n_mci = pcm%n_mci process%component(:)%i_mci = pcm%i_mci(:) do i = 1, pcm%n_components i_mci = process%pcm%i_mci(i) if (i_mci > 0) then associate (component => process%component(i), & mci_entry => process%mci_entry(i_mci)) call mci_entry%configure (mci_template, & process%meta%type, & i_mci, i, component, process%beam_config%n_sfpar, & process%rng_factory) call mci_entry%set_parameters (process%get_var_list_ptr ()) end associate end if end do end associate end subroutine process_setup_mci @ %def process_setup_mci @ Set cuts. This is a parse node, namely the right-hand side of the [[cut]] assignment. When creating an instance, we compile this into an evaluation tree. The parse node may be null. <>= procedure :: set_cuts => process_set_cuts <>= module subroutine process_set_cuts (process, ef_cuts) class(process_t), intent(inout) :: process class(expr_factory_t), intent(in) :: ef_cuts end subroutine process_set_cuts <>= module subroutine process_set_cuts (process, ef_cuts) class(process_t), intent(inout) :: process class(expr_factory_t), intent(in) :: ef_cuts allocate (process%config%ef_cuts, source = ef_cuts) end subroutine process_set_cuts @ %def process_set_cuts @ Analogously for the other expressions. <>= procedure :: set_scale => process_set_scale procedure :: set_fac_scale => process_set_fac_scale procedure :: set_ren_scale => process_set_ren_scale procedure :: set_weight => process_set_weight <>= module subroutine process_set_scale (process, ef_scale) class(process_t), intent(inout) :: process class(expr_factory_t), intent(in) :: ef_scale end subroutine process_set_scale module subroutine process_set_weight (process, ef_weight) class(process_t), intent(inout) :: process class(expr_factory_t), intent(in) :: ef_weight end subroutine process_set_weight module subroutine process_set_fac_scale (process, ef_fac_scale) class(process_t), intent(inout) :: process class(expr_factory_t), intent(in) :: ef_fac_scale end subroutine process_set_fac_scale module subroutine process_set_ren_scale (process, ef_ren_scale) class(process_t), intent(inout) :: process class(expr_factory_t), intent(in) :: ef_ren_scale end subroutine process_set_ren_scale <>= module subroutine process_set_scale (process, ef_scale) class(process_t), intent(inout) :: process class(expr_factory_t), intent(in) :: ef_scale allocate (process%config%ef_scale, source = ef_scale) end subroutine process_set_scale module subroutine process_set_fac_scale (process, ef_fac_scale) class(process_t), intent(inout) :: process class(expr_factory_t), intent(in) :: ef_fac_scale allocate (process%config%ef_fac_scale, source = ef_fac_scale) end subroutine process_set_fac_scale module subroutine process_set_ren_scale (process, ef_ren_scale) class(process_t), intent(inout) :: process class(expr_factory_t), intent(in) :: ef_ren_scale allocate (process%config%ef_ren_scale, source = ef_ren_scale) end subroutine process_set_ren_scale module subroutine process_set_weight (process, ef_weight) class(process_t), intent(inout) :: process class(expr_factory_t), intent(in) :: ef_weight allocate (process%config%ef_weight, source = ef_weight) end subroutine process_set_weight @ %def process_set_scale @ %def process_set_fac_scale @ %def process_set_ren_scale @ %def process_set_weight @ \subsubsection{MD5 sum} The MD5 sum of the process object should reflect the state completely, including integration results. It is used for checking the integrity of event files. This global checksum includes checksums for the various parts. In particular, the MCI object receives a checksum that includes the configuration of all configuration parts relevant for an individual integration. This checksum is used for checking the integrity of integration grids. We do not need MD5 sums for the process terms, since these are generated from the component definitions. <>= procedure :: compute_md5sum => process_compute_md5sum <>= module subroutine process_compute_md5sum (process) class(process_t), intent(inout) :: process end subroutine process_compute_md5sum <>= module subroutine process_compute_md5sum (process) class(process_t), intent(inout) :: process integer :: i call process%config%compute_md5sum () do i = 1, process%config%n_components associate (component => process%component(i)) if (component%active) then call component%compute_md5sum () end if end associate end do call process%beam_config%compute_md5sum () do i = 1, process%config%n_mci call process%mci_entry(i)%compute_md5sum & (process%config, process%component, process%beam_config) end do end subroutine process_compute_md5sum @ %def process_compute_md5sum @ <>= procedure :: sampler_test => process_sampler_test <>= module subroutine process_sampler_test (process, sampler, n_calls, i_mci) class(process_t), intent(inout) :: process class(mci_sampler_t), intent(inout) :: sampler integer, intent(in) :: n_calls, i_mci end subroutine process_sampler_test <>= module subroutine process_sampler_test (process, sampler, n_calls, i_mci) class(process_t), intent(inout) :: process class(mci_sampler_t), intent(inout) :: sampler integer, intent(in) :: n_calls, i_mci call process%mci_entry(i_mci)%sampler_test (sampler, n_calls) end subroutine process_sampler_test @ %def process_sampler_test @ The finalizer should be called after all integration passes have been completed. It will, for instance, write a summary of the integration results. [[integrate_dummy]] does a ``dummy'' integration in the sense that nothing is done but just empty integration results appended. <>= procedure :: final_integration => process_final_integration procedure :: integrate_dummy => process_integrate_dummy <>= module subroutine process_final_integration (process, i_mci) class(process_t), intent(inout) :: process integer, intent(in) :: i_mci end subroutine process_final_integration module subroutine process_integrate_dummy (process) class(process_t), intent(inout) :: process end subroutine process_integrate_dummy <>= module subroutine process_final_integration (process, i_mci) class(process_t), intent(inout) :: process integer, intent(in) :: i_mci call process%mci_entry(i_mci)%final_integration () end subroutine process_final_integration module subroutine process_integrate_dummy (process) class(process_t), intent(inout) :: process type(integration_results_t) :: results integer :: u_log u_log = logfile_unit () call results%init (process%meta%type) call results%display_init (screen = .true., unit = u_log) call results%new_pass () call results%record (1, 0, 0._default, 0._default, 0._default) call results%display_final () end subroutine process_integrate_dummy @ %def process_final_integration @ %def process_integrate_dummy @ <>= procedure :: integrate => process_integrate <>= module subroutine process_integrate (process, i_mci, mci_work, & mci_sampler, n_it, n_calls, adapt_grids, adapt_weights, final, & pacify, nlo_type) class(process_t), intent(inout) :: process integer, intent(in) :: i_mci type(mci_work_t), intent(inout) :: mci_work class(mci_sampler_t), intent(inout) :: mci_sampler integer, intent(in) :: n_it, n_calls logical, intent(in), optional :: adapt_grids, adapt_weights logical, intent(in), optional :: final logical, intent(in), optional :: pacify integer, intent(in), optional :: nlo_type end subroutine process_integrate <>= module subroutine process_integrate (process, i_mci, mci_work, & mci_sampler, n_it, n_calls, adapt_grids, adapt_weights, final, & pacify, nlo_type) class(process_t), intent(inout) :: process integer, intent(in) :: i_mci type(mci_work_t), intent(inout) :: mci_work class(mci_sampler_t), intent(inout) :: mci_sampler integer, intent(in) :: n_it, n_calls logical, intent(in), optional :: adapt_grids, adapt_weights logical, intent(in), optional :: final logical, intent(in), optional :: pacify integer, intent(in), optional :: nlo_type associate (mci_entry => process%mci_entry(i_mci)) call mci_entry%integrate (mci_work%mci, mci_sampler, n_it, n_calls, & adapt_grids, adapt_weights, final, pacify, & nlo_type = nlo_type) call mci_entry%results%display_pass (pacify) end associate end subroutine process_integrate @ %def process_integrate @ <>= procedure :: generate_weighted_event => process_generate_weighted_event <>= module subroutine process_generate_weighted_event (process, i_mci, & mci_work, mci_sampler, keep_failed_events) class(process_t), intent(inout) :: process integer, intent(in) :: i_mci type(mci_work_t), intent(inout) :: mci_work class(mci_sampler_t), intent(inout) :: mci_sampler logical, intent(in) :: keep_failed_events end subroutine process_generate_weighted_event <>= module subroutine process_generate_weighted_event (process, i_mci, & mci_work, mci_sampler, keep_failed_events) class(process_t), intent(inout) :: process integer, intent(in) :: i_mci type(mci_work_t), intent(inout) :: mci_work class(mci_sampler_t), intent(inout) :: mci_sampler logical, intent(in) :: keep_failed_events associate (mci_entry => process%mci_entry(i_mci)) call mci_entry%generate_weighted_event (mci_work%mci, & mci_sampler, keep_failed_events) end associate end subroutine process_generate_weighted_event @ %def process_generate_weighted_event <>= procedure :: generate_unweighted_event => process_generate_unweighted_event <>= module subroutine process_generate_unweighted_event (process, i_mci, & mci_work, mci_sampler) class(process_t), intent(inout) :: process integer, intent(in) :: i_mci type(mci_work_t), intent(inout) :: mci_work class(mci_sampler_t), intent(inout) :: mci_sampler end subroutine process_generate_unweighted_event <>= module subroutine process_generate_unweighted_event (process, i_mci, & mci_work, mci_sampler) class(process_t), intent(inout) :: process integer, intent(in) :: i_mci type(mci_work_t), intent(inout) :: mci_work class(mci_sampler_t), intent(inout) :: mci_sampler associate (mci_entry => process%mci_entry(i_mci)) call mci_entry%generate_unweighted_event & (mci_work%mci, mci_sampler) end associate end subroutine process_generate_unweighted_event @ %def process_generate_unweighted_event @ Display the final results for the sum of all components. This is useful, obviously, only if there is more than one component and not if a combined integration of all components together has been performed. <>= procedure :: display_summed_results => process_display_summed_results <>= module subroutine process_display_summed_results (process, pacify) class(process_t), intent(inout) :: process logical, intent(in) :: pacify end subroutine process_display_summed_results <>= module subroutine process_display_summed_results (process, pacify) class(process_t), intent(inout) :: process logical, intent(in) :: pacify type(integration_results_t) :: results integer :: u_log u_log = logfile_unit () call results%init (process%meta%type) call results%display_init (screen = .true., unit = u_log) call results%new_pass () call results%record (1, 0, & process%get_integral (), & process%get_error (), & process%get_efficiency (), suppress = pacify) select type (pcm => process%pcm) class is (pcm_nlo_t) !!! Check that Born integral is there if (.not. pcm%settings%combined_integration .and. & process%component_can_be_integrated (1)) then call results%record_correction (process%get_correction (), & process%get_correction_error ()) end if end select call results%display_final () end subroutine process_display_summed_results @ %def process_display_summed_results @ Run LaTeX/Metapost to generate a ps/pdf file for the integration history. We (re)write the driver file -- just in case it has been missed before -- then we compile it. <>= procedure :: display_integration_history => & process_display_integration_history <>= module subroutine process_display_integration_history & (process, i_mci, filename, os_data, eff_reset) class(process_t), intent(inout) :: process integer, intent(in) :: i_mci type(string_t), intent(in) :: filename type(os_data_t), intent(in) :: os_data logical, intent(in), optional :: eff_reset end subroutine process_display_integration_history <>= module subroutine process_display_integration_history & (process, i_mci, filename, os_data, eff_reset) class(process_t), intent(inout) :: process integer, intent(in) :: i_mci type(string_t), intent(in) :: filename type(os_data_t), intent(in) :: os_data logical, intent(in), optional :: eff_reset call integration_results_write_driver & (process%mci_entry(i_mci)%results, filename, eff_reset) call integration_results_compile_driver & (process%mci_entry(i_mci)%results, filename, os_data) end subroutine process_display_integration_history @ %def subroutine process_display_integration_history @ Write a complete logfile (with hardcoded name based on the process ID). We do not write internal data. <>= procedure :: write_logfile => process_write_logfile <>= module subroutine process_write_logfile (process, i_mci, filename) class(process_t), intent(inout) :: process integer, intent(in) :: i_mci type(string_t), intent(in) :: filename end subroutine process_write_logfile <>= module subroutine process_write_logfile (process, i_mci, filename) class(process_t), intent(inout) :: process integer, intent(in) :: i_mci type(string_t), intent(in) :: filename type(time_t) :: time integer :: unit, u unit = free_unit () open (unit = unit, file = char (filename), action = "write", & status = "replace") u = given_output_unit (unit) write (u, "(A)") repeat ("#", 79) call process%meta%write (u, .false.) write (u, "(A)") repeat ("#", 79) write (u, "(3x,A,ES17.10)") "Integral = ", & process%mci_entry(i_mci)%get_integral () write (u, "(3x,A,ES17.10)") "Error = ", & process%mci_entry(i_mci)%get_error () write (u, "(3x,A,ES17.10)") "Accuracy = ", & process%mci_entry(i_mci)%get_accuracy () write (u, "(3x,A,ES17.10)") "Chi2 = ", & process%mci_entry(i_mci)%get_chi2 () write (u, "(3x,A,ES17.10)") "Efficiency = ", & process%mci_entry(i_mci)%get_efficiency () call process%mci_entry(i_mci)%get_time (time, 10000) if (time%is_known ()) then write (u, "(3x,A,1x,A)") "T(10k evt) = ", char (time%to_string_dhms ()) else write (u, "(3x,A)") "T(10k evt) = [undefined]" end if call process%mci_entry(i_mci)%results%write (u) write (u, "(A)") repeat ("#", 79) call process%mci_entry(i_mci)%results%write_chain_weights (u) write (u, "(A)") repeat ("#", 79) call process%mci_entry(i_mci)%counter%write (u) write (u, "(A)") repeat ("#", 79) call process%mci_entry(i_mci)%mci%write_log_entry (u) write (u, "(A)") repeat ("#", 79) call process%beam_config%data%write (u) write (u, "(A)") repeat ("#", 79) if (allocated (process%config%ef_cuts)) then write (u, "(3x,A)") "Cut expression:" call process%config%ef_cuts%write (u) else write (u, "(3x,A)") "No cuts used." end if call write_separator (u) if (allocated (process%config%ef_scale)) then write (u, "(3x,A)") "Scale expression:" call process%config%ef_scale%write (u) else write (u, "(3x,A)") "No scale expression was given." end if call write_separator (u) if (allocated (process%config%ef_fac_scale)) then write (u, "(3x,A)") "Factorization scale expression:" call process%config%ef_fac_scale%write (u) else write (u, "(3x,A)") "No factorization scale expression was given." end if call write_separator (u) if (allocated (process%config%ef_ren_scale)) then write (u, "(3x,A)") "Renormalization scale expression:" call process%config%ef_ren_scale%write (u) else write (u, "(3x,A)") "No renormalization scale expression was given." end if call write_separator (u) if (allocated (process%config%ef_weight)) then call write_separator (u) write (u, "(3x,A)") "Weight expression:" call process%config%ef_weight%write (u) else write (u, "(3x,A)") "No weight expression was given." end if write (u, "(A)") repeat ("#", 79) write (u, "(1x,A)") "Summary of quantum-number states:" write (u, "(1x,A)") " + sign: allowed and contributing" write (u, "(1x,A)") " no + : switched off at runtime" call process%write_state_summary (u) write (u, "(A)") repeat ("#", 79) call process%env%write (u, show_var_list=.true., & show_model=.false., show_lib=.false., show_os_data=.false.) write (u, "(A)") repeat ("#", 79) close (u) end subroutine process_write_logfile @ %def process_write_logfile @ Display the quantum-number combinations of the process components, and their current status (allowed or switched off). <>= procedure :: write_state_summary => process_write_state_summary <>= module subroutine process_write_state_summary (process, unit) class(process_t), intent(in) :: process integer, intent(in), optional :: unit end subroutine process_write_state_summary <>= module subroutine process_write_state_summary (process, unit) class(process_t), intent(in) :: process integer, intent(in), optional :: unit integer :: i, i_component, u u = given_output_unit (unit) do i = 1, size (process%term) call write_separator (u) i_component = process%term(i)%i_component if (i_component /= 0) then call process%term(i)%write_state_summary & (process%get_core_term(i), unit) end if end do end subroutine process_write_state_summary @ %def process_write_state_summary @ Prepare event generation for the specified MCI entry. This implies, in particular, checking the phase-space file. <>= procedure :: prepare_simulation => process_prepare_simulation <>= module subroutine process_prepare_simulation (process, i_mci) class(process_t), intent(inout) :: process integer, intent(in) :: i_mci end subroutine process_prepare_simulation <>= module subroutine process_prepare_simulation (process, i_mci) class(process_t), intent(inout) :: process integer, intent(in) :: i_mci call process%mci_entry(i_mci)%prepare_simulation () end subroutine process_prepare_simulation @ %def process_prepare_simulation @ \subsubsection{Retrieve process data} Tell whether integral (and error) are known. <>= generic :: has_integral => has_integral_tot, has_integral_mci procedure :: has_integral_tot => process_has_integral_tot procedure :: has_integral_mci => process_has_integral_mci <>= module function process_has_integral_tot (process) result (flag) logical :: flag class(process_t), intent(in) :: process end function process_has_integral_tot module function process_has_integral_mci (process, i_mci) result (flag) logical :: flag class(process_t), intent(in) :: process integer, intent(in) :: i_mci end function process_has_integral_mci <>= module function process_has_integral_mci (process, i_mci) result (flag) logical :: flag class(process_t), intent(in) :: process integer, intent(in) :: i_mci if (allocated (process%mci_entry)) then flag = process%mci_entry(i_mci)%has_integral () else flag = .false. end if end function process_has_integral_mci module function process_has_integral_tot (process) result (flag) logical :: flag class(process_t), intent(in) :: process integer :: i, j, i_component if (allocated (process%mci_entry)) then flag = .true. do i = 1, size (process%mci_entry) do j = 1, size (process%mci_entry(i)%i_component) i_component = process%mci_entry(i)%i_component(j) if (process%component_can_be_integrated (i_component)) & flag = flag .and. process%mci_entry(i)%has_integral () end do end do else flag = .false. end if end function process_has_integral_tot @ %def process_has_integral @ Return the current integral and error obtained by the integrator [[i_mci]]. <>= generic :: get_integral => get_integral_tot, get_integral_mci generic :: get_error => get_error_tot, get_error_mci generic :: get_efficiency => get_efficiency_tot, get_efficiency_mci procedure :: get_integral_tot => process_get_integral_tot procedure :: get_integral_mci => process_get_integral_mci procedure :: get_error_tot => process_get_error_tot procedure :: get_error_mci => process_get_error_mci procedure :: get_efficiency_tot => process_get_efficiency_tot procedure :: get_efficiency_mci => process_get_efficiency_mci <>= module function process_get_integral_mci (process, i_mci) result (integral) real(default) :: integral class(process_t), intent(in) :: process integer, intent(in) :: i_mci end function process_get_integral_mci module function process_get_error_mci (process, i_mci) result (error) real(default) :: error class(process_t), intent(in) :: process integer, intent(in) :: i_mci end function process_get_error_mci module function process_get_efficiency_mci & (process, i_mci) result (efficiency) real(default) :: efficiency class(process_t), intent(in) :: process integer, intent(in) :: i_mci end function process_get_efficiency_mci module function process_get_integral_tot (process) result (integral) real(default) :: integral class(process_t), intent(in) :: process end function process_get_integral_tot module function process_get_error_tot (process) result (error) real(default) :: variance class(process_t), intent(in) :: process real(default) :: error end function process_get_error_tot module function process_get_efficiency_tot (process) result (efficiency) real(default) :: efficiency class(process_t), intent(in) :: process end function process_get_efficiency_tot <>= module function process_get_integral_mci (process, i_mci) result (integral) real(default) :: integral class(process_t), intent(in) :: process integer, intent(in) :: i_mci integral = process%mci_entry(i_mci)%get_integral () end function process_get_integral_mci module function process_get_error_mci (process, i_mci) result (error) real(default) :: error class(process_t), intent(in) :: process integer, intent(in) :: i_mci error = process%mci_entry(i_mci)%get_error () end function process_get_error_mci module function process_get_efficiency_mci & (process, i_mci) result (efficiency) real(default) :: efficiency class(process_t), intent(in) :: process integer, intent(in) :: i_mci efficiency = process%mci_entry(i_mci)%get_efficiency () end function process_get_efficiency_mci module function process_get_integral_tot (process) result (integral) real(default) :: integral class(process_t), intent(in) :: process integer :: i, j, i_component integral = zero if (allocated (process%mci_entry)) then do i = 1, size (process%mci_entry) do j = 1, size (process%mci_entry(i)%i_component) i_component = process%mci_entry(i)%i_component(j) if (process%component_can_be_integrated(i_component)) & integral = integral + process%mci_entry(i)%get_integral () end do end do end if end function process_get_integral_tot module function process_get_error_tot (process) result (error) real(default) :: variance class(process_t), intent(in) :: process real(default) :: error integer :: i, j, i_component variance = zero if (allocated (process%mci_entry)) then do i = 1, size (process%mci_entry) do j = 1, size (process%mci_entry(i)%i_component) i_component = process%mci_entry(i)%i_component(j) if (process%component_can_be_integrated(i_component)) & variance = variance + process%mci_entry(i)%get_error () ** 2 end do end do end if error = sqrt (variance) end function process_get_error_tot module function process_get_efficiency_tot (process) result (efficiency) real(default) :: efficiency class(process_t), intent(in) :: process real(default) :: den, eff, int integer :: i, j, i_component den = zero if (allocated (process%mci_entry)) then do i = 1, size (process%mci_entry) do j = 1, size (process%mci_entry(i)%i_component) i_component = process%mci_entry(i)%i_component(j) if (process%component_can_be_integrated(i_component)) then int = process%get_integral (i) if (int > 0) then eff = process%mci_entry(i)%get_efficiency () if (eff > 0) then den = den + int / eff else efficiency = 0 return end if end if end if end do end do end if if (den > 0) then efficiency = process%get_integral () / den else efficiency = 0 end if end function process_get_efficiency_tot @ %def process_get_integral process_get_efficiency @ Let us call the ratio of the NLO and the LO result $\iota = I_{NLO} / I_{LO}$. Then usual error propagation gives \begin{equation*} \sigma_{\iota}^2 = \left(\frac{\partial \iota}{\partial I_{LO}}\right)^2 \sigma_{I_{LO}}^2 + \left(\frac{\partial \iota}{\partial I_{NLO}}\right)^2 \sigma_{I_{NLO}}^2 = \frac{I_{NLO}^2\sigma_{I_{LO}}^2}{I_{LO}^4} + \frac{\sigma_{I_{NLO}}^2}{I_{LO}^2}. \end{equation*} <>= procedure :: get_correction => process_get_correction procedure :: get_correction_error => process_get_correction_error <>= module function process_get_correction (process) result (ratio) real(default) :: ratio class(process_t), intent(in) :: process end function process_get_correction module function process_get_correction_error (process) result (error) real(default) :: error class(process_t), intent(in) :: process end function process_get_correction_error <>= module function process_get_correction (process) result (ratio) real(default) :: ratio class(process_t), intent(in) :: process integer :: i_mci, i_component real(default) :: int_born, int_nlo int_nlo = zero int_born = process%mci_entry(1)%get_integral () i_mci = 2 do i_component = 2, size (process%component) if (process%component_can_be_integrated (i_component)) then int_nlo = int_nlo + process%mci_entry(i_mci)%get_integral () i_mci = i_mci + 1 end if end do ratio = int_nlo / int_born * 100 end function process_get_correction module function process_get_correction_error (process) result (error) real(default) :: error class(process_t), intent(in) :: process real(default) :: int_born, sum_int_nlo real(default) :: err_born, err2 integer :: i_mci, i_component sum_int_nlo = zero; err2 = zero int_born = process%mci_entry(1)%get_integral () err_born = process%mci_entry(1)%get_error () i_mci = 2 do i_component = 2, size (process%component) if (process%component_can_be_integrated (i_component)) then sum_int_nlo = sum_int_nlo + process%mci_entry(i_mci)%get_integral () err2 = err2 + process%mci_entry(i_mci)%get_error()**2 i_mci = i_mci + 1 end if end do error = sqrt (err2 / int_born**2 + sum_int_nlo**2 * err_born**2 / int_born**4) * 100 end function process_get_correction_error @ %def process_get_correction process_get_correction_error @ This routine asks [[beam_config]] for the frame. <>= procedure :: lab_is_cm => process_lab_is_cm <>= pure module function process_lab_is_cm (process) result (lab_is_cm) logical :: lab_is_cm class(process_t), intent(in) :: process end function process_lab_is_cm <>= pure module function process_lab_is_cm (process) result (lab_is_cm) logical :: lab_is_cm class(process_t), intent(in) :: process lab_is_cm = process%beam_config%lab_is_cm end function process_lab_is_cm @ %def process_lab_is_cm @ <>= procedure :: get_component_ptr => process_get_component_ptr <>= module function process_get_component_ptr (process, i) result (component) type(process_component_t), pointer :: component class(process_t), intent(in), target :: process integer, intent(in) :: i end function process_get_component_ptr <>= module function process_get_component_ptr (process, i) result (component) type(process_component_t), pointer :: component class(process_t), intent(in), target :: process integer, intent(in) :: i component => process%component(i) end function process_get_component_ptr @ %def process_get_component_ptr @ <>= procedure :: get_qcd => process_get_qcd <>= module function process_get_qcd (process) result (qcd) type(qcd_t) :: qcd class(process_t), intent(in) :: process end function process_get_qcd <>= module function process_get_qcd (process) result (qcd) type(qcd_t) :: qcd class(process_t), intent(in) :: process qcd = process%config%get_qcd () end function process_get_qcd @ %def process_get_qcd @ <>= generic :: get_component_type => get_component_type_single procedure :: get_component_type_single => process_get_component_type_single <>= elemental module function process_get_component_type_single & (process, i_component) result (comp_type) integer :: comp_type class(process_t), intent(in) :: process integer, intent(in) :: i_component end function process_get_component_type_single <>= elemental module function process_get_component_type_single & (process, i_component) result (comp_type) integer :: comp_type class(process_t), intent(in) :: process integer, intent(in) :: i_component comp_type = process%component(i_component)%component_type end function process_get_component_type_single @ %def process_get_component_type_single @ <>= generic :: get_component_type => get_component_type_all procedure :: get_component_type_all => process_get_component_type_all <>= module function process_get_component_type_all & (process) result (comp_type) integer, dimension(:), allocatable :: comp_type class(process_t), intent(in) :: process end function process_get_component_type_all <>= module function process_get_component_type_all & (process) result (comp_type) integer, dimension(:), allocatable :: comp_type class(process_t), intent(in) :: process allocate (comp_type (size (process%component))) comp_type = process%component%component_type end function process_get_component_type_all @ %def process_get_component_type_all @ <>= procedure :: get_component_i_terms => process_get_component_i_terms <>= module function process_get_component_i_terms & (process, i_component) result (i_term) integer, dimension(:), allocatable :: i_term class(process_t), intent(in) :: process integer, intent(in) :: i_component end function process_get_component_i_terms <>= module function process_get_component_i_terms & (process, i_component) result (i_term) integer, dimension(:), allocatable :: i_term class(process_t), intent(in) :: process integer, intent(in) :: i_component allocate (i_term (size (process%component(i_component)%i_term))) i_term = process%component(i_component)%i_term end function process_get_component_i_terms @ %def process_get_component_i_terms @ <>= procedure :: get_n_allowed_born => process_get_n_allowed_born <>= module function process_get_n_allowed_born (process, i_born) result (n_born) class(process_t), intent(inout) :: process integer, intent(in) :: i_born integer :: n_born end function process_get_n_allowed_born <>= module function process_get_n_allowed_born (process, i_born) result (n_born) class(process_t), intent(inout) :: process integer, intent(in) :: i_born integer :: n_born n_born = process%term(i_born)%n_allowed end function process_get_n_allowed_born @ %def process_get_n_allowed_born @ Workaround getter. Would be better to remove this. <>= procedure :: get_pcm_ptr => process_get_pcm_ptr <>= module function process_get_pcm_ptr (process) result (pcm) class(pcm_t), pointer :: pcm class(process_t), intent(in), target :: process end function process_get_pcm_ptr <>= module function process_get_pcm_ptr (process) result (pcm) class(pcm_t), pointer :: pcm class(process_t), intent(in), target :: process pcm => process%pcm end function process_get_pcm_ptr @ %def process_get_pcm_ptr <>= generic :: component_can_be_integrated => component_can_be_integrated_single generic :: component_can_be_integrated => component_can_be_integrated_all procedure :: component_can_be_integrated_single => & process_component_can_be_integrated_single <>= module function process_component_can_be_integrated_single & (process, i_component) result (active) logical :: active class(process_t), intent(in) :: process integer, intent(in) :: i_component end function process_component_can_be_integrated_single <>= module function process_component_can_be_integrated_single & (process, i_component) result (active) logical :: active class(process_t), intent(in) :: process integer, intent(in) :: i_component logical :: combined_integration select type (pcm => process%pcm) type is (pcm_nlo_t) combined_integration = pcm%settings%combined_integration class default combined_integration = .false. end select associate (component => process%component(i_component)) active = component%can_be_integrated () if (combined_integration) & active = active .and. component%component_type <= COMP_MASTER end associate end function process_component_can_be_integrated_single @ %def process_component_can_be_integrated_single @ <>= procedure :: component_can_be_integrated_all => & process_component_can_be_integrated_all <>= module function process_component_can_be_integrated_all & (process) result (val) logical, dimension(:), allocatable :: val class(process_t), intent(in) :: process end function process_component_can_be_integrated_all <>= module function process_component_can_be_integrated_all (process) result (val) logical, dimension(:), allocatable :: val class(process_t), intent(in) :: process integer :: i allocate (val (size (process%component))) do i = 1, size (process%component) val(i) = process%component_can_be_integrated (i) end do end function process_component_can_be_integrated_all @ %def process_component_can_be_integrated_all @ <>= procedure :: reset_selected_cores => process_reset_selected_cores <>= pure module subroutine process_reset_selected_cores (process) class(process_t), intent(inout) :: process end subroutine process_reset_selected_cores <>= pure module subroutine process_reset_selected_cores (process) class(process_t), intent(inout) :: process process%pcm%component_selected = .false. end subroutine process_reset_selected_cores @ %def process_reset_selected_cores @ <>= procedure :: select_components => process_select_components <>= pure module subroutine process_select_components (process, indices) class(process_t), intent(inout) :: process integer, dimension(:), intent(in) :: indices end subroutine process_select_components <>= pure module subroutine process_select_components (process, indices) class(process_t), intent(inout) :: process integer, dimension(:), intent(in) :: indices associate (pcm => process%pcm) pcm%component_selected(indices) = .true. end associate end subroutine process_select_components @ %def process_select_components @ <>= procedure :: component_is_selected => process_component_is_selected <>= pure module function process_component_is_selected & (process, index) result (val) logical :: val class(process_t), intent(in) :: process integer, intent(in) :: index end function process_component_is_selected <>= pure module function process_component_is_selected & (process, index) result (val) logical :: val class(process_t), intent(in) :: process integer, intent(in) :: index associate (pcm => process%pcm) val = pcm%component_selected(index) end associate end function process_component_is_selected @ %def process_component_is_selected @ <>= procedure :: get_coupling_powers => process_get_coupling_powers <>= pure module subroutine process_get_coupling_powers & (process, alpha_power, alphas_power) class(process_t), intent(in) :: process integer, intent(out) :: alpha_power, alphas_power end subroutine process_get_coupling_powers <>= pure module subroutine process_get_coupling_powers & (process, alpha_power, alphas_power) class(process_t), intent(in) :: process integer, intent(out) :: alpha_power, alphas_power call process%component(1)%config%get_coupling_powers & (alpha_power, alphas_power) end subroutine process_get_coupling_powers @ %def process_get_coupling_powers @ <>= procedure :: get_real_component => process_get_real_component <>= module function process_get_real_component (process) result (i_real) integer :: i_real class(process_t), intent(in) :: process end function process_get_real_component <>= module function process_get_real_component (process) result (i_real) integer :: i_real class(process_t), intent(in) :: process integer :: i_component type(process_component_def_t), pointer :: config => null () i_real = 0 do i_component = 1, size (process%component) config => process%get_component_def_ptr (i_component) if (config%get_nlo_type () == NLO_REAL) then i_real = i_component exit end if end do end function process_get_real_component @ %def process_get_real_component @ <>= procedure :: extract_active_component_mci => & process_extract_active_component_mci <>= module function process_extract_active_component_mci & (process) result (i_active) integer :: i_active class(process_t), intent(in) :: process end function process_extract_active_component_mci <>= module function process_extract_active_component_mci & (process) result (i_active) integer :: i_active class(process_t), intent(in) :: process integer :: i_mci, j, i_component, n_active call count_n_active () if (n_active /= 1) i_active = 0 contains subroutine count_n_active () n_active = 0 do i_mci = 1, size (process%mci_entry) associate (mci_entry => process%mci_entry(i_mci)) do j = 1, size (mci_entry%i_component) i_component = mci_entry%i_component(j) associate (component => process%component (i_component)) if (component%can_be_integrated ()) then i_active = i_mci n_active = n_active + 1 end if end associate end do end associate end do end subroutine count_n_active end function process_extract_active_component_mci @ %def process_extract_active_component_mci @ <>= procedure :: uses_real_partition => process_uses_real_partition <>= module function process_uses_real_partition (process) result (val) logical :: val class(process_t), intent(in) :: process end function process_uses_real_partition <>= module function process_uses_real_partition (process) result (val) logical :: val class(process_t), intent(in) :: process val = any (process%mci_entry%real_partition_type /= REAL_FULL) end function process_uses_real_partition @ %def process_uses_real_partition @ Return the MD5 sums that summarize the process component definitions. These values should be independent of parameters, beam details, expressions, etc. They can be used for checking the integrity of a process when reusing an old event file. <>= procedure :: get_md5sum_prc => process_get_md5sum_prc <>= module function process_get_md5sum_prc & (process, i_component) result (md5sum) character(32) :: md5sum class(process_t), intent(in) :: process integer, intent(in) :: i_component end function process_get_md5sum_prc <>= module function process_get_md5sum_prc (process, i_component) result (md5sum) character(32) :: md5sum class(process_t), intent(in) :: process integer, intent(in) :: i_component if (process%component(i_component)%active) then md5sum = process%component(i_component)%config%get_md5sum () else md5sum = "" end if end function process_get_md5sum_prc @ %def process_get_md5sum_prc @ Return the MD5 sums that summarize the state of the MCI integrators. These values should encode all process data, integration and phase space configuration, etc., and the integration results. They can thus be used for checking the integrity of an event-generation setup when reusing an old event file. <>= procedure :: get_md5sum_mci => process_get_md5sum_mci <>= module function process_get_md5sum_mci (process, i_mci) result (md5sum) character(32) :: md5sum class(process_t), intent(in) :: process integer, intent(in) :: i_mci end function process_get_md5sum_mci <>= module function process_get_md5sum_mci (process, i_mci) result (md5sum) character(32) :: md5sum class(process_t), intent(in) :: process integer, intent(in) :: i_mci md5sum = process%mci_entry(i_mci)%get_md5sum () end function process_get_md5sum_mci @ %def process_get_md5sum_mci @ Return the MD5 sum of the process configuration. This should encode the process setup, data, and expressions, but no integration results. <>= procedure :: get_md5sum_cfg => process_get_md5sum_cfg <>= module function process_get_md5sum_cfg (process) result (md5sum) character(32) :: md5sum class(process_t), intent(in) :: process end function process_get_md5sum_cfg <>= module function process_get_md5sum_cfg (process) result (md5sum) character(32) :: md5sum class(process_t), intent(in) :: process md5sum = process%config%md5sum end function process_get_md5sum_cfg @ %def process_get_md5sum_cfg @ <>= procedure :: get_n_cores => process_get_n_cores <>= module function process_get_n_cores (process) result (n) integer :: n class(process_t), intent(in) :: process end function process_get_n_cores <>= module function process_get_n_cores (process) result (n) integer :: n class(process_t), intent(in) :: process n = process%pcm%n_cores end function process_get_n_cores @ %def process_get_n_cores @ <>= procedure :: get_base_i_term => process_get_base_i_term <>= module function process_get_base_i_term & (process, i_component) result (i_term) integer :: i_term class(process_t), intent(in) :: process integer, intent(in) :: i_component end function process_get_base_i_term <>= module function process_get_base_i_term (process, i_component) result (i_term) integer :: i_term class(process_t), intent(in) :: process integer, intent(in) :: i_component i_term = process%component(i_component)%i_term(1) end function process_get_base_i_term @ %def process_get_base_i_term @ <>= procedure :: get_core_term => process_get_core_term <>= module function process_get_core_term (process, i_term) result (core) class(prc_core_t), pointer :: core class(process_t), intent(in), target :: process integer, intent(in) :: i_term end function process_get_core_term <>= module function process_get_core_term (process, i_term) result (core) class(prc_core_t), pointer :: core class(process_t), intent(in), target :: process integer, intent(in) :: i_term integer :: i_core i_core = process%term(i_term)%i_core core => process%core_entry(i_core)%get_core_ptr () end function process_get_core_term @ %def process_get_core_term @ <>= procedure :: get_core_ptr => process_get_core_ptr <>= module function process_get_core_ptr (process, i_core) result (core) class(prc_core_t), pointer :: core class(process_t), intent(in), target :: process integer, intent(in) :: i_core end function process_get_core_ptr <>= module function process_get_core_ptr (process, i_core) result (core) class(prc_core_t), pointer :: core class(process_t), intent(in), target :: process integer, intent(in) :: i_core if (allocated (process%core_entry)) then core => process%core_entry(i_core)%get_core_ptr () else core => null () end if end function process_get_core_ptr @ %def process_get_core_ptr @ <>= procedure :: get_term_ptr => process_get_term_ptr <>= module function process_get_term_ptr (process, i) result (term) type(process_term_t), pointer :: term class(process_t), intent(in), target :: process integer, intent(in) :: i end function process_get_term_ptr <>= module function process_get_term_ptr (process, i) result (term) type(process_term_t), pointer :: term class(process_t), intent(in), target :: process integer, intent(in) :: i term => process%term(i) end function process_get_term_ptr @ %def process_get_term_ptr @ <>= procedure :: get_i_term => process_get_i_term <>= module function process_get_i_term (process, i_core) result (i_term) integer :: i_term class(process_t), intent(in) :: process integer, intent(in) :: i_core end function process_get_i_term <>= module function process_get_i_term (process, i_core) result (i_term) integer :: i_term class(process_t), intent(in) :: process integer, intent(in) :: i_core do i_term = 1, process%get_n_terms () if (process%term(i_term)%i_core == i_core) return end do i_term = -1 end function process_get_i_term @ %def process_get_i_term @ <>= procedure :: get_i_core => process_get_i_core <>= module function process_get_i_core (process, i_term) result (i_core) class(process_t), intent(in) :: process integer, intent(in) :: i_term integer :: i_core end function process_get_i_core <>= module function process_get_i_core (process, i_term) result (i_core) class(process_t), intent(in) :: process integer, intent(in) :: i_term integer :: i_core i_core = process%term(i_term)%i_core end function process_get_i_core @ %def process_get_i_core @ <>= procedure :: set_i_mci_work => process_set_i_mci_work <>= module subroutine process_set_i_mci_work (process, i_mci) class(process_t), intent(inout) :: process integer, intent(in) :: i_mci end subroutine process_set_i_mci_work <>= module subroutine process_set_i_mci_work (process, i_mci) class(process_t), intent(inout) :: process integer, intent(in) :: i_mci process%mci_entry(i_mci)%i_mci = i_mci end subroutine process_set_i_mci_work @ %def process_set_i_mci_work @ <>= procedure :: get_i_mci_work => process_get_i_mci_work <>= pure module function process_get_i_mci_work & (process, i_mci) result (i_mci_work) integer :: i_mci_work class(process_t), intent(in) :: process integer, intent(in) :: i_mci end function process_get_i_mci_work <>= pure module function process_get_i_mci_work & (process, i_mci) result (i_mci_work) integer :: i_mci_work class(process_t), intent(in) :: process integer, intent(in) :: i_mci i_mci_work = process%mci_entry(i_mci)%i_mci end function process_get_i_mci_work @ %def process_get_i_mci_work @ <>= procedure :: get_i_sub => process_get_i_sub <>= elemental module function process_get_i_sub (process, i_term) result (i_sub) integer :: i_sub class(process_t), intent(in) :: process integer, intent(in) :: i_term end function process_get_i_sub <>= elemental module function process_get_i_sub (process, i_term) result (i_sub) integer :: i_sub class(process_t), intent(in) :: process integer, intent(in) :: i_term i_sub = process%term(i_term)%i_sub end function process_get_i_sub @ %def process_get_i_sub @ <>= procedure :: get_i_term_virtual => process_get_i_term_virtual <>= elemental module function process_get_i_term_virtual & (process) result (i_term) integer :: i_term class(process_t), intent(in) :: process end function process_get_i_term_virtual <>= elemental module function process_get_i_term_virtual (process) result (i_term) integer :: i_term class(process_t), intent(in) :: process integer :: i_component i_term = 0 do i_component = 1, size (process%component) if (process%component(i_component)%get_nlo_type () == NLO_VIRTUAL) & i_term = process%component(i_component)%i_term(1) end do end function process_get_i_term_virtual @ %def process_get_i_term_virtual @ <>= generic :: component_is_active => component_is_active_single procedure :: component_is_active_single => process_component_is_active_single <>= elemental module function process_component_is_active_single & (process, i_comp) result (val) logical :: val class(process_t), intent(in) :: process integer, intent(in) :: i_comp end function process_component_is_active_single <>= elemental module function process_component_is_active_single & (process, i_comp) result (val) logical :: val class(process_t), intent(in) :: process integer, intent(in) :: i_comp val = process%component(i_comp)%is_active () end function process_component_is_active_single @ %def process_component_is_active_single @ <>= generic :: component_is_active => component_is_active_all procedure :: component_is_active_all => process_component_is_active_all <>= pure module function process_component_is_active_all (process) result (val) logical, dimension(:), allocatable :: val class(process_t), intent(in) :: process end function process_component_is_active_all <>= pure module function process_component_is_active_all (process) result (val) logical, dimension(:), allocatable :: val class(process_t), intent(in) :: process allocate (val (size (process%component))) val = process%component%is_active () end function process_component_is_active_all @ %def process_component_is_active_all @ \subsection{Default iterations} If the user does not specify the passes and iterations for integration, we should be able to give reasonable defaults. These depend on the process, therefore we implement the following procedures as methods of the process object. The algorithm is not very sophisticated yet, it may be improved by looking at the process in more detail. We investigate only the first process component, assuming that it characterizes the complexity of the process reasonable well. The number of passes is limited to two: one for adaption, one for integration. <>= procedure :: get_n_pass_default => process_get_n_pass_default procedure :: adapt_grids_default => process_adapt_grids_default procedure :: adapt_weights_default => process_adapt_weights_default <>= module function process_get_n_pass_default (process) result (n_pass) class(process_t), intent(in) :: process integer :: n_pass end function process_get_n_pass_default module function process_adapt_grids_default (process, pass) result (flag) class(process_t), intent(in) :: process integer, intent(in) :: pass logical :: flag end function process_adapt_grids_default module function process_adapt_weights_default (process, pass) result (flag) class(process_t), intent(in) :: process integer, intent(in) :: pass logical :: flag end function process_adapt_weights_default <>= module function process_get_n_pass_default (process) result (n_pass) class(process_t), intent(in) :: process integer :: n_pass integer :: n_eff type(process_component_def_t), pointer :: config config => process%component(1)%config n_eff = config%get_n_tot () - 2 select case (n_eff) case (1) n_pass = 1 case default n_pass = 2 end select end function process_get_n_pass_default module function process_adapt_grids_default (process, pass) result (flag) class(process_t), intent(in) :: process integer, intent(in) :: pass logical :: flag integer :: n_eff type(process_component_def_t), pointer :: config config => process%component(1)%config n_eff = config%get_n_tot () - 2 select case (n_eff) case (1) flag = .false. case default select case (pass) case (1); flag = .true. case (2); flag = .false. case default call msg_bug ("adapt grids default: impossible pass index") end select end select end function process_adapt_grids_default module function process_adapt_weights_default (process, pass) result (flag) class(process_t), intent(in) :: process integer, intent(in) :: pass logical :: flag integer :: n_eff type(process_component_def_t), pointer :: config config => process%component(1)%config n_eff = config%get_n_tot () - 2 select case (n_eff) case (1) flag = .false. case default select case (pass) case (1); flag = .true. case (2); flag = .false. case default call msg_bug ("adapt weights default: impossible pass index") end select end select end function process_adapt_weights_default @ %def process_get_n_pass_default @ %def process_adapt_grids_default @ %def process_adapt_weights_default @ The number of iterations and calls per iteration depends on the number of outgoing particles. <>= procedure :: get_n_it_default => process_get_n_it_default procedure :: get_n_calls_default => process_get_n_calls_default <>= module function process_get_n_it_default (process, pass) result (n_it) class(process_t), intent(in) :: process integer, intent(in) :: pass integer :: n_it end function process_get_n_it_default module function process_get_n_calls_default (process, pass) result (n_calls) class(process_t), intent(in) :: process integer, intent(in) :: pass integer :: n_calls end function process_get_n_calls_default <>= module function process_get_n_it_default (process, pass) result (n_it) class(process_t), intent(in) :: process integer, intent(in) :: pass integer :: n_it integer :: n_eff type(process_component_def_t), pointer :: config config => process%component(1)%config n_eff = config%get_n_tot () - 2 select case (pass) case (1) select case (n_eff) case (1); n_it = 1 case (2); n_it = 3 case (3); n_it = 5 case (4:5); n_it = 10 case (6); n_it = 15 case (7:); n_it = 20 end select case (2) select case (n_eff) case (:3); n_it = 3 case (4:); n_it = 5 end select end select end function process_get_n_it_default module function process_get_n_calls_default (process, pass) result (n_calls) class(process_t), intent(in) :: process integer, intent(in) :: pass integer :: n_calls integer :: n_eff type(process_component_def_t), pointer :: config config => process%component(1)%config n_eff = config%get_n_tot () - 2 select case (pass) case (1) select case (n_eff) case (1); n_calls = 100 case (2); n_calls = 1000 case (3); n_calls = 5000 case (4); n_calls = 10000 case (5); n_calls = 20000 case (6:); n_calls = 50000 end select case (2) select case (n_eff) case (:3); n_calls = 10000 case (4); n_calls = 20000 case (5); n_calls = 50000 case (6); n_calls = 100000 case (7:); n_calls = 200000 end select end select end function process_get_n_calls_default @ %def process_get_n_it_default @ %def process_get_n_calls_default @ \subsection{Constant process data} Manually set the Run ID (unit test only). <>= procedure :: set_run_id => process_set_run_id <>= module subroutine process_set_run_id (process, run_id) class(process_t), intent(inout) :: process type(string_t), intent(in) :: run_id end subroutine process_set_run_id <>= module subroutine process_set_run_id (process, run_id) class(process_t), intent(inout) :: process type(string_t), intent(in) :: run_id process%meta%run_id = run_id end subroutine process_set_run_id @ %def process_set_run_id @ The following methods return basic process data that stay constant after initialization. The process and IDs. <>= procedure :: get_id => process_get_id procedure :: get_num_id => process_get_num_id procedure :: get_run_id => process_get_run_id procedure :: get_library_name => process_get_library_name <>= module function process_get_id (process) result (id) class(process_t), intent(in) :: process type(string_t) :: id end function process_get_id module function process_get_num_id (process) result (id) class(process_t), intent(in) :: process integer :: id end function process_get_num_id module function process_get_run_id (process) result (id) class(process_t), intent(in) :: process type(string_t) :: id end function process_get_run_id module function process_get_library_name (process) result (id) class(process_t), intent(in) :: process type(string_t) :: id end function process_get_library_name <>= module function process_get_id (process) result (id) class(process_t), intent(in) :: process type(string_t) :: id id = process%meta%id end function process_get_id module function process_get_num_id (process) result (id) class(process_t), intent(in) :: process integer :: id id = process%meta%num_id end function process_get_num_id module function process_get_run_id (process) result (id) class(process_t), intent(in) :: process type(string_t) :: id id = process%meta%run_id end function process_get_run_id module function process_get_library_name (process) result (id) class(process_t), intent(in) :: process type(string_t) :: id id = process%meta%lib_name end function process_get_library_name @ %def process_get_id process_get_num_id @ %def process_get_run_id process_get_library_name @ The number of incoming particles. <>= procedure :: get_n_in => process_get_n_in <>= module function process_get_n_in (process) result (n) class(process_t), intent(in) :: process integer :: n end function process_get_n_in <>= module function process_get_n_in (process) result (n) class(process_t), intent(in) :: process integer :: n n = process%config%n_in end function process_get_n_in @ %def process_get_n_in @ The number of MCI data sets. <>= procedure :: get_n_mci => process_get_n_mci <>= module function process_get_n_mci (process) result (n) class(process_t), intent(in) :: process integer :: n end function process_get_n_mci <>= module function process_get_n_mci (process) result (n) class(process_t), intent(in) :: process integer :: n n = process%config%n_mci end function process_get_n_mci @ %def process_get_n_mci @ The number of process components, total. <>= procedure :: get_n_components => process_get_n_components <>= module function process_get_n_components (process) result (n) class(process_t), intent(in) :: process integer :: n end function process_get_n_components <>= module function process_get_n_components (process) result (n) class(process_t), intent(in) :: process integer :: n n = process%meta%n_components end function process_get_n_components @ %def process_get_n_components @ The number of process terms, total. <>= procedure :: get_n_terms => process_get_n_terms <>= module function process_get_n_terms (process) result (n) class(process_t), intent(in) :: process integer :: n end function process_get_n_terms <>= module function process_get_n_terms (process) result (n) class(process_t), intent(in) :: process integer :: n n = process%config%n_terms end function process_get_n_terms @ %def process_get_n_terms @ Return the indices of the components that belong to a specific MCI entry. <>= procedure :: get_i_component => process_get_i_component <>= module subroutine process_get_i_component (process, i_mci, i_component) class(process_t), intent(in) :: process integer, intent(in) :: i_mci integer, dimension(:), intent(out), allocatable :: i_component end subroutine process_get_i_component <>= module subroutine process_get_i_component (process, i_mci, i_component) class(process_t), intent(in) :: process integer, intent(in) :: i_mci integer, dimension(:), intent(out), allocatable :: i_component associate (mci_entry => process%mci_entry(i_mci)) allocate (i_component (size (mci_entry%i_component))) i_component = mci_entry%i_component end associate end subroutine process_get_i_component @ %def process_get_i_component @ Return the ID of a specific component. <>= procedure :: get_component_id => process_get_component_id <>= module function process_get_component_id (process, i_component) result (id) class(process_t), intent(in) :: process integer, intent(in) :: i_component type(string_t) :: id end function process_get_component_id <>= module function process_get_component_id (process, i_component) result (id) class(process_t), intent(in) :: process integer, intent(in) :: i_component type(string_t) :: id id = process%meta%component_id(i_component) end function process_get_component_id @ %def process_get_component_id @ Return a pointer to the definition of a specific component. <>= procedure :: get_component_def_ptr => process_get_component_def_ptr <>= module function process_get_component_def_ptr & (process, i_component) result (ptr) type(process_component_def_t), pointer :: ptr class(process_t), intent(in) :: process integer, intent(in) :: i_component end function process_get_component_def_ptr <>= module function process_get_component_def_ptr & (process, i_component) result (ptr) type(process_component_def_t), pointer :: ptr class(process_t), intent(in) :: process integer, intent(in) :: i_component ptr => process%config%process_def%get_component_def_ptr (i_component) end function process_get_component_def_ptr @ %def process_get_component_def_ptr @ These procedures extract and restore (by transferring the allocation) the process core. This is useful for changing process parameters from outside this module. <>= procedure :: extract_core => process_extract_core procedure :: restore_core => process_restore_core <>= module subroutine process_extract_core (process, i_term, core) class(process_t), intent(inout) :: process integer, intent(in) :: i_term class(prc_core_t), intent(inout), allocatable :: core end subroutine process_extract_core module subroutine process_restore_core (process, i_term, core) class(process_t), intent(inout) :: process integer, intent(in) :: i_term class(prc_core_t), intent(inout), allocatable :: core end subroutine process_restore_core <>= module subroutine process_extract_core (process, i_term, core) class(process_t), intent(inout) :: process integer, intent(in) :: i_term class(prc_core_t), intent(inout), allocatable :: core integer :: i_core i_core = process%term(i_term)%i_core call move_alloc (from = process%core_entry(i_core)%core, to = core) end subroutine process_extract_core module subroutine process_restore_core (process, i_term, core) class(process_t), intent(inout) :: process integer, intent(in) :: i_term class(prc_core_t), intent(inout), allocatable :: core integer :: i_core i_core = process%term(i_term)%i_core call move_alloc (from = core, to = process%core_entry(i_core)%core) end subroutine process_restore_core @ %def process_extract_core @ %def process_restore_core @ The block of process constants. <>= procedure :: get_constants => process_get_constants <>= module function process_get_constants (process, i_core) result (data) type(process_constants_t) :: data class(process_t), intent(in) :: process integer, intent(in) :: i_core end function process_get_constants <>= module function process_get_constants (process, i_core) result (data) type(process_constants_t) :: data class(process_t), intent(in) :: process integer, intent(in) :: i_core data = process%core_entry(i_core)%core%data end function process_get_constants @ %def process_get_constants @ <>= procedure :: get_config => process_get_config <>= module function process_get_config (process) result (config) type(process_config_data_t) :: config class(process_t), intent(in) :: process end function process_get_config <>= module function process_get_config (process) result (config) type(process_config_data_t) :: config class(process_t), intent(in) :: process config = process%config end function process_get_config @ %def process_get_config @ Construct an MD5 sum for the constant data, including the NLO type. For the NLO type [[NLO_MISMATCH]], we pretend that this was [[NLO_SUBTRACTION]] instead. TODO wk 2018: should not depend explicitly on NLO data. <>= procedure :: get_md5sum_constants => process_get_md5sum_constants <>= module function process_get_md5sum_constants (process, i_component, & type_string, nlo_type) result (this_md5sum) character(32) :: this_md5sum class(process_t), intent(in) :: process integer, intent(in) :: i_component type(string_t), intent(in) :: type_string integer, intent(in) :: nlo_type end function process_get_md5sum_constants <>= module function process_get_md5sum_constants (process, i_component, & type_string, nlo_type) result (this_md5sum) character(32) :: this_md5sum class(process_t), intent(in) :: process integer, intent(in) :: i_component type(string_t), intent(in) :: type_string integer, intent(in) :: nlo_type type(process_constants_t) :: data integer :: unit call process%env%fill_process_constants (process%meta%id, i_component, data) unit = data%fill_unit_for_md5sum (.false.) write (unit, '(A)') char(type_string) select case (nlo_type) case (NLO_MISMATCH) write (unit, '(I0)') NLO_SUBTRACTION case default write (unit, '(I0)') nlo_type end select rewind (unit) this_md5sum = md5sum (unit) close (unit) end function process_get_md5sum_constants @ %def process_get_md5sum_constants @ Return the set of outgoing flavors that are associated with a particular term. We deduce this from the effective interaction. <>= procedure :: get_term_flv_out => process_get_term_flv_out <>= module subroutine process_get_term_flv_out (process, i_term, flv) class(process_t), intent(in), target :: process integer, intent(in) :: i_term type(flavor_t), dimension(:,:), allocatable, intent(out) :: flv end subroutine process_get_term_flv_out <>= module subroutine process_get_term_flv_out (process, i_term, flv) class(process_t), intent(in), target :: process integer, intent(in) :: i_term type(flavor_t), dimension(:,:), allocatable, intent(out) :: flv type(interaction_t), pointer :: int int => process%term(i_term)%int_eff if (.not. associated (int)) int => process%term(i_term)%int call int%get_flv_out (flv) end subroutine process_get_term_flv_out @ %def process_get_term_flv_out @ Return true if there is any unstable particle in any of the process terms. We decide this based on the provided model instance, not the one that is stored in the process object. <>= procedure :: contains_unstable => process_contains_unstable <>= module function process_contains_unstable (process, model) result (flag) class(process_t), intent(in) :: process class(model_data_t), intent(in), target :: model logical :: flag end function process_contains_unstable <>= module function process_contains_unstable (process, model) result (flag) class(process_t), intent(in) :: process class(model_data_t), intent(in), target :: model logical :: flag integer :: i_term type(flavor_t), dimension(:,:), allocatable :: flv flag = .false. do i_term = 1, process%get_n_terms () call process%get_term_flv_out (i_term, flv) call flv%set_model (model) flag = .not. all (flv%is_stable ()) deallocate (flv) if (flag) return end do end function process_contains_unstable @ %def process_contains_unstable @ The nominal process energy. <>= procedure :: get_sqrts => process_get_sqrts <>= module function process_get_sqrts (process) result (sqrts) class(process_t), intent(in) :: process real(default) :: sqrts end function process_get_sqrts <>= module function process_get_sqrts (process) result (sqrts) class(process_t), intent(in) :: process real(default) :: sqrts sqrts = process%beam_config%data%get_sqrts () end function process_get_sqrts @ %def process_get_sqrts @ The lab-frame beam energy/energies.. <>= procedure :: get_energy => process_get_energy <>= module function process_get_energy (process) result (e) class(process_t), intent(in) :: process real(default), dimension(:), allocatable :: e end function process_get_energy <>= module function process_get_energy (process) result (e) class(process_t), intent(in) :: process real(default), dimension(:), allocatable :: e e = process%beam_config%data%get_energy () end function process_get_energy @ %def process_get_energy @ The beam polarization in case of simple degrees. <>= procedure :: get_polarization => process_get_polarization <>= module function process_get_polarization (process) result (pol) class(process_t), intent(in) :: process real(default), dimension(process%beam_config%data%n) :: pol end function process_get_polarization <>= module function process_get_polarization (process) result (pol) class(process_t), intent(in) :: process real(default), dimension(process%beam_config%data%n) :: pol pol = process%beam_config%data%get_polarization () end function process_get_polarization @ %def process_get_polarization @ <>= procedure :: get_meta => process_get_meta <>= module function process_get_meta (process) result (meta) type(process_metadata_t) :: meta class(process_t), intent(in) :: process end function process_get_meta <>= module function process_get_meta (process) result (meta) type(process_metadata_t) :: meta class(process_t), intent(in) :: process meta = process%meta end function process_get_meta @ %def process_get_meta <>= procedure :: has_matrix_element => process_has_matrix_element <>= module function process_has_matrix_element & (process, i, is_term_index) result (active) logical :: active class(process_t), intent(in) :: process integer, intent(in), optional :: i logical, intent(in), optional :: is_term_index end function process_has_matrix_element <>= module function process_has_matrix_element & (process, i, is_term_index) result (active) logical :: active class(process_t), intent(in) :: process integer, intent(in), optional :: i logical, intent(in), optional :: is_term_index integer :: i_component logical :: is_term is_term = .false. if (present (i)) then if (present (is_term_index)) is_term = is_term_index if (is_term) then i_component = process%term(i)%i_component else i_component = i end if active = process%component(i_component)%active else active = any (process%component%active) end if end function process_has_matrix_element @ %def process_has_matrix_element @ Pointer to the beam data object. <>= procedure :: get_beam_data_ptr => process_get_beam_data_ptr <>= module function process_get_beam_data_ptr (process) result (beam_data) class(process_t), intent(in), target :: process type(beam_data_t), pointer :: beam_data end function process_get_beam_data_ptr <>= module function process_get_beam_data_ptr (process) result (beam_data) class(process_t), intent(in), target :: process type(beam_data_t), pointer :: beam_data beam_data => process%beam_config%data end function process_get_beam_data_ptr @ %def process_get_beam_data_ptr @ <>= procedure :: get_beam_config => process_get_beam_config <>= module function process_get_beam_config (process) result (beam_config) type(process_beam_config_t) :: beam_config class(process_t), intent(in) :: process end function process_get_beam_config <>= module function process_get_beam_config (process) result (beam_config) type(process_beam_config_t) :: beam_config class(process_t), intent(in) :: process beam_config = process%beam_config end function process_get_beam_config @ %def process_get_beam_config @ <>= procedure :: get_beam_config_ptr => process_get_beam_config_ptr <>= module function process_get_beam_config_ptr (process) result (beam_config) type(process_beam_config_t), pointer :: beam_config class(process_t), intent(in), target :: process end function process_get_beam_config_ptr <>= module function process_get_beam_config_ptr (process) result (beam_config) type(process_beam_config_t), pointer :: beam_config class(process_t), intent(in), target :: process beam_config => process%beam_config end function process_get_beam_config_ptr @ %def process_get_beam_config_ptr @ Get the PDF set currently in use, if any. <>= procedure :: get_pdf_set => process_get_pdf_set <>= module function process_get_pdf_set (process) result (pdf_set) class(process_t), intent(in) :: process integer :: pdf_set end function process_get_pdf_set <>= module function process_get_pdf_set (process) result (pdf_set) class(process_t), intent(in) :: process integer :: pdf_set pdf_set = process%beam_config%get_pdf_set () end function process_get_pdf_set @ %def process_get_pdf_set @ <>= procedure :: pcm_contains_pdfs => process_pcm_contains_pdfs <>= module function process_pcm_contains_pdfs (process) result (has_pdfs) logical :: has_pdfs class(process_t), intent(in) :: process end function process_pcm_contains_pdfs <>= module function process_pcm_contains_pdfs (process) result (has_pdfs) logical :: has_pdfs class(process_t), intent(in) :: process has_pdfs = process%pcm%has_pdfs end function process_pcm_contains_pdfs @ %def process_pcm_contains_pdfs @ Get the beam spectrum file currently in use, if any. <>= procedure :: get_beam_file => process_get_beam_file <>= module function process_get_beam_file (process) result (file) class(process_t), intent(in) :: process type(string_t) :: file end function process_get_beam_file <>= module function process_get_beam_file (process) result (file) class(process_t), intent(in) :: process type(string_t) :: file file = process%beam_config%get_beam_file () end function process_get_beam_file @ %def process_get_beam_file @ Pointer to the process variable list. <>= procedure :: get_var_list_ptr => process_get_var_list_ptr <>= module function process_get_var_list_ptr (process) result (ptr) class(process_t), intent(in), target :: process type(var_list_t), pointer :: ptr end function process_get_var_list_ptr <>= module function process_get_var_list_ptr (process) result (ptr) class(process_t), intent(in), target :: process type(var_list_t), pointer :: ptr ptr => process%env%get_var_list_ptr () end function process_get_var_list_ptr @ %def process_get_var_list_ptr @ Pointer to the common model. <>= procedure :: get_model_ptr => process_get_model_ptr <>= module function process_get_model_ptr (process) result (ptr) class(process_t), intent(in) :: process class(model_data_t), pointer :: ptr end function process_get_model_ptr <>= module function process_get_model_ptr (process) result (ptr) class(process_t), intent(in) :: process class(model_data_t), pointer :: ptr ptr => process%config%model end function process_get_model_ptr @ %def process_get_model_ptr @ Use the embedded RNG factory to spawn a new random-number generator instance. (This modifies the state of the factory.) <>= procedure :: make_rng => process_make_rng <>= module subroutine process_make_rng (process, rng) class(process_t), intent(inout) :: process class(rng_t), intent(out), allocatable :: rng end subroutine process_make_rng <>= module subroutine process_make_rng (process, rng) class(process_t), intent(inout) :: process class(rng_t), intent(out), allocatable :: rng if (allocated (process%rng_factory)) then call process%rng_factory%make (rng) else call msg_bug ("Process: make rng: factory not allocated") end if end subroutine process_make_rng @ %def process_make_rng @ \subsection{Compute an amplitude} Each process variant should allow for computing an amplitude value directly, without generating a process instance. The process component is selected by the index [[i]]. The term within the process component is selected by [[j]]. The momentum combination is transferred as the array [[p]]. The function sets the specific quantum state via the indices of a flavor [[f]], helicity [[h]], and color [[c]] combination. Each index refers to the list of flavor, helicity, and color states, respectively, as stored in the process data. Optionally, we may set factorization and renormalization scale. If unset, the partonic c.m.\ energy is inserted. The function checks arguments for validity. For invalid arguments (quantum states), we return zero. <>= procedure :: compute_amplitude => process_compute_amplitude <>= module function process_compute_amplitude (process, i_core, i, j, p, & f, h, c, fac_scale, ren_scale, alpha_qcd_forced) result (amp) class(process_t), intent(in), target :: process integer, intent(in) :: i_core integer, intent(in) :: i, j type(vector4_t), dimension(:), intent(in) :: p integer, intent(in) :: f, h, c real(default), intent(in), optional :: fac_scale, ren_scale real(default), intent(in), allocatable, optional :: alpha_qcd_forced complex(default) :: amp end function process_compute_amplitude <>= module function process_compute_amplitude (process, i_core, i, j, p, & f, h, c, fac_scale, ren_scale, alpha_qcd_forced) result (amp) class(process_t), intent(in), target :: process integer, intent(in) :: i_core integer, intent(in) :: i, j type(vector4_t), dimension(:), intent(in) :: p integer, intent(in) :: f, h, c real(default), intent(in), optional :: fac_scale, ren_scale real(default), intent(in), allocatable, optional :: alpha_qcd_forced real(default) :: fscale, rscale real(default), allocatable :: aqcd_forced complex(default) :: amp class(prc_core_t), pointer :: core amp = 0 if (0 < i .and. i <= process%meta%n_components) then if (process%component(i)%active) then associate (core => process%core_entry(i_core)%core) associate (data => core%data) if (size (p) == data%n_in + data%n_out & .and. 0 < f .and. f <= data%n_flv & .and. 0 < h .and. h <= data%n_hel & .and. 0 < c .and. c <= data%n_col) then if (present (fac_scale)) then fscale = fac_scale else fscale = sum (p(data%n_in+1:)) ** 1 end if if (present (ren_scale)) then rscale = ren_scale else rscale = fscale end if if (present (alpha_qcd_forced)) then if (allocated (alpha_qcd_forced)) & allocate (aqcd_forced, source = alpha_qcd_forced) end if amp = core%compute_amplitude (j, p, f, h, c, & fscale, rscale, aqcd_forced) end if end associate end associate else amp = 0 end if end if end function process_compute_amplitude @ %def process_compute_amplitude @ Sanity check for the process library. We abort the program if it has changed after process initialization. <>= procedure :: check_library_sanity => process_check_library_sanity <>= module subroutine process_check_library_sanity (process) class(process_t), intent(in) :: process end subroutine process_check_library_sanity <>= module subroutine process_check_library_sanity (process) class(process_t), intent(in) :: process call process%env%check_lib_sanity (process%meta) end subroutine process_check_library_sanity @ %def process_check_library_sanity @ Reset the association to a process library. <>= procedure :: reset_library_ptr => process_reset_library_ptr <>= module subroutine process_reset_library_ptr (process) class(process_t), intent(inout) :: process end subroutine process_reset_library_ptr <>= module subroutine process_reset_library_ptr (process) class(process_t), intent(inout) :: process call process%env%reset_lib_ptr () end subroutine process_reset_library_ptr @ %def process_reset_library_ptr @ <>= procedure :: set_counter_mci_entry => process_set_counter_mci_entry <>= module subroutine process_set_counter_mci_entry (process, i_mci, counter) class(process_t), intent(inout) :: process integer, intent(in) :: i_mci type(process_counter_t), intent(in) :: counter end subroutine process_set_counter_mci_entry <>= module subroutine process_set_counter_mci_entry (process, i_mci, counter) class(process_t), intent(inout) :: process integer, intent(in) :: i_mci type(process_counter_t), intent(in) :: counter process%mci_entry(i_mci)%counter = counter end subroutine process_set_counter_mci_entry @ %def process_set_counter_mci_entry @ This is for suppression of numerical noise in the integration results stored in the [[process_mci_entry]] type. As the error and efficiency enter the MD5 sum, we recompute it. <>= procedure :: pacify => process_pacify <>= module subroutine process_pacify (process, efficiency_reset, error_reset) class(process_t), intent(inout) :: process logical, intent(in), optional :: efficiency_reset, error_reset end subroutine process_pacify <>= module subroutine process_pacify (process, efficiency_reset, error_reset) class(process_t), intent(inout) :: process logical, intent(in), optional :: efficiency_reset, error_reset logical :: eff_reset, err_reset integer :: i eff_reset = .false. err_reset = .false. if (present (efficiency_reset)) eff_reset = efficiency_reset if (present (error_reset)) err_reset = error_reset if (allocated (process%mci_entry)) then do i = 1, size (process%mci_entry) call process%mci_entry(i)%results%pacify (efficiency_reset) if (allocated (process%mci_entry(i)%mci)) then associate (mci => process%mci_entry(i)%mci) if (process%mci_entry(i)%mci%error_known & .and. err_reset) & mci%error = 0 if (process%mci_entry(i)%mci%efficiency_known & .and. eff_reset) & mci%efficiency = 1 call mci%pacify (efficiency_reset, error_reset) call mci%compute_md5sum () end associate end if end do end if end subroutine process_pacify @ %def process_pacify @ The following methods are used only in the unit tests; the access process internals directly that would otherwise be hidden. <>= procedure :: test_allocate_sf_channels procedure :: test_set_component_sf_channel procedure :: test_get_mci_ptr <>= module subroutine test_allocate_sf_channels (process, n) class(process_t), intent(inout) :: process integer, intent(in) :: n end subroutine test_allocate_sf_channels module subroutine test_set_component_sf_channel (process, c) class(process_t), intent(inout) :: process integer, dimension(:), intent(in) :: c end subroutine test_set_component_sf_channel module subroutine test_get_mci_ptr (process, mci) class(process_t), intent(in), target :: process class(mci_t), intent(out), pointer :: mci end subroutine test_get_mci_ptr <>= module subroutine test_allocate_sf_channels (process, n) class(process_t), intent(inout) :: process integer, intent(in) :: n call process%beam_config%allocate_sf_channels (n) end subroutine test_allocate_sf_channels module subroutine test_set_component_sf_channel (process, c) class(process_t), intent(inout) :: process integer, dimension(:), intent(in) :: c call process%component(1)%phs_config%set_sf_channel (c) end subroutine test_set_component_sf_channel module subroutine test_get_mci_ptr (process, mci) class(process_t), intent(in), target :: process class(mci_t), intent(out), pointer :: mci mci => process%mci_entry(1)%mci end subroutine test_get_mci_ptr @ %def test_allocate_sf_channels @ %def test_set_component_sf_channel @ %def test_get_mci_ptr @ <>= procedure :: init_mci_work => process_init_mci_work <>= module subroutine process_init_mci_work (process, mci_work, i) class(process_t), intent(in), target :: process type(mci_work_t), intent(out) :: mci_work integer, intent(in) :: i end subroutine process_init_mci_work <>= module subroutine process_init_mci_work (process, mci_work, i) class(process_t), intent(in), target :: process type(mci_work_t), intent(out) :: mci_work integer, intent(in) :: i call mci_work%init (process%mci_entry(i)) end subroutine process_init_mci_work @ %def process_init_mci_work @ Prepare the process core with type [[test_me]], or otherwise the externally provided [[type_string]] version. The toy dispatchers as a procedure argument come handy, knowing that we need to support only the [[test_me]] and [[template]] matrix-element types. Gfortran 7/8/9 bug, has to remain in the main module: <>= procedure :: setup_test_cores => process_setup_test_cores <>= subroutine dispatch_test_me_core (core, core_def, model, & helicity_selection, qcd, use_color_factors, has_beam_pol) use prc_test_core, only: test_t class(prc_core_t), allocatable, intent(inout) :: core class(prc_core_def_t), intent(in) :: core_def class(model_data_t), intent(in), target, optional :: model type(helicity_selection_t), intent(in), optional :: helicity_selection type(qcd_t), intent(in), optional :: qcd logical, intent(in), optional :: use_color_factors logical, intent(in), optional :: has_beam_pol allocate (test_t :: core) end subroutine dispatch_test_me_core subroutine dispatch_template_core (core, core_def, model, & helicity_selection, qcd, use_color_factors, has_beam_pol) use prc_template_me, only: prc_template_me_t class(prc_core_t), allocatable, intent(inout) :: core class(prc_core_def_t), intent(in) :: core_def class(model_data_t), intent(in), target, optional :: model type(helicity_selection_t), intent(in), optional :: helicity_selection type(qcd_t), intent(in), optional :: qcd logical, intent(in), optional :: use_color_factors logical, intent(in), optional :: has_beam_pol allocate (prc_template_me_t :: core) select type (core) type is (prc_template_me_t) call core%set_parameters (model) end select end subroutine dispatch_template_core subroutine process_setup_test_cores (process, type_string) class(process_t), intent(inout) :: process class(prc_core_t), allocatable :: core type(string_t), intent(in), optional :: type_string if (present (type_string)) then select case (char (type_string)) case ("template") call process%setup_cores (dispatch_template_core) case ("test_me") call process%setup_cores (dispatch_test_me_core) case default call msg_bug ("process setup test cores: unsupported type string") end select else call process%setup_cores (dispatch_test_me_core) end if end subroutine process_setup_test_cores @ %def process_setup_test_cores @ <>= procedure :: get_connected_states => process_get_connected_states <>= module function process_get_connected_states (process, i_component, & connected_terms) result (connected) type(connected_state_t), dimension(:), allocatable :: connected class(process_t), intent(in) :: process integer, intent(in) :: i_component type(connected_state_t), dimension(:), intent(in) :: connected_terms end function process_get_connected_states <>= module function process_get_connected_states (process, i_component, & connected_terms) result (connected) type(connected_state_t), dimension(:), allocatable :: connected class(process_t), intent(in) :: process integer, intent(in) :: i_component type(connected_state_t), dimension(:), intent(in) :: connected_terms integer :: i, i_conn integer :: n_conn n_conn = 0 do i = 1, process%get_n_terms () if (process%term(i)%i_component == i_component) then n_conn = n_conn + 1 end if end do allocate (connected (n_conn)) i_conn = 1 do i = 1, process%get_n_terms () if (process%term(i)%i_component == i_component) then connected (i_conn) = connected_terms(i) i_conn = i_conn + 1 end if end do end function process_get_connected_states @ %def process_get_connected_states @ \subsection{NLO specifics} These subroutines (and the NLO specific properties they work on) could potentially be moved to [[pcm_nlo_t]] and used more generically in [[process_t]] with an appropriate interface in [[pcm_t]] TODO wk 2018: This is used only by event initialization, which deals with an incomplete process object. <>= procedure :: init_nlo_settings => process_init_nlo_settings <>= module subroutine process_init_nlo_settings (process, var_list) class(process_t), intent(inout) :: process type(var_list_t), intent(in), target :: var_list end subroutine process_init_nlo_settings <>= module subroutine process_init_nlo_settings (process, var_list) class(process_t), intent(inout) :: process type(var_list_t), intent(in), target :: var_list select type (pcm => process%pcm) type is (pcm_nlo_t) call pcm%init_nlo_settings (var_list) if (debug_active (D_SUBTRACTION) .or. debug_active (D_VIRTUAL)) & call pcm%settings%write () class default call msg_fatal ("Attempt to set nlo_settings with a non-NLO pcm!") end select end subroutine process_init_nlo_settings @ %def process_init_nlo_settings @ <>= generic :: get_nlo_type_component => get_nlo_type_component_single procedure :: get_nlo_type_component_single => & process_get_nlo_type_component_single <>= elemental module function process_get_nlo_type_component_single & (process, i_component) result (val) integer :: val class(process_t), intent(in) :: process integer, intent(in) :: i_component end function process_get_nlo_type_component_single <>= elemental module function process_get_nlo_type_component_single & (process, i_component) result (val) integer :: val class(process_t), intent(in) :: process integer, intent(in) :: i_component val = process%component(i_component)%get_nlo_type () end function process_get_nlo_type_component_single @ %def process_get_nlo_type_component_single @ <>= generic :: get_nlo_type_component => get_nlo_type_component_all procedure :: get_nlo_type_component_all => process_get_nlo_type_component_all <>= pure module function process_get_nlo_type_component_all & (process) result (val) integer, dimension(:), allocatable :: val class(process_t), intent(in) :: process end function process_get_nlo_type_component_all <>= pure module function process_get_nlo_type_component_all (process) result (val) integer, dimension(:), allocatable :: val class(process_t), intent(in) :: process allocate (val (size (process%component))) val = process%component%get_nlo_type () end function process_get_nlo_type_component_all @ %def process_get_nlo_type_component_all @ <>= procedure :: is_nlo_calculation => process_is_nlo_calculation <>= module function process_is_nlo_calculation (process) result (nlo) logical :: nlo class(process_t), intent(in) :: process end function process_is_nlo_calculation <>= module function process_is_nlo_calculation (process) result (nlo) logical :: nlo class(process_t), intent(in) :: process select type (pcm => process%pcm) type is (pcm_nlo_t) nlo = .true. class default nlo = .false. end select end function process_is_nlo_calculation @ %def process_is_nlo_calculation @ <>= procedure :: get_negative_sf => process_get_negative_sf <>= module function process_get_negative_sf (process) result (neg_sf) logical :: neg_sf class(process_t), intent(in) :: process end function process_get_negative_sf <>= module function process_get_negative_sf (process) result (neg_sf) logical :: neg_sf class(process_t), intent(in) :: process neg_sf = process%config%process_def%get_negative_sf () end function process_get_negative_sf @ %def process_get_negative_sf @ <>= procedure :: is_combined_nlo_integration & => process_is_combined_nlo_integration <>= module function process_is_combined_nlo_integration & (process) result (combined) logical :: combined class(process_t), intent(in) :: process end function process_is_combined_nlo_integration <>= module function process_is_combined_nlo_integration & (process) result (combined) logical :: combined class(process_t), intent(in) :: process select type (pcm => process%pcm) type is (pcm_nlo_t) combined = pcm%settings%combined_integration class default combined = .false. end select end function process_is_combined_nlo_integration @ %def process_is_combined_nlo_integration @ <>= procedure :: component_is_real_finite => process_component_is_real_finite <>= pure module function process_component_is_real_finite & (process, i_component) result (val) logical :: val class(process_t), intent(in) :: process integer, intent(in) :: i_component end function process_component_is_real_finite <>= pure module function process_component_is_real_finite & (process, i_component) result (val) logical :: val class(process_t), intent(in) :: process integer, intent(in) :: i_component val = process%component(i_component)%component_type == COMP_REAL_FIN end function process_component_is_real_finite @ %def process_component_is_real_finite @ Return nlo data of a process component <>= procedure :: get_component_nlo_type => process_get_component_nlo_type <>= elemental module function process_get_component_nlo_type & (process, i_component) result (nlo_type) integer :: nlo_type class(process_t), intent(in) :: process integer, intent(in) :: i_component end function process_get_component_nlo_type <>= elemental module function process_get_component_nlo_type & (process, i_component) result (nlo_type) integer :: nlo_type class(process_t), intent(in) :: process integer, intent(in) :: i_component nlo_type = process%component(i_component)%config%get_nlo_type () end function process_get_component_nlo_type @ %def process_get_component_nlo_type @ Return a pointer to the core that belongs to a component. <>= procedure :: get_component_core_ptr => process_get_component_core_ptr <>= module function process_get_component_core_ptr & (process, i_component) result (core) class(process_t), intent(in), target :: process integer, intent(in) :: i_component class(prc_core_t), pointer :: core end function process_get_component_core_ptr <>= module function process_get_component_core_ptr & (process, i_component) result (core) class(process_t), intent(in), target :: process integer, intent(in) :: i_component class(prc_core_t), pointer :: core integer :: i_core i_core = process%pcm%get_i_core(i_component) core => process%core_entry(i_core)%core end function process_get_component_core_ptr @ %def process_get_component_core_ptr @ <>= procedure :: get_component_associated_born & => process_get_component_associated_born <>= module function process_get_component_associated_born & (process, i_component) result (i_born) class(process_t), intent(in) :: process integer, intent(in) :: i_component integer :: i_born end function process_get_component_associated_born <>= module function process_get_component_associated_born & (process, i_component) result (i_born) class(process_t), intent(in) :: process integer, intent(in) :: i_component integer :: i_born i_born = process%component(i_component)%config%get_associated_born () end function process_get_component_associated_born @ %def process_get_component_associated_born @ <>= procedure :: get_first_real_component => process_get_first_real_component <>= module function process_get_first_real_component (process) result (i_real) integer :: i_real class(process_t), intent(in) :: process end function process_get_first_real_component <>= module function process_get_first_real_component (process) result (i_real) integer :: i_real class(process_t), intent(in) :: process i_real = process%component(1)%config%get_associated_real () end function process_get_first_real_component @ %def process_get_first_real_component @ <>= procedure :: get_first_real_term => process_get_first_real_term <>= module function process_get_first_real_term (process) result (i_real) integer :: i_real class(process_t), intent(in) :: process integer :: i_component, i_term end function process_get_first_real_term <>= module function process_get_first_real_term (process) result (i_real) integer :: i_real class(process_t), intent(in) :: process integer :: i_component, i_term i_component = process%component(1)%config%get_associated_real () i_real = 0 do i_term = 1, size (process%term) if (process%term(i_term)%i_component == i_component) then i_real = i_term exit end if end do if (i_real == 0) call msg_fatal ("Did not find associated real term!") end function process_get_first_real_term @ %def process_get_first_real_term @ <>= procedure :: get_associated_real_fin => process_get_associated_real_fin <>= elemental module function process_get_associated_real_fin & (process, i_component) result (i_real) integer :: i_real class(process_t), intent(in) :: process integer, intent(in) :: i_component end function process_get_associated_real_fin <>= elemental module function process_get_associated_real_fin & (process, i_component) result (i_real) integer :: i_real class(process_t), intent(in) :: process integer, intent(in) :: i_component i_real = process%component(i_component)%config%get_associated_real_fin () end function process_get_associated_real_fin @ %def process_get_associated_real_fin @ <>= procedure :: select_i_term => process_select_i_term <>= pure module function process_select_i_term (process, i_mci) result (i_term) integer :: i_term class(process_t), intent(in) :: process integer, intent(in) :: i_mci end function process_select_i_term <>= pure module function process_select_i_term (process, i_mci) result (i_term) integer :: i_term class(process_t), intent(in) :: process integer, intent(in) :: i_mci integer :: i_component, i_sub i_component = process%mci_entry(i_mci)%i_component(1) i_term = process%component(i_component)%i_term(1) i_sub = process%term(i_term)%i_sub if (i_sub > 0) & i_term = process%term(i_sub)%i_term_global end function process_select_i_term @ %def process_select_i_term @ Would be better to do this at the level of the writer of the core but one has to bring NLO information there. <>= procedure :: prepare_any_external_code & => process_prepare_any_external_code <>= module subroutine process_prepare_any_external_code (process) class(process_t), intent(inout), target :: process end subroutine process_prepare_any_external_code <>= module subroutine process_prepare_any_external_code (process) class(process_t), intent(inout), target :: process integer :: i if (debug_on) call msg_debug2 (D_PROCESS_INTEGRATION, & "process_prepare_external_code") associate (pcm => process%pcm) do i = 1, pcm%n_cores call pcm%prepare_any_external_code ( & process%core_entry(i), i, & process%get_library_name (), & process%config%model, & process%env%get_var_list_ptr ()) end do end associate end subroutine process_prepare_any_external_code @ %def process_prepare_any_external_code @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Process config} <<[[process_config.f90]]>>= <> module process_config <> <> use os_interface use sf_base use sf_mappings use mappings, only: mapping_defaults_t use phs_forests, only: phs_parameters_t use sm_qcd use integration_results use flavors use interactions use model_data use models use process_libraries use process_constants use prc_core use beams use mci_base use beam_structures use dispatch_beams, only: dispatch_qcd use phs_base use expr_base use variables <> <> <> <> interface <> end interface contains <> end module process_config @ %def process_config @ <<[[process_config_sub.f90]]>>= <> submodule (process_config) process_config_s use format_utils, only: write_separator use io_units use diagnostics use md5 use physics_defs use helicities use colors use quantum_numbers use state_matrices use prc_external use prc_openloops, only: prc_openloops_t use prc_threshold, only: prc_threshold_t use blha_olp_interfaces, only: prc_blha_t implicit none contains <> end submodule process_config_s @ %def process_config_s @ Identifiers for the NLO setup. <>= integer, parameter, public :: COMP_DEFAULT = 0 integer, parameter, public :: COMP_REAL_FIN = 1 integer, parameter, public :: COMP_MASTER = 2 integer, parameter, public :: COMP_VIRT = 3 integer, parameter, public :: COMP_REAL = 4 integer, parameter, public :: COMP_REAL_SING = 5 integer, parameter, public :: COMP_MISMATCH = 6 integer, parameter, public :: COMP_PDF = 7 integer, parameter, public :: COMP_SUB = 8 integer, parameter, public :: COMP_RESUM = 9 @ \subsection{Output selection flags} We declare a number of identifiers for write methods, so they only displays selected parts. The identifiers can be supplied to the [[vlist]] array argument of the standard F2008 derived-type writer call. <>= integer, parameter, public :: F_PACIFY = 1 integer, parameter, public :: F_SHOW_VAR_LIST = 11 integer, parameter, public :: F_SHOW_EXPRESSIONS = 12 integer, parameter, public :: F_SHOW_LIB = 13 integer, parameter, public :: F_SHOW_MODEL = 14 integer, parameter, public :: F_SHOW_QCD = 15 integer, parameter, public :: F_SHOW_OS_DATA = 16 integer, parameter, public :: F_SHOW_RNG = 17 integer, parameter, public :: F_SHOW_BEAMS = 18 @ %def SHOW_VAR_LIST @ %def SHOW_EXPRESSIONS @ This is a simple function that returns true if a flag value is present in [[v_list]], but not its negative. If neither is present, it returns [[default]]. <>= public :: flagged <>= module function flagged (v_list, id, def) result (flag) logical :: flag integer, dimension(:), intent(in) :: v_list integer, intent(in) :: id logical, intent(in), optional :: def end function flagged <>= module function flagged (v_list, id, def) result (flag) logical :: flag integer, dimension(:), intent(in) :: v_list integer, intent(in) :: id logical, intent(in), optional :: def logical :: default_result default_result = .false.; if (present (def)) default_result = def if (default_result) then flag = all (v_list /= -id) else flag = all (v_list /= -id) .and. any (v_list == id) end if end function flagged @ %def flagged @ Related: if flag is set (unset), append [[value]] (its negative) to the [[v_list]], respectively. [[v_list]] must be allocated. <>= public :: set_flag <>= module subroutine set_flag (v_list, value, flag) integer, dimension(:), intent(inout), allocatable :: v_list integer, intent(in) :: value logical, intent(in), optional :: flag end subroutine set_flag <>= module subroutine set_flag (v_list, value, flag) integer, dimension(:), intent(inout), allocatable :: v_list integer, intent(in) :: value logical, intent(in), optional :: flag if (present (flag)) then if (flag) then v_list = [v_list, value] else v_list = [v_list, -value] end if end if end subroutine set_flag @ %def set_flag @ \subsection{Generic configuration data} This information concerns physical and technical properties of the process. It is fixed upon initialization, using data from the process specification and the variable list. The number [[n_in]] is the number of incoming beam particles, simultaneously the number of incoming partons, 1 for a decay and 2 for a scattering process. (The number of outgoing partons may depend on the process component.) The number [[n_components]] is the number of components that constitute the current process. The number [[n_terms]] is the number of distinct contributions to the scattering matrix that constitute the current process. Each component may generate several terms. The number [[n_mci]] is the number of independent MC integration configurations that this process uses. Distinct process components that share a MCI configuration may be combined pointwise. (Nevertheless, a given MC variable set may correspond to several ``nearby'' kinematical configurations.) This is also the number of distinct sampling-function results that this process can generate. Process components that use distinct variable sets are added only once after an integration pass has completed. The [[model]] pointer identifies the physics model and its parameters. This is a pointer to an external object. Various [[parse_node_t]] objects are taken from the SINDARIN input. They encode expressions for evaluating cuts and scales. The workspaces for evaluating those expressions are set up in the [[effective_state]] subobjects. Note that these are really pointers, so the actual nodes are not stored inside the process object. The [[md5sum]] is taken and used to verify the process configuration when re-reading data from file. <>= public :: process_config_data_t <>= type :: process_config_data_t class(process_def_t), pointer :: process_def => null () integer :: n_in = 0 integer :: n_components = 0 integer :: n_terms = 0 integer :: n_mci = 0 type(string_t) :: model_name class(model_data_t), pointer :: model => null () type(qcd_t) :: qcd class(expr_factory_t), allocatable :: ef_cuts class(expr_factory_t), allocatable :: ef_scale class(expr_factory_t), allocatable :: ef_fac_scale class(expr_factory_t), allocatable :: ef_ren_scale class(expr_factory_t), allocatable :: ef_weight character(32) :: md5sum = "" contains <> end type process_config_data_t @ %def process_config_data_t @ Here, we may compress the expressions for cuts etc. <>= procedure :: write => process_config_data_write <>= module subroutine process_config_data_write & (config, u, counters, model, expressions) class(process_config_data_t), intent(in) :: config integer, intent(in) :: u logical, intent(in) :: counters logical, intent(in) :: model logical, intent(in) :: expressions end subroutine process_config_data_write <>= module subroutine process_config_data_write & (config, u, counters, model, expressions) class(process_config_data_t), intent(in) :: config integer, intent(in) :: u logical, intent(in) :: counters logical, intent(in) :: model logical, intent(in) :: expressions write (u, "(1x,A)") "Configuration data:" if (counters) then write (u, "(3x,A,I0)") "Number of incoming particles = ", & config%n_in write (u, "(3x,A,I0)") "Number of process components = ", & config%n_components write (u, "(3x,A,I0)") "Number of process terms = ", & config%n_terms write (u, "(3x,A,I0)") "Number of MCI configurations = ", & config%n_mci end if if (associated (config%model)) then write (u, "(3x,A,A)") "Model = ", char (config%model_name) if (model) then call write_separator (u) call config%model%write (u) call write_separator (u) end if else write (u, "(3x,A,A,A)") "Model = ", char (config%model_name), & " [not associated]" end if call config%qcd%write (u, show_md5sum = .false.) call write_separator (u) if (expressions) then if (allocated (config%ef_cuts)) then call write_separator (u) write (u, "(3x,A)") "Cut expression:" call config%ef_cuts%write (u) end if if (allocated (config%ef_scale)) then call write_separator (u) write (u, "(3x,A)") "Scale expression:" call config%ef_scale%write (u) end if if (allocated (config%ef_fac_scale)) then call write_separator (u) write (u, "(3x,A)") "Factorization scale expression:" call config%ef_fac_scale%write (u) end if if (allocated (config%ef_ren_scale)) then call write_separator (u) write (u, "(3x,A)") "Renormalization scale expression:" call config%ef_ren_scale%write (u) end if if (allocated (config%ef_weight)) then call write_separator (u) write (u, "(3x,A)") "Weight expression:" call config%ef_weight%write (u) end if else call write_separator (u) write (u, "(3x,A)") "Expressions (cut, scales, weight): [not shown]" end if if (config%md5sum /= "") then call write_separator (u) write (u, "(3x,A,A,A)") "MD5 sum (config) = '", config%md5sum, "'" end if end subroutine process_config_data_write @ %def process_config_data_write @ Initialize. We use information from the process metadata and from the process library, given the process ID. We also store the currently active OS data set. The model pointer references the model data within the [[env]] record. That should be an instance of the global model. We initialize the QCD object, unless the environment information is unavailable (unit tests). The RNG factory object is imported by moving the allocation. Gfortran 7/8/9 bug: has to remain in the main module: <>= procedure :: init => process_config_data_init <>= subroutine process_config_data_init (config, meta, env) class(process_config_data_t), intent(out) :: config type(process_metadata_t), intent(in) :: meta type(process_environment_t), intent(in) :: env config%process_def => env%lib%get_process_def_ptr (meta%id) config%n_in = config%process_def%get_n_in () config%n_components = size (meta%component_id) config%model => env%get_model_ptr () config%model_name = config%model%get_name () if (env%got_var_list ()) then call dispatch_qcd & (config%qcd, env%get_var_list_ptr (), env%get_os_data ()) end if end subroutine process_config_data_init @ %def process_config_data_init @ Current implementation: nothing to finalize. <>= procedure :: final => process_config_data_final <>= module subroutine process_config_data_final (config) class(process_config_data_t), intent(inout) :: config end subroutine process_config_data_final <>= module subroutine process_config_data_final (config) class(process_config_data_t), intent(inout) :: config end subroutine process_config_data_final @ %def process_config_data_final @ Return a copy of the QCD data block. <>= procedure :: get_qcd => process_config_data_get_qcd <>= module function process_config_data_get_qcd (config) result (qcd) class(process_config_data_t), intent(in) :: config type(qcd_t) :: qcd end function process_config_data_get_qcd <>= module function process_config_data_get_qcd (config) result (qcd) class(process_config_data_t), intent(in) :: config type(qcd_t) :: qcd qcd = config%qcd end function process_config_data_get_qcd @ %def process_config_data_get_qcd @ Compute the MD5 sum of the configuration data. This encodes, in particular, the model and the expressions for cut, scales, weight, etc. It should not contain the IDs and number of components, etc., since the MD5 sum should be useful for integrating individual components. This is done only once. If the MD5 sum is nonempty, the calculation is skipped. <>= procedure :: compute_md5sum => process_config_data_compute_md5sum <>= module subroutine process_config_data_compute_md5sum (config) class(process_config_data_t), intent(inout) :: config end subroutine process_config_data_compute_md5sum <>= module subroutine process_config_data_compute_md5sum (config) class(process_config_data_t), intent(inout) :: config integer :: u if (config%md5sum == "") then u = free_unit () open (u, status = "scratch", action = "readwrite") call config%write (u, counters = .false., & model = .true., expressions = .true.) rewind (u) config%md5sum = md5sum (u) close (u) end if end subroutine process_config_data_compute_md5sum @ %def process_config_data_compute_md5sum @ <>= procedure :: get_md5sum => process_config_data_get_md5sum <>= pure module function process_config_data_get_md5sum (config) result (md5) character(32) :: md5 class(process_config_data_t), intent(in) :: config end function process_config_data_get_md5sum <>= pure module function process_config_data_get_md5sum (config) result (md5) character(32) :: md5 class(process_config_data_t), intent(in) :: config md5 = config%md5sum end function process_config_data_get_md5sum @ %def process_config_data_get_md5sum @ \subsection{Environment} This record stores a snapshot of the process environment at the point where the process object is created. Model and variable list are implemented as pointer, so they always have the [[target]] attribute. For unit-testing purposes, setting the var list is optional. If not set, the pointer is null. <>= public :: process_environment_t <>= type :: process_environment_t private type(model_t), pointer :: model => null () type(var_list_t), pointer :: var_list => null () logical :: var_list_is_set = .false. type(process_library_t), pointer :: lib => null () type(beam_structure_t) :: beam_structure type(os_data_t) :: os_data contains <> end type process_environment_t @ %def process_environment_t @ Model and local var list are snapshots and need a finalizer. <>= procedure :: final => process_environment_final <>= module subroutine process_environment_final (env) class(process_environment_t), intent(inout) :: env end subroutine process_environment_final <>= module subroutine process_environment_final (env) class(process_environment_t), intent(inout) :: env if (associated (env%model)) then call env%model%final () deallocate (env%model) end if if (associated (env%var_list)) then call env%var_list%final (follow_link=.true.) deallocate (env%var_list) end if end subroutine process_environment_final @ %def process_environment_final @ Output, DTIO compatible. <>= procedure :: write => process_environment_write procedure :: write_formatted => process_environment_write_formatted ! generic :: write (formatted) => write_formatted <>= module subroutine process_environment_write (env, unit, & show_var_list, show_model, show_lib, show_beams, show_os_data) class(process_environment_t), intent(in) :: env integer, intent(in), optional :: unit logical, intent(in), optional :: show_var_list logical, intent(in), optional :: show_model logical, intent(in), optional :: show_lib logical, intent(in), optional :: show_beams logical, intent(in), optional :: show_os_data end subroutine process_environment_write <>= module subroutine process_environment_write (env, unit, & show_var_list, show_model, show_lib, show_beams, show_os_data) class(process_environment_t), intent(in) :: env integer, intent(in), optional :: unit logical, intent(in), optional :: show_var_list logical, intent(in), optional :: show_model logical, intent(in), optional :: show_lib logical, intent(in), optional :: show_beams logical, intent(in), optional :: show_os_data integer :: u, iostat integer, dimension(:), allocatable :: v_list character(0) :: iomsg u = given_output_unit (unit) allocate (v_list (0)) call set_flag (v_list, F_SHOW_VAR_LIST, show_var_list) call set_flag (v_list, F_SHOW_MODEL, show_model) call set_flag (v_list, F_SHOW_LIB, show_lib) call set_flag (v_list, F_SHOW_BEAMS, show_beams) call set_flag (v_list, F_SHOW_OS_DATA, show_os_data) call env%write_formatted (u, "LISTDIRECTED", v_list, iostat, iomsg) end subroutine process_environment_write @ %def process_environment_write @ DTIO standard write. <>= module subroutine process_environment_write_formatted & (dtv, unit, iotype, v_list, iostat, iomsg) class(process_environment_t), intent(in) :: dtv integer, intent(in) :: unit character(*), intent(in) :: iotype integer, dimension(:), intent(in) :: v_list integer, intent(out) :: iostat character(*), intent(inout) :: iomsg end subroutine process_environment_write_formatted <>= module subroutine process_environment_write_formatted & (dtv, unit, iotype, v_list, iostat, iomsg) class(process_environment_t), intent(in) :: dtv integer, intent(in) :: unit character(*), intent(in) :: iotype integer, dimension(:), intent(in) :: v_list integer, intent(out) :: iostat character(*), intent(inout) :: iomsg associate (env => dtv) if (flagged (v_list, F_SHOW_VAR_LIST, .true.)) then write (unit, "(1x,A)") "Variable list:" if (associated (env%var_list)) then call write_separator (unit) call env%var_list%write (unit) else write (unit, "(3x,A)") "[not allocated]" end if call write_separator (unit) end if if (flagged (v_list, F_SHOW_MODEL, .true.)) then write (unit, "(1x,A)") "Model:" if (associated (env%model)) then call write_separator (unit) call env%model%write (unit) else write (unit, "(3x,A)") "[not allocated]" end if call write_separator (unit) end if if (flagged (v_list, F_SHOW_LIB, .true.)) then write (unit, "(1x,A)") "Process library:" if (associated (env%lib)) then call write_separator (unit) call env%lib%write (unit) else write (unit, "(3x,A)") "[not allocated]" end if end if if (flagged (v_list, F_SHOW_BEAMS, .true.)) then call write_separator (unit) call env%beam_structure%write (unit) end if if (flagged (v_list, F_SHOW_OS_DATA, .true.)) then write (unit, "(1x,A)") "Operating-system data:" call write_separator (unit) call env%os_data%write (unit) end if end associate iostat = 0 end subroutine process_environment_write_formatted @ %def process_environment_write_formatted @ Initialize: Make a snapshot of the provided model. Make a link to the current process library. Also make a snapshot of the variable list, if provided. If none is provided, there is an empty variable list nevertheless, so a pointer lookup does not return null. If no beam structure is provided, the beam-structure member is empty and will yield a number of zero beams when queried. <>= procedure :: init => process_environment_init <>= module subroutine process_environment_init & (env, model, lib, os_data, var_list, beam_structure) class(process_environment_t), intent(out) :: env type(model_t), intent(in), target :: model type(process_library_t), intent(in), target :: lib type(os_data_t), intent(in) :: os_data type(var_list_t), intent(in), target, optional :: var_list type(beam_structure_t), intent(in), optional :: beam_structure end subroutine process_environment_init <>= module subroutine process_environment_init & (env, model, lib, os_data, var_list, beam_structure) class(process_environment_t), intent(out) :: env type(model_t), intent(in), target :: model type(process_library_t), intent(in), target :: lib type(os_data_t), intent(in) :: os_data type(var_list_t), intent(in), target, optional :: var_list type(beam_structure_t), intent(in), optional :: beam_structure allocate (env%model) call env%model%init_instance (model) env%lib => lib env%os_data = os_data allocate (env%var_list) if (present (var_list)) then call env%var_list%init_snapshot (var_list, follow_link=.true.) env%var_list_is_set = .true. end if if (present (beam_structure)) then env%beam_structure = beam_structure end if end subroutine process_environment_init @ %def process_environment_init @ Indicate whether a variable list has been provided upon initialization. <>= procedure :: got_var_list => process_environment_got_var_list <>= module function process_environment_got_var_list (env) result (flag) class(process_environment_t), intent(in) :: env logical :: flag end function process_environment_got_var_list <>= module function process_environment_got_var_list (env) result (flag) class(process_environment_t), intent(in) :: env logical :: flag flag = env%var_list_is_set end function process_environment_got_var_list @ %def process_environment_got_var_list @ Return a pointer to the variable list. <>= procedure :: get_var_list_ptr => process_environment_get_var_list_ptr <>= module function process_environment_get_var_list_ptr (env) result (var_list) class(process_environment_t), intent(in) :: env type(var_list_t), pointer :: var_list end function process_environment_get_var_list_ptr <>= module function process_environment_get_var_list_ptr (env) result (var_list) class(process_environment_t), intent(in) :: env type(var_list_t), pointer :: var_list var_list => env%var_list end function process_environment_get_var_list_ptr @ %def process_environment_get_var_list_ptr @ Return a pointer to the model, if it exists. <>= procedure :: get_model_ptr => process_environment_get_model_ptr <>= module function process_environment_get_model_ptr (env) result (model) class(process_environment_t), intent(in) :: env type(model_t), pointer :: model end function process_environment_get_model_ptr <>= module function process_environment_get_model_ptr (env) result (model) class(process_environment_t), intent(in) :: env type(model_t), pointer :: model model => env%model end function process_environment_get_model_ptr @ %def process_environment_get_model_ptr @ Return the process library pointer. <>= procedure :: get_lib_ptr => process_environment_get_lib_ptr <>= module function process_environment_get_lib_ptr (env) result (lib) class(process_environment_t), intent(inout) :: env type(process_library_t), pointer :: lib end function process_environment_get_lib_ptr <>= module function process_environment_get_lib_ptr (env) result (lib) class(process_environment_t), intent(inout) :: env type(process_library_t), pointer :: lib lib => env%lib end function process_environment_get_lib_ptr @ %def process_environment_get_lib_ptr @ Clear the process library pointer, in case the library is deleted. <>= procedure :: reset_lib_ptr => process_environment_reset_lib_ptr <>= module subroutine process_environment_reset_lib_ptr (env) class(process_environment_t), intent(inout) :: env end subroutine process_environment_reset_lib_ptr <>= module subroutine process_environment_reset_lib_ptr (env) class(process_environment_t), intent(inout) :: env env%lib => null () end subroutine process_environment_reset_lib_ptr @ %def process_environment_reset_lib_ptr @ Check whether the process library has changed, in case the library is recompiled, etc. <>= procedure :: check_lib_sanity => process_environment_check_lib_sanity <>= module subroutine process_environment_check_lib_sanity (env, meta) class(process_environment_t), intent(in) :: env type(process_metadata_t), intent(in) :: meta end subroutine process_environment_check_lib_sanity <>= module subroutine process_environment_check_lib_sanity (env, meta) class(process_environment_t), intent(in) :: env type(process_metadata_t), intent(in) :: meta if (associated (env%lib)) then if (env%lib%get_update_counter () /= meta%lib_update_counter) then call msg_fatal ("Process '" // char (meta%id) & // "': library has been recompiled after integration") end if end if end subroutine process_environment_check_lib_sanity @ %def process_environment_check_lib_sanity @ Fill the [[data]] block using the appropriate process-library access entry. <>= procedure :: fill_process_constants => & process_environment_fill_process_constants <>= module subroutine process_environment_fill_process_constants & (env, id, i_component, data) class(process_environment_t), intent(in) :: env type(string_t), intent(in) :: id integer, intent(in) :: i_component type(process_constants_t), intent(out) :: data end subroutine process_environment_fill_process_constants <>= module subroutine process_environment_fill_process_constants & (env, id, i_component, data) class(process_environment_t), intent(in) :: env type(string_t), intent(in) :: id integer, intent(in) :: i_component type(process_constants_t), intent(out) :: data call env%lib%fill_constants (id, i_component, data) end subroutine process_environment_fill_process_constants @ %def process_environment_fill_process_constants @ Return the entire beam structure. <>= procedure :: get_beam_structure => process_environment_get_beam_structure <>= module function process_environment_get_beam_structure & (env) result (beam_structure) class(process_environment_t), intent(in) :: env type(beam_structure_t) :: beam_structure end function process_environment_get_beam_structure <>= module function process_environment_get_beam_structure & (env) result (beam_structure) class(process_environment_t), intent(in) :: env type(beam_structure_t) :: beam_structure beam_structure = env%beam_structure end function process_environment_get_beam_structure @ %def process_environment_get_beam_structure @ Check the beam structure for PDFs. <>= procedure :: has_pdfs => process_environment_has_pdfs <>= module function process_environment_has_pdfs (env) result (flag) class(process_environment_t), intent(in) :: env logical :: flag end function process_environment_has_pdfs <>= module function process_environment_has_pdfs (env) result (flag) class(process_environment_t), intent(in) :: env logical :: flag flag = env%beam_structure%has_pdf () end function process_environment_has_pdfs @ %def process_environment_has_pdfs @ Check the beam structure for polarized beams. <>= procedure :: has_polarized_beams => process_environment_has_polarized_beams <>= module function process_environment_has_polarized_beams (env) result (flag) class(process_environment_t), intent(in) :: env logical :: flag end function process_environment_has_polarized_beams <>= module function process_environment_has_polarized_beams (env) result (flag) class(process_environment_t), intent(in) :: env logical :: flag flag = env%beam_structure%has_polarized_beams () end function process_environment_has_polarized_beams @ %def process_environment_has_polarized_beams @ Return a copy of the OS data block. <>= procedure :: get_os_data => process_environment_get_os_data <>= module function process_environment_get_os_data (env) result (os_data) class(process_environment_t), intent(in) :: env type(os_data_t) :: os_data end function process_environment_get_os_data <>= module function process_environment_get_os_data (env) result (os_data) class(process_environment_t), intent(in) :: env type(os_data_t) :: os_data os_data = env%os_data end function process_environment_get_os_data @ %def process_environment_get_os_data @ \subsection{Metadata} This information describes the process. It is fixed upon initialization. The [[id]] string is the name of the process object, as given by the user. The matrix element generator will use this string for naming Fortran procedures and types, so it should qualify as a Fortran name. The [[num_id]] is meaningful if nonzero. It is used for communication with external programs or file standards which do not support string IDs. The [[run_id]] string distinguishes among several runs for the same process. It identifies process instances with respect to adapted integration grids and similar run-specific data. The run ID is kept when copying processes for creating instances, however, so it does not distinguish event samples. The [[lib_name]] identifies the process library where the process definition and the process driver are located. The [[lib_index]] is the index of entry in the process library that corresponds to the current process. The [[component_id]] array identifies the individual process components. The [[component_description]] is an array of human-readable strings that characterize the process components, for instance [[a, b => c, d]]. The [[active]] mask array marks those components which are active. The others are skipped. <>= public :: process_metadata_t <>= type :: process_metadata_t integer :: type = PRC_UNKNOWN type(string_t) :: id integer :: num_id = 0 type(string_t) :: run_id type(string_t), allocatable :: lib_name integer :: lib_update_counter = 0 integer :: lib_index = 0 integer :: n_components = 0 type(string_t), dimension(:), allocatable :: component_id type(string_t), dimension(:), allocatable :: component_description logical, dimension(:), allocatable :: active contains <> end type process_metadata_t @ %def process_metadata_t @ Output: ID and run ID. We write the variable list only upon request. <>= procedure :: write => process_metadata_write <>= module subroutine process_metadata_write (meta, u, screen) class(process_metadata_t), intent(in) :: meta integer, intent(in) :: u logical, intent(in) :: screen end subroutine process_metadata_write <>= module subroutine process_metadata_write (meta, u, screen) class(process_metadata_t), intent(in) :: meta integer, intent(in) :: u logical, intent(in) :: screen integer :: i select case (meta%type) case (PRC_UNKNOWN) if (screen) then write (msg_buffer, "(A)") "Process [undefined]" else write (u, "(1x,A)") "Process [undefined]" end if return case (PRC_DECAY) if (screen) then write (msg_buffer, "(A,1x,A,A,A)") "Process [decay]:", & "'", char (meta%id), "'" else write (u, "(1x,A)", advance="no") "Process [decay]:" end if case (PRC_SCATTERING) if (screen) then write (msg_buffer, "(A,1x,A,A,A)") "Process [scattering]:", & "'", char (meta%id), "'" else write (u, "(1x,A)", advance="no") "Process [scattering]:" end if case default call msg_bug ("process_write: undefined process type") end select if (screen) then call msg_message () else write (u, "(1x,A,A,A)") "'", char (meta%id), "'" end if if (meta%num_id /= 0) then if (screen) then write (msg_buffer, "(2x,A,I0)") "ID (num) = ", meta%num_id call msg_message () else write (u, "(3x,A,I0)") "ID (num) = ", meta%num_id end if end if if (screen) then if (meta%run_id /= "") then write (msg_buffer, "(2x,A,A,A)") "Run ID = '", & char (meta%run_id), "'" call msg_message () end if else write (u, "(3x,A,A,A)") "Run ID = '", char (meta%run_id), "'" end if if (allocated (meta%lib_name)) then if (screen) then write (msg_buffer, "(2x,A,A,A)") "Library name = '", & char (meta%lib_name), "'" call msg_message () else write (u, "(3x,A,A,A)") "Library name = '", & char (meta%lib_name), "'" end if else if (screen) then write (msg_buffer, "(2x,A)") "Library name = [not associated]" call msg_message () else write (u, "(3x,A)") "Library name = [not associated]" end if end if if (screen) then write (msg_buffer, "(2x,A,I0)") "Process index = ", meta%lib_index call msg_message () else write (u, "(3x,A,I0)") "Process index = ", meta%lib_index end if if (allocated (meta%component_id)) then if (screen) then if (any (meta%active)) then write (msg_buffer, "(2x,A)") "Process components:" else write (msg_buffer, "(2x,A)") "Process components: [none]" end if call msg_message () else write (u, "(3x,A)") "Process components:" end if do i = 1, size (meta%component_id) if (.not. meta%active(i)) cycle if (screen) then write (msg_buffer, "(4x,I0,9A)") i, ": '", & char (meta%component_id (i)), "': ", & char (meta%component_description (i)) call msg_message () else write (u, "(5x,I0,9A)") i, ": '", & char (meta%component_id (i)), "': ", & char (meta%component_description (i)) end if end do end if if (screen) then write (msg_buffer, "(A)") repeat ("-", 72) call msg_message () else call write_separator (u) end if end subroutine process_metadata_write @ %def process_metadata_write @ Short output: list components. <>= procedure :: show => process_metadata_show <>= module subroutine process_metadata_show (meta, u, model_name) class(process_metadata_t), intent(in) :: meta integer, intent(in) :: u type(string_t), intent(in) :: model_name end subroutine process_metadata_show <>= module subroutine process_metadata_show (meta, u, model_name) class(process_metadata_t), intent(in) :: meta integer, intent(in) :: u type(string_t), intent(in) :: model_name integer :: i select case (meta%type) case (PRC_UNKNOWN) write (u, "(A)") "Process: [undefined]" return case default write (u, "(A)", advance="no") "Process:" end select write (u, "(1x,A)", advance="no") char (meta%id) select case (meta%num_id) case (0) case default write (u, "(1x,'(',I0,')')", advance="no") meta%num_id end select select case (char (model_name)) case ("") case default write (u, "(1x,'[',A,']')", advance="no") char (model_name) end select write (u, *) if (allocated (meta%component_id)) then do i = 1, size (meta%component_id) if (meta%active(i)) then write (u, "(2x,I0,':',1x,A)") i, & char (meta%component_description (i)) end if end do end if end subroutine process_metadata_show @ %def process_metadata_show @ Initialize. Find process ID and run ID. Also find the process ID in the process library and retrieve some metadata from there. <>= procedure :: init => process_metadata_init <>= module subroutine process_metadata_init (meta, id, lib, var_list) class(process_metadata_t), intent(out) :: meta type(string_t), intent(in) :: id type(process_library_t), intent(in), target :: lib type(var_list_t), intent(in) :: var_list end subroutine process_metadata_init <>= module subroutine process_metadata_init (meta, id, lib, var_list) class(process_metadata_t), intent(out) :: meta type(string_t), intent(in) :: id type(process_library_t), intent(in), target :: lib type(var_list_t), intent(in) :: var_list select case (lib%get_n_in (id)) case (1); meta%type = PRC_DECAY case (2); meta%type = PRC_SCATTERING case default call msg_bug ("Process '" // char (id) // "': impossible n_in") end select meta%id = id meta%run_id = var_list%get_sval (var_str ("$run_id")) allocate (meta%lib_name) meta%lib_name = lib%get_name () meta%lib_update_counter = lib%get_update_counter () if (lib%contains (id)) then meta%lib_index = lib%get_entry_index (id) meta%num_id = lib%get_num_id (id) call lib%get_component_list (id, meta%component_id) meta%n_components = size (meta%component_id) call lib%get_component_description_list & (id, meta%component_description) allocate (meta%active (meta%n_components), source = .true.) else call msg_fatal ("Process library does not contain process '" & // char (id) // "'") end if if (.not. lib%is_active ()) then call msg_bug ("Process init: inactive library not handled yet") end if end subroutine process_metadata_init @ %def process_metadata_init @ Mark a component as inactive. <>= procedure :: deactivate_component => process_metadata_deactivate_component <>= module subroutine process_metadata_deactivate_component (meta, i) class(process_metadata_t), intent(inout) :: meta integer, intent(in) :: i end subroutine process_metadata_deactivate_component <>= module subroutine process_metadata_deactivate_component (meta, i) class(process_metadata_t), intent(inout) :: meta integer, intent(in) :: i call msg_message ("Process component '" & // char (meta%component_id(i)) // "': matrix element vanishes") meta%active(i) = .false. end subroutine process_metadata_deactivate_component @ %def process_metadata_deactivate_component @ \subsection{Phase-space configuration} A process can have a number of independent phase-space configuration entries, depending on the process definition and evaluation algorithm. Each entry holds various configuration-parameter data and the actual [[phs_config_t]] record, which can vary in concrete type. <>= public :: process_phs_config_t <>= type :: process_phs_config_t type(phs_parameters_t) :: phs_par type(mapping_defaults_t) :: mapping_defs class(phs_config_t), allocatable :: phs_config contains <> end type process_phs_config_t @ %def process_phs_config_t @ Output, DTIO compatible. <>= procedure :: write => process_phs_config_write procedure :: write_formatted => process_phs_config_write_formatted ! generic :: write (formatted) => write_formatted <>= module subroutine process_phs_config_write (phs_config, unit) class(process_phs_config_t), intent(in) :: phs_config integer, intent(in), optional :: unit end subroutine process_phs_config_write <>= module subroutine process_phs_config_write (phs_config, unit) class(process_phs_config_t), intent(in) :: phs_config integer, intent(in), optional :: unit integer :: u, iostat integer, dimension(:), allocatable :: v_list character(0) :: iomsg u = given_output_unit (unit) allocate (v_list (0)) call phs_config%write_formatted (u, "LISTDIRECTED", v_list, iostat, iomsg) end subroutine process_phs_config_write @ %def process_phs_config_write @ DTIO standard write. <>= module subroutine process_phs_config_write_formatted & (dtv, unit, iotype, v_list, iostat, iomsg) class(process_phs_config_t), intent(in) :: dtv integer, intent(in) :: unit character(*), intent(in) :: iotype integer, dimension(:), intent(in) :: v_list integer, intent(out) :: iostat character(*), intent(inout) :: iomsg end subroutine process_phs_config_write_formatted <>= module subroutine process_phs_config_write_formatted & (dtv, unit, iotype, v_list, iostat, iomsg) class(process_phs_config_t), intent(in) :: dtv integer, intent(in) :: unit character(*), intent(in) :: iotype integer, dimension(:), intent(in) :: v_list integer, intent(out) :: iostat character(*), intent(inout) :: iomsg associate (phs_config => dtv) write (unit, "(1x, A)") "Phase-space configuration entry:" call phs_config%phs_par%write (unit) call phs_config%mapping_defs%write (unit) end associate iostat = 0 end subroutine process_phs_config_write_formatted @ %def process_phs_config_write_formatted @ \subsection{Beam configuration} The object [[data]] holds all details about the initial beam configuration. The allocatable array [[sf]] holds the structure-function configuration blocks. There are [[n_strfun]] entries in the structure-function chain (not counting the initial beam object). We maintain [[n_channel]] independent parameterizations of this chain. If this is greater than zero, we need a multi-channel sampling algorithm, where for each point one channel is selected to generate kinematics. The number of parameters that are required for generating a structure-function chain is [[n_sfpar]]. The flag [[azimuthal_dependence]] tells whether the process setup is symmetric about the beam axis in the c.m.\ system. This implies that there is no transversal beam polarization. The flag [[lab_is_cm]] is obvious. <>= public :: process_beam_config_t <>= type :: process_beam_config_t type(beam_data_t) :: data integer :: n_strfun = 0 integer :: n_channel = 1 integer :: n_sfpar = 0 type(sf_config_t), dimension(:), allocatable :: sf type(sf_channel_t), dimension(:), allocatable :: sf_channel logical :: azimuthal_dependence = .false. logical :: lab_is_cm = .true. character(32) :: md5sum = "" logical :: sf_trace = .false. type(string_t) :: sf_trace_file contains <> end type process_beam_config_t @ %def process_beam_config_t @ Here we write beam data only if they are actually used. The [[verbose]] flag is passed to the beam-data writer. <>= procedure :: write => process_beam_config_write <>= module subroutine process_beam_config_write (object, unit, verbose) class(process_beam_config_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: verbose end subroutine process_beam_config_write <>= module subroutine process_beam_config_write (object, unit, verbose) class(process_beam_config_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: verbose integer :: u, i, c u = given_output_unit (unit) call object%data%write (u, verbose = verbose) if (object%data%initialized) then write (u, "(3x,A,L1)") "Azimuthal dependence = ", & object%azimuthal_dependence write (u, "(3x,A,L1)") "Lab frame is c.m. frame = ", & object%lab_is_cm if (object%md5sum /= "") then write (u, "(3x,A,A,A)") "MD5 sum (beams/strf) = '", & object%md5sum, "'" end if if (allocated (object%sf)) then do i = 1, size (object%sf) call object%sf(i)%write (u) end do if (any_sf_channel_has_mapping (object%sf_channel)) then write (u, "(1x,A,L1)") "Structure-function mappings per channel:" do c = 1, object%n_channel write (u, "(3x,I0,':')", advance="no") c call object%sf_channel(c)%write (u) end do end if end if end if end subroutine process_beam_config_write @ %def process_beam_config_write @ The beam data have a finalizer. We assume that there is none for the structure-function data. <>= procedure :: final => process_beam_config_final <>= module subroutine process_beam_config_final (object) class(process_beam_config_t), intent(inout) :: object end subroutine process_beam_config_final <>= module subroutine process_beam_config_final (object) class(process_beam_config_t), intent(inout) :: object call object%data%final () end subroutine process_beam_config_final @ %def process_beam_config_final @ Initialize the beam setup with a given beam structure object. <>= procedure :: init_beam_structure => process_beam_config_init_beam_structure <>= module subroutine process_beam_config_init_beam_structure & (beam_config, beam_structure, sqrts, model, decay_rest_frame) class(process_beam_config_t), intent(out) :: beam_config type(beam_structure_t), intent(in) :: beam_structure logical, intent(in), optional :: decay_rest_frame real(default), intent(in) :: sqrts class(model_data_t), intent(in), target :: model end subroutine process_beam_config_init_beam_structure <>= module subroutine process_beam_config_init_beam_structure & (beam_config, beam_structure, sqrts, model, decay_rest_frame) class(process_beam_config_t), intent(out) :: beam_config type(beam_structure_t), intent(in) :: beam_structure logical, intent(in), optional :: decay_rest_frame real(default), intent(in) :: sqrts class(model_data_t), intent(in), target :: model call beam_config%data%init_structure (beam_structure, & sqrts, model, decay_rest_frame) beam_config%lab_is_cm = beam_config%data%lab_is_cm end subroutine process_beam_config_init_beam_structure @ %def process_beam_config_init_beam_structure @ Initialize the beam setup for a scattering process with specified flavor combination, other properties taken from the beam structure object (if any). <>= procedure :: init_scattering => process_beam_config_init_scattering <>= module subroutine process_beam_config_init_scattering & (beam_config, flv_in, sqrts, beam_structure) class(process_beam_config_t), intent(out) :: beam_config type(flavor_t), dimension(2), intent(in) :: flv_in real(default), intent(in) :: sqrts type(beam_structure_t), intent(in), optional :: beam_structure end subroutine process_beam_config_init_scattering <>= module subroutine process_beam_config_init_scattering & (beam_config, flv_in, sqrts, beam_structure) class(process_beam_config_t), intent(out) :: beam_config type(flavor_t), dimension(2), intent(in) :: flv_in real(default), intent(in) :: sqrts type(beam_structure_t), intent(in), optional :: beam_structure if (present (beam_structure)) then if (beam_structure%polarized ()) then call beam_config%data%init_sqrts (sqrts, flv_in, & beam_structure%get_smatrix (), beam_structure%get_pol_f ()) else call beam_config%data%init_sqrts (sqrts, flv_in) end if else call beam_config%data%init_sqrts (sqrts, flv_in) end if end subroutine process_beam_config_init_scattering @ %def process_beam_config_init_scattering @ Initialize the beam setup for a decay process with specified flavor, other properties taken from the beam structure object (if present). For a cascade decay, we set [[rest_frame]] to false, indicating a event-wise varying momentum. The beam data itself are initialized for the particle at rest. <>= procedure :: init_decay => process_beam_config_init_decay <>= module subroutine process_beam_config_init_decay & (beam_config, flv_in, rest_frame, beam_structure) class(process_beam_config_t), intent(out) :: beam_config type(flavor_t), dimension(1), intent(in) :: flv_in logical, intent(in), optional :: rest_frame type(beam_structure_t), intent(in), optional :: beam_structure end subroutine process_beam_config_init_decay <>= module subroutine process_beam_config_init_decay & (beam_config, flv_in, rest_frame, beam_structure) class(process_beam_config_t), intent(out) :: beam_config type(flavor_t), dimension(1), intent(in) :: flv_in logical, intent(in), optional :: rest_frame type(beam_structure_t), intent(in), optional :: beam_structure if (present (beam_structure)) then if (beam_structure%polarized ()) then call beam_config%data%init_decay (flv_in, & beam_structure%get_smatrix (), beam_structure%get_pol_f (), & rest_frame = rest_frame) else call beam_config%data%init_decay (flv_in, rest_frame = rest_frame) end if else call beam_config%data%init_decay (flv_in, & rest_frame = rest_frame) end if beam_config%lab_is_cm = beam_config%data%lab_is_cm end subroutine process_beam_config_init_decay @ %def process_beam_config_init_decay @ Print an informative message. <>= procedure :: startup_message => process_beam_config_startup_message <>= module subroutine process_beam_config_startup_message & (beam_config, unit, beam_structure) class(process_beam_config_t), intent(in) :: beam_config integer, intent(in), optional :: unit type(beam_structure_t), intent(in), optional :: beam_structure end subroutine process_beam_config_startup_message <>= module subroutine process_beam_config_startup_message & (beam_config, unit, beam_structure) class(process_beam_config_t), intent(in) :: beam_config integer, intent(in), optional :: unit type(beam_structure_t), intent(in), optional :: beam_structure integer :: u u = free_unit () open (u, status="scratch", action="readwrite") if (present (beam_structure)) then call beam_structure%write (u) end if call beam_config%data%write (u) rewind (u) do read (u, "(1x,A)", end=1) msg_buffer call msg_message () end do 1 continue close (u) end subroutine process_beam_config_startup_message @ %def process_beam_config_startup_message @ Allocate the structure-function array. <>= procedure :: init_sf_chain => process_beam_config_init_sf_chain <>= module subroutine process_beam_config_init_sf_chain & (beam_config, sf_config, sf_trace_file) class(process_beam_config_t), intent(inout) :: beam_config type(sf_config_t), dimension(:), intent(in) :: sf_config type(string_t), intent(in), optional :: sf_trace_file end subroutine process_beam_config_init_sf_chain <>= module subroutine process_beam_config_init_sf_chain & (beam_config, sf_config, sf_trace_file) class(process_beam_config_t), intent(inout) :: beam_config type(sf_config_t), dimension(:), intent(in) :: sf_config type(string_t), intent(in), optional :: sf_trace_file integer :: i beam_config%n_strfun = size (sf_config) allocate (beam_config%sf (beam_config%n_strfun)) do i = 1, beam_config%n_strfun associate (sf => sf_config(i)) call beam_config%sf(i)%init (sf%i, sf%data) if (.not. sf%data%is_generator ()) then beam_config%n_sfpar = beam_config%n_sfpar + sf%data%get_n_par () end if end associate end do if (present (sf_trace_file)) then beam_config%sf_trace = .true. beam_config%sf_trace_file = sf_trace_file end if end subroutine process_beam_config_init_sf_chain @ %def process_beam_config_init_sf_chain @ Allocate the structure-function mapping channel array, given the requested number of channels. <>= procedure :: allocate_sf_channels => process_beam_config_allocate_sf_channels <>= module subroutine process_beam_config_allocate_sf_channels & (beam_config, n_channel) class(process_beam_config_t), intent(inout) :: beam_config integer, intent(in) :: n_channel end subroutine process_beam_config_allocate_sf_channels <>= module subroutine process_beam_config_allocate_sf_channels & (beam_config, n_channel) class(process_beam_config_t), intent(inout) :: beam_config integer, intent(in) :: n_channel beam_config%n_channel = n_channel call allocate_sf_channels (beam_config%sf_channel, & n_channel = n_channel, & n_strfun = beam_config%n_strfun) end subroutine process_beam_config_allocate_sf_channels @ %def process_beam_config_allocate_sf_channels @ Set a structure-function mapping channel for an array of structure-function entries, for a single channel. (The default is no mapping.) <>= procedure :: set_sf_channel => process_beam_config_set_sf_channel <>= module subroutine process_beam_config_set_sf_channel & (beam_config, c, sf_channel) class(process_beam_config_t), intent(inout) :: beam_config integer, intent(in) :: c type(sf_channel_t), intent(in) :: sf_channel end subroutine process_beam_config_set_sf_channel <>= module subroutine process_beam_config_set_sf_channel & (beam_config, c, sf_channel) class(process_beam_config_t), intent(inout) :: beam_config integer, intent(in) :: c type(sf_channel_t), intent(in) :: sf_channel beam_config%sf_channel(c) = sf_channel end subroutine process_beam_config_set_sf_channel @ %def process_beam_config_set_sf_channel @ Print an informative startup message. <>= procedure :: sf_startup_message => process_beam_config_sf_startup_message <>= module subroutine process_beam_config_sf_startup_message & (beam_config, sf_string, unit) class(process_beam_config_t), intent(in) :: beam_config type(string_t), intent(in) :: sf_string integer, intent(in), optional :: unit end subroutine process_beam_config_sf_startup_message <>= module subroutine process_beam_config_sf_startup_message & (beam_config, sf_string, unit) class(process_beam_config_t), intent(in) :: beam_config type(string_t), intent(in) :: sf_string integer, intent(in), optional :: unit if (beam_config%n_strfun > 0) then call msg_message ("Beam structure: " // char (sf_string), unit = unit) write (msg_buffer, "(A,3(1x,I0,1x,A))") & "Beam structure:", & beam_config%n_channel, "channels,", & beam_config%n_sfpar, "dimensions" call msg_message (unit = unit) if (beam_config%sf_trace) then call msg_message ("Beam structure: tracing & &values in '" // char (beam_config%sf_trace_file) // "'") end if end if end subroutine process_beam_config_sf_startup_message @ %def process_beam_config_startup_message @ Return the PDF set currently in use, if any. This should be unique, so we scan the structure functions until we get a nonzero number. (This implies that if the PDF set is not unique (e.g., proton and photon structure used together), this does not work correctly.) <>= procedure :: get_pdf_set => process_beam_config_get_pdf_set <>= module function process_beam_config_get_pdf_set & (beam_config) result (pdf_set) class(process_beam_config_t), intent(in) :: beam_config integer :: pdf_set end function process_beam_config_get_pdf_set <>= module function process_beam_config_get_pdf_set (beam_config) result (pdf_set) class(process_beam_config_t), intent(in) :: beam_config integer :: pdf_set integer :: i pdf_set = 0 if (allocated (beam_config%sf)) then do i = 1, size (beam_config%sf) pdf_set = beam_config%sf(i)%get_pdf_set () if (pdf_set /= 0) return end do end if end function process_beam_config_get_pdf_set @ %def process_beam_config_get_pdf_set @ Return the beam file. <>= procedure :: get_beam_file => process_beam_config_get_beam_file <>= module function process_beam_config_get_beam_file & (beam_config) result (file) class(process_beam_config_t), intent(in) :: beam_config type(string_t) :: file end function process_beam_config_get_beam_file <>= module function process_beam_config_get_beam_file (beam_config) result (file) class(process_beam_config_t), intent(in) :: beam_config type(string_t) :: file integer :: i file = "" if (allocated (beam_config%sf)) then do i = 1, size (beam_config%sf) file = beam_config%sf(i)%get_beam_file () if (file /= "") return end do end if end function process_beam_config_get_beam_file @ %def process_beam_config_get_beam_file @ Compute the MD5 sum for the complete beam setup. We rely on the default output of [[write]] to contain all relevant data. This is done only once, when the MD5 sum is still empty. <>= procedure :: compute_md5sum => process_beam_config_compute_md5sum <>= module subroutine process_beam_config_compute_md5sum (beam_config) class(process_beam_config_t), intent(inout) :: beam_config end subroutine process_beam_config_compute_md5sum <>= module subroutine process_beam_config_compute_md5sum (beam_config) class(process_beam_config_t), intent(inout) :: beam_config integer :: u if (beam_config%md5sum == "") then u = free_unit () open (u, status = "scratch", action = "readwrite") call beam_config%write (u, verbose=.true.) rewind (u) beam_config%md5sum = md5sum (u) close (u) end if end subroutine process_beam_config_compute_md5sum @ %def process_beam_config_compute_md5sum @ <>= procedure :: get_md5sum => process_beam_config_get_md5sum <>= pure module function process_beam_config_get_md5sum & (beam_config) result (md5) character(32) :: md5 class(process_beam_config_t), intent(in) :: beam_config end function process_beam_config_get_md5sum <>= pure module function process_beam_config_get_md5sum (beam_config) result (md5) character(32) :: md5 class(process_beam_config_t), intent(in) :: beam_config md5 = beam_config%md5sum end function process_beam_config_get_md5sum @ %def process_beam_config_get_md5sum @ <>= procedure :: has_structure_function => & process_beam_config_has_structure_function <>= pure module function process_beam_config_has_structure_function & (beam_config) result (has_sf) logical :: has_sf class(process_beam_config_t), intent(in) :: beam_config end function process_beam_config_has_structure_function <>= pure module function process_beam_config_has_structure_function & (beam_config) result (has_sf) logical :: has_sf class(process_beam_config_t), intent(in) :: beam_config has_sf = beam_config%n_strfun > 0 end function process_beam_config_has_structure_function @ %def process_beam_config_has_structure_function @ \subsection{Process components} A process component is an individual contribution to a process (scattering or decay) which needs not be physical. The sum over all components should be physical. The [[index]] indentifies this component within its parent process. The actual process component is stored in the [[core]] subobject. We use a polymorphic subobject instead of an extension of [[process_component_t]], because the individual entries in the array of process components can have different types. In short, [[process_component_t]] is a wrapper for the actual process variants. If the [[active]] flag is false, we should skip this component. This happens if the associated process has vanishing matrix element. The index array [[i_term]] points to the individual terms generated by this component. The indices refer to the parent process. The index [[i_mci]] is the index of the MC integrator and parameter set which are associated to this process component. <>= public :: process_component_t <>= type :: process_component_t type(process_component_def_t), pointer :: config => null () integer :: index = 0 logical :: active = .false. integer, dimension(:), allocatable :: i_term integer :: i_mci = 0 class(phs_config_t), allocatable :: phs_config character(32) :: md5sum_phs = "" integer :: component_type = COMP_DEFAULT contains <> end type process_component_t @ %def process_component_t @ Finalizer. The MCI template may (potentially) need a finalizer. The process configuration finalizer may include closing an open scratch file. <>= procedure :: final => process_component_final <>= module subroutine process_component_final (object) class(process_component_t), intent(inout) :: object end subroutine process_component_final <>= module subroutine process_component_final (object) class(process_component_t), intent(inout) :: object if (allocated (object%phs_config)) then call object%phs_config%final () end if end subroutine process_component_final @ %def process_component_final @ The meaning of [[verbose]] depends on the process variant. <>= procedure :: write => process_component_write <>= module subroutine process_component_write (object, unit) class(process_component_t), intent(in) :: object integer, intent(in), optional :: unit end subroutine process_component_write <>= module subroutine process_component_write (object, unit) class(process_component_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) if (associated (object%config)) then write (u, "(1x,A,I0)") "Component #", object%index call object%config%write (u) if (object%md5sum_phs /= "") then write (u, "(3x,A,A,A)") "MD5 sum (phs) = '", & object%md5sum_phs, "'" end if else write (u, "(1x,A)") "Process component: [not allocated]" end if if (.not. object%active) then write (u, "(1x,A)") "[Inactive]" return end if write (u, "(1x,A)") "Referenced data:" if (allocated (object%i_term)) then write (u, "(3x,A,999(1x,I0))") "Terms =", & object%i_term else write (u, "(3x,A)") "Terms = [undefined]" end if if (object%i_mci /= 0) then write (u, "(3x,A,I0)") "MC dataset = ", object%i_mci else write (u, "(3x,A)") "MC dataset = [undefined]" end if if (allocated (object%phs_config)) then call object%phs_config%write (u) end if end subroutine process_component_write @ %def process_component_write @ Initialize the component. <>= procedure :: init => process_component_init <>= module subroutine process_component_init (component, & i_component, env, meta, config, & active, & phs_config_template) class(process_component_t), intent(out) :: component integer, intent(in) :: i_component type(process_environment_t), intent(in) :: env type(process_metadata_t), intent(in) :: meta type(process_config_data_t), intent(in) :: config logical, intent(in) :: active class(phs_config_t), intent(in), allocatable :: phs_config_template end subroutine process_component_init <>= module subroutine process_component_init (component, & i_component, env, meta, config, & active, & phs_config_template) class(process_component_t), intent(out) :: component integer, intent(in) :: i_component type(process_environment_t), intent(in) :: env type(process_metadata_t), intent(in) :: meta type(process_config_data_t), intent(in) :: config logical, intent(in) :: active class(phs_config_t), intent(in), allocatable :: phs_config_template type(process_constants_t) :: data component%index = i_component component%config => & config%process_def%get_component_def_ptr (i_component) component%active = active if (component%active) then allocate (component%phs_config, source = phs_config_template) call env%fill_process_constants (meta%id, i_component, data) call component%phs_config%init (data, config%model) end if end subroutine process_component_init @ %def process_component_init @ <>= procedure :: is_active => process_component_is_active <>= elemental module function process_component_is_active & (component) result (active) logical :: active class(process_component_t), intent(in) :: component end function process_component_is_active <>= elemental module function process_component_is_active & (component) result (active) logical :: active class(process_component_t), intent(in) :: component active = component%active end function process_component_is_active @ %def process_component_is_active @ Finalize the phase-space configuration. <>= procedure :: configure_phs => process_component_configure_phs <>= module subroutine process_component_configure_phs & (component, sqrts, beam_config, rebuild, & ignore_mismatch, subdir) class(process_component_t), intent(inout) :: component real(default), intent(in) :: sqrts type(process_beam_config_t), intent(in) :: beam_config logical, intent(in), optional :: rebuild logical, intent(in), optional :: ignore_mismatch type(string_t), intent(in), optional :: subdir end subroutine process_component_configure_phs <>= module subroutine process_component_configure_phs & (component, sqrts, beam_config, rebuild, & ignore_mismatch, subdir) class(process_component_t), intent(inout) :: component real(default), intent(in) :: sqrts type(process_beam_config_t), intent(in) :: beam_config logical, intent(in), optional :: rebuild logical, intent(in), optional :: ignore_mismatch type(string_t), intent(in), optional :: subdir logical :: no_strfun integer :: nlo_type no_strfun = beam_config%n_strfun == 0 nlo_type = component%config%get_nlo_type () call component%phs_config%configure (sqrts, & azimuthal_dependence = beam_config%azimuthal_dependence, & sqrts_fixed = no_strfun, & lab_is_cm = beam_config%lab_is_cm .and. no_strfun, & rebuild = rebuild, ignore_mismatch = ignore_mismatch, & nlo_type = nlo_type, & subdir = subdir) end subroutine process_component_configure_phs @ %def process_component_configure_phs @ The process component possesses two MD5 sums: the checksum of the component definition, which should be available when the component is initialized, and the phase-space MD5 sum, which is available after configuration. <>= procedure :: compute_md5sum => process_component_compute_md5sum <>= module subroutine process_component_compute_md5sum (component) class(process_component_t), intent(inout) :: component end subroutine process_component_compute_md5sum <>= module subroutine process_component_compute_md5sum (component) class(process_component_t), intent(inout) :: component component%md5sum_phs = component%phs_config%get_md5sum () end subroutine process_component_compute_md5sum @ %def process_component_compute_md5sum @ Match phase-space channels with structure-function channels, where applicable. This calls a method of the [[phs_config]] phase-space implementation. <>= procedure :: collect_channels => process_component_collect_channels <>= module subroutine process_component_collect_channels (component, coll) class(process_component_t), intent(inout) :: component type(phs_channel_collection_t), intent(inout) :: coll end subroutine process_component_collect_channels <>= module subroutine process_component_collect_channels (component, coll) class(process_component_t), intent(inout) :: component type(phs_channel_collection_t), intent(inout) :: coll call component%phs_config%collect_channels (coll) end subroutine process_component_collect_channels @ %def process_component_collect_channels @ <>= procedure :: get_config => process_component_get_config <>= module function process_component_get_config (component) & result (config) type(process_component_def_t) :: config class(process_component_t), intent(in) :: component end function process_component_get_config <>= module function process_component_get_config (component) & result (config) type(process_component_def_t) :: config class(process_component_t), intent(in) :: component config = component%config end function process_component_get_config @ %def process_component_get_config @ <>= procedure :: get_md5sum => process_component_get_md5sum <>= pure module function process_component_get_md5sum (component) result (md5) type(string_t) :: md5 class(process_component_t), intent(in) :: component end function process_component_get_md5sum <>= pure module function process_component_get_md5sum (component) result (md5) type(string_t) :: md5 class(process_component_t), intent(in) :: component md5 = component%config%get_md5sum () // component%md5sum_phs end function process_component_get_md5sum @ %def process_component_get_md5sum @ Return the number of phase-space parameters. <>= procedure :: get_n_phs_par => process_component_get_n_phs_par <>= module function process_component_get_n_phs_par (component) result (n_par) class(process_component_t), intent(in) :: component integer :: n_par end function process_component_get_n_phs_par <>= module function process_component_get_n_phs_par (component) result (n_par) class(process_component_t), intent(in) :: component integer :: n_par n_par = component%phs_config%get_n_par () end function process_component_get_n_phs_par @ %def process_component_get_n_phs_par @ <>= procedure :: get_phs_config => process_component_get_phs_config <>= module subroutine process_component_get_phs_config (component, phs_config) class(process_component_t), intent(in), target :: component class(phs_config_t), intent(out), pointer :: phs_config end subroutine process_component_get_phs_config <>= module subroutine process_component_get_phs_config (component, phs_config) class(process_component_t), intent(in), target :: component class(phs_config_t), intent(out), pointer :: phs_config phs_config => component%phs_config end subroutine process_component_get_phs_config @ %def process_component_get_phs_config @ <>= procedure :: get_nlo_type => process_component_get_nlo_type <>= elemental module function process_component_get_nlo_type & (component) result (nlo_type) integer :: nlo_type class(process_component_t), intent(in) :: component end function process_component_get_nlo_type <>= elemental module function process_component_get_nlo_type & (component) result (nlo_type) integer :: nlo_type class(process_component_t), intent(in) :: component nlo_type = component%config%get_nlo_type () end function process_component_get_nlo_type @ %def process_component_get_nlo_type @ <>= procedure :: needs_mci_entry => process_component_needs_mci_entry <>= module function process_component_needs_mci_entry & (component, combined_integration) result (value) logical :: value class(process_component_t), intent(in) :: component logical, intent(in), optional :: combined_integration end function process_component_needs_mci_entry <>= module function process_component_needs_mci_entry & (component, combined_integration) result (value) logical :: value class(process_component_t), intent(in) :: component logical, intent(in), optional :: combined_integration value = component%active if (present (combined_integration)) then if (combined_integration) & value = value .and. component%component_type <= COMP_MASTER end if end function process_component_needs_mci_entry @ %def process_component_needs_mci_entry @ <>= procedure :: can_be_integrated => process_component_can_be_integrated <>= elemental module function process_component_can_be_integrated & (component) result (active) logical :: active class(process_component_t), intent(in) :: component end function process_component_can_be_integrated <>= elemental module function process_component_can_be_integrated & (component) result (active) logical :: active class(process_component_t), intent(in) :: component active = component%config%can_be_integrated () end function process_component_can_be_integrated @ %def process_component_can_be_integrated @ \subsection{Process terms} For straightforward tree-level calculations, each process component corresponds to a unique elementary interaction. However, in the case of NLO calculations with subtraction terms, a process component may split into several separate contributions to the scattering, which are qualified by interactions with distinct kinematics and particle content. We represent their configuration as [[process_term_t]] objects, the actual instances will be introduced below as [[term_instance_t]]. In any case, the process term contains an elementary interaction with a definite quantum-number and momentum content. The index [[i_term_global]] identifies the term relative to the process. The index [[i_component]] identifies the process component which generates this term, relative to the parent process. The index [[i_term]] identifies the term relative to the process component (not the process). The [[data]] subobject holds all process constants. The number of allowed flavor/helicity/color combinations is stored as [[n_allowed]]. This is the total number of independent entries in the density matrix. For each combination, the index of the flavor, helicity, and color state is stored in the arrays [[flv]], [[hel]], and [[col]], respectively. The flag [[rearrange]] is true if we need to rearrange the particles of the hard interaction, to obtain the effective parton state. The interaction [[int]] holds the quantum state for the (resolved) hard interaction, the parent-child relations of the particles, and their momenta. The momenta are not filled yet; this is postponed to copies of [[int]] which go into the process instances. If recombination is in effect, we should allocate [[int_eff]] to describe the rearranged partonic state. This type is public only for use in a unit test. <>= public :: process_term_t <>= type :: process_term_t integer :: i_term_global = 0 integer :: i_component = 0 integer :: i_term = 0 integer :: i_sub = 0 integer :: i_core = 0 integer :: n_allowed = 0 type(process_constants_t) :: data real(default) :: alpha_s = 0 integer, dimension(:), allocatable :: flv, hel, col integer :: n_sub, n_sub_color, n_sub_spin type(interaction_t) :: int type(interaction_t), pointer :: int_eff => null () contains <> end type process_term_t @ %def process_term_t @ For the output, we skip the process constants and the tables of allowed quantum numbers. Those can also be read off from the interaction object. <>= procedure :: write => process_term_write <>= module subroutine process_term_write (term, unit) class(process_term_t), intent(in) :: term integer, intent(in), optional :: unit end subroutine process_term_write <>= module subroutine process_term_write (term, unit) class(process_term_t), intent(in) :: term integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(1x,A,I0)") "Term #", term%i_term_global write (u, "(3x,A,I0)") "Process component index = ", & term%i_component write (u, "(3x,A,I0)") "Term index w.r.t. component = ", & term%i_term call write_separator (u) write (u, "(1x,A)") "Hard interaction:" call write_separator (u) call term%int%basic_write (u) end subroutine process_term_write @ %def process_term_write @ Write an account of all quantum number states and their current status. <>= procedure :: write_state_summary => process_term_write_state_summary <>= module subroutine process_term_write_state_summary (term, core, unit) class(process_term_t), intent(in) :: term class(prc_core_t), intent(in) :: core integer, intent(in), optional :: unit end subroutine process_term_write_state_summary <>= module subroutine process_term_write_state_summary (term, core, unit) class(process_term_t), intent(in) :: term class(prc_core_t), intent(in) :: core integer, intent(in), optional :: unit integer :: u, i, f, h, c type(state_iterator_t) :: it character :: sgn u = given_output_unit (unit) write (u, "(1x,A,I0)") "Term #", term%i_term_global call it%init (term%int%get_state_matrix_ptr ()) do while (it%is_valid ()) i = it%get_me_index () f = term%flv(i) h = term%hel(i) if (allocated (term%col)) then c = term%col(i) else c = 1 end if if (core%is_allowed (term%i_term, f, h, c)) then sgn = "+" else sgn = " " end if write (u, "(1x,A1,1x,I0,2x)", advance="no") sgn, i call quantum_numbers_write (it%get_quantum_numbers (), u) write (u, *) call it%advance () end do end subroutine process_term_write_state_summary @ %def process_term_write_state_summary @ Finalizer: the [[int]] and potentially [[int_eff]] components have a finalizer that we must call. <>= procedure :: final => process_term_final <>= module subroutine process_term_final (term) class(process_term_t), intent(inout) :: term end subroutine process_term_final <>= module subroutine process_term_final (term) class(process_term_t), intent(inout) :: term call term%int%final () end subroutine process_term_final @ %def process_term_final @ Initialize the term. We copy the process constants from the [[core]] object and set up the [[int]] hard interaction accordingly. The [[alpha_s]] value is useful for writing external event records. This is the constant value which may be overridden by an event-specific running value. If the model does not contain the strong coupling, the value is zero. The [[rearrange]] part is commented out; this or something equivalent could become relevant for NLO algorithms. <>= procedure :: init => process_term_init <>= module subroutine process_term_init & (term, i_term_global, i_component, i_term, core, model, & nlo_type, use_beam_pol, subtraction_method, & has_pdfs, n_emitters) class(process_term_t), intent(inout), target :: term integer, intent(in) :: i_term_global integer, intent(in) :: i_component integer, intent(in) :: i_term class(prc_core_t), intent(inout) :: core class(model_data_t), intent(in), target :: model integer, intent(in), optional :: nlo_type logical, intent(in), optional :: use_beam_pol type(string_t), intent(in), optional :: subtraction_method logical, intent(in), optional :: has_pdfs integer, intent(in), optional :: n_emitters end subroutine process_term_init <>= module subroutine process_term_init & (term, i_term_global, i_component, i_term, core, model, & nlo_type, use_beam_pol, subtraction_method, & has_pdfs, n_emitters) class(process_term_t), intent(inout), target :: term integer, intent(in) :: i_term_global integer, intent(in) :: i_component integer, intent(in) :: i_term class(prc_core_t), intent(inout) :: core class(model_data_t), intent(in), target :: model integer, intent(in), optional :: nlo_type logical, intent(in), optional :: use_beam_pol type(string_t), intent(in), optional :: subtraction_method logical, intent(in), optional :: has_pdfs integer, intent(in), optional :: n_emitters class(modelpar_data_t), pointer :: alpha_s_ptr logical :: use_internal_color term%i_term_global = i_term_global term%i_component = i_component term%i_term = i_term call core%get_constants (term%data, i_term) alpha_s_ptr => model%get_par_data_ptr (var_str ("alphas")) if (associated (alpha_s_ptr)) then term%alpha_s = alpha_s_ptr%get_real () else term%alpha_s = -1 end if use_internal_color = .false. if (present (subtraction_method)) & use_internal_color = (char (subtraction_method) == 'omega') & .or. (char (subtraction_method) == 'threshold') call term%setup_interaction (core, model, nlo_type = nlo_type, & pol_beams = use_beam_pol, use_internal_color = use_internal_color, & has_pdfs = has_pdfs, n_emitters = n_emitters) end subroutine process_term_init @ %def process_term_init @ We fetch the process constants which determine the quantum numbers and use those to create the interaction. The interaction contains incoming and outgoing particles, no virtuals. The incoming particles are parents of the outgoing ones. Keeping previous \whizard\ conventions, we invert the color assignment (but not flavor or helicity) for the incoming particles. When the color-flow square matrix is evaluated, this inversion is done again, so in the color-flow sequence we get the color assignments of the matrix element. \textbf{Why are these four subtraction entries for structure-function aware interactions?} Taking the soft or collinear limit of the real-emission matrix element, the behavior of the parton energy fractions has to be taken into account. In the pure real case, $x_\oplus$ and $x_\ominus$ are given by \begin{equation*} x_\oplus = \frac{\bar{x}_\oplus}{\sqrt{1-\xi}} \sqrt{\frac{2 - \xi(1-y)}{2 - \xi(1+y)}}, \quad x_\ominus = \frac{\bar{x}_\ominus}{\sqrt{1-\xi}} \sqrt{\frac{2 - \xi(1+y)}{2 - \xi(1-y)}}. \end{equation*} In the soft limit, $\xi \to 0$, this yields $x_\oplus = \bar{x}_\oplus$ and $x_\ominus = \bar{x}_\ominus$. In the collinear limit, $y \to 1$, it is $x_\oplus = \bar{x}_\oplus / (1 - \xi)$ and $x_\ominus = \bar{x}_\ominus$. Likewise, in the anti-collinear limit $y \to -1$, the inverse relation holds. We therefore have to distinguish four cases with the PDF assignments $f(x_\oplus) \cdot f(x_\ominus)$, $f(\bar{x}_\oplus) \cdot f(\bar{x}_\ominus)$, $f\left(\bar{x}_\oplus / (1-\xi)\right) \cdot f(\bar{x}_\ominus)$ and $f(\bar{x}_\oplus) \cdot f\left(\bar{x}_\ominus / (1-\xi)\right)$. The [[n_emitters]] optional argument is provided by the caller if this term requires spin-correlated matrix elements, and thus involves additional subtractions. <>= procedure :: setup_interaction => process_term_setup_interaction <>= module subroutine process_term_setup_interaction (term, core, model, & nlo_type, pol_beams, has_pdfs, use_internal_color, n_emitters) class(process_term_t), intent(inout) :: term class(prc_core_t), intent(inout) :: core class(model_data_t), intent(in), target :: model logical, intent(in), optional :: pol_beams logical, intent(in), optional :: has_pdfs integer, intent(in), optional :: nlo_type logical, intent(in), optional :: use_internal_color integer, intent(in), optional :: n_emitters end subroutine process_term_setup_interaction <>= module subroutine process_term_setup_interaction (term, core, model, & nlo_type, pol_beams, has_pdfs, use_internal_color, n_emitters) class(process_term_t), intent(inout) :: term class(prc_core_t), intent(inout) :: core class(model_data_t), intent(in), target :: model logical, intent(in), optional :: pol_beams logical, intent(in), optional :: has_pdfs integer, intent(in), optional :: nlo_type logical, intent(in), optional :: use_internal_color integer, intent(in), optional :: n_emitters integer :: n, n_tot type(flavor_t), dimension(:), allocatable :: flv type(color_t), dimension(:), allocatable :: col type(helicity_t), dimension(:), allocatable :: hel type(quantum_numbers_t), dimension(:), allocatable :: qn logical :: is_pol, use_color integer :: nlo_t, n_sub is_pol = .false.; if (present (pol_beams)) is_pol = pol_beams nlo_t = BORN; if (present (nlo_type)) nlo_t = nlo_type n_tot = term%data%n_in + term%data%n_out call count_number_of_states () term%n_allowed = n call compute_n_sub (n_emitters, has_pdfs) call fill_quantum_numbers () call term%int%basic_init & (term%data%n_in, 0, term%data%n_out, set_relations = .true.) select type (core) class is (prc_blha_t) call setup_states_blha_olp () type is (prc_threshold_t) call setup_states_threshold () class is (prc_external_t) call setup_states_other_prc_external () class default call setup_states_omega () end select call term%int%freeze () contains subroutine count_number_of_states () integer :: f, h, c n = 0 select type (core) class is (prc_external_t) do f = 1, term%data%n_flv do h = 1, term%data%n_hel do c = 1, term%data%n_col n = n + 1 end do end do end do class default !!! Omega and all test cores do f = 1, term%data%n_flv do h = 1, term%data%n_hel do c = 1, term%data%n_col if (core%is_allowed (term%i_term, f, h, c)) n = n + 1 end do end do end do end select end subroutine count_number_of_states subroutine compute_n_sub (n_emitters, has_pdfs) integer, intent(in), optional :: n_emitters logical, intent(in), optional :: has_pdfs logical :: can_have_sub integer :: n_sub_color, n_sub_spin use_color = .false.; if (present (use_internal_color)) & use_color = use_internal_color can_have_sub = nlo_t == NLO_VIRTUAL .or. & (nlo_t == NLO_REAL .and. term%i_term_global == term%i_sub) .or. & nlo_t == NLO_MISMATCH .or. nlo_t == NLO_DGLAP n_sub_color = 0; n_sub_spin = 0 if (can_have_sub) then if (.not. use_color) n_sub_color = n_tot * (n_tot - 1) / 2 if (nlo_t == NLO_REAL) then if (present (n_emitters)) then n_sub_spin = 6 * n_emitters end if end if end if n_sub = n_sub_color + n_sub_spin !!! For the virtual subtraction we also need the finite virtual contribution !!! corresponding to the $\epsilon^0$-pole if (nlo_t == NLO_VIRTUAL) n_sub = n_sub + 1 if (present (has_pdfs)) then if (has_pdfs & .and. ((nlo_t == NLO_REAL .and. can_have_sub) & .or. nlo_t == NLO_DGLAP)) then !!! necessary dummy, needs refactoring, !!! c.f. [[term_instance_evaluate_interaction_external_tree]] n_sub = n_sub + n_beams_rescaled end if end if term%n_sub = n_sub term%n_sub_color = n_sub_color term%n_sub_spin = n_sub_spin end subroutine compute_n_sub subroutine fill_quantum_numbers () integer :: nn logical :: can_have_sub select type (core) class is (prc_external_t) can_have_sub = nlo_t == NLO_VIRTUAL .or. & (nlo_t == NLO_REAL .and. term%i_term_global == term%i_sub) .or. & nlo_t == NLO_MISMATCH .or. nlo_t == NLO_DGLAP if (can_have_sub) then nn = (n_sub + 1) * n else nn = n end if class default nn = n end select allocate (term%flv (nn), term%col (nn), term%hel (nn)) allocate (flv (n_tot), col (n_tot), hel (n_tot)) allocate (qn (n_tot)) end subroutine fill_quantum_numbers subroutine setup_states_blha_olp () integer :: s, f, c, h, i i = 0 associate (data => term%data) do s = 0, n_sub do f = 1, data%n_flv do h = 1, data%n_hel do c = 1, data%n_col i = i + 1 term%flv(i) = f term%hel(i) = h !!! Dummy-initialization of color term%col(i) = c call flv%init (data%flv_state (:,f), model) call color_init_from_array (col, & data%col_state(:,:,c), data%ghost_flag(:,c)) call col(1:data%n_in)%invert () if (is_pol) then select type (core) type is (prc_openloops_t) call hel%init (data%hel_state (:,h)) call qn%init (flv, hel, col, s) class default call msg_fatal ("Polarized beams only supported by OpenLoops") end select else call qn%init (flv, col, s) end if call qn%tag_hard_process () call term%int%add_state (qn) end do end do end do end do end associate end subroutine setup_states_blha_olp subroutine setup_states_threshold () integer :: s, f, c, h, i i = 0 n_sub = 0; if (nlo_t == NLO_VIRTUAL) n_sub = 1 associate (data => term%data) do s = 0, n_sub do f = 1, term%data%n_flv do h = 1, data%n_hel do c = 1, data%n_col i = i + 1 term%flv(i) = f term%hel(i) = h !!! Dummy-initialization of color term%col(i) = 1 call flv%init (term%data%flv_state (:,f), model) if (is_pol) then call hel%init (data%hel_state (:,h)) call qn%init (flv, hel, s) else call qn%init (flv, s) end if call qn%tag_hard_process () call term%int%add_state (qn) end do end do end do end do end associate end subroutine setup_states_threshold subroutine setup_states_other_prc_external () integer :: s, f, i, c, h if (is_pol) & call msg_fatal ("Polarized beams only supported by OpenLoops") i = 0 !!! n_sub = 0; if (nlo_t == NLO_VIRTUAL) n_sub = 1 associate (data => term%data) do s = 0, n_sub do f = 1, data%n_flv do h = 1, data%n_hel do c = 1, data%n_col i = i + 1 term%flv(i) = f term%hel(i) = h !!! Dummy-initialization of color term%col(i) = c call flv%init (data%flv_state (:,f), model) call color_init_from_array (col, & data%col_state(:,:,c), data%ghost_flag(:,c)) call col(1:data%n_in)%invert () call qn%init (flv, col, s) call qn%tag_hard_process () call term%int%add_state (qn) end do end do end do end do end associate end subroutine setup_states_other_prc_external subroutine setup_states_omega () integer :: f, h, c, i i = 0 associate (data => term%data) do f = 1, data%n_flv do h = 1, data%n_hel do c = 1, data%n_col if (core%is_allowed (term%i_term, f, h, c)) then i = i + 1 term%flv(i) = f term%hel(i) = h term%col(i) = c call flv%init (data%flv_state(:,f), model) call color_init_from_array (col, & data%col_state(:,:,c), & data%ghost_flag(:,c)) call col(:data%n_in)%invert () call hel%init (data%hel_state(:,h)) call qn%init (flv, col, hel) call qn%tag_hard_process () call term%int%add_state (qn) end if end do end do end do end associate end subroutine setup_states_omega end subroutine process_term_setup_interaction @ %def process_term_setup_interaction @ <>= procedure :: get_process_constants => process_term_get_process_constants <>= module subroutine process_term_get_process_constants & (term, prc_constants) class(process_term_t), intent(inout) :: term type(process_constants_t), intent(out) :: prc_constants end subroutine process_term_get_process_constants <>= module subroutine process_term_get_process_constants & (term, prc_constants) class(process_term_t), intent(inout) :: term type(process_constants_t), intent(out) :: prc_constants prc_constants = term%data end subroutine process_term_get_process_constants @ %def process_term_get_process_constants @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Process call statistics} Very simple object for statistics. Could be moved to a more basic chapter. <<[[process_counter.f90]]>>= <> module process_counter <> <> <> <> interface <> end interface end module process_counter @ %def process_counter @ This object can record process calls, categorized by evaluation status. It is a part of the [[mci_entry]] component below. <>= public :: process_counter_t <>= type :: process_counter_t integer :: total = 0 integer :: failed_kinematics = 0 integer :: failed_cuts = 0 integer :: has_passed = 0 integer :: evaluated = 0 integer :: complete = 0 contains <> end type process_counter_t @ %def process_counter_t @ Here are the corresponding numeric codes: <>= integer, parameter, public :: STAT_UNDEFINED = 0 integer, parameter, public :: STAT_INITIAL = 1 integer, parameter, public :: STAT_ACTIVATED = 2 integer, parameter, public :: STAT_BEAM_MOMENTA = 3 integer, parameter, public :: STAT_FAILED_KINEMATICS = 4 integer, parameter, public :: STAT_SEED_KINEMATICS = 5 integer, parameter, public :: STAT_HARD_KINEMATICS = 6 integer, parameter, public :: STAT_EFF_KINEMATICS = 7 integer, parameter, public :: STAT_FAILED_CUTS = 8 integer, parameter, public :: STAT_PASSED_CUTS = 9 integer, parameter, public :: STAT_EVALUATED_TRACE = 10 integer, parameter, public :: STAT_EVENT_COMPLETE = 11 @ %def STAT_UNDEFINED STAT_INITIAL STAT_ACTIVATED @ %def STAT_BEAM_MOMENTA STAT_FAILED_KINEMATICS @ %def STAT_SEED_KINEMATICS STAT_HARD_KINEMATICS STAT_EFF_KINEMATICS @ %def STAT_EVALUATED_TRACE STAT_EVENT_COMPLETE @ Output. <>= procedure :: write => process_counter_write <>= module subroutine process_counter_write (object, unit) class(process_counter_t), intent(in) :: object integer, intent(in), optional :: unit end subroutine process_counter_write <>= module subroutine process_counter_write (object, unit) class(process_counter_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) if (object%total > 0) then write (u, "(1x,A)") "Call statistics (current run):" write (u, "(3x,A,I0)") "total = ", object%total write (u, "(3x,A,I0)") "failed kin. = ", object%failed_kinematics write (u, "(3x,A,I0)") "failed cuts = ", object%failed_cuts write (u, "(3x,A,I0)") "passed cuts = ", object%has_passed write (u, "(3x,A,I0)") "evaluated = ", object%evaluated else write (u, "(1x,A)") "Call statistics (current run): [no calls]" end if end subroutine process_counter_write @ %def process_counter_write @ <<[[process_counter_sub.f90]]>>= <> submodule (process_counter) process_counter_s use io_units implicit none contains <> end submodule process_counter_s @ %def process_counter_s @ Reset. Just enforce default initialization. <>= procedure :: reset => process_counter_reset <>= module subroutine process_counter_reset (counter) class(process_counter_t), intent(out) :: counter end subroutine process_counter_reset <>= module subroutine process_counter_reset (counter) class(process_counter_t), intent(out) :: counter counter%total = 0 counter%failed_kinematics = 0 counter%failed_cuts = 0 counter%has_passed = 0 counter%evaluated = 0 counter%complete = 0 end subroutine process_counter_reset @ %def process_counter_reset @ We record an event according to the lowest status code greater or equal to the actual status. This is actually done by the process instance; the process object just copies the instance counter. <>= procedure :: record => process_counter_record <>= module subroutine process_counter_record (counter, status) class(process_counter_t), intent(inout) :: counter integer, intent(in) :: status end subroutine process_counter_record <>= module subroutine process_counter_record (counter, status) class(process_counter_t), intent(inout) :: counter integer, intent(in) :: status if (status <= STAT_FAILED_KINEMATICS) then counter%failed_kinematics = counter%failed_kinematics + 1 else if (status <= STAT_FAILED_CUTS) then counter%failed_cuts = counter%failed_cuts + 1 else if (status <= STAT_PASSED_CUTS) then counter%has_passed = counter%has_passed + 1 else counter%evaluated = counter%evaluated + 1 end if counter%total = counter%total + 1 end subroutine process_counter_record @ %def process_counter_record @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Multi-channel integration} <<[[process_mci.f90]]>>= <> module process_mci <> <> use cputime use rng_base use mci_base use variables use integration_results use process_libraries use phs_base use process_counter use process_config <> <> <> <> interface <> end interface end module process_mci @ %def process_mci @ <<[[process_mci_sub.f90]]>>= <> submodule (process_mci) process_mci_s <> use io_units use diagnostics use physics_defs use md5 implicit none contains <> end submodule process_mci_s @ %def process_mci_s \subsection{Process MCI entry} The [[process_mci_entry_t]] block contains, for each process component that is integrated independently, the configuration data for its MC input parameters. Each input parameter set is handled by a [[mci_t]] integrator. The MC input parameter set is broken down into the parameters required by the structure-function chain and the parameters required by the phase space of the elementary process. The MD5 sum collects all information about the associated processes that may affect the integration. It does not contain the MCI object itself or integration results. MC integration is organized in passes. Each pass may consist of several iterations, and for each iteration there is a number of calls. We store explicitly the values that apply to the current pass. Previous values are archived in the [[results]] object. The [[counter]] receives the counter statistics from the associated process instance, for diagnostics. The [[results]] object records results, broken down in passes and iterations. <>= public :: process_mci_entry_t <>= type :: process_mci_entry_t integer :: i_mci = 0 integer, dimension(:), allocatable :: i_component integer :: process_type = PRC_UNKNOWN integer :: n_par = 0 integer :: n_par_sf = 0 integer :: n_par_phs = 0 character(32) :: md5sum = "" integer :: pass = 0 integer :: n_it = 0 integer :: n_calls = 0 logical :: activate_timer = .false. real(default) :: error_threshold = 0 class(mci_t), allocatable :: mci type(process_counter_t) :: counter type(integration_results_t) :: results logical :: negative_weights = .false. logical :: combined_integration = .false. integer :: real_partition_type = REAL_FULL contains <> end type process_mci_entry_t @ %def process_mci_entry_t @ Finalizer for the [[mci]] component. <>= procedure :: final => process_mci_entry_final <>= module subroutine process_mci_entry_final (object) class(process_mci_entry_t), intent(inout) :: object end subroutine process_mci_entry_final <>= module subroutine process_mci_entry_final (object) class(process_mci_entry_t), intent(inout) :: object if (allocated (object%mci)) call object%mci%final () end subroutine process_mci_entry_final @ %def process_mci_entry_final @ Output. Write pass/iteration information only if set (the pass index is nonzero). Write the MCI block only if it exists (for some self-tests it does not). Write results only if there are any. <>= procedure :: write => process_mci_entry_write <>= module subroutine process_mci_entry_write (object, unit, pacify) class(process_mci_entry_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: pacify end subroutine process_mci_entry_write <>= module subroutine process_mci_entry_write (object, unit, pacify) class(process_mci_entry_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: pacify integer :: u u = given_output_unit (unit) write (u, "(3x,A,I0)") "Associated components = ", object%i_component write (u, "(3x,A,I0)") "MC input parameters = ", object%n_par write (u, "(3x,A,I0)") "MC parameters (SF) = ", object%n_par_sf write (u, "(3x,A,I0)") "MC parameters (PHS) = ", object%n_par_phs if (object%pass > 0) then write (u, "(3x,A,I0)") "Current pass = ", object%pass write (u, "(3x,A,I0)") "Number of iterations = ", object%n_it write (u, "(3x,A,I0)") "Number of calls = ", object%n_calls end if if (object%md5sum /= "") then write (u, "(3x,A,A,A)") "MD5 sum (components) = '", object%md5sum, "'" end if if (allocated (object%mci)) then call object%mci%write (u) end if call object%counter%write (u) if (object%results%exist ()) then call object%results%write (u, suppress = pacify) call object%results%write_chain_weights (u) end if end subroutine process_mci_entry_write @ %def process_mci_entry_write @ Configure the MCI entry. This is intent(inout) since some specific settings may be done before this. The actual [[mci_t]] object is an instance of the [[mci_template]] argument, which determines the concrete types. In a unit-test context, the [[mci_template]] argument may be unallocated. We obtain the number of channels and the number of parameters separately for the structure-function chain and for the associated process component. We assume that the phase-space object has already been configured. We assume that there is only one process component directly associated with an MCI entry. <>= procedure :: configure => process_mci_entry_configure <>= module subroutine process_mci_entry_configure (mci_entry, mci_template, & process_type, i_mci, i_component, component, & n_sfpar, rng_factory) class(process_mci_entry_t), intent(inout) :: mci_entry class(mci_t), intent(in), allocatable :: mci_template integer, intent(in) :: process_type integer, intent(in) :: i_mci integer, intent(in) :: i_component type(process_component_t), intent(in), target :: component integer, intent(in) :: n_sfpar class(rng_factory_t), intent(inout) :: rng_factory end subroutine process_mci_entry_configure <>= module subroutine process_mci_entry_configure (mci_entry, mci_template, & process_type, i_mci, i_component, component, & n_sfpar, rng_factory) class(process_mci_entry_t), intent(inout) :: mci_entry class(mci_t), intent(in), allocatable :: mci_template integer, intent(in) :: process_type integer, intent(in) :: i_mci integer, intent(in) :: i_component type(process_component_t), intent(in), target :: component integer, intent(in) :: n_sfpar class(rng_factory_t), intent(inout) :: rng_factory class(rng_t), allocatable :: rng associate (phs_config => component%phs_config) mci_entry%i_mci = i_mci call mci_entry%create_component_list (i_component, component%get_config ()) mci_entry%n_par_sf = n_sfpar mci_entry%n_par_phs = phs_config%get_n_par () mci_entry%n_par = mci_entry%n_par_sf + mci_entry%n_par_phs mci_entry%process_type = process_type if (allocated (mci_template)) then allocate (mci_entry%mci, source = mci_template) call mci_entry%mci%record_index (mci_entry%i_mci) call mci_entry%mci%set_dimensions & (mci_entry%n_par, phs_config%get_n_channel ()) call mci_entry%mci%declare_flat_dimensions & (phs_config%get_flat_dimensions ()) if (phs_config%provides_equivalences) then call mci_entry%mci%declare_equivalences & (phs_config%channel, mci_entry%n_par_sf) end if if (phs_config%provides_chains) then call mci_entry%mci%declare_chains (phs_config%chain) end if call rng_factory%make (rng) call mci_entry%mci%import_rng (rng) end if call mci_entry%results%init (process_type) end associate end subroutine process_mci_entry_configure @ %def process_mci_entry_configure @ <>= integer, parameter, public :: REAL_FULL = 0 integer, parameter, public :: REAL_SINGULAR = 1 integer, parameter, public :: REAL_FINITE = 2 @ <>= procedure :: create_component_list => & process_mci_entry_create_component_list <>= module subroutine process_mci_entry_create_component_list (mci_entry, & i_component, component_config) class (process_mci_entry_t), intent(inout) :: mci_entry integer, intent(in) :: i_component type(process_component_def_t), intent(in) :: component_config end subroutine process_mci_entry_create_component_list <>= module subroutine process_mci_entry_create_component_list (mci_entry, & i_component, component_config) class (process_mci_entry_t), intent(inout) :: mci_entry integer, intent(in) :: i_component type(process_component_def_t), intent(in) :: component_config integer, dimension(:), allocatable :: i_list integer :: n integer, save :: i_rfin_offset = 0 if (debug_on) call msg_debug & (D_PROCESS_INTEGRATION, "process_mci_entry_create_component_list") if (mci_entry%combined_integration) then if (debug_on) call msg_debug (D_PROCESS_INTEGRATION, & "mci_entry%real_partition_type", mci_entry%real_partition_type) n = get_n_components (mci_entry%real_partition_type) allocate (i_list (n)) select case (mci_entry%real_partition_type) case (REAL_FULL) i_list = component_config%get_association_list () allocate (mci_entry%i_component (size (i_list))) mci_entry%i_component = i_list case (REAL_SINGULAR) i_list = component_config%get_association_list (ASSOCIATED_REAL_FIN) allocate (mci_entry%i_component (size(i_list))) mci_entry%i_component = i_list case (REAL_FINITE) allocate (mci_entry%i_component (1)) mci_entry%i_component(1) = & component_config%get_associated_real_fin () + i_rfin_offset i_rfin_offset = i_rfin_offset + 1 end select else allocate (mci_entry%i_component (1)) mci_entry%i_component(1) = i_component end if contains function get_n_components (real_partition_type) result (n_components) integer :: n_components integer, intent(in) :: real_partition_type select case (real_partition_type) case (REAL_FULL) n_components = size (component_config%get_association_list ()) case (REAL_SINGULAR) n_components = size (component_config%get_association_list & (ASSOCIATED_REAL_FIN)) end select if (debug_on) call msg_debug & (D_PROCESS_INTEGRATION, "n_components", n_components) end function get_n_components end subroutine process_mci_entry_create_component_list @ %def process_mci_entry_create_component_list @ Set some additional parameters. <>= procedure :: set_parameters => process_mci_entry_set_parameters <>= module subroutine process_mci_entry_set_parameters (mci_entry, var_list) class(process_mci_entry_t), intent(inout) :: mci_entry type(var_list_t), intent(in) :: var_list end subroutine process_mci_entry_set_parameters <>= module subroutine process_mci_entry_set_parameters (mci_entry, var_list) class(process_mci_entry_t), intent(inout) :: mci_entry type(var_list_t), intent(in) :: var_list integer :: integration_results_verbosity real(default) :: error_threshold integration_results_verbosity = & var_list%get_ival (var_str ("integration_results_verbosity")) error_threshold = & var_list%get_rval (var_str ("error_threshold")) mci_entry%activate_timer = & var_list%get_lval (var_str ("?integration_timer")) call mci_entry%results%set_verbosity (integration_results_verbosity) call mci_entry%results%set_error_threshold (error_threshold) end subroutine process_mci_entry_set_parameters @ %def process_mci_entry_set_parameters @ Compute an MD5 sum that summarizes all information that could influence integration results, for the associated process components. We take the process-configuration MD5 sum which represents parameters, cuts, etc., the MD5 sums for the process component definitions and their phase space objects (which should be configured), and the beam configuration MD5 sum. (The QCD setup is included in the process configuration data MD5 sum.) Done only once, when the MD5 sum is still empty. <>= procedure :: compute_md5sum => process_mci_entry_compute_md5sum <>= module subroutine process_mci_entry_compute_md5sum (mci_entry, & config, component, beam_config) class(process_mci_entry_t), intent(inout) :: mci_entry type(process_config_data_t), intent(in) :: config type(process_component_t), dimension(:), intent(in) :: component type(process_beam_config_t), intent(in) :: beam_config end subroutine process_mci_entry_compute_md5sum <>= module subroutine process_mci_entry_compute_md5sum (mci_entry, & config, component, beam_config) class(process_mci_entry_t), intent(inout) :: mci_entry type(process_config_data_t), intent(in) :: config type(process_component_t), dimension(:), intent(in) :: component type(process_beam_config_t), intent(in) :: beam_config type(string_t) :: buffer integer :: i if (mci_entry%md5sum == "") then buffer = config%get_md5sum () // beam_config%get_md5sum () do i = 1, size (component) if (component(i)%is_active ()) then buffer = buffer // component(i)%get_md5sum () end if end do mci_entry%md5sum = md5sum (char (buffer)) end if if (allocated (mci_entry%mci)) then call mci_entry%mci%set_md5sum (mci_entry%md5sum) end if end subroutine process_mci_entry_compute_md5sum @ %def process_mci_entry_compute_md5sum @ Test the MCI sampler by calling it a given number of time, discarding the results. The instance should be initialized. The [[mci_entry]] is [[intent(inout)]] because the integrator contains the random-number state. <>= procedure :: sampler_test => process_mci_entry_sampler_test <>= module subroutine process_mci_entry_sampler_test & (mci_entry, mci_sampler, n_calls) class(process_mci_entry_t), intent(inout) :: mci_entry class(mci_sampler_t), intent(inout), target :: mci_sampler integer, intent(in) :: n_calls end subroutine process_mci_entry_sampler_test <>= module subroutine process_mci_entry_sampler_test & (mci_entry, mci_sampler, n_calls) class(process_mci_entry_t), intent(inout) :: mci_entry class(mci_sampler_t), intent(inout), target :: mci_sampler integer, intent(in) :: n_calls call mci_entry%mci%sampler_test (mci_sampler, n_calls) end subroutine process_mci_entry_sampler_test @ %def process_mci_entry_sampler_test @ Integrate. The [[integrate]] method counts as an integration pass; the pass count is increased by one. We transfer the pass parameters (number of iterations and number of calls) to the actual integration routine. The [[mci_entry]] is [[intent(inout)]] because the integrator contains the random-number state. Note: The results are written to screen and to logfile. This behavior is hardcoded. <>= procedure :: integrate => process_mci_entry_integrate procedure :: final_integration => process_mci_entry_final_integration <>= module subroutine process_mci_entry_integrate (mci_entry, mci_instance, & mci_sampler, n_it, n_calls, & adapt_grids, adapt_weights, final, pacify, & nlo_type) class(process_mci_entry_t), intent(inout) :: mci_entry class(mci_instance_t), intent(inout) :: mci_instance class(mci_sampler_t), intent(inout) :: mci_sampler integer, intent(in) :: n_it integer, intent(in) :: n_calls logical, intent(in), optional :: adapt_grids logical, intent(in), optional :: adapt_weights logical, intent(in), optional :: final, pacify integer, intent(in), optional :: nlo_type end subroutine process_mci_entry_integrate module subroutine process_mci_entry_final_integration (mci_entry) class(process_mci_entry_t), intent(inout) :: mci_entry end subroutine process_mci_entry_final_integration <>= module subroutine process_mci_entry_integrate (mci_entry, mci_instance, & mci_sampler, n_it, n_calls, & adapt_grids, adapt_weights, final, pacify, & nlo_type) class(process_mci_entry_t), intent(inout) :: mci_entry class(mci_instance_t), intent(inout) :: mci_instance class(mci_sampler_t), intent(inout) :: mci_sampler integer, intent(in) :: n_it integer, intent(in) :: n_calls logical, intent(in), optional :: adapt_grids logical, intent(in), optional :: adapt_weights logical, intent(in), optional :: final, pacify integer, intent(in), optional :: nlo_type integer :: u_log u_log = logfile_unit () mci_entry%pass = mci_entry%pass + 1 mci_entry%n_it = n_it mci_entry%n_calls = n_calls if (mci_entry%pass == 1) & call mci_entry%mci%startup_message (n_calls = n_calls) call mci_entry%mci%set_timer (active = mci_entry%activate_timer) call mci_entry%results%display_init (screen = .true., unit = u_log) call mci_entry%results%new_pass () if (present (nlo_type)) then select case (nlo_type) case (NLO_VIRTUAL, NLO_REAL, NLO_MISMATCH, NLO_DGLAP) mci_instance%negative_weights = .true. end select end if call mci_entry%mci%add_pass (adapt_grids, adapt_weights, final) call mci_entry%mci%start_timer () call mci_entry%mci%integrate (mci_instance, mci_sampler, n_it, & n_calls, mci_entry%results, pacify = pacify) call mci_entry%mci%stop_timer () if (signal_is_pending ()) return end subroutine process_mci_entry_integrate module subroutine process_mci_entry_final_integration (mci_entry) class(process_mci_entry_t), intent(inout) :: mci_entry call mci_entry%results%display_final () call mci_entry%time_message () end subroutine process_mci_entry_final_integration @ %def process_mci_entry_integrate @ %def process_mci_entry_final_integration @ If appropriate, issue an informative message about the expected time for an event sample. <>= procedure :: get_time => process_mci_entry_get_time procedure :: time_message => process_mci_entry_time_message <>= module subroutine process_mci_entry_get_time (mci_entry, time, sample) class(process_mci_entry_t), intent(in) :: mci_entry type(time_t), intent(out) :: time integer, intent(in) :: sample end subroutine process_mci_entry_get_time module subroutine process_mci_entry_time_message (mci_entry) class(process_mci_entry_t), intent(in) :: mci_entry end subroutine process_mci_entry_time_message <>= module subroutine process_mci_entry_get_time (mci_entry, time, sample) class(process_mci_entry_t), intent(in) :: mci_entry type(time_t), intent(out) :: time integer, intent(in) :: sample real(default) :: time_last_pass, efficiency, calls time_last_pass = mci_entry%mci%get_time () calls = mci_entry%results%get_n_calls () efficiency = mci_entry%mci%get_efficiency () if (time_last_pass > 0 .and. calls > 0 .and. efficiency > 0) then time = nint (time_last_pass / calls / efficiency * sample) end if end subroutine process_mci_entry_get_time module subroutine process_mci_entry_time_message (mci_entry) class(process_mci_entry_t), intent(in) :: mci_entry type(time_t) :: time integer :: sample sample = 10000 call mci_entry%get_time (time, sample) if (time%is_known ()) then call msg_message ("Time estimate for generating 10000 events: " & // char (time%to_string_dhms ())) end if end subroutine process_mci_entry_time_message @ %def process_mci_entry_time_message @ Prepare event generation. (For the test integrator, this does nothing. It is relevant for the VAMP integrator.) <>= procedure :: prepare_simulation => process_mci_entry_prepare_simulation <>= module subroutine process_mci_entry_prepare_simulation (mci_entry) class(process_mci_entry_t), intent(inout) :: mci_entry end subroutine process_mci_entry_prepare_simulation <>= module subroutine process_mci_entry_prepare_simulation (mci_entry) class(process_mci_entry_t), intent(inout) :: mci_entry call mci_entry%mci%prepare_simulation () end subroutine process_mci_entry_prepare_simulation @ %def process_mci_entry_prepare_simulation @ Generate an event. The instance should be initialized, otherwise event generation is directed by the [[mci]] integrator subobject. The integrator instance is contained in a [[mci_work]] subobject of the process instance, which simultaneously serves as the sampler object. (We avoid the anti-aliasing rules if we assume that the sampling itself does not involve the integrator instance contained in the process instance.) Regarding weighted events, we only take events which are valid, which means that they have valid kinematics and have passed cuts. Therefore, we have a rejection loop. For unweighted events, the unweighting routine should already take care of this. The [[keep_failed]] flag determines whether events which failed cuts are nevertheless produced, to be recorded with zero weight. Alternatively, failed events are dropped, and this fact is recorded by the counter [[n_dropped]]. <>= procedure :: generate_weighted_event => & process_mci_entry_generate_weighted_event procedure :: generate_unweighted_event => & process_mci_entry_generate_unweighted_event <>= module subroutine process_mci_entry_generate_weighted_event (mci_entry, & mci_instance, mci_sampler, keep_failed) class(process_mci_entry_t), intent(inout) :: mci_entry class(mci_instance_t), intent(inout) :: mci_instance class(mci_sampler_t), intent(inout) :: mci_sampler logical, intent(in) :: keep_failed end subroutine process_mci_entry_generate_weighted_event module subroutine process_mci_entry_generate_unweighted_event & (mci_entry, mci_instance, mci_sampler) class(process_mci_entry_t), intent(inout) :: mci_entry class(mci_instance_t), intent(inout) :: mci_instance class(mci_sampler_t), intent(inout) :: mci_sampler end subroutine process_mci_entry_generate_unweighted_event <>= module subroutine process_mci_entry_generate_weighted_event (mci_entry, & mci_instance, mci_sampler, keep_failed) class(process_mci_entry_t), intent(inout) :: mci_entry class(mci_instance_t), intent(inout) :: mci_instance class(mci_sampler_t), intent(inout) :: mci_sampler logical, intent(in) :: keep_failed logical :: generate_new generate_new = .true. call mci_instance%reset_n_event_dropped () REJECTION: do while (generate_new) call mci_entry%mci%generate_weighted_event (mci_instance, mci_sampler) if (signal_is_pending ()) return if (.not. mci_sampler%is_valid()) then if (keep_failed) then generate_new = .false. else call mci_instance%record_event_dropped () generate_new = .true. end if else generate_new = .false. end if end do REJECTION end subroutine process_mci_entry_generate_weighted_event module subroutine process_mci_entry_generate_unweighted_event & (mci_entry, mci_instance, mci_sampler) class(process_mci_entry_t), intent(inout) :: mci_entry class(mci_instance_t), intent(inout) :: mci_instance class(mci_sampler_t), intent(inout) :: mci_sampler call mci_entry%mci%generate_unweighted_event (mci_instance, mci_sampler) end subroutine process_mci_entry_generate_unweighted_event @ %def process_mci_entry_generate_weighted_event @ %def process_mci_entry_generate_unweighted_event @ Extract results. <>= procedure :: has_integral => process_mci_entry_has_integral procedure :: get_integral => process_mci_entry_get_integral procedure :: get_error => process_mci_entry_get_error procedure :: get_accuracy => process_mci_entry_get_accuracy procedure :: get_chi2 => process_mci_entry_get_chi2 procedure :: get_efficiency => process_mci_entry_get_efficiency <>= module function process_mci_entry_has_integral (mci_entry) result (flag) class(process_mci_entry_t), intent(in) :: mci_entry logical :: flag end function process_mci_entry_has_integral module function process_mci_entry_get_integral (mci_entry) result (integral) class(process_mci_entry_t), intent(in) :: mci_entry real(default) :: integral end function process_mci_entry_get_integral module function process_mci_entry_get_error (mci_entry) result (error) class(process_mci_entry_t), intent(in) :: mci_entry real(default) :: error end function process_mci_entry_get_error module function process_mci_entry_get_accuracy (mci_entry) result (accuracy) class(process_mci_entry_t), intent(in) :: mci_entry real(default) :: accuracy end function process_mci_entry_get_accuracy module function process_mci_entry_get_chi2 (mci_entry) result (chi2) class(process_mci_entry_t), intent(in) :: mci_entry real(default) :: chi2 end function process_mci_entry_get_chi2 module function process_mci_entry_get_efficiency & (mci_entry) result (efficiency) class(process_mci_entry_t), intent(in) :: mci_entry real(default) :: efficiency end function process_mci_entry_get_efficiency <>= module function process_mci_entry_has_integral (mci_entry) result (flag) class(process_mci_entry_t), intent(in) :: mci_entry logical :: flag flag = mci_entry%results%exist () end function process_mci_entry_has_integral module function process_mci_entry_get_integral (mci_entry) result (integral) class(process_mci_entry_t), intent(in) :: mci_entry real(default) :: integral integral = mci_entry%results%get_integral () end function process_mci_entry_get_integral module function process_mci_entry_get_error (mci_entry) result (error) class(process_mci_entry_t), intent(in) :: mci_entry real(default) :: error error = mci_entry%results%get_error () end function process_mci_entry_get_error module function process_mci_entry_get_accuracy (mci_entry) result (accuracy) class(process_mci_entry_t), intent(in) :: mci_entry real(default) :: accuracy accuracy = mci_entry%results%get_accuracy () end function process_mci_entry_get_accuracy module function process_mci_entry_get_chi2 (mci_entry) result (chi2) class(process_mci_entry_t), intent(in) :: mci_entry real(default) :: chi2 chi2 = mci_entry%results%get_chi2 () end function process_mci_entry_get_chi2 module function process_mci_entry_get_efficiency & (mci_entry) result (efficiency) class(process_mci_entry_t), intent(in) :: mci_entry real(default) :: efficiency efficiency = mci_entry%results%get_efficiency () end function process_mci_entry_get_efficiency @ %def process_mci_entry_get_integral process_mci_entry_get_error @ %def process_mci_entry_get_accuracy process_mci_entry_get_chi2 @ %def process_mci_entry_get_efficiency @ Return the MCI checksum. This may be the one used for configuration, but may also incorporate results, if they change the state of the integrator (adaptation). <>= procedure :: get_md5sum => process_mci_entry_get_md5sum <>= pure module function process_mci_entry_get_md5sum (entry) result (md5sum) class(process_mci_entry_t), intent(in) :: entry character(32) :: md5sum end function process_mci_entry_get_md5sum <>= pure module function process_mci_entry_get_md5sum (entry) result (md5sum) class(process_mci_entry_t), intent(in) :: entry character(32) :: md5sum md5sum = entry%mci%get_md5sum () end function process_mci_entry_get_md5sum @ %def process_mci_entry_get_md5sum @ \subsection{MC parameter set and MCI instance} For each process component that is associated with a multi-channel integration (MCI) object, the [[mci_work_t]] object contains the currently active parameter set. It also holds the implementation of the [[mci_instance_t]] that the integrator needs for doing its work. <>= public :: mci_work_t <>= type :: mci_work_t type(process_mci_entry_t), pointer :: config => null () real(default), dimension(:), allocatable :: x class(mci_instance_t), pointer :: mci => null () type(process_counter_t) :: counter logical :: keep_failed_events = .false. integer :: n_event_dropped = 0 contains <> end type mci_work_t @ %def mci_work_t @ First write configuration data, then the current values. <>= procedure :: write => mci_work_write <>= module subroutine mci_work_write (mci_work, unit, testflag) class(mci_work_t), intent(in) :: mci_work integer, intent(in), optional :: unit logical, intent(in), optional :: testflag end subroutine mci_work_write <>= module subroutine mci_work_write (mci_work, unit, testflag) class(mci_work_t), intent(in) :: mci_work integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u, i u = given_output_unit (unit) write (u, "(1x,A,I0,A)") "Active MCI instance #", & mci_work%config%i_mci, " =" write (u, "(2x)", advance="no") do i = 1, mci_work%config%n_par write (u, "(1x,F7.5)", advance="no") mci_work%x(i) if (i == mci_work%config%n_par_sf) & write (u, "(1x,'|')", advance="no") end do write (u, *) if (associated (mci_work%mci)) then call mci_work%mci%write (u, pacify = testflag) call mci_work%counter%write (u) end if end subroutine mci_work_write @ %def mci_work_write @ The [[mci]] component may require finalization. <>= procedure :: final => mci_work_final <>= module subroutine mci_work_final (mci_work) class(mci_work_t), intent(inout) :: mci_work end subroutine mci_work_final <>= module subroutine mci_work_final (mci_work) class(mci_work_t), intent(inout) :: mci_work if (associated (mci_work%mci)) then call mci_work%mci%final () deallocate (mci_work%mci) end if end subroutine mci_work_final @ %def mci_work_final @ Initialize with the maximum length that we will need. Contents are not initialized. The integrator inside the [[mci_entry]] object is responsible for allocating and initializing its own instance, which is referred to by a pointer in the [[mci_work]] object. <>= procedure :: init => mci_work_init <>= module subroutine mci_work_init (mci_work, mci_entry) class(mci_work_t), intent(out) :: mci_work type(process_mci_entry_t), intent(in), target :: mci_entry end subroutine mci_work_init <>= module subroutine mci_work_init (mci_work, mci_entry) class(mci_work_t), intent(out) :: mci_work type(process_mci_entry_t), intent(in), target :: mci_entry mci_work%config => mci_entry allocate (mci_work%x (mci_entry%n_par)) if (allocated (mci_entry%mci)) then call mci_entry%mci%allocate_instance (mci_work%mci) call mci_work%mci%init (mci_entry%mci) end if end subroutine mci_work_init @ %def mci_work_init @ Set parameters explicitly, either all at once, or separately for the structure-function and process parts. <>= procedure :: set => mci_work_set procedure :: set_x_strfun => mci_work_set_x_strfun procedure :: set_x_process => mci_work_set_x_process <>= module subroutine mci_work_set (mci_work, x) class(mci_work_t), intent(inout) :: mci_work real(default), dimension(:), intent(in) :: x end subroutine mci_work_set module subroutine mci_work_set_x_strfun (mci_work, x) class(mci_work_t), intent(inout) :: mci_work real(default), dimension(:), intent(in) :: x end subroutine mci_work_set_x_strfun module subroutine mci_work_set_x_process (mci_work, x) class(mci_work_t), intent(inout) :: mci_work real(default), dimension(:), intent(in) :: x end subroutine mci_work_set_x_process <>= module subroutine mci_work_set (mci_work, x) class(mci_work_t), intent(inout) :: mci_work real(default), dimension(:), intent(in) :: x mci_work%x = x end subroutine mci_work_set module subroutine mci_work_set_x_strfun (mci_work, x) class(mci_work_t), intent(inout) :: mci_work real(default), dimension(:), intent(in) :: x mci_work%x(1 : mci_work%config%n_par_sf) = x end subroutine mci_work_set_x_strfun module subroutine mci_work_set_x_process (mci_work, x) class(mci_work_t), intent(inout) :: mci_work real(default), dimension(:), intent(in) :: x mci_work%x(mci_work%config%n_par_sf + 1 : mci_work%config%n_par) = x end subroutine mci_work_set_x_process @ %def mci_work_set @ %def mci_work_set_x_strfun @ %def mci_work_set_x_process @ Return the array of active components, i.e., those that correspond to the currently selected MC parameter set. <>= procedure :: get_active_components => mci_work_get_active_components <>= module function mci_work_get_active_components & (mci_work) result (i_component) class(mci_work_t), intent(in) :: mci_work integer, dimension(:), allocatable :: i_component end function mci_work_get_active_components <>= module function mci_work_get_active_components (mci_work) result (i_component) class(mci_work_t), intent(in) :: mci_work integer, dimension(:), allocatable :: i_component allocate (i_component (size (mci_work%config%i_component))) i_component = mci_work%config%i_component end function mci_work_get_active_components @ %def mci_work_get_active_components @ Return the active parameters as a simple array with correct length. Do this separately for the structure-function parameters and the process parameters. <>= procedure :: get_x_strfun => mci_work_get_x_strfun procedure :: get_x_process => mci_work_get_x_process <>= pure module function mci_work_get_x_strfun (mci_work) result (x) class(mci_work_t), intent(in) :: mci_work real(default), dimension(mci_work%config%n_par_sf) :: x end function mci_work_get_x_strfun pure module function mci_work_get_x_process (mci_work) result (x) class(mci_work_t), intent(in) :: mci_work real(default), dimension(mci_work%config%n_par_phs) :: x end function mci_work_get_x_process <>= pure module function mci_work_get_x_strfun (mci_work) result (x) class(mci_work_t), intent(in) :: mci_work real(default), dimension(mci_work%config%n_par_sf) :: x x = mci_work%x(1 : mci_work%config%n_par_sf) end function mci_work_get_x_strfun pure module function mci_work_get_x_process (mci_work) result (x) class(mci_work_t), intent(in) :: mci_work real(default), dimension(mci_work%config%n_par_phs) :: x x = mci_work%x(mci_work%config%n_par_sf + 1 : mci_work%config%n_par) end function mci_work_get_x_process @ %def mci_work_get_x_strfun @ %def mci_work_get_x_process @ Initialize and finalize event generation for the specified MCI entry. This also resets the counter. <>= procedure :: init_simulation => mci_work_init_simulation procedure :: final_simulation => mci_work_final_simulation <>= module subroutine mci_work_final_simulation (mci_work) class(mci_work_t), intent(inout) :: mci_work end subroutine mci_work_final_simulation module subroutine mci_work_init_simulation & (mci_work, safety_factor, keep_failed_events) class(mci_work_t), intent(inout) :: mci_work real(default), intent(in), optional :: safety_factor logical, intent(in), optional :: keep_failed_events end subroutine mci_work_init_simulation <>= module subroutine mci_work_init_simulation & (mci_work, safety_factor, keep_failed_events) class(mci_work_t), intent(inout) :: mci_work real(default), intent(in), optional :: safety_factor logical, intent(in), optional :: keep_failed_events call mci_work%mci%init_simulation (safety_factor) call mci_work%counter%reset () if (present (keep_failed_events)) & mci_work%keep_failed_events = keep_failed_events end subroutine mci_work_init_simulation module subroutine mci_work_final_simulation (mci_work) class(mci_work_t), intent(inout) :: mci_work call mci_work%mci%final_simulation () end subroutine mci_work_final_simulation @ %def mci_work_init_simulation @ %def mci_work_final_simulation @ Counter. <>= procedure :: reset_counter => mci_work_reset_counter procedure :: record_call => mci_work_record_call procedure :: get_counter => mci_work_get_counter <>= module subroutine mci_work_reset_counter (mci_work) class(mci_work_t), intent(inout) :: mci_work end subroutine mci_work_reset_counter module subroutine mci_work_record_call (mci_work, status) class(mci_work_t), intent(inout) :: mci_work integer, intent(in) :: status end subroutine mci_work_record_call pure module function mci_work_get_counter (mci_work) result (counter) class(mci_work_t), intent(in) :: mci_work type(process_counter_t) :: counter end function mci_work_get_counter <>= module subroutine mci_work_reset_counter (mci_work) class(mci_work_t), intent(inout) :: mci_work call mci_work%counter%reset () end subroutine mci_work_reset_counter module subroutine mci_work_record_call (mci_work, status) class(mci_work_t), intent(inout) :: mci_work integer, intent(in) :: status call mci_work%counter%record (status) end subroutine mci_work_record_call pure module function mci_work_get_counter (mci_work) result (counter) class(mci_work_t), intent(in) :: mci_work type(process_counter_t) :: counter counter = mci_work%counter end function mci_work_get_counter @ %def mci_work_reset_counter @ %def mci_work_record_call @ %def mci_work_get_counter @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Process component manager} <<[[pcm.f90]]>>= <> module pcm <> <> use lorentz use model_data, only: model_data_t use models, only: model_t use quantum_numbers, only: quantum_numbers_t, quantum_numbers_mask_t use variables, only: var_list_t use nlo_data, only: nlo_settings_t use nlo_data, only: fks_template_t use nlo_data, only: FKS_DEFAULT, FKS_RESONANCES use mci_base, only: mci_t use phs_base, only: phs_config_t use mappings, only: mapping_defaults_t use phs_forests, only: phs_parameters_t use phs_fks, only: isr_kinematics_t, real_kinematics_t use phs_fks, only: phs_identifier_t use fks_regions, only: region_data_t use phs_fks, only: phs_fks_generator_t use phs_fks, only: dalitz_plot_t use phs_fks, only: phs_fks_config_t, get_filtered_resonance_histories use dispatch_phase_space, only: dispatch_phs use real_subtraction, only: real_subtraction_t, soft_mismatch_t use real_subtraction, only: FIXED_ORDER_EVENTS, POWHEG use real_subtraction, only: real_partition_t, powheg_damping_simple_t use real_subtraction, only: real_partition_fixed_order_t use virtual, only: virtual_t use dglap_remnant, only: dglap_remnant_t use blha_config, only: blha_master_t use pcm_base use process_config use process_mci, only: process_mci_entry_t use process_mci, only: REAL_SINGULAR, REAL_FINITE <> <> <> interface <> end interface contains <> end module pcm @ %def pcm @ <<[[pcm_sub.f90]]>>= <> submodule (pcm) pcm_s <> use constants, only: zero, two use diagnostics use phs_points, only: assignment(=) use io_units, only: free_unit use os_interface use process_constants, only: process_constants_t use physics_defs use flavors, only: flavor_t use interactions, only: interaction_t use dispatch_fks, only: dispatch_fks_setup use process_libraries, only: process_component_def_t use resonances, only: resonance_history_t, resonance_history_set_t use prc_threshold, only: threshold_def_t use blha_olp_interfaces, only: prc_blha_t implicit none contains <> end submodule pcm_s @ %def pcm_s @ \subsection{Default process component manager} This is the configuration object which has the duty of allocating the corresponding instance. The default version is trivial. <>= public :: pcm_default_t <>= type, extends (pcm_t) :: pcm_default_t contains <> end type pcm_default_t @ %def pcm_default_t Gfortran 7/8/9 bug, has to remain in the main module: <>= procedure :: allocate_workspace => pcm_default_allocate_workspace <>= subroutine pcm_default_allocate_workspace (pcm, work) class(pcm_default_t), intent(in) :: pcm class(pcm_workspace_t), intent(inout), allocatable :: work allocate (pcm_default_workspace_t :: work) end subroutine pcm_default_allocate_workspace @ %def pcm_default_allocate_workspace @ Finalizer: apply to core manager. <>= procedure :: final => pcm_default_final <>= module subroutine pcm_default_final (pcm) class(pcm_default_t), intent(inout) :: pcm end subroutine pcm_default_final <>= module subroutine pcm_default_final (pcm) class(pcm_default_t), intent(inout) :: pcm end subroutine pcm_default_final @ %def pcm_default_final @ <>= procedure :: is_nlo => pcm_default_is_nlo <>= module function pcm_default_is_nlo (pcm) result (is_nlo) logical :: is_nlo class(pcm_default_t), intent(in) :: pcm end function pcm_default_is_nlo <>= module function pcm_default_is_nlo (pcm) result (is_nlo) logical :: is_nlo class(pcm_default_t), intent(in) :: pcm is_nlo = .false. end function pcm_default_is_nlo @ %def pcm_default_is_nlo @ Initialize configuration data, using environment variables. <>= procedure :: init => pcm_default_init <>= module subroutine pcm_default_init (pcm, env, meta) class(pcm_default_t), intent(out) :: pcm type(process_environment_t), intent(in) :: env type(process_metadata_t), intent(in) :: meta end subroutine pcm_default_init <>= module subroutine pcm_default_init (pcm, env, meta) class(pcm_default_t), intent(out) :: pcm type(process_environment_t), intent(in) :: env type(process_metadata_t), intent(in) :: meta pcm%has_pdfs = env%has_pdfs () call pcm%set_blha_defaults & (env%has_polarized_beams (), env%get_var_list_ptr ()) pcm%os_data = env%get_os_data () end subroutine pcm_default_init @ %def pcm_default_init @ <>= type, extends (pcm_workspace_t) :: pcm_default_workspace_t contains <> end type pcm_default_workspace_t @ %def pcm_default_workspace_t @ <>= procedure :: final => pcm_default_workspace_final <>= module subroutine pcm_default_workspace_final (pcm_work) class(pcm_default_workspace_t), intent(inout) :: pcm_work end subroutine pcm_default_workspace_final <>= module subroutine pcm_default_workspace_final (pcm_work) class(pcm_default_workspace_t), intent(inout) :: pcm_work end subroutine pcm_default_workspace_final @ %def pcm_default_workspace_final @ <>= procedure :: is_nlo => pcm_default_workspace_is_nlo <>= module function pcm_default_workspace_is_nlo (pcm_work) result (is_nlo) logical :: is_nlo class(pcm_default_workspace_t), intent(inout) :: pcm_work end function pcm_default_workspace_is_nlo <>= module function pcm_default_workspace_is_nlo (pcm_work) result (is_nlo) logical :: is_nlo class(pcm_default_workspace_t), intent(inout) :: pcm_work is_nlo = .false. end function pcm_default_workspace_is_nlo @ %def pcm_default_workspace_is_nlo @ \subsection{Implementations for the default manager} Categorize components. Nothing to do here, all components are of Born type. <>= procedure :: categorize_components => pcm_default_categorize_components <>= module subroutine pcm_default_categorize_components (pcm, config) class(pcm_default_t), intent(inout) :: pcm type(process_config_data_t), intent(in) :: config end subroutine pcm_default_categorize_components <>= module subroutine pcm_default_categorize_components (pcm, config) class(pcm_default_t), intent(inout) :: pcm type(process_config_data_t), intent(in) :: config end subroutine pcm_default_categorize_components @ %def pcm_default_categorize_components @ \subsubsection{Phase-space configuration} Default setup for tree processes: a single phase-space configuration that is valid for all components. <>= procedure :: init_phs_config => pcm_default_init_phs_config <>= module subroutine pcm_default_init_phs_config & (pcm, phs_entry, meta, env, phs_par, mapping_defs) class(pcm_default_t), intent(inout) :: pcm type(process_phs_config_t), & dimension(:), allocatable, intent(out) :: phs_entry type(process_metadata_t), intent(in) :: meta type(process_environment_t), intent(in) :: env type(mapping_defaults_t), intent(in) :: mapping_defs type(phs_parameters_t), intent(in) :: phs_par end subroutine pcm_default_init_phs_config <>= module subroutine pcm_default_init_phs_config & (pcm, phs_entry, meta, env, phs_par, mapping_defs) class(pcm_default_t), intent(inout) :: pcm type(process_phs_config_t), & dimension(:), allocatable, intent(out) :: phs_entry type(process_metadata_t), intent(in) :: meta type(process_environment_t), intent(in) :: env type(mapping_defaults_t), intent(in) :: mapping_defs type(phs_parameters_t), intent(in) :: phs_par allocate (phs_entry (1)) allocate (pcm%i_phs_config (pcm%n_components), source=1) call dispatch_phs (phs_entry(1)%phs_config, & env%get_var_list_ptr (), & env%get_os_data (), & meta%id, & mapping_defs, phs_par) end subroutine pcm_default_init_phs_config @ %def pcm_default_init_phs_config @ \subsubsection{Core management} The default component manager assigns one core per component. We allocate and configure the core objects, using the process-component configuration data. <>= procedure :: allocate_cores => pcm_default_allocate_cores <>= module subroutine pcm_default_allocate_cores (pcm, config, core_entry) class(pcm_default_t), intent(inout) :: pcm type(process_config_data_t), intent(in) :: config type(core_entry_t), dimension(:), allocatable, intent(out) :: core_entry end subroutine pcm_default_allocate_cores <>= module subroutine pcm_default_allocate_cores (pcm, config, core_entry) class(pcm_default_t), intent(inout) :: pcm type(process_config_data_t), intent(in) :: config type(core_entry_t), dimension(:), allocatable, intent(out) :: core_entry type(process_component_def_t), pointer :: component_def integer :: i allocate (pcm%i_core (pcm%n_components), source = 0) pcm%n_cores = pcm%n_components allocate (core_entry (pcm%n_cores)) do i = 1, pcm%n_cores pcm%i_core(i) = i core_entry(i)%i_component = i component_def => config%process_def%get_component_def_ptr (i) core_entry(i)%core_def => component_def%get_core_def_ptr () core_entry(i)%active = component_def%can_be_integrated () end do end subroutine pcm_default_allocate_cores @ %def pcm_default_allocate_cores @ Extra code is required for certain core types (threshold) or if BLHA uses an external OLP (Born only, this case) for getting its matrix elements. <>= procedure :: prepare_any_external_code => & pcm_default_prepare_any_external_code <>= module subroutine pcm_default_prepare_any_external_code & (pcm, core_entry, i_core, libname, model, var_list) class(pcm_default_t), intent(in) :: pcm type(core_entry_t), intent(inout) :: core_entry integer, intent(in) :: i_core type(string_t), intent(in) :: libname type(model_data_t), intent(in), target :: model type(var_list_t), intent(in) :: var_list end subroutine pcm_default_prepare_any_external_code <>= module subroutine pcm_default_prepare_any_external_code & (pcm, core_entry, i_core, libname, model, var_list) class(pcm_default_t), intent(in) :: pcm type(core_entry_t), intent(inout) :: core_entry integer, intent(in) :: i_core type(string_t), intent(in) :: libname type(model_data_t), intent(in), target :: model type(var_list_t), intent(in) :: var_list if (core_entry%active) then associate (core => core_entry%core) if (core%needs_external_code ()) then call core%prepare_external_code & (core%data%flv_state, & var_list, pcm%os_data, libname, model, i_core, .false.) end if call core%set_equivalent_flv_hel_indices () end associate end if end subroutine pcm_default_prepare_any_external_code @ %def pcm_default_prepare_any_external_code @ Allocate and configure the BLHA record for a specific core, assuming that the core type requires it. In the default case, this is a Born configuration. <>= procedure :: setup_blha => pcm_default_setup_blha <>= module subroutine pcm_default_setup_blha (pcm, core_entry) class(pcm_default_t), intent(in) :: pcm type(core_entry_t), intent(inout) :: core_entry end subroutine pcm_default_setup_blha <>= module subroutine pcm_default_setup_blha (pcm, core_entry) class(pcm_default_t), intent(in) :: pcm type(core_entry_t), intent(inout) :: core_entry allocate (core_entry%blha_config, source = pcm%blha_defaults) call core_entry%blha_config%set_born () end subroutine pcm_default_setup_blha @ %def pcm_default_setup_blha @ Apply the configuration, using [[pcm]] data. <>= procedure :: prepare_blha_core => pcm_default_prepare_blha_core <>= module subroutine pcm_default_prepare_blha_core (pcm, core_entry, model) class(pcm_default_t), intent(in) :: pcm type(core_entry_t), intent(inout) :: core_entry class(model_data_t), intent(in), target :: model end subroutine pcm_default_prepare_blha_core <>= module subroutine pcm_default_prepare_blha_core (pcm, core_entry, model) class(pcm_default_t), intent(in) :: pcm type(core_entry_t), intent(inout) :: core_entry class(model_data_t), intent(in), target :: model integer :: n_in integer :: n_legs integer :: n_flv integer :: n_hel select type (core => core_entry%core) class is (prc_blha_t) associate (blha_config => core_entry%blha_config) n_in = core%data%n_in n_legs = core%data%get_n_tot () n_flv = core%data%n_flv n_hel = blha_config%get_n_hel (core%data%flv_state (1:n_in,1), model) call core%init_blha (blha_config, n_in, n_legs, n_flv, n_hel) call core%init_driver (pcm%os_data) end associate end select end subroutine pcm_default_prepare_blha_core @ %def pcm_default_prepare_blha_core @ Read the method settings from the variable list and store them in the BLHA master. This version: no NLO flag. <>= procedure :: set_blha_methods => pcm_default_set_blha_methods <>= module subroutine pcm_default_set_blha_methods (pcm, blha_master, var_list) class(pcm_default_t), intent(inout) :: pcm type(blha_master_t), intent(inout) :: blha_master type(var_list_t), intent(in) :: var_list end subroutine pcm_default_set_blha_methods <>= module subroutine pcm_default_set_blha_methods (pcm, blha_master, var_list) class(pcm_default_t), intent(inout) :: pcm type(blha_master_t), intent(inout) :: blha_master type(var_list_t), intent(in) :: var_list call blha_master%set_methods (.false., var_list) end subroutine pcm_default_set_blha_methods @ %def pcm_default_set_blha_methods @ Produce the LO and NLO flavor-state tables (as far as available), as appropriate for BLHA configuration. The default version looks at the first process core only, to get the Born data. (Multiple cores are thus unsupported.) The NLO flavor table is left unallocated. <>= procedure :: get_blha_flv_states => pcm_default_get_blha_flv_states <>= module subroutine pcm_default_get_blha_flv_states & (pcm, core_entry, flv_born, flv_real) class(pcm_default_t), intent(in) :: pcm type(core_entry_t), dimension(:), intent(in) :: core_entry integer, dimension(:,:), allocatable, intent(out) :: flv_born integer, dimension(:,:), allocatable, intent(out) :: flv_real end subroutine pcm_default_get_blha_flv_states <>= module subroutine pcm_default_get_blha_flv_states & (pcm, core_entry, flv_born, flv_real) class(pcm_default_t), intent(in) :: pcm type(core_entry_t), dimension(:), intent(in) :: core_entry integer, dimension(:,:), allocatable, intent(out) :: flv_born integer, dimension(:,:), allocatable, intent(out) :: flv_real flv_born = core_entry(1)%core%data%flv_state end subroutine pcm_default_get_blha_flv_states @ %def pcm_default_get_blha_flv_states @ Allocate and configure the MCI (multi-channel integrator) records. There is one record per active process component. Second procedure: call the MCI dispatcher with default-setup arguments. <>= procedure :: setup_mci => pcm_default_setup_mci procedure :: call_dispatch_mci => pcm_default_call_dispatch_mci <>= module subroutine pcm_default_setup_mci (pcm, mci_entry) class(pcm_default_t), intent(inout) :: pcm type(process_mci_entry_t), & dimension(:), allocatable, intent(out) :: mci_entry end subroutine pcm_default_setup_mci module subroutine pcm_default_call_dispatch_mci (pcm, & dispatch_mci, var_list, process_id, mci_template) class(pcm_default_t), intent(inout) :: pcm procedure(dispatch_mci_proc) :: dispatch_mci type(var_list_t), intent(in) :: var_list type(string_t), intent(in) :: process_id class(mci_t), allocatable, intent(out) :: mci_template end subroutine pcm_default_call_dispatch_mci <>= module subroutine pcm_default_setup_mci (pcm, mci_entry) class(pcm_default_t), intent(inout) :: pcm type(process_mci_entry_t), & dimension(:), allocatable, intent(out) :: mci_entry class(mci_t), allocatable :: mci_template integer :: i, i_mci pcm%n_mci = count (pcm%component_active) allocate (pcm%i_mci (pcm%n_components), source = 0) i_mci = 0 do i = 1, pcm%n_components if (pcm%component_active(i)) then i_mci = i_mci + 1 pcm%i_mci(i) = i_mci end if end do allocate (mci_entry (pcm%n_mci)) end subroutine pcm_default_setup_mci module subroutine pcm_default_call_dispatch_mci (pcm, & dispatch_mci, var_list, process_id, mci_template) class(pcm_default_t), intent(inout) :: pcm procedure(dispatch_mci_proc) :: dispatch_mci type(var_list_t), intent(in) :: var_list type(string_t), intent(in) :: process_id class(mci_t), allocatable, intent(out) :: mci_template call dispatch_mci (mci_template, var_list, process_id) end subroutine pcm_default_call_dispatch_mci @ %def pcm_default_setup_mci @ %def pcm_default_call_dispatch_mci @ Nothing left to do for the default algorithm. <>= procedure :: complete_setup => pcm_default_complete_setup <>= module subroutine pcm_default_complete_setup & (pcm, core_entry, component, model) class(pcm_default_t), intent(inout) :: pcm type(core_entry_t), dimension(:), intent(in) :: core_entry type(process_component_t), dimension(:), intent(inout) :: component type(model_t), intent(in), target :: model end subroutine pcm_default_complete_setup <>= module subroutine pcm_default_complete_setup & (pcm, core_entry, component, model) class(pcm_default_t), intent(inout) :: pcm type(core_entry_t), dimension(:), intent(in) :: core_entry type(process_component_t), dimension(:), intent(inout) :: component type(model_t), intent(in), target :: model end subroutine pcm_default_complete_setup @ %def pcm_default_complete_setup @ \subsubsection{Component management} Initialize a single component. We require all process-configuration blocks, and specific templates for the phase-space and integrator configuration. We also provide the current component index [[i]] and the [[active]] flag. In the default mode, all components are marked as master components. <>= procedure :: init_component => pcm_default_init_component <>= module subroutine pcm_default_init_component (pcm, component, i, active, & phs_config, env, meta, config) class(pcm_default_t), intent(in) :: pcm type(process_component_t), intent(out) :: component integer, intent(in) :: i logical, intent(in) :: active class(phs_config_t), allocatable, intent(in) :: phs_config type(process_environment_t), intent(in) :: env type(process_metadata_t), intent(in) :: meta type(process_config_data_t), intent(in) :: config end subroutine pcm_default_init_component <>= module subroutine pcm_default_init_component (pcm, component, i, active, & phs_config, env, meta, config) class(pcm_default_t), intent(in) :: pcm type(process_component_t), intent(out) :: component integer, intent(in) :: i logical, intent(in) :: active class(phs_config_t), allocatable, intent(in) :: phs_config type(process_environment_t), intent(in) :: env type(process_metadata_t), intent(in) :: meta type(process_config_data_t), intent(in) :: config call component%init (i, & env, meta, config, & active, & phs_config) component%component_type = COMP_MASTER end subroutine pcm_default_init_component @ %def pcm_default_init_component @ \subsection{NLO process component manager} The NLO-aware version of the process-component manager. This is the configuration object, which has the duty of allocating the corresponding instance. This is the nontrivial NLO version. <>= public :: pcm_nlo_t <>= type, extends (pcm_t) :: pcm_nlo_t type(string_t) :: id logical :: combined_integration = .false. logical :: vis_fks_regions = .false. integer, dimension(:), allocatable :: nlo_type integer, dimension(:), allocatable :: nlo_type_core integer, dimension(:), allocatable :: component_type integer :: i_born = 0 integer :: i_real = 0 integer :: i_sub = 0 type(nlo_settings_t) :: settings type(region_data_t) :: region_data logical :: use_real_partition = .false. logical :: use_real_singular = .false. real(default) :: real_partition_scale = 0 class(real_partition_t), allocatable :: real_partition type(dalitz_plot_t) :: dalitz_plot type(quantum_numbers_t), dimension(:,:), allocatable :: qn_real, qn_born contains <> end type pcm_nlo_t @ %def pcm_nlo_t @ Initialize configuration data, using environment variables. <>= procedure :: init => pcm_nlo_init <>= module subroutine pcm_nlo_init (pcm, env, meta) class(pcm_nlo_t), intent(out) :: pcm type(process_metadata_t), intent(in) :: meta type(process_environment_t), intent(in) :: env end subroutine pcm_nlo_init <>= module subroutine pcm_nlo_init (pcm, env, meta) class(pcm_nlo_t), intent(out) :: pcm type(process_metadata_t), intent(in) :: meta type(process_environment_t), intent(in) :: env type(var_list_t), pointer :: var_list type(fks_template_t) :: fks_template pcm%id = meta%id pcm%has_pdfs = env%has_pdfs () var_list => env%get_var_list_ptr () call dispatch_fks_setup (fks_template, var_list) call pcm%settings%init (var_list, fks_template) pcm%combined_integration = & var_list%get_lval (var_str ('?combined_nlo_integration')) select case (char (var_list%get_sval (var_str ("$real_partition_mode")))) case ("default", "off") pcm%use_real_partition = .false. pcm%use_real_singular = .false. case ("all", "on", "singular") pcm%use_real_partition = .true. pcm%use_real_singular = .true. case ("finite") pcm%use_real_partition = .true. pcm%use_real_singular = .false. case default call msg_fatal ("The real partition mode can only be " // & "default, off, all, on, singular or finite.") end select pcm%real_partition_scale = & var_list%get_rval (var_str ("real_partition_scale")) pcm%vis_fks_regions = & var_list%get_lval (var_str ("?vis_fks_regions")) call pcm%set_blha_defaults & (env%has_polarized_beams (), env%get_var_list_ptr ()) pcm%os_data = env%get_os_data () end subroutine pcm_nlo_init @ %def pcm_nlo_init @ Init/rewrite NLO settings without the FKS template. <>= procedure :: init_nlo_settings => pcm_nlo_init_nlo_settings <>= module subroutine pcm_nlo_init_nlo_settings (pcm, var_list) class(pcm_nlo_t), intent(inout) :: pcm type(var_list_t), intent(in), target :: var_list end subroutine pcm_nlo_init_nlo_settings <>= module subroutine pcm_nlo_init_nlo_settings (pcm, var_list) class(pcm_nlo_t), intent(inout) :: pcm type(var_list_t), intent(in), target :: var_list call pcm%settings%init (var_list) end subroutine pcm_nlo_init_nlo_settings @ %def pcm_nlo_init_nlo_settings @ As appropriate for the NLO/FKS algorithm, the category defined by the process, is called [[nlo_type]]. We refine this by setting the component category [[component_type]] separately. The component types [[COMP_MISMATCH]], [[COMP_PDF]], [[COMP_SUB]] are set only if the algorithm uses combined integration. Otherwise, they are set to [[COMP_DEFAULT]]. The component type [[COMP_REAL]] is further distinguished between [[COMP_REAL_SING]] or [[COMP_REAL_FIN]], if the algorithm uses real partitions. The former acts as a reference component for the latter, and we always assume that it is the first real component. Each component is assigned its own core. Exceptions: the finite-real component gets the same core as the singular-real component. The mismatch component gets the same core as the subtraction component. TODO wk 2018: this convention for real components can be improved. Check whether all component types should be assigned, not just for combined integration. <>= procedure :: categorize_components => pcm_nlo_categorize_components <>= module subroutine pcm_nlo_categorize_components (pcm, config) class(pcm_nlo_t), intent(inout) :: pcm type(process_config_data_t), intent(in) :: config end subroutine pcm_nlo_categorize_components <>= module subroutine pcm_nlo_categorize_components (pcm, config) class(pcm_nlo_t), intent(inout) :: pcm type(process_config_data_t), intent(in) :: config type(process_component_def_t), pointer :: component_def integer :: i allocate (pcm%nlo_type (pcm%n_components), source = COMPONENT_UNDEFINED) allocate (pcm%component_type (pcm%n_components), source = COMP_DEFAULT) do i = 1, pcm%n_components component_def => config%process_def%get_component_def_ptr (i) pcm%nlo_type(i) = component_def%get_nlo_type () if (pcm%combined_integration) then select case (pcm%nlo_type(i)) case (BORN) pcm%i_born = i pcm%component_type(i) = COMP_MASTER case (NLO_REAL) pcm%component_type(i) = COMP_REAL case (NLO_VIRTUAL) pcm%component_type(i) = COMP_VIRT case (NLO_MISMATCH) pcm%component_type(i) = COMP_MISMATCH case (NLO_DGLAP) pcm%component_type(i) = COMP_PDF case (NLO_SUBTRACTION) pcm%component_type(i) = COMP_SUB pcm%i_sub = i end select else select case (pcm%nlo_type(i)) case (BORN) pcm%i_born = i pcm%component_type(i) = COMP_MASTER case (NLO_REAL) pcm%component_type(i) = COMP_REAL case (NLO_VIRTUAL) pcm%component_type(i) = COMP_VIRT case (NLO_MISMATCH) pcm%component_type(i) = COMP_MISMATCH case (NLO_SUBTRACTION) pcm%i_sub = i end select end if end do call refine_real_type ( & pack ([(i, i=1, pcm%n_components)], & pcm%component_type==COMP_REAL)) contains subroutine refine_real_type (i_real) integer, dimension(:), intent(in) :: i_real pcm%i_real = i_real(1) if (pcm%use_real_partition) then pcm%component_type (i_real(1)) = COMP_REAL_SING pcm%component_type (i_real(2:)) = COMP_REAL_FIN end if end subroutine refine_real_type end subroutine pcm_nlo_categorize_components @ %def pcm_nlo_categorize_components @ \subsubsection{Phase-space initial configuration} Setup for the NLO/PHS processes: two phase-space configurations, (1) Born/wood, (2) real correction/FKS. All components use either one of these two configurations. TODO wk 2018: The [[first_real_component]] identifier is really ugly. Nothing should rely on the ordering. <>= procedure :: init_phs_config => pcm_nlo_init_phs_config <>= module subroutine pcm_nlo_init_phs_config & (pcm, phs_entry, meta, env, phs_par, mapping_defs) class(pcm_nlo_t), intent(inout) :: pcm type(process_phs_config_t), & dimension(:), allocatable, intent(out) :: phs_entry type(process_metadata_t), intent(in) :: meta type(process_environment_t), intent(in) :: env type(mapping_defaults_t), intent(in) :: mapping_defs type(phs_parameters_t), intent(in) :: phs_par end subroutine pcm_nlo_init_phs_config <>= module subroutine pcm_nlo_init_phs_config & (pcm, phs_entry, meta, env, phs_par, mapping_defs) class(pcm_nlo_t), intent(inout) :: pcm type(process_phs_config_t), & dimension(:), allocatable, intent(out) :: phs_entry type(process_metadata_t), intent(in) :: meta type(process_environment_t), intent(in) :: env type(mapping_defaults_t), intent(in) :: mapping_defs type(phs_parameters_t), intent(in) :: phs_par integer :: i logical :: first_real_component allocate (phs_entry (2)) call dispatch_phs (phs_entry(1)%phs_config, & env%get_var_list_ptr (), & env%get_os_data (), & meta%id, & mapping_defs, phs_par, & var_str ("wood")) call dispatch_phs (phs_entry(2)%phs_config, & env%get_var_list_ptr (), & env%get_os_data (), & meta%id, & mapping_defs, phs_par, & var_str ("fks")) allocate (pcm%i_phs_config (pcm%n_components), source=0) first_real_component = .true. do i = 1, pcm%n_components select case (pcm%nlo_type(i)) case (BORN, NLO_VIRTUAL, NLO_SUBTRACTION) pcm%i_phs_config(i) = 1 case (NLO_REAL) if (pcm%use_real_partition) then if (pcm%use_real_singular) then if (first_real_component) then pcm%i_phs_config(i) = 2 first_real_component = .false. else pcm%i_phs_config(i) = 1 end if else pcm%i_phs_config(i) = 1 end if else pcm%i_phs_config(i) = 2 end if case (NLO_MISMATCH, NLO_DGLAP, GKS) pcm%i_phs_config(i) = 2 end select end do end subroutine pcm_nlo_init_phs_config @ %def pcm_nlo_init_phs_config @ \subsubsection{Core management} Allocate the core (matrix-element interface) objects that we will need for evaluation. Every component gets an associated core, except for the real-finite and mismatch components (if any). Those components are associated with their previous corresponding real-singular and subtraction cores, respectively. After cores are allocated, configure the region-data block that is maintained by the NLO process-component manager. <>= procedure :: allocate_cores => pcm_nlo_allocate_cores <>= module subroutine pcm_nlo_allocate_cores (pcm, config, core_entry) class(pcm_nlo_t), intent(inout) :: pcm type(process_config_data_t), intent(in) :: config type(core_entry_t), dimension(:), allocatable, intent(out) :: core_entry end subroutine pcm_nlo_allocate_cores <>= module subroutine pcm_nlo_allocate_cores (pcm, config, core_entry) class(pcm_nlo_t), intent(inout) :: pcm type(process_config_data_t), intent(in) :: config type(core_entry_t), dimension(:), allocatable, intent(out) :: core_entry type(process_component_def_t), pointer :: component_def integer :: i, i_core allocate (pcm%i_core (pcm%n_components), source = 0) pcm%n_cores = pcm%n_components & - count (pcm%component_type(:) == COMP_REAL_FIN) & - count (pcm%component_type(:) == COMP_MISMATCH) allocate (core_entry (pcm%n_cores)) allocate (pcm%nlo_type_core (pcm%n_cores), source = BORN) i_core = 0 do i = 1, pcm%n_components select case (pcm%component_type(i)) case default i_core = i_core + 1 pcm%i_core(i) = i_core pcm%nlo_type_core(i_core) = pcm%nlo_type(i) core_entry(i_core)%i_component = i component_def => config%process_def%get_component_def_ptr (i) core_entry(i_core)%core_def => component_def%get_core_def_ptr () select case (pcm%nlo_type(i)) case default core_entry(i)%active = component_def%can_be_integrated () case (NLO_REAL, NLO_SUBTRACTION) core_entry(i)%active = .true. end select case (COMP_REAL_FIN) pcm%i_core(i) = pcm%i_core(pcm%i_real) case (COMP_MISMATCH) pcm%i_core(i) = pcm%i_core(pcm%i_sub) end select end do end subroutine pcm_nlo_allocate_cores @ %def pcm_nlo_allocate_cores @ Extra code is required for certain core types (threshold) or if BLHA uses an external OLP for getting its matrix elements. OMega matrix elements, by definition, do not need extra code. NLO-virtual or subtraction matrix elements always need extra code. More precisely: for the Born and virtual matrix element, the extra code is accessed only if the component is active. The radiation (real) and the subtraction corrections (singular and finite), extra code is accessed in any case. The flavor state is taken from the [[region_data]] table in the [[pcm]] record. We use the Born and real flavor-state tables as appropriate. <>= procedure :: prepare_any_external_code => & pcm_nlo_prepare_any_external_code <>= module subroutine pcm_nlo_prepare_any_external_code & (pcm, core_entry, i_core, libname, model, var_list) class(pcm_nlo_t), intent(in) :: pcm type(core_entry_t), intent(inout) :: core_entry integer, intent(in) :: i_core type(string_t), intent(in) :: libname type(model_data_t), intent(in), target :: model type(var_list_t), intent(in) :: var_list end subroutine pcm_nlo_prepare_any_external_code <>= module subroutine pcm_nlo_prepare_any_external_code & (pcm, core_entry, i_core, libname, model, var_list) class(pcm_nlo_t), intent(in) :: pcm type(core_entry_t), intent(inout) :: core_entry integer, intent(in) :: i_core type(string_t), intent(in) :: libname type(model_data_t), intent(in), target :: model type(var_list_t), intent(in) :: var_list integer, dimension(:,:), allocatable :: flv_born, flv_real integer :: i call pcm%region_data%get_all_flv_states (flv_born, flv_real) if (core_entry%active) then associate (core => core_entry%core) if (core%needs_external_code ()) then select case (pcm%nlo_type (core_entry%i_component)) case default call core%data%set_flv_state (flv_born) case (NLO_REAL) call core%data%set_flv_state (flv_real) end select call core%prepare_external_code & (core%data%flv_state, & var_list, pcm%os_data, libname, model, i_core, .true.) end if call core%set_equivalent_flv_hel_indices () end associate end if end subroutine pcm_nlo_prepare_any_external_code @ %def pcm_nlo_prepare_any_external_code @ Allocate and configure the BLHA record for a specific core, assuming that the core type requires it. The configuration depends on the NLO type of the core. <>= procedure :: setup_blha => pcm_nlo_setup_blha <>= module subroutine pcm_nlo_setup_blha (pcm, core_entry) class(pcm_nlo_t), intent(in) :: pcm type(core_entry_t), intent(inout) :: core_entry end subroutine pcm_nlo_setup_blha <>= module subroutine pcm_nlo_setup_blha (pcm, core_entry) class(pcm_nlo_t), intent(in) :: pcm type(core_entry_t), intent(inout) :: core_entry allocate (core_entry%blha_config, source = pcm%blha_defaults) select case (pcm%nlo_type(core_entry%i_component)) case (BORN) call core_entry%blha_config%set_born () case (NLO_REAL) call core_entry%blha_config%set_real_trees () case (NLO_VIRTUAL) call core_entry%blha_config%set_loop () case (NLO_SUBTRACTION) call core_entry%blha_config%set_subtraction () call core_entry%blha_config%set_internal_color_correlations () case (NLO_DGLAP) call core_entry%blha_config%set_dglap () end select end subroutine pcm_nlo_setup_blha @ %def pcm_nlo_setup_blha @ After phase-space configuration data and core entries are available, we fill tables and compute the remaining NLO data that will steer the integration and subtraction algorithm. There are three parts: recognize a threshold-type process core (if it exists), prepare the region-data tables (always), and prepare for real partitioning (if requested). The real-component phase space acts as the source for resonance-history information, required for the region data. <>= procedure :: complete_setup => pcm_nlo_complete_setup <>= module subroutine pcm_nlo_complete_setup (pcm, core_entry, component, model) class(pcm_nlo_t), intent(inout) :: pcm type(core_entry_t), dimension(:), intent(in) :: core_entry type(process_component_t), dimension(:), intent(inout) :: component type(model_t), intent(in), target :: model end subroutine pcm_nlo_complete_setup <>= module subroutine pcm_nlo_complete_setup (pcm, core_entry, component, model) class(pcm_nlo_t), intent(inout) :: pcm type(core_entry_t), dimension(:), intent(in) :: core_entry type(process_component_t), dimension(:), intent(inout) :: component type(model_t), intent(in), target :: model integer :: alpha_power, alphas_power call pcm%handle_threshold_core (core_entry) call component(1)%config%get_coupling_powers (alpha_power, alphas_power) call pcm%setup_region_data (core_entry, & component(pcm%i_real)%phs_config, model, alpha_power, alphas_power) call pcm%setup_real_partition () end subroutine pcm_nlo_complete_setup @ %def pcm_nlo_complete_setup @ Apply the BLHA configuration to a core object, using the region data from [[pcm]] for determining the particle content. <>= procedure :: prepare_blha_core => pcm_nlo_prepare_blha_core <>= module subroutine pcm_nlo_prepare_blha_core (pcm, core_entry, model) class(pcm_nlo_t), intent(in) :: pcm type(core_entry_t), intent(inout) :: core_entry class(model_data_t), intent(in), target :: model end subroutine pcm_nlo_prepare_blha_core <>= module subroutine pcm_nlo_prepare_blha_core (pcm, core_entry, model) class(pcm_nlo_t), intent(in) :: pcm type(core_entry_t), intent(inout) :: core_entry class(model_data_t), intent(in), target :: model integer :: n_in integer :: n_legs integer :: n_flv integer :: n_hel select type (core => core_entry%core) class is (prc_blha_t) associate (blha_config => core_entry%blha_config) n_in = core%data%n_in select case (pcm%nlo_type(core_entry%i_component)) case (NLO_REAL) n_legs = pcm%region_data%get_n_legs_real () n_flv = pcm%region_data%get_n_flv_real () case default n_legs = pcm%region_data%get_n_legs_born () n_flv = pcm%region_data%get_n_flv_born () end select n_hel = blha_config%get_n_hel (core%data%flv_state (1:n_in,1), model) call core%init_blha (blha_config, n_in, n_legs, n_flv, n_hel) call core%init_driver (pcm%os_data) end associate end select end subroutine pcm_nlo_prepare_blha_core @ %def pcm_nlo_prepare_blha_core @ Read the method settings from the variable list and store them in the BLHA master. This version: NLO flag set. <>= procedure :: set_blha_methods => pcm_nlo_set_blha_methods <>= module subroutine pcm_nlo_set_blha_methods (pcm, blha_master, var_list) class(pcm_nlo_t), intent(inout) :: pcm type(blha_master_t), intent(inout) :: blha_master type(var_list_t), intent(in) :: var_list end subroutine pcm_nlo_set_blha_methods <>= module subroutine pcm_nlo_set_blha_methods (pcm, blha_master, var_list) class(pcm_nlo_t), intent(inout) :: pcm type(blha_master_t), intent(inout) :: blha_master type(var_list_t), intent(in) :: var_list call blha_master%set_methods (.true., var_list) call pcm%blha_defaults%set_loop_method (blha_master) end subroutine pcm_nlo_set_blha_methods @ %def pcm_nlo_set_blha_methods @ Produce the LO and NLO flavor-state tables (as far as available), as appropriate for BLHA configuration. The NLO version copies the tables from the region data inside [[pcm]]. The core array is not needed. <>= procedure :: get_blha_flv_states => pcm_nlo_get_blha_flv_states <>= module subroutine pcm_nlo_get_blha_flv_states & (pcm, core_entry, flv_born, flv_real) class(pcm_nlo_t), intent(in) :: pcm type(core_entry_t), dimension(:), intent(in) :: core_entry integer, dimension(:,:), allocatable, intent(out) :: flv_born integer, dimension(:,:), allocatable, intent(out) :: flv_real end subroutine pcm_nlo_get_blha_flv_states <>= module subroutine pcm_nlo_get_blha_flv_states & (pcm, core_entry, flv_born, flv_real) class(pcm_nlo_t), intent(in) :: pcm type(core_entry_t), dimension(:), intent(in) :: core_entry integer, dimension(:,:), allocatable, intent(out) :: flv_born integer, dimension(:,:), allocatable, intent(out) :: flv_real call pcm%region_data%get_all_flv_states (flv_born, flv_real) end subroutine pcm_nlo_get_blha_flv_states @ %def pcm_nlo_get_blha_flv_states @ Allocate and configure the MCI (multi-channel integrator) records. The relation depends on the [[combined_integration]] setting. If we integrate components separately, each component gets its own record, except for the subtraction component. If we do the combination, there is one record for the master (Born) component and a second one for the real-finite component, if present. Each entry acquires some NLO-specific initialization. Generic configuration follows later. Second procedure: call the MCI dispatcher with NLO-setup arguments. <>= procedure :: setup_mci => pcm_nlo_setup_mci procedure :: call_dispatch_mci => pcm_nlo_call_dispatch_mci <>= module subroutine pcm_nlo_setup_mci (pcm, mci_entry) class(pcm_nlo_t), intent(inout) :: pcm type(process_mci_entry_t), & dimension(:), allocatable, intent(out) :: mci_entry end subroutine pcm_nlo_setup_mci module subroutine pcm_nlo_call_dispatch_mci (pcm, & dispatch_mci, var_list, process_id, mci_template) class(pcm_nlo_t), intent(inout) :: pcm procedure(dispatch_mci_proc) :: dispatch_mci type(var_list_t), intent(in) :: var_list type(string_t), intent(in) :: process_id class(mci_t), allocatable, intent(out) :: mci_template end subroutine pcm_nlo_call_dispatch_mci <>= module subroutine pcm_nlo_setup_mci (pcm, mci_entry) class(pcm_nlo_t), intent(inout) :: pcm type(process_mci_entry_t), & dimension(:), allocatable, intent(out) :: mci_entry class(mci_t), allocatable :: mci_template integer :: i, i_mci if (pcm%combined_integration) then pcm%n_mci = 1 & + count (pcm%component_active(:) & & .and. pcm%component_type(:) == COMP_REAL_FIN) allocate (pcm%i_mci (pcm%n_components), source = 0) do i = 1, pcm%n_components if (pcm%component_active(i)) then select case (pcm%component_type(i)) case (COMP_MASTER) pcm%i_mci(i) = 1 case (COMP_REAL_FIN) pcm%i_mci(i) = 2 end select end if end do else pcm%n_mci = count (pcm%component_active(:) & & .and. pcm%nlo_type(:) /= NLO_SUBTRACTION) allocate (pcm%i_mci (pcm%n_components), source = 0) i_mci = 0 do i = 1, pcm%n_components if (pcm%component_active(i)) then select case (pcm%nlo_type(i)) case default i_mci = i_mci + 1 pcm%i_mci(i) = i_mci case (NLO_SUBTRACTION) end select end if end do end if allocate (mci_entry (pcm%n_mci)) mci_entry(:)%combined_integration = pcm%combined_integration if (pcm%use_real_partition) then do i = 1, pcm%n_components i_mci = pcm%i_mci(i) if (i_mci > 0) then select case (pcm%component_type(i)) case (COMP_REAL_FIN) mci_entry(i_mci)%real_partition_type = REAL_FINITE case default mci_entry(i_mci)%real_partition_type = REAL_SINGULAR end select end if end do end if end subroutine pcm_nlo_setup_mci module subroutine pcm_nlo_call_dispatch_mci (pcm, & dispatch_mci, var_list, process_id, mci_template) class(pcm_nlo_t), intent(inout) :: pcm procedure(dispatch_mci_proc) :: dispatch_mci type(var_list_t), intent(in) :: var_list type(string_t), intent(in) :: process_id class(mci_t), allocatable, intent(out) :: mci_template call dispatch_mci (mci_template, var_list, process_id, is_nlo = .true.) end subroutine pcm_nlo_call_dispatch_mci @ %def pcm_nlo_setup_mci @ %def pcm_nlo_call_dispatch_mci @ Check for a threshold core and adjust the configuration accordingly, before singular region data are considered. <>= procedure :: handle_threshold_core => pcm_nlo_handle_threshold_core <>= module subroutine pcm_nlo_handle_threshold_core (pcm, core_entry) class(pcm_nlo_t), intent(inout) :: pcm type(core_entry_t), dimension(:), intent(in) :: core_entry end subroutine pcm_nlo_handle_threshold_core <>= module subroutine pcm_nlo_handle_threshold_core (pcm, core_entry) class(pcm_nlo_t), intent(inout) :: pcm type(core_entry_t), dimension(:), intent(in) :: core_entry integer :: i do i = 1, size (core_entry) select type (core => core_entry(i)%core_def) type is (threshold_def_t) pcm%settings%factorization_mode = FACTORIZATION_THRESHOLD return end select end do end subroutine pcm_nlo_handle_threshold_core @ %def pcm_nlo_handle_threshold_core @ Configure the singular-region tables based on the process data for the Born and Real (singular) cores, using also the appropriate FKS phase-space configuration object. In passing, we may create a table of resonance histories that are relevant for the singular-region configuration. TODO wk 2018: check whether [[phs_entry]] needs to be intent(inout). <>= procedure :: setup_region_data => pcm_nlo_setup_region_data <>= module subroutine pcm_nlo_setup_region_data & (pcm, core_entry, phs_config, model, alpha_power, alphas_power) class(pcm_nlo_t), intent(inout) :: pcm type(core_entry_t), dimension(:), intent(in) :: core_entry class(phs_config_t), intent(inout) :: phs_config type(model_t), intent(in), target :: model integer, intent(in) :: alpha_power, alphas_power end subroutine pcm_nlo_setup_region_data <>= module subroutine pcm_nlo_setup_region_data & (pcm, core_entry, phs_config, model, alpha_power, alphas_power) class(pcm_nlo_t), intent(inout) :: pcm type(core_entry_t), dimension(:), intent(in) :: core_entry class(phs_config_t), intent(inout) :: phs_config type(model_t), intent(in), target :: model integer, intent(in) :: alpha_power, alphas_power type(process_constants_t) :: data_born, data_real integer, dimension (:,:), allocatable :: flavor_born, flavor_real type(resonance_history_t), dimension(:), allocatable :: resonance_histories type(var_list_t), pointer :: var_list logical :: success data_born = core_entry(pcm%i_core(pcm%i_born))%core%data data_real = core_entry(pcm%i_core(pcm%i_real))%core%data call data_born%get_flv_state (flavor_born) call data_real%get_flv_state (flavor_real) call pcm%region_data%init & (data_born%n_in, model, flavor_born, flavor_real, & pcm%settings%nlo_correction_type, alpha_power, alphas_power) associate (template => pcm%settings%fks_template) if (template%mapping_type == FKS_RESONANCES) then select type (phs_config) type is (phs_fks_config_t) call get_filtered_resonance_histories (phs_config, & data_born%n_in, flavor_born, model, & template%excluded_resonances, & resonance_histories, success) end select if (.not. success) template%mapping_type = FKS_DEFAULT end if call pcm%region_data%setup_fks_mappings (template, data_born%n_in) !!! Check again, mapping_type might have changed if (template%mapping_type == FKS_RESONANCES) then call pcm%region_data%set_resonance_mappings (resonance_histories) call pcm%region_data%init_resonance_information () pcm%settings%use_resonance_mappings = .true. end if end associate if (pcm%settings%factorization_mode == FACTORIZATION_THRESHOLD) then call pcm%region_data%set_isr_pseudo_regions () call pcm%region_data%split_up_interference_regions_for_threshold () end if call pcm%region_data%compute_number_of_phase_spaces () call pcm%region_data%set_i_phs_to_i_con () call pcm%region_data%write_to_file & (pcm%id, pcm%vis_fks_regions, pcm%os_data) if (debug_active (D_SUBTRACTION)) & call pcm%region_data%check_consistency (.true.) end subroutine pcm_nlo_setup_region_data @ %def pcm_nlo_setup_region_data @ After region data are set up, we allocate and configure the [[real_partition]] objects, if requested. Gfortran 7/8/9 bug, has to remain in the main module: <>= procedure :: setup_real_partition => pcm_nlo_setup_real_partition <>= subroutine pcm_nlo_setup_real_partition (pcm) class(pcm_nlo_t), intent(inout) :: pcm if (pcm%use_real_partition) then if (.not. allocated (pcm%real_partition)) then allocate (real_partition_fixed_order_t :: pcm%real_partition) select type (partition => pcm%real_partition) type is (real_partition_fixed_order_t) call pcm%region_data%get_all_ftuples (partition%fks_pairs) partition%scale = pcm%real_partition_scale end select end if end if end subroutine pcm_nlo_setup_real_partition @ %def pcm_nlo_setup_real_partition @ Initialize a single component. We require all process-configuration blocks, and specific templates for the phase-space and integrator configuration. We also provide the current component index [[i]] and the [[active]] flag. For a subtraction component, the [[active]] flag is overridden. In the nlo mode, the component types have been determined before. TODO wk 2018: the component type need not be stored in the component; we may remove this when everything is controlled by [[pcm]]. <>= procedure :: init_component => pcm_nlo_init_component <>= module subroutine pcm_nlo_init_component (pcm, component, i, active, & phs_config, env, meta, config) class(pcm_nlo_t), intent(in) :: pcm type(process_component_t), intent(out) :: component integer, intent(in) :: i logical, intent(in) :: active class(phs_config_t), allocatable, intent(in) :: phs_config type(process_environment_t), intent(in) :: env type(process_metadata_t), intent(in) :: meta type(process_config_data_t), intent(in) :: config end subroutine pcm_nlo_init_component <>= module subroutine pcm_nlo_init_component (pcm, component, i, active, & phs_config, env, meta, config) class(pcm_nlo_t), intent(in) :: pcm type(process_component_t), intent(out) :: component integer, intent(in) :: i logical, intent(in) :: active class(phs_config_t), allocatable, intent(in) :: phs_config type(process_environment_t), intent(in) :: env type(process_metadata_t), intent(in) :: meta type(process_config_data_t), intent(in) :: config logical :: activate select case (pcm%nlo_type(i)) case default; activate = active case (NLO_SUBTRACTION); activate = .false. end select call component%init (i, & env, meta, config, & activate, & phs_config) component%component_type = pcm%component_type(i) end subroutine pcm_nlo_init_component @ %def pcm_nlo_init_component @ Override the base method: record the active components in the PCM object, and report inactive components (except for the subtraction component). <>= procedure :: record_inactive_components => pcm_nlo_record_inactive_components <>= module subroutine pcm_nlo_record_inactive_components (pcm, component, meta) class(pcm_nlo_t), intent(inout) :: pcm type(process_component_t), dimension(:), intent(in) :: component type(process_metadata_t), intent(inout) :: meta end subroutine pcm_nlo_record_inactive_components <>= module subroutine pcm_nlo_record_inactive_components (pcm, component, meta) class(pcm_nlo_t), intent(inout) :: pcm type(process_component_t), dimension(:), intent(in) :: component type(process_metadata_t), intent(inout) :: meta integer :: i pcm%component_active = component%active do i = 1, pcm%n_components select case (pcm%nlo_type(i)) case (NLO_SUBTRACTION) case default if (.not. component(i)%active) call meta%deactivate_component (i) end select end do end subroutine pcm_nlo_record_inactive_components @ %def pcm_nlo_record_inactive_components @ <>= procedure :: core_is_radiation => pcm_nlo_core_is_radiation <>= module function pcm_nlo_core_is_radiation (pcm, i_core) result (is_rad) logical :: is_rad class(pcm_nlo_t), intent(in) :: pcm integer, intent(in) :: i_core end function pcm_nlo_core_is_radiation <>= module function pcm_nlo_core_is_radiation (pcm, i_core) result (is_rad) logical :: is_rad class(pcm_nlo_t), intent(in) :: pcm integer, intent(in) :: i_core is_rad = pcm%nlo_type(i_core) == NLO_REAL ! .and. .not. pcm%cm%sub(i_core) end function pcm_nlo_core_is_radiation @ %def pcm_nlo_core_is_radiation @ <>= procedure :: get_n_flv_born => pcm_nlo_get_n_flv_born <>= module function pcm_nlo_get_n_flv_born (pcm_nlo) result (n_flv) integer :: n_flv class(pcm_nlo_t), intent(in) :: pcm_nlo end function pcm_nlo_get_n_flv_born <>= module function pcm_nlo_get_n_flv_born (pcm_nlo) result (n_flv) integer :: n_flv class(pcm_nlo_t), intent(in) :: pcm_nlo n_flv = pcm_nlo%region_data%n_flv_born end function pcm_nlo_get_n_flv_born @ %def pcm_nlo_get_n_flv_born @ <>= procedure :: get_n_flv_real => pcm_nlo_get_n_flv_real <>= module function pcm_nlo_get_n_flv_real (pcm_nlo) result (n_flv) integer :: n_flv class(pcm_nlo_t), intent(in) :: pcm_nlo end function pcm_nlo_get_n_flv_real <>= module function pcm_nlo_get_n_flv_real (pcm_nlo) result (n_flv) integer :: n_flv class(pcm_nlo_t), intent(in) :: pcm_nlo n_flv = pcm_nlo%region_data%n_flv_real end function pcm_nlo_get_n_flv_real @ %def pcm_nlo_get_n_flv_real @ <>= procedure :: get_n_alr => pcm_nlo_get_n_alr <>= module function pcm_nlo_get_n_alr (pcm) result (n_alr) integer :: n_alr class(pcm_nlo_t), intent(in) :: pcm end function pcm_nlo_get_n_alr <>= module function pcm_nlo_get_n_alr (pcm) result (n_alr) integer :: n_alr class(pcm_nlo_t), intent(in) :: pcm n_alr = pcm%region_data%n_regions end function pcm_nlo_get_n_alr @ %def pcm_nlo_get_n_alr @ <>= procedure :: get_flv_states => pcm_nlo_get_flv_states <>= module function pcm_nlo_get_flv_states (pcm, born) result (flv) integer, dimension(:,:), allocatable :: flv class(pcm_nlo_t), intent(in) :: pcm logical, intent(in) :: born end function pcm_nlo_get_flv_states <>= module function pcm_nlo_get_flv_states (pcm, born) result (flv) integer, dimension(:,:), allocatable :: flv class(pcm_nlo_t), intent(in) :: pcm logical, intent(in) :: born if (born) then flv = pcm%region_data%get_flv_states_born () else flv = pcm%region_data%get_flv_states_real () end if end function pcm_nlo_get_flv_states @ %def pcm_nlo_get_flv_states @ <>= procedure :: get_qn => pcm_nlo_get_qn <>= module function pcm_nlo_get_qn (pcm, born) result (qn) type(quantum_numbers_t), dimension(:,:), allocatable :: qn class(pcm_nlo_t), intent(in) :: pcm logical, intent(in) :: born end function pcm_nlo_get_qn <>= module function pcm_nlo_get_qn (pcm, born) result (qn) type(quantum_numbers_t), dimension(:,:), allocatable :: qn class(pcm_nlo_t), intent(in) :: pcm logical, intent(in) :: born if (born) then qn = pcm%qn_born else qn = pcm%qn_real end if end function pcm_nlo_get_qn @ %def pcm_nlo_get_qn @ Check if there are massive emitters. Since the mass-structure of all underlying Born configurations have to be the same (\textbf{This does not have to be the case when different components are generated at LO}) , we just use the first one to determine this. <>= procedure :: has_massive_emitter => pcm_nlo_has_massive_emitter <>= module function pcm_nlo_has_massive_emitter (pcm) result (val) logical :: val class(pcm_nlo_t), intent(in) :: pcm end function pcm_nlo_has_massive_emitter <>= module function pcm_nlo_has_massive_emitter (pcm) result (val) logical :: val class(pcm_nlo_t), intent(in) :: pcm integer :: i val = .false. associate (reg_data => pcm%region_data) do i = reg_data%n_in + 1, reg_data%n_legs_born if (any (i == reg_data%emitters)) & val = val .or. reg_data%flv_born(1)%massive(i) end do end associate end function pcm_nlo_has_massive_emitter @ %def pcm_nlo_has_massive_emitter @ Returns an array which specifies if the particle at position [[i]] is massive. <>= procedure :: get_mass_info => pcm_nlo_get_mass_info <>= module function pcm_nlo_get_mass_info (pcm, i_flv) result (massive) class(pcm_nlo_t), intent(in) :: pcm integer, intent(in) :: i_flv logical, dimension(:), allocatable :: massive end function pcm_nlo_get_mass_info <>= module function pcm_nlo_get_mass_info (pcm, i_flv) result (massive) class(pcm_nlo_t), intent(in) :: pcm integer, intent(in) :: i_flv logical, dimension(:), allocatable :: massive allocate (massive (size (pcm%region_data%flv_born(i_flv)%massive))) massive = pcm%region_data%flv_born(i_flv)%massive end function pcm_nlo_get_mass_info @ %def pcm_nlo_get_mass_info @ Gfortran 7/8/9 bug, has to remain in the main module: <>= procedure :: allocate_workspace => pcm_nlo_allocate_workspace <>= subroutine pcm_nlo_allocate_workspace (pcm, work) class(pcm_nlo_t), intent(in) :: pcm class(pcm_workspace_t), intent(inout), allocatable :: work allocate (pcm_nlo_workspace_t :: work) end subroutine pcm_nlo_allocate_workspace @ %def pcm_nlo_allocate_workspace @ <>= procedure :: init_qn => pcm_nlo_init_qn <>= module subroutine pcm_nlo_init_qn (pcm, model) class(pcm_nlo_t), intent(inout) :: pcm class(model_data_t), intent(in) :: model end subroutine pcm_nlo_init_qn <>= module subroutine pcm_nlo_init_qn (pcm, model) class(pcm_nlo_t), intent(inout) :: pcm class(model_data_t), intent(in) :: model integer, dimension(:,:), allocatable :: flv_states type(flavor_t), dimension(:), allocatable :: flv integer :: i type(quantum_numbers_t), dimension(:), allocatable :: qn allocate (flv_states (pcm%region_data%n_legs_born, & pcm%region_data%n_flv_born)) flv_states = pcm%get_flv_states (.true.) allocate (pcm%qn_born (size (flv_states, dim = 1), & size (flv_states, dim = 2))) allocate (flv (size (flv_states, dim = 1))) allocate (qn (size (flv_states, dim = 1))) do i = 1, pcm%get_n_flv_born () call flv%init (flv_states (:,i), model) call qn%init (flv) pcm%qn_born(:,i) = qn end do deallocate (flv); deallocate (qn) deallocate (flv_states) allocate (flv_states (pcm%region_data%n_legs_real, pcm%region_data%n_flv_real)) flv_states = pcm%get_flv_states (.false.) allocate (pcm%qn_real (size (flv_states, dim = 1), size (flv_states, dim = 2))) allocate (flv (size (flv_states, dim = 1))) allocate (qn (size (flv_states, dim = 1))) do i = 1, pcm%get_n_flv_real () call flv%init (flv_states (:,i), model) call qn%init (flv) pcm%qn_real(:,i) = qn end do end subroutine pcm_nlo_init_qn @ %def pcm_nlo_init_qn @ Gfortran 7/8/9 bug, has to remain in the main module: <>= procedure :: allocate_ps_matching => pcm_nlo_allocate_ps_matching <>= subroutine pcm_nlo_allocate_ps_matching (pcm) class(pcm_nlo_t), intent(inout) :: pcm if (.not. allocated (pcm%real_partition)) then allocate (powheg_damping_simple_t :: pcm%real_partition) end if end subroutine pcm_nlo_allocate_ps_matching @ %def pcm_nlo_allocate_ps_matching @ <>= procedure :: activate_dalitz_plot => pcm_nlo_activate_dalitz_plot <>= module subroutine pcm_nlo_activate_dalitz_plot (pcm, filename) class(pcm_nlo_t), intent(inout) :: pcm type(string_t), intent(in) :: filename end subroutine pcm_nlo_activate_dalitz_plot <>= module subroutine pcm_nlo_activate_dalitz_plot (pcm, filename) class(pcm_nlo_t), intent(inout) :: pcm type(string_t), intent(in) :: filename call pcm%dalitz_plot%init (free_unit (), filename, .false.) call pcm%dalitz_plot%write_header () end subroutine pcm_nlo_activate_dalitz_plot @ %def pcm_nlo_activate_dalitz_plot @ <>= procedure :: register_dalitz_plot => pcm_nlo_register_dalitz_plot <>= module subroutine pcm_nlo_register_dalitz_plot (pcm, emitter, p) class(pcm_nlo_t), intent(inout) :: pcm integer, intent(in) :: emitter type(vector4_t), intent(in), dimension(:) :: p end subroutine pcm_nlo_register_dalitz_plot <>= module subroutine pcm_nlo_register_dalitz_plot (pcm, emitter, p) class(pcm_nlo_t), intent(inout) :: pcm integer, intent(in) :: emitter type(vector4_t), intent(in), dimension(:) :: p real(default) :: k0_n, k0_np1 k0_n = p(emitter)%p(0) k0_np1 = p(size(p))%p(0) call pcm%dalitz_plot%register (k0_n, k0_np1) end subroutine pcm_nlo_register_dalitz_plot @ %def pcm_nlo_register_dalitz_plot @ <>= procedure :: setup_phs_generator => pcm_nlo_setup_phs_generator <>= module subroutine pcm_nlo_setup_phs_generator (pcm, pcm_work, generator, & sqrts, mode, singular_jacobian) class(pcm_nlo_t), intent(in) :: pcm type(phs_fks_generator_t), intent(inout) :: generator type(pcm_nlo_workspace_t), intent(in), target :: pcm_work real(default), intent(in) :: sqrts integer, intent(in), optional:: mode logical, intent(in), optional :: singular_jacobian end subroutine pcm_nlo_setup_phs_generator <>= module subroutine pcm_nlo_setup_phs_generator (pcm, pcm_work, generator, & sqrts, mode, singular_jacobian) class(pcm_nlo_t), intent(in) :: pcm type(phs_fks_generator_t), intent(inout) :: generator type(pcm_nlo_workspace_t), intent(in), target :: pcm_work real(default), intent(in) :: sqrts integer, intent(in), optional:: mode logical, intent(in), optional :: singular_jacobian logical :: yorn yorn = .false.; if (present (singular_jacobian)) yorn = singular_jacobian call generator%connect_kinematics (pcm_work%isr_kinematics, & pcm_work%real_kinematics, pcm%has_massive_emitter ()) generator%n_in = pcm%region_data%n_in call generator%set_sqrts_hat (sqrts) call generator%set_emitters (pcm%region_data%emitters) call generator%setup_masses (pcm%region_data%n_legs_born) generator%is_massive = pcm%get_mass_info (1) generator%singular_jacobian = yorn if (present (mode)) generator%mode = mode call generator%set_xi_and_y_bounds (pcm%settings%fks_template%xi_min, & pcm%settings%fks_template%y_max) end subroutine pcm_nlo_setup_phs_generator @ %def pcm_nlo_setup_phs_generator @ <>= procedure :: final => pcm_nlo_final <>= module subroutine pcm_nlo_final (pcm) class(pcm_nlo_t), intent(inout) :: pcm end subroutine pcm_nlo_final <>= module subroutine pcm_nlo_final (pcm) class(pcm_nlo_t), intent(inout) :: pcm if (allocated (pcm%real_partition)) deallocate (pcm%real_partition) call pcm%dalitz_plot%final () end subroutine pcm_nlo_final @ %def pcm_nlo_final @ <>= procedure :: is_nlo => pcm_nlo_is_nlo <>= module function pcm_nlo_is_nlo (pcm) result (is_nlo) logical :: is_nlo class(pcm_nlo_t), intent(in) :: pcm end function pcm_nlo_is_nlo <>= module function pcm_nlo_is_nlo (pcm) result (is_nlo) logical :: is_nlo class(pcm_nlo_t), intent(in) :: pcm is_nlo = .true. end function pcm_nlo_is_nlo @ %def pcm_nlo_is_nlo @ As a first implementation, it acts as a wrapper for the NLO controller object and the squared matrix-element collector. <>= public :: pcm_nlo_workspace_t <>= type, extends (pcm_workspace_t) :: pcm_nlo_workspace_t type(real_kinematics_t), pointer :: real_kinematics => null () type(isr_kinematics_t), pointer :: isr_kinematics => null () type(real_subtraction_t) :: real_sub type(virtual_t) :: virtual type(soft_mismatch_t) :: soft_mismatch type(dglap_remnant_t) :: dglap_remnant integer, dimension(:), allocatable :: i_mci_to_real_component contains <> end type pcm_nlo_workspace_t @ %def pcm_nlo_workspace_t @ <>= procedure :: set_radiation_event => pcm_nlo_workspace_set_radiation_event procedure :: set_subtraction_event => pcm_nlo_workspace_set_subtraction_event <>= module subroutine pcm_nlo_workspace_set_radiation_event (pcm_work) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work end subroutine pcm_nlo_workspace_set_radiation_event module subroutine pcm_nlo_workspace_set_subtraction_event (pcm_work) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work end subroutine pcm_nlo_workspace_set_subtraction_event <>= module subroutine pcm_nlo_workspace_set_radiation_event (pcm_work) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work pcm_work%real_sub%radiation_event = .true. pcm_work%real_sub%subtraction_event = .false. end subroutine pcm_nlo_workspace_set_radiation_event module subroutine pcm_nlo_workspace_set_subtraction_event (pcm_work) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work pcm_work%real_sub%radiation_event = .false. pcm_work%real_sub%subtraction_event = .true. end subroutine pcm_nlo_workspace_set_subtraction_event @ %def pcm_nlo_workspace_set_radiation_event @ %def pcm_nlo_workspace_set_subtraction_event <>= procedure :: disable_subtraction => pcm_nlo_workspace_disable_subtraction <>= module subroutine pcm_nlo_workspace_disable_subtraction (pcm_work) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work end subroutine pcm_nlo_workspace_disable_subtraction <>= module subroutine pcm_nlo_workspace_disable_subtraction (pcm_work) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work pcm_work%real_sub%subtraction_deactivated = .true. end subroutine pcm_nlo_workspace_disable_subtraction @ %def pcm_nlo_workspace_disable_subtraction @ <>= procedure :: init_config => pcm_nlo_workspace_init_config <>= module subroutine pcm_nlo_workspace_init_config (pcm_work, pcm, & active_components, nlo_types, energy, i_real_fin, model) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work class(pcm_t), intent(in) :: pcm logical, intent(in), dimension(:) :: active_components integer, intent(in), dimension(:) :: nlo_types real(default), intent(in), dimension(:) :: energy integer, intent(in) :: i_real_fin class(model_data_t), intent(in) :: model end subroutine pcm_nlo_workspace_init_config <>= module subroutine pcm_nlo_workspace_init_config (pcm_work, pcm, & active_components, nlo_types, energy, i_real_fin, model) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work class(pcm_t), intent(in) :: pcm logical, intent(in), dimension(:) :: active_components integer, intent(in), dimension(:) :: nlo_types real(default), intent(in), dimension(:) :: energy integer, intent(in) :: i_real_fin class(model_data_t), intent(in) :: model integer :: i_component if (debug_on) call msg_debug (D_PROCESS_INTEGRATION, & "pcm_nlo_workspace_init_config") call pcm_work%init_real_and_isr_kinematics (pcm, energy) select type (pcm) type is (pcm_nlo_t) do i_component = 1, size (active_components) if (active_components(i_component) .or. & pcm%settings%combined_integration) then select case (nlo_types(i_component)) case (NLO_REAL) if (i_component /= i_real_fin) then call pcm_work%setup_real_component (pcm, & pcm%settings%fks_template%subtraction_disabled) end if case (NLO_VIRTUAL) call pcm_work%init_virtual (pcm, model) case (NLO_MISMATCH) call pcm_work%init_soft_mismatch (pcm) case (NLO_DGLAP) call pcm_work%init_dglap_remnant (pcm) end select end if end do end select end subroutine pcm_nlo_workspace_init_config @ %def pcm_nlo_workspace_init_config @ <>= procedure :: setup_real_component => pcm_nlo_workspace_setup_real_component <>= module subroutine pcm_nlo_workspace_setup_real_component (pcm_work, pcm, & subtraction_disabled) class(pcm_nlo_workspace_t), intent(inout), target :: pcm_work class(pcm_t), intent(in) :: pcm logical, intent(in) :: subtraction_disabled end subroutine pcm_nlo_workspace_setup_real_component <>= module subroutine pcm_nlo_workspace_setup_real_component (pcm_work, pcm, & subtraction_disabled) class(pcm_nlo_workspace_t), intent(inout), target :: pcm_work class(pcm_t), intent(in) :: pcm logical, intent(in) :: subtraction_disabled select type (pcm) type is (pcm_nlo_t) call pcm_work%init_real_subtraction (pcm) if (subtraction_disabled) call pcm_work%disable_subtraction () end select end subroutine pcm_nlo_workspace_setup_real_component @ %def pcm_nlo_workspace_setup_real_component @ <>= procedure :: init_real_and_isr_kinematics => & pcm_nlo_workspace_init_real_and_isr_kinematics <>= module subroutine pcm_nlo_workspace_init_real_and_isr_kinematics & (pcm_work, pcm, energy) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work class(pcm_t), intent(in) :: pcm real(default), dimension(:), intent(in) :: energy end subroutine pcm_nlo_workspace_init_real_and_isr_kinematics <>= module subroutine pcm_nlo_workspace_init_real_and_isr_kinematics & (pcm_work, pcm, energy) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work class(pcm_t), intent(in) :: pcm real(default), dimension(:), intent(in) :: energy integer :: n_contr allocate (pcm_work%real_kinematics) allocate (pcm_work%isr_kinematics) select type (pcm) type is (pcm_nlo_t) associate (region_data => pcm%region_data) if (allocated (region_data%alr_contributors)) then n_contr = size (region_data%alr_contributors) else if (pcm%settings%factorization_mode == FACTORIZATION_THRESHOLD) then n_contr = 2 else n_contr = 1 end if call pcm_work%real_kinematics%init & (region_data%n_legs_real, region_data%n_phs, & region_data%n_regions, n_contr) if (pcm%settings%factorization_mode == FACTORIZATION_THRESHOLD) & call pcm_work%real_kinematics%init_onshell & (region_data%n_legs_real, region_data%n_phs) pcm_work%isr_kinematics%n_in = region_data%n_in end associate end select pcm_work%isr_kinematics%beam_energy = energy end subroutine pcm_nlo_workspace_init_real_and_isr_kinematics @ %def pcm_nlo_workspace_init_real_and_isr_kinematics @ <>= procedure :: set_real_and_isr_kinematics => & pcm_nlo_workspace_set_real_and_isr_kinematics <>= module subroutine pcm_nlo_workspace_set_real_and_isr_kinematics & (pcm_work, phs_identifiers, sqrts) class(pcm_nlo_workspace_t), intent(inout), target :: pcm_work type(phs_identifier_t), intent(in), dimension(:) :: phs_identifiers real(default), intent(in) :: sqrts end subroutine pcm_nlo_workspace_set_real_and_isr_kinematics <>= module subroutine pcm_nlo_workspace_set_real_and_isr_kinematics & (pcm_work, phs_identifiers, sqrts) class(pcm_nlo_workspace_t), intent(inout), target :: pcm_work type(phs_identifier_t), intent(in), dimension(:) :: phs_identifiers real(default), intent(in) :: sqrts call pcm_work%real_sub%set_real_kinematics & (pcm_work%real_kinematics) call pcm_work%real_sub%set_isr_kinematics & (pcm_work%isr_kinematics) end subroutine pcm_nlo_workspace_set_real_and_isr_kinematics @ %def pcm_nlo_workspace_set_real_and_isr_kinematics @ <>= procedure :: init_real_subtraction => pcm_nlo_workspace_init_real_subtraction <>= module subroutine pcm_nlo_workspace_init_real_subtraction (pcm_work, pcm) class(pcm_nlo_workspace_t), intent(inout), target :: pcm_work class(pcm_t), intent(in) :: pcm end subroutine pcm_nlo_workspace_init_real_subtraction <>= module subroutine pcm_nlo_workspace_init_real_subtraction (pcm_work, pcm) class(pcm_nlo_workspace_t), intent(inout), target :: pcm_work class(pcm_t), intent(in) :: pcm select type (pcm) type is (pcm_nlo_t) associate (region_data => pcm%region_data) call pcm_work%real_sub%init (region_data, pcm%settings) if (allocated (pcm%settings%selected_alr)) then associate (selected_alr => pcm%settings%selected_alr) if (any (selected_alr < 0)) then call msg_fatal ("Fixed alpha region must be non-negative!") else if (any (selected_alr > region_data%n_regions)) then call msg_fatal ("Fixed alpha region is larger than the"& &" total number of singular regions!") else allocate (pcm_work%real_sub%selected_alr & (size (selected_alr))) pcm_work%real_sub%selected_alr = selected_alr end if end associate end if end associate end select end subroutine pcm_nlo_workspace_init_real_subtraction @ %def pcm_nlo_workspace_init_real_subtraction @ <>= procedure :: set_momenta_and_scales_virtual => & pcm_nlo_workspace_set_momenta_and_scales_virtual <>= module subroutine pcm_nlo_workspace_set_momenta_and_scales_virtual & (pcm_work, p, ren_scale, fac_scale, es_scale) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work type(vector4_t), intent(in), dimension(:) :: p real(default), allocatable, intent(in) :: ren_scale real(default), intent(in) :: fac_scale real(default), allocatable, intent(in) :: es_scale end subroutine pcm_nlo_workspace_set_momenta_and_scales_virtual <>= module subroutine pcm_nlo_workspace_set_momenta_and_scales_virtual & (pcm_work, p, ren_scale, fac_scale, es_scale) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work type(vector4_t), intent(in), dimension(:) :: p real(default), allocatable, intent(in) :: ren_scale real(default), intent(in) :: fac_scale real(default), allocatable, intent(in) :: es_scale associate (virtual => pcm_work%virtual) call virtual%set_ren_scale (ren_scale) call virtual%set_fac_scale (p, fac_scale) call virtual%set_ellis_sexton_scale (es_scale) end associate end subroutine pcm_nlo_workspace_set_momenta_and_scales_virtual @ %def pcm_nlo_workspace_set_momenta_and_scales_virtual @ <>= procedure :: set_fac_scale => pcm_nlo_workspace_set_fac_scale <>= module subroutine pcm_nlo_workspace_set_fac_scale (pcm_work, fac_scale) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work real(default), intent(in) :: fac_scale end subroutine pcm_nlo_workspace_set_fac_scale <>= module subroutine pcm_nlo_workspace_set_fac_scale (pcm_work, fac_scale) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work real(default), intent(in) :: fac_scale pcm_work%isr_kinematics%fac_scale = fac_scale end subroutine pcm_nlo_workspace_set_fac_scale @ %def pcm_nlo_workspace_set_fac_scale @ <>= procedure :: set_momenta => pcm_nlo_workspace_set_momenta <>= module subroutine pcm_nlo_workspace_set_momenta (pcm_work, & p_born, p_real, i_phs, cms) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work type(vector4_t), dimension(:), intent(in) :: p_born, p_real integer, intent(in) :: i_phs logical, intent(in), optional :: cms end subroutine pcm_nlo_workspace_set_momenta <>= module subroutine pcm_nlo_workspace_set_momenta (pcm_work, & p_born, p_real, i_phs, cms) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work type(vector4_t), dimension(:), intent(in) :: p_born, p_real integer, intent(in) :: i_phs logical, intent(in), optional :: cms logical :: yorn yorn = .false.; if (present (cms)) yorn = cms associate (kinematics => pcm_work%real_kinematics) if (yorn) then if (.not. kinematics%p_born_cms%initialized) & call kinematics%p_born_cms%init (size (p_born), 1) if (.not. kinematics%p_real_cms%initialized) & call kinematics%p_real_cms%init (size (p_real), 1) kinematics%p_born_cms%phs_point(1) = p_born kinematics%p_real_cms%phs_point(i_phs) = p_real else if (.not. kinematics%p_born_lab%initialized) & call kinematics%p_born_lab%init (size (p_born), 1) if (.not. kinematics%p_real_lab%initialized) & call kinematics%p_real_lab%init (size (p_real), 1) kinematics%p_born_lab%phs_point(1) = p_born kinematics%p_real_lab%phs_point(i_phs) = p_real end if end associate end subroutine pcm_nlo_workspace_set_momenta @ %def pcm_nlo_workspace_set_momenta @ <>= procedure :: get_momenta => pcm_nlo_workspace_get_momenta <>= module function pcm_nlo_workspace_get_momenta (pcm_work, pcm, & i_phs, born_phsp, cms) result (p) type(vector4_t), dimension(:), allocatable :: p class(pcm_nlo_workspace_t), intent(in) :: pcm_work class(pcm_t), intent(in) :: pcm integer, intent(in) :: i_phs logical, intent(in) :: born_phsp logical, intent(in), optional :: cms end function pcm_nlo_workspace_get_momenta <>= module function pcm_nlo_workspace_get_momenta (pcm_work, pcm, & i_phs, born_phsp, cms) result (p) type(vector4_t), dimension(:), allocatable :: p class(pcm_nlo_workspace_t), intent(in) :: pcm_work class(pcm_t), intent(in) :: pcm integer, intent(in) :: i_phs logical, intent(in) :: born_phsp logical, intent(in), optional :: cms logical :: yorn yorn = .false.; if (present (cms)) yorn = cms select type (pcm) type is (pcm_nlo_t) if (born_phsp) then if (yorn) then p = pcm_work%real_kinematics%p_born_cms%phs_point(1) else p = pcm_work%real_kinematics%p_born_lab%phs_point(1) end if else if (yorn) then p = pcm_work%real_kinematics%p_real_cms%phs_point(i_phs) else p = pcm_work%real_kinematics%p_real_lab%phs_point(i_phs) end if end if end select end function pcm_nlo_workspace_get_momenta @ %def pcm_nlo_workspace_get_momenta @ <>= procedure :: get_xi_max => pcm_nlo_workspace_get_xi_max <>= module function pcm_nlo_workspace_get_xi_max (pcm_work, alr) result (xi_max) real(default) :: xi_max class(pcm_nlo_workspace_t), intent(in) :: pcm_work integer, intent(in) :: alr end function pcm_nlo_workspace_get_xi_max <>= module function pcm_nlo_workspace_get_xi_max (pcm_work, alr) result (xi_max) real(default) :: xi_max class(pcm_nlo_workspace_t), intent(in) :: pcm_work integer, intent(in) :: alr integer :: i_phs i_phs = pcm_work%real_kinematics%alr_to_i_phs (alr) xi_max = pcm_work%real_kinematics%xi_max (i_phs) end function pcm_nlo_workspace_get_xi_max @ %def pcm_nlo_workspace_get_xi_max @ <>= procedure :: set_x_rad => pcm_nlo_workspace_set_x_rad <>= module subroutine pcm_nlo_workspace_set_x_rad (pcm_work, x_tot) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work real(default), intent(in), dimension(:) :: x_tot end subroutine pcm_nlo_workspace_set_x_rad <>= module subroutine pcm_nlo_workspace_set_x_rad (pcm_work, x_tot) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work real(default), intent(in), dimension(:) :: x_tot integer :: n_par n_par = size (x_tot) if (n_par < 3) then pcm_work%real_kinematics%x_rad = zero else pcm_work%real_kinematics%x_rad = x_tot (n_par - 2 : n_par) end if end subroutine pcm_nlo_workspace_set_x_rad @ %def pcm_nlo_workspace_set_x_rad @ <>= procedure :: init_virtual => pcm_nlo_workspace_init_virtual <>= module subroutine pcm_nlo_workspace_init_virtual (pcm_work, pcm, model) class(pcm_nlo_workspace_t), intent(inout), target :: pcm_work class(pcm_t), intent(in) :: pcm class(model_data_t), intent(in) :: model end subroutine pcm_nlo_workspace_init_virtual <>= module subroutine pcm_nlo_workspace_init_virtual (pcm_work, pcm, model) class(pcm_nlo_workspace_t), intent(inout), target :: pcm_work class(pcm_t), intent(in) :: pcm class(model_data_t), intent(in) :: model select type (pcm) type is (pcm_nlo_t) associate (region_data => pcm%region_data) call pcm_work%virtual%init (region_data%get_flv_states_born (), & region_data%n_in, pcm%settings, model, pcm%has_pdfs) end associate end select end subroutine pcm_nlo_workspace_init_virtual @ %def pcm_nlo_workspace_init_virtual @ <>= procedure :: disable_virtual_subtraction => & pcm_nlo_workspace_disable_virtual_subtraction <>= module subroutine pcm_nlo_workspace_disable_virtual_subtraction (pcm_work) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work end subroutine pcm_nlo_workspace_disable_virtual_subtraction <>= module subroutine pcm_nlo_workspace_disable_virtual_subtraction (pcm_work) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work end subroutine pcm_nlo_workspace_disable_virtual_subtraction @ %def pcm_nlo_workspace_disable_virtual_subtraction @ <>= procedure :: compute_sqme_virt => pcm_nlo_workspace_compute_sqme_virt <>= module subroutine pcm_nlo_workspace_compute_sqme_virt (pcm_work, pcm, p, & alpha_coupling, separate_uborns, sqme_virt) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work class(pcm_t), intent(in) :: pcm type(vector4_t), intent(in), dimension(:) :: p real(default), dimension(2), intent(in) :: alpha_coupling logical, intent(in) :: separate_uborns real(default), dimension(:), allocatable, intent(inout) :: sqme_virt end subroutine pcm_nlo_workspace_compute_sqme_virt <>= module subroutine pcm_nlo_workspace_compute_sqme_virt (pcm_work, pcm, p, & alpha_coupling, separate_uborns, sqme_virt) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work class(pcm_t), intent(in) :: pcm type(vector4_t), intent(in), dimension(:) :: p real(default), dimension(2), intent(in) :: alpha_coupling logical, intent(in) :: separate_uborns real(default), dimension(:), allocatable, intent(inout) :: sqme_virt type(vector4_t), dimension(:), allocatable :: pp associate (virtual => pcm_work%virtual) allocate (pp (size (p))) if (virtual%settings%factorization_mode == FACTORIZATION_THRESHOLD) then pp = pcm_work%real_kinematics%p_born_onshell%get_momenta (1) else pp = p end if select type (pcm) type is (pcm_nlo_t) if (separate_uborns) then allocate (sqme_virt (pcm%get_n_flv_born ())) else allocate (sqme_virt (1)) end if sqme_virt = zero call virtual%evaluate (pcm%region_data, & alpha_coupling, pp, separate_uborns, sqme_virt) end select end associate end subroutine pcm_nlo_workspace_compute_sqme_virt @ %def pcm_nlo_workspace_compute_sqme_virt @ <>= procedure :: compute_sqme_mismatch => pcm_nlo_workspace_compute_sqme_mismatch <>= module subroutine pcm_nlo_workspace_compute_sqme_mismatch (pcm_work, pcm, & alpha_s, separate_uborns, sqme_mism) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work class(pcm_t), intent(in) :: pcm real(default), intent(in) :: alpha_s logical, intent(in) :: separate_uborns real(default), dimension(:), allocatable, intent(inout) :: sqme_mism end subroutine pcm_nlo_workspace_compute_sqme_mismatch <>= module subroutine pcm_nlo_workspace_compute_sqme_mismatch (pcm_work, pcm, & alpha_s, separate_uborns, sqme_mism) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work class(pcm_t), intent(in) :: pcm real(default), intent(in) :: alpha_s logical, intent(in) :: separate_uborns real(default), dimension(:), allocatable, intent(inout) :: sqme_mism select type (pcm) type is (pcm_nlo_t) if (separate_uborns) then allocate (sqme_mism (pcm%get_n_flv_born ())) else allocate (sqme_mism (1)) end if sqme_mism = zero sqme_mism = pcm_work%soft_mismatch%evaluate (alpha_s) end select end subroutine pcm_nlo_workspace_compute_sqme_mismatch @ %def pcm_nlo_workspace_compute_sqme_mismatch @ <>= procedure :: compute_sqme_dglap_remnant => & pcm_nlo_workspace_compute_sqme_dglap_remnant <>= module subroutine pcm_nlo_workspace_compute_sqme_dglap_remnant (pcm_work, & pcm, alpha_coupling, separate_uborns, sqme_dglap) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work class(pcm_t), intent(in) :: pcm real(default), dimension(2), intent(in) :: alpha_coupling logical, intent(in) :: separate_uborns real(default), dimension(:), allocatable, intent(inout) :: sqme_dglap end subroutine pcm_nlo_workspace_compute_sqme_dglap_remnant <>= module subroutine pcm_nlo_workspace_compute_sqme_dglap_remnant (pcm_work, & pcm, alpha_coupling, separate_uborns, sqme_dglap) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work class(pcm_t), intent(in) :: pcm real(default), dimension(2), intent(in) :: alpha_coupling logical, intent(in) :: separate_uborns real(default), dimension(:), allocatable, intent(inout) :: sqme_dglap select type (pcm) type is (pcm_nlo_t) if (separate_uborns) then allocate (sqme_dglap (pcm%get_n_flv_born ())) else allocate (sqme_dglap (1)) end if end select sqme_dglap = zero call pcm_work%dglap_remnant%evaluate (alpha_coupling, & separate_uborns, sqme_dglap) end subroutine pcm_nlo_workspace_compute_sqme_dglap_remnant @ %def pcm_nlo_workspace_compute_sqme_dglap_remnant @ <>= procedure :: set_fixed_order_event_mode => & pcm_nlo_workspace_set_fixed_order_event_mode <>= module subroutine pcm_nlo_workspace_set_fixed_order_event_mode (pcm_work) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work end subroutine pcm_nlo_workspace_set_fixed_order_event_mode <>= module subroutine pcm_nlo_workspace_set_fixed_order_event_mode (pcm_work) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work pcm_work%real_sub%purpose = FIXED_ORDER_EVENTS end subroutine pcm_nlo_workspace_set_fixed_order_event_mode <>= procedure :: set_powheg_mode => pcm_nlo_workspace_set_powheg_mode <>= module subroutine pcm_nlo_workspace_set_powheg_mode (pcm_work) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work end subroutine pcm_nlo_workspace_set_powheg_mode <>= module subroutine pcm_nlo_workspace_set_powheg_mode (pcm_work) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work pcm_work%real_sub%purpose = POWHEG end subroutine pcm_nlo_workspace_set_powheg_mode @ %def pcm_nlo_workspace_set_fixed_order_event_mode @ %def pcm_nlo_workspace_set_powheg_mode @ <>= procedure :: init_soft_mismatch => pcm_nlo_workspace_init_soft_mismatch <>= module subroutine pcm_nlo_workspace_init_soft_mismatch (pcm_work, pcm) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work class(pcm_t), intent(in) :: pcm end subroutine pcm_nlo_workspace_init_soft_mismatch <>= module subroutine pcm_nlo_workspace_init_soft_mismatch (pcm_work, pcm) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work class(pcm_t), intent(in) :: pcm select type (pcm) type is (pcm_nlo_t) call pcm_work%soft_mismatch%init (pcm%region_data, & pcm_work%real_kinematics, pcm%settings%factorization_mode) end select end subroutine pcm_nlo_workspace_init_soft_mismatch @ %def pcm_nlo_workspace_init_soft_mismatch @ <>= procedure :: init_dglap_remnant => pcm_nlo_workspace_init_dglap_remnant <>= module subroutine pcm_nlo_workspace_init_dglap_remnant (pcm_work, pcm) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work class(pcm_t), intent(in) :: pcm end subroutine pcm_nlo_workspace_init_dglap_remnant <>= module subroutine pcm_nlo_workspace_init_dglap_remnant (pcm_work, pcm) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work class(pcm_t), intent(in) :: pcm select type (pcm) type is (pcm_nlo_t) call pcm_work%dglap_remnant%init ( & pcm%settings, & pcm%region_data, & pcm_work%isr_kinematics) end select end subroutine pcm_nlo_workspace_init_dglap_remnant @ %def pcm_nlo_workspace_init_dglap_remnant @ <>= procedure :: is_fixed_order_nlo_events & => pcm_nlo_workspace_is_fixed_order_nlo_events <>= module function pcm_nlo_workspace_is_fixed_order_nlo_events & (pcm_work) result (is_fnlo) logical :: is_fnlo class(pcm_nlo_workspace_t), intent(in) :: pcm_work end function pcm_nlo_workspace_is_fixed_order_nlo_events <>= module function pcm_nlo_workspace_is_fixed_order_nlo_events & (pcm_work) result (is_fnlo) logical :: is_fnlo class(pcm_nlo_workspace_t), intent(in) :: pcm_work is_fnlo = pcm_work%real_sub%purpose == FIXED_ORDER_EVENTS end function pcm_nlo_workspace_is_fixed_order_nlo_events @ %def pcm_nlo_workspace_is_fixed_order_nlo_events @ <>= procedure :: final => pcm_nlo_workspace_final <>= module subroutine pcm_nlo_workspace_final (pcm_work) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work end subroutine pcm_nlo_workspace_final <>= module subroutine pcm_nlo_workspace_final (pcm_work) class(pcm_nlo_workspace_t), intent(inout) :: pcm_work call pcm_work%real_sub%final () call pcm_work%virtual%final () call pcm_work%soft_mismatch%final () call pcm_work%dglap_remnant%final () if (associated (pcm_work%real_kinematics)) then call pcm_work%real_kinematics%final () nullify (pcm_work%real_kinematics) end if if (associated (pcm_work%isr_kinematics)) then nullify (pcm_work%isr_kinematics) end if end subroutine pcm_nlo_workspace_final @ %def pcm_nlo_workspace_final @ <>= procedure :: is_nlo => pcm_nlo_workspace_is_nlo <>= module function pcm_nlo_workspace_is_nlo (pcm_work) result (is_nlo) logical :: is_nlo class(pcm_nlo_workspace_t), intent(inout) :: pcm_work end function pcm_nlo_workspace_is_nlo <>= module function pcm_nlo_workspace_is_nlo (pcm_work) result (is_nlo) logical :: is_nlo class(pcm_nlo_workspace_t), intent(inout) :: pcm_work is_nlo = .true. end function pcm_nlo_workspace_is_nlo @ %def pcm_nlo_workspace_is_nlo @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Kinematics instance} In this data type we combine all objects (instances) necessary for generating (or recovering) a kinematical configuration. The components work together as an implementation of multi-channel phase space. [[sf_chain]] is an instance of the structure-function chain. It is used both for generating kinematics and, after the proper scale has been determined, evaluating the structure function entries. [[phs]] is an instance of the phase space for the elementary process. The array [[f]] contains the products of the Jacobians that originate from parameter mappings in the structure-function chain or in the phase space. We allocate this explicitly if either [[sf_chain]] or [[phs]] are explicitly allocated, otherwise we can take over a pointer. All components are implemented as pointers to (anonymous) targets. For each component, there is a flag that tells whether this component is to be regarded as a proper component (`owned' by the object) or as a pointer. @ <<[[kinematics.f90]]>>= <> module kinematics <> use lorentz use physics_defs use sf_base use phs_base use fks_regions use mci_base use process_config use process_mci use pcm_base, only: pcm_t, pcm_workspace_t use pcm, only: pcm_nlo_t, pcm_nlo_workspace_t <> <> <> interface <> end interface end module kinematics @ %def kinematics @ <<[[kinematics_sub.f90]]>>= <> submodule (kinematics) kinematics_s <> use format_utils, only: write_separator use diagnostics use io_units use phs_points, only: assignment(=), size use interactions use phs_fks use ttv_formfactors, only: m1s_to_mpole implicit none contains <> end submodule kinematics_s @ %def kinematics_s @ <>= public :: kinematics_t <>= type :: kinematics_t integer :: n_in = 0 integer :: n_channel = 0 integer :: selected_channel = 0 type(sf_chain_instance_t), pointer :: sf_chain => null () class(phs_t), pointer :: phs => null () real(default), dimension(:), pointer :: f => null () real(default) :: phs_factor logical :: sf_chain_allocated = .false. logical :: phs_allocated = .false. logical :: f_allocated = .false. integer :: emitter = -1 integer :: i_phs = 0 integer :: i_con = 0 logical :: only_cm_frame = .false. logical :: new_seed = .true. logical :: threshold = .false. contains <> end type kinematics_t @ %def kinematics_t @ Output. Show only those components which are marked as owned. <>= procedure :: write => kinematics_write <>= module subroutine kinematics_write (object, unit) class(kinematics_t), intent(in) :: object integer, intent(in), optional :: unit end subroutine kinematics_write <>= module subroutine kinematics_write (object, unit) class(kinematics_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u, c u = given_output_unit (unit) if (object%f_allocated) then write (u, "(1x,A)") "Flux * PHS volume:" write (u, "(2x,ES19.12)") object%phs_factor write (u, "(1x,A)") "Jacobian factors per channel:" do c = 1, size (object%f) write (u, "(3x,I0,':',1x,ES14.7)", advance="no") c, object%f(c) if (c == object%selected_channel) then write (u, "(1x,A)") "[selected]" else write (u, *) end if end do end if if (object%sf_chain_allocated) then call write_separator (u) call object%sf_chain%write (u) end if if (object%phs_allocated) then call write_separator (u) call object%phs%write (u) end if end subroutine kinematics_write @ %def kinematics_write @ Finalizer. Delete only those components which are marked as owned. <>= procedure :: final => kinematics_final <>= module subroutine kinematics_final (object) class(kinematics_t), intent(inout) :: object end subroutine kinematics_final <>= module subroutine kinematics_final (object) class(kinematics_t), intent(inout) :: object if (object%sf_chain_allocated) then call object%sf_chain%final () deallocate (object%sf_chain) object%sf_chain_allocated = .false. end if if (object%phs_allocated) then call object%phs%final () deallocate (object%phs) object%phs_allocated = .false. end if if (object%f_allocated) then deallocate (object%f) object%f_allocated = .false. end if end subroutine kinematics_final @ %def kinematics_final @ Configure the kinematics object. This consists of several configuration steps which correspond to individual procedures. In essence, we configure the structure-function part, the partonic phase-space part, and various NLO items. TODO wk 19-03-01: This includes some region-data setup within [[pcm]], hence [[pcm]] is intent(inout). This should be moved elsewhere, so [[pcm]] can become strictly intent(in). <>= procedure :: configure => kinematics_configure <>= module subroutine kinematics_configure (kin, pcm, pcm_work, & sf_chain, beam_config, phs_config, nlo_type, is_i_sub) class(kinematics_t), intent(out) :: kin class(pcm_t), intent(inout) :: pcm class(pcm_workspace_t), intent(in) :: pcm_work type(sf_chain_t), intent(in), target :: sf_chain type(process_beam_config_t), intent(in), target :: beam_config class(phs_config_t), intent(in), target :: phs_config integer, intent(in) :: nlo_type logical, intent(in) :: is_i_sub end subroutine kinematics_configure <>= module subroutine kinematics_configure (kin, pcm, pcm_work, & sf_chain, beam_config, phs_config, nlo_type, is_i_sub) class(kinematics_t), intent(out) :: kin class(pcm_t), intent(inout) :: pcm class(pcm_workspace_t), intent(in) :: pcm_work type(sf_chain_t), intent(in), target :: sf_chain type(process_beam_config_t), intent(in), target :: beam_config class(phs_config_t), intent(in), target :: phs_config integer, intent(in) :: nlo_type logical, intent(in) :: is_i_sub logical :: extended_sf extended_sf = nlo_type == NLO_DGLAP .or. & (nlo_type == NLO_REAL .and. is_i_sub) call kin%init_sf_chain (sf_chain, beam_config, & extended_sf = pcm%has_pdfs .and. extended_sf) !!! Add one for additional Born matrix element call kin%init_phs (phs_config) call kin%set_nlo_info (nlo_type) select type (phs => kin%phs) type is (phs_fks_t) call phs%allocate_momenta (phs_config, .not. (nlo_type == NLO_REAL)) select type (pcm) type is (pcm_nlo_t) call pcm%region_data%init_phs_identifiers (phs%phs_identifiers) !!! The triple select type pyramid of doom select type (pcm_work) type is (pcm_nlo_workspace_t) if (allocated (pcm_work%real_kinematics%alr_to_i_phs)) & call pcm%region_data%set_alr_to_i_phs (phs%phs_identifiers, & pcm_work%real_kinematics%alr_to_i_phs) end select end select end select end subroutine kinematics_configure @ %def kinematics_configure @ Set the flags indicating whether the phase space shall be set up for the calculation of the real contribution. For this case, also set the emitter. <>= procedure :: set_nlo_info => kinematics_set_nlo_info <>= module subroutine kinematics_set_nlo_info (k, nlo_type) class(kinematics_t), intent(inout) :: k integer, intent(in) :: nlo_type end subroutine kinematics_set_nlo_info <>= module subroutine kinematics_set_nlo_info (k, nlo_type) class(kinematics_t), intent(inout) :: k integer, intent(in) :: nlo_type if (nlo_type == NLO_VIRTUAL) k%only_cm_frame = .true. end subroutine kinematics_set_nlo_info @ %def kinematics_set_nlo_info @ <>= procedure :: set_threshold => kinematics_set_threshold <>= module subroutine kinematics_set_threshold (kin, factorization_mode) class(kinematics_t), intent(inout) :: kin integer, intent(in) :: factorization_mode end subroutine kinematics_set_threshold <>= module subroutine kinematics_set_threshold (kin, factorization_mode) class(kinematics_t), intent(inout) :: kin integer, intent(in) :: factorization_mode kin%threshold = factorization_mode == FACTORIZATION_THRESHOLD end subroutine kinematics_set_threshold @ %def kinematics_set_threshold @ Allocate the structure-function chain instance, initialize it as a copy of the [[sf_chain]] template, and prepare it for evaluation. The [[sf_chain]] remains a target because the (usually constant) beam momenta are taken from there. <>= procedure :: init_sf_chain => kinematics_init_sf_chain <>= module subroutine kinematics_init_sf_chain & (k, sf_chain, config, extended_sf) class(kinematics_t), intent(inout) :: k type(sf_chain_t), intent(in), target :: sf_chain type(process_beam_config_t), intent(in) :: config logical, intent(in), optional :: extended_sf end subroutine kinematics_init_sf_chain <>= module subroutine kinematics_init_sf_chain (k, sf_chain, config, extended_sf) class(kinematics_t), intent(inout) :: k type(sf_chain_t), intent(in), target :: sf_chain type(process_beam_config_t), intent(in) :: config logical, intent(in), optional :: extended_sf integer :: n_strfun, n_channel integer :: c k%n_in = config%data%get_n_in () n_strfun = config%n_strfun n_channel = config%n_channel allocate (k%sf_chain) k%sf_chain_allocated = .true. call k%sf_chain%init (sf_chain, n_channel) if (n_strfun /= 0) then do c = 1, n_channel call k%sf_chain%set_channel (c, config%sf_channel(c)) end do end if call k%sf_chain%link_interactions () call k%sf_chain%exchange_mask () call k%sf_chain%init_evaluators (extended_sf = extended_sf) end subroutine kinematics_init_sf_chain @ %def kinematics_init_sf_chain @ Allocate and initialize the phase-space part and the array of Jacobian factors. <>= procedure :: init_phs => kinematics_init_phs <>= module subroutine kinematics_init_phs (k, config) class(kinematics_t), intent(inout) :: k class(phs_config_t), intent(in), target :: config end subroutine kinematics_init_phs <>= module subroutine kinematics_init_phs (k, config) class(kinematics_t), intent(inout) :: k class(phs_config_t), intent(in), target :: config k%n_channel = config%get_n_channel () call config%allocate_instance (k%phs) call k%phs%init (config) k%phs_allocated = .true. allocate (k%f (k%n_channel)) k%f = 0 k%f_allocated = .true. end subroutine kinematics_init_phs @ %def kinematics_init_phs @ <>= procedure :: evaluate_radiation_kinematics => & kinematics_evaluate_radiation_kinematics <>= module subroutine kinematics_evaluate_radiation_kinematics (k, r_in) class(kinematics_t), intent(inout) :: k real(default), intent(in), dimension(:) :: r_in end subroutine kinematics_evaluate_radiation_kinematics <>= module subroutine kinematics_evaluate_radiation_kinematics (k, r_in) class(kinematics_t), intent(inout) :: k real(default), intent(in), dimension(:) :: r_in select type (phs => k%phs) type is (phs_fks_t) if (phs%mode == PHS_MODE_ADDITIONAL_PARTICLE) then call phs%generate_radiation_variables & (r_in(phs%n_r_born + 1 : phs%n_r_born + 3), & threshold = k%threshold) call phs%compute_cms_energy () end if end select end subroutine kinematics_evaluate_radiation_kinematics @ %def kinematics_evaluate_radiation_kinematics @ <>= procedure :: generate_fsr_in => kinematics_generate_fsr_in <>= module subroutine kinematics_generate_fsr_in (kin) class(kinematics_t), intent(inout) :: kin end subroutine kinematics_generate_fsr_in <>= module subroutine kinematics_generate_fsr_in (kin) class(kinematics_t), intent(inout) :: kin select type (phs => kin%phs) type is (phs_fks_t) call phs%generate_fsr_in () end select end subroutine kinematics_generate_fsr_in @ %def kinematics_generate_fsr_in @ <>= procedure :: compute_xi_ref_momenta => kinematics_compute_xi_ref_momenta <>= module subroutine kinematics_compute_xi_ref_momenta (k, reg_data, nlo_type) class(kinematics_t), intent(inout) :: k type(region_data_t), intent(in) :: reg_data integer, intent(in) :: nlo_type end subroutine kinematics_compute_xi_ref_momenta <>= module subroutine kinematics_compute_xi_ref_momenta (k, reg_data, nlo_type) class(kinematics_t), intent(inout) :: k type(region_data_t), intent(in) :: reg_data integer, intent(in) :: nlo_type logical :: use_contributors use_contributors = allocated (reg_data%alr_contributors) select type (phs => k%phs) type is (phs_fks_t) if (use_contributors) then call phs%compute_xi_ref_momenta (contributors = reg_data%alr_contributors) else if (k%threshold) then if (.not. is_subtraction_component (k%emitter, nlo_type)) & call phs%compute_xi_ref_momenta_threshold () else call phs%compute_xi_ref_momenta () end if end select end subroutine kinematics_compute_xi_ref_momenta @ %def kinematics_compute_xi_ref_momenta @ Generate kinematics, given a phase-space channel and a MC parameter set. The main result is the momentum array [[p]], but we also fill the momentum entries in the structure-function chain and the Jacobian-factor array [[f]]. Regarding phase space, we fill only the parameter arrays for the selected channel. <>= procedure :: compute_selected_channel => kinematics_compute_selected_channel <>= module subroutine kinematics_compute_selected_channel & (k, mci_work, phs_channel, p, success) class(kinematics_t), intent(inout) :: k type(mci_work_t), intent(in) :: mci_work integer, intent(in) :: phs_channel type(vector4_t), dimension(:), intent(out) :: p logical, intent(out) :: success end subroutine kinematics_compute_selected_channel <>= module subroutine kinematics_compute_selected_channel & (k, mci_work, phs_channel, p, success) class(kinematics_t), intent(inout) :: k type(mci_work_t), intent(in) :: mci_work integer, intent(in) :: phs_channel type(vector4_t), dimension(:), intent(out) :: p logical, intent(out) :: success integer :: sf_channel k%selected_channel = phs_channel sf_channel = k%phs%config%get_sf_channel (phs_channel) call k%sf_chain%compute_kinematics (sf_channel, mci_work%get_x_strfun ()) call k%sf_chain%get_out_momenta (p(1:k%n_in)) call k%phs%set_incoming_momenta (p(1:k%n_in)) call k%phs%compute_flux () call k%phs%select_channel (phs_channel) call k%phs%evaluate_selected_channel (phs_channel, & mci_work%get_x_process ()) select type (phs => k%phs) type is (phs_fks_t) if (debug_on) call msg_debug2 (D_REAL, "phase space is phs_FKS") if (phs%q_defined) then call phs%get_born_momenta (p) if (debug_on) then call msg_debug2 (D_REAL, "q is defined") call msg_debug2 (D_REAL, "get_born_momenta called") end if k%phs_factor = phs%get_overall_factor () success = .true. else k%phs_factor = 0 success = .false. end if class default if (phs%q_defined) then call k%phs%get_outgoing_momenta (p(k%n_in + 1 :)) k%phs_factor = k%phs%get_overall_factor () success = .true. else k%phs_factor = 0 success = .false. end if end select end subroutine kinematics_compute_selected_channel @ %def kinematics_compute_selected_channel @ <>= procedure :: redo_sf_chain => kinematics_redo_sf_chain <>= module subroutine kinematics_redo_sf_chain (kin, mci_work, phs_channel) class(kinematics_t), intent(inout) :: kin type(mci_work_t), intent(in) :: mci_work integer, intent(in) :: phs_channel end subroutine kinematics_redo_sf_chain <>= module subroutine kinematics_redo_sf_chain (kin, mci_work, phs_channel) class(kinematics_t), intent(inout) :: kin type(mci_work_t), intent(in) :: mci_work integer, intent(in) :: phs_channel real(default), dimension(:), allocatable :: x integer :: sf_channel, n real(default) :: xi, y n = size (mci_work%get_x_strfun ()) if (n > 0) then allocate (x(n)) x = mci_work%get_x_strfun () sf_channel = kin%phs%config%get_sf_channel (phs_channel) call kin%sf_chain%compute_kinematics (sf_channel, x) end if end subroutine kinematics_redo_sf_chain @ %def kinematics_redo_sf_chain @ Complete kinematics by filling the non-selected phase-space parameter arrays. <>= procedure :: compute_other_channels => kinematics_compute_other_channels <>= module subroutine kinematics_compute_other_channels & (k, mci_work, phs_channel) class(kinematics_t), intent(inout) :: k type(mci_work_t), intent(in) :: mci_work integer, intent(in) :: phs_channel end subroutine kinematics_compute_other_channels <>= module subroutine kinematics_compute_other_channels (k, mci_work, phs_channel) class(kinematics_t), intent(inout) :: k type(mci_work_t), intent(in) :: mci_work integer, intent(in) :: phs_channel integer :: c, c_sf call k%phs%evaluate_other_channels (phs_channel) do c = 1, k%n_channel c_sf = k%phs%config%get_sf_channel (c) k%f(c) = k%sf_chain%get_f (c_sf) * k%phs%get_f (c) end do end subroutine kinematics_compute_other_channels @ %def kinematics_compute_other_channels @ Just fetch the outgoing momenta of the [[sf_chain]] subobject, which become the incoming (seed) momenta of the hard interaction. This is a stripped down-version of the above which we use when recovering kinematics. Momenta are known, but no MC parameters yet. (We do not use the [[get_out_momenta]] method of the chain, since this relies on the structure-function interactions, which are not necessary filled here. We do rely on the momenta of the last evaluator in the chain, however.) <>= procedure :: get_incoming_momenta => kinematics_get_incoming_momenta <>= module subroutine kinematics_get_incoming_momenta (k, p) class(kinematics_t), intent(in) :: k type(vector4_t), dimension(:), intent(out) :: p end subroutine kinematics_get_incoming_momenta <>= module subroutine kinematics_get_incoming_momenta (k, p) class(kinematics_t), intent(in) :: k type(vector4_t), dimension(:), intent(out) :: p type(interaction_t), pointer :: int integer :: i int => k%sf_chain%get_out_int_ptr () do i = 1, k%n_in p(i) = int%get_momentum (k%sf_chain%get_out_i (i)) end do end subroutine kinematics_get_incoming_momenta @ %def kinematics_get_incoming_momenta @ <>= procedure :: get_boost_to_lab => kinematics_get_boost_to_lab <>= module function kinematics_get_boost_to_lab (kin) result (lt) type(lorentz_transformation_t) :: lt class(kinematics_t), intent(in) :: kin end function kinematics_get_boost_to_lab <>= module function kinematics_get_boost_to_lab (kin) result (lt) type(lorentz_transformation_t) :: lt class(kinematics_t), intent(in) :: kin lt = kin%phs%get_lorentz_transformation () end function kinematics_get_boost_to_lab @ %def kinematics_get_boost_to_lab @ <>= procedure :: get_boost_to_cms => kinematics_get_boost_to_cms <>= module function kinematics_get_boost_to_cms (kin) result (lt) type(lorentz_transformation_t) :: lt class(kinematics_t), intent(in) :: kin end function kinematics_get_boost_to_cms <>= module function kinematics_get_boost_to_cms (kin) result (lt) type(lorentz_transformation_t) :: lt class(kinematics_t), intent(in) :: kin lt = inverse (kin%phs%get_lorentz_transformation ()) end function kinematics_get_boost_to_cms @ %def kinematics_get_boost_to_cms @ This inverts the remainder of the above [[compute]] method. We know the momenta and recover the rest, as far as needed. If we select a channel, we can complete the inversion and reconstruct the MC parameter set. <>= procedure :: recover_mcpar => kinematics_recover_mcpar <>= module subroutine kinematics_recover_mcpar (k, mci_work, phs_channel, p) class(kinematics_t), intent(inout) :: k type(mci_work_t), intent(inout) :: mci_work integer, intent(in) :: phs_channel type(vector4_t), dimension(:), intent(in) :: p end subroutine kinematics_recover_mcpar <>= module subroutine kinematics_recover_mcpar (k, mci_work, phs_channel, p) class(kinematics_t), intent(inout) :: k type(mci_work_t), intent(inout) :: mci_work integer, intent(in) :: phs_channel type(vector4_t), dimension(:), intent(in) :: p integer :: c, c_sf real(default), dimension(:), allocatable :: x_sf, x_phs c = phs_channel c_sf = k%phs%config%get_sf_channel (c) k%selected_channel = c call k%sf_chain%recover_kinematics (c_sf) call k%phs%set_incoming_momenta (p(1:k%n_in)) call k%phs%compute_flux () call k%phs%set_outgoing_momenta (p(k%n_in+1:)) call k%phs%inverse () do c = 1, k%n_channel c_sf = k%phs%config%get_sf_channel (c) k%f(c) = k%sf_chain%get_f (c_sf) * k%phs%get_f (c) end do k%phs_factor = k%phs%get_overall_factor () c = phs_channel c_sf = k%phs%config%get_sf_channel (c) allocate (x_sf (k%sf_chain%config%get_n_bound ())) allocate (x_phs (k%phs%config%get_n_par ())) call k%phs%select_channel (c) call k%sf_chain%get_mcpar (c_sf, x_sf) call k%phs%get_mcpar (c, x_phs) call mci_work%set_x_strfun (x_sf) call mci_work%set_x_process (x_phs) end subroutine kinematics_recover_mcpar @ %def kinematics_recover_mcpar @ This first part of [[recover_mcpar]]: just handle the sfchain. <>= procedure :: recover_sfchain => kinematics_recover_sfchain <>= module subroutine kinematics_recover_sfchain (k, channel, p) class(kinematics_t), intent(inout) :: k integer, intent(in) :: channel type(vector4_t), dimension(:), intent(in) :: p end subroutine kinematics_recover_sfchain <>= module subroutine kinematics_recover_sfchain (k, channel, p) class(kinematics_t), intent(inout) :: k integer, intent(in) :: channel type(vector4_t), dimension(:), intent(in) :: p k%selected_channel = channel call k%sf_chain%recover_kinematics (channel) end subroutine kinematics_recover_sfchain @ %def kinematics_recover_sfchain @ Retrieve the MC input parameter array for a specific channel. We assume that the kinematics is complete, so this is known for all channels. <>= procedure :: get_mcpar => kinematics_get_mcpar <>= module subroutine kinematics_get_mcpar (k, phs_channel, r) class(kinematics_t), intent(in) :: k integer, intent(in) :: phs_channel real(default), dimension(:), intent(out) :: r end subroutine kinematics_get_mcpar <>= module subroutine kinematics_get_mcpar (k, phs_channel, r) class(kinematics_t), intent(in) :: k integer, intent(in) :: phs_channel real(default), dimension(:), intent(out) :: r integer :: sf_channel, n_par_sf, n_par_phs sf_channel = k%phs%config%get_sf_channel (phs_channel) n_par_phs = k%phs%config%get_n_par () n_par_sf = k%sf_chain%config%get_n_bound () if (n_par_sf > 0) then call k%sf_chain%get_mcpar (sf_channel, r(1:n_par_sf)) end if if (n_par_phs > 0) then call k%phs%get_mcpar (phs_channel, r(n_par_sf+1:)) end if end subroutine kinematics_get_mcpar @ %def kinematics_get_mcpar @ Evaluate the structure function chain, assuming that kinematics is known. The status must be precisely [[SF_DONE_KINEMATICS]]. We thus avoid evaluating the chain twice via different pointers to the same target. <>= procedure :: evaluate_sf_chain => kinematics_evaluate_sf_chain <>= module subroutine kinematics_evaluate_sf_chain & (k, fac_scale, negative_sf, sf_rescale) class(kinematics_t), intent(inout) :: k real(default), intent(in) :: fac_scale logical, intent(in), optional :: negative_sf class(sf_rescale_t), intent(inout), optional :: sf_rescale end subroutine kinematics_evaluate_sf_chain <>= module subroutine kinematics_evaluate_sf_chain & (k, fac_scale, negative_sf, sf_rescale) class(kinematics_t), intent(inout) :: k real(default), intent(in) :: fac_scale logical, intent(in), optional :: negative_sf class(sf_rescale_t), intent(inout), optional :: sf_rescale select case (k%sf_chain%get_status ()) case (SF_DONE_KINEMATICS) call k%sf_chain%evaluate (fac_scale, negative_sf = negative_sf, & sf_rescale = sf_rescale) end select end subroutine kinematics_evaluate_sf_chain @ %def kinematics_evaluate_sf_chain @ Recover beam momenta, i.e., return the beam momenta stored in the current [[sf_chain]] to their source. This is a side effect. <>= procedure :: return_beam_momenta => kinematics_return_beam_momenta <>= module subroutine kinematics_return_beam_momenta (k) class(kinematics_t), intent(in) :: k end subroutine kinematics_return_beam_momenta <>= module subroutine kinematics_return_beam_momenta (k) class(kinematics_t), intent(in) :: k call k%sf_chain%return_beam_momenta () end subroutine kinematics_return_beam_momenta @ %def kinematics_return_beam_momenta @ Check wether the phase space is configured in the center-of-mass frame. Relevant for using the proper momenta input for BLHA matrix elements. <>= procedure :: lab_is_cm => kinematics_lab_is_cm <>= module function kinematics_lab_is_cm (k) result (lab_is_cm) logical :: lab_is_cm class(kinematics_t), intent(in) :: k end function kinematics_lab_is_cm <>= module function kinematics_lab_is_cm (k) result (lab_is_cm) logical :: lab_is_cm class(kinematics_t), intent(in) :: k lab_is_cm = k%phs%config%lab_is_cm end function kinematics_lab_is_cm @ %def kinematics_lab_is_cm @ <>= procedure :: modify_momenta_for_subtraction => & kinematics_modify_momenta_for_subtraction <>= module subroutine kinematics_modify_momenta_for_subtraction (k, p_in, p_out) class(kinematics_t), intent(inout) :: k type(vector4_t), intent(in), dimension(:) :: p_in type(vector4_t), intent(out), dimension(:), allocatable :: p_out end subroutine kinematics_modify_momenta_for_subtraction <>= module subroutine kinematics_modify_momenta_for_subtraction (k, p_in, p_out) class(kinematics_t), intent(inout) :: k type(vector4_t), intent(in), dimension(:) :: p_in type(vector4_t), intent(out), dimension(:), allocatable :: p_out allocate (p_out (size (p_in))) if (k%threshold) then select type (phs => k%phs) type is (phs_fks_t) p_out = phs%get_onshell_projected_momenta () end select else p_out = p_in end if end subroutine kinematics_modify_momenta_for_subtraction @ %def kinematics_modify_momenta_for_subtraction @ <>= procedure :: threshold_projection => kinematics_threshold_projection <>= module subroutine kinematics_threshold_projection (k, pcm_work, nlo_type) class(kinematics_t), intent(inout) :: k type(pcm_nlo_workspace_t), intent(inout) :: pcm_work integer, intent(in) :: nlo_type end subroutine kinematics_threshold_projection <>= module subroutine kinematics_threshold_projection (k, pcm_work, nlo_type) class(kinematics_t), intent(inout) :: k type(pcm_nlo_workspace_t), intent(inout) :: pcm_work integer, intent(in) :: nlo_type real(default) :: sqrts, mtop type(lorentz_transformation_t) :: L_to_cms type(vector4_t), dimension(:), allocatable :: p_tot, p_onshell integer :: n_tot n_tot = k%phs%get_n_tot () allocate (p_tot (size (pcm_work%real_kinematics%p_born_cms%phs_point(1)))) select type (phs => k%phs) type is (phs_fks_t) p_tot = pcm_work%real_kinematics%p_born_cms%phs_point(1) class default p_tot(1 : k%n_in) = phs%p p_tot(k%n_in + 1 : n_tot) = phs%q end select sqrts = sum (p_tot (1:k%n_in))**1 mtop = m1s_to_mpole (sqrts) L_to_cms = get_boost_for_threshold_projection (p_tot, sqrts, mtop) call pcm_work%real_kinematics%p_born_cms%set_momenta (1, p_tot) p_onshell = pcm_work%real_kinematics%p_born_onshell%phs_point(1) call threshold_projection_born (mtop, L_to_cms, p_tot, p_onshell) pcm_work%real_kinematics%p_born_onshell%phs_point(1) = p_onshell if (debug2_active (D_THRESHOLD)) then print *, 'On-shell projected Born: ' call vector4_write_set (p_onshell) end if end subroutine kinematics_threshold_projection @ %def kinematics_threshold_projection @ <>= procedure :: evaluate_radiation => kinematics_evaluate_radiation <>= module subroutine kinematics_evaluate_radiation (k, p_in, p_out, success) class(kinematics_t), intent(inout) :: k type(vector4_t), intent(in), dimension(:) :: p_in type(vector4_t), intent(out), dimension(:), allocatable :: p_out logical, intent(out) :: success end subroutine kinematics_evaluate_radiation <>= module subroutine kinematics_evaluate_radiation (k, p_in, p_out, success) class(kinematics_t), intent(inout) :: k type(vector4_t), intent(in), dimension(:) :: p_in type(vector4_t), intent(out), dimension(:), allocatable :: p_out logical, intent(out) :: success type(vector4_t), dimension(:), allocatable :: p_real type(vector4_t), dimension(:), allocatable :: p_born real(default) :: xi_max_offshell, xi_offshell, y_offshell, jac_rand_dummy, phi select type (phs => k%phs) type is (phs_fks_t) allocate (p_born (size (p_in))) if (k%threshold) then p_born = phs%get_onshell_projected_momenta () else p_born = p_in end if if (.not. k%phs%lab_is_cm () .and. .not. k%threshold) then p_born = inverse (k%phs%lt_cm_to_lab) * p_born end if call phs%compute_xi_max (p_born, k%threshold) if (k%emitter >= 0) then allocate (p_real (size (p_born) + 1)) allocate (p_out (size (p_born) + 1)) if (k%emitter <= k%n_in) then call phs%generate_isr (k%i_phs, p_real) else if (k%threshold) then jac_rand_dummy = 1._default call compute_y_from_emitter (phs%generator%real_kinematics%x_rad (I_Y), & phs%generator%real_kinematics%p_born_cms%get_momenta(1), & k%n_in, k%emitter, .false., phs%generator%y_max, jac_rand_dummy, & y_offshell) call phs%compute_xi_max (k%emitter, k%i_phs, y_offshell, & phs%generator%real_kinematics%p_born_cms%get_momenta(1), & xi_max_offshell) xi_offshell = xi_max_offshell * phs%generator%real_kinematics%xi_tilde phi = phs%generator%real_kinematics%phi call phs%generate_fsr (k%emitter, k%i_phs, p_real, & xi_y_phi = [xi_offshell, y_offshell, phi], no_jacobians = .true.) call phs%generator%real_kinematics%p_real_cms%set_momenta (k%i_phs, p_real) call phs%generate_fsr_threshold (k%emitter, k%i_phs, p_real) if (debug2_active (D_SUBTRACTION)) & call generate_fsr_threshold_for_other_emitters (k%emitter, k%i_phs) else if (k%i_con > 0) then call phs%generate_fsr (k%emitter, k%i_phs, p_real, k%i_con) else call phs%generate_fsr (k%emitter, k%i_phs, p_real) end if end if success = check_scalar_products (p_real) if (debug2_active (D_SUBTRACTION)) then call msg_debug2 (D_SUBTRACTION, "Real phase-space: ") call vector4_write_set (p_real) end if p_out = p_real else allocate (p_out (size (p_in))); p_out = p_in success = .true. end if end select contains subroutine generate_fsr_threshold_for_other_emitters (emitter, i_phs) integer, intent(in) :: emitter, i_phs integer :: ii_phs, this_emitter select type (phs => k%phs) type is (phs_fks_t) do ii_phs = 1, size (phs%phs_identifiers) this_emitter = phs%phs_identifiers(ii_phs)%emitter if (ii_phs /= i_phs .and. this_emitter /= emitter) & call phs%generate_fsr_threshold (this_emitter, i_phs) end do end select end subroutine end subroutine kinematics_evaluate_radiation @ %def kinematics_evaluate_radiation @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Instances} <<[[instances.f90]]>>= <> module instances <> <> use lorentz use mci_base use particles use sm_qcd, only: qcd_t use quantum_numbers use interactions use model_data use variables use sf_base use pdf, only: pdf_data_t use physics_defs use process_constants use state_matrices use phs_base use prc_core, only: prc_core_t, prc_core_state_t !!! local modules use parton_states use process_counter use pcm_base use pcm use process_config use process_mci use process use kinematics <> <> <> <> interface <> end interface contains <> end module instances @ %def instances @ <<[[instances_sub.f90]]>>= <> submodule (instances) instances_s <> use io_units use format_utils, only: write_separator use constants use diagnostics use numeric_utils use helicities use flavors - use pdg_arrays, only: is_quark + use pdg_arrays, only: is_quark, is_charged_lepton, flv_eqv_expr_class !!! We should depend less on these modules (move it to pcm_nlo_t e.g.) use phs_wood, only: phs_wood_t use phs_fks use blha_olp_interfaces, only: prc_blha_t use blha_config, only: BLHA_AMP_COLOR_C use prc_external, only: prc_external_t, prc_external_state_t use prc_threshold, only: prc_threshold_t use blha_olp_interfaces, only: blha_result_array_size use prc_openloops, only: prc_openloops_t, openloops_state_t use prc_recola, only: prc_recola_t use blha_olp_interfaces, only: blha_color_c_fill_offdiag, blha_color_c_fill_diag use ttv_formfactors, only: m1s_to_mpole implicit none contains <> end submodule instances_s @ %def instances_s @ \subsection{Term instance} A [[term_instance_t]] object contains all data that describe a term. Each process component consists of one or more distinct terms which may differ in kinematics, but whose squared transition matrices have to be added pointwise. The [[active]] flag is set when this term is connected to an active process component. Inactive terms are skipped for kinematics and evaluation. The [[amp]] array stores the amplitude values when we get them from evaluating the associated matrix-element code. The [[int_hard]] interaction describes the elementary hard process. It receives the momenta and the amplitude entries for each sampling point. The [[isolated]] object holds the effective parton state for the elementary interaction. The amplitude entries are computed from [[int_hard]]. The [[connected]] evaluator set convolutes this scattering matrix with the beam (and possibly structure-function) density matrix. The [[checked]] flag is set once we have applied cuts on this term. The result of this is stored in the [[passed]] flag. Although each [[term_instance]] carries a [[weight]], this currently always keeps the value $1$ and is only used to be given to routines to fulfill their signature. <>= type :: term_instance_t type(process_term_t), pointer :: config => null () class(pcm_t), pointer :: pcm => null () class(pcm_workspace_t), pointer :: pcm_work => null () logical :: active = .false. complex(default), dimension(:), allocatable :: amp type(interaction_t) :: int_hard type(isolated_state_t) :: isolated type(connected_state_t) :: connected class(prc_core_state_t), allocatable :: core_state logical :: checked = .false. logical :: passed = .false. + logical, dimension(:), allocatable :: passed_array + integer, dimension(:), allocatable :: i_flv_to_i_flv_rep real(default) :: scale = 0 real(default), allocatable :: fac_scale real(default), allocatable :: ren_scale real(default), allocatable :: es_scale real(default), allocatable :: alpha_qcd_forced real(default) :: weight = 1 type(vector4_t), dimension(:), allocatable :: p_seed type(vector4_t), dimension(:), allocatable :: p_hard integer :: nlo_type = BORN integer, dimension(:), allocatable :: same_kinematics logical :: negative_sf = .false. + logical :: flv_dep_cut_eval = .false. contains <> end type term_instance_t @ %def term_instance_t @ <>= procedure :: write => term_instance_write <>= module subroutine term_instance_write & (term, unit, kin, show_eff_state, testflag) class(term_instance_t), intent(in) :: term integer, intent(in), optional :: unit type(kinematics_t), intent(in), optional :: kin logical, intent(in), optional :: show_eff_state logical, intent(in), optional :: testflag end subroutine term_instance_write <>= module subroutine term_instance_write & (term, unit, kin, show_eff_state, testflag) class(term_instance_t), intent(in) :: term integer, intent(in), optional :: unit type(kinematics_t), intent(in), optional :: kin logical, intent(in), optional :: show_eff_state logical, intent(in), optional :: testflag real(default) :: fac_scale, ren_scale integer :: u logical :: state u = given_output_unit (unit) state = .true.; if (present (show_eff_state)) state = show_eff_state if (term%active) then if (associated (term%config)) then write (u, "(1x,A,I0,A,I0,A)") "Term #", term%config%i_term, & " (component #", term%config%i_component, ")" else write (u, "(1x,A)") "Term [undefined]" end if else write (u, "(1x,A,I0,A)") "Term #", term%config%i_term, & " [inactive]" end if if (term%checked) then write (u, "(3x,A,L1)") "passed cuts = ", term%passed end if if (term%passed) then write (u, "(3x,A,ES19.12)") "overall scale = ", term%scale write (u, "(3x,A,ES19.12)") "factorization scale = ", term%get_fac_scale () write (u, "(3x,A,ES19.12)") "renormalization scale = ", term%get_ren_scale () if (allocated (term%alpha_qcd_forced)) then write (u, "(3x,A,ES19.12)") "alpha(QCD) forced = ", & term%alpha_qcd_forced end if write (u, "(3x,A,ES19.12)") "reweighting factor = ", term%weight end if !!! This used to be a member of term_instance if (present (kin)) then call kin%write (u) end if call write_separator (u) write (u, "(1x,A)") "Amplitude (transition matrix of the & &hard interaction):" call write_separator (u) call term%int_hard%basic_write (u, testflag = testflag) if (state .and. term%isolated%has_trace) then call write_separator (u) write (u, "(1x,A)") "Evaluators for the hard interaction:" call term%isolated%write (u, testflag = testflag) end if if (state .and. term%connected%has_trace) then call write_separator (u) write (u, "(1x,A)") "Evaluators for the connected process:" call term%connected%write (u, testflag = testflag) end if end subroutine term_instance_write @ %def term_instance_write @ The interactions and evaluators must be finalized. <>= procedure :: final => term_instance_final <>= module subroutine term_instance_final (term) class(term_instance_t), intent(inout) :: term end subroutine term_instance_final <>= module subroutine term_instance_final (term) class(term_instance_t), intent(inout) :: term if (allocated (term%amp)) deallocate (term%amp) if (allocated (term%core_state)) deallocate (term%core_state) if (allocated (term%ren_scale)) deallocate (term%ren_scale) if (allocated (term%fac_scale)) deallocate (term%fac_scale) if (allocated (term%es_scale)) deallocate (term%es_scale) if (allocated (term%alpha_qcd_forced)) & deallocate (term%alpha_qcd_forced) if (allocated (term%p_seed)) deallocate(term%p_seed) if (allocated (term%p_hard)) deallocate (term%p_hard) call term%connected%final () call term%isolated%final () call term%int_hard%final () term%pcm => null () term%pcm_work => null () end subroutine term_instance_final @ %def term_instance_final @ For a new term object, we configure the structure-function interface, the phase space, the matrix-element (interaction) interface, etc. <>= procedure :: configure => term_instance_configure <>= module subroutine term_instance_configure & (term_instance, process, i, pcm_work, sf_chain, kin) class(term_instance_t), intent(out), target :: term_instance type(process_t), intent(in), target :: process integer, intent(in) :: i class(pcm_workspace_t), intent(in), target :: pcm_work type(sf_chain_t), intent(in), target :: sf_chain type(kinematics_t), intent(inout), target :: kin end subroutine term_instance_configure <>= module subroutine term_instance_configure & (term_instance, process, i, pcm_work, sf_chain, kin) class(term_instance_t), intent(out), target :: term_instance type(process_t), intent(in), target :: process integer, intent(in) :: i class(pcm_workspace_t), intent(in), target :: pcm_work type(sf_chain_t), intent(in), target :: sf_chain type(kinematics_t), intent(inout), target :: kin type(process_term_t) :: term integer :: i_component logical :: requires_extended_sf term = process%get_term_ptr (i) i_component = term%i_component if (i_component /= 0) then call term_instance%init & (process%get_pcm_ptr (), pcm_work, process%get_nlo_type_component (i_component)) requires_extended_sf = term_instance%nlo_type == NLO_DGLAP .or. & (term_instance%nlo_type == NLO_REAL .and. process%get_i_sub (i) == i) call term_instance%setup_dynamics (process, i, kin, & real_finite = process%component_is_real_finite (i_component)) select type (phs => kin%phs) type is (phs_fks_t) call term_instance%set_emitter (kin) call term_instance%setup_fks_kinematics (kin, & process%get_var_list_ptr (), & process%get_beam_config_ptr ()) end select select type (pcm => term_instance%pcm) type is (pcm_nlo_t) call kin%set_threshold (pcm%settings%factorization_mode) end select call term_instance%setup_expressions (process%get_meta (), process%get_config ()) end if end subroutine term_instance_configure @ %def term_instance_configure @ First part of term-instance configuration: initialize by assigning pointers to the overall [[pcm]] and the associated [[pcm_workspace]] objects. <>= procedure :: init => term_instance_init <>= module subroutine term_instance_init & (term_instance, pcm, pcm_work, nlo_type) class(term_instance_t), intent(out) :: term_instance class(pcm_t), intent(in), target :: pcm class(pcm_workspace_t), intent(in), target :: pcm_work integer, intent(in) :: nlo_type end subroutine term_instance_init <>= module subroutine term_instance_init (term_instance, pcm, pcm_work, nlo_type) class(term_instance_t), intent(out) :: term_instance class(pcm_t), intent(in), target :: pcm class(pcm_workspace_t), intent(in), target :: pcm_work integer, intent(in) :: nlo_type term_instance%pcm => pcm term_instance%pcm_work => pcm_work term_instance%nlo_type = nlo_type end subroutine term_instance_init @ %def term_instance_init @ The second part of term-instance configuration concerns dynamics, i.e., the interface to the matrix-element (interaction), and the parton-state objects that combine all kinematics and matrix-element data for evaluation. The hard interaction (incoming momenta) is linked to the structure function instance. In the isolated state, we either set pointers to both, or we create modified copies ([[rearrange]]) as effective structure-function chain and interaction, respectively. Finally, we set up the [[subevt]] component that will be used for evaluating observables, collecting particles from the trace evaluator in the effective connected state. Their quantum numbers must be determined by following back source links and set explicitly, since they are already eliminated in that trace. The [[rearrange]] parts are still commented out; they could become relevant for a NLO algorithm. <>= procedure :: setup_dynamics => term_instance_setup_dynamics <>= module subroutine term_instance_setup_dynamics & (term, process, i_term, kin, real_finite) class(term_instance_t), intent(inout), target :: term type(process_t), intent(in), target:: process integer, intent(in) :: i_term type(kinematics_t), intent(in) :: kin logical, intent(in), optional :: real_finite end subroutine term_instance_setup_dynamics <>= module subroutine term_instance_setup_dynamics & (term, process, i_term, kin, real_finite) class(term_instance_t), intent(inout), target :: term type(process_t), intent(in), target:: process integer, intent(in) :: i_term type(kinematics_t), intent(in) :: kin logical, intent(in), optional :: real_finite class(prc_core_t), pointer :: core => null () type(process_beam_config_t) :: beam_config type(interaction_t), pointer :: sf_chain_int type(interaction_t), pointer :: src_int type(quantum_numbers_mask_t), dimension(:), allocatable :: mask_in type(state_matrix_t), pointer :: state_matrix type(flavor_t), dimension(:), allocatable :: flv_int, flv_src, f_in, f_out integer, dimension(:,:), allocatable :: flv_born, flv_real type(flavor_t), dimension(:,:), allocatable :: flv_pdf type(quantum_numbers_t), dimension(:,:), allocatable :: qn_pdf integer :: n_in, n_vir, n_out, n_tot, n_sub integer :: n_flv_born, n_flv_real, n_flv_total integer :: i, j logical :: me_already_squared, keep_fs_flavors logical :: decrease_n_tot logical :: requires_extended_sf me_already_squared = .false. keep_fs_flavors = .false. term%config => process%get_term_ptr (i_term) term%int_hard = term%config%int core => process%get_core_term (i_term) term%negative_sf = process%get_negative_sf () call core%allocate_workspace (term%core_state) select type (core) class is (prc_external_t) call reduce_interaction (term%int_hard, & core%includes_polarization (), .true., .false.) me_already_squared = .true. allocate (term%amp (term%int_hard%get_n_matrix_elements ())) class default allocate (term%amp (term%config%n_allowed)) end select if (allocated (term%core_state)) then select type (core_state => term%core_state) type is (openloops_state_t) call core_state%init_threshold (process%get_model_ptr ()) end select end if term%amp = cmplx (0, 0, default) decrease_n_tot = term%nlo_type == NLO_REAL .and. & term%config%i_term_global /= term%config%i_sub if (present (real_finite)) then if (real_finite) decrease_n_tot = .false. end if if (decrease_n_tot) then allocate (term%p_seed (term%int_hard%get_n_tot () - 1)) else allocate (term%p_seed (term%int_hard%get_n_tot ())) end if allocate (term%p_hard (term%int_hard%get_n_tot ())) sf_chain_int => kin%sf_chain%get_out_int_ptr () n_in = term%int_hard%get_n_in () do j = 1, n_in i = kin%sf_chain%get_out_i (j) call term%int_hard%set_source_link (j, sf_chain_int, i) end do call term%isolated%init (kin%sf_chain, term%int_hard) allocate (mask_in (n_in)) mask_in = kin%sf_chain%get_out_mask () select type (phs => kin%phs) type is (phs_wood_t) if (me_already_squared) then call term%isolated%setup_identity_trace & (core, mask_in, .true., .false.) else call term%isolated%setup_square_trace & (core, mask_in, term%config%col, .false.) end if type is (phs_fks_t) select case (phs%mode) case (PHS_MODE_ADDITIONAL_PARTICLE) if (me_already_squared) then call term%isolated%setup_identity_trace & (core, mask_in, .true., .false.) else keep_fs_flavors = term%config%data%n_flv > 1 call term%isolated%setup_square_trace & (core, mask_in, term%config%col, & keep_fs_flavors) end if case (PHS_MODE_COLLINEAR_REMNANT) if (me_already_squared) then call term%isolated%setup_identity_trace & (core, mask_in, .true., .false.) else call term%isolated%setup_square_trace & (core, mask_in, term%config%col, .false.) end if end select class default call term%isolated%setup_square_trace & (core, mask_in, term%config%col, .false.) end select if (term%nlo_type == NLO_VIRTUAL .or. (term%nlo_type == NLO_REAL .and. & term%config%i_term_global == term%config%i_sub) .or. & term%nlo_type == NLO_MISMATCH) then n_sub = term%get_n_sub () else if (term%nlo_type == NLO_DGLAP) then n_sub = n_beams_rescaled + term%get_n_sub () else !!! No integration of real subtraction in interactions yet n_sub = 0 end if keep_fs_flavors = keep_fs_flavors .or. me_already_squared requires_extended_sf = term%nlo_type == NLO_DGLAP .or. & (term%is_subtraction () .and. process%pcm_contains_pdfs ()) call term%connected%setup_connected_trace (term%isolated, & undo_helicities = undo_helicities (core, me_already_squared), & keep_fs_flavors = keep_fs_flavors, & requires_extended_sf = requires_extended_sf) associate (int_eff => term%isolated%int_eff) state_matrix => int_eff%get_state_matrix_ptr () n_tot = int_eff%get_n_tot () flv_int = quantum_numbers_get_flavor & (state_matrix%get_quantum_number (1)) allocate (f_in (n_in)) f_in = flv_int(1:n_in) deallocate (flv_int) end associate n_in = term%connected%trace%get_n_in () n_vir = term%connected%trace%get_n_vir () n_out = term%connected%trace%get_n_out () allocate (f_out (n_out)) do j = 1, n_out call term%connected%trace%find_source & (n_in + n_vir + j, src_int, i) if (associated (src_int)) then state_matrix => src_int%get_state_matrix_ptr () flv_src = quantum_numbers_get_flavor & (state_matrix%get_quantum_number (1)) f_out(j) = flv_src(i) deallocate (flv_src) end if end do beam_config = process%get_beam_config () + select type (pcm => term%pcm) + type is (pcm_nlo_t) + term%flv_dep_cut_eval = pcm%settings%nlo_correction_type == "EW" & + .and. pcm%region_data%alphas_power > 0 & + .and. any(is_charged_lepton(f_out%get_pdg())) + end select call term%connected%setup_subevt (term%isolated%sf_chain_eff, & beam_config%data%flv, f_in, f_out) call term%connected%setup_var_list & (process%get_var_list_ptr (), beam_config%data) ! Does connected%trace never have any helicity qn? call term%init_interaction_qn_index (core, term%connected%trace, n_sub, & process%get_model_ptr (), is_polarized = .false.) call term%init_interaction_qn_index & (core, term%int_hard, n_sub, process%get_model_ptr ()) + call term%init_eqv_expr_classes () if (requires_extended_sf) then select type (pcm => term%pcm) type is (pcm_nlo_t) n_in = pcm%region_data%get_n_in () flv_born = pcm%region_data%get_flv_states_born () flv_real = pcm%region_data%get_flv_states_real () n_flv_born = pcm%region_data%get_n_flv_born () n_flv_real = pcm%region_data%get_n_flv_real () n_flv_total = n_flv_born + n_flv_real allocate (flv_pdf(n_in, n_flv_total), & qn_pdf(n_in, n_flv_total)) call flv_pdf(:, :n_flv_born)%init (flv_born(:n_in, :)) call flv_pdf(:, n_flv_born + 1:n_flv_total)%init (flv_real(:n_in, :)) call qn_pdf%init (flv_pdf) call sf_chain_int%init_qn_index (qn_pdf, n_flv_born, n_flv_real) end select end if contains function undo_helicities (core, me_squared) result (val) logical :: val class(prc_core_t), intent(in) :: core logical, intent(in) :: me_squared select type (core) class is (prc_external_t) val = me_squared .and. .not. core%includes_polarization () class default val = .false. end select end function undo_helicities subroutine reduce_interaction (int, polarized_beams, keep_fs_flavors, & keep_colors) type(interaction_t), intent(inout) :: int logical, intent(in) :: polarized_beams logical, intent(in) :: keep_fs_flavors, keep_colors type(quantum_numbers_mask_t), dimension(:), allocatable :: qn_mask logical, dimension(:), allocatable :: mask_f, mask_c, mask_h integer :: n_tot, n_in n_in = int%get_n_in (); n_tot = int%get_n_tot () allocate (qn_mask (n_tot)) allocate (mask_f (n_tot), mask_c (n_tot), mask_h (n_tot)) mask_c = .not. keep_colors mask_f (1 : n_in) = .false. if (keep_fs_flavors) then mask_f (n_in + 1 : ) = .false. else mask_f (n_in + 1 : ) = .true. end if if (polarized_beams) then mask_h (1 : n_in) = .false. else mask_h (1 : n_in) = .true. end if mask_h (n_in + 1 : ) = .true. call qn_mask%init (mask_f, mask_c, mask_h) call int%reduce_state_matrix (qn_mask, keep_order = .true.) end subroutine reduce_interaction end subroutine term_instance_setup_dynamics @ %def term_instance_setup_dynamics @ Set up index mapping from state matrix to index pair [[i_flv]], [[i_sub]]. <>= public :: setup_interaction_qn_index <>= module subroutine setup_interaction_qn_index & (int, data, qn_config, n_sub, is_polarized) class(interaction_t), intent(inout) :: int class(process_constants_t), intent(in) :: data type(quantum_numbers_t), dimension(:, :), intent(in) :: qn_config integer, intent(in) :: n_sub logical, intent(in) :: is_polarized end subroutine setup_interaction_qn_index <>= module subroutine setup_interaction_qn_index & (int, data, qn_config, n_sub, is_polarized) class(interaction_t), intent(inout) :: int class(process_constants_t), intent(in) :: data type(quantum_numbers_t), dimension(:, :), intent(in) :: qn_config integer, intent(in) :: n_sub logical, intent(in) :: is_polarized integer :: i type(quantum_numbers_t), dimension(:, :), allocatable :: qn_hel if (is_polarized) then call setup_interaction_qn_hel (int, data, qn_hel) call int%init_qn_index (qn_config, n_sub, qn_hel) call int%set_qn_index_helicity_flip (.true.) else call int%init_qn_index (qn_config, n_sub) end if end subroutine setup_interaction_qn_index @ %def setup_interaction_qn_index @ Set up beam polarisation quantum numbers, if beam polarisation is required. We retrieve the full helicity information from [[term%config%data]] and reduce the information only to the inital state. Afterwards, we uniquify the initial state polarization by a applying an index (hash) table. The helicity information is fed into an array of quantum numbers to assign flavor, helicity and subtraction indices correctly to their matrix element. <>= public :: setup_interaction_qn_hel <>= module subroutine setup_interaction_qn_hel (int, data, qn_hel) class(interaction_t), intent(in) :: int class(process_constants_t), intent(in) :: data type(quantum_numbers_t), dimension(:, :), allocatable, intent(out) :: & qn_hel end subroutine setup_interaction_qn_hel <>= module subroutine setup_interaction_qn_hel (int, data, qn_hel) class(interaction_t), intent(in) :: int class(process_constants_t), intent(in) :: data type(quantum_numbers_t), dimension(:, :), allocatable, intent(out) :: & qn_hel type(helicity_t), dimension(:), allocatable :: hel integer, dimension(:), allocatable :: index_table integer, dimension(:, :), allocatable :: hel_state integer :: i, j, n_hel_unique associate (n_in => int%get_n_in (), n_tot => int%get_n_tot ()) allocate (hel_state (n_tot, data%get_n_hel ()), & source = data%hel_state) allocate (index_table (data%get_n_hel ()), & source = 0) forall (j=1:data%get_n_hel (), i=n_in+1:n_tot) hel_state(i, j) = 0 n_hel_unique = 0 HELICITY: do i = 1, data%get_n_hel () do j = 1, data%get_n_hel () if (index_table (j) == 0) then index_table(j) = i; n_hel_unique = n_hel_unique + 1 cycle HELICITY else if (all (hel_state(:, i) == & hel_state(:, index_table(j)))) then cycle HELICITY end if end do end do HELICITY allocate (qn_hel (n_tot, n_hel_unique)) allocate (hel (n_tot)) do j = 1, n_hel_unique call hel%init (hel_state(:, index_table(j))) call qn_hel(:, j)%init (hel) end do end associate end subroutine setup_interaction_qn_hel @ %def setup_interaction_qn_hel +@ Initialization of equivalent cut expression classes. + +Each flavor index [[i_flv]] here is assigned to the corresponding one +representative for an equivalent cut expression class. This class describes +the set of flavor quantum numbers for which the phase space cut expression +evaluation yield the same output. The representative [[i_flv]] for one class +correspond to the first flavor quantum numbers of that kind occuring in the +state matrix. +<>= + procedure :: init_eqv_expr_classes => term_instance_init_eqv_expr_classes +<>= + module subroutine term_instance_init_eqv_expr_classes (term) + class(term_instance_t), intent(inout), target :: term + end subroutine term_instance_init_eqv_expr_classes +<>= + module subroutine term_instance_init_eqv_expr_classes (term) + class(term_instance_t), intent(inout), target :: term + type(interaction_t), pointer :: src_int + type(state_matrix_t), pointer :: state_matrix + type(flavor_t), dimension(:), allocatable :: flv_src + logical, dimension(:,:,:), allocatable :: eqv_expr_class + logical, dimension (:), allocatable :: evaluated + integer :: n_in, n_vir, n_out + integer :: k, j, i + n_in = term%connected%trace%get_n_in () + n_vir = term%connected%trace%get_n_vir () + n_out = term%connected%trace%get_n_out () + allocate (eqv_expr_class (3, n_out, & + term%connected%trace%get_qn_index_n_flv ())) + do k = 1, term%connected%trace%get_qn_index_n_flv () + do j = 1, n_out + call term%connected%trace%find_source & + (n_in + n_vir + j, src_int, i) + if (associated (src_int)) then + state_matrix => src_int%get_state_matrix_ptr () + flv_src = quantum_numbers_get_flavor & + (state_matrix%get_quantum_number (k)) + eqv_expr_class (:, j, k) = flv_eqv_expr_class (flv_src(i)%get_pdg()) + deallocate (flv_src) + end if + end do + end do + if (term%flv_dep_cut_eval) then + allocate (evaluated (term%connected%trace%get_qn_index_n_flv ())) + evaluated = .false. + allocate (term%i_flv_to_i_flv_rep (term%connected%trace%get_qn_index_n_flv ())) + do i = 1, term%connected%trace%get_qn_index_n_flv () + if (.not. evaluated (i)) then + do k = i, term%connected%trace%get_qn_index_n_flv () + if (same_eqv_expr_class(eqv_expr_class (:,:,i), eqv_expr_class (:,:,k))) then + term%i_flv_to_i_flv_rep (k) = i + evaluated (k) = .true. + end if + end do + end if + end do + end if + + contains + + function same_eqv_expr_class (flv_mask1, flv_mask2) result (same) + logical, dimension (:,:), intent(in) :: flv_mask1, flv_mask2 + logical :: same + integer :: l + same = .true. + do l = 1, size (flv_mask1, dim = 2) + same = same .and. all (flv_mask1(:,l) .eqv. flv_mask2(:,l)) + end do + end function same_eqv_expr_class + end subroutine term_instance_init_eqv_expr_classes + +@ %def term_instance_init_eqv_expr_classes @ <>= procedure :: init_interaction_qn_index => & term_instance_init_interaction_qn_index <>= module subroutine term_instance_init_interaction_qn_index (term, core, & int, n_sub, model, is_polarized) class(term_instance_t), intent(inout), target :: term class(prc_core_t), intent(in) :: core class(interaction_t), intent(inout) :: int integer, intent(in) :: n_sub class(model_data_t), intent(in) :: model logical, intent(in), optional :: is_polarized end subroutine term_instance_init_interaction_qn_index <>= module subroutine term_instance_init_interaction_qn_index (term, core, & int, n_sub, model, is_polarized) class(term_instance_t), intent(inout), target :: term class(prc_core_t), intent(in) :: core class(interaction_t), intent(inout) :: int integer, intent(in) :: n_sub class(model_data_t), intent(in) :: model logical, intent(in), optional :: is_polarized logical :: polarized type(quantum_numbers_t), dimension(:, :), allocatable :: qn_config integer, dimension(:,:), allocatable :: flv_born type(flavor_t), dimension(:), allocatable :: flv integer :: i select type (core) class is (prc_external_t) if (present (is_polarized)) then polarized = is_polarized else polarized = core%includes_polarization () end if select type (pcm_work => term%pcm_work) type is (pcm_nlo_workspace_t) associate (is_born => .not. (term%nlo_type == NLO_REAL .and. & .not. term%is_subtraction ())) select type (pcm => term%pcm) type is (pcm_nlo_t) qn_config = pcm%get_qn (is_born) end select call setup_interaction_qn_index (int, term%config%data, & qn_config, n_sub, polarized) end associate class default call term%config%data%get_flv_state (flv_born) allocate (flv (size (flv_born, dim = 1))) allocate (qn_config (size (flv_born, dim = 1), size (flv_born, dim = 2))) do i = 1, core%data%n_flv call flv%init (flv_born(:,i), model) call qn_config(:, i)%init (flv) end do call setup_interaction_qn_index (int, term%config%data, & qn_config, n_sub, polarized) end select class default call int%init_qn_index () end select end subroutine term_instance_init_interaction_qn_index @ %def term_instance_init_interaction_qn_index @ <>= procedure :: setup_fks_kinematics => term_instance_setup_fks_kinematics <>= module subroutine term_instance_setup_fks_kinematics & (term, kin, var_list, beam_config) class(term_instance_t), intent(inout), target :: term type(kinematics_t), intent(inout) :: kin type(var_list_t), intent(in) :: var_list type(process_beam_config_t), intent(in) :: beam_config end subroutine term_instance_setup_fks_kinematics <>= module subroutine term_instance_setup_fks_kinematics & (term, kin, var_list, beam_config) class(term_instance_t), intent(inout), target :: term type(kinematics_t), intent(inout) :: kin type(var_list_t), intent(in) :: var_list type(process_beam_config_t), intent(in) :: beam_config integer :: mode logical :: singular_jacobian if (.not. (term%nlo_type == NLO_REAL .or. term%nlo_type == NLO_DGLAP .or. & term%nlo_type == NLO_MISMATCH)) return singular_jacobian = var_list%get_lval & (var_str ("?powheg_use_singular_jacobian")) if (term%nlo_type == NLO_REAL) then mode = check_generator_mode (GEN_REAL_PHASE_SPACE) else if (term%nlo_type == NLO_MISMATCH) then mode = check_generator_mode (GEN_SOFT_MISMATCH) else mode = PHS_MODE_UNDEFINED end if select type (phs => kin%phs) type is (phs_fks_t) select type (pcm => term%pcm) type is (pcm_nlo_t) select type (pcm_work => term%pcm_work) type is (pcm_nlo_workspace_t) call pcm%setup_phs_generator (pcm_work, & phs%generator, phs%config%sqrts, mode, singular_jacobian) if (beam_config%has_structure_function ()) then pcm_work%isr_kinematics%isr_mode = SQRTS_VAR else pcm_work%isr_kinematics%isr_mode = SQRTS_FIXED end if if (debug_on) call msg_debug & (D_PHASESPACE, "isr_mode: ", pcm_work%isr_kinematics%isr_mode) end select end select class default call msg_fatal ("Phase space should be an FKS phase space!") end select contains function check_generator_mode (gen_mode_default) result (gen_mode) integer :: gen_mode integer, intent(in) :: gen_mode_default select type (pcm => term%pcm) type is (pcm_nlo_t) associate (settings => pcm%settings) if (settings%test_coll_limit .and. settings%test_anti_coll_limit) & call msg_fatal ("You cannot check the collinear and anti-collinear limit "& &"at the same time!") if (settings%test_soft_limit .and. .not. settings%test_coll_limit & .and. .not. settings%test_anti_coll_limit) then gen_mode = GEN_SOFT_LIMIT_TEST else if (.not. settings%test_soft_limit .and. settings%test_coll_limit) then gen_mode = GEN_COLL_LIMIT_TEST else if (.not. settings%test_soft_limit .and. settings%test_anti_coll_limit) then gen_mode = GEN_ANTI_COLL_LIMIT_TEST else if (settings%test_soft_limit .and. settings%test_coll_limit) then gen_mode = GEN_SOFT_COLL_LIMIT_TEST else if (settings%test_soft_limit .and. settings%test_anti_coll_limit) then gen_mode = GEN_SOFT_ANTI_COLL_LIMIT_TEST else gen_mode = gen_mode_default end if end associate end select end function check_generator_mode end subroutine term_instance_setup_fks_kinematics @ %def term_instance_setup_fks_kinematics @ Set up seed kinematics, starting from the MC parameter set given as argument. As a result, the [[k_seed]] kinematics object is evaluated (except for the structure-function matrix-element evaluation, which we postpone until we know the factorization scale), and we have a valid [[p_seed]] momentum array. <>= procedure :: compute_seed_kinematics => term_instance_compute_seed_kinematics <>= module subroutine term_instance_compute_seed_kinematics & (term, kin, mci_work, phs_channel, success) class(term_instance_t), intent(inout), target :: term type(kinematics_t), intent(inout) :: kin type(mci_work_t), intent(in) :: mci_work integer, intent(in) :: phs_channel logical, intent(out) :: success end subroutine term_instance_compute_seed_kinematics <>= module subroutine term_instance_compute_seed_kinematics & (term, kin, mci_work, phs_channel, success) class(term_instance_t), intent(inout), target :: term type(kinematics_t), intent(inout) :: kin type(mci_work_t), intent(in) :: mci_work integer, intent(in) :: phs_channel logical, intent(out) :: success call kin%compute_selected_channel & (mci_work, phs_channel, term%p_seed, success) end subroutine term_instance_compute_seed_kinematics @ %def term_instance_compute_seed_kinematics @ <>= procedure :: evaluate_projections => term_instance_evaluate_projections <>= module subroutine term_instance_evaluate_projections (term, kin) class(term_instance_t), intent(inout) :: term type(kinematics_t), intent(inout) :: kin end subroutine term_instance_evaluate_projections <>= module subroutine term_instance_evaluate_projections (term, kin) class(term_instance_t), intent(inout) :: term type(kinematics_t), intent(inout) :: kin if (kin%threshold .and. term%nlo_type > BORN) then if (debug2_active (D_THRESHOLD)) & print *, 'Evaluate on-shell projection: ', & char (component_status (term%nlo_type)) select type (pcm_work => term%pcm_work) type is (pcm_nlo_workspace_t) call kin%threshold_projection (pcm_work, term%nlo_type) end select end if end subroutine term_instance_evaluate_projections @ %def term_instance_evaluate_projections @ Compute the momenta in the hard interactions, one for each term that constitutes this process component. In simple cases this amounts to just copying momenta. In more advanced cases, we may generate distinct sets of momenta from the seed kinematics. The interactions in the term instances are accessed individually. We may choose to calculate all terms at once together with the seed kinematics, use [[component%core_state]] for storage, and just fill the interactions here. <>= procedure :: compute_hard_kinematics => & term_instance_compute_hard_kinematics <>= module subroutine term_instance_compute_hard_kinematics & (term, kin, recover, skip_term, success) class(term_instance_t), intent(inout) :: term type(kinematics_t), intent(inout) :: kin integer, intent(in), optional :: skip_term logical, intent(in), optional :: recover logical, intent(out) :: success end subroutine term_instance_compute_hard_kinematics <>= module subroutine term_instance_compute_hard_kinematics & (term, kin, recover, skip_term, success) class(term_instance_t), intent(inout) :: term type(kinematics_t), intent(inout) :: kin integer, intent(in), optional :: skip_term logical, intent(in), optional :: recover logical, intent(out) :: success type(vector4_t), dimension(:), allocatable :: p if (allocated (term%core_state)) & call term%core_state%reset_new_kinematics () if (present (skip_term)) then if (term%config%i_term_global == skip_term) return end if if (present (recover)) then if (recover) return end if if (term%nlo_type == NLO_REAL .and. kin%emitter >= 0) then call kin%evaluate_radiation (term%p_seed, p, success) select type (pcm => term%pcm) type is (pcm_nlo_t) if (pcm%dalitz_plot%active) then if (kin%emitter > kin%n_in) then if (p(kin%emitter)**2 > tiny_07) & call pcm%register_dalitz_plot (kin%emitter, p) end if end if end select else if (is_subtraction_component (kin%emitter, term%nlo_type)) then call kin%modify_momenta_for_subtraction (term%p_seed, p) success = .true. else allocate (p (size (term%p_seed))); p = term%p_seed success = .true. end if call term%int_hard%set_momenta (p) if (debug_on) then call msg_debug2 (D_REAL, "inside compute_hard_kinematics") if (debug2_active (D_REAL)) call vector4_write_set (p) end if end subroutine term_instance_compute_hard_kinematics @ %def term_instance_compute_hard_kinematics @ Here, we invert this. We fetch the incoming momenta which reside in the appropriate [[sf_chain]] object, stored within the [[k_seed]] subobject. On the other hand, we have the outgoing momenta of the effective interaction. We rely on the process core to compute the remaining seed momenta and to fill the momenta within the hard interaction. (The latter is trivial if hard and effective interaction coincide.) After this is done, the incoming momenta in the trace evaluator that corresponds to the hard (effective) interaction, are still left undefined. We remedy this by calling [[receive_kinematics]] once. <>= procedure :: recover_seed_kinematics => & term_instance_recover_seed_kinematics <>= module subroutine term_instance_recover_seed_kinematics & (term, kin, p_seed_ref) class(term_instance_t), intent(inout) :: term type(kinematics_t), intent(in) :: kin type(vector4_t), dimension(:), intent(in), optional :: p_seed_ref end subroutine term_instance_recover_seed_kinematics <>= module subroutine term_instance_recover_seed_kinematics & (term, kin, p_seed_ref) class(term_instance_t), intent(inout) :: term type(kinematics_t), intent(in) :: kin integer :: n_in type(vector4_t), dimension(:), intent(in), optional :: p_seed_ref n_in = kin%n_in call kin%get_incoming_momenta (term%p_seed(1:n_in)) associate (int_eff => term%isolated%int_eff) call int_eff%set_momenta (term%p_seed(1:n_in), outgoing = .false.) if (present (p_seed_ref)) then term%p_seed(n_in + 1 : ) = p_seed_ref else term%p_seed(n_in + 1 : ) = int_eff%get_momenta (outgoing = .true.) end if end associate call term%isolated%receive_kinematics () end subroutine term_instance_recover_seed_kinematics @ %def term_instance_recover_seed_kinematics @ Compute the integration parameters for all channels except the selected one. JRR: Obsolete now. <>= procedure :: compute_other_channels => & term_instance_compute_other_channels <>= subroutine term_instance_compute_other_channels & (term, mci_work, phs_channel) class(term_instance_t), intent(inout), target :: term type(mci_work_t), intent(in) :: mci_work integer, intent(in) :: phs_channel call term%k_term%compute_other_channels (mci_work, phs_channel) end subroutine term_instance_compute_other_channels @ %def term_instance_compute_other_channels @ Recover beam momenta, i.e., return the beam momenta as currently stored in the kinematics subobject to their source. This is a side effect. JRR: Obsolete now. <>= procedure :: return_beam_momenta => term_instance_return_beam_momenta <>= subroutine term_instance_return_beam_momenta (term) class(term_instance_t), intent(in) :: term call term%k_term%return_beam_momenta () end subroutine term_instance_return_beam_momenta @ %def term_instance_return_beam_momenta @ Applies the real partition by computing the real partition function $F(\Phi)$ and multiplying either $\mathcal{R}_\text{sin} = \mathcal{R} \cdot F$ or $\mathcal{R}_\text{fin} = \mathcal{R} \cdot (1-F)$. <>= procedure :: apply_real_partition => term_instance_apply_real_partition <>= module subroutine term_instance_apply_real_partition (term, kin) class(term_instance_t), intent(inout) :: term type(kinematics_t), intent(in) :: kin end subroutine term_instance_apply_real_partition <>= module subroutine term_instance_apply_real_partition (term, kin) class(term_instance_t), intent(inout) :: term type(kinematics_t), intent(in) :: kin real(default) :: f, sqme integer :: i_component integer :: i_amp, n_amps, qn_index logical :: is_subtraction i_component = term%config%i_component select type (pcm => term%pcm) type is (pcm_nlo_t) if (pcm%component_selected (i_component) .and. & pcm%nlo_type (i_component) == NLO_REAL) then is_subtraction = pcm%component_type (i_component) == & COMP_REAL_SING .and. kin%emitter < 0 if (is_subtraction) return select case (pcm%component_type (i_component)) case (COMP_REAL_FIN) call term%connected%trace%set_duplicate_flv_zero() end select f = pcm%real_partition%get_f (term%p_hard) n_amps = term%connected%trace%get_n_matrix_elements () do i_amp = 1, n_amps qn_index = term%connected%trace%get_qn_index (i_amp, i_sub = 0) - sqme = real (term%connected%trace%get_matrix_element (qn_index)) + if (term%passed_array(i_amp) .or. .not. term%passed) then + sqme = real (term%connected%trace%get_matrix_element (qn_index)) + else + sqme = zero + end if if (debug_on) call msg_debug2 & (D_PROCESS_INTEGRATION, "term_instance_apply_real_partition") select case (pcm%component_type (i_component)) case (COMP_REAL_FIN) if (debug_on) call msg_debug2 & (D_PROCESS_INTEGRATION, "Real finite") sqme = sqme * (one - f) case (COMP_REAL_SING) if (debug_on) call msg_debug2 & (D_PROCESS_INTEGRATION, "Real singular") sqme = sqme * f end select if (debug_on) call msg_debug2 & (D_PROCESS_INTEGRATION, "apply_damping: sqme", sqme) call term%connected%trace%set_matrix_element & (qn_index, cmplx (sqme, zero, default)) end do end if end select end subroutine term_instance_apply_real_partition @ %def term_instance_apply_real_partition @ <>= procedure :: get_p_hard => term_instance_get_p_hard <>= pure module function term_instance_get_p_hard & (term_instance) result (p_hard) type(vector4_t), dimension(:), allocatable :: p_hard class(term_instance_t), intent(in) :: term_instance end function term_instance_get_p_hard <>= pure module function term_instance_get_p_hard (term_instance) result (p_hard) type(vector4_t), dimension(:), allocatable :: p_hard class(term_instance_t), intent(in) :: term_instance allocate (p_hard (size (term_instance%p_hard))) p_hard = term_instance%p_hard end function term_instance_get_p_hard @ %def term_instance_get_p_hard @ <>= procedure :: set_emitter => term_instance_set_emitter <>= module subroutine term_instance_set_emitter (term, kin) class(term_instance_t), intent(inout) :: term type(kinematics_t), intent(inout) :: kin end subroutine term_instance_set_emitter <>= module subroutine term_instance_set_emitter (term, kin) class(term_instance_t), intent(inout) :: term type(kinematics_t), intent(inout) :: kin integer :: i_phs logical :: set_emitter select type (pcm => term%pcm) type is (pcm_nlo_t) select type (phs => kin%phs) type is (phs_fks_t) !!! Without resonances, i_alr = i_phs i_phs = term%config%i_term kin%i_phs = i_phs set_emitter = i_phs <= pcm%region_data%n_phs .and. & term%nlo_type == NLO_REAL if (set_emitter) then kin%emitter = phs%phs_identifiers(i_phs)%emitter select type (pcm => term%pcm) type is (pcm_nlo_t) if (allocated (pcm%region_data%i_phs_to_i_con)) & kin%i_con = pcm%region_data%i_phs_to_i_con (i_phs) end select end if end select end select end subroutine term_instance_set_emitter @ %def term_instance_set_emitter @ For initializing the expressions, we need the local variable list and the parse trees. <>= procedure :: setup_expressions => term_instance_setup_expressions <>= module subroutine term_instance_setup_expressions (term, meta, config) class(term_instance_t), intent(inout), target :: term type(process_metadata_t), intent(in), target :: meta type(process_config_data_t), intent(in) :: config end subroutine term_instance_setup_expressions <>= module subroutine term_instance_setup_expressions (term, meta, config) class(term_instance_t), intent(inout), target :: term type(process_metadata_t), intent(in), target :: meta type(process_config_data_t), intent(in) :: config if (allocated (config%ef_cuts)) & call term%connected%setup_cuts (config%ef_cuts) if (allocated (config%ef_scale)) & call term%connected%setup_scale (config%ef_scale) if (allocated (config%ef_fac_scale)) & call term%connected%setup_fac_scale (config%ef_fac_scale) if (allocated (config%ef_ren_scale)) & call term%connected%setup_ren_scale (config%ef_ren_scale) if (allocated (config%ef_weight)) & call term%connected%setup_weight (config%ef_weight) end subroutine term_instance_setup_expressions @ %def term_instance_setup_expressions @ Prepare the extra evaluators that we need for processing events. The matrix elements we get from OpenLoops and GoSam are already squared and summed over color and helicity. They should not be squared again. <>= procedure :: setup_event_data => term_instance_setup_event_data <>= module subroutine term_instance_setup_event_data (term, kin, core, model) class(term_instance_t), intent(inout), target :: term type(kinematics_t), intent(in) :: kin class(prc_core_t), intent(in) :: core class(model_data_t), intent(in), target :: model end subroutine term_instance_setup_event_data <>= module subroutine term_instance_setup_event_data (term, kin, core, model) class(term_instance_t), intent(inout), target :: term type(kinematics_t), intent(in) :: kin class(prc_core_t), intent(in) :: core class(model_data_t), intent(in), target :: model integer :: n_in logical :: mask_color type(quantum_numbers_mask_t), dimension(:), allocatable :: mask_in n_in = term%int_hard%get_n_in () allocate (mask_in (n_in)) mask_in = kin%sf_chain%get_out_mask () call setup_isolated (term%isolated, core, model, mask_in, term%config%col) select type (pcm_work => term%pcm_work) type is (pcm_nlo_workspace_t) mask_color = pcm_work%is_fixed_order_nlo_events () class default mask_color = .false. end select call setup_connected (term%connected, term%isolated, core, & term%nlo_type, mask_color) contains subroutine setup_isolated (isolated, core, model, mask, color) type(isolated_state_t), intent(inout), target :: isolated class(prc_core_t), intent(in) :: core class(model_data_t), intent(in), target :: model type(quantum_numbers_mask_t), intent(in), dimension(:) :: mask integer, intent(in), dimension(:) :: color select type (core) class is (prc_blha_t) call isolated%matrix%init_identity(isolated%int_eff) isolated%has_matrix = .true. class default call isolated%setup_square_matrix (core, model, mask, color) end select !!! TODO (PS-09-10-20) We should not square the flows !!! if they come from BLHA either call isolated%setup_square_flows (core, model, mask) end subroutine setup_isolated subroutine setup_connected (connected, isolated, core, nlo_type, mask_color) type(connected_state_t), intent(inout), target :: connected type(isolated_state_t), intent(in), target :: isolated class(prc_core_t), intent(in) :: core integer, intent(in) :: nlo_type logical, intent(in) :: mask_color type(quantum_numbers_mask_t), dimension(:), allocatable :: mask call connected%setup_connected_matrix (isolated) if (term%nlo_type == NLO_VIRTUAL .or. (term%nlo_type == NLO_REAL & .and. term%config%i_term_global == term%config%i_sub) & .or. term%nlo_type == NLO_DGLAP) then !!! We do not care about the subtraction matrix elements in !!! connected%matrix, because all entries there are supposed !!! to be squared. To be able to match with flavor quantum numbers, !!! we remove the subtraction quantum entries from the state matrix. allocate (mask (connected%matrix%get_n_tot())) call mask%set_sub (1) call connected%matrix%reduce_state_matrix (mask, keep_order = .true.) end if call term%init_interaction_qn_index (core, connected%matrix, 0, model, & is_polarized = .false.) select type (core) class is (prc_blha_t) call connected%setup_connected_flows & (isolated, mask_color = mask_color) class default call connected%setup_connected_flows (isolated) end select call connected%setup_state_flv (isolated%get_n_out ()) end subroutine setup_connected end subroutine term_instance_setup_event_data @ %def term_instance_setup_event_data @ Color-correlated matrix elements should be obtained from the external BLHA provider. According to the standard, the matrix elements output is a one-dimensional array. For FKS subtraction, we require the matrix $B_{ij}$. BLHA prescribes a mapping $(i, j) \to k$, where $k$ is the index of the matrix element in the output array. It focusses on the off-diagonal entries, i.e. $i \neq j$. The subroutine [[blha_color_c_fill_offdiag]] realizes this mapping. The diagonal entries can simply be obtained as the product of the Born matrix element and either $C_A$ or $C_F$, which is achieved by [[blha_color_c_fill_diag]]. For simple processes, i.e. those with only one color line, it is $B_{ij} = C_F \cdot B$. For those, we keep the possibility of computing color correlations by a multiplication of the Born matrix element with $C_F$. It is triggered by the [[use_internal_color_correlations]] flag and should be used only for testing purposes. However, it is also used for the threshold computation where the process is well-defined and fixed. <>= procedure :: evaluate_color_correlations => & term_instance_evaluate_color_correlations <>= module subroutine term_instance_evaluate_color_correlations (term, core) class(term_instance_t), intent(inout) :: term class(prc_core_t), intent(inout) :: core end subroutine term_instance_evaluate_color_correlations <>= module subroutine term_instance_evaluate_color_correlations (term, core) class(term_instance_t), intent(inout) :: term class(prc_core_t), intent(inout) :: core integer :: i_flv_born select type (pcm_work => term%pcm_work) type is (pcm_nlo_workspace_t) select type (pcm => term%pcm) type is (pcm_nlo_t) if (debug_on) call msg_debug2 (D_SUBTRACTION, & "term_instance_evaluate_color_correlations: " // & "use_internal_color_correlations:", & pcm%settings%use_internal_color_correlations) if (debug_on) call msg_debug2 (D_SUBTRACTION, "fac_scale", term%get_fac_scale ()) do i_flv_born = 1, pcm%region_data%n_flv_born select case (term%nlo_type) case (NLO_REAL) call transfer_me_array_to_bij (pcm, i_flv_born, & pcm_work%real_sub%sqme_born (i_flv_born), & pcm_work%real_sub%sqme_born_color_c (:, :, i_flv_born)) case (NLO_MISMATCH) call transfer_me_array_to_bij (pcm, i_flv_born, & pcm_work%soft_mismatch%sqme_born (i_flv_born), & pcm_work%soft_mismatch%sqme_born_color_c (:, :, i_flv_born)) case (NLO_VIRTUAL) !!! This is just a copy of the above with a different offset and can for sure be unified call transfer_me_array_to_bij (pcm, i_flv_born, & -one, pcm_work%virtual%sqme_color_c (:, :, i_flv_born)) case (NLO_DGLAP) call transfer_me_array_to_bij (pcm, i_flv_born, & pcm_work%dglap_remnant%sqme_born (i_flv_born), & pcm_work%dglap_remnant%sqme_color_c_extra (:, :, i_flv_born)) end select end do end select end select contains function get_trivial_cf_factors (n_tot, flv, factorization_mode) result (beta_ij) integer, intent(in) :: n_tot, factorization_mode integer, intent(in), dimension(:) :: flv real(default), dimension(n_tot, n_tot) :: beta_ij if (factorization_mode == NO_FACTORIZATION) then beta_ij = get_trivial_cf_factors_default (n_tot, flv) else beta_ij = get_trivial_cf_factors_threshold (n_tot, flv) end if end function get_trivial_cf_factors function get_trivial_cf_factors_default (n_tot, flv) result (beta_ij) integer, intent(in) :: n_tot integer, intent(in), dimension(:) :: flv real(default), dimension(n_tot, n_tot) :: beta_ij integer :: i, j beta_ij = zero if (count (is_quark (flv)) == 2) then do i = 1, n_tot do j = 1, n_tot if (is_quark(flv(i)) .and. is_quark(flv(j))) then if (i == j) then beta_ij(i,j)= -cf else beta_ij(i,j) = cf end if end if end do end do end if end function get_trivial_cf_factors_default function get_trivial_cf_factors_threshold (n_tot, flv) result (beta_ij) integer, intent(in) :: n_tot integer, intent(in), dimension(:) :: flv real(default), dimension(n_tot, n_tot) :: beta_ij integer :: i beta_ij = zero do i = 1, 4 beta_ij(i,i) = -cf end do beta_ij(1,2) = cf; beta_ij(2,1) = cf beta_ij(3,4) = cf; beta_ij(4,3) = cf end function get_trivial_cf_factors_threshold subroutine transfer_me_array_to_bij (pcm, i_flv, & sqme_born, sqme_color_c) type(pcm_nlo_t), intent(in) :: pcm integer, intent(in) :: i_flv real(default), intent(in) :: sqme_born real(default), dimension(:,:), intent(inout) :: sqme_color_c logical :: special_case_interferences - integer :: i_color_c, i_sub, n_offset + integer :: i_color_c, i_sub, n_offset, i_qn real(default), dimension(:), allocatable :: sqme + real(default) :: sqme_born_c if (debug_on) call msg_debug2 (D_PROCESS_INTEGRATION, "transfer_me_array_to_bij") if (pcm%settings%use_internal_color_correlations) then !!! A negative value for sqme_born indicates that the Born matrix !!! element is multiplied at a different place, e.g. in the case !!! of the virtual component sqme_color_c = get_trivial_cf_factors & (pcm%region_data%get_n_legs_born (), & pcm%region_data%get_flv_states_born (i_flv), & pcm%settings%factorization_mode) if (sqme_born > zero) then sqme_color_c = sqme_born * sqme_color_c else if (sqme_born == zero) then sqme_color_c = zero end if else special_case_interferences = & pcm%region_data%nlo_correction_type == "EW" n_offset = 0 if (term%nlo_type == NLO_VIRTUAL) then n_offset = 1 else if (pcm%has_pdfs .and. (term%is_subtraction () & .or. term%nlo_type == NLO_DGLAP)) then n_offset = n_beams_rescaled end if allocate (sqme (term%get_n_sub_color ()), source = zero) do i_sub = 1, term%get_n_sub_color () - sqme(i_sub) = real(term%connected%trace%get_matrix_element ( & - term%connected%trace%get_qn_index & - (i_flv, i_sub = i_sub + n_offset)), default) + i_qn = term%connected%trace%get_qn_index (i_flv, i_sub = i_sub + n_offset) + if (term%passed_array(i_flv) .or. .not. term%passed) then + sqme(i_sub) = real(term%connected%trace%get_matrix_element (i_qn), default) + else + sqme(i_sub) = zero + end if end do call blha_color_c_fill_offdiag (pcm%region_data%n_legs_born, & sqme, sqme_color_c) - call blha_color_c_fill_diag & - (real(term%connected%trace%get_matrix_element ( & - term%connected%trace%get_qn_index (i_flv, i_sub = 0)), default), & + i_qn = term%connected%trace%get_qn_index (i_flv, i_sub = 0) + if (term%passed_array(i_flv) .or. .not. term%passed) then + sqme_born_c = real(term%connected%trace%get_matrix_element (i_qn), default) + else + sqme_born_c = zero + end if + call blha_color_c_fill_diag (sqme_born_c, & pcm%region_data%get_flv_states_born (i_flv), & sqme_color_c, special_case_interferences) end if end subroutine transfer_me_array_to_bij end subroutine term_instance_evaluate_color_correlations @ %def term_instance_evaluate_color_correlations @ <>= procedure :: evaluate_charge_correlations => & term_instance_evaluate_charge_correlations <>= module subroutine term_instance_evaluate_charge_correlations (term, core) class(term_instance_t), intent(inout) :: term class(prc_core_t), intent(inout) :: core end subroutine term_instance_evaluate_charge_correlations <>= module subroutine term_instance_evaluate_charge_correlations (term, core) class(term_instance_t), intent(inout) :: term class(prc_core_t), intent(inout) :: core integer :: i_flv_born select type (pcm_work => term%pcm_work) type is (pcm_nlo_workspace_t) select type (pcm => term%pcm) type is (pcm_nlo_t) do i_flv_born = 1, pcm%region_data%n_flv_born select case (term%nlo_type) case (NLO_REAL) call transfer_me_array_to_bij (pcm, i_flv_born, & pcm_work%real_sub%sqme_born (i_flv_born), & pcm_work%real_sub%sqme_born_charge_c (:, :, i_flv_born)) case (NLO_MISMATCH) call transfer_me_array_to_bij (pcm, i_flv_born, & pcm_work%soft_mismatch%sqme_born (i_flv_born), & pcm_work%soft_mismatch%sqme_born_charge_c (:, :, i_flv_born)) case (NLO_VIRTUAL) call transfer_me_array_to_bij (pcm, i_flv_born, & one, pcm_work%virtual%sqme_charge_c (:, :, i_flv_born)) end select end do end select end select contains subroutine transfer_me_array_to_bij (pcm, i_flv, sqme_born, sqme_charge_c) type(pcm_nlo_t), intent(in) :: pcm integer, intent(in) :: i_flv real(default), intent(in) :: sqme_born real(default), dimension(:,:), intent(inout) :: sqme_charge_c integer :: n_legs_born, i, j real(default), dimension(:), allocatable :: sigma real(default), dimension(:), allocatable :: Q n_legs_born = pcm%region_data%n_legs_born associate (flv_born => pcm%region_data%flv_born(i_flv)) allocate (sigma (n_legs_born), Q (size (flv_born%charge))) Q = flv_born%charge sigma(1:flv_born%n_in) = -one sigma(flv_born%n_in + 1: ) = one end associate do i = 1, n_legs_born do j = 1, n_legs_born sqme_charge_c(i, j) = sigma(i) * sigma(j) * Q(i) * Q(j) * (-one) end do end do sqme_charge_c = sqme_charge_c * sqme_born end subroutine transfer_me_array_to_bij end subroutine term_instance_evaluate_charge_correlations @ %def term_instance_evaluate_charge_correlations @ The information about spin correlations is not stored in the [[nlo_settings]] because it is only available after the [[fks_regions]] have been created. <>= procedure :: evaluate_spin_correlations => & term_instance_evaluate_spin_correlations <>= module subroutine term_instance_evaluate_spin_correlations (term, core) class(term_instance_t), intent(inout) :: term class(prc_core_t), intent(inout) :: core end subroutine term_instance_evaluate_spin_correlations <>= module subroutine term_instance_evaluate_spin_correlations (term, core) class(term_instance_t), intent(inout) :: term class(prc_core_t), intent(inout) :: core - integer :: i_flv, i_sub, i_emitter, emitter + integer :: i_flv, i_sub, i_emitter, emitter, i_qn integer :: n_flv, n_sub_color, n_sub_spin, n_offset,i,j real(default), dimension(1:3, 1:3) :: sqme_spin_c real(default), dimension(:), allocatable :: sqme_spin_c_all real(default), dimension(:), allocatable :: sqme_spin_c_arr if (debug_on) call msg_debug2 (D_PROCESS_INTEGRATION, & "term_instance_evaluate_spin_correlations") select type (pcm_work => term%pcm_work) type is (pcm_nlo_workspace_t) if (pcm_work%real_sub%requires_spin_correlations () & .and. term%nlo_type == NLO_REAL) then select type (core) type is (prc_openloops_t) select type (pcm => term%pcm) type is (pcm_nlo_t) n_flv = term%connected%trace%get_qn_index_n_flv () n_sub_color = term%get_n_sub_color () n_sub_spin = term%get_n_sub_spin () n_offset = 0; if(pcm%has_pdfs) n_offset = n_beams_rescaled allocate (sqme_spin_c_arr(6)) do i_flv = 1, n_flv allocate (sqme_spin_c_all(n_sub_spin)) do i_sub = 1, n_sub_spin - sqme_spin_c_all(i_sub) = real(term%connected%trace%get_matrix_element & - (term%connected%trace%get_qn_index (i_flv, & - i_sub = i_sub + n_offset + n_sub_color)), default) + i_qn = term%connected%trace%get_qn_index (i_flv, & + i_sub = i_sub + n_offset + n_sub_color) + if (term%passed_array(i_flv) .or. .not. term%passed) then + sqme_spin_c_all(i_sub) = & + real(term%connected%trace%get_matrix_element (i_qn), default) + else + sqme_spin_c_all(i_sub) = zero + end if end do do i_emitter = 1, pcm%region_data%n_emitters emitter = pcm%region_data%emitters(i_emitter) if (emitter > 0) then call split_array (sqme_spin_c_all, sqme_spin_c_arr) do j = 1, size (sqme_spin_c, dim=2) do i = j, size (sqme_spin_c, dim=1) !!! Restoring the symmetric matrix packed into a 1-dim array !!! c.f. [[prc_openloops_compute_sqme_spin_c]] sqme_spin_c(i,j) = sqme_spin_c_arr(j + i * (i - 1) / 2) if (i /= j) sqme_spin_c(j,i) = sqme_spin_c(i,j) end do end do pcm_work%real_sub%sqme_born_spin_c(:,:,emitter,i_flv) = sqme_spin_c end if end do deallocate (sqme_spin_c_all) end do end select class default call msg_fatal & ("Spin correlations so far only supported by OpenLoops.") end select end if end select end subroutine term_instance_evaluate_spin_correlations @ %def term_instance_evaluate_spin_correlations @ <>= procedure :: apply_fks => term_instance_apply_fks <>= module subroutine term_instance_apply_fks & (term, kin, alpha_s_sub, alpha_qed_sub) class(term_instance_t), intent(inout) :: term class(kinematics_t), intent(inout) :: kin real(default), intent(in) :: alpha_s_sub, alpha_qed_sub end subroutine term_instance_apply_fks <>= module subroutine term_instance_apply_fks & (term, kin, alpha_s_sub, alpha_qed_sub) class(term_instance_t), intent(inout) :: term class(kinematics_t), intent(inout) :: kin real(default), intent(in) :: alpha_s_sub, alpha_qed_sub real(default), dimension(:), allocatable :: sqme - integer :: i, i_phs, emitter + integer :: i, i_phs, emitter, i_qn logical :: is_subtraction select type (pcm_work => term%pcm_work) type is (pcm_nlo_workspace_t) select type (pcm => term%pcm) type is (pcm_nlo_t) if (term%connected%has_matrix) then allocate (sqme (pcm%get_n_alr ())) else allocate (sqme (1)) end if sqme = zero select type (phs => kin%phs) type is (phs_fks_t) if (pcm%has_pdfs .and. & pcm%settings%use_internal_color_correlations) then call msg_fatal ("Color correlations for proton processes " // & "so far only supported by OpenLoops.") end if call pcm_work%set_real_and_isr_kinematics & (phs%phs_identifiers, kin%phs%get_sqrts ()) if (kin%emitter < 0) then call pcm_work%set_subtraction_event () do i_phs = 1, pcm%region_data%n_phs emitter = phs%phs_identifiers(i_phs)%emitter call pcm_work%real_sub%compute (emitter, & i_phs, alpha_s_sub, alpha_qed_sub, term%connected%has_matrix, sqme) end do else call pcm_work%set_radiation_event () emitter = kin%emitter; i_phs = kin%i_phs do i = 1, term%connected%trace%get_qn_index_n_flv () - pcm_work%real_sub%sqme_real_non_sub (i, i_phs) = & - real (term%connected%trace%get_matrix_element ( & - term%connected%trace%get_qn_index (i))) + i_qn = term%connected%trace%get_qn_index (i) + if (term%passed_array(i) .or. .not. term%passed) then + pcm_work%real_sub%sqme_real_non_sub (i, i_phs) = & + real (term%connected%trace%get_matrix_element (i_qn)) + else + pcm_work%real_sub%sqme_real_non_sub (i, i_phs) = zero + end if end do call pcm_work%real_sub%compute (emitter, i_phs, alpha_s_sub, & alpha_qed_sub, term%connected%has_matrix, sqme) end if end select end select end select if (term%connected%has_trace) & call term%connected%trace%set_only_matrix_element & (1, cmplx (sum(sqme), 0, default)) select type (pcm => term%pcm) type is (pcm_nlo_t) is_subtraction = kin%emitter < 0 if (term%connected%has_matrix) & call refill_evaluator (cmplx (sqme * term%weight, 0, default), & pcm%get_qn (is_subtraction), & pcm%region_data%get_flavor_indices (is_subtraction), & term%connected%matrix) if (term%connected%has_flows) & call refill_evaluator (cmplx (sqme * term%weight, 0, default), & pcm%get_qn (is_subtraction), & pcm%region_data%get_flavor_indices (is_subtraction), & term%connected%flows) end select end subroutine term_instance_apply_fks @ %def term_instance_apply_fks @ <>= procedure :: evaluate_sqme_virt => term_instance_evaluate_sqme_virt <>= module subroutine term_instance_evaluate_sqme_virt & (term, alpha_s, alpha_qed) class(term_instance_t), intent(inout) :: term real(default), intent(in) :: alpha_s, alpha_qed end subroutine term_instance_evaluate_sqme_virt <>= module subroutine term_instance_evaluate_sqme_virt (term, alpha_s, alpha_qed) class(term_instance_t), intent(inout) :: term real(default), intent(in) :: alpha_s, alpha_qed real(default), dimension(2) :: alpha_coupling type(vector4_t), dimension(:), allocatable :: p_born real(default), dimension(:), allocatable :: sqme_virt - integer :: i_flv + integer :: i_flv, i_qn_born, i_qn_virt if (term%nlo_type /= NLO_VIRTUAL) call msg_fatal ("Trying to " // & "evaluate virtual matrix element with unsuited term_instance.") if (debug2_active (D_VIRTUAL)) then call msg_debug2 & (D_VIRTUAL, "Evaluating virtual-subtracted matrix elements") print *, 'ren_scale: ', term%get_ren_scale () print *, 'fac_scale: ', term%get_fac_scale () if (allocated (term%es_scale)) then print *, 'ES scale: ', term%es_scale else print *, 'ES scale: ', term%get_ren_scale () end if end if select type (pcm => term%pcm) type is (pcm_nlo_t) select type (pcm_work => term%pcm_work) type is (pcm_nlo_workspace_t) alpha_coupling = [alpha_s, alpha_qed] if (debug2_active (D_VIRTUAL)) then print *, 'alpha_s: ', alpha_coupling (1) print *, 'alpha_qed: ', alpha_coupling (2) end if allocate (p_born (pcm%region_data%n_legs_born)) if (pcm%settings%factorization_mode == FACTORIZATION_THRESHOLD) then p_born = pcm_work%real_kinematics%p_born_onshell%get_momenta(1) else p_born = term%int_hard%get_momenta () end if call pcm_work%set_momenta_and_scales_virtual & (p_born, term%ren_scale, term%get_fac_scale (), & term%es_scale) select type (pcm_work => term%pcm_work) type is (pcm_nlo_workspace_t) associate (virtual => pcm_work%virtual) do i_flv = 1, term%connected%trace%get_qn_index_n_flv () - virtual%sqme_born(i_flv) = & - real (term%connected%trace%get_matrix_element ( & - term%connected%trace%get_qn_index (i_flv, i_sub = 0))) - virtual%sqme_virt_fin(i_flv) = & - real (term%connected%trace%get_matrix_element ( & - term%connected%trace%get_qn_index (i_flv, i_sub = 1))) + i_qn_born = term%connected%trace%get_qn_index (i_flv, i_sub = 0) + i_qn_virt = term%connected%trace%get_qn_index (i_flv, i_sub = 1) + if (term%passed_array(i_flv) .or. .not. term%passed) then + virtual%sqme_born(i_flv) = & + real (term%connected%trace%get_matrix_element (i_qn_born)) + virtual%sqme_virt_fin(i_flv) = & + real (term%connected%trace%get_matrix_element (i_qn_virt)) + else + virtual%sqme_born(i_flv) = zero + virtual%sqme_virt_fin(i_flv) = zero + end if end do end associate end select call pcm_work%compute_sqme_virt (term%pcm, term%p_hard, & alpha_coupling, term%connected%has_matrix, sqme_virt) call term%connected%trace%set_only_matrix_element & (1, cmplx (sum(sqme_virt), 0, default)) if (term%connected%has_matrix) & call refill_evaluator (cmplx (sqme_virt * term%weight, & 0, default), pcm%get_qn (.true.), & remove_duplicates_from_int_array ( & pcm%region_data%get_flavor_indices (.true.)), & term%connected%matrix) if (term%connected%has_flows) & call refill_evaluator (cmplx (sqme_virt * term%weight, & 0, default), pcm%get_qn (.true.), & remove_duplicates_from_int_array ( & pcm%region_data%get_flavor_indices (.true.)), & term%connected%flows) end select end select end subroutine term_instance_evaluate_sqme_virt @ %def term_instance_evaluate_sqme_virt @ Needs generalization to electroweak corrections. <>= procedure :: evaluate_sqme_mismatch => term_instance_evaluate_sqme_mismatch <>= module subroutine term_instance_evaluate_sqme_mismatch (term, alpha_s) class(term_instance_t), intent(inout) :: term real(default), intent(in) :: alpha_s end subroutine term_instance_evaluate_sqme_mismatch <>= module subroutine term_instance_evaluate_sqme_mismatch (term, alpha_s) class(term_instance_t), intent(inout) :: term real(default), intent(in) :: alpha_s real(default), dimension(:), allocatable :: sqme_mism if (term%nlo_type /= NLO_MISMATCH) call msg_fatal & ("Trying to evaluate soft mismatch with unsuited term_instance.") select type (pcm_work => term%pcm_work) type is (pcm_nlo_workspace_t) call pcm_work%compute_sqme_mismatch & (term%pcm, alpha_s, term%connected%has_matrix, sqme_mism) end select call term%connected%trace%set_only_matrix_element & (1, cmplx (sum (sqme_mism) * term%weight, 0, default)) if (term%connected%has_matrix) then select type (pcm => term%pcm) type is (pcm_nlo_t) if (term%connected%has_matrix) & call refill_evaluator (cmplx (sqme_mism * term%weight, 0, default), & pcm%get_qn (.true.), & remove_duplicates_from_int_array ( & pcm%region_data%get_flavor_indices (.true.)), & term%connected%matrix) if (term%connected%has_flows) & call refill_evaluator (cmplx (sqme_mism * term%weight, 0, default), & pcm%get_qn (.true.), & remove_duplicates_from_int_array ( & pcm%region_data%get_flavor_indices (.true.)), & term%connected%flows) end select end if end subroutine term_instance_evaluate_sqme_mismatch @ %def term_instance_evaluate_sqme_mismatch @ <>= procedure :: evaluate_sqme_dglap => term_instance_evaluate_sqme_dglap <>= module subroutine term_instance_evaluate_sqme_dglap & (term, alpha_s, alpha_qed) class(term_instance_t), intent(inout) :: term real(default), intent(in) :: alpha_s, alpha_qed end subroutine term_instance_evaluate_sqme_dglap <>= module subroutine term_instance_evaluate_sqme_dglap (term, alpha_s, alpha_qed) class(term_instance_t), intent(inout) :: term real(default), intent(in) :: alpha_s, alpha_qed real(default), dimension(2) :: alpha_coupling real(default), dimension(:), allocatable :: sqme_dglap integer :: i_flv if (term%nlo_type /= NLO_DGLAP) call msg_fatal & ("Trying to evaluate DGLAP remnant with unsuited term_instance.") if (debug_on) call msg_debug2 & (D_PROCESS_INTEGRATION, "term_instance_evaluate_sqme_dglap") select type (pcm => term%pcm) type is (pcm_nlo_t) select type (pcm_work => term%pcm_work) type is (pcm_nlo_workspace_t) alpha_coupling = [alpha_s,alpha_qed] if (debug2_active (D_PROCESS_INTEGRATION)) then associate (n_flv => pcm_work%dglap_remnant%reg_data%n_flv_born) print *, "size(sqme_born) = ", & size (pcm_work%dglap_remnant%sqme_born) call term%connected%trace%write () end associate end if call pcm_work%compute_sqme_dglap_remnant (pcm, alpha_coupling, & term%connected%has_matrix, sqme_dglap) end select end select call term%connected%trace%set_only_matrix_element & (1, cmplx (sum (sqme_dglap) * term%weight, 0, default)) if (term%connected%has_matrix) then select type (pcm => term%pcm) type is (pcm_nlo_t) call refill_evaluator (cmplx (sqme_dglap * term%weight, 0, default), & pcm%get_qn (.true.), & remove_duplicates_from_int_array ( & pcm%region_data%get_flavor_indices (.true.)), & term%connected%matrix) if (term%connected%has_flows) then call refill_evaluator & (cmplx (sqme_dglap * term%weight, 0, default), & pcm%get_qn (.true.), & remove_duplicates_from_int_array ( & pcm%region_data%get_flavor_indices (.true.)), & term%connected%flows) end if end select end if end subroutine term_instance_evaluate_sqme_dglap @ %def term_instance_evaluate_sqme_dglap @ Reset the term instance: clear the parton-state expressions and deactivate. <>= procedure :: reset => term_instance_reset <>= module subroutine term_instance_reset (term) class(term_instance_t), intent(inout) :: term end subroutine term_instance_reset <>= module subroutine term_instance_reset (term) class(term_instance_t), intent(inout) :: term call term%connected%reset_expressions () if (allocated (term%alpha_qcd_forced)) deallocate (term%alpha_qcd_forced) term%active = .false. end subroutine term_instance_reset @ %def term_instance_reset @ Force an $\alpha_s$ value that should be used in the matrix-element calculation. <>= procedure :: set_alpha_qcd_forced => term_instance_set_alpha_qcd_forced <>= module subroutine term_instance_set_alpha_qcd_forced (term, alpha_qcd) class(term_instance_t), intent(inout) :: term real(default), intent(in) :: alpha_qcd end subroutine term_instance_set_alpha_qcd_forced <>= module subroutine term_instance_set_alpha_qcd_forced (term, alpha_qcd) class(term_instance_t), intent(inout) :: term real(default), intent(in) :: alpha_qcd if (allocated (term%alpha_qcd_forced)) then term%alpha_qcd_forced = alpha_qcd else allocate (term%alpha_qcd_forced, source = alpha_qcd) end if end subroutine term_instance_set_alpha_qcd_forced @ %def term_instance_set_alpha_qcd_forced @ Complete the kinematics computation for the effective parton states. We assume that the [[compute_hard_kinematics]] method of the process component instance has already been called, so the [[int_hard]] contains the correct hard kinematics. The duty of this procedure is first to compute the effective kinematics and store this in the [[int_eff]] effective interaction inside the [[isolated]] parton state. The effective kinematics may differ from the kinematics in the hard interaction. It may involve parton recombination or parton splitting. The [[rearrange_partons]] method is responsible for this part. We may also call a method to compute the effective structure-function chain at this point. This is not implemented yet. In the simple case that no rearrangement is necessary, as indicated by the [[rearrange]] flag, the effective interaction is a pointer to the hard interaction, and we can skip the rearrangement method. Similarly for the effective structure-function chain. The final step of kinematics setup is to transfer the effective kinematics to the evaluators and to the [[subevt]]. <>= procedure :: compute_eff_kinematics => & term_instance_compute_eff_kinematics <>= module subroutine term_instance_compute_eff_kinematics (term) class(term_instance_t), intent(inout) :: term end subroutine term_instance_compute_eff_kinematics <>= module subroutine term_instance_compute_eff_kinematics (term) class(term_instance_t), intent(inout) :: term term%checked = .false. term%passed = .false. call term%isolated%receive_kinematics () call term%connected%receive_kinematics () end subroutine term_instance_compute_eff_kinematics @ %def term_instance_compute_eff_kinematics @ Inverse. Reconstruct the connected state from the momenta in the trace evaluator (which we assume to be set), then reconstruct the isolated state as far as possible. The second part finalizes the momentum configuration, using the incoming seed momenta <>= procedure :: recover_hard_kinematics => & term_instance_recover_hard_kinematics <>= module subroutine term_instance_recover_hard_kinematics (term) class(term_instance_t), intent(inout) :: term end subroutine term_instance_recover_hard_kinematics <>= module subroutine term_instance_recover_hard_kinematics (term) class(term_instance_t), intent(inout) :: term term%checked = .false. term%passed = .false. call term%connected%send_kinematics () call term%isolated%send_kinematics () end subroutine term_instance_recover_hard_kinematics @ %def term_instance_recover_hard_kinematics @ Check the term whether it passes cuts and, if successful, evaluate scales and weights. The factorization scale is also given to the term kinematics, enabling structure-function evaluation. <>= procedure :: evaluate_expressions => & term_instance_evaluate_expressions <>= - module subroutine term_instance_evaluate_expressions (term, scale_forced) + module subroutine term_instance_evaluate_expressions & + (term, config, scale_forced) class(term_instance_t), intent(inout) :: term + type(process_beam_config_t), intent(in) :: config real(default), intent(in), allocatable, optional :: scale_forced end subroutine term_instance_evaluate_expressions <>= - module subroutine term_instance_evaluate_expressions (term, scale_forced) + module subroutine term_instance_evaluate_expressions & + (term, config, scale_forced) class(term_instance_t), intent(inout) :: term + type(process_beam_config_t), intent(in) :: config real(default), intent(in), allocatable, optional :: scale_forced - call term%connected%evaluate_expressions (term%passed, & - term%scale, term%fac_scale, term%ren_scale, term%weight, & - scale_forced, force_evaluation = .true.) + real(default) :: scale = 0 + real(default) :: weight = 1 + real(default), allocatable :: fac_scale, ren_scale + type(interaction_t), pointer :: src_int + type(state_matrix_t), pointer :: state_matrix + type(flavor_t), dimension(:), allocatable :: flv_int, flv_src, f_in, f_out + logical :: passed + integer :: n_in, n_vir, n_out, n_tot, n_flv + integer :: i, j, k + n_flv = term%connected%trace%get_qn_index_n_flv () + if (.not. allocated (term%passed_array)) allocate (term%passed_array(n_flv)) + if (term%flv_dep_cut_eval) then + do k = 1, n_flv + if (k == term%i_flv_to_i_flv_rep(k)) then + n_in = term%int_hard%get_n_in () + associate (int_eff => term%isolated%int_eff) + state_matrix => int_eff%get_state_matrix_ptr () + n_tot = int_eff%get_n_tot () + flv_int = quantum_numbers_get_flavor & + (state_matrix%get_quantum_number (k)) + allocate (f_in (n_in)) + f_in = flv_int(1:n_in) + deallocate (flv_int) + end associate + n_in = term%connected%trace%get_n_in () + n_vir = term%connected%trace%get_n_vir () + n_out = term%connected%trace%get_n_out () + allocate (f_out (n_out)) + do j = 1, n_out + call term%connected%trace%find_source & + (n_in + n_vir + j, src_int, i) + if (associated (src_int)) then + state_matrix => src_int%get_state_matrix_ptr () + flv_src = quantum_numbers_get_flavor & + (state_matrix%get_quantum_number (k)) + f_out(j) = flv_src(i) + deallocate (flv_src) + end if + end do + + call term%connected%renew_flv_content_subevt & + (term%isolated%sf_chain_eff, & + config%data%flv, f_in, f_out) + call term%connected%evaluate_expressions (passed, & + scale, fac_scale, ren_scale, weight, & + scale_forced, force_evaluation = .true.) + if (k == 1) then + term%scale = scale + if (allocated (fac_scale)) then + if (.not. allocated (term%fac_scale)) then + allocate (term%fac_scale, source = fac_scale) + else + term%fac_scale = fac_scale + end if + end if + if (allocated (ren_scale)) then + if (.not. allocated (term%ren_scale)) then + allocate (term%ren_scale, source = ren_scale) + else + term%ren_scale = ren_scale + end if + end if + term%weight = weight + end if + term%passed_array(k) = passed + deallocate (f_in) + deallocate (f_out) + else + term%passed_array(k) = term%passed_array(term%i_flv_to_i_flv_rep(k)) + end if + end do + term%passed = any (term%passed_array) + else + call term%connected%evaluate_expressions (term%passed, & + term%scale, term%fac_scale, term%ren_scale, term%weight, & + scale_forced, force_evaluation = .true.) + term%passed_array = term%passed + end if term%checked = .true. end subroutine term_instance_evaluate_expressions @ %def term_instance_evaluate_expressions @ Evaluate the trace: first evaluate the hard interaction, then the trace evaluator. We use the [[evaluate_interaction]] method of the process component which generated this term. The [[subevt]] and cut expressions are not yet filled. The [[component]] argument is intent(inout) because the [[compute_amplitude]] method may modify the [[core_state]] workspace object. <>= procedure :: evaluate_interaction => term_instance_evaluate_interaction <>= module subroutine term_instance_evaluate_interaction (term, core, kin) class(term_instance_t), intent(inout) :: term class(prc_core_t), intent(in), pointer :: core type(kinematics_t), intent(inout) :: kin end subroutine term_instance_evaluate_interaction <>= module subroutine term_instance_evaluate_interaction (term, core, kin) class(term_instance_t), intent(inout) :: term class(prc_core_t), intent(in), pointer :: core type(kinematics_t), intent(inout) :: kin if (debug_on) call msg_debug2 (D_PROCESS_INTEGRATION, & "term_instance_evaluate_interaction") if (kin%only_cm_frame .and. (.not. kin%lab_is_cm())) then term%p_hard = kin%get_boost_to_cms () * term%int_hard%get_momenta () else term%p_hard = term%int_hard%get_momenta () end if select type (core) class is (prc_external_t) call term%evaluate_interaction_external (core, kin) class default call term%evaluate_interaction_default (core) end select call term%int_hard%set_matrix_element (term%amp) end subroutine term_instance_evaluate_interaction @ %def term_instance_evaluate_interaction @ <>= procedure :: evaluate_interaction_default & => term_instance_evaluate_interaction_default <>= module subroutine term_instance_evaluate_interaction_default (term, core) class(term_instance_t), intent(inout) :: term class(prc_core_t), intent(in) :: core end subroutine term_instance_evaluate_interaction_default <>= module subroutine term_instance_evaluate_interaction_default (term, core) class(term_instance_t), intent(inout) :: term class(prc_core_t), intent(in) :: core real(default) :: fac_scale, ren_scale integer :: i if (allocated (term%fac_scale)) then fac_scale = term%fac_scale else fac_scale = term%scale end if if (allocated (term%ren_scale)) then ren_scale = term%ren_scale else ren_scale = term%scale end if do i = 1, term%config%n_allowed term%amp(i) = core%compute_amplitude (term%config%i_term, term%p_hard, & term%config%flv(i), term%config%hel(i), term%config%col(i), & fac_scale, ren_scale, term%alpha_qcd_forced, & term%core_state) end do select type (pcm_work => term%pcm_work) type is (pcm_nlo_workspace_t) call pcm_work%set_fac_scale (fac_scale) end select end subroutine term_instance_evaluate_interaction_default @ %def term_instance_evaluate_interaction_default @ <>= procedure :: evaluate_interaction_external & => term_instance_evaluate_interaction_external <>= module subroutine term_instance_evaluate_interaction_external & (term, core, kin) class(term_instance_t), intent(inout) :: term class(prc_core_t), intent(inout) :: core type(kinematics_t), intent(inout) :: kin end subroutine term_instance_evaluate_interaction_external <>= module subroutine term_instance_evaluate_interaction_external & (term, core, kin) class(term_instance_t), intent(inout) :: term class(prc_core_t), intent(inout) :: core type(kinematics_t), intent(inout) :: kin if (debug_on) call msg_debug2 (D_PROCESS_INTEGRATION, & "term_instance_evaluate_interaction_external") select type (core_state => term%core_state) type is (openloops_state_t) select type (core) type is (prc_openloops_t) call core%compute_alpha_s (core_state, term%get_ren_scale ()) if (allocated (core_state%threshold_data)) & call evaluate_threshold_parameters (core_state, core, kin%phs%get_sqrts ()) end select class is (prc_external_state_t) select type (core) class is (prc_external_t) call core%compute_alpha_s (core_state, term%get_ren_scale ()) end select end select call evaluate_threshold_interaction () if (term%nlo_type == NLO_VIRTUAL) then call term%evaluate_interaction_external_loop (core) else call term%evaluate_interaction_external_tree (core) end if select type (pcm_work => term%pcm_work) type is (pcm_nlo_workspace_t) call pcm_work%set_fac_scale (term%get_fac_scale ()) end select contains subroutine evaluate_threshold_parameters (core_state, core, sqrts) type(openloops_state_t), intent(inout) :: core_state type(prc_openloops_t), intent(inout) :: core real(default), intent(in) :: sqrts real(default) :: mtop, wtop mtop = m1s_to_mpole (sqrts) wtop = core_state%threshold_data%compute_top_width & (mtop, core_state%alpha_qcd) call core%set_mass_and_width (6, mtop, wtop) end subroutine subroutine evaluate_threshold_interaction () integer :: leg select type (core) type is (prc_threshold_t) if (term%nlo_type > BORN) then select type (pcm_work => term%pcm_work) type is (pcm_nlo_workspace_t) if (kin%emitter >= 0) then call core%set_offshell_momenta & (pcm_work%real_kinematics%p_real_cms%get_momenta(term%config%i_term)) leg = thr_leg (kin%emitter) call core%set_leg (leg) call core%set_onshell_momenta & (pcm_work%real_kinematics%p_real_onshell(leg)%get_momenta(term%config%i_term)) else call core%set_leg (0) call core%set_offshell_momenta & (pcm_work%real_kinematics%p_born_cms%get_momenta(1)) end if end select else call core%set_leg (-1) call core%set_offshell_momenta (term%p_hard) end if end select end subroutine evaluate_threshold_interaction end subroutine term_instance_evaluate_interaction_external @ %def term_instance_evaluate_interaction_external @ Retrieve the matrix elements from a matrix element provider and place them into [[term%amp]]. For the handling of NLO calculations, FKS applies a book keeping handling flavor and/or particle type (e.g. for QCD: quark/gluon and quark flavor) in order to calculate the subtraction terms. Therefore, we have to insert the calculated matrix elements correctly into the state matrix where each entry corresponds to a set of quantum numbers. We apply a mapping [[hard_qn_ind]] from a list of quantum numbers provided by FKS to the hard process [[int_hard]]. The calculated matrix elements are insert into [[term%amp]] in the following way. The first [[n_born]] particles are the matrix element of the hard process. In non-trivial beams, we store another [[n_beams_rescaled]] copies of these matrix elements as the first [[n_beams_rescaled]] subtractions. This is a remnant from times before the method [[term_instance_set_sf_factors]] and these entries are not used anymore. However, eliminating these entries involves deeper changes in how the connection tables for the evaluator product are set up and should therefore be part of a larger refactoring of the interactions \& state matrices. The next $n_{\text{born}}\times n_{sub_color}$ are color-correlated Born matrix elements, with then again the next $n_{\text{born}}\times n_{emitters}\times n_{sub_spin}$ being spin-correlated Born matrix elements. If two or more flavor structures would produce the same amplitude we only compute one and use the [[eqv_index]] determined by the [[prc_core]] and just copy the result to improve performance. <>= procedure :: evaluate_interaction_external_tree & => term_instance_evaluate_interaction_external_tree <>= module subroutine term_instance_evaluate_interaction_external_tree & (term, core) class(term_instance_t), intent(inout) :: term class(prc_core_t), intent(inout) :: core end subroutine term_instance_evaluate_interaction_external_tree <>= module subroutine term_instance_evaluate_interaction_external_tree & (term, core) class(term_instance_t), intent(inout) :: term class(prc_core_t), intent(inout) :: core real(default) :: sqme real(default), dimension(:), allocatable :: sqme_color_c real(default), dimension(:), allocatable :: sqme_spin_c real(default), dimension(6) :: sqme_spin_c_tmp integer :: n_flv, n_hel, n_sub_color, n_sub_spin, n_pdf_off integer :: i_flv, i_hel, i_sub, i_color_c, i_color_c_eqv, & i_spin_c, i_spin_c_eqv integer :: i_flv_eqv, i_hel_eqv integer :: emitter, i_emitter logical :: bad_point, bp logical, dimension(:,:), allocatable :: eqv_me_evaluated if (debug_on) call msg_debug2 (D_PROCESS_INTEGRATION, & "term_instance_evaluate_interaction_external_tree") allocate (sqme_color_c (blha_result_array_size & (term%int_hard%get_n_tot (), BLHA_AMP_COLOR_C))) n_flv = term%int_hard%get_qn_index_n_flv () n_hel = term%int_hard%get_qn_index_n_hel () n_sub_color = term%get_n_sub_color () n_sub_spin = term%get_n_sub_spin () allocate (eqv_me_evaluated(n_flv,n_hel)) eqv_me_evaluated = .false. do i_flv = 1, n_flv + if (.not. term%passed_array(i_flv) .and. term%passed) cycle do i_hel = 1, n_hel i_flv_eqv = core%data%eqv_flv_index(i_flv) i_hel_eqv = core%data%eqv_hel_index(i_hel) if (.not. eqv_me_evaluated(i_flv_eqv, i_hel_eqv)) then select type (core) class is (prc_external_t) call core%update_alpha_s (term%core_state, term%get_ren_scale ()) call core%compute_sqme (i_flv, i_hel, term%p_hard, & term%get_ren_scale (), sqme, bad_point) call term%pcm_work%set_bad_point (bad_point) associate (i_int => term%int_hard%get_qn_index & (i_flv = i_flv, i_hel = i_hel, i_sub = 0)) term%amp(i_int) = cmplx (sqme, 0, default) end associate end select n_pdf_off = 0 if (term%pcm%has_pdfs .and. & (term%is_subtraction () .or. term%nlo_type == NLO_DGLAP)) then n_pdf_off = n_pdf_off + n_beams_rescaled do i_sub = 1, n_pdf_off term%amp(term%int_hard%get_qn_index (i_flv, i_hel, i_sub)) = & term%amp(term%int_hard%get_qn_index (i_flv, i_hel, i_sub = 0)) end do end if if (term%pcm%has_pdfs .and. term%nlo_type == NLO_DGLAP) then sqme_color_c = zero select type (pcm => term%pcm) type is (pcm_nlo_t) if (pcm%settings%nlo_correction_type == "EW" .and. & pcm%region_data%alphas_power > 0) then select type (core) class is (prc_blha_t) call core%compute_sqme_color_c_raw (i_flv, i_hel, & term%p_hard, term%get_ren_scale (), sqme_color_c, & bad_point) call term%pcm_work%set_bad_point (bad_point) class is (prc_recola_t) call core%compute_sqme_color_c_raw (i_flv, i_hel, & term%p_hard, term%get_ren_scale (), sqme_color_c, & bad_point) call term%pcm_work%set_bad_point (bad_point) end select end if end select do i_sub = 1, n_sub_color i_color_c = term%int_hard%get_qn_index & (i_flv, i_hel, i_sub + n_pdf_off) term%amp(i_color_c) = cmplx (sqme_color_c(i_sub), 0, default) end do end if if ((term%nlo_type == NLO_REAL .and. term%is_subtraction ()) .or. & term%nlo_type == NLO_MISMATCH) then sqme_color_c = zero select type (core) class is (prc_blha_t) call core%compute_sqme_color_c_raw (i_flv, i_hel, & term%p_hard, term%get_ren_scale (), sqme_color_c, bad_point) call term%pcm_work%set_bad_point (bad_point) class is (prc_recola_t) call core%compute_sqme_color_c_raw (i_flv, i_hel, & term%p_hard, term%get_ren_scale (), sqme_color_c, bad_point) call term%pcm_work%set_bad_point (bad_point) end select do i_sub = 1, n_sub_color i_color_c = term%int_hard%get_qn_index & (i_flv, i_hel, i_sub + n_pdf_off) term%amp(i_color_c) = cmplx (sqme_color_c(i_sub), 0, default) end do if (n_sub_spin > 0) then bad_point = .false. allocate (sqme_spin_c(0)) select type (core) type is (prc_openloops_t) select type (pcm => term%pcm) type is (pcm_nlo_t) do i_emitter = 1, pcm%region_data%n_emitters emitter = pcm%region_data%emitters(i_emitter) if (emitter > 0) then call core%compute_sqme_spin_c & (i_flv, & i_hel, & emitter, & term%p_hard, & term%get_ren_scale (), & sqme_spin_c_tmp, & bp) sqme_spin_c = [sqme_spin_c, sqme_spin_c_tmp] bad_point = bad_point .or. bp end if end do end select do i_sub = 1, n_sub_spin i_spin_c = term%int_hard%get_qn_index (i_flv, i_hel, & i_sub + n_pdf_off + n_sub_color) term%amp(i_spin_c) = cmplx & (sqme_spin_c(i_sub), 0, default) end do end select deallocate (sqme_spin_c) end if end if eqv_me_evaluated(i_flv_eqv, i_hel_eqv) = .true. else associate (i_int => term%int_hard%get_qn_index & (i_flv = i_flv, i_hel = i_hel, i_sub = 0), & i_int_eqv => term%int_hard%get_qn_index & (i_flv = i_flv_eqv, i_hel = i_hel_eqv, i_sub = 0)) term%amp(i_int) = term%amp(i_int_eqv) end associate n_pdf_off = 0 if (term%pcm%has_pdfs .and. & (term%is_subtraction () .or. term%nlo_type == NLO_DGLAP)) then n_pdf_off = n_pdf_off + n_beams_rescaled do i_sub = 1, n_pdf_off term%amp(term%int_hard%get_qn_index (i_flv, i_hel, i_sub)) = & term%amp(term%int_hard%get_qn_index (i_flv, i_hel, i_sub = 0)) end do end if if (term%pcm%has_pdfs .and. term%nlo_type == NLO_DGLAP) then do i_sub = 1, n_sub_color i_color_c = term%int_hard%get_qn_index & (i_flv, i_hel, i_sub + n_pdf_off) i_color_c_eqv = term%int_hard%get_qn_index & (i_flv_eqv, i_hel_eqv, i_sub + n_pdf_off) term%amp(i_color_c) = term%amp(i_color_c_eqv) end do end if if ((term%nlo_type == NLO_REAL .and. term%is_subtraction ()) .or. & term%nlo_type == NLO_MISMATCH) then do i_sub = 1, n_sub_color i_color_c = term%int_hard%get_qn_index & (i_flv, i_hel, i_sub + n_pdf_off) i_color_c_eqv = term%int_hard%get_qn_index & (i_flv_eqv, i_hel_eqv, i_sub + n_pdf_off) term%amp(i_color_c) = term%amp(i_color_c_eqv) end do do i_sub = 1, n_sub_spin i_spin_c = term%int_hard%get_qn_index (i_flv, i_hel, & i_sub + n_pdf_off + n_sub_color) i_spin_c_eqv = term%int_hard%get_qn_index (i_flv_eqv, i_hel_eqv, & i_sub + n_pdf_off + n_sub_color) term%amp(i_spin_c) = term%amp(i_spin_c_eqv) end do end if end if end do end do end subroutine term_instance_evaluate_interaction_external_tree @ %def term_instance_evaluate_interaction_external_tree @ Same as for [[term_instance_evaluate_interaction_external_tree]], but for the integrated-subtraction and finite one-loop terms. We only need color-correlated Born matrix elements, but an additional entry per flavor structure for the finite one-loop contribution. We thus have $2+n_{sub_color}$ entries in the [[term%amp]] for each [[i_flv]] and [[i_hel]] combination. If two or more flavor structures would produce the same amplitude we only compute one and use the [[eqv_index]] determined by the [[prc_core]] and just copy the result to improve performance. <>= procedure :: evaluate_interaction_external_loop & => term_instance_evaluate_interaction_external_loop <>= module subroutine term_instance_evaluate_interaction_external_loop & (term, core) class(term_instance_t), intent(inout) :: term class(prc_core_t), intent(in) :: core end subroutine term_instance_evaluate_interaction_external_loop <>= module subroutine term_instance_evaluate_interaction_external_loop & (term, core) class(term_instance_t), intent(inout) :: term class(prc_core_t), intent(in) :: core integer :: n_hel, n_sub, n_flv integer :: i, i_flv, i_hel, i_sub, i_virt, i_color_c, i_color_c_eqv integer :: i_flv_eqv, i_hel_eqv real(default), dimension(4) :: sqme_virt real(default), dimension(:), allocatable :: sqme_color_c real(default) :: es_scale logical :: bad_point logical, dimension(:,:), allocatable :: eqv_me_evaluated if (debug_on) call msg_debug (D_PROCESS_INTEGRATION, & "term_instance_evaluate_interaction_external_loop") allocate (sqme_color_c (blha_result_array_size & (term%int_hard%get_n_tot (), BLHA_AMP_COLOR_C))) n_flv = term%int_hard%get_qn_index_n_flv () n_hel = term%int_hard%get_qn_index_n_hel () n_sub = term%int_hard%get_qn_index_n_sub () allocate (eqv_me_evaluated(n_flv,n_hel)) eqv_me_evaluated = .false. i_virt = 1 do i_flv = 1, n_flv + if (.not. term%passed_array(i_flv) .and. term%passed) cycle do i_hel = 1, n_hel i_flv_eqv = core%data%eqv_flv_index(i_flv) i_hel_eqv = core%data%eqv_hel_index(i_hel) if (.not. eqv_me_evaluated(i_flv_eqv, i_hel_eqv)) then select type (core) class is (prc_external_t) if (allocated (term%es_scale)) then es_scale = term%es_scale else es_scale = term%get_ren_scale () end if call core%compute_sqme_virt (i_flv, i_hel, term%p_hard, & term%get_ren_scale (), es_scale, & term%pcm%blha_defaults%loop_method, & sqme_virt, bad_point) call term%pcm_work%set_bad_point (bad_point) end select associate (i_born => term%int_hard%get_qn_index (i_flv, i_hel = i_hel, i_sub = 0), & i_loop => term%int_hard%get_qn_index (i_flv, i_hel = i_hel, i_sub = i_virt)) term%amp(i_loop) = cmplx (sqme_virt(3), 0, default) term%amp(i_born) = cmplx (sqme_virt(4), 0, default) end associate select type (pcm => term%pcm) type is (pcm_nlo_t) select type (core) class is (prc_blha_t) call core%compute_sqme_color_c_raw (i_flv, i_hel, & term%p_hard, term%get_ren_scale (), & sqme_color_c, bad_point) call term%pcm_work%set_bad_point (bad_point) do i_sub = 1 + i_virt, n_sub i_color_c = term%int_hard%get_qn_index & (i_flv, i_hel = i_hel, i_sub = i_sub) ! Index shift: i_sub - i_virt term%amp(i_color_c) = & cmplx (sqme_color_c(i_sub - i_virt), 0, default) end do type is (prc_recola_t) call core%compute_sqme_color_c_raw (i_flv, i_hel, & term%p_hard, term%get_ren_scale (), sqme_color_c, bad_point) call term%pcm_work%set_bad_point (bad_point) do i_sub = 1 + i_virt, n_sub i_color_c = term%int_hard%get_qn_index & (i_flv, i_hel = i_hel, i_sub = i_sub) ! Index shift: i_sub - i_virt term%amp(i_color_c) = & cmplx (sqme_color_c(i_sub - i_virt), 0, default) end do end select end select eqv_me_evaluated(i_flv_eqv, i_hel_eqv) = .true. else associate (i_born => term%int_hard%get_qn_index (i_flv, i_hel = i_hel, i_sub = 0), & i_loop => term%int_hard%get_qn_index (i_flv, i_hel = i_hel, i_sub = i_virt), & i_born_eqv => term%int_hard%get_qn_index & (i_flv_eqv, i_hel = i_hel_eqv, i_sub = 0), & i_loop_eqv => term%int_hard%get_qn_index & (i_flv_eqv, i_hel = i_hel_eqv, i_sub = 1)) term%amp(i_loop) = term%amp(i_loop_eqv) term%amp(i_born) = term%amp(i_born_eqv) end associate do i_sub = 1 + i_virt, n_sub i_color_c = term%int_hard%get_qn_index & (i_flv, i_hel = i_hel, i_sub = i_sub) i_color_c_eqv = term%int_hard%get_qn_index & (i_flv_eqv, i_hel = i_hel_eqv, i_sub = i_sub) ! Index shift: i_sub - i_virt term%amp(i_color_c) = term%amp(i_color_c_eqv) end do end if end do end do end subroutine term_instance_evaluate_interaction_external_loop @ %def term_instance_evaluate_interaction_external_loop @ Evaluate the trace. First evaluate the structure-function chain (i.e., the density matrix of the incoming partons). Do this twice, in case the sf-chain instances within [[kin]] and [[isolated]] differ. Next, evaluate the hard interaction, then compute the convolution with the initial state. <>= procedure :: evaluate_trace => term_instance_evaluate_trace <>= module subroutine term_instance_evaluate_trace (term, kin) class(term_instance_t), intent(inout) :: term type(kinematics_t), intent(inout) :: kin end subroutine term_instance_evaluate_trace <>= module subroutine term_instance_evaluate_trace (term, kin) class(term_instance_t), intent(inout) :: term type(kinematics_t), intent(inout) :: kin real(default) :: fac_scale if (allocated (term%fac_scale)) then fac_scale = term%fac_scale else fac_scale = term%scale end if call kin%evaluate_sf_chain (fac_scale, term%negative_sf) call term%evaluate_scaled_sf_chains (kin) call term%isolated%evaluate_sf_chain (fac_scale) call term%isolated%evaluate_trace () call term%connected%evaluate_trace () end subroutine term_instance_evaluate_trace @ %def term_instance_evaluate_trace @ Include rescaled structure functions due to NLO calculation. We rescale the structure function for the real subtraction [[sf_rescale_collinear]], the collinear counter terms [[sf_rescale_dglap_t]] and for the case, in which we have an emitter in the initial state, we rescale the kinematics for it using [[sf_rescale_real_t]]. The references are arXiv:0709.2092, Eqs.~(2.35)-(2.42). Obviously, it is completely irrelevant, which beam is treated. It becomes problematic when handling $ep$ collisions. Gfortran 7/8/9 bug, has to remain in the main module: <>= procedure :: evaluate_scaled_sf_chains => & term_instance_evaluate_scaled_sf_chains <>= subroutine term_instance_evaluate_scaled_sf_chains (term, kin) class(term_instance_t), intent(inout) :: term type(kinematics_t), intent(inout) :: kin class(sf_rescale_t), allocatable :: sf_rescale if (.not. term%pcm%has_pdfs) return if (term%nlo_type == NLO_REAL) then if (term%is_subtraction ()) then allocate (sf_rescale_collinear_t :: sf_rescale) select type (pcm_work => term%pcm_work) type is (pcm_nlo_workspace_t) select type (sf_rescale) type is (sf_rescale_collinear_t) call sf_rescale%set (pcm_work%real_kinematics%xi_tilde) end select end select call kin%sf_chain%evaluate (term%get_fac_scale (), & term%negative_sf, sf_rescale) deallocate (sf_rescale) else if (kin%emitter >= 0 .and. kin%emitter <= kin%n_in) then allocate (sf_rescale_real_t :: sf_rescale) select type (pcm_work => term%pcm_work) type is (pcm_nlo_workspace_t) select type (sf_rescale) type is (sf_rescale_real_t) call sf_rescale%set (pcm_work%real_kinematics%xi_tilde * & pcm_work%real_kinematics%xi_max (kin%i_phs), & pcm_work%real_kinematics%y (kin%i_phs)) end select end select call kin%sf_chain%evaluate (term%get_fac_scale (), & term%negative_sf, sf_rescale) deallocate (sf_rescale) else call kin%sf_chain%evaluate (term%get_fac_scale (), term%negative_sf) end if else if (term%nlo_type == NLO_DGLAP) then allocate (sf_rescale_dglap_t :: sf_rescale) select type (pcm_work => term%pcm_work) type is (pcm_nlo_workspace_t) select type (sf_rescale) type is (sf_rescale_dglap_t) call sf_rescale%set (pcm_work%isr_kinematics%z) end select end select call kin%sf_chain%evaluate (term%get_fac_scale (), & term%negative_sf, sf_rescale) deallocate (sf_rescale) end if end subroutine term_instance_evaluate_scaled_sf_chains @ %def term_instance_evaluate_scaled_sf_chains @ Evaluate the extra data that we need for processing the object as a physical event. <>= procedure :: evaluate_event_data => term_instance_evaluate_event_data <>= module subroutine term_instance_evaluate_event_data (term) class(term_instance_t), intent(inout) :: term end subroutine term_instance_evaluate_event_data <>= module subroutine term_instance_evaluate_event_data (term) class(term_instance_t), intent(inout) :: term logical :: only_momenta only_momenta = term%nlo_type > BORN call term%isolated%evaluate_event_data (only_momenta) call term%connected%evaluate_event_data (only_momenta) end subroutine term_instance_evaluate_event_data @ %def term_instance_evaluate_event_data @ <>= procedure :: set_fac_scale => term_instance_set_fac_scale <>= module subroutine term_instance_set_fac_scale (term, fac_scale) class(term_instance_t), intent(inout) :: term real(default), intent(in) :: fac_scale end subroutine term_instance_set_fac_scale <>= module subroutine term_instance_set_fac_scale (term, fac_scale) class(term_instance_t), intent(inout) :: term real(default), intent(in) :: fac_scale term%fac_scale = fac_scale end subroutine term_instance_set_fac_scale @ %def term_instance_set_fac_scale @ Return data that might be useful for external processing. The factorization scale and renormalization scale are identical to the general scale if not explicitly set: <>= procedure :: get_fac_scale => term_instance_get_fac_scale procedure :: get_ren_scale => term_instance_get_ren_scale <>= module function term_instance_get_fac_scale (term) result (fac_scale) class(term_instance_t), intent(in) :: term real(default) :: fac_scale end function term_instance_get_fac_scale module function term_instance_get_ren_scale (term) result (ren_scale) class(term_instance_t), intent(in) :: term real(default) :: ren_scale end function term_instance_get_ren_scale <>= module function term_instance_get_fac_scale (term) result (fac_scale) class(term_instance_t), intent(in) :: term real(default) :: fac_scale if (allocated (term%fac_scale)) then fac_scale = term%fac_scale else fac_scale = term%scale end if end function term_instance_get_fac_scale module function term_instance_get_ren_scale (term) result (ren_scale) class(term_instance_t), intent(in) :: term real(default) :: ren_scale if (allocated (term%ren_scale)) then ren_scale = term%ren_scale else ren_scale = term%scale end if end function term_instance_get_ren_scale @ %def term_instance_get_fac_scale term_instance_get_ren_scale @ We take the strong coupling from the process core. The value is calculated when a new event is requested, so we should call it only after the event has been evaluated. If it is not available there (a negative number is returned), we take the value stored in the term configuration, which should be determined by the model. If the model does not provide a value, the result is zero. <>= procedure :: get_alpha_s => term_instance_get_alpha_s <>= module function term_instance_get_alpha_s (term, core) result (alpha_s) class(term_instance_t), intent(in) :: term class(prc_core_t), intent(in) :: core real(default) :: alpha_s end function term_instance_get_alpha_s <>= module function term_instance_get_alpha_s (term, core) result (alpha_s) class(term_instance_t), intent(in) :: term class(prc_core_t), intent(in) :: core real(default) :: alpha_s alpha_s = core%get_alpha_s (term%core_state) if (alpha_s < zero) alpha_s = term%config%alpha_s end function term_instance_get_alpha_s @ %def term_instance_get_alpha_s @ The second helicity for [[helicities]] comes with a minus sign because OpenLoops inverts the helicity index of antiparticles. <>= procedure :: get_helicities_for_openloops => & term_instance_get_helicities_for_openloops <>= module subroutine term_instance_get_helicities_for_openloops & (term, helicities) class(term_instance_t), intent(in) :: term integer, dimension(:,:), allocatable, intent(out) :: helicities end subroutine term_instance_get_helicities_for_openloops <>= module subroutine term_instance_get_helicities_for_openloops & (term, helicities) class(term_instance_t), intent(in) :: term integer, dimension(:,:), allocatable, intent(out) :: helicities type(helicity_t), dimension(:), allocatable :: hel type(quantum_numbers_t), dimension(:,:), allocatable :: qn type(quantum_numbers_mask_t) :: qn_mask integer :: h, i, j, n_in call qn_mask%set_sub (1) call term%isolated%trace%get_quantum_numbers_mask (qn_mask, qn) n_in = term%int_hard%get_n_in () allocate (helicities (size (qn, dim=1), n_in)) allocate (hel (n_in)) do i = 1, size (qn, dim=1) do j = 1, n_in hel(j) = qn(i, j)%get_helicity () call hel(j)%diagonalize () call hel(j)%get_indices (h, h) helicities (i, j) = h end do end do end subroutine term_instance_get_helicities_for_openloops @ %def term_instance_get_helicities_for_openloops @ <>= procedure :: get_i_term_global => term_instance_get_i_term_global <>= elemental module function term_instance_get_i_term_global & (term) result (i_term) integer :: i_term class(term_instance_t), intent(in) :: term end function term_instance_get_i_term_global <>= elemental module function term_instance_get_i_term_global & (term) result (i_term) integer :: i_term class(term_instance_t), intent(in) :: term i_term = term%config%i_term_global end function term_instance_get_i_term_global @ %def term_instance_get_i_term_global @ <>= procedure :: is_subtraction => term_instance_is_subtraction <>= elemental module function term_instance_is_subtraction (term) result (sub) logical :: sub class(term_instance_t), intent(in) :: term end function term_instance_is_subtraction <>= elemental module function term_instance_is_subtraction (term) result (sub) logical :: sub class(term_instance_t), intent(in) :: term sub = term%config%i_term_global == term%config%i_sub end function term_instance_is_subtraction @ %def term_instance_is_subtraction @ Retrieve [[n_sub]] which was calculated in [[process_term_setup_interaction]]. <>= procedure :: get_n_sub => term_instance_get_n_sub procedure :: get_n_sub_color => term_instance_get_n_sub_color procedure :: get_n_sub_spin => term_instance_get_n_sub_spin <>= module function term_instance_get_n_sub (term) result (n_sub) integer :: n_sub class(term_instance_t), intent(in) :: term end function term_instance_get_n_sub module function term_instance_get_n_sub_color (term) result (n_sub_color) integer :: n_sub_color class(term_instance_t), intent(in) :: term end function term_instance_get_n_sub_color module function term_instance_get_n_sub_spin (term) result (n_sub_spin) integer :: n_sub_spin class(term_instance_t), intent(in) :: term end function term_instance_get_n_sub_spin <>= module function term_instance_get_n_sub (term) result (n_sub) integer :: n_sub class(term_instance_t), intent(in) :: term n_sub = term%config%n_sub end function term_instance_get_n_sub module function term_instance_get_n_sub_color (term) result (n_sub_color) integer :: n_sub_color class(term_instance_t), intent(in) :: term n_sub_color = term%config%n_sub_color end function term_instance_get_n_sub_color module function term_instance_get_n_sub_spin (term) result (n_sub_spin) integer :: n_sub_spin class(term_instance_t), intent(in) :: term n_sub_spin = term%config%n_sub_spin end function term_instance_get_n_sub_spin @ %def term_instance_get_n_sub @ %def term_instance_get_n_sub_color @ %def term_instance_get_n_sub_spin @ \subsection{The process instance} NOTE: The description below represents the intended structure after refactoring and disentangling the FKS-NLO vs. LO algorithm dependencies. A process instance contains all process data that depend on the sampling point and thus change often. In essence, it is an event record at the elementary (parton) level. We do not call it such, to avoid confusion with the actual event records. If decays are involved, the latter are compositions of several elementary processes (i.e., their instances). We implement the process instance as an extension of the [[mci_sampler_t]] that we need for computing integrals and generate events. The base type contains: the [[integrand]], the [[selected_channel]], the two-dimensional array [[x]] of parameters, and the one-dimensional array [[f]] of Jacobians. These subobjects are public and used for communicating with the multi-channel integrator. The [[process]] pointer accesses the process of which this record is an instance. It is required whenever the calculation needs invariant configuration data, therefore the process should stay in memory for the whole lifetime of its instances. The [[pcm]] pointer is a shortcut to the [[pcm]] (process-component manager) component of the associated process, which we need wherever the calculation depends on the overall algorithm. The [[pcm_work]] component is the workspace for the [[pcm]] object referenced above. The [[evaluation_status]] code is used to check the current status. In particular, failure at various stages is recorded there. The [[count]] object records process evaluations, broken down according to status. The [[sqme]] value is the single real number that results from evaluating and tracing the kinematics and matrix elements. This is the number that is handed over to an integration routine. The [[weight]] value is the event weight. It is defined when an event has been generated from the process instance, either weighted or unweighted. The value is the [[sqme]] value times Jacobian weights from the integration, or unity, respectively. The [[i_mci]] index chooses a subset of components that are associated with a common parameter set and integrator, i.e., that are added coherently. The [[sf_chain]] subobject is a realization of the beam and structure-function configuration in the [[process]] object. It is not used for calculation directly but serves as the template for the sf-chain instances that are contained in the [[component]] objects. The [[kinematics]] array contains the set of phase-space points that are associated with the current calculation. The entries may correspond to different process components and terms. (TODO wk 19-02-22: Not implemented yet.) TODO wk 19-02-22: May include extra arrays for storing (squared) amplitude data. The [[term]] data set may be reduced to just results, or be removed altogether. The [[term]] subobjects are workspace for evaluating kinematics, matrix elements, cuts etc. The array entries correspond to the [[term]] configuration entries in the associated process object. The [[mci_work]] subobject contains the array of real input parameters (random numbers) that generates the kinematical point. It also contains the workspace for the MC integrators. The active entry of the [[mci_work]] array is selected by the [[i_mci]] index above. The [[hook]] pointer accesses a list of after evaluate objects which are evalutated after the matrix element. <>= public :: process_instance_t <>= type, extends (mci_sampler_t) :: process_instance_t type(process_t), pointer :: process => null () class(pcm_t), pointer :: pcm => null () class(pcm_workspace_t), allocatable :: pcm_work integer :: evaluation_status = STAT_UNDEFINED real(default) :: sqme = 0 real(default) :: weight = 0 real(default) :: excess = 0 integer :: n_dropped = 0 integer :: i_mci = 0 integer :: selected_channel = 0 type(sf_chain_t) :: sf_chain type(kinematics_t), dimension(:), allocatable :: kin type(term_instance_t), dimension(:), allocatable :: term type(mci_work_t), dimension(:), allocatable :: mci_work class(process_instance_hook_t), pointer :: hook => null () contains <> end type process_instance_t @ %def process_instance @ Wrapper type for storing pointers to process instance objects in arrays. <>= public :: process_instance_ptr_t <>= type :: process_instance_ptr_t type(process_instance_t), pointer :: p => null () end type process_instance_ptr_t @ %def process_instance_ptr_t @ The process hooks are first-in-last-out list of objects which are evaluated after the phase space and matrixelement are evaluated. It is possible to retrieve the sampler object and read the sampler information. The hook object are part of the [[process_instance]] and therefore, share a common lifetime. A data transfer, after the usual lifetime of the [[process_instance]], is not provided, as such the finalisation procedure has to take care of this! E.g. write the object to file from which later the collected information can then be retrieved. <>= public :: process_instance_hook_t <>= type, abstract :: process_instance_hook_t class(process_instance_hook_t), pointer :: next => null () contains procedure(process_instance_hook_init), deferred :: init procedure(process_instance_hook_final), deferred :: final procedure(process_instance_hook_evaluate), deferred :: evaluate end type process_instance_hook_t @ %def process_instance_hook_t @ We have to provide an [[init]], a [[final]] procedure and, for after evaluation, the [[evaluate]] procedure. The [[init]] procedures accesses [[var_list]] and current [[instance]] object. <>= public :: process_instance_hook_final, process_instance_hook_evaluate <>= abstract interface subroutine process_instance_hook_init (hook, var_list, instance, pdf_data) import :: process_instance_hook_t, var_list_t, process_instance_t, pdf_data_t class(process_instance_hook_t), intent(inout), target :: hook type(var_list_t), intent(in) :: var_list class(process_instance_t), intent(in), target :: instance type(pdf_data_t), intent(in), optional :: pdf_data end subroutine process_instance_hook_init subroutine process_instance_hook_final (hook) import :: process_instance_hook_t class(process_instance_hook_t), intent(inout) :: hook end subroutine process_instance_hook_final subroutine process_instance_hook_evaluate (hook, instance) import :: process_instance_hook_t, process_instance_t class(process_instance_hook_t), intent(inout) :: hook class(process_instance_t), intent(in), target :: instance end subroutine process_instance_hook_evaluate end interface @ %def process_instance_hook_final, process_instance_hook_evaluate @ The output routine contains a header with the most relevant information about the process, copied from [[process_metadata_write]]. We mark the active components by an asterisk. The next section is the MC parameter input. The following sections are written only if the evaluation status is beyond setting the parameters, or if the [[verbose]] option is set. <>= procedure :: write_header => process_instance_write_header procedure :: write => process_instance_write <>= module subroutine process_instance_write_header (object, unit, testflag) class(process_instance_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag end subroutine process_instance_write_header module subroutine process_instance_write (object, unit, testflag) class(process_instance_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag end subroutine process_instance_write <>= module subroutine process_instance_write_header (object, unit, testflag) class(process_instance_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u u = given_output_unit (unit) call write_separator (u, 2) if (associated (object%process)) then call object%process%write_meta (u, testflag) else write (u, "(1x,A)") "Process instance [undefined process]" return end if write (u, "(3x,A)", advance = "no") "status = " select case (object%evaluation_status) case (STAT_INITIAL); write (u, "(A)") "initialized" case (STAT_ACTIVATED); write (u, "(A)") "activated" case (STAT_BEAM_MOMENTA); write (u, "(A)") "beam momenta set" case (STAT_FAILED_KINEMATICS); write (u, "(A)") "failed kinematics" case (STAT_SEED_KINEMATICS); write (u, "(A)") "seed kinematics" case (STAT_HARD_KINEMATICS); write (u, "(A)") "hard kinematics" case (STAT_EFF_KINEMATICS); write (u, "(A)") "effective kinematics" case (STAT_FAILED_CUTS); write (u, "(A)") "failed cuts" case (STAT_PASSED_CUTS); write (u, "(A)") "passed cuts" case (STAT_EVALUATED_TRACE); write (u, "(A)") "evaluated trace" call write_separator (u) write (u, "(3x,A,ES19.12)") "sqme = ", object%sqme case (STAT_EVENT_COMPLETE); write (u, "(A)") "event complete" call write_separator (u) write (u, "(3x,A,ES19.12)") "sqme = ", object%sqme write (u, "(3x,A,ES19.12)") "weight = ", object%weight if (.not. vanishes (object%excess)) & write (u, "(3x,A,ES19.12)") "excess = ", object%excess case default; write (u, "(A)") "undefined" end select if (object%i_mci /= 0) then call write_separator (u) call object%mci_work(object%i_mci)%write (u, testflag) end if call write_separator (u, 2) end subroutine process_instance_write_header module subroutine process_instance_write (object, unit, testflag) class(process_instance_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u, i u = given_output_unit (unit) call object%write_header (u) if (object%evaluation_status >= STAT_BEAM_MOMENTA) then call object%sf_chain%write (u) call write_separator (u, 2) if (object%evaluation_status >= STAT_SEED_KINEMATICS) then if (object%evaluation_status >= STAT_HARD_KINEMATICS) then call write_separator (u, 2) write (u, "(1x,A)") "Active terms:" if (any (object%term%active)) then do i = 1, size (object%term) if (object%term(i)%active) then call write_separator (u) call object%term(i)%write (u, & kin = object%kin(i), & show_eff_state = & object%evaluation_status >= STAT_EFF_KINEMATICS, & testflag = testflag) end if end do end if end if call write_separator (u, 2) end if end if end subroutine process_instance_write @ %def process_instance_write_header @ %def process_instance_write @ Initialization connects the instance with a process. All initial information is transferred from the process object. The process object contains templates for the interaction subobjects (beam and term), but no evaluators. The initialization routine creates evaluators for the matrix element trace, other evaluators are left untouched. Before we start generating, we double-check if the process library has been updated after the process was initializated ([[check_library_sanity]]). This may happen if between integration and event generation the library has been recompiled, so all links become broken. The [[instance]] object must have the [[target]] attribute (also in any caller) since the initialization routine assigns various pointers to subobject of [[instance]]. <>= procedure :: init => process_instance_init <>= module subroutine process_instance_init (instance, process) class(process_instance_t), intent(out), target :: instance type(process_t), intent(inout), target :: process end subroutine process_instance_init <>= module subroutine process_instance_init (instance, process) class(process_instance_t), intent(out), target :: instance type(process_t), intent(inout), target :: process integer :: i class(pcm_t), pointer :: pcm type(process_term_t), pointer :: term type(var_list_t), pointer :: var_list integer :: i_born, i_real, i_real_fin, i_component if (debug_on) call msg_debug & (D_PROCESS_INTEGRATION, "process_instance_init") instance%process => process instance%pcm => process%get_pcm_ptr () call instance%process%check_library_sanity () call instance%setup_sf_chain (process%get_beam_config_ptr ()) allocate (instance%mci_work (process%get_n_mci ())) do i = 1, size (instance%mci_work) call instance%process%init_mci_work (instance%mci_work(i), i) end do call instance%process%reset_selected_cores () pcm => instance%process%get_pcm_ptr () call pcm%allocate_workspace (instance%pcm_work) select type (pcm) type is (pcm_nlo_t) !!! The process is kept when the integration is finalized, but not the !!! process_instance. Thus, we check whether pcm has been initialized !!! but set up the pcm_work each time. i_real_fin = process%get_associated_real_fin (1) if (.not. pcm%initialized) then i_born = pcm%get_i_core (pcm%i_born) i_real = pcm%get_i_core (pcm%i_real) call pcm%init_qn (process%get_model_ptr ()) if (i_real_fin > 0) call pcm%allocate_ps_matching () var_list => process%get_var_list_ptr () if (var_list%get_sval (var_str ("$dalitz_plot")) /= var_str ('')) & call pcm%activate_dalitz_plot (var_list%get_sval (var_str ("$dalitz_plot"))) end if pcm%initialized = .true. select type (pcm_work => instance%pcm_work) type is (pcm_nlo_workspace_t) call pcm_work%init_config (pcm, & process%component_can_be_integrated (), & process%get_nlo_type_component (), process%get_energy (), & i_real_fin, process%get_model_ptr ()) end select end select ! TODO wk-03-01 n_terms will eventually acquire a different meaning allocate (instance%kin (process%get_n_terms ())) do i = 1, process%get_n_terms () term => process%get_term_ptr (i) i_component = term%i_component call instance%kin(i)%configure (pcm, instance%pcm_work, & instance%sf_chain, & process%get_beam_config_ptr (), & process%get_phs_config (i_component), & process%get_nlo_type_component (i_component), & term%i_sub == i) end do ! TODO wk-03-01 n_terms will eventually acquire a different meaning allocate (instance%term (process%get_n_terms ())) do i = 1, process%get_n_terms () call instance%term(i)%configure (process, i, instance%pcm_work, & instance%sf_chain, instance%kin(i)) end do call instance%set_i_mci_to_real_component () call instance%find_same_kinematics () instance%evaluation_status = STAT_INITIAL end subroutine process_instance_init @ %def process_instance_init @ @ Finalize all subobjects that may contain allocated pointers. <>= procedure :: final => process_instance_final <>= module subroutine process_instance_final (instance) class(process_instance_t), intent(inout) :: instance end subroutine process_instance_final <>= module subroutine process_instance_final (instance) class(process_instance_t), intent(inout) :: instance class(process_instance_hook_t), pointer :: current integer :: i instance%process => null () if (allocated (instance%mci_work)) then do i = 1, size (instance%mci_work) call instance%mci_work(i)%final () end do deallocate (instance%mci_work) end if call instance%sf_chain%final () if (allocated (instance%kin)) then do i = 1, size (instance%kin) call instance%kin(i)%final () end do deallocate (instance%kin) end if if (allocated (instance%term)) then do i = 1, size (instance%term) call instance%term(i)%final () end do deallocate (instance%term) end if call instance%pcm_work%final () instance%evaluation_status = STAT_UNDEFINED do while (associated (instance%hook)) current => instance%hook call current%final () instance%hook => current%next deallocate (current) end do instance%hook => null () end subroutine process_instance_final @ %def process_instance_final @ Revert the process instance to initial state. We do not deallocate anything, just reset the state index and deactivate all components and terms. We do not reset the choice of the MCI set [[i_mci]] unless this is required explicitly. <>= procedure :: reset => process_instance_reset <>= module subroutine process_instance_reset (instance, reset_mci) class(process_instance_t), intent(inout), target :: instance logical, intent(in), optional :: reset_mci end subroutine process_instance_reset <>= module subroutine process_instance_reset (instance, reset_mci) class(process_instance_t), intent(inout), target :: instance logical, intent(in), optional :: reset_mci integer :: i call instance%process%reset_selected_cores () do i = 1, size (instance%term) call instance%term(i)%reset () end do instance%term%checked = .false. instance%term%passed = .false. instance%kin%new_seed = .true. if (present (reset_mci)) then if (reset_mci) instance%i_mci = 0 end if instance%selected_channel = 0 instance%evaluation_status = STAT_INITIAL end subroutine process_instance_reset @ %def process_instance_reset @ \subsubsection{Integration and event generation} The sampler test should just evaluate the squared matrix element [[n_calls]] times, discarding the results, and return. This can be done before integration, e.g., for timing estimates. <>= procedure :: sampler_test => process_instance_sampler_test <>= module subroutine process_instance_sampler_test (instance, i_mci, n_calls) class(process_instance_t), intent(inout), target :: instance integer, intent(in) :: i_mci integer, intent(in) :: n_calls end subroutine process_instance_sampler_test <>= module subroutine process_instance_sampler_test (instance, i_mci, n_calls) class(process_instance_t), intent(inout), target :: instance integer, intent(in) :: i_mci integer, intent(in) :: n_calls integer :: i_mci_work i_mci_work = instance%process%get_i_mci_work (i_mci) call instance%choose_mci (i_mci_work) call instance%reset_counter () call instance%process%sampler_test (instance, n_calls, i_mci_work) call instance%process%set_counter_mci_entry (i_mci_work, instance%get_counter ()) end subroutine process_instance_sampler_test @ %def process_instance_sampler_test @ Generate a weighted event. We select one of the available MCI integrators by its index [[i_mci]] and thus generate an event for the associated (group of) process component(s). The arguments exactly correspond to the initializer and finalizer above. The resulting event is stored in the [[process_instance]] object, which also holds the workspace of the integrator. Note: The [[process]] object contains the random-number state, which changes for each event. Otherwise, all volatile data are inside the [[instance]] object. <>= procedure :: generate_weighted_event => & process_instance_generate_weighted_event <>= module subroutine process_instance_generate_weighted_event (instance, i_mci) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_mci end subroutine process_instance_generate_weighted_event <>= module subroutine process_instance_generate_weighted_event (instance, i_mci) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_mci integer :: i_mci_work i_mci_work = instance%process%get_i_mci_work (i_mci) call instance%choose_mci (i_mci_work) associate (mci_work => instance%mci_work(i_mci_work)) call instance%process%generate_weighted_event & (i_mci_work, mci_work, instance, & instance%keep_failed_events ()) end associate end subroutine process_instance_generate_weighted_event @ %def process_instance_generate_weighted_event @ <>= procedure :: generate_unweighted_event => & process_instance_generate_unweighted_event <>= module subroutine process_instance_generate_unweighted_event & (instance, i_mci) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_mci end subroutine process_instance_generate_unweighted_event <>= module subroutine process_instance_generate_unweighted_event (instance, i_mci) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_mci integer :: i_mci_work i_mci_work = instance%process%get_i_mci_work (i_mci) call instance%choose_mci (i_mci_work) associate (mci_work => instance%mci_work(i_mci_work)) call instance%process%generate_unweighted_event & (i_mci_work, mci_work, instance) end associate end subroutine process_instance_generate_unweighted_event @ %def process_instance_generate_unweighted_event @ This replaces the event generation methods for the situation that the process instance object has been filled by other means (i.e., reading and/or recalculating its contents). We just have to fill in missing MCI data, especially the event weight. <>= procedure :: recover_event => process_instance_recover_event <>= module subroutine process_instance_recover_event (instance) class(process_instance_t), intent(inout) :: instance end subroutine process_instance_recover_event <>= module subroutine process_instance_recover_event (instance) class(process_instance_t), intent(inout) :: instance integer :: i_mci i_mci = instance%i_mci call instance%process%set_i_mci_work (i_mci) associate (mci_instance => instance%mci_work(i_mci)%mci) call mci_instance%fetch (instance, instance%selected_channel) end associate end subroutine process_instance_recover_event @ %def process_instance_recover_event @ @ Activate the components and terms that correspond to a currently selected MCI parameter set. <>= procedure :: activate => process_instance_activate <>= module subroutine process_instance_activate (instance) class(process_instance_t), intent(inout) :: instance end subroutine process_instance_activate <>= module subroutine process_instance_activate (instance) class(process_instance_t), intent(inout) :: instance integer :: i, j integer, dimension(:), allocatable :: i_term associate (mci_work => instance%mci_work(instance%i_mci)) call instance%process%select_components & (mci_work%get_active_components ()) end associate associate (process => instance%process) do i = 1, instance%process%get_n_components () if (instance%process%component_is_selected (i)) then allocate (i_term (size (process%get_component_i_terms (i)))) i_term = process%get_component_i_terms (i) do j = 1, size (i_term) instance%term(i_term(j))%active = .true. end do end if if (allocated (i_term)) deallocate (i_term) end do end associate instance%evaluation_status = STAT_ACTIVATED end subroutine process_instance_activate @ %def process_instance_activate @ <>= procedure :: find_same_kinematics => process_instance_find_same_kinematics <>= module subroutine process_instance_find_same_kinematics (instance) class(process_instance_t), intent(inout) :: instance end subroutine process_instance_find_same_kinematics <>= module subroutine process_instance_find_same_kinematics (instance) class(process_instance_t), intent(inout) :: instance integer :: i_term1, i_term2, k, n_same do i_term1 = 1, size (instance%term) if (.not. allocated (instance%term(i_term1)%same_kinematics)) then n_same = 1 !!! Index group includes the index of its term_instance do i_term2 = 1, size (instance%term) if (i_term1 == i_term2) cycle if (compare_md5s (i_term1, i_term2)) n_same = n_same + 1 end do allocate (instance%term(i_term1)%same_kinematics (n_same)) associate (same_kinematics1 => instance%term(i_term1)%same_kinematics) same_kinematics1 = 0 k = 1 do i_term2 = 1, size (instance%term) if (compare_md5s (i_term1, i_term2)) then same_kinematics1(k) = i_term2 k = k + 1 end if end do do k = 1, size (same_kinematics1) if (same_kinematics1(k) == i_term1) cycle i_term2 = same_kinematics1(k) allocate (instance%term(i_term2)%same_kinematics (n_same)) instance%term(i_term2)%same_kinematics = same_kinematics1 end do end associate end if end do contains function compare_md5s (i, j) result (same) logical :: same integer, intent(in) :: i, j character(32) :: md5sum_1, md5sum_2 integer :: mode_1, mode_2 mode_1 = 0; mode_2 = 0 select type (phs => instance%kin(i)%phs%config) type is (phs_fks_config_t) md5sum_1 = phs%md5sum_born_config mode_1 = phs%mode class default md5sum_1 = phs%md5sum_phs_config end select select type (phs => instance%kin(j)%phs%config) type is (phs_fks_config_t) md5sum_2 = phs%md5sum_born_config mode_2 = phs%mode class default md5sum_2 = phs%md5sum_phs_config end select same = (md5sum_1 == md5sum_2) .and. (mode_1 == mode_2) end function compare_md5s end subroutine process_instance_find_same_kinematics @ %def process_instance_find_same_kinematics @ <>= procedure :: transfer_same_kinematics => & process_instance_transfer_same_kinematics <>= module subroutine process_instance_transfer_same_kinematics & (instance, i_term) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_term end subroutine process_instance_transfer_same_kinematics <>= module subroutine process_instance_transfer_same_kinematics (instance, i_term) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_term integer :: i, i_term_same associate (same_kinematics => instance%term(i_term)%same_kinematics) do i = 1, size (same_kinematics) i_term_same = same_kinematics(i) instance%term(i_term_same)%p_seed = instance%term(i_term)%p_seed associate (phs => instance%kin(i_term_same)%phs) call phs%set_lorentz_transformation & (instance%kin(i_term)%phs%get_lorentz_transformation ()) select type (phs) type is (phs_fks_t) call phs%set_momenta (instance%term(i_term_same)%p_seed) if (i_term_same /= i_term) then call phs%set_reference_frames (.false.) end if end select end associate instance%kin(i_term_same)%new_seed = .false. end do end associate end subroutine process_instance_transfer_same_kinematics @ %def process_instance_transfer_same_kinematics @ <>= procedure :: redo_sf_chains => process_instance_redo_sf_chains <>= module subroutine process_instance_redo_sf_chains & (instance, i_term, phs_channel) class(process_instance_t), intent(inout) :: instance integer, intent(in), dimension(:) :: i_term integer, intent(in) :: phs_channel end subroutine process_instance_redo_sf_chains <>= module subroutine process_instance_redo_sf_chains & (instance, i_term, phs_channel) class(process_instance_t), intent(inout) :: instance integer, intent(in), dimension(:) :: i_term integer, intent(in) :: phs_channel integer :: i do i = 1, size (i_term) call instance%kin(i_term(i))%redo_sf_chain & (instance%mci_work(instance%i_mci), phs_channel) end do end subroutine process_instance_redo_sf_chains @ %def process_instance_redo_sf_chains @ Integrate the process, using a previously initialized process instance. We select one of the available MCI integrators by its index [[i_mci]] and thus integrate over (structure functions and) phase space for the associated (group of) process component(s). <>= procedure :: integrate => process_instance_integrate <>= module subroutine process_instance_integrate (instance, i_mci, & n_it, n_calls, adapt_grids, adapt_weights, final, pacify) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_mci integer, intent(in) :: n_it integer, intent(in) :: n_calls logical, intent(in), optional :: adapt_grids logical, intent(in), optional :: adapt_weights logical, intent(in), optional :: final, pacify end subroutine process_instance_integrate <>= module subroutine process_instance_integrate (instance, i_mci, & n_it, n_calls, adapt_grids, adapt_weights, final, pacify) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_mci integer, intent(in) :: n_it integer, intent(in) :: n_calls logical, intent(in), optional :: adapt_grids logical, intent(in), optional :: adapt_weights logical, intent(in), optional :: final, pacify integer :: nlo_type, i_mci_work nlo_type = instance%process%get_component_nlo_type (i_mci) i_mci_work = instance%process%get_i_mci_work (i_mci) call instance%choose_mci (i_mci_work) call instance%reset_counter () associate (mci_work => instance%mci_work(i_mci_work), & process => instance%process) call process%integrate (i_mci_work, mci_work, & instance, n_it, n_calls, adapt_grids, adapt_weights, & final, pacify, nlo_type = nlo_type) call process%set_counter_mci_entry (i_mci_work, instance%get_counter ()) end associate end subroutine process_instance_integrate @ %def process_instance_integrate @ Subroutine of the initialization above: initialize the beam and structure-function chain template. We establish pointers to the configuration data, so [[beam_config]] must have a [[target]] attribute. The resulting chain is not used directly for calculation. It will acquire instances which are stored in the process-component instance objects. <>= procedure :: setup_sf_chain => process_instance_setup_sf_chain <>= module subroutine process_instance_setup_sf_chain (instance, config) class(process_instance_t), intent(inout) :: instance type(process_beam_config_t), intent(in), target :: config end subroutine process_instance_setup_sf_chain <>= module subroutine process_instance_setup_sf_chain (instance, config) class(process_instance_t), intent(inout) :: instance type(process_beam_config_t), intent(in), target :: config integer :: n_strfun n_strfun = config%n_strfun if (n_strfun /= 0) then call instance%sf_chain%init (config%data, config%sf) else call instance%sf_chain%init (config%data) end if if (config%sf_trace) then call instance%sf_chain%setup_tracing (config%sf_trace_file) end if end subroutine process_instance_setup_sf_chain @ %def process_instance_setup_sf_chain @ This initialization routine should be called only for process instances which we intend as a source for physical events. It initializes the evaluators in the parton states of the terms. They describe the (semi-)exclusive transition matrix and the distribution of color flow for the partonic process, convoluted with the beam and structure-function chain. If the model is not provided explicitly, we may use the model instance that belongs to the process. However, an explicit model allows us to override particle settings. <>= procedure :: setup_event_data => process_instance_setup_event_data <>= module subroutine process_instance_setup_event_data & (instance, model, i_core) class(process_instance_t), intent(inout), target :: instance class(model_data_t), intent(in), optional, target :: model integer, intent(in), optional :: i_core end subroutine process_instance_setup_event_data <>= module subroutine process_instance_setup_event_data (instance, model, i_core) class(process_instance_t), intent(inout), target :: instance class(model_data_t), intent(in), optional, target :: model integer, intent(in), optional :: i_core class(model_data_t), pointer :: current_model integer :: i class(prc_core_t), pointer :: core => null () if (present (model)) then current_model => model else current_model => instance%process%get_model_ptr () end if do i = 1, size (instance%term) associate (term => instance%term(i), kin => instance%kin(i)) if (associated (term%config)) then core => instance%process%get_core_term (i) call term%setup_event_data (kin, core, current_model) end if end associate end do core => null () end subroutine process_instance_setup_event_data @ %def process_instance_setup_event_data @ Choose a MC parameter set and the corresponding integrator. The choice persists beyond calls of the [[reset]] method above. This method is automatically called here. <>= procedure :: choose_mci => process_instance_choose_mci <>= module subroutine process_instance_choose_mci (instance, i_mci) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_mci end subroutine process_instance_choose_mci <>= module subroutine process_instance_choose_mci (instance, i_mci) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_mci instance%i_mci = i_mci call instance%reset () end subroutine process_instance_choose_mci @ %def process_instance_choose_mci @ Explicitly set a MC parameter set. Works only if we are in initial state. We assume that the length of the parameter set is correct. After setting the parameters, activate the components and terms that correspond to the chosen MC parameter set. The [[warmup_flag]] is used when a dummy phase-space point is computed for the warmup of e.g. OpenLoops helicities. The setting of the the [[evaluation_status]] has to be avoided then. <>= procedure :: set_mcpar => process_instance_set_mcpar <>= module subroutine process_instance_set_mcpar (instance, x, warmup_flag) class(process_instance_t), intent(inout) :: instance real(default), dimension(:), intent(in) :: x logical, intent(in), optional :: warmup_flag end subroutine process_instance_set_mcpar <>= module subroutine process_instance_set_mcpar (instance, x, warmup_flag) class(process_instance_t), intent(inout) :: instance real(default), dimension(:), intent(in) :: x logical, intent(in), optional :: warmup_flag logical :: activate activate = .true.; if (present (warmup_flag)) activate = .not. warmup_flag if (instance%evaluation_status == STAT_INITIAL) then associate (mci_work => instance%mci_work(instance%i_mci)) call mci_work%set (x) end associate if (activate) call instance%activate () end if end subroutine process_instance_set_mcpar @ %def process_instance_set_mcpar @ Receive the beam momentum/momenta from a source interaction. This applies to a cascade decay process instance, where the `beam' momentum varies event by event. The master beam momentum array is contained in the main structure function chain subobject [[sf_chain]]. The sf-chain instance that reside in the components will take their beam momenta from there. The procedure transforms the instance status into [[STAT_BEAM_MOMENTA]]. For process instance with fixed beam, this intermediate status is skipped. <>= procedure :: receive_beam_momenta => process_instance_receive_beam_momenta <>= module subroutine process_instance_receive_beam_momenta (instance) class(process_instance_t), intent(inout) :: instance end subroutine process_instance_receive_beam_momenta <>= module subroutine process_instance_receive_beam_momenta (instance) class(process_instance_t), intent(inout) :: instance if (instance%evaluation_status >= STAT_INITIAL) then call instance%sf_chain%receive_beam_momenta () instance%evaluation_status = STAT_BEAM_MOMENTA end if end subroutine process_instance_receive_beam_momenta @ %def process_instance_receive_beam_momenta @ Set the beam momentum/momenta explicitly. Otherwise, analogous to the previous procedure. <>= procedure :: set_beam_momenta => process_instance_set_beam_momenta <>= module subroutine process_instance_set_beam_momenta (instance, p) class(process_instance_t), intent(inout) :: instance type(vector4_t), dimension(:), intent(in) :: p end subroutine process_instance_set_beam_momenta <>= module subroutine process_instance_set_beam_momenta (instance, p) class(process_instance_t), intent(inout) :: instance type(vector4_t), dimension(:), intent(in) :: p if (instance%evaluation_status >= STAT_INITIAL) then call instance%sf_chain%set_beam_momenta (p) instance%evaluation_status = STAT_BEAM_MOMENTA end if end subroutine process_instance_set_beam_momenta @ %def process_instance_set_beam_momenta @ Recover the initial beam momenta (those in the [[sf_chain]] component), given a valid (recovered) [[sf_chain_instance]] in one of the active components. We need to do this only if the lab frame is not the c.m.\ frame, otherwise those beams would be fixed anyway. <>= procedure :: recover_beam_momenta => process_instance_recover_beam_momenta <>= module subroutine process_instance_recover_beam_momenta (instance, i_term) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_term end subroutine process_instance_recover_beam_momenta <>= module subroutine process_instance_recover_beam_momenta (instance, i_term) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_term if (.not. instance%process%lab_is_cm ()) then if (instance%evaluation_status >= STAT_EFF_KINEMATICS) then call instance%kin(i_term)%return_beam_momenta () end if end if end subroutine process_instance_recover_beam_momenta @ %def process_instance_recover_beam_momenta @ Explicitly choose MC integration channel. We assume here that the channel count is identical for all active components. <>= procedure :: select_channel => process_instance_select_channel <>= module subroutine process_instance_select_channel (instance, channel) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: channel end subroutine process_instance_select_channel <>= module subroutine process_instance_select_channel (instance, channel) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: channel instance%selected_channel = channel end subroutine process_instance_select_channel @ %def process_instance_select_channel @ First step of process evaluation: set up seed kinematics. That is, for each active process component, compute a momentum array from the MC input parameters. If [[skip_term]] is set, we skip the component that accesses this term. We can assume that the associated data have already been recovered, and we are just computing the rest. <>= procedure :: compute_seed_kinematics => & process_instance_compute_seed_kinematics <>= module subroutine process_instance_compute_seed_kinematics & (instance, recover, skip_term) class(process_instance_t), intent(inout) :: instance logical, intent(in), optional :: recover integer, intent(in), optional :: skip_term end subroutine process_instance_compute_seed_kinematics <>= module subroutine process_instance_compute_seed_kinematics & (instance, recover, skip_term) class(process_instance_t), intent(inout) :: instance logical, intent(in), optional :: recover integer, intent(in), optional :: skip_term integer :: channel, skip_component, i, j logical :: success integer, dimension(:), allocatable :: i_term channel = instance%selected_channel if (channel == 0) then call msg_bug ("Compute seed kinematics: undefined integration channel") end if if (present (skip_term)) then skip_component = instance%term(skip_term)%config%i_component else skip_component = 0 end if if (present (recover)) then if (recover) return end if if (instance%evaluation_status >= STAT_ACTIVATED) then success = .true. do i = 1, instance%process%get_n_components () if (i == skip_component) cycle if (instance%process%component_is_selected (i)) then allocate (i_term (size (instance%process%get_component_i_terms (i)))) i_term = instance%process%get_component_i_terms (i) do j = 1, size (i_term) associate (term => instance%term(i_term(j)), kin => instance%kin(i_term(j))) if (kin%new_seed) then call term%compute_seed_kinematics (kin, & instance%mci_work(instance%i_mci), channel, success) call instance%transfer_same_kinematics (i_term(j)) end if if (.not. success) exit select type (pcm => instance%pcm) class is (pcm_nlo_t) call term%evaluate_projections (kin) call kin%evaluate_radiation_kinematics & (instance%mci_work(instance%i_mci)%get_x_process ()) call kin%generate_fsr_in () call kin%compute_xi_ref_momenta (pcm%region_data, term%nlo_type) end select end associate end do end if if (allocated (i_term)) deallocate (i_term) end do if (success) then instance%evaluation_status = STAT_SEED_KINEMATICS else instance%evaluation_status = STAT_FAILED_KINEMATICS end if end if associate (mci_work => instance%mci_work(instance%i_mci)) select type (pcm_work => instance%pcm_work) class is (pcm_nlo_workspace_t) call pcm_work%set_x_rad (mci_work%get_x_process ()) end select end associate end subroutine process_instance_compute_seed_kinematics @ %def process_instance_compute_seed_kinematics @ <>= procedure :: get_x_process => process_instance_get_x_process <>= pure module function process_instance_get_x_process (instance) result (x) real(default), dimension(:), allocatable :: x class(process_instance_t), intent(in) :: instance end function process_instance_get_x_process <>= pure module function process_instance_get_x_process (instance) result (x) real(default), dimension(:), allocatable :: x class(process_instance_t), intent(in) :: instance allocate (x(size (instance%mci_work(instance%i_mci)%get_x_process ()))) x = instance%mci_work(instance%i_mci)%get_x_process () end function process_instance_get_x_process @ %def process_instance_get_x_process @ <>= procedure :: get_active_component_type => & process_instance_get_active_component_type <>= pure module function process_instance_get_active_component_type & (instance) result (nlo_type) integer :: nlo_type class(process_instance_t), intent(in) :: instance end function process_instance_get_active_component_type <>= pure module function process_instance_get_active_component_type & (instance) result (nlo_type) integer :: nlo_type class(process_instance_t), intent(in) :: instance nlo_type = instance%process%get_component_nlo_type (instance%i_mci) end function process_instance_get_active_component_type @ %def process_instance_get_active_component_type @ Inverse: recover missing parts of the kinematics from the momentum configuration, which we know for a single term and component. Given a channel, reconstruct the MC parameter set. <>= procedure :: recover_mcpar => process_instance_recover_mcpar <>= module subroutine process_instance_recover_mcpar (instance, i_term) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_term end subroutine process_instance_recover_mcpar <>= module subroutine process_instance_recover_mcpar (instance, i_term) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_term integer :: channel, i if (instance%evaluation_status >= STAT_EFF_KINEMATICS) then channel = instance%selected_channel if (channel == 0) then call msg_bug ("Recover MC parameters: undefined integration channel") end if call instance%kin(i_term)%recover_mcpar & (instance%mci_work(instance%i_mci), channel, instance%term(i_term)%p_seed) if (instance%term(i_term)%nlo_type == NLO_REAL) then do i = 1, size (instance%term) if (i /= i_term .and. instance%term(i)%nlo_type == NLO_REAL) then if (instance%term(i)%active) then call instance%kin(i)%recover_mcpar & (instance%mci_work(instance%i_mci), channel, & instance%term(i)%p_seed) end if end if end do end if end if end subroutine process_instance_recover_mcpar @ %def process_instance_recover_mcpar @ This is part of [[recover_mcpar]], extracted for the case when there is no phase space and parameters to recover, but we still need the structure function kinematics for evaluation. <>= procedure :: recover_sfchain => process_instance_recover_sfchain <>= module subroutine process_instance_recover_sfchain (instance, i_term) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_term end subroutine process_instance_recover_sfchain <>= module subroutine process_instance_recover_sfchain (instance, i_term) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_term integer :: channel if (instance%evaluation_status >= STAT_EFF_KINEMATICS) then channel = instance%selected_channel if (channel == 0) then call msg_bug ("Recover sfchain: undefined integration channel") end if call instance%kin(i_term)%recover_sfchain & (channel, instance%term(i_term)%p_seed) end if end subroutine process_instance_recover_sfchain @ %def process_instance_recover_sfchain @ Second step of process evaluation: compute all momenta, for all active components, from the seed kinematics. <>= procedure :: compute_hard_kinematics => & process_instance_compute_hard_kinematics <>= module subroutine process_instance_compute_hard_kinematics & (instance, recover, skip_term) class(process_instance_t), intent(inout) :: instance integer, intent(in), optional :: skip_term logical, intent(in), optional :: recover end subroutine process_instance_compute_hard_kinematics <>= module subroutine process_instance_compute_hard_kinematics & (instance, recover, skip_term) class(process_instance_t), intent(inout) :: instance integer, intent(in), optional :: skip_term logical, intent(in), optional :: recover integer :: i logical :: success success = .true. if (instance%evaluation_status >= STAT_SEED_KINEMATICS) then do i = 1, size (instance%term) associate (term => instance%term(i), kin => instance%kin(i)) if (term%active) then call term%compute_hard_kinematics & (kin, recover, skip_term, success) if (.not. success) exit !!! Ren scale is zero when this is commented out! Understand! if (term%nlo_type == NLO_REAL) & call kin%redo_sf_chain (instance%mci_work(instance%i_mci), & instance%selected_channel) end if end associate end do if (success) then instance%evaluation_status = STAT_HARD_KINEMATICS else instance%evaluation_status = STAT_FAILED_KINEMATICS end if end if end subroutine process_instance_compute_hard_kinematics @ %def process_instance_setup_compute_hard_kinematics @ Inverse: recover seed kinematics. We know the beam momentum configuration and the outgoing momenta of the effective interaction, for one specific term. <>= procedure :: recover_seed_kinematics => & process_instance_recover_seed_kinematics <>= module subroutine process_instance_recover_seed_kinematics & (instance, i_term) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_term end subroutine process_instance_recover_seed_kinematics <>= module subroutine process_instance_recover_seed_kinematics (instance, i_term) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_term type(vector4_t), dimension(:), allocatable :: p_seed_ref integer :: i if (instance%evaluation_status >= STAT_EFF_KINEMATICS) then call instance%term(i_term)%recover_seed_kinematics (instance%kin(i_term)) if (instance%term(i_term)%nlo_type == NLO_REAL) then allocate (p_seed_ref & (instance%term(i_term)%isolated%int_eff%get_n_out ())) p_seed_ref = instance%term(i_term)%isolated%int_eff%get_momenta & (outgoing = .true.) do i = 1, size (instance%term) if (i /= i_term .and. instance%term(i)%nlo_type == NLO_REAL) then if (instance%term(i)%active) then call instance%term(i)%recover_seed_kinematics & (instance%kin(i), p_seed_ref) end if end if end do end if end if end subroutine process_instance_recover_seed_kinematics @ %def process_instance_recover_seed_kinematics @ Third step of process evaluation: compute the effective momentum configurations, for all active terms, from the hard kinematics. <>= procedure :: compute_eff_kinematics => & process_instance_compute_eff_kinematics <>= module subroutine process_instance_compute_eff_kinematics & (instance, skip_term) class(process_instance_t), intent(inout) :: instance integer, intent(in), optional :: skip_term end subroutine process_instance_compute_eff_kinematics <>= module subroutine process_instance_compute_eff_kinematics & (instance, skip_term) class(process_instance_t), intent(inout) :: instance integer, intent(in), optional :: skip_term integer :: i if (instance%evaluation_status >= STAT_HARD_KINEMATICS) then do i = 1, size (instance%term) if (present (skip_term)) then if (i == skip_term) cycle end if if (instance%term(i)%active) then call instance%term(i)%compute_eff_kinematics () end if end do instance%evaluation_status = STAT_EFF_KINEMATICS end if end subroutine process_instance_compute_eff_kinematics @ %def process_instance_setup_compute_eff_kinematics @ Inverse: recover the hard kinematics from effective kinematics for one term, then compute effective kinematics for the other terms. <>= procedure :: recover_hard_kinematics => & process_instance_recover_hard_kinematics <>= module subroutine process_instance_recover_hard_kinematics & (instance, i_term) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_term end subroutine process_instance_recover_hard_kinematics <>= module subroutine process_instance_recover_hard_kinematics (instance, i_term) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_term integer :: i if (instance%evaluation_status >= STAT_EFF_KINEMATICS) then call instance%term(i_term)%recover_hard_kinematics () do i = 1, size (instance%term) if (i /= i_term) then if (instance%term(i)%active) then call instance%term(i)%compute_eff_kinematics () end if end if end do instance%evaluation_status = STAT_EFF_KINEMATICS end if end subroutine process_instance_recover_hard_kinematics @ %def recover_hard_kinematics @ Fourth step of process evaluation: check cuts for all terms. Where successful, compute any scales and weights. Otherwise, deactive the term. If any of the terms has passed, set the state to [[STAT_PASSED_CUTS]]. The argument [[scale_forced]], if present, will override the scale calculation in the term expressions. <>= procedure :: evaluate_expressions => & process_instance_evaluate_expressions <>= module subroutine process_instance_evaluate_expressions & (instance, scale_forced) class(process_instance_t), intent(inout) :: instance real(default), intent(in), allocatable, optional :: scale_forced end subroutine process_instance_evaluate_expressions <>= module subroutine process_instance_evaluate_expressions & (instance, scale_forced) class(process_instance_t), intent(inout) :: instance real(default), intent(in), allocatable, optional :: scale_forced integer :: i logical :: passed_real if (instance%evaluation_status >= STAT_EFF_KINEMATICS) then do i = 1, size (instance%term) if (instance%term(i)%active) then - call instance%term(i)%evaluate_expressions (scale_forced) + call instance%term(i)%evaluate_expressions & + (instance%process%get_beam_config (), scale_forced) end if end do call evaluate_real_scales_and_cuts () call set_ellis_sexton_scale () if (.not. passed_real) then instance%evaluation_status = STAT_FAILED_CUTS else if (any (instance%term%passed)) then instance%evaluation_status = STAT_PASSED_CUTS else instance%evaluation_status = STAT_FAILED_CUTS end if end if end if contains subroutine evaluate_real_scales_and_cuts () integer :: i passed_real = .true. select type (pcm => instance%pcm) type is (pcm_nlo_t) do i = 1, size (instance%term) if (instance%term(i)%active .and. instance%term(i)%nlo_type == NLO_REAL) then if (pcm%settings%cut_all_real_sqmes) & passed_real = passed_real .and. instance%term(i)%passed if (pcm%settings%use_born_scale) & call replace_scales (instance%term(i)) end if end do end select end subroutine evaluate_real_scales_and_cuts subroutine replace_scales (this_term) type(term_instance_t), intent(inout) :: this_term integer :: i_sub i_sub = this_term%config%i_sub if (this_term%config%i_term_global /= i_sub .and. i_sub > 0) then this_term%ren_scale = instance%term(i_sub)%ren_scale this_term%fac_scale = instance%term(i_sub)%fac_scale end if end subroutine replace_scales subroutine set_ellis_sexton_scale () real(default) :: es_scale type(var_list_t), pointer :: var_list integer :: i var_list => instance%process%get_var_list_ptr () es_scale = var_list%get_rval (var_str ("ellis_sexton_scale")) do i = 1, size (instance%term) if (instance%term(i)%active .and. instance%term(i)%nlo_type == NLO_VIRTUAL) then if (es_scale > zero) then if (allocated (instance%term(i)%es_scale)) then instance%term(i)%es_scale = es_scale else allocate (instance%term(i)%es_scale, source=es_scale) end if end if end if end do end subroutine set_ellis_sexton_scale end subroutine process_instance_evaluate_expressions @ %def process_instance_evaluate_expressions @ Fifth step of process evaluation: fill the parameters for the non-selected channels, that have not been used for seeding. We should do this after evaluating cuts, since we may save some expensive calculations if the phase space point fails the cuts. If [[skip_term]] is set, we skip the component that accesses this term. We can assume that the associated data have already been recovered, and we are just computing the rest. <>= procedure :: compute_other_channels => & process_instance_compute_other_channels <>= module subroutine process_instance_compute_other_channels & (instance, skip_term) class(process_instance_t), intent(inout) :: instance integer, intent(in), optional :: skip_term end subroutine process_instance_compute_other_channels <>= module subroutine process_instance_compute_other_channels & (instance, skip_term) class(process_instance_t), intent(inout) :: instance integer, intent(in), optional :: skip_term integer :: channel, skip_component, i, j integer, dimension(:), allocatable :: i_term channel = instance%selected_channel if (channel == 0) then call msg_bug ("Compute other channels: undefined integration channel") end if if (present (skip_term)) then skip_component = instance%term(skip_term)%config%i_component else skip_component = 0 end if if (instance%evaluation_status >= STAT_PASSED_CUTS) then do i = 1, instance%process%get_n_components () if (i == skip_component) cycle if (instance%process%component_is_selected (i)) then allocate (i_term (size (instance%process%get_component_i_terms (i)))) i_term = instance%process%get_component_i_terms (i) do j = 1, size (i_term) call instance%kin(i_term(j))%compute_other_channels & (instance%mci_work(instance%i_mci), channel) end do end if if (allocated (i_term)) deallocate (i_term) end do end if end subroutine process_instance_compute_other_channels @ %def process_instance_compute_other_channels @ If not done otherwise, we flag the kinematics as new for the core state, such that the routine below will actually compute the matrix element and not just look it up. <>= procedure :: reset_core_kinematics => process_instance_reset_core_kinematics <>= module subroutine process_instance_reset_core_kinematics (instance) class(process_instance_t), intent(inout) :: instance end subroutine process_instance_reset_core_kinematics <>= module subroutine process_instance_reset_core_kinematics (instance) class(process_instance_t), intent(inout) :: instance integer :: i if (instance%evaluation_status >= STAT_PASSED_CUTS) then do i = 1, size (instance%term) associate (term => instance%term(i)) if (term%active .and. term%passed) then if (allocated (term%core_state)) & call term%core_state%reset_new_kinematics () end if end associate end do end if end subroutine process_instance_reset_core_kinematics @ %def process_instance_reset_core_kinematics @ Sixth step of process evaluation: evaluate the matrix elements, and compute the trace (summed over quantum numbers) for all terms. Finally, sum up the terms, iterating over all active process components. <>= procedure :: evaluate_trace => process_instance_evaluate_trace <>= module subroutine process_instance_evaluate_trace (instance, recover) class(process_instance_t), intent(inout) :: instance logical, intent(in), optional :: recover end subroutine process_instance_evaluate_trace <>= module subroutine process_instance_evaluate_trace (instance, recover) class(process_instance_t), intent(inout) :: instance logical, intent(in), optional :: recover class(prc_core_t), pointer :: core => null () - integer :: i, i_real_fin, i_core + integer :: i, i_real_fin, i_core, i_qn, i_flv real(default) :: alpha_s, alpha_qed class(prc_core_t), pointer :: core_sub => null () class(model_data_t), pointer :: model => null () logical :: has_pdfs if (debug_on) call msg_debug2 (D_PROCESS_INTEGRATION, "process_instance_evaluate_trace") has_pdfs = instance%process%pcm_contains_pdfs () instance%sqme = zero call instance%reset_matrix_elements () if (instance%evaluation_status >= STAT_PASSED_CUTS) then do i = 1, size (instance%term) associate (term => instance%term(i), kin => instance%kin(i)) if (term%active .and. term%passed) then core => instance%process%get_core_term (i) select type (pcm => instance%process%get_pcm_ptr ()) class is (pcm_nlo_t) i_core = pcm%get_i_core (pcm%i_sub) core_sub => instance%process%get_core_ptr (i_core) end select call term%evaluate_interaction (core, kin) call term%evaluate_trace (kin) i_real_fin = instance%process%get_associated_real_fin (1) if (instance%process%uses_real_partition ()) & call term%apply_real_partition (kin) if (term%config%i_component /= i_real_fin) then + if (term%nlo_type == BORN) then + do i_flv = 1, term%connected%trace%get_qn_index_n_flv () + i_qn = term%connected%trace%get_qn_index (i_flv, i_sub = 0) + if (.not. term%passed_array(i_flv)) then + call term%connected%trace%set_matrix_element & + (i_qn, cmplx (zero, zero, default)) + end if + end do + end if if ((term%nlo_type == NLO_REAL .and. kin%emitter < 0) & .or. term%nlo_type == NLO_MISMATCH & .or. term%nlo_type == NLO_DGLAP) & call term%set_born_sqmes (core) if (term%is_subtraction () .or. & term%nlo_type == NLO_DGLAP) & call term%set_sf_factors (kin, has_pdfs) if (term%nlo_type > BORN) then if (.not. (term%nlo_type == NLO_REAL .and. & kin%emitter >= 0)) then select type (pcm => term%pcm) type is (pcm_nlo_t) if (char (pcm%settings%nlo_correction_type) == "QCD" .or. & char (pcm%settings%nlo_correction_type) == "Full") & call term%evaluate_color_correlations (core_sub) if (char (pcm%settings%nlo_correction_type) == "EW" .or. & char (pcm%settings%nlo_correction_type) == "Full") then call term%evaluate_charge_correlations (core_sub) select type (pcm => term%pcm) type is (pcm_nlo_t) associate (reg_data => pcm%region_data) if (reg_data%alphas_power > 0) & call term%evaluate_color_correlations (core_sub) end associate end select end if end select end if if (term%is_subtraction ()) then call term%evaluate_spin_correlations (core_sub) end if end if alpha_s = core%get_alpha_s (term%core_state) alpha_qed = core%get_alpha_qed (term%core_state) if (term%nlo_type > BORN) then select type (pcm => term%pcm) type is (pcm_nlo_t) if (alpha_qed == -1 .and. (& char (pcm%settings%nlo_correction_type) == "EW" .or. & char (pcm%settings%nlo_correction_type) == "Full")) then call msg_bug("Attempting to compute EW corrections with alpha_qed = -1") end if end select end if if (present (recover)) then if (recover) return end if select case (term%nlo_type) case (NLO_REAL) call term%apply_fks (kin, alpha_s, alpha_qed) case (NLO_VIRTUAL) call term%evaluate_sqme_virt (alpha_s, alpha_qed) case (NLO_MISMATCH) call term%evaluate_sqme_mismatch (alpha_s) case (NLO_DGLAP) call term%evaluate_sqme_dglap (alpha_s, alpha_qed) end select end if end if core_sub => null () instance%sqme = instance%sqme + real (sum (& term%connected%trace%get_matrix_element () * & term%weight)) end associate end do core => null () if (instance%pcm_work%is_valid ()) then instance%evaluation_status = STAT_EVALUATED_TRACE else instance%evaluation_status = STAT_FAILED_KINEMATICS end if else !!! Failed kinematics or failed cuts: set sqme to zero instance%sqme = zero end if end subroutine process_instance_evaluate_trace @ %def process_instance_evaluate_trace <>= procedure :: set_born_sqmes => term_instance_set_born_sqmes <>= module subroutine term_instance_set_born_sqmes (term, core) class(term_instance_t), intent(inout) :: term class(prc_core_t), intent(in) :: core end subroutine term_instance_set_born_sqmes <>= module subroutine term_instance_set_born_sqmes (term, core) class(term_instance_t), intent(inout) :: term class(prc_core_t), intent(in) :: core integer :: i_flv, ii_flv real(default) :: sqme select type (pcm_work => term%pcm_work) type is (pcm_nlo_workspace_t) do i_flv = 1, term%connected%trace%get_qn_index_n_flv () ii_flv = term%connected%trace%get_qn_index (i_flv, i_sub = 0) - sqme = real (term%connected%trace%get_matrix_element (ii_flv)) + if (term%passed_array (i_flv) .or. .not. term%passed) then + sqme = real (term%connected%trace%get_matrix_element (ii_flv)) + else + sqme = zero + end if select case (term%nlo_type) case (NLO_REAL) pcm_work%real_sub%sqme_born(i_flv) = sqme case (NLO_MISMATCH) pcm_work%soft_mismatch%sqme_born(i_flv) = sqme case (NLO_DGLAP) pcm_work%dglap_remnant%sqme_born(i_flv) = sqme end select end do end select end subroutine term_instance_set_born_sqmes @ %def term_instance_set_born_sqmes @ Calculates and then saves the ratio of the value of the (rescaled) real structure function chain of each ISR alpha region over the value of the corresponding underlying born flavor structure. In the case of emitter 0 we also need the rescaled ratio for emitter 1 and 2 in that region for the (soft-)collinear limits. If the emitter is 1 or 2 in some cases, e. g. for EW corrections where a photon in the proton is required, there can be the possibility of soft radiation off the initial state. For that purpose the unrescaled ratio is needed and as a default we always save these numbers in [[sf_factors(:,0)]]. Although this procedure is implying functionality for general structure functions, it should be reviewed for anything else besides PDFs, as there might be complications in the details. The general idea of getting the ratio in this way should hold up in these cases as well, however. <>= procedure :: set_sf_factors => term_instance_set_sf_factors <>= module subroutine term_instance_set_sf_factors (term, kin, has_pdfs) class(term_instance_t), intent(inout) :: term type(kinematics_t), intent(inout) :: kin logical, intent(in) :: has_pdfs end subroutine term_instance_set_sf_factors <>= module subroutine term_instance_set_sf_factors (term, kin, has_pdfs) class(term_instance_t), intent(inout) :: term type(kinematics_t), intent(inout) :: kin logical, intent(in) :: has_pdfs type(interaction_t), pointer :: sf_chain_int real(default) :: factor_born, factor_real integer :: n_in, alr, em integer :: i_born, i_real select type (pcm_work => term%pcm_work) type is (pcm_nlo_workspace_t) if (.not. has_pdfs) then pcm_work%real_sub%sf_factors = one return end if select type (pcm => term%pcm) type is (pcm_nlo_t) sf_chain_int => kin%sf_chain%get_out_int_ptr () associate (reg_data => pcm%region_data) n_in = reg_data%get_n_in () do alr = 1, reg_data%n_regions em = reg_data%regions(alr)%emitter if (em <= n_in) then i_born = reg_data%regions(alr)%uborn_index i_real = reg_data%regions(alr)%real_index factor_born = sf_chain_int%get_matrix_element & (sf_chain_int%get_sf_qn_index_born (i_born, i_sub = 0)) factor_real = sf_chain_int%get_matrix_element & (sf_chain_int%get_sf_qn_index_real (i_real, i_sub = em)) call set_factor (pcm_work, alr, em, factor_born, factor_real) if (em == 0) then do em = 1, 2 factor_real = sf_chain_int%get_matrix_element & (sf_chain_int%get_sf_qn_index_real (i_real, i_sub = em)) call set_factor (pcm_work, alr, em, factor_born, factor_real) end do else factor_real = sf_chain_int%get_matrix_element & (sf_chain_int%get_sf_qn_index_real (i_real, i_sub = 0)) call set_factor (pcm_work, alr, 0, factor_born, factor_real) end if end if end do end associate end select end select contains subroutine set_factor (pcm_work, alr, em, factor_born, factor_real) type(pcm_nlo_workspace_t), intent(inout), target :: pcm_work integer, intent(in) :: alr, em real(default), intent(in) :: factor_born, factor_real real(default) :: factor if (any (vanishes ([factor_real, factor_born], tiny(1._default), tiny(1._default)))) then factor = zero else factor = factor_real / factor_born end if select case (term%nlo_type) case (NLO_REAL) pcm_work%real_sub%sf_factors(alr, em) = factor case (NLO_DGLAP) pcm_work%dglap_remnant%sf_factors(alr, em) = factor end select end subroutine end subroutine term_instance_set_sf_factors @ %def term_instance_set_sf_factors @ <>= procedure :: apply_real_partition => process_instance_apply_real_partition <>= module subroutine process_instance_apply_real_partition (instance) class(process_instance_t), intent(inout) :: instance end subroutine process_instance_apply_real_partition <>= module subroutine process_instance_apply_real_partition (instance) class(process_instance_t), intent(inout) :: instance integer :: i_component, i_term integer, dimension(:), allocatable :: i_terms associate (process => instance%process) i_component = process%get_first_real_component () if (process%component_is_selected (i_component) .and. & process%get_component_nlo_type (i_component) == NLO_REAL) then allocate (i_terms & (size (process%get_component_i_terms (i_component)))) i_terms = process%get_component_i_terms (i_component) do i_term = 1, size (i_terms) call instance%term(i_terms(i_term))%apply_real_partition ( & instance%kin(i_terms(i_term))) end do end if if (allocated (i_terms)) deallocate (i_terms) end associate end subroutine process_instance_apply_real_partition @ %def process_instance_apply_real_partition @ <>= procedure :: set_i_mci_to_real_component => & process_instance_set_i_mci_to_real_component <>= module subroutine process_instance_set_i_mci_to_real_component (instance) class(process_instance_t), intent(inout) :: instance end subroutine process_instance_set_i_mci_to_real_component <>= module subroutine process_instance_set_i_mci_to_real_component (instance) class(process_instance_t), intent(inout) :: instance integer :: i_mci, i_component type(process_component_t), pointer :: component => null () select type (pcm_work => instance%pcm_work) type is (pcm_nlo_workspace_t) if (allocated (pcm_work%i_mci_to_real_component)) then call msg_warning & ("i_mci_to_real_component already allocated - replace it") deallocate (pcm_work%i_mci_to_real_component) end if allocate (pcm_work%i_mci_to_real_component (size (instance%mci_work))) do i_mci = 1, size (instance%mci_work) do i_component = 1, instance%process%get_n_components () component => instance%process%get_component_ptr (i_component) if (component%i_mci /= i_mci) cycle select case (component%component_type) case (COMP_MASTER, COMP_REAL) pcm_work%i_mci_to_real_component (i_mci) = & component%config%get_associated_real () case (COMP_REAL_FIN) pcm_work%i_mci_to_real_component (i_mci) = & component%config%get_associated_real_fin () case (COMP_REAL_SING) pcm_work%i_mci_to_real_component (i_mci) = & component%config%get_associated_real_sing () end select end do end do component => null () end select end subroutine process_instance_set_i_mci_to_real_component @ %def process_instance_set_i_mci_to_real_component @ Final step of process evaluation: evaluate the matrix elements, and compute the trace (summed over quantum numbers) for all terms. Finally, sum up the terms, iterating over all active process components. If [[weight]] is provided, we already know the kinematical event weight (the MCI weight which depends on the kinematics sampling algorithm, but not on the matrix element), so we do not need to take it from the MCI record. <>= procedure :: evaluate_event_data => process_instance_evaluate_event_data <>= module subroutine process_instance_evaluate_event_data (instance, weight) class(process_instance_t), intent(inout) :: instance real(default), intent(in), optional :: weight end subroutine process_instance_evaluate_event_data <>= module subroutine process_instance_evaluate_event_data (instance, weight) class(process_instance_t), intent(inout) :: instance real(default), intent(in), optional :: weight integer :: i if (instance%evaluation_status >= STAT_EVALUATED_TRACE) then do i = 1, size (instance%term) associate (term => instance%term(i)) if (term%active) then call term%evaluate_event_data () end if end associate end do if (present (weight)) then instance%weight = weight else instance%weight = & instance%mci_work(instance%i_mci)%mci%get_event_weight () instance%excess = & instance%mci_work(instance%i_mci)%mci%get_event_excess () end if instance%n_dropped = & instance%mci_work(instance%i_mci)%mci%get_n_event_dropped () instance%evaluation_status = STAT_EVENT_COMPLETE else !!! failed kinematics etc.: set weight to zero instance%weight = zero !!! Maybe we want to process and keep the event nevertheless if (instance%keep_failed_events ()) then do i = 1, size (instance%term) associate (term => instance%term(i)) if (term%active) then call term%evaluate_event_data () end if end associate end do ! do i = 1, size (instance%term) ! instance%term(i)%fac_scale = zero ! end do instance%evaluation_status = STAT_EVENT_COMPLETE end if end if end subroutine process_instance_evaluate_event_data @ %def process_instance_evaluate_event_data @ Computes the real-emission matrix element for externally supplied momenta for the term instance with index [[i_term]] and a phase space point set with index [[i_phs]]. In addition, for the real emission, each term instance corresponds to one emitter. There is the possibility to supply an external $\alpha_s$ as well as an external scale to override the scale set in the Sindarin, e.g. for POWHEG. <>= procedure :: compute_sqme_rad => process_instance_compute_sqme_rad <>= module subroutine process_instance_compute_sqme_rad (instance, & i_term, i_phs, is_subtraction, alpha_s_external, scale_forced) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_term, i_phs logical, intent(in) :: is_subtraction real(default), intent(in), optional :: alpha_s_external real(default), intent(in), allocatable, optional :: scale_forced end subroutine process_instance_compute_sqme_rad <>= module subroutine process_instance_compute_sqme_rad (instance, & i_term, i_phs, is_subtraction, alpha_s_external, scale_forced) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_term, i_phs logical, intent(in) :: is_subtraction real(default), intent(in), optional :: alpha_s_external real(default), intent(in), allocatable, optional :: scale_forced class(prc_core_t), pointer :: core integer :: i_real_fin logical :: has_pdfs has_pdfs = instance%process%pcm_contains_pdfs () if (debug_on) call msg_debug2 (D_PROCESS_INTEGRATION, "process_instance_compute_sqme_rad") select type (pcm_work => instance%pcm_work) type is (pcm_nlo_workspace_t) associate (term => instance%term(i_term), kin => instance%kin(i_term)) core => instance%process%get_core_term (i_term) if (is_subtraction) then call pcm_work%set_subtraction_event () else call pcm_work%set_radiation_event () end if call term%int_hard%set_momenta (pcm_work%get_momenta & (term%pcm, i_phs = i_phs, born_phsp = is_subtraction)) if (allocated (term%core_state)) & call term%core_state%reset_new_kinematics () if (present (alpha_s_external)) then call term%set_alpha_qcd_forced (alpha_s_external) end if call term%compute_eff_kinematics () - call term%evaluate_expressions (scale_forced) + call term%evaluate_expressions & + (instance%process%get_beam_config (), scale_forced) call term%evaluate_interaction (core, kin) call term%evaluate_trace (kin) if (term%is_subtraction ()) then call term%set_sf_factors (kin, has_pdfs) select type (pcm => instance%pcm) type is (pcm_nlo_t) if (char (pcm%settings%nlo_correction_type) == "QCD" .or. & char (pcm%settings%nlo_correction_type) == "Full") & call term%evaluate_color_correlations (core) if (char (pcm%settings%nlo_correction_type) == "EW" .or. & char (pcm%settings%nlo_correction_type) == "Full") & call term%evaluate_charge_correlations (core) end select call term%evaluate_spin_correlations (core) end if i_real_fin = instance%process%get_associated_real_fin (1) if (term%config%i_component /= i_real_fin) & call term%apply_fks (kin, core%get_alpha_s (term%core_state), & core%get_alpha_qed (term%core_state)) if (instance%process%uses_real_partition ()) & call instance%apply_real_partition () end associate end select core => null () end subroutine process_instance_compute_sqme_rad @ %def process_instance_compute_sqme_rad @ For unweighted event generation, we should reset the reported event weight to unity (signed) or zero. The latter case is appropriate for an event which failed for whatever reason. <>= procedure :: normalize_weight => process_instance_normalize_weight <>= module subroutine process_instance_normalize_weight (instance) class(process_instance_t), intent(inout) :: instance end subroutine process_instance_normalize_weight <>= module subroutine process_instance_normalize_weight (instance) class(process_instance_t), intent(inout) :: instance if (.not. vanishes (instance%weight)) then instance%weight = sign (1._default, instance%weight) end if end subroutine process_instance_normalize_weight @ %def process_instance_normalize_weight @ This is a convenience routine that performs the computations of the steps 1 to 5 in a single step. The arguments are the input for [[set_mcpar]]. After this, the evaluation status should be either [[STAT_FAILED_KINEMATICS]], [[STAT_FAILED_CUTS]] or [[STAT_EVALUATED_TRACE]]. Before calling this, we should call [[choose_mci]]. <>= procedure :: evaluate_sqme => process_instance_evaluate_sqme <>= module subroutine process_instance_evaluate_sqme (instance, channel, x) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: channel real(default), dimension(:), intent(in) :: x end subroutine process_instance_evaluate_sqme <>= module subroutine process_instance_evaluate_sqme (instance, channel, x) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: channel real(default), dimension(:), intent(in) :: x call instance%reset () call instance%set_mcpar (x) call instance%select_channel (channel) call instance%compute_seed_kinematics () call instance%compute_hard_kinematics () call instance%compute_eff_kinematics () call instance%evaluate_expressions () call instance%compute_other_channels () call instance%evaluate_trace () end subroutine process_instance_evaluate_sqme @ %def process_instance_evaluate_sqme @ This is the inverse. Assuming that the final trace evaluator contains a valid momentum configuration, recover kinematics and recalculate the matrix elements and their trace. To be precise, we first recover kinematics for the given term and associated component, then recalculate from that all other terms and active components. The [[channel]] is not really required to obtain the matrix element, but it allows us to reconstruct the exact MC parameter set that corresponds to the given phase space point. Before calling this, we should call [[choose_mci]]. <>= procedure :: recover => process_instance_recover <>= module subroutine process_instance_recover & (instance, channel, i_term, update_sqme, recover_phs, scale_forced) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: channel integer, intent(in) :: i_term logical, intent(in) :: update_sqme logical, intent(in) :: recover_phs real(default), intent(in), allocatable, optional :: scale_forced end subroutine process_instance_recover <>= module subroutine process_instance_recover & (instance, channel, i_term, update_sqme, recover_phs, scale_forced) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: channel integer, intent(in) :: i_term logical, intent(in) :: update_sqme logical, intent(in) :: recover_phs real(default), intent(in), allocatable, optional :: scale_forced logical :: skip_phs, recover call instance%activate () instance%evaluation_status = STAT_EFF_KINEMATICS call instance%recover_hard_kinematics (i_term) call instance%recover_seed_kinematics (i_term) call instance%select_channel (channel) recover = instance%pcm_work%is_nlo () if (recover_phs) then call instance%recover_mcpar (i_term) call instance%recover_beam_momenta (i_term) call instance%compute_seed_kinematics & (recover = recover, skip_term = i_term) call instance%compute_hard_kinematics & (recover = recover, skip_term = i_term) call instance%compute_eff_kinematics (i_term) call instance%compute_other_channels (i_term) else call instance%recover_sfchain (i_term) end if call instance%evaluate_expressions (scale_forced) if (update_sqme) then call instance%reset_core_kinematics () call instance%evaluate_trace (recover) end if end subroutine process_instance_recover @ %def process_instance_recover @ The [[evaluate]] method is required by the [[sampler_t]] base type of which the process instance is an extension. The requirement is that after the process instance is evaluated, the integrand, the selected channel, the $x$ array, and the $f$ Jacobian array are exposed by the [[sampler_t]] object. We allow for the additional [[hook]] to be called, if associated, for outlying object to access information from the current state of the [[sampler]]. <>= procedure :: evaluate => process_instance_evaluate <>= module subroutine process_instance_evaluate (sampler, c, x_in, val, x, f) class(process_instance_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 process_instance_evaluate <>= module subroutine process_instance_evaluate (sampler, c, x_in, val, x, f) class(process_instance_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%evaluate_sqme (c, x_in) if (sampler%is_valid ()) then call sampler%fetch (val, x, f) end if call sampler%record_call () call sampler%evaluate_after_hook () end subroutine process_instance_evaluate @ %def process_instance_evaluate @ The phase-space point is valid if the event has valid kinematics and has passed the cuts. <>= procedure :: is_valid => process_instance_is_valid <>= module function process_instance_is_valid (sampler) result (valid) class(process_instance_t), intent(in) :: sampler logical :: valid end function process_instance_is_valid <>= module function process_instance_is_valid (sampler) result (valid) class(process_instance_t), intent(in) :: sampler logical :: valid valid = sampler%evaluation_status >= STAT_PASSED_CUTS end function process_instance_is_valid @ %def process_instance_is_valid @ Add a [[process_instance_hook]] object.. <>= procedure :: append_after_hook => process_instance_append_after_hook <>= module subroutine process_instance_append_after_hook (sampler, new_hook) class(process_instance_t), intent(inout), target :: sampler class(process_instance_hook_t), intent(inout), target :: new_hook end subroutine process_instance_append_after_hook <>= module subroutine process_instance_append_after_hook (sampler, new_hook) class(process_instance_t), intent(inout), target :: sampler class(process_instance_hook_t), intent(inout), target :: new_hook class(process_instance_hook_t), pointer :: last if (associated (new_hook%next)) then call msg_bug ("process_instance_append_after_hook: " // & "reuse of SAME hook object is forbidden.") end if if (associated (sampler%hook)) then last => sampler%hook do while (associated (last%next)) last => last%next end do last%next => new_hook else sampler%hook => new_hook end if end subroutine process_instance_append_after_hook @ %def process_instance_append_after_evaluate_hook @ Evaluate the after hook as first in, last out. <>= procedure :: evaluate_after_hook => process_instance_evaluate_after_hook <>= module subroutine process_instance_evaluate_after_hook (sampler) class(process_instance_t), intent(in) :: sampler end subroutine process_instance_evaluate_after_hook <>= module subroutine process_instance_evaluate_after_hook (sampler) class(process_instance_t), intent(in) :: sampler class(process_instance_hook_t), pointer :: current current => sampler%hook do while (associated(current)) call current%evaluate (sampler) current => current%next end do end subroutine process_instance_evaluate_after_hook @ %def process_instance_evaluate_after_hook @ The [[rebuild]] method should rebuild the kinematics section out of the [[x_in]] parameter set. The integrand value [[val]] should not be computed, but is provided as input. <>= procedure :: rebuild => process_instance_rebuild <>= module subroutine process_instance_rebuild (sampler, c, x_in, val, x, f) class(process_instance_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 process_instance_rebuild <>= module subroutine process_instance_rebuild (sampler, c, x_in, val, x, f) class(process_instance_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 msg_bug ("process_instance_rebuild not implemented yet") x = 0 f = 0 end subroutine process_instance_rebuild @ %def process_instance_rebuild @ This is another method required by the [[sampler_t]] base type: fetch the data that are relevant for the MCI record. <>= procedure :: fetch => process_instance_fetch <>= module subroutine process_instance_fetch (sampler, val, x, f) class(process_instance_t), intent(in) :: sampler real(default), intent(out) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f end subroutine process_instance_fetch <>= module subroutine process_instance_fetch (sampler, val, x, f) class(process_instance_t), intent(in) :: sampler real(default), intent(out) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f integer, dimension(:), allocatable :: i_terms integer :: i, i_term_base, cc integer :: n_channel val = 0 associate (process => sampler%process) FIND_COMPONENT: do i = 1, process%get_n_components () if (sampler%process%component_is_selected (i)) then allocate (i_terms (size (process%get_component_i_terms (i)))) i_terms = process%get_component_i_terms (i) i_term_base = i_terms(1) associate (k => sampler%kin(i_term_base)) n_channel = k%n_channel do cc = 1, n_channel call k%get_mcpar (cc, x(:,cc)) end do f = k%f val = sampler%sqme * k%phs_factor end associate if (allocated (i_terms)) deallocate (i_terms) exit FIND_COMPONENT end if end do FIND_COMPONENT end associate end subroutine process_instance_fetch @ %def process_instance_fetch @ Initialize and finalize event generation for the specified MCI entry. <>= procedure :: init_simulation => process_instance_init_simulation procedure :: final_simulation => process_instance_final_simulation <>= module subroutine process_instance_init_simulation (instance, i_mci, & safety_factor, keep_failed_events) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_mci real(default), intent(in), optional :: safety_factor logical, intent(in), optional :: keep_failed_events end subroutine process_instance_init_simulation module subroutine process_instance_final_simulation (instance, i_mci) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_mci end subroutine process_instance_final_simulation <>= module subroutine process_instance_init_simulation (instance, i_mci, & safety_factor, keep_failed_events) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_mci real(default), intent(in), optional :: safety_factor logical, intent(in), optional :: keep_failed_events call instance%mci_work(i_mci)%init_simulation & (safety_factor, keep_failed_events) end subroutine process_instance_init_simulation module subroutine process_instance_final_simulation (instance, i_mci) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_mci call instance%mci_work(i_mci)%final_simulation () end subroutine process_instance_final_simulation @ %def process_instance_init_simulation @ %def process_instance_final_simulation @ \subsubsection{Accessing the process instance} Once the seed kinematics is complete, we can retrieve the MC input parameters for all channels, not just the seed channel. Note: We choose the first active component. This makes sense only if the seed kinematics is identical for all active components. <>= procedure :: get_mcpar => process_instance_get_mcpar <>= module subroutine process_instance_get_mcpar (instance, channel, x) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: channel real(default), dimension(:), intent(out) :: x end subroutine process_instance_get_mcpar <>= module subroutine process_instance_get_mcpar (instance, channel, x) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: channel real(default), dimension(:), intent(out) :: x integer :: i if (instance%evaluation_status >= STAT_SEED_KINEMATICS) then do i = 1, size (instance%term) if (instance%term(i)%active) then call instance%kin(i)%get_mcpar (channel, x) return end if end do call msg_bug ("Process instance: get_mcpar: no active channels") else call msg_bug ("Process instance: get_mcpar: no seed kinematics") end if end subroutine process_instance_get_mcpar @ %def process_instance_get_mcpar @ Return true if the [[sqme]] value is known. This also implies that the event is kinematically valid and has passed all cuts. <>= procedure :: has_evaluated_trace => process_instance_has_evaluated_trace <>= module function process_instance_has_evaluated_trace & (instance) result (flag) class(process_instance_t), intent(in) :: instance logical :: flag end function process_instance_has_evaluated_trace <>= module function process_instance_has_evaluated_trace (instance) result (flag) class(process_instance_t), intent(in) :: instance logical :: flag flag = instance%evaluation_status >= STAT_EVALUATED_TRACE end function process_instance_has_evaluated_trace @ %def process_instance_has_evaluated_trace @ Return true if the event is complete. In particular, the event must be kinematically valid, passed all cuts, and the event data have been computed. <>= procedure :: is_complete_event => process_instance_is_complete_event <>= module function process_instance_is_complete_event (instance) result (flag) class(process_instance_t), intent(in) :: instance logical :: flag end function process_instance_is_complete_event <>= module function process_instance_is_complete_event (instance) result (flag) class(process_instance_t), intent(in) :: instance logical :: flag flag = instance%evaluation_status >= STAT_EVENT_COMPLETE end function process_instance_is_complete_event @ %def process_instance_is_complete_event @ Select the term for the process instance that will provide the basic event record (used in [[evt_trivial_make_particle_set]]). It might be necessary to write out additional events corresponding to other terms (done in [[evt_nlo]]). <>= procedure :: select_i_term => process_instance_select_i_term <>= module function process_instance_select_i_term (instance) result (i_term) integer :: i_term class(process_instance_t), intent(in) :: instance end function process_instance_select_i_term <>= module function process_instance_select_i_term (instance) result (i_term) integer :: i_term class(process_instance_t), intent(in) :: instance integer :: i_mci i_mci = instance%i_mci i_term = instance%process%select_i_term (i_mci) end function process_instance_select_i_term @ %def process_instance_select_i_term @ Return pointer to the master beam interaction. <>= procedure :: get_beam_int_ptr => process_instance_get_beam_int_ptr <>= module function process_instance_get_beam_int_ptr (instance) result (ptr) class(process_instance_t), intent(in), target :: instance type(interaction_t), pointer :: ptr end function process_instance_get_beam_int_ptr <>= module function process_instance_get_beam_int_ptr (instance) result (ptr) class(process_instance_t), intent(in), target :: instance type(interaction_t), pointer :: ptr ptr => instance%sf_chain%get_beam_int_ptr () end function process_instance_get_beam_int_ptr @ %def process_instance_get_beam_int_ptr @ Return pointers to the matrix and flows interactions, given a term index. <>= procedure :: get_trace_int_ptr => process_instance_get_trace_int_ptr procedure :: get_matrix_int_ptr => process_instance_get_matrix_int_ptr procedure :: get_flows_int_ptr => process_instance_get_flows_int_ptr <>= module function process_instance_get_trace_int_ptr & (instance, i_term) result (ptr) class(process_instance_t), intent(in), target :: instance integer, intent(in) :: i_term type(interaction_t), pointer :: ptr end function process_instance_get_trace_int_ptr module function process_instance_get_matrix_int_ptr & (instance, i_term) result (ptr) class(process_instance_t), intent(in), target :: instance integer, intent(in) :: i_term type(interaction_t), pointer :: ptr end function process_instance_get_matrix_int_ptr module function process_instance_get_flows_int_ptr & (instance, i_term) result (ptr) class(process_instance_t), intent(in), target :: instance integer, intent(in) :: i_term type(interaction_t), pointer :: ptr end function process_instance_get_flows_int_ptr <>= module function process_instance_get_trace_int_ptr & (instance, i_term) result (ptr) class(process_instance_t), intent(in), target :: instance integer, intent(in) :: i_term type(interaction_t), pointer :: ptr ptr => instance%term(i_term)%connected%get_trace_int_ptr () end function process_instance_get_trace_int_ptr module function process_instance_get_matrix_int_ptr & (instance, i_term) result (ptr) class(process_instance_t), intent(in), target :: instance integer, intent(in) :: i_term type(interaction_t), pointer :: ptr ptr => instance%term(i_term)%connected%get_matrix_int_ptr () end function process_instance_get_matrix_int_ptr module function process_instance_get_flows_int_ptr & (instance, i_term) result (ptr) class(process_instance_t), intent(in), target :: instance integer, intent(in) :: i_term type(interaction_t), pointer :: ptr ptr => instance%term(i_term)%connected%get_flows_int_ptr () end function process_instance_get_flows_int_ptr @ %def process_instance_get_trace_int_ptr @ %def process_instance_get_matrix_int_ptr @ %def process_instance_get_flows_int_ptr @ Return the complete account of flavor combinations in the underlying interaction object, including beams, radiation, and hard interaction. <>= procedure :: get_state_flv => process_instance_get_state_flv <>= module function process_instance_get_state_flv & (instance, i_term) result (state_flv) class(process_instance_t), intent(in) :: instance integer, intent(in) :: i_term type(state_flv_content_t) :: state_flv end function process_instance_get_state_flv <>= module function process_instance_get_state_flv & (instance, i_term) result (state_flv) class(process_instance_t), intent(in) :: instance integer, intent(in) :: i_term type(state_flv_content_t) :: state_flv state_flv = instance%term(i_term)%connected%get_state_flv () end function process_instance_get_state_flv @ %def process_instance_get_state_flv @ Return pointers to the parton states of a selected term. <>= procedure :: get_isolated_state_ptr => & process_instance_get_isolated_state_ptr procedure :: get_connected_state_ptr => & process_instance_get_connected_state_ptr <>= module function process_instance_get_isolated_state_ptr & (instance, i_term) result (ptr) class(process_instance_t), intent(in), target :: instance integer, intent(in) :: i_term type(isolated_state_t), pointer :: ptr end function process_instance_get_isolated_state_ptr module function process_instance_get_connected_state_ptr & (instance, i_term) result (ptr) class(process_instance_t), intent(in), target :: instance integer, intent(in) :: i_term type(connected_state_t), pointer :: ptr end function process_instance_get_connected_state_ptr <>= module function process_instance_get_isolated_state_ptr & (instance, i_term) result (ptr) class(process_instance_t), intent(in), target :: instance integer, intent(in) :: i_term type(isolated_state_t), pointer :: ptr ptr => instance%term(i_term)%isolated end function process_instance_get_isolated_state_ptr module function process_instance_get_connected_state_ptr & (instance, i_term) result (ptr) class(process_instance_t), intent(in), target :: instance integer, intent(in) :: i_term type(connected_state_t), pointer :: ptr ptr => instance%term(i_term)%connected end function process_instance_get_connected_state_ptr @ %def process_instance_get_isolated_state_ptr @ %def process_instance_get_connected_state_ptr @ Return the indices of the beam particles and incoming partons within the currently active state matrix, respectively. <>= procedure :: get_beam_index => process_instance_get_beam_index procedure :: get_in_index => process_instance_get_in_index <>= module subroutine process_instance_get_beam_index (instance, i_term, i_beam) class(process_instance_t), intent(in) :: instance integer, intent(in) :: i_term integer, dimension(:), intent(out) :: i_beam end subroutine process_instance_get_beam_index module subroutine process_instance_get_in_index (instance, i_term, i_in) class(process_instance_t), intent(in) :: instance integer, intent(in) :: i_term integer, dimension(:), intent(out) :: i_in end subroutine process_instance_get_in_index <>= module subroutine process_instance_get_beam_index (instance, i_term, i_beam) class(process_instance_t), intent(in) :: instance integer, intent(in) :: i_term integer, dimension(:), intent(out) :: i_beam call instance%term(i_term)%connected%get_beam_index (i_beam) end subroutine process_instance_get_beam_index module subroutine process_instance_get_in_index (instance, i_term, i_in) class(process_instance_t), intent(in) :: instance integer, intent(in) :: i_term integer, dimension(:), intent(out) :: i_in call instance%term(i_term)%connected%get_in_index (i_in) end subroutine process_instance_get_in_index @ %def process_instance_get_beam_index @ %def process_instance_get_in_index @ Return squared matrix element and event weight, and event weight excess where applicable. [[n_dropped]] is a number that can be nonzero when a weighted event has been generated, dropping events with zero weight (failed cuts) on the fly. If [[i_term]] is provided for [[get_sqme]], we take the first matrix element as we also set the first matrix element with [[set_only_matrix_element]] when computing the real, the dglap or the virtual contribution. <>= procedure :: get_sqme => process_instance_get_sqme procedure :: get_weight => process_instance_get_weight procedure :: get_excess => process_instance_get_excess procedure :: get_n_dropped => process_instance_get_n_dropped <>= module function process_instance_get_sqme (instance, i_term) result (sqme) real(default) :: sqme class(process_instance_t), intent(in) :: instance integer, intent(in), optional :: i_term end function process_instance_get_sqme module function process_instance_get_weight (instance) result (weight) real(default) :: weight class(process_instance_t), intent(in) :: instance end function process_instance_get_weight module function process_instance_get_excess (instance) result (excess) real(default) :: excess class(process_instance_t), intent(in) :: instance end function process_instance_get_excess module function process_instance_get_n_dropped (instance) result (n_dropped) integer :: n_dropped class(process_instance_t), intent(in) :: instance end function process_instance_get_n_dropped <>= module function process_instance_get_sqme (instance, i_term) result (sqme) real(default) :: sqme class(process_instance_t), intent(in) :: instance integer, intent(in), optional :: i_term if (instance%evaluation_status >= STAT_EVALUATED_TRACE) then if (present (i_term)) then sqme = instance%term(i_term)%connected%trace%get_matrix_element (1) else sqme = instance%sqme end if else sqme = 0 end if end function process_instance_get_sqme module function process_instance_get_weight (instance) result (weight) real(default) :: weight class(process_instance_t), intent(in) :: instance if (instance%evaluation_status >= STAT_EVENT_COMPLETE) then weight = instance%weight else weight = 0 end if end function process_instance_get_weight module function process_instance_get_excess (instance) result (excess) real(default) :: excess class(process_instance_t), intent(in) :: instance if (instance%evaluation_status >= STAT_EVENT_COMPLETE) then excess = instance%excess else excess = 0 end if end function process_instance_get_excess module function process_instance_get_n_dropped (instance) result (n_dropped) integer :: n_dropped class(process_instance_t), intent(in) :: instance if (instance%evaluation_status >= STAT_EVENT_COMPLETE) then n_dropped = instance%n_dropped else n_dropped = 0 end if end function process_instance_get_n_dropped @ %def process_instance_get_sqme @ %def process_instance_get_weight @ %def process_instance_get_excess @ %def process_instance_get_n_dropped @ Return the currently selected MCI channel. <>= procedure :: get_channel => process_instance_get_channel <>= module function process_instance_get_channel (instance) result (channel) integer :: channel class(process_instance_t), intent(in) :: instance end function process_instance_get_channel <>= module function process_instance_get_channel (instance) result (channel) integer :: channel class(process_instance_t), intent(in) :: instance channel = instance%selected_channel end function process_instance_get_channel @ %def process_instance_get_channel @ <>= procedure :: set_fac_scale => process_instance_set_fac_scale <>= module subroutine process_instance_set_fac_scale (instance, fac_scale) class(process_instance_t), intent(inout) :: instance real(default), intent(in) :: fac_scale end subroutine process_instance_set_fac_scale <>= module subroutine process_instance_set_fac_scale (instance, fac_scale) class(process_instance_t), intent(inout) :: instance real(default), intent(in) :: fac_scale integer :: i_term i_term = 1 call instance%term(i_term)%set_fac_scale (fac_scale) end subroutine process_instance_set_fac_scale @ %def process_instance_set_fac_scale @ Return factorization scale and strong coupling. We have to select a term instance. <>= procedure :: get_fac_scale => process_instance_get_fac_scale procedure :: get_alpha_s => process_instance_get_alpha_s <>= module function process_instance_get_fac_scale & (instance, i_term) result (fac_scale) class(process_instance_t), intent(in) :: instance integer, intent(in) :: i_term real(default) :: fac_scale end function process_instance_get_fac_scale module function process_instance_get_alpha_s & (instance, i_term) result (alpha_s) real(default) :: alpha_s class(process_instance_t), intent(in) :: instance integer, intent(in) :: i_term end function process_instance_get_alpha_s <>= module function process_instance_get_fac_scale & (instance, i_term) result (fac_scale) class(process_instance_t), intent(in) :: instance integer, intent(in) :: i_term real(default) :: fac_scale fac_scale = instance%term(i_term)%get_fac_scale () end function process_instance_get_fac_scale module function process_instance_get_alpha_s & (instance, i_term) result (alpha_s) real(default) :: alpha_s class(process_instance_t), intent(in) :: instance integer, intent(in) :: i_term class(prc_core_t), pointer :: core => null () core => instance%process%get_core_term (i_term) alpha_s = instance%term(i_term)%get_alpha_s (core) core => null () end function process_instance_get_alpha_s @ %def process_instance_get_fac_scale @ %def process_instance_get_alpha_s @ <>= procedure :: get_qcd => process_instance_get_qcd <>= module function process_instance_get_qcd (process_instance) result (qcd) type(qcd_t) :: qcd class(process_instance_t), intent(in) :: process_instance end function process_instance_get_qcd <>= module function process_instance_get_qcd (process_instance) result (qcd) type(qcd_t) :: qcd class(process_instance_t), intent(in) :: process_instance qcd = process_instance%process%get_qcd () end function process_instance_get_qcd @ %def process_instance_get_qcd @ Counter. <>= procedure :: reset_counter => process_instance_reset_counter procedure :: record_call => process_instance_record_call procedure :: get_counter => process_instance_get_counter <>= module subroutine process_instance_reset_counter (process_instance) class(process_instance_t), intent(inout) :: process_instance end subroutine process_instance_reset_counter module subroutine process_instance_record_call (process_instance) class(process_instance_t), intent(inout) :: process_instance end subroutine process_instance_record_call pure module function process_instance_get_counter & (process_instance) result (counter) class(process_instance_t), intent(in) :: process_instance type(process_counter_t) :: counter end function process_instance_get_counter <>= module subroutine process_instance_reset_counter (process_instance) class(process_instance_t), intent(inout) :: process_instance call process_instance%mci_work(process_instance%i_mci)%reset_counter () end subroutine process_instance_reset_counter module subroutine process_instance_record_call (process_instance) class(process_instance_t), intent(inout) :: process_instance call process_instance%mci_work(process_instance%i_mci)%record_call & (process_instance%evaluation_status) end subroutine process_instance_record_call pure module function process_instance_get_counter & (process_instance) result (counter) class(process_instance_t), intent(in) :: process_instance type(process_counter_t) :: counter counter = process_instance%mci_work(process_instance%i_mci)%get_counter () end function process_instance_get_counter @ %def process_instance_reset_counter @ %def process_instance_record_call @ %def process_instance_get_counter @ Sum up the total number of calls for all MCI records. <>= procedure :: get_actual_calls_total => process_instance_get_actual_calls_total <>= pure module function process_instance_get_actual_calls_total & (process_instance) result (n) class(process_instance_t), intent(in) :: process_instance integer :: n end function process_instance_get_actual_calls_total <>= pure module function process_instance_get_actual_calls_total & (process_instance) result (n) class(process_instance_t), intent(in) :: process_instance integer :: n integer :: i type(process_counter_t) :: counter n = 0 do i = 1, size (process_instance%mci_work) counter = process_instance%mci_work(i)%get_counter () n = n + counter%total end do end function process_instance_get_actual_calls_total @ %def process_instance_get_actual_calls_total @ <>= procedure :: reset_matrix_elements => process_instance_reset_matrix_elements <>= module subroutine process_instance_reset_matrix_elements (instance) class(process_instance_t), intent(inout) :: instance end subroutine process_instance_reset_matrix_elements <>= module subroutine process_instance_reset_matrix_elements (instance) class(process_instance_t), intent(inout) :: instance integer :: i_term do i_term = 1, size (instance%term) call instance%term(i_term)%connected%trace%set_matrix_element & (cmplx (0, 0, default)) call instance%term(i_term)%connected%matrix%set_matrix_element & (cmplx (0, 0, default)) end do end subroutine process_instance_reset_matrix_elements @ %def process_instance_reset_matrix_elements @ <>= procedure :: get_test_phase_space_point & => process_instance_get_test_phase_space_point <>= module subroutine process_instance_get_test_phase_space_point (instance, & i_component, i_core, p) type(vector4_t), dimension(:), allocatable, intent(out) :: p class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_component, i_core end subroutine process_instance_get_test_phase_space_point <>= module subroutine process_instance_get_test_phase_space_point (instance, & i_component, i_core, p) type(vector4_t), dimension(:), allocatable, intent(out) :: p class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_component, i_core real(default), dimension(:), allocatable :: x logical :: success integer :: i_term instance%i_mci = i_component i_term = instance%process%get_i_term (i_core) associate (term => instance%term(i_term), kin => instance%kin(i_term)) allocate (x (instance%mci_work(i_component)%config%n_par)) x = 0.5_default call instance%set_mcpar (x, .true.) call instance%select_channel (1) call term%compute_seed_kinematics & (kin, instance%mci_work(i_component), 1, success) call kin%evaluate_radiation_kinematics & (instance%mci_work(instance%i_mci)%get_x_process ()) call term%compute_hard_kinematics (kin, success = success) allocate (p (size (term%p_hard))) p = term%int_hard%get_momenta () end associate end subroutine process_instance_get_test_phase_space_point @ %def process_instance_get_test_phase_space_point @ <>= procedure :: get_p_hard => process_instance_get_p_hard <>= pure module function process_instance_get_p_hard & (process_instance, i_term) result (p_hard) type(vector4_t), dimension(:), allocatable :: p_hard class(process_instance_t), intent(in) :: process_instance integer, intent(in) :: i_term end function process_instance_get_p_hard <>= pure module function process_instance_get_p_hard & (process_instance, i_term) result (p_hard) type(vector4_t), dimension(:), allocatable :: p_hard class(process_instance_t), intent(in) :: process_instance integer, intent(in) :: i_term allocate (p_hard (size (process_instance%term(i_term)%get_p_hard ()))) p_hard = process_instance%term(i_term)%get_p_hard () end function process_instance_get_p_hard @ %def process_instance_get_p_hard @ <>= procedure :: get_first_active_i_term => & process_instance_get_first_active_i_term <>= module function process_instance_get_first_active_i_term & (instance) result (i_term) integer :: i_term class(process_instance_t), intent(in) :: instance end function process_instance_get_first_active_i_term <>= module function process_instance_get_first_active_i_term & (instance) result (i_term) integer :: i_term class(process_instance_t), intent(in) :: instance integer :: i i_term = 0 do i = 1, size (instance%term) if (instance%term(i)%active) then i_term = i exit end if end do end function process_instance_get_first_active_i_term @ %def process_instance_get_first_active_i_term @ <>= procedure :: get_real_of_mci => process_instance_get_real_of_mci <>= module function process_instance_get_real_of_mci (instance) result (i_real) integer :: i_real class(process_instance_t), intent(in) :: instance end function process_instance_get_real_of_mci <>= module function process_instance_get_real_of_mci (instance) result (i_real) integer :: i_real class(process_instance_t), intent(in) :: instance select type (pcm_work => instance%pcm_work) type is (pcm_nlo_workspace_t) i_real = pcm_work%i_mci_to_real_component (instance%i_mci) end select end function process_instance_get_real_of_mci @ %def process_instance_get_real_of_mci @ <>= procedure :: get_connected_states => process_instance_get_connected_states <>= module function process_instance_get_connected_states & (instance, i_component) result (connected) type(connected_state_t), dimension(:), allocatable :: connected class(process_instance_t), intent(in) :: instance integer, intent(in) :: i_component end function process_instance_get_connected_states <>= module function process_instance_get_connected_states & (instance, i_component) result (connected) type(connected_state_t), dimension(:), allocatable :: connected class(process_instance_t), intent(in) :: instance integer, intent(in) :: i_component connected = instance%process%get_connected_states (i_component, & instance%term(:)%connected) end function process_instance_get_connected_states @ %def process_instance_get_connected_states @ Get the hadronic center-of-mass energy <>= procedure :: get_sqrts => process_instance_get_sqrts <>= module function process_instance_get_sqrts (instance) result (sqrts) class(process_instance_t), intent(in) :: instance real(default) :: sqrts end function process_instance_get_sqrts <>= module function process_instance_get_sqrts (instance) result (sqrts) class(process_instance_t), intent(in) :: instance real(default) :: sqrts sqrts = instance%process%get_sqrts () end function process_instance_get_sqrts @ %def process_instance_get_sqrts @ Get the polarizations <>= procedure :: get_polarization => process_instance_get_polarization <>= module function process_instance_get_polarization (instance) result (pol) class(process_instance_t), intent(in) :: instance real(default), dimension(:), allocatable :: pol end function process_instance_get_polarization <>= module function process_instance_get_polarization (instance) result (pol) class(process_instance_t), intent(in) :: instance real(default), dimension(:), allocatable :: pol pol = instance%process%get_polarization () end function process_instance_get_polarization @ %def process_instance_get_polarization @ Get the beam spectrum <>= procedure :: get_beam_file => process_instance_get_beam_file <>= module function process_instance_get_beam_file (instance) result (file) class(process_instance_t), intent(in) :: instance type(string_t) :: file end function process_instance_get_beam_file <>= module function process_instance_get_beam_file (instance) result (file) class(process_instance_t), intent(in) :: instance type(string_t) :: file file = instance%process%get_beam_file () end function process_instance_get_beam_file @ %def process_instance_get_beam_file @ Get the process name <>= procedure :: get_process_name => process_instance_get_process_name <>= module function process_instance_get_process_name (instance) result (name) class(process_instance_t), intent(in) :: instance type(string_t) :: name end function process_instance_get_process_name <>= module function process_instance_get_process_name (instance) result (name) class(process_instance_t), intent(in) :: instance type(string_t) :: name name = instance%process%get_id () end function process_instance_get_process_name @ %def process_instance_get_process_name @ \subsubsection{Particle sets} Here we provide two procedures that convert the process instance from/to a particle set. The conversion applies to the trace evaluator which has no quantum-number information, thus it involves only the momenta and the parent-child relations. We keep virtual particles. If [[n_incoming]] is provided, the status code of the first [[n_incoming]] particles will be reset to incoming. Otherwise, they would be classified as virtual. Nevertheless, it is possible to reconstruct the complete structure from a particle set. The reconstruction implies a re-evaluation of the structure function and matrix-element codes. The [[i_term]] index is needed for both input and output, to select among different active trace evaluators. In both cases, the [[instance]] object must be properly initialized. NB: The [[recover_beams]] option should be used only when the particle set originates from an external event file, and the user has asked for it. It should be switched off when reading from raw event file. <>= procedure :: get_trace => process_instance_get_trace procedure :: set_trace => process_instance_set_trace <>= module subroutine process_instance_get_trace & (instance, pset, i_term, n_incoming) class(process_instance_t), intent(in), target :: instance type(particle_set_t), intent(out) :: pset integer, intent(in) :: i_term integer, intent(in), optional :: n_incoming end subroutine process_instance_get_trace module subroutine process_instance_set_trace & (instance, pset, i_term, recover_beams, check_match, success) class(process_instance_t), intent(inout), target :: instance type(particle_set_t), intent(in) :: pset integer, intent(in) :: i_term logical, intent(in), optional :: recover_beams, check_match logical, intent(out), optional :: success end subroutine process_instance_set_trace <>= module subroutine process_instance_get_trace & (instance, pset, i_term, n_incoming) class(process_instance_t), intent(in), target :: instance type(particle_set_t), intent(out) :: pset integer, intent(in) :: i_term integer, intent(in), optional :: n_incoming type(interaction_t), pointer :: int logical :: ok int => instance%get_trace_int_ptr (i_term) call pset%init (ok, int, int, FM_IGNORE_HELICITY, & [0._default, 0._default], .false., .true., n_incoming) end subroutine process_instance_get_trace module subroutine process_instance_set_trace & (instance, pset, i_term, recover_beams, check_match, success) class(process_instance_t), intent(inout), target :: instance type(particle_set_t), intent(in) :: pset integer, intent(in) :: i_term logical, intent(in), optional :: recover_beams, check_match logical, intent(out), optional :: success type(interaction_t), pointer :: int integer :: n_in int => instance%get_trace_int_ptr (i_term) n_in = instance%process%get_n_in () call pset%fill_interaction (int, n_in, & recover_beams = recover_beams, & check_match = check_match, & state_flv = instance%get_state_flv (i_term), & success = success) end subroutine process_instance_set_trace @ %def process_instance_get_trace @ %def process_instance_set_trace @ This procedure allows us to override any QCD setting of the WHIZARD process and directly set the coupling value that comes together with a particle set. <>= procedure :: set_alpha_qcd_forced => process_instance_set_alpha_qcd_forced <>= module subroutine process_instance_set_alpha_qcd_forced & (instance, i_term, alpha_qcd) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_term real(default), intent(in) :: alpha_qcd end subroutine process_instance_set_alpha_qcd_forced <>= module subroutine process_instance_set_alpha_qcd_forced & (instance, i_term, alpha_qcd) class(process_instance_t), intent(inout) :: instance integer, intent(in) :: i_term real(default), intent(in) :: alpha_qcd call instance%term(i_term)%set_alpha_qcd_forced (alpha_qcd) end subroutine process_instance_set_alpha_qcd_forced @ %def process_instance_set_alpha_qcd_forced @ <>= procedure :: has_nlo_component => process_instance_has_nlo_component <>= module function process_instance_has_nlo_component (instance) result (nlo) class(process_instance_t), intent(in) :: instance logical :: nlo end function process_instance_has_nlo_component <>= module function process_instance_has_nlo_component (instance) result (nlo) class(process_instance_t), intent(in) :: instance logical :: nlo nlo = instance%process%is_nlo_calculation () end function process_instance_has_nlo_component @ %def process_instance_has_nlo_component @ <>= procedure :: keep_failed_events => process_instance_keep_failed_events <>= module function process_instance_keep_failed_events (instance) result (keep) logical :: keep class(process_instance_t), intent(in) :: instance end function process_instance_keep_failed_events <>= module function process_instance_keep_failed_events (instance) result (keep) logical :: keep class(process_instance_t), intent(in) :: instance keep = instance%mci_work(instance%i_mci)%keep_failed_events end function process_instance_keep_failed_events @ %def process_instance_keep_failed_events @ <>= procedure :: get_term_indices => process_instance_get_term_indices <>= module function process_instance_get_term_indices & (instance, nlo_type) result (i_term) integer, dimension(:), allocatable :: i_term class(process_instance_t), intent(in) :: instance integer :: nlo_type end function process_instance_get_term_indices <>= module function process_instance_get_term_indices & (instance, nlo_type) result (i_term) integer, dimension(:), allocatable :: i_term class(process_instance_t), intent(in) :: instance integer :: nlo_type allocate (i_term (count (instance%term%nlo_type == nlo_type))) i_term = pack (instance%term%get_i_term_global (), & instance%term%nlo_type == nlo_type) end function process_instance_get_term_indices @ %def process_instance_get_term_indices @ <>= procedure :: get_boost_to_lab => process_instance_get_boost_to_lab <>= module function process_instance_get_boost_to_lab & (instance, i_term) result (lt) type(lorentz_transformation_t) :: lt class(process_instance_t), intent(in) :: instance integer, intent(in) :: i_term end function process_instance_get_boost_to_lab <>= module function process_instance_get_boost_to_lab & (instance, i_term) result (lt) type(lorentz_transformation_t) :: lt class(process_instance_t), intent(in) :: instance integer, intent(in) :: i_term lt = instance%kin(i_term)%get_boost_to_lab () end function process_instance_get_boost_to_lab @ %def process_instance_get_boost_to_lab @ <>= procedure :: get_boost_to_cms => process_instance_get_boost_to_cms <>= module function process_instance_get_boost_to_cms & (instance, i_term) result (lt) type(lorentz_transformation_t) :: lt class(process_instance_t), intent(in) :: instance integer, intent(in) :: i_term end function process_instance_get_boost_to_cms <>= module function process_instance_get_boost_to_cms & (instance, i_term) result (lt) type(lorentz_transformation_t) :: lt class(process_instance_t), intent(in) :: instance integer, intent(in) :: i_term lt = instance%kin(i_term)%get_boost_to_cms () end function process_instance_get_boost_to_cms @ %def process_instance_get_boost_to_cms @ <>= procedure :: lab_is_cm => process_instance_lab_is_cm <>= module function process_instance_lab_is_cm & (instance, i_term) result (lab_is_cm) logical :: lab_is_cm class(process_instance_t), intent(in) :: instance integer, intent(in) :: i_term end function process_instance_lab_is_cm <>= module function process_instance_lab_is_cm & (instance, i_term) result (lab_is_cm) logical :: lab_is_cm class(process_instance_t), intent(in) :: instance integer, intent(in) :: i_term lab_is_cm = instance%kin(i_term)%phs%lab_is_cm () end function process_instance_lab_is_cm @ %def process_instance_lab_is_cm @ The [[pacify]] subroutine has the purpose of setting numbers to zero which are (by comparing with a [[tolerance]] parameter) considered equivalent with zero. We do this in some unit tests. Here, we a apply this to the phase space subobject of the process instance. <>= public :: pacify <>= interface pacify module procedure pacify_process_instance end interface pacify <>= module subroutine pacify_process_instance (instance) type(process_instance_t), intent(inout) :: instance end subroutine pacify_process_instance <>= module subroutine pacify_process_instance (instance) type(process_instance_t), intent(inout) :: instance integer :: i do i = 1, size (instance%kin) call pacify (instance%kin(i)%phs) end do end subroutine pacify_process_instance @ %def pacify @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Unit tests} Test module, followed by the corresponding implementation module. <<[[processes_ut.f90]]>>= <> module processes_ut use unit_tests use processes_uti <> <> <> contains <> end module processes_ut @ %def processes_ut @ <<[[processes_uti.f90]]>>= <> module processes_uti <> <> use format_utils, only: write_separator use constants, only: TWOPI4 use physics_defs, only: CONV use os_interface use sm_qcd use lorentz use pdg_arrays use model_data use models use var_base, only: vars_t use variables, only: var_list_t use model_testbed, only: prepare_model use particle_specifiers, only: new_prt_spec use flavors use interactions, only: reset_interaction_counter use particles use rng_base use mci_base use mci_none, only: mci_none_t use mci_midpoint use sf_mappings use sf_base use phs_base use phs_single use phs_forests, only: syntax_phs_forest_init, syntax_phs_forest_final use phs_wood, only: phs_wood_config_t use resonances, only: resonance_history_set_t use process_constants use prc_core_def, only: prc_core_def_t use prc_core use prc_test, only: prc_test_create_library use prc_template_me, only: template_me_def_t use process_libraries use prc_test_core use pdf, only: pdf_data_t use process_counter use process_config, only: process_term_t use process, only: process_t use instances, only: process_instance_t, process_instance_hook_t use rng_base_ut, only: rng_test_factory_t use sf_base_ut, only: sf_test_data_t use mci_base_ut, only: mci_test_t use phs_base_ut, only: phs_test_config_t <> <> <> <> contains <> <> end module processes_uti @ %def processes_uti @ API: driver for the unit tests below. <>= public :: processes_test <>= subroutine processes_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine processes_test @ %def processes_test \subsubsection{Write an empty process object} The most trivial test is to write an uninitialized process object. <>= call test (processes_1, "processes_1", & "write an empty process object", & u, results) <>= public :: processes_1 <>= subroutine processes_1 (u) integer, intent(in) :: u type(process_t) :: process write (u, "(A)") "* Test output: processes_1" write (u, "(A)") "* Purpose: display an empty process object" write (u, "(A)") call process%write (.false., u) write (u, "(A)") write (u, "(A)") "* Test output end: processes_1" end subroutine processes_1 @ %def processes_1 @ \subsubsection{Initialize a process object} Initialize a process and display it. <>= call test (processes_2, "processes_2", & "initialize a simple process object", & u, results) <>= public :: processes_2 <>= subroutine processes_2 (u) integer, intent(in) :: u type(process_library_t), target :: lib type(string_t) :: libname type(string_t) :: procname type(os_data_t) :: os_data type(model_t), target :: model type(process_t), allocatable :: process class(mci_t), allocatable :: mci_template class(phs_config_t), allocatable :: phs_config_template write (u, "(A)") "* Test output: processes_2" write (u, "(A)") "* Purpose: initialize a simple process object" write (u, "(A)") write (u, "(A)") "* Build and load a test library with one process" write (u, "(A)") libname = "processes2" procname = libname call os_data%init () call prc_test_create_library (libname, lib) write (u, "(A)") "* Initialize a process object" write (u, "(A)") call model%init_test () allocate (process) call process%init (procname, lib, os_data, model) call process%set_run_id (var_str ("run_2")) call process%setup_test_cores () allocate (phs_test_config_t :: phs_config_template) call process%init_components (phs_config_template) call process%setup_mci (dispatch_mci_empty) call process%write (.false., u) write (u, "(A)") write (u, "(A)") "* Cleanup" call process%final () deallocate (process) call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: processes_2" end subroutine processes_2 @ %def processes_2 @ Trivial for testing: do not allocate the MCI record. <>= subroutine dispatch_mci_empty (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 end subroutine dispatch_mci_empty @ %def dispatch_mci_empty @ \subsubsection{Compute a trivial matrix element} Initialize a process, retrieve some information and compute a matrix element. We use the same trivial process as for the previous test. All momentum and state dependence is trivial, so we just test basic functionality. <>= call test (processes_3, "processes_3", & "retrieve a trivial matrix element", & u, results) <>= public :: processes_3 <>= subroutine processes_3 (u) integer, intent(in) :: u type(process_library_t), target :: lib type(string_t) :: libname type(string_t) :: procname type(os_data_t) :: os_data type(model_t), target :: model type(process_t), allocatable :: process class(phs_config_t), allocatable :: phs_config_template type(process_constants_t) :: data type(vector4_t), dimension(:), allocatable :: p write (u, "(A)") "* Test output: processes_3" write (u, "(A)") "* Purpose: create a process & &and compute a matrix element" write (u, "(A)") write (u, "(A)") "* Build and load a test library with one process" write (u, "(A)") libname = "processes3" procname = libname call os_data%init () call prc_test_create_library (libname, lib) call model%init_test () allocate (process) call process%init (procname, lib, os_data, model) call process%setup_test_cores () allocate (phs_test_config_t :: phs_config_template) call process%init_components (phs_config_template) call process%setup_mci (dispatch_mci_test3) write (u, "(A)") "* Return the number of process components" write (u, "(A)") write (u, "(A,I0)") "n_components = ", process%get_n_components () write (u, "(A)") write (u, "(A)") "* Return the number of flavor states" write (u, "(A)") data = process%get_constants (1) write (u, "(A,I0)") "n_flv(1) = ", data%n_flv write (u, "(A)") write (u, "(A)") "* Return the first flavor state" write (u, "(A)") write (u, "(A,4(1x,I0))") "flv_state(1) =", data%flv_state (:,1) write (u, "(A)") write (u, "(A)") "* Set up kinematics & &[arbitrary, the matrix element is constant]" allocate (p (4)) write (u, "(A)") write (u, "(A)") "* Retrieve the matrix element" write (u, "(A)") write (u, "(A,F5.3,' + ',F5.3,' I')") "me (1, p, 1, 1, 1) = ", & process%compute_amplitude (1, 1, 1, p, 1, 1, 1) write (u, "(A)") write (u, "(A)") "* Cleanup" call process%final () deallocate (process) call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: processes_3" end subroutine processes_3 @ %def processes_3 @ MCI record with some contents. <>= subroutine dispatch_mci_test3 (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 allocate (mci_test_t :: mci) select type (mci) type is (mci_test_t) call mci%set_dimensions (2, 2) call mci%set_divisions (100) end select end subroutine dispatch_mci_test3 @ %def dispatch_mci_test3 @ \subsubsection{Generate a process instance} Initialize a process and process instance, choose a sampling point and fill the process instance. We use the same trivial process as for the previous test. All momentum and state dependence is trivial, so we just test basic functionality. <>= call test (processes_4, "processes_4", & "create and fill a process instance (partonic event)", & u, results) <>= public :: processes_4 <>= subroutine processes_4 (u) integer, intent(in) :: u type(process_library_t), target :: lib type(string_t) :: libname type(string_t) :: procname type(os_data_t) :: os_data type(model_t), target :: model type(process_t), allocatable, target :: process class(phs_config_t), allocatable :: phs_config_template real(default) :: sqrts type(process_instance_t), allocatable, target :: process_instance type(particle_set_t) :: pset write (u, "(A)") "* Test output: processes_4" write (u, "(A)") "* Purpose: create a process & &and fill a process instance" write (u, "(A)") write (u, "(A)") "* Build and initialize a test process" write (u, "(A)") libname = "processes4" procname = libname call os_data%init () call prc_test_create_library (libname, lib) call reset_interaction_counter () call model%init_test () allocate (process) call process%init (procname, lib, os_data, model) call process%setup_test_cores () allocate (phs_test_config_t :: phs_config_template) call process%init_components (phs_config_template) write (u, "(A)") "* Prepare a trivial beam setup" write (u, "(A)") sqrts = 1000 call process%setup_beams_sqrts (sqrts, i_core = 1) call process%configure_phs () call process%setup_mci (dispatch_mci_empty) write (u, "(A)") "* Complete process initialization" write (u, "(A)") call process%setup_terms () call process%write (.false., u) write (u, "(A)") write (u, "(A)") "* Create a process instance" write (u, "(A)") allocate (process_instance) call process_instance%init (process) call process_instance%write (u) write (u, "(A)") write (u, "(A)") "* Inject a set of random numbers" write (u, "(A)") call process_instance%choose_mci (1) call process_instance%set_mcpar ([0._default, 0._default]) call process_instance%write (u) write (u, "(A)") write (u, "(A)") "* Set up hard kinematics" write (u, "(A)") call process_instance%select_channel (1) call process_instance%compute_seed_kinematics () call process_instance%compute_hard_kinematics () call process_instance%compute_eff_kinematics () call process_instance%evaluate_expressions () call process_instance%compute_other_channels () write (u, "(A)") "* Evaluate matrix element and square" write (u, "(A)") call process_instance%evaluate_trace () call process_instance%write (u) call process_instance%get_trace (pset, 1) call process_instance%final () deallocate (process_instance) write (u, "(A)") write (u, "(A)") "* Particle content:" write (u, "(A)") call write_separator (u) call pset%write (u) call write_separator (u) write (u, "(A)") write (u, "(A)") "* Recover process instance" write (u, "(A)") allocate (process_instance) call process_instance%init (process) call process_instance%choose_mci (1) call process_instance%set_trace (pset, 1, check_match = .false.) call process_instance%activate () process_instance%evaluation_status = STAT_EFF_KINEMATICS call process_instance%recover_hard_kinematics (i_term = 1) call process_instance%recover_seed_kinematics (i_term = 1) call process_instance%select_channel (1) call process_instance%recover_mcpar (i_term = 1) call process_instance%compute_seed_kinematics (skip_term = 1) call process_instance%compute_hard_kinematics (skip_term = 1) call process_instance%compute_eff_kinematics (skip_term = 1) call process_instance%evaluate_expressions () call process_instance%compute_other_channels (skip_term = 1) call process_instance%evaluate_trace () call process_instance%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call pset%final () call process_instance%final () deallocate (process_instance) call process%final () deallocate (process) call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: processes_4" end subroutine processes_4 @ %def processes_4 @ \subsubsection{Structure function configuration} Configure structure functions (multi-channel) in a process object. <>= call test (processes_7, "processes_7", & "process configuration with structure functions", & u, results) <>= public :: processes_7 <>= subroutine processes_7 (u) integer, intent(in) :: u type(process_library_t), target :: lib type(string_t) :: libname type(string_t) :: procname type(os_data_t) :: os_data type(model_t), target :: model type(process_t), allocatable, target :: process class(phs_config_t), allocatable :: phs_config_template real(default) :: sqrts type(pdg_array_t) :: pdg_in class(sf_data_t), allocatable, target :: data type(sf_config_t), dimension(:), allocatable :: sf_config type(sf_channel_t), dimension(2) :: sf_channel write (u, "(A)") "* Test output: processes_7" write (u, "(A)") "* Purpose: initialize a process with & &structure functions" write (u, "(A)") write (u, "(A)") "* Build and initialize a process object" write (u, "(A)") libname = "processes7" procname = libname call os_data%init () call prc_test_create_library (libname, lib) call model%init_test () allocate (process) call process%init (procname, lib, os_data, model) call process%setup_test_cores () allocate (phs_test_config_t :: phs_config_template) call process%init_components (phs_config_template) write (u, "(A)") "* Set beam, structure functions, and mappings" write (u, "(A)") sqrts = 1000 call process%setup_beams_sqrts (sqrts, i_core = 1) call process%configure_phs () pdg_in = 25 allocate (sf_test_data_t :: data) select type (data) type is (sf_test_data_t) call data%init (process%get_model_ptr (), pdg_in) end select allocate (sf_config (2)) call sf_config(1)%init ([1], data) call sf_config(2)%init ([2], data) call process%init_sf_chain (sf_config) deallocate (sf_config) call process%test_allocate_sf_channels (3) call sf_channel(1)%init (2) call sf_channel(1)%activate_mapping ([1,2]) call process%set_sf_channel (2, sf_channel(1)) call sf_channel(2)%init (2) call sf_channel(2)%set_s_mapping ([1,2]) call process%set_sf_channel (3, sf_channel(2)) call process%setup_mci (dispatch_mci_empty) call process%write (.false., u) write (u, "(A)") write (u, "(A)") "* Cleanup" call process%final () deallocate (process) call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: processes_7" end subroutine processes_7 @ %def processes_7 @ \subsubsection{Evaluating a process with structure function} Configure structure functions (single-channel) in a process object, create an instance, compute kinematics and evaluate. Note the order of operations when setting up structure functions and phase space. The beams are first, they determine the [[sqrts]] value. We can also set up the chain of structure functions. We then configure the phase space. From this, we can obtain information about special configurations (resonances, etc.), which we need for allocating the possible structure-function channels (parameterizations and mappings). Finally, we match phase-space channels onto structure-function channels. In the current example, this matching is trivial; we only have one structure-function channel. <>= call test (processes_8, "processes_8", & "process evaluation with structure functions", & u, results) <>= public :: processes_8 <>= subroutine processes_8 (u) integer, intent(in) :: u type(process_library_t), target :: lib type(string_t) :: libname type(string_t) :: procname type(os_data_t) :: os_data type(model_t), target :: model type(process_t), allocatable, target :: process class(phs_config_t), allocatable :: phs_config_template real(default) :: sqrts type(process_instance_t), allocatable, target :: process_instance type(pdg_array_t) :: pdg_in class(sf_data_t), allocatable, target :: data type(sf_config_t), dimension(:), allocatable :: sf_config type(sf_channel_t) :: sf_channel type(particle_set_t) :: pset write (u, "(A)") "* Test output: processes_8" write (u, "(A)") "* Purpose: evaluate a process with & &structure functions" write (u, "(A)") write (u, "(A)") "* Build and initialize a process object" write (u, "(A)") libname = "processes8" procname = libname call os_data%init () call prc_test_create_library (libname, lib) call reset_interaction_counter () call model%init_test () allocate (process) call process%init (procname, lib, os_data, model) call process%setup_test_cores () allocate (phs_test_config_t :: phs_config_template) call process%init_components (phs_config_template) write (u, "(A)") "* Set beam, structure functions, and mappings" write (u, "(A)") sqrts = 1000 call process%setup_beams_sqrts (sqrts, i_core = 1) pdg_in = 25 allocate (sf_test_data_t :: data) select type (data) type is (sf_test_data_t) call data%init (process%get_model_ptr (), pdg_in) end select allocate (sf_config (2)) call sf_config(1)%init ([1], data) call sf_config(2)%init ([2], data) call process%init_sf_chain (sf_config) deallocate (sf_config) call process%configure_phs () call process%test_allocate_sf_channels (1) call sf_channel%init (2) call sf_channel%activate_mapping ([1,2]) call process%set_sf_channel (1, sf_channel) write (u, "(A)") "* Complete process initialization" write (u, "(A)") call process%setup_mci (dispatch_mci_empty) call process%setup_terms () call process%write (.false., u) write (u, "(A)") write (u, "(A)") "* Create a process instance" write (u, "(A)") allocate (process_instance) call process_instance%init (process) write (u, "(A)") "* Set up kinematics and evaluate" write (u, "(A)") call process_instance%choose_mci (1) call process_instance%evaluate_sqme (1, & [0.8_default, 0.8_default, 0.1_default, 0.2_default]) call process_instance%write (u) call process_instance%get_trace (pset, 1) call process_instance%final () deallocate (process_instance) write (u, "(A)") write (u, "(A)") "* Particle content:" write (u, "(A)") call write_separator (u) call pset%write (u) call write_separator (u) write (u, "(A)") write (u, "(A)") "* Recover process instance" write (u, "(A)") call reset_interaction_counter (2) allocate (process_instance) call process_instance%init (process) call process_instance%choose_mci (1) call process_instance%set_trace (pset, 1, check_match = .false.) call process_instance%recover & (channel = 1, i_term = 1, update_sqme = .true., recover_phs = .true.) call process_instance%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call pset%final () call process_instance%final () deallocate (process_instance) call process%final () deallocate (process) call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: processes_8" end subroutine processes_8 @ %def processes_8 @ \subsubsection{Multi-channel phase space and structure function} This is an extension of the previous example. This time, we have two distinct structure-function channels which are matched to the two distinct phase-space channels. <>= call test (processes_9, "processes_9", & "multichannel kinematics and structure functions", & u, results) <>= public :: processes_9 <>= subroutine processes_9 (u) integer, intent(in) :: u type(process_library_t), target :: lib type(string_t) :: libname type(string_t) :: procname type(os_data_t) :: os_data type(model_t), target :: model type(process_t), allocatable, target :: process class(phs_config_t), allocatable :: phs_config_template real(default) :: sqrts type(process_instance_t), allocatable, target :: process_instance type(pdg_array_t) :: pdg_in class(sf_data_t), allocatable, target :: data type(sf_config_t), dimension(:), allocatable :: sf_config type(sf_channel_t) :: sf_channel real(default), dimension(4) :: x_saved type(particle_set_t) :: pset write (u, "(A)") "* Test output: processes_9" write (u, "(A)") "* Purpose: evaluate a process with & &structure functions" write (u, "(A)") "* in a multi-channel configuration" write (u, "(A)") write (u, "(A)") "* Build and initialize a process object" write (u, "(A)") libname = "processes9" procname = libname call os_data%init () call prc_test_create_library (libname, lib) call reset_interaction_counter () call model%init_test () allocate (process) call process%init (procname, lib, os_data, model) call process%setup_test_cores () allocate (phs_test_config_t :: phs_config_template) call process%init_components (phs_config_template) write (u, "(A)") "* Set beam, structure functions, and mappings" write (u, "(A)") sqrts = 1000 call process%setup_beams_sqrts (sqrts, i_core = 1) pdg_in = 25 allocate (sf_test_data_t :: data) select type (data) type is (sf_test_data_t) call data%init (process%get_model_ptr (), pdg_in) end select allocate (sf_config (2)) call sf_config(1)%init ([1], data) call sf_config(2)%init ([2], data) call process%init_sf_chain (sf_config) deallocate (sf_config) call process%configure_phs () call process%test_allocate_sf_channels (2) call sf_channel%init (2) call process%set_sf_channel (1, sf_channel) call sf_channel%init (2) call sf_channel%activate_mapping ([1,2]) call process%set_sf_channel (2, sf_channel) call process%test_set_component_sf_channel ([1, 2]) write (u, "(A)") "* Complete process initialization" write (u, "(A)") call process%setup_mci (dispatch_mci_empty) call process%setup_terms () call process%write (.false., u) write (u, "(A)") write (u, "(A)") "* Create a process instance" write (u, "(A)") allocate (process_instance) call process_instance%init (process) write (u, "(A)") "* Set up kinematics in channel 1 and evaluate" write (u, "(A)") call process_instance%choose_mci (1) call process_instance%evaluate_sqme (1, & [0.8_default, 0.8_default, 0.1_default, 0.2_default]) call process_instance%write (u) write (u, "(A)") write (u, "(A)") "* Extract MC input parameters" write (u, "(A)") write (u, "(A)") "Channel 1:" call process_instance%get_mcpar (1, x_saved) write (u, "(2x,9(1x,F7.5))") x_saved write (u, "(A)") "Channel 2:" call process_instance%get_mcpar (2, x_saved) write (u, "(2x,9(1x,F7.5))") x_saved write (u, "(A)") write (u, "(A)") "* Set up kinematics in channel 2 and evaluate" write (u, "(A)") call process_instance%evaluate_sqme (2, x_saved) call process_instance%write (u) call process_instance%get_trace (pset, 1) call process_instance%final () deallocate (process_instance) write (u, "(A)") write (u, "(A)") "* Recover process instance for channel 2" write (u, "(A)") call reset_interaction_counter (2) allocate (process_instance) call process_instance%init (process) call process_instance%choose_mci (1) call process_instance%set_trace (pset, 1, check_match = .false.) call process_instance%recover & (channel = 2, i_term = 1, update_sqme = .true., recover_phs = .true.) call process_instance%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call pset%final () call process_instance%final () deallocate (process_instance) call process%final () deallocate (process) call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: processes_9" end subroutine processes_9 @ %def processes_9 @ \subsubsection{Event generation} Activate the MC integrator for the process object and use it to generate a single event. Note that the test integrator does not require integration in preparation for generating events. <>= call test (processes_10, "processes_10", & "event generation", & u, results) <>= public :: processes_10 <>= subroutine processes_10 (u) integer, intent(in) :: u type(process_library_t), target :: lib type(string_t) :: libname type(string_t) :: procname type(os_data_t) :: os_data type(model_t), target :: model type(process_t), allocatable, target :: process class(mci_t), pointer :: mci class(phs_config_t), allocatable :: phs_config_template real(default) :: sqrts type(process_instance_t), allocatable, target :: process_instance write (u, "(A)") "* Test output: processes_10" write (u, "(A)") "* Purpose: generate events for a process without & &structure functions" write (u, "(A)") "* in a multi-channel configuration" write (u, "(A)") write (u, "(A)") "* Build and initialize a process object" write (u, "(A)") libname = "processes10" procname = libname call os_data%init () call prc_test_create_library (libname, lib) call reset_interaction_counter () call model%init_test () allocate (process) call process%init (procname, lib, os_data, model) call process%setup_test_cores () allocate (phs_test_config_t :: phs_config_template) call process%init_components (phs_config_template) write (u, "(A)") "* Prepare a trivial beam setup" write (u, "(A)") sqrts = 1000 call process%setup_beams_sqrts (sqrts, i_core = 1) call process%configure_phs () call process%setup_mci (dispatch_mci_test10) write (u, "(A)") "* Complete process initialization" write (u, "(A)") call process%setup_terms () call process%write (.false., u) write (u, "(A)") write (u, "(A)") "* Create a process instance" write (u, "(A)") allocate (process_instance) call process_instance%init (process) write (u, "(A)") "* Generate weighted event" write (u, "(A)") call process%test_get_mci_ptr (mci) select type (mci) type is (mci_test_t) ! This ensures that the next 'random' numbers are 0.3, 0.5, 0.7 call mci%rng%init (3) ! Include the constant PHS factor in the stored maximum of the integrand call mci%set_max_factor (conv * twopi4 & / (2 * sqrt (lambda (sqrts **2, 125._default**2, 125._default**2)))) end select call process_instance%generate_weighted_event (1) call process_instance%write (u) write (u, "(A)") write (u, "(A)") "* Generate unweighted event" write (u, "(A)") call process_instance%generate_unweighted_event (1) call process%test_get_mci_ptr (mci) select type (mci) type is (mci_test_t) write (u, "(A,I0)") " Success in try ", mci%tries write (u, "(A)") end select call process_instance%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call process_instance%final () deallocate (process_instance) call process%final () deallocate (process) call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: processes_10" end subroutine processes_10 @ %def processes_10 @ MCI record with some contents. <>= subroutine dispatch_mci_test10 (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 allocate (mci_test_t :: mci) select type (mci) type is (mci_test_t); call mci%set_divisions (100) end select end subroutine dispatch_mci_test10 @ %def dispatch_mci_test10 @ \subsubsection{Integration} Activate the MC integrator for the process object and use it to integrate over phase space. <>= call test (processes_11, "processes_11", & "integration", & u, results) <>= public :: processes_11 <>= subroutine processes_11 (u) integer, intent(in) :: u type(process_library_t), target :: lib type(string_t) :: libname type(string_t) :: procname type(os_data_t) :: os_data type(model_t), target :: model type(process_t), allocatable, target :: process class(mci_t), allocatable :: mci_template class(phs_config_t), allocatable :: phs_config_template real(default) :: sqrts type(process_instance_t), allocatable, target :: process_instance write (u, "(A)") "* Test output: processes_11" write (u, "(A)") "* Purpose: integrate a process without & &structure functions" write (u, "(A)") "* in a multi-channel configuration" write (u, "(A)") write (u, "(A)") "* Build and initialize a process object" write (u, "(A)") libname = "processes11" procname = libname call os_data%init () call prc_test_create_library (libname, lib) call reset_interaction_counter () call model%init_test () allocate (process) call process%init (procname, lib, os_data, model) call process%setup_test_cores () allocate (phs_test_config_t :: phs_config_template) call process%init_components (phs_config_template) write (u, "(A)") "* Prepare a trivial beam setup" write (u, "(A)") sqrts = 1000 call process%setup_beams_sqrts (sqrts, i_core = 1) call process%configure_phs () call process%setup_mci (dispatch_mci_test10) write (u, "(A)") "* Complete process initialization" write (u, "(A)") call process%setup_terms () call process%write (.false., u) write (u, "(A)") write (u, "(A)") "* Create a process instance" write (u, "(A)") allocate (process_instance) call process_instance%init (process) write (u, "(A)") "* Integrate with default test parameters" write (u, "(A)") call process_instance%integrate (1, n_it=1, n_calls=10000) call process%final_integration (1) call process%write (.false., u) write (u, "(A)") write (u, "(A,ES13.7)") " Integral divided by phs factor = ", & process%get_integral (1) & / process_instance%kin(1)%phs_factor write (u, "(A)") write (u, "(A)") "* Cleanup" call process_instance%final () deallocate (process_instance) call process%final () deallocate (process) call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: processes_11" end subroutine processes_11 @ %def processes_11 @ \subsubsection{Complete events} For the purpose of simplifying further tests, we implement a convenience routine that initializes a process and prepares a single event. This is a wrapup of the test [[processes_10]]. The procedure is re-exported by the [[processes_ut]] module. <>= public :: prepare_test_process <>= subroutine prepare_test_process & (process, process_instance, model, var_list, run_id) type(process_t), intent(out), target :: process type(process_instance_t), intent(out), target :: process_instance class(model_data_t), intent(in), target :: model type(var_list_t), intent(inout), optional :: var_list type(string_t), intent(in), optional :: run_id type(process_library_t), target :: lib type(string_t) :: libname type(string_t) :: procname type(os_data_t) :: os_data type(model_t), allocatable, target :: process_model class(mci_t), pointer :: mci class(phs_config_t), allocatable :: phs_config_template real(default) :: sqrts libname = "processes_test" procname = libname call os_data%init () call prc_test_create_library (libname, lib) call reset_interaction_counter () allocate (process_model) call process_model%init (model%get_name (), & model%get_n_real (), & model%get_n_complex (), & model%get_n_field (), & model%get_n_vtx ()) call process_model%copy_from (model) call process%init (procname, lib, os_data, process_model, var_list) if (present (run_id)) call process%set_run_id (run_id) call process%setup_test_cores () allocate (phs_test_config_t :: phs_config_template) call process%init_components (phs_config_template) sqrts = 1000 call process%setup_beams_sqrts (sqrts, i_core = 1) call process%configure_phs () call process%setup_mci (dispatch_mci_test10) call process%setup_terms () call process_instance%init (process) call process%test_get_mci_ptr (mci) select type (mci) type is (mci_test_t) ! This ensures that the next 'random' numbers are 0.3, 0.5, 0.7 call mci%rng%init (3) ! Include the constant PHS factor in the stored maximum of the integrand call mci%set_max_factor (conv * twopi4 & / (2 * sqrt (lambda (sqrts **2, 125._default**2, 125._default**2)))) end select call process%reset_library_ptr () ! avoid dangling pointer call process_model%final () end subroutine prepare_test_process @ %def prepare_test_process @ Here we do the cleanup of the process and process instance emitted by the previous routine. <>= public :: cleanup_test_process <>= subroutine cleanup_test_process (process, process_instance) type(process_t), intent(inout) :: process type(process_instance_t), intent(inout) :: process_instance call process_instance%final () call process%final () end subroutine cleanup_test_process @ %def cleanup_test_process @ This is the actual test. Prepare the test process and event, fill all evaluators, and display the results. Use a particle set as temporary storage, read kinematics and recalculate the event. <>= call test (processes_12, "processes_12", & "event post-processing", & u, results) <>= public :: processes_12 <>= subroutine processes_12 (u) integer, intent(in) :: u type(process_t), allocatable, target :: process type(process_instance_t), allocatable, target :: process_instance type(particle_set_t) :: pset type(model_data_t), target :: model write (u, "(A)") "* Test output: processes_12" write (u, "(A)") "* Purpose: generate a complete partonic event" write (u, "(A)") call model%init_test () write (u, "(A)") "* Build and initialize process and process instance & &and generate event" write (u, "(A)") allocate (process) allocate (process_instance) call prepare_test_process (process, process_instance, model, & run_id = var_str ("run_12")) call process_instance%setup_event_data (i_core = 1) call process%prepare_simulation (1) call process_instance%init_simulation (1) call process_instance%generate_weighted_event (1) call process_instance%evaluate_event_data () call process_instance%write (u) call process_instance%get_trace (pset, 1) call process_instance%final_simulation (1) call process_instance%final () deallocate (process_instance) write (u, "(A)") write (u, "(A)") "* Recover kinematics and recalculate" write (u, "(A)") call reset_interaction_counter (2) allocate (process_instance) call process_instance%init (process) call process_instance%setup_event_data () call process_instance%choose_mci (1) call process_instance%set_trace (pset, 1, check_match = .false.) call process_instance%recover & (channel = 1, i_term = 1, update_sqme = .true., recover_phs = .true.) call process_instance%recover_event () call process_instance%evaluate_event_data () call process_instance%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call cleanup_test_process (process, process_instance) deallocate (process_instance) deallocate (process) call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: processes_12" end subroutine processes_12 @ %def processes_12 @ \subsubsection{Colored interaction} This test specifically checks the transformation of process data (flavor, helicity, and color) into an interaction in a process term. We use the [[test_t]] process core (which has no nontrivial particles), but call only the [[is_allowed]] method, which always returns true. <>= call test (processes_13, "processes_13", & "colored interaction", & u, results) <>= public :: processes_13 <>= subroutine processes_13 (u) integer, intent(in) :: u type(os_data_t) :: os_data type(model_data_t), target :: model type(process_term_t) :: term class(prc_core_t), allocatable :: core write (u, "(A)") "* Test output: processes_13" write (u, "(A)") "* Purpose: initialized a colored interaction" write (u, "(A)") write (u, "(A)") "* Set up a process constants block" write (u, "(A)") call os_data%init () call model%init_sm_test () allocate (test_t :: core) associate (data => term%data) data%n_in = 2 data%n_out = 3 data%n_flv = 2 data%n_hel = 2 data%n_col = 2 data%n_cin = 2 allocate (data%flv_state (5, 2)) data%flv_state (:,1) = [ 1, 21, 1, 21, 21] data%flv_state (:,2) = [ 2, 21, 2, 21, 21] allocate (data%hel_state (5, 2)) data%hel_state (:,1) = [1, 1, 1, 1, 0] data%hel_state (:,2) = [1,-1, 1,-1, 0] allocate (data%col_state (2, 5, 2)) data%col_state (:,:,1) = & reshape ([[1, 0], [2,-1], [3, 0], [2,-3], [0,0]], [2,5]) data%col_state (:,:,2) = & reshape ([[1, 0], [2,-3], [3, 0], [2,-1], [0,0]], [2,5]) allocate (data%ghost_flag (5, 2)) data%ghost_flag(1:4,:) = .false. data%ghost_flag(5,:) = .true. end associate write (u, "(A)") "* Set up the interaction" write (u, "(A)") call reset_interaction_counter () call term%setup_interaction (core, model) call term%int%basic_write (u) call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: processes_13" end subroutine processes_13 @ %def processes_13 @ \subsubsection{MD5 sums} Configure a process with structure functions (multi-channel) and compute MD5 sums <>= call test (processes_14, "processes_14", & "process configuration and MD5 sum", & u, results) <>= public :: processes_14 <>= subroutine processes_14 (u) integer, intent(in) :: u type(process_library_t), target :: lib type(string_t) :: libname type(string_t) :: procname type(os_data_t) :: os_data type(model_t), target :: model type(process_t), allocatable, target :: process class(phs_config_t), allocatable :: phs_config_template real(default) :: sqrts type(pdg_array_t) :: pdg_in class(sf_data_t), allocatable, target :: data type(sf_config_t), dimension(:), allocatable :: sf_config type(sf_channel_t), dimension(3) :: sf_channel write (u, "(A)") "* Test output: processes_14" write (u, "(A)") "* Purpose: initialize a process with & &structure functions" write (u, "(A)") "* and compute MD5 sum" write (u, "(A)") write (u, "(A)") "* Build and initialize a process object" write (u, "(A)") libname = "processes7" procname = libname call os_data%init () call prc_test_create_library (libname, lib) call lib%compute_md5sum () call model%init_test () allocate (process) call process%init (procname, lib, os_data, model) call process%setup_test_cores () allocate (phs_test_config_t :: phs_config_template) call process%init_components (phs_config_template) write (u, "(A)") "* Set beam, structure functions, and mappings" write (u, "(A)") sqrts = 1000 call process%setup_beams_sqrts (sqrts, i_core = 1) call process%configure_phs () pdg_in = 25 allocate (sf_test_data_t :: data) select type (data) type is (sf_test_data_t) call data%init (process%get_model_ptr (), pdg_in) end select call process%test_allocate_sf_channels (3) allocate (sf_config (2)) call sf_config(1)%init ([1], data) call sf_config(2)%init ([2], data) call process%init_sf_chain (sf_config) deallocate (sf_config) call sf_channel(1)%init (2) call process%set_sf_channel (1, sf_channel(1)) call sf_channel(2)%init (2) call sf_channel(2)%activate_mapping ([1,2]) call process%set_sf_channel (2, sf_channel(2)) call sf_channel(3)%init (2) call sf_channel(3)%set_s_mapping ([1,2]) call process%set_sf_channel (3, sf_channel(3)) call process%setup_mci (dispatch_mci_empty) call process%compute_md5sum () call process%write (.false., u) write (u, "(A)") write (u, "(A)") "* Cleanup" call process%final () deallocate (process) call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: processes_14" end subroutine processes_14 @ %def processes_14 @ \subsubsection{Decay Process Evaluation} Initialize an evaluate a decay process. <>= call test (processes_15, "processes_15", & "decay process", & u, results) <>= public :: processes_15 <>= subroutine processes_15 (u) integer, intent(in) :: u type(process_library_t), target :: lib type(string_t) :: libname type(string_t) :: procname type(os_data_t) :: os_data type(model_t), target :: model type(process_t), allocatable, target :: process class(phs_config_t), allocatable :: phs_config_template type(process_instance_t), allocatable, target :: process_instance type(particle_set_t) :: pset write (u, "(A)") "* Test output: processes_15" write (u, "(A)") "* Purpose: initialize a decay process object" write (u, "(A)") write (u, "(A)") "* Build and load a test library with one process" write (u, "(A)") libname = "processes15" procname = libname call os_data%init () call prc_test_create_library (libname, lib, scattering = .false., & decay = .true.) call model%init_test () call model%set_par (var_str ("ff"), 0.4_default) call model%set_par (var_str ("mf"), & model%get_real (var_str ("ff")) * model%get_real (var_str ("ms"))) write (u, "(A)") "* Initialize a process object" write (u, "(A)") allocate (process) call process%init (procname, lib, os_data, model) call process%setup_test_cores () allocate (phs_single_config_t :: phs_config_template) call process%init_components (phs_config_template) write (u, "(A)") "* Prepare a trivial beam setup" write (u, "(A)") call process%setup_beams_decay (i_core = 1) call process%configure_phs () call process%setup_mci (dispatch_mci_empty) write (u, "(A)") "* Complete process initialization" write (u, "(A)") call process%setup_terms () call process%write (.false., u) write (u, "(A)") write (u, "(A)") "* Create a process instance" write (u, "(A)") call reset_interaction_counter (3) allocate (process_instance) call process_instance%init (process) call process_instance%write (u) write (u, "(A)") write (u, "(A)") "* Inject a set of random numbers" write (u, "(A)") call process_instance%choose_mci (1) call process_instance%set_mcpar ([0._default, 0._default]) call process_instance%write (u) write (u, "(A)") write (u, "(A)") "* Set up hard kinematics" write (u, "(A)") call process_instance%select_channel (1) call process_instance%compute_seed_kinematics () call process_instance%compute_hard_kinematics () write (u, "(A)") "* Evaluate matrix element and square" write (u, "(A)") call process_instance%compute_eff_kinematics () call process_instance%evaluate_expressions () call process_instance%compute_other_channels () call process_instance%evaluate_trace () call process_instance%write (u) call process_instance%get_trace (pset, 1) call process_instance%final () deallocate (process_instance) write (u, "(A)") write (u, "(A)") "* Particle content:" write (u, "(A)") call write_separator (u) call pset%write (u) call write_separator (u) write (u, "(A)") write (u, "(A)") "* Recover process instance" write (u, "(A)") call reset_interaction_counter (3) allocate (process_instance) call process_instance%init (process) call process_instance%choose_mci (1) call process_instance%set_trace (pset, 1, check_match = .false.) call process_instance%recover (1, 1, .true., .true.) call process_instance%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call pset%final () call process_instance%final () deallocate (process_instance) call process%final () deallocate (process) call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: processes_15" end subroutine processes_15 @ %def processes_15 @ \subsubsection{Integration: decay} Activate the MC integrator for the decay object and use it to integrate over phase space. <>= call test (processes_16, "processes_16", & "decay integration", & u, results) <>= public :: processes_16 <>= subroutine processes_16 (u) integer, intent(in) :: u type(process_library_t), target :: lib type(string_t) :: libname type(string_t) :: procname type(os_data_t) :: os_data type(model_t), target :: model type(process_t), allocatable, target :: process class(phs_config_t), allocatable :: phs_config_template type(process_instance_t), allocatable, target :: process_instance write (u, "(A)") "* Test output: processes_16" write (u, "(A)") "* Purpose: integrate a process without & &structure functions" write (u, "(A)") "* in a multi-channel configuration" write (u, "(A)") write (u, "(A)") "* Build and initialize a process object" write (u, "(A)") libname = "processes16" procname = libname call os_data%init () call prc_test_create_library (libname, lib, scattering = .false., & decay = .true.) call reset_interaction_counter () call model%init_test () call model%set_par (var_str ("ff"), 0.4_default) call model%set_par (var_str ("mf"), & model%get_real (var_str ("ff")) * model%get_real (var_str ("ms"))) allocate (process) call process%init (procname, lib, os_data, model) call process%setup_test_cores () allocate (phs_single_config_t :: phs_config_template) call process%init_components (phs_config_template) write (u, "(A)") "* Prepare a trivial beam setup" write (u, "(A)") call process%setup_beams_decay (i_core = 1) call process%configure_phs () call process%setup_mci (dispatch_mci_test_midpoint) write (u, "(A)") "* Complete process initialization" write (u, "(A)") call process%setup_terms () call process%write (.false., u) write (u, "(A)") write (u, "(A)") "* Create a process instance" write (u, "(A)") allocate (process_instance) call process_instance%init (process) write (u, "(A)") "* Integrate with default test parameters" write (u, "(A)") call process_instance%integrate (1, n_it=1, n_calls=10000) call process%final_integration (1) call process%write (.false., u) write (u, "(A)") write (u, "(A,ES13.7)") " Integral divided by phs factor = ", & process%get_integral (1) & / process_instance%kin(1)%phs_factor write (u, "(A)") write (u, "(A)") "* Cleanup" call process_instance%final () deallocate (process_instance) call process%final () deallocate (process) call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: processes_16" end subroutine processes_16 @ %def processes_16 @ MCI record prepared for midpoint integrator. <>= subroutine dispatch_mci_test_midpoint (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 allocate (mci_midpoint_t :: mci) end subroutine dispatch_mci_test_midpoint @ %def dispatch_mci_test_midpoint @ \subsubsection{Decay Process Evaluation} Initialize an evaluate a decay process for a moving particle. <>= call test (processes_17, "processes_17", & "decay of moving particle", & u, results) <>= public :: processes_17 <>= subroutine processes_17 (u) integer, intent(in) :: u type(process_library_t), target :: lib type(string_t) :: libname type(string_t) :: procname type(os_data_t) :: os_data type(model_t), target :: model type(process_t), allocatable, target :: process class(phs_config_t), allocatable :: phs_config_template type(process_instance_t), allocatable, target :: process_instance type(particle_set_t) :: pset type(flavor_t) :: flv_beam real(default) :: m, p, E write (u, "(A)") "* Test output: processes_17" write (u, "(A)") "* Purpose: initialize a decay process object" write (u, "(A)") write (u, "(A)") "* Build and load a test library with one process" write (u, "(A)") libname = "processes17" procname = libname call os_data%init () call prc_test_create_library (libname, lib, scattering = .false., & decay = .true.) write (u, "(A)") "* Initialize a process object" write (u, "(A)") call model%init_test () call model%set_par (var_str ("ff"), 0.4_default) call model%set_par (var_str ("mf"), & model%get_real (var_str ("ff")) * model%get_real (var_str ("ms"))) allocate (process) call process%init (procname, lib, os_data, model) call process%setup_test_cores () allocate (phs_single_config_t :: phs_config_template) call process%init_components (phs_config_template) write (u, "(A)") "* Prepare a trivial beam setup" write (u, "(A)") call process%setup_beams_decay (rest_frame = .false., i_core = 1) call process%configure_phs () call process%setup_mci (dispatch_mci_empty) write (u, "(A)") "* Complete process initialization" write (u, "(A)") call process%setup_terms () call process%write (.false., u) write (u, "(A)") write (u, "(A)") "* Create a process instance" write (u, "(A)") call reset_interaction_counter (3) allocate (process_instance) call process_instance%init (process) call process_instance%write (u) write (u, "(A)") write (u, "(A)") "* Set parent momentum and random numbers" write (u, "(A)") call process_instance%choose_mci (1) call process_instance%set_mcpar ([0._default, 0._default]) call flv_beam%init (25, process%get_model_ptr ()) m = flv_beam%get_mass () p = 3 * m / 4 E = sqrt (m**2 + p**2) call process_instance%set_beam_momenta ([vector4_moving (E, p, 3)]) call process_instance%write (u) write (u, "(A)") write (u, "(A)") "* Set up hard kinematics" write (u, "(A)") call process_instance%select_channel (1) call process_instance%compute_seed_kinematics () call process_instance%compute_hard_kinematics () write (u, "(A)") "* Evaluate matrix element and square" write (u, "(A)") call process_instance%compute_eff_kinematics () call process_instance%evaluate_expressions () call process_instance%compute_other_channels () call process_instance%evaluate_trace () call process_instance%write (u) call process_instance%get_trace (pset, 1) call process_instance%final () deallocate (process_instance) write (u, "(A)") write (u, "(A)") "* Particle content:" write (u, "(A)") call write_separator (u) call pset%write (u) call write_separator (u) write (u, "(A)") write (u, "(A)") "* Recover process instance" write (u, "(A)") call reset_interaction_counter (3) allocate (process_instance) call process_instance%init (process) call process_instance%choose_mci (1) call process_instance%set_trace (pset, 1, check_match = .false.) call process_instance%recover (1, 1, .true., .true.) call process_instance%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call pset%final () call process_instance%final () deallocate (process_instance) call process%final () deallocate (process) call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: processes_17" end subroutine processes_17 @ %def processes_17 @ \subsubsection{Resonances in Phase Space} This test demonstrates the extraction of the resonance-history set from the generated phase space. We need a nontrivial process, but no matrix element. This is provided by the [[prc_template]] method, using the [[SM]] model. We also need the [[phs_wood]] method, otherwise we would not have resonances in the phase space configuration. <>= call test (processes_18, "processes_18", & "extract resonance history set", & u, results) <>= public :: processes_18 <>= subroutine processes_18 (u) integer, intent(in) :: u type(process_library_t), target :: lib type(string_t) :: libname type(string_t) :: procname type(string_t) :: model_name type(os_data_t) :: os_data class(model_data_t), pointer :: model class(vars_t), pointer :: vars type(process_t), pointer :: process type(resonance_history_set_t) :: res_set integer :: i write (u, "(A)") "* Test output: processes_18" write (u, "(A)") "* Purpose: extra resonance histories" write (u, "(A)") write (u, "(A)") "* Build and load a test library with one process" write (u, "(A)") libname = "processes_18_lib" procname = "processes_18_p" call os_data%init () call syntax_phs_forest_init () model_name = "SM" model => null () call prepare_model (model, model_name, vars) write (u, "(A)") "* Initialize a process library with one process" write (u, "(A)") select type (model) class is (model_t) call prepare_resonance_test_library (lib, libname, procname, model, os_data, u) end select write (u, "(A)") write (u, "(A)") "* Initialize a process object with phase space" allocate (process) select type (model) class is (model_t) call prepare_resonance_test_process (process, lib, procname, model, os_data) end select write (u, "(A)") write (u, "(A)") "* Extract resonance history set" write (u, "(A)") call process%extract_resonance_history_set (res_set) call res_set%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call process%final () deallocate (process) call model%final () deallocate (model) call syntax_phs_forest_final () write (u, "(A)") write (u, "(A)") "* Test output end: processes_18" end subroutine processes_18 @ %def processes_18 @ Auxiliary subroutine that constructs the process library for the above test. <>= subroutine prepare_resonance_test_library & (lib, libname, procname, model, os_data, u) type(process_library_t), target, intent(out) :: lib type(string_t), intent(in) :: libname type(string_t), intent(in) :: procname type(model_t), intent(in), target :: model type(os_data_t), intent(in) :: os_data integer, intent(in) :: u type(string_t), dimension(:), allocatable :: prt_in, prt_out class(prc_core_def_t), allocatable :: def type(process_def_entry_t), pointer :: entry call lib%init (libname) allocate (prt_in (2), prt_out (3)) prt_in = [var_str ("e+"), var_str ("e-")] prt_out = [var_str ("d"), var_str ("ubar"), var_str ("W+")] allocate (template_me_def_t :: def) select type (def) type is (template_me_def_t) call def%init (model, prt_in, prt_out, unity = .false.) end select allocate (entry) call entry%init (procname, & model_name = model%get_name (), & n_in = 2, n_components = 1) call entry%import_component (1, n_out = size (prt_out), & prt_in = new_prt_spec (prt_in), & prt_out = new_prt_spec (prt_out), & method = var_str ("template"), & variant = def) call entry%write (u) call lib%append (entry) call lib%configure (os_data) call lib%write_makefile (os_data, force = .true., verbose = .false.) call lib%clean (os_data, distclean = .false.) call lib%write_driver (force = .true.) call lib%load (os_data) end subroutine prepare_resonance_test_library @ %def prepare_resonance_test_library @ We want a test process which has been initialized up to the point where we can evaluate the matrix element. This is in fact rather complicated. We copy the steps from [[integration_setup_process]] in the [[integrate]] module, which is not available at this point. <>= subroutine prepare_resonance_test_process & (process, lib, procname, model, os_data) class(process_t), intent(out), target :: process type(process_library_t), intent(in), target :: lib type(string_t), intent(in) :: procname type(model_t), intent(in), target :: model type(os_data_t), intent(in) :: os_data class(phs_config_t), allocatable :: phs_config_template real(default) :: sqrts call process%init (procname, lib, os_data, model) allocate (phs_wood_config_t :: phs_config_template) call process%init_components (phs_config_template) call process%setup_test_cores (type_string = var_str ("template")) sqrts = 1000 call process%setup_beams_sqrts (sqrts, i_core = 1) call process%configure_phs () call process%setup_mci (dispatch_mci_none) call process%setup_terms () end subroutine prepare_resonance_test_process @ %def prepare_resonance_test_process @ MCI record prepared for the none (dummy) integrator. <>= subroutine dispatch_mci_none (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 allocate (mci_none_t :: mci) end subroutine dispatch_mci_none @ %def dispatch_mci_none @ \subsubsection{Add after evaluate hook(s)} Initialize a process and process instance, add a trivial process hook, choose a sampling point and fill the process instance. We use the same trivial process as for the previous test. All momentum and state dependence is trivial, so we just test basic functionality. <>= type, extends(process_instance_hook_t) :: process_instance_hook_test_t integer :: unit character(len=15) :: name contains procedure :: init => process_instance_hook_test_init procedure :: final => process_instance_hook_test_final procedure :: evaluate => process_instance_hook_test_evaluate end type process_instance_hook_test_t @ <>= subroutine process_instance_hook_test_init (hook, var_list, instance, pdf_data) class(process_instance_hook_test_t), intent(inout), target :: hook type(var_list_t), intent(in) :: var_list class(process_instance_t), intent(in), target :: instance type(pdf_data_t), intent(in), optional :: pdf_data end subroutine process_instance_hook_test_init subroutine process_instance_hook_test_final (hook) class(process_instance_hook_test_t), intent(inout) :: hook end subroutine process_instance_hook_test_final subroutine process_instance_hook_test_evaluate (hook, instance) class(process_instance_hook_test_t), intent(inout) :: hook class(process_instance_t), intent(in), target :: instance write (hook%unit, "(A)") "Execute hook:" write (hook%unit, "(2X,A,1X,A,I0,A)") hook%name, "(", len (trim (hook%name)), ")" end subroutine process_instance_hook_test_evaluate @ <>= call test (processes_19, "processes_19", & "add trivial hooks to a process instance ", & u, results) <>= public :: processes_19 <>= subroutine processes_19 (u) integer, intent(in) :: u type(process_library_t), target :: lib type(string_t) :: libname type(string_t) :: procname type(os_data_t) :: os_data class(model_data_t), pointer :: model type(process_t), allocatable, target :: process class(phs_config_t), allocatable :: phs_config_template real(default) :: sqrts type(process_instance_t) :: process_instance class(process_instance_hook_t), allocatable, target :: process_instance_hook, process_instance_hook2 type(particle_set_t) :: pset write (u, "(A)") "* Test output: processes_19" write (u, "(A)") "* Purpose: allocate process instance & &and add an after evaluate hook" write (u, "(A)") write (u, "(A)") write (u, "(A)") "* Allocate a process instance" write (u, "(A)") call process_instance%write (u) write (u, "(A)") write (u, "(A)") "* Allocate hook and add to process instance" write (u, "(A)") allocate (process_instance_hook_test_t :: process_instance_hook) call process_instance%append_after_hook (process_instance_hook) allocate (process_instance_hook_test_t :: process_instance_hook2) call process_instance%append_after_hook (process_instance_hook2) select type (process_instance_hook) type is (process_instance_hook_test_t) process_instance_hook%unit = u process_instance_hook%name = "Hook 1" end select select type (process_instance_hook2) type is (process_instance_hook_test_t) process_instance_hook2%unit = u process_instance_hook2%name = "Hook 2" end select write (u, "(A)") "* Evaluate matrix element and square" write (u, "(A)") call process_instance%evaluate_after_hook () write (u, "(A)") write (u, "(A)") "* Cleanup" call process_instance_hook%final () deallocate (process_instance_hook) write (u, "(A)") write (u, "(A)") "* Test output end: processes_19" end subroutine processes_19 @ %def processes_19 @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Process Stacks} For storing and handling multiple processes, we define process stacks. These are ordinary stacks where new process entries are pushed onto the top. We allow for multiple entries with identical process ID, but distinct run ID. The implementation is essentially identical to the [[prclib_stacks]] module above. Unfortunately, Fortran supports no generic programming, so we do not make use of this fact. When searching for a specific process ID, we will get (a pointer to) the topmost process entry with that ID on the stack, which was entered last. Usually, this is the best version of the process (in terms of integral, etc.) Thus the stack terminology makes sense. <<[[process_stacks.f90]]>>= <> module process_stacks <> <> use variables use process <> <> <> interface <> end interface end module process_stacks @ %def process_stacks @ <<[[process_stacks_sub.f90]]>>= <> submodule (process_stacks) process_stacks_s use io_units use format_utils, only: write_separator use diagnostics use observables implicit none contains <> end submodule process_stacks_s @ %def process_stacks_s @ \subsection{The process entry type} A process entry is a process object, augmented by a pointer to the next entry. We do not need specific methods, all relevant methods are inherited. On higher level, processes should be prepared as process entry objects. <>= public :: process_entry_t <>= type, extends (process_t) :: process_entry_t type(process_entry_t), pointer :: next => null () end type process_entry_t @ %def process_entry_t @ \subsection{The process stack type} For easy conversion and lookup it is useful to store the filling number in the object. The content is stored as a linked list. The [[var_list]] component stores process-specific results, so they can be retrieved as (pseudo) variables. The process stack can be linked to another one. This allows us to work with stacks of local scope. <>= public :: process_stack_t <>= type :: process_stack_t integer :: n = 0 type(process_entry_t), pointer :: first => null () type(var_list_t), pointer :: var_list => null () type(process_stack_t), pointer :: next => null () contains <> end type process_stack_t @ %def process_stack_t @ Finalize partly: deallocate the process stack and variable list entries, but keep the variable list as an empty object. This way, the variable list links are kept. <>= procedure :: clear => process_stack_clear <>= module subroutine process_stack_clear (stack) class(process_stack_t), intent(inout) :: stack end subroutine process_stack_clear <>= module subroutine process_stack_clear (stack) class(process_stack_t), intent(inout) :: stack type(process_entry_t), pointer :: process if (associated (stack%var_list)) then call stack%var_list%final () end if do while (associated (stack%first)) process => stack%first stack%first => process%next call process%final () deallocate (process) end do stack%n = 0 end subroutine process_stack_clear @ %def process_stack_clear @ Finalizer. Clear and deallocate the variable list. <>= procedure :: final => process_stack_final <>= module subroutine process_stack_final (object) class(process_stack_t), intent(inout) :: object end subroutine process_stack_final <>= module subroutine process_stack_final (object) class(process_stack_t), intent(inout) :: object call object%clear () if (associated (object%var_list)) then deallocate (object%var_list) end if end subroutine process_stack_final @ %def process_stack_final @ Output. The processes on the stack will be ordered LIFO, i.e., backwards. <>= procedure :: write => process_stack_write <>= recursive module subroutine process_stack_write (object, unit, pacify) class(process_stack_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: pacify end subroutine process_stack_write <>= recursive module subroutine process_stack_write (object, unit, pacify) class(process_stack_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: pacify type(process_entry_t), pointer :: process integer :: u u = given_output_unit (unit) call write_separator (u, 2) select case (object%n) case (0) write (u, "(1x,A)") "Process stack: [empty]" call write_separator (u, 2) case default write (u, "(1x,A)") "Process stack:" process => object%first do while (associated (process)) call process%write (.false., u, pacify = pacify) process => process%next end do end select if (associated (object%next)) then write (u, "(1x,A)") "[Processes from context environment:]" call object%next%write (u, pacify) end if end subroutine process_stack_write @ %def process_stack_write @ The variable list is printed by a separate routine, since it should be linked to the global variable list, anyway. <>= procedure :: write_var_list => process_stack_write_var_list <>= module subroutine process_stack_write_var_list (object, unit) class(process_stack_t), intent(in) :: object integer, intent(in), optional :: unit end subroutine process_stack_write_var_list <>= module subroutine process_stack_write_var_list (object, unit) class(process_stack_t), intent(in) :: object integer, intent(in), optional :: unit if (associated (object%var_list)) then call object%var_list%write (unit) end if end subroutine process_stack_write_var_list @ %def process_stack_write_var_list @ Short output. Since this is a stack, the default output ordering for each stack will be last-in, first-out. To enable first-in, first-out, which is more likely to be requested, there is an optional [[fifo]] argument. <>= procedure :: show => process_stack_show <>= recursive module subroutine process_stack_show (object, unit, fifo) class(process_stack_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: fifo end subroutine process_stack_show <>= recursive module subroutine process_stack_show (object, unit, fifo) class(process_stack_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: fifo type(process_entry_t), pointer :: process logical :: reverse integer :: u, i, j u = given_output_unit (unit) reverse = .false.; if (present (fifo)) reverse = fifo select case (object%n) case (0) case default if (.not. reverse) then process => object%first do while (associated (process)) call process%show (u, verbose=.false.) process => process%next end do else do i = 1, object%n process => object%first do j = 1, object%n - i process => process%next end do call process%show (u, verbose=.false.) end do end if end select if (associated (object%next)) call object%next%show () end subroutine process_stack_show @ %def process_stack_show @ \subsection{Link} Link the current process stack to a global one. <>= procedure :: link => process_stack_link <>= module subroutine process_stack_link (local_stack, global_stack) class(process_stack_t), intent(inout) :: local_stack type(process_stack_t), intent(in), target :: global_stack end subroutine process_stack_link <>= module subroutine process_stack_link (local_stack, global_stack) class(process_stack_t), intent(inout) :: local_stack type(process_stack_t), intent(in), target :: global_stack local_stack%next => global_stack end subroutine process_stack_link @ %def process_stack_link @ Initialize the process variable list and link the main variable list to it. <>= procedure :: init_var_list => process_stack_init_var_list <>= module subroutine process_stack_init_var_list (stack, var_list) class(process_stack_t), intent(inout) :: stack type(var_list_t), intent(inout), optional :: var_list end subroutine process_stack_init_var_list <>= module subroutine process_stack_init_var_list (stack, var_list) class(process_stack_t), intent(inout) :: stack type(var_list_t), intent(inout), optional :: var_list allocate (stack%var_list) if (present (var_list)) call var_list%link (stack%var_list) end subroutine process_stack_init_var_list @ %def process_stack_init_var_list @ Link the process variable list to a global variable list. <>= procedure :: link_var_list => process_stack_link_var_list <>= module subroutine process_stack_link_var_list (stack, var_list) class(process_stack_t), intent(inout) :: stack type(var_list_t), intent(in), target :: var_list end subroutine process_stack_link_var_list <>= module subroutine process_stack_link_var_list (stack, var_list) class(process_stack_t), intent(inout) :: stack type(var_list_t), intent(in), target :: var_list call stack%var_list%link (var_list) end subroutine process_stack_link_var_list @ %def process_stack_link_var_list @ \subsection{Push} We take a process pointer and push it onto the stack. The previous pointer is nullified. Subsequently, the process is `owned' by the stack and will be finalized when the stack is deleted. <>= procedure :: push => process_stack_push <>= module subroutine process_stack_push (stack, process) class(process_stack_t), intent(inout) :: stack type(process_entry_t), intent(inout), pointer :: process end subroutine process_stack_push <>= module subroutine process_stack_push (stack, process) class(process_stack_t), intent(inout) :: stack type(process_entry_t), intent(inout), pointer :: process process%next => stack%first stack%first => process process => null () stack%n = stack%n + 1 end subroutine process_stack_push @ %def process_stack_push @ Inverse: Remove the last process pointer in the list and return it. <>= procedure :: pop_last => process_stack_pop_last <>= module subroutine process_stack_pop_last (stack, process) class(process_stack_t), intent(inout) :: stack type(process_entry_t), intent(inout), pointer :: process end subroutine process_stack_pop_last <>= module subroutine process_stack_pop_last (stack, process) class(process_stack_t), intent(inout) :: stack type(process_entry_t), intent(inout), pointer :: process type(process_entry_t), pointer :: previous integer :: i select case (stack%n) case (:0) process => null () case (1) process => stack%first stack%first => null () stack%n = 0 case (2:) process => stack%first do i = 2, stack%n previous => process process => process%next end do previous%next => null () stack%n = stack%n - 1 end select end subroutine process_stack_pop_last @ %def process_stack_pop_last @ Initialize process variables for a given process ID, without setting values. <>= procedure :: init_result_vars => process_stack_init_result_vars <>= module subroutine process_stack_init_result_vars (stack, id) class(process_stack_t), intent(inout) :: stack type(string_t), intent(in) :: id end subroutine process_stack_init_result_vars <>= module subroutine process_stack_init_result_vars (stack, id) class(process_stack_t), intent(inout) :: stack type(string_t), intent(in) :: id call var_list_init_num_id (stack%var_list, id) call var_list_init_process_results (stack%var_list, id) end subroutine process_stack_init_result_vars @ %def process_stack_init_result_vars @ Fill process variables with values. This is executed after the integration pass. Note: We set only integral and error. With multiple MCI records possible, the results for [[n_calls]], [[chi2]] etc. are not necessarily unique. (We might set the efficiency, though.) <>= procedure :: fill_result_vars => process_stack_fill_result_vars <>= module subroutine process_stack_fill_result_vars (stack, id) class(process_stack_t), intent(inout) :: stack type(string_t), intent(in) :: id end subroutine process_stack_fill_result_vars <>= module subroutine process_stack_fill_result_vars (stack, id) class(process_stack_t), intent(inout) :: stack type(string_t), intent(in) :: id type(process_t), pointer :: process process => stack%get_process_ptr (id) if (associated (process)) then call var_list_init_num_id (stack%var_list, id, process%get_num_id ()) if (process%has_integral ()) then call var_list_init_process_results (stack%var_list, id, & integral = process%get_integral (), & error = process%get_error ()) end if else call msg_bug ("process_stack_fill_result_vars: unknown process ID") end if end subroutine process_stack_fill_result_vars @ %def process_stack_fill_result_vars @ If one of the result variables has a local image in [[var_list_local]], update the value there as well. <>= procedure :: update_result_vars => process_stack_update_result_vars <>= module subroutine process_stack_update_result_vars & (stack, id, var_list_local) class(process_stack_t), intent(inout) :: stack type(string_t), intent(in) :: id type(var_list_t), intent(inout) :: var_list_local end subroutine process_stack_update_result_vars <>= module subroutine process_stack_update_result_vars (stack, id, var_list_local) class(process_stack_t), intent(inout) :: stack type(string_t), intent(in) :: id type(var_list_t), intent(inout) :: var_list_local call update ("integral(" // id // ")") call update ("error(" // id // ")") contains subroutine update (var_name) type(string_t), intent(in) :: var_name real(default) :: value if (var_list_local%contains (var_name, follow_link = .false.)) then value = stack%var_list%get_rval (var_name) call var_list_local%set_real (var_name, value, is_known = .true.) end if end subroutine update end subroutine process_stack_update_result_vars @ %def process_stack_update_result_vars @ \subsection{Data Access} Tell if a process exists. <>= procedure :: exists => process_stack_exists <>= module function process_stack_exists (stack, id) result (flag) class(process_stack_t), intent(in) :: stack type(string_t), intent(in) :: id logical :: flag end function process_stack_exists <>= module function process_stack_exists (stack, id) result (flag) class(process_stack_t), intent(in) :: stack type(string_t), intent(in) :: id logical :: flag type(process_t), pointer :: process process => stack%get_process_ptr (id) flag = associated (process) end function process_stack_exists @ %def process_stack_exists @ Return a pointer to a process with specific ID. Look also at a linked stack, if necessary. <>= procedure :: get_process_ptr => process_stack_get_process_ptr <>= recursive module function process_stack_get_process_ptr & (stack, id) result (ptr) class(process_stack_t), intent(in) :: stack type(string_t), intent(in) :: id type(process_t), pointer :: ptr end function process_stack_get_process_ptr <>= recursive module function process_stack_get_process_ptr & (stack, id) result (ptr) class(process_stack_t), intent(in) :: stack type(string_t), intent(in) :: id type(process_t), pointer :: ptr type(process_entry_t), pointer :: entry ptr => null () entry => stack%first do while (associated (entry)) if (entry%get_id () == id) then ptr => entry%process_t return end if entry => entry%next end do if (associated (stack%next)) ptr => stack%next%get_process_ptr (id) end function process_stack_get_process_ptr @ %def process_stack_get_process_ptr @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[process_stacks_ut.f90]]>>= <> module process_stacks_ut use unit_tests use process_stacks_uti <> <> contains <> end module process_stacks_ut @ %def process_stacks_ut @ <<[[process_stacks_uti.f90]]>>= <> module process_stacks_uti <> use os_interface use sm_qcd use models use model_data use variables, only: var_list_t use process_libraries use rng_base use prc_test, only: prc_test_create_library use process, only: process_t use instances, only: process_instance_t use processes_ut, only: prepare_test_process use process_stacks use rng_base_ut, only: rng_test_factory_t <> <> contains <> end module process_stacks_uti @ %def process_stacks_uti @ API: driver for the unit tests below. <>= public :: process_stacks_test <>= subroutine process_stacks_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine process_stacks_test @ %def process_stacks_test @ \subsubsection{Write an empty process stack} The most trivial test is to write an uninitialized process stack. <>= call test (process_stacks_1, "process_stacks_1", & "write an empty process stack", & u, results) <>= public :: process_stacks_1 <>= subroutine process_stacks_1 (u) integer, intent(in) :: u type(process_stack_t) :: stack write (u, "(A)") "* Test output: process_stacks_1" write (u, "(A)") "* Purpose: display an empty process stack" write (u, "(A)") call stack%write (u) write (u, "(A)") write (u, "(A)") "* Test output end: process_stacks_1" end subroutine process_stacks_1 @ %def process_stacks_1 @ \subsubsection{Fill a process stack} Fill a process stack with two (identical) processes. <>= call test (process_stacks_2, "process_stacks_2", & "fill a process stack", & u, results) <>= public :: process_stacks_2 <>= subroutine process_stacks_2 (u) integer, intent(in) :: u type(process_stack_t) :: stack type(process_library_t), target :: lib type(string_t) :: libname type(string_t) :: procname type(os_data_t) :: os_data type(model_t), target :: model type(var_list_t) :: var_list type(process_entry_t), pointer :: process => null () write (u, "(A)") "* Test output: process_stacks_2" write (u, "(A)") "* Purpose: fill a process stack" write (u, "(A)") write (u, "(A)") "* Build, initialize and store two test processes" write (u, "(A)") libname = "process_stacks2" procname = libname call os_data%init () call prc_test_create_library (libname, lib) call model%init_test () call var_list%append_string (var_str ("$run_id")) call var_list%append_log (var_str ("?alphas_is_fixed"), .true.) call var_list%append_int (var_str ("seed"), 0) allocate (process) call var_list%set_string & (var_str ("$run_id"), var_str ("run1"), is_known=.true.) call process%init (procname, lib, os_data, model, var_list) call stack%push (process) allocate (process) call var_list%set_string & (var_str ("$run_id"), var_str ("run2"), is_known=.true.) call process%init (procname, lib, os_data, model, var_list) call stack%push (process) call stack%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call stack%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: process_stacks_2" end subroutine process_stacks_2 @ %def process_stacks_2 @ \subsubsection{Fill a process stack} Fill a process stack with two (identical) processes. <>= call test (process_stacks_3, "process_stacks_3", & "process variables", & u, results) <>= public :: process_stacks_3 <>= subroutine process_stacks_3 (u) integer, intent(in) :: u type(process_stack_t) :: stack type(model_t), target :: model type(string_t) :: procname type(process_entry_t), pointer :: process => null () type(process_instance_t), target :: process_instance write (u, "(A)") "* Test output: process_stacks_3" write (u, "(A)") "* Purpose: setup process variables" write (u, "(A)") write (u, "(A)") "* Initialize process variables" write (u, "(A)") procname = "processes_test" call model%init_test () write (u, "(A)") "* Initialize process variables" write (u, "(A)") call stack%init_var_list () call stack%init_result_vars (procname) call stack%write_var_list (u) write (u, "(A)") write (u, "(A)") "* Build and integrate a test process" write (u, "(A)") allocate (process) call prepare_test_process (process%process_t, process_instance, model) call process_instance%integrate (1, 1, 1000) call process_instance%final () call process%final_integration (1) call stack%push (process) write (u, "(A)") "* Fill process variables" write (u, "(A)") call stack%fill_result_vars (procname) call stack%write_var_list (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call stack%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: process_stacks_3" end subroutine process_stacks_3 @ %def process_stacks_3 @ \subsubsection{Linked a process stack} Fill two process stack, linked to each other. <>= call test (process_stacks_4, "process_stacks_4", & "linked stacks", & u, results) <>= public :: process_stacks_4 <>= subroutine process_stacks_4 (u) integer, intent(in) :: u type(process_library_t), target :: lib type(process_stack_t), target :: stack1, stack2 type(model_t), target :: model type(string_t) :: libname type(string_t) :: procname1, procname2 type(os_data_t) :: os_data type(process_entry_t), pointer :: process => null () write (u, "(A)") "* Test output: process_stacks_4" write (u, "(A)") "* Purpose: link process stacks" write (u, "(A)") write (u, "(A)") "* Initialize process variables" write (u, "(A)") libname = "process_stacks_4_lib" procname1 = "process_stacks_4a" procname2 = "process_stacks_4b" call os_data%init () write (u, "(A)") "* Initialize first process" write (u, "(A)") call prc_test_create_library (procname1, lib) call model%init_test () allocate (process) call process%init (procname1, lib, os_data, model) call stack1%push (process) write (u, "(A)") "* Initialize second process" write (u, "(A)") call stack2%link (stack1) call prc_test_create_library (procname2, lib) allocate (process) call process%init (procname2, lib, os_data, model) call stack2%push (process) write (u, "(A)") "* Show linked stacks" write (u, "(A)") call stack2%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call stack2%final () call stack1%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: process_stacks_4" end subroutine process_stacks_4 @ %def process_stacks_4 @ Index: trunk/src/fks/fks.nw =================================================================== --- trunk/src/fks/fks.nw (revision 8817) +++ trunk/src/fks/fks.nw (revision 8818) @@ -1,12030 +1,12036 @@ % -*- ess-noweb-default-code-mode: f90-mode; noweb-default-code-mode: f90-mode; -*- % WHIZARD code as NOWEB source: matrix elements and process libraries %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \chapter{FKS Subtraction Scheme} \includemodulegraph{fks} The code in this chapter implements the FKS subtraction scheme for use with \whizard. These are the modules: \begin{description} \item[fks\_regions] Given a process definition, identify singular regions in the associated phase space. \item[virtual] Handle the virtual correction matrix element. \item[real\_subtraction] Handle the real-subtraction matrix element. \item[nlo\_data] Manage the subtraction objects. \item[dglap\_remnant] Handle the DGLAP Remnant matrix element. \end{description} This chapter deals with next-to-leading order contributions to cross sections. Basically, there are three major issues to be adressed: The creation of the $N+1$-particle flavor structure, the construction of the $N+1$-particle phase space and the actual calculation of the real- and virtual-subtracted matrix elements. The first is dealt with using the [[auto_components]] class, and it will be shown that the second and third issue are connected in FKS subtraction. \section{Brief outline of FKS subtraction} {\em In the current state, this discussion is only concerned with lepton collisions. For hadron collisions, renormalization of parton distributions has to be taken into account. Further, for QCD corrections, initial-state radiation is necessarily present.} The aim is to calculate the next-to-leading order cross section according to \begin{equation*} d\sigma_{\rm{NLO}} = \mathcal{B} + \mathcal{V} + \mathcal{R}d\Phi_{\rm{rad}}. \end{equation*} Analytically, the divergences, in terms of poles in the complex quantity $\varepsilon = 2-d/2$, cancel. However, this is in general only valid in an arbitrary, complex number of dimensions. This is, roughly, the content of the KLN-theorem. \whizard, as any other numerical program, is confined to four dimensions. We will assume that the KLN-theorem is valid and that there exist subtraction terms $\mathcal{C}$ such that \begin{equation*} d\sigma_{\rm{NLO}} = \mathcal{B} + \underbrace{\mathcal{V} + \mathcal{C}}_{\text{finite}} + \underbrace{\mathcal{R} - \mathcal{C}}_{\text{finite}}, \end{equation*} i.e. the subtraction terms correspond to the divergent limits of the real and virtual matrix element. Because $\mathcal{C}$ subtracts the divergences of $\mathcal{R}$ as well as those of $\mathcal{V}$, it suffices to consider one of them, so we focus on $\mathcal{R}$. For this purpose, $\mathcal{R}$ is rewritten as \begin{equation*} \mathcal{R} = \frac{1}{\xi^2}\frac{1}{1-y} \left(\xi^2 (1-y)\mathcal{R}\right) = \frac{1}{\xi^2}\frac{1}{1-y}\tilde{\mathcal{R}}, \end{equation*} with $\xi = \left(2k_{\rm{rad}}^0\right)/\sqrt{s}$ and $y = \cos\theta$, where $k_{\rm{rad}}^0$ denotes the energy of the radiated parton and $\theta$ is the angle between emitter and radiated parton. $\tilde{\mathcal{R}}$ is finite, therefore the whole singularity structure is contained in the prefactor $\xi^{-2}(1-y)^{-1}$. Combined with the $d$-dimensional phase space element, \begin{equation*} \frac{d^{d-1}k}{2k^0(2\pi)^{d-1}} = \frac{s^{1-\varepsilon}}{(4\pi)^{d-1}}\xi^{1-2\varepsilon}\left(1-y^2\right)^{-\varepsilon} d\xi dy d\Omega^{d-2}, \end{equation*} this yields \begin{equation*} d\Phi_{\rm{rad}} \mathcal{R} = dy (1-y)^{-1-\varepsilon} d\xi \xi^{-1-2\varepsilon} \tilde{R}. \end{equation*} This can further be rewritten in terms of plus-distributions, \begin{align*} \xi^{-1-2\varepsilon} &= -\frac{1}{2\varepsilon}\delta(\xi) + \left(\frac{1}{\xi}\right)_+ - 2\varepsilon\left(\frac{\log\xi}{\xi}\right)_+ + \mathcal{O}(\varepsilon^2),\\ (1-y)^{-1-\varepsilon} &= -\frac{2^{-\varepsilon}}{\varepsilon} \delta(1-y) + \left(\frac{1}{1-y}\right)_+ - \varepsilon \left(\frac{1}{1-y}\right)_+\log(1-y) + \mathcal{O}(\varepsilon^2), \end{align*} (imagine that all this is written inside of integrals, which are spared for ease of notation) such that \begin{align*} d\Phi_{\rm{rad}} \mathcal{R} &= -\frac{1}{2\varepsilon} dy (1-y)^{-1-\varepsilon}\tilde{R} (0,y) - d\xi\left[\frac{2^{-\varepsilon}}{\varepsilon}\left(\frac{1}{\xi}\right)_+ - 2\left(\frac{\log\xi}{\xi}\right)_+\right] \tilde{R}(\xi,1) \\ &+ dy d\xi \left(\frac{1}{\xi}\right)_+ \left(\frac{1}{1-y}\right)_+ \tilde{R}(\xi, y) + \mathcal{O}(\varepsilon).\\ \end{align*} The summand in the second line is of order $\mathcal{O}(1)$ and is the only one to reproduce $\mathcal{R}(\xi,y)$. It thus constitutes the sum of the real matrix element and the corresponding counterterms. The first summand consequently consists of the subtraction terms to the virtual matrix elements. Above formula thus allows to calculate all quantities to render the matrix elements finite. \clearpage %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Identifying singular regions} In the FKS subtraction scheme, the phase space is decomposed into disjoint singular regions, such that \begin{equation} \label{eq:S_complete} \sum_i \mathcal{S}_i + \sum_{ij}\mathcal{S}_{ij} = 1. \end{equation} The quantities $\mathcal{S}_i$ and $\mathcal{S}_{ij}$ are functions of phase space corresponding to a pair of particles indices which can make up a divergent phase space region. We call such an index pair a fundamental tuple. For example, the process $e^+ \, e^- \rightarrow u \, \bar{u} \, g$ has two singular regions, $(3,5)$ and $(4,5)$, indicating that the gluon can be soft or collinear with respect to either the quark or the anti-quark. Therefore, the functions $S_{ij}$ have to be chosen in such a way that their contribution makes up most of \eqref{eq:S_complete} in phase-space configurations where (final-state) particle $j$ is collinear to particle $i$ or/and particle $j$ is soft. The functions $S_i$ is the corresponding quantity for initial-state divergences. As a singular region we understand the collection of real flavor structures associated with an emitter and a list of all possible fundamental tuples. As an example, consider the process $e^+ \, e^- \rightarrow u \, \bar{u} \, g$. At next-to-leading order, processes with an additionally radiated particle have to be considered. In this case, these are $e^+ \, e^- \rightarrow u \, \bar{u}, \, g \, g$, and $e^+ \, e^- \rightarrow u \, \bar{u} \, u \, \bar{u}$ (or the same process with any other quark). Table \ref{table:singular regions} sums up all possible singular regions for this problem. \begin{table} \begin{tabular}{|c|c|c|c|} \hline \texttt{alr} & \texttt{flst\_alr} & \texttt{emitter} & \texttt{ftuple\_list}\\ \hline 1 & [-11,11,2,-2,21,21] & 3 & {(3,5), (3,6), (4,5), (4,6), (5,6)} \\ \hline 2 & [-11,11,2,-2,21,21] & 4 & {(3,5), (3,6), (4,5), (4,6), (5,6)} \\ \hline 3 & [-11,11,2,-2,21,21] & 5 & {(3,5), (3,6), (4,5), (4,6), (5,6)} \\ \hline 4 & [-11,11,2,-2,2,-2] & 5 & {(3,4), (3,6), (4,5), (5,6)} \\ \hline \end{tabular} \caption{List of singular regions. The particles are represented by their PDG codes. The third column contains the emitter for the specific singular region. For the process involving an additional gluon, the gluon can either be emitted from one of the quarks or from the first gluon. Each emitter yields the same list of fundamental tuples, five in total. The last singular region corresponds to the process where the gluon splits up into two quarks. As the matrix element for this process has no information on which quarks originate from a gluon splitting, there are ftuples for all the quark pairs and not just those involving the emitter.} \label{table:singular regions} \end{table} \\ \begin{table} \begin{tabular}{|c|c|c|c|} \hline \texttt{alr} & \texttt{ftuple} & \texttt{emitter} & \texttt{flst\_alr} \\ \hline 1 & $(3,5)$ & 5 & [-11,11,-2,21,2,21] \\ \hline 2 & $(4,5)$ & 5 & [-11,11,2,21,-2,21] \\ \hline 3 & $(3,6)$ & 5 & [-11,11,-2,21,2,21] \\ \hline 4 & $(4,6)$ & 5 & [-11,11,2,21,-2,21] \\ \hline 5 & $(5,6)$ & 5 & [-11,11,2,-2,21,21] \\ \hline 6 & $(5,6)$ & 5 & [-11,11,2,-2,2,-2] \\ \hline \end{tabular} \caption{Initial list of singular regions} \label{table:ftuples and flavors} \end{table} Thus, during the preparation of a NLO-calculation, the possible singular regions have to be identified. [[fks_regions.f90]] deals with this issue. \clearpage %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{FKS Regions} <<[[fks_regions.f90]]>>= <> module fks_regions <> <> use diagnostics use os_interface use constants use process_constants use lorentz use models use resonances, only: resonance_contributors_t, resonance_history_t use phs_fks, only: phs_identifier_t, check_for_phs_identifier use nlo_data <> <> <> <> <> interface <> end interface contains <> end module fks_regions @ %def fks_regions @ <<[[fks_regions_sub.f90]]>>= <> submodule (fks_regions) fks_regions_s <> use format_utils, only: write_separator use numeric_utils use string_utils, only: str use io_units use permutations use physics_defs use flavors use pdg_arrays implicit none contains <> end submodule fks_regions_s @ %def fks_regions_s @ There are three fundamental splitting types: $q \rightarrow qg$, $g \rightarrow gg$ and $g \rightarrow qq$ for FSR and additionally $q \rightarrow gq$ for ISR which is different from $q \rightarrow qg$ by which particle enters the hard process. <>= integer, parameter :: UNDEFINED_SPLITTING = 0 integer, parameter :: F_TO_FV = 1 integer, parameter :: V_TO_VV = 2 integer, parameter :: V_TO_FF = 3 integer, parameter :: F_TO_VF = 4 @ @ We group the indices of the emitting and the radiated particle in the [[ftuple]]-object. <>= public :: ftuple_t <>= type :: ftuple_t integer, dimension(2) :: ireg = [-1,-1] integer :: i_res = 0 integer :: splitting_type logical :: pseudo_isr = .false. logical :: qcd_split = .false. contains <> end type ftuple_t @ %def ftuple_t @ <>= interface assignment(=) module procedure ftuple_assign end interface interface operator(==) module procedure ftuple_equal end interface interface operator(>) module procedure ftuple_greater end interface interface operator(<) module procedure ftuple_less end interface <>= pure module subroutine ftuple_assign (ftuple_out, ftuple_in) type(ftuple_t), intent(out) :: ftuple_out type(ftuple_t), intent(in) :: ftuple_in end subroutine ftuple_assign <>= pure module subroutine ftuple_assign (ftuple_out, ftuple_in) type(ftuple_t), intent(out) :: ftuple_out type(ftuple_t), intent(in) :: ftuple_in ftuple_out%ireg = ftuple_in%ireg ftuple_out%i_res = ftuple_in%i_res ftuple_out%splitting_type = ftuple_in%splitting_type ftuple_out%pseudo_isr = ftuple_in%pseudo_isr ftuple_out%qcd_split = ftuple_in%qcd_split end subroutine ftuple_assign @ %def ftuple_assign @ <>= elemental module function ftuple_equal (f1, f2) result (value) logical :: value type(ftuple_t), intent(in) :: f1, f2 end function ftuple_equal <>= elemental module function ftuple_equal (f1, f2) result (value) logical :: value type(ftuple_t), intent(in) :: f1, f2 value = all (f1%ireg == f2%ireg) .and. f1%i_res == f2%i_res & .and. f1%splitting_type == f2%splitting_type & .and. (f1%pseudo_isr .eqv. f2%pseudo_isr) & .and. (f1%qcd_split .eqv. f2%qcd_split) end function ftuple_equal @ %def ftuple_equal @ <>= elemental function ftuple_equal_ireg (f1, f2) result (value) logical :: value type(ftuple_t), intent(in) :: f1, f2 value = all (f1%ireg == f2%ireg) end function ftuple_equal_ireg @ %def ftuple_equal_ireg @ <>= elemental module function ftuple_greater (f1, f2) result (greater) logical :: greater type(ftuple_t), intent(in) :: f1, f2 end function ftuple_greater <>= elemental module function ftuple_greater (f1, f2) result (greater) logical :: greater type(ftuple_t), intent(in) :: f1, f2 if (f1%ireg(1) == f2%ireg(1)) then greater = f1%ireg(2) > f2%ireg(2) else greater = f1%ireg(1) > f2%ireg(1) end if end function ftuple_greater @ %def ftuple_greater @ <>= elemental module function ftuple_less (f1, f2) result (less) logical :: less type(ftuple_t), intent(in) :: f1, f2 end function ftuple_less <>= elemental module function ftuple_less (f1, f2) result (less) logical :: less type(ftuple_t), intent(in) :: f1, f2 if (f1%ireg(1) == f2%ireg(1)) then less = f1%ireg(2) < f2%ireg(2) else less = f1%ireg(1) < f2%ireg(1) end if end function ftuple_less @ %def ftuple_less <>= subroutine ftuple_sort_array (ftuple_array, equivalences) type(ftuple_t), intent(inout), dimension(:), allocatable :: ftuple_array logical, intent(inout), dimension(:,:), allocatable :: equivalences type(ftuple_t) :: ftuple_tmp logical, dimension(:), allocatable :: eq_tmp integer :: i1, i2, n n = size (ftuple_array) allocate (eq_tmp (n)) do i1 = 2, n i2 = i1 do while (ftuple_array(i2 - 1) > ftuple_array(i2)) ftuple_tmp = ftuple_array(i2 - 1) eq_tmp = equivalences(i2, :) ftuple_array(i2 - 1) = ftuple_array(i2) ftuple_array(i2) = ftuple_tmp equivalences(i2 - 1, :) = equivalences(i2, :) equivalences(i2, :) = eq_tmp i2 = i2 - 1 if (i2 == 1) exit end do end do end subroutine ftuple_sort_array @ %def ftuple_sort_array @ <>= procedure :: write => ftuple_write <>= module subroutine ftuple_write (ftuple, unit, newline) class(ftuple_t), intent(in) :: ftuple integer, intent(in), optional :: unit logical, intent(in), optional :: newline end subroutine ftuple_write <>= module subroutine ftuple_write (ftuple, unit, newline) class(ftuple_t), intent(in) :: ftuple integer, intent(in), optional :: unit logical, intent(in), optional :: newline integer :: u logical :: nl u = given_output_unit (unit); if (u < 0) return nl = .true.; if (present(newline)) nl = newline if (all (ftuple%ireg > -1)) then if (ftuple%i_res > 0) then if (nl) then write (u, "(A1,I1,A1,I1,A1,I1,A1)") & '(', ftuple%ireg(1), ',', ftuple%ireg(2), ';', ftuple%i_res, ')' else write (u, "(A1,I1,A1,I1,A1,I1,A1)", advance = "no") & '(', ftuple%ireg(1), ',', ftuple%ireg(2), ';', ftuple%i_res, ')' end if else if (nl) then write (u, "(A1,I1,A1,I1,A1)") & '(', ftuple%ireg(1), ',', ftuple%ireg(2), ')' else write (u, "(A1,I1,A1,I1,A1)", advance = "no") & '(', ftuple%ireg(1), ',', ftuple%ireg(2), ')' end if end if else write (u, "(A)") "(Empty)" end if end subroutine ftuple_write @ %def ftuple_write @ <>= function ftuple_string (ftuples, latex) type(string_t) :: ftuple_string type(ftuple_t), intent(in), dimension(:) :: ftuples logical, intent(in) :: latex integer :: i, nreg if (latex) then ftuple_string = var_str ("$\left\{") else ftuple_string = var_str ("{") end if nreg = size(ftuples) do i = 1, nreg if (ftuples(i)%i_res == 0) then ftuple_string = ftuple_string // var_str ("(") // & str (ftuples(i)%ireg(1)) // var_str (",") // & str (ftuples(i)%ireg(2)) // var_str (")") else ftuple_string = ftuple_string // var_str ("(") // & str (ftuples(i)%ireg(1)) // var_str (",") // & str (ftuples(i)%ireg(2)) // var_str (";") // & str (ftuples(i)%i_res) // var_str (")") end if if (ftuples(i)%pseudo_isr) ftuple_string = ftuple_string // var_str ("*") if (i < nreg) ftuple_string = ftuple_string // var_str (",") end do if (latex) then ftuple_string = ftuple_string // var_str ("\right\}$") else ftuple_string = ftuple_string // var_str ("}") end if end function ftuple_string @ %def ftuple_string @ <>= procedure :: get => ftuple_get <>= module subroutine ftuple_get (ftuple, pos1, pos2) class(ftuple_t), intent(in) :: ftuple integer, intent(out) :: pos1, pos2 end subroutine ftuple_get <>= module subroutine ftuple_get (ftuple, pos1, pos2) class(ftuple_t), intent(in) :: ftuple integer, intent(out) :: pos1, pos2 pos1 = ftuple%ireg(1) pos2 = ftuple%ireg(2) end subroutine ftuple_get @ %def ftuple_get @ <>= procedure :: set => ftuple_set <>= module subroutine ftuple_set (ftuple, pos1, pos2) class(ftuple_t), intent(inout) :: ftuple integer, intent(in) :: pos1, pos2 end subroutine ftuple_set <>= module subroutine ftuple_set (ftuple, pos1, pos2) class(ftuple_t), intent(inout) :: ftuple integer, intent(in) :: pos1, pos2 ftuple%ireg(1) = pos1 ftuple%ireg(2) = pos2 end subroutine ftuple_set @ %def ftuple_set @ Determines the splitting type for FSR. There are three different types of splittings relevant here: $g \to gg$ tagged [[V_TO_VV]], $g \to qq$ tagged [[V_TO_FF]] and $q \to qg$ tagged [[F_TO_FV]]. For FSR, there is no need to differentiate between $q \to qg$ and $q \to gq$ splittings. <>= procedure :: determine_splitting_type_fsr => & ftuple_determine_splitting_type_fsr <>= module subroutine ftuple_determine_splitting_type_fsr (ftuple, flv, i, j) class(ftuple_t), intent(inout) :: ftuple type(flv_structure_t), intent(in) :: flv integer, intent(in) :: i, j end subroutine ftuple_determine_splitting_type_fsr <>= module subroutine ftuple_determine_splitting_type_fsr (ftuple, flv, i, j) class(ftuple_t), intent(inout) :: ftuple type(flv_structure_t), intent(in) :: flv integer, intent(in) :: i, j associate (flst => flv%flst) if (is_vector (flst(i)) .and. is_vector (flst(j))) then ftuple%splitting_type = V_TO_VV else if (flst(i)+flst(j) == 0 & .and. is_fermion (flst(i))) then ftuple%splitting_type = V_TO_FF else if (is_fermion(flst(i)) .and. is_massless_vector (flst(j)) & .or. is_fermion(flst(j)) .and. is_massless_vector (flst(i))) then ftuple%splitting_type = F_TO_FV else ftuple%splitting_type = UNDEFINED_SPLITTING end if end associate end subroutine ftuple_determine_splitting_type_fsr @ %def ftuple_determine_splitting_type_fsr @ Determines the splitting type for ISR. There are four different types of splittings relevant here: $g \to gg$ tagged [[V_TO_VV]], $g \to qq$ tagged [[V_TO_FF]], $q \to qg$ tagged [[F_TO_FV]] and $q \to gq$ tagged [[F_TO_VF]]. The latter two need to be considered separately for ISR as they differ with respect to which particle enters the hard process. A splitting [[F_TO_FV]] may lead to soft divergences while [[F_TO_VF]] does not. We also want to emphasize that the splitting type naming convention for ISR names the splittings considering backwards evolution. So in the splitting [[V_TO_FF]], it is the \textit{gluon} that enteres the hard process. Special treatment here is required if emitter $0$ is assigned. This is the case only when a gluon was radiated from any of the IS particles. In this case, both splittings are soft divergent so we can equivalently choose $1$ or $2$ as the emitter here even if both have different flavors. <>= procedure :: determine_splitting_type_isr => & ftuple_determine_splitting_type_isr <>= module subroutine ftuple_determine_splitting_type_isr (ftuple, flv, i, j) class(ftuple_t), intent(inout) :: ftuple type(flv_structure_t), intent(in) :: flv integer, intent(in) :: i, j end subroutine ftuple_determine_splitting_type_isr <>= module subroutine ftuple_determine_splitting_type_isr (ftuple, flv, i, j) class(ftuple_t), intent(inout) :: ftuple type(flv_structure_t), intent(in) :: flv integer, intent(in) :: i, j integer :: em em = i; if (i == 0) em = 1 associate (flst => flv%flst) if (is_vector (flst(em)) .and. is_vector (flst(j))) then ftuple%splitting_type = V_TO_VV else if (is_massless_vector(flst(em)) .and. is_fermion(flst(j))) then ftuple%splitting_type = F_TO_VF else if (is_fermion(flst(em)) .and. is_massless_vector(flst(j))) then ftuple%splitting_type = F_TO_FV else if (is_fermion(flst(em)) .and. is_fermion(flst(j))) then ftuple%splitting_type = V_TO_FF else ftuple%splitting_type = UNDEFINED_SPLITTING end if end associate end subroutine ftuple_determine_splitting_type_isr @ %def ftuple_determine_splitting_type_isr <>= procedure :: determine_sub_correction_type => & ftuple_determine_sub_correction_type <>= module subroutine ftuple_determine_sub_correction_type & (ftuple, flv_born, flv_real, i, j) class(ftuple_t), intent(inout) :: ftuple type(flv_structure_t), intent(in) :: flv_born, flv_real integer, intent(in) :: i, j end subroutine ftuple_determine_sub_correction_type <>= module subroutine ftuple_determine_sub_correction_type & (ftuple, flv_born, flv_real, i, j) class(ftuple_t), intent(inout) :: ftuple type(flv_structure_t), intent(in) :: flv_born, flv_real integer, intent(in) :: i, j type(flv_structure_t) :: flv_test_qcd integer :: em em = i; if (i == 0) em = 1 select case (ftuple%splitting_type) case (V_TO_VV) ftuple%qcd_split = is_gluon (flv_real%flst(em)) .and. is_gluon (flv_real%flst(j)) case (F_TO_VF) ftuple%qcd_split = is_gluon (flv_real%flst(em)) case (F_TO_FV) if (i == 0) then ftuple%qcd_split = is_gluon (flv_real%flst(j)) else ftuple%qcd_split = is_gluon (flv_real%flst(i)) .or. is_gluon (flv_real%flst(j)) end if case (V_TO_FF) if (any ([i, j] <= flv_real%n_in)) then flv_test_qcd = flv_real%insert_particle_isr (i, j, GLUON) else flv_test_qcd = flv_real%insert_particle_fsr (i, j, GLUON) end if ftuple%qcd_split = flv_test_qcd .equiv. flv_born case (UNDEFINED_SPLITTING) ftuple%qcd_split = .false. end select end subroutine ftuple_determine_sub_correction_type @ %def ftuple_determine_sub_correction_type @ Two debug functions to check the consistency of [[ftuples]] <>= procedure :: has_negative_elements => ftuple_has_negative_elements procedure :: has_identical_elements => ftuple_has_identical_elements <>= elemental module function ftuple_has_negative_elements & (ftuple) result (value) logical :: value class(ftuple_t), intent(in) :: ftuple end function ftuple_has_negative_elements elemental module function ftuple_has_identical_elements & (ftuple) result (value) logical :: value class(ftuple_t), intent(in) :: ftuple end function ftuple_has_identical_elements <>= elemental module function ftuple_has_negative_elements & (ftuple) result (value) logical :: value class(ftuple_t), intent(in) :: ftuple value = any (ftuple%ireg < 0) end function ftuple_has_negative_elements elemental module function ftuple_has_identical_elements & (ftuple) result (value) logical :: value class(ftuple_t), intent(in) :: ftuple value = ftuple%ireg(1) == ftuple%ireg(2) end function ftuple_has_identical_elements @ %def ftuple_has_negative_elements, ftuple_has_identical_elements @ Each singular region can have a different number of emitter-radiation pairs. This is coped with using the linked list [[ftuple_list]]. <>= type :: ftuple_list_t integer :: index = 0 type(ftuple_t) :: ftuple type(ftuple_list_t), pointer :: next => null () type(ftuple_list_t), pointer :: prev => null () type(ftuple_list_t), pointer :: equiv => null () contains <> end type ftuple_list_t @ %def ftuple_list_t @ <>= procedure :: write => ftuple_list_write <>= module subroutine ftuple_list_write (list, unit, verbose) class(ftuple_list_t), intent(in), target :: list integer, intent(in), optional :: unit logical, intent(in), optional :: verbose end subroutine ftuple_list_write <>= module subroutine ftuple_list_write (list, unit, verbose) class(ftuple_list_t), intent(in), target :: list integer, intent(in), optional :: unit logical, intent(in), optional :: verbose type(ftuple_list_t), pointer :: current logical :: verb integer :: u u = given_output_unit (unit); if (u < 0) return verb = .false.; if (present (verbose)) verb = verbose select type (list) type is (ftuple_list_t) current => list do call current%ftuple%write (unit = u, newline = .false.) if (verb .and. associated (current%equiv)) & write (u, '(A)', advance = "no") "'" if (associated (current%next)) then current => current%next else exit end if end do write (u, *) "" end select end subroutine ftuple_list_write @ %def ftuple_list_write @ <>= procedure :: append => ftuple_list_append <>= module subroutine ftuple_list_append (list, ftuple) class(ftuple_list_t), intent(inout), target :: list type(ftuple_t), intent(in) :: ftuple end subroutine ftuple_list_append <>= module subroutine ftuple_list_append (list, ftuple) class(ftuple_list_t), intent(inout), target :: list type(ftuple_t), intent(in) :: ftuple type(ftuple_list_t), pointer :: current select type (list) type is (ftuple_list_t) if (list%index == 0) then nullify (list%next) list%index = 1 list%ftuple = ftuple else current => list do if (associated (current%next)) then current => current%next else allocate (current%next) nullify (current%next%next) nullify (current%next%equiv) current%next%prev => current current%next%index = current%index + 1 current%next%ftuple = ftuple exit end if end do end if end select end subroutine ftuple_list_append @ %def ftuple_list_append @ <>= procedure :: get_n_tuples => ftuple_list_get_n_tuples <>= impure elemental module function ftuple_list_get_n_tuples & (list) result(n_tuples) integer :: n_tuples class(ftuple_list_t), intent(in), target :: list end function ftuple_list_get_n_tuples <>= impure elemental module function ftuple_list_get_n_tuples & (list) result(n_tuples) integer :: n_tuples class(ftuple_list_t), intent(in), target :: list type(ftuple_list_t), pointer :: current n_tuples = 0 select type (list) type is (ftuple_list_t) current => list if (current%index > 0) then n_tuples = 1 do if (associated (current%next)) then current => current%next n_tuples = n_tuples + 1 else exit end if end do end if end select end function ftuple_list_get_n_tuples @ %def ftuple_list_get_n_tuples @ <>= procedure :: get_entry => ftuple_list_get_entry <>= module function ftuple_list_get_entry (list, index) result (entry) type(ftuple_list_t), pointer :: entry class(ftuple_list_t), intent(in), target :: list integer, intent(in) :: index end function ftuple_list_get_entry <>= module function ftuple_list_get_entry (list, index) result (entry) type(ftuple_list_t), pointer :: entry class(ftuple_list_t), intent(in), target :: list integer, intent(in) :: index type(ftuple_list_t), pointer :: current integer :: i entry => null() select type (list) type is (ftuple_list_t) current => list if (index == 1) then entry => current else do i = 1, index - 1 current => current%next end do entry => current end if end select end function ftuple_list_get_entry @ %def ftuple_list_get_entry @ <>= procedure :: get_ftuple => ftuple_list_get_ftuple <>= module function ftuple_list_get_ftuple (list, index) result (ftuple) type(ftuple_t) :: ftuple class(ftuple_list_t), intent(in), target :: list integer, intent(in) :: index end function ftuple_list_get_ftuple <>= module function ftuple_list_get_ftuple (list, index) result (ftuple) type(ftuple_t) :: ftuple class(ftuple_list_t), intent(in), target :: list integer, intent(in) :: index type(ftuple_list_t), pointer :: entry entry => list%get_entry (index) ftuple = entry%ftuple end function ftuple_list_get_ftuple @ %def ftuple_list_get_ftuple @ <>= procedure :: set_equiv => ftuple_list_set_equiv <>= module subroutine ftuple_list_set_equiv (list, i1, i2) class(ftuple_list_t), intent(in) :: list integer, intent(in) :: i1, i2 end subroutine ftuple_list_set_equiv <>= module subroutine ftuple_list_set_equiv (list, i1, i2) class(ftuple_list_t), intent(in) :: list integer, intent(in) :: i1, i2 type(ftuple_list_t), pointer :: list1, list2 => null () select type (list) type is (ftuple_list_t) if (list%get_ftuple (i1) > list%get_ftuple (i2)) then list1 => list%get_entry (i2) list2 => list%get_entry (i1) else list1 => list%get_entry (i1) list2 => list%get_entry (i2) end if do if (associated (list1%equiv)) then list1 => list1%equiv else exit end if end do list1%equiv => list2 end select end subroutine ftuple_list_set_equiv @ %def ftuple_list_set_equiv @ <>= procedure :: check_equiv => ftuple_list_check_equiv <>= module function ftuple_list_check_equiv(list, i1, i2) result (eq) class(ftuple_list_t), intent(in) :: list integer, intent(in) :: i1, i2 logical :: eq end function ftuple_list_check_equiv <>= module function ftuple_list_check_equiv(list, i1, i2) result (eq) class(ftuple_list_t), intent(in) :: list integer, intent(in) :: i1, i2 logical :: eq type(ftuple_list_t), pointer :: current eq = .false. select type (list) type is (ftuple_list_t) current => list%get_entry (i1) do if (associated (current%equiv)) then current => current%equiv if (current%index == i2) then eq = .true. exit end if else exit end if end do end select end function ftuple_list_check_equiv @ %def ftuple_list_sort @ <>= procedure :: to_array => ftuple_list_to_array <>= module subroutine ftuple_list_to_array & (ftuple_list, ftuple_array, equivalences, ordered) class(ftuple_list_t), intent(in), target :: ftuple_list type(ftuple_t), intent(out), dimension(:), allocatable :: ftuple_array logical, intent(out), dimension(:,:), allocatable :: equivalences logical, intent(in) :: ordered end subroutine ftuple_list_to_array <>= module subroutine ftuple_list_to_array & (ftuple_list, ftuple_array, equivalences, ordered) class(ftuple_list_t), intent(in), target :: ftuple_list type(ftuple_t), intent(out), dimension(:), allocatable :: ftuple_array logical, intent(out), dimension(:,:), allocatable :: equivalences logical, intent(in) :: ordered integer :: i_tuple, n type(ftuple_list_t), pointer :: current => null () integer :: i1, i2 type(ftuple_t) :: ftuple_tmp logical, dimension(:), allocatable :: eq_tmp n = ftuple_list%get_n_tuples () allocate (ftuple_array (n), equivalences (n, n)) equivalences = .false. select type (ftuple_list) type is (ftuple_list_t) current => ftuple_list i_tuple = 1 do ftuple_array(i_tuple) = current%ftuple if (associated (current%equiv)) then i1 = current%index i2 = current%equiv%index equivalences (i1, i2) = .true. end if if (associated (current%next)) then current => current%next i_tuple = i_tuple + 1 else exit end if end do end select if (ordered) call ftuple_sort_array (ftuple_array, equivalences) end subroutine ftuple_list_to_array @ %def ftuple_list_to_array @ <>= subroutine print_equivalence_matrix (ftuple_array, equivalences) type(ftuple_t), intent(in), dimension(:) :: ftuple_array logical, intent(in), dimension(:,:) :: equivalences integer :: i, i1, i2 print *, 'Equivalence matrix: ' do i = 1, size (ftuple_array) call ftuple_array(i)%get(i1,i2) print *, 'i: ', i, '(', i1, i2, '): ', equivalences(i,:) end do end subroutine print_equivalence_matrix @ %def print_equivalence_matrix @ Class for working with the flavor specification arrays. <>= public :: flv_structure_t <>= type :: flv_structure_t integer, dimension(:), allocatable :: flst integer, dimension(:), allocatable :: tag integer :: nlegs = 0 integer :: n_in = 0 logical, dimension(:), allocatable :: massive logical, dimension(:), allocatable :: colored real(default), dimension(:), allocatable :: charge real(default) :: prt_symm_fs = 1._default integer :: eqv_index = 0 contains <> end type flv_structure_t @ %def flv_structure_t @ Returns \texttt{true} if the two particles at position \texttt{i} and \texttt{j} in the flavor array can originate from the same splitting. For this purpose, the function first checks whether the splitting is allowed at all. If this is the case, the emitter is removed from the flavor array. If the resulting array is equivalent to the Born flavor structure \texttt{flv\_born}, the pair is accepted as a valid splitting. We first check whether the splitting is possible. The array [[flv_orig]] contains all particles which share a vertex with the particles at position [[i]] and [[j]]. If any of these particles belongs to the initial state, a PDG-ID flip is necessary to correctly recognize the vertex. If its size is equal to zero, no splitting is possible and the subroutine is exited. Otherwise, we loop over all possible underlying Born flavor structures and check if any of them equals the actual underlying Born flavor structure. For a quark emitting a gluon, [[flv_orig]] contains the PDG code of the anti-quark. To be on the safe side, a second array is created, which contains both the positively and negatively signed PDG codes. Then, the origial tuple $(i,j)$ is removed from the real flavor structure and the particles in [[flv_orig2]] are inserted. If the resulting Born configuration is equal to the underlying Born configuration, up to a permutation of final-state particles, the tuple $(i,j)$ is accepted as valid. <>= procedure :: valid_pair => flv_structure_valid_pair <>= module function flv_structure_valid_pair & (flv, i, j, flv_ref, model) result (valid) logical :: valid class(flv_structure_t), intent(in) :: flv integer, intent(in) :: i,j type(flv_structure_t), intent(in) :: flv_ref type(model_t), intent(in) :: model end function flv_structure_valid_pair <>= module function flv_structure_valid_pair & (flv, i, j, flv_ref, model) result (valid) logical :: valid class(flv_structure_t), intent(in) :: flv integer, intent(in) :: i,j type(flv_structure_t), intent(in) :: flv_ref type(model_t), intent(in) :: model integer :: k, n_orig type(flv_structure_t) :: flv_test integer, dimension(:), allocatable :: flv_orig valid = .false. if (all ([i, j] <= flv%n_in)) return if (i <= flv%n_in .and. is_fermion(flv%flst(i))) then call model%match_vertex (-flv%flst(i), flv%flst(j), flv_orig) else if (j <= flv%n_in .and. is_fermion(flv%flst(j))) then call model%match_vertex (flv%flst(i), -flv%flst(j), flv_orig) else call model%match_vertex (flv%flst(i), flv%flst(j), flv_orig) end if n_orig = size (flv_orig) if (n_orig == 0) then return else do k = 1, n_orig if (any ([i, j] <= flv%n_in)) then flv_test = flv%insert_particle_isr (i, j, flv_orig(k)) else flv_test = flv%insert_particle_fsr (i, j, flv_orig(k)) end if valid = flv_ref .equiv. flv_test call flv_test%final () if (valid) return end do end if deallocate (flv_orig) end function flv_structure_valid_pair @ %def flv_structure_valid_pair @ This function checks whether two flavor arrays are the same up to a permutation of the final-state particles <>= function flv_structure_equivalent (flv1, flv2, with_tag) result (equiv) logical :: equiv type(flv_structure_t), intent(in) :: flv1, flv2 logical, intent(in) :: with_tag type(flv_perm_t) :: perm integer :: n n = size (flv1%flst) equiv = .true. if (n /= size (flv2%flst)) then call msg_fatal & ('flv_structure_equivalent: flavor arrays do not have equal lengths') else if (flv1%n_in /= flv2%n_in) then call msg_fatal & ('flv_structure_equivalent: flavor arrays do not have equal n_in') else call perm%init (flv1, flv2, flv1%n_in, flv1%nlegs, with_tag) equiv = perm%eqv (flv2, flv1, with_tag) call perm%final () end if end function flv_structure_equivalent @ %def flv_structure_equivalent @ <>= module function flv_structure_equivalent_no_tag (flv1, flv2) result(equiv) logical :: equiv type(flv_structure_t), intent(in) :: flv1, flv2 end function flv_structure_equivalent_no_tag module function flv_structure_equivalent_with_tag (flv1, flv2) result(equiv) logical :: equiv type(flv_structure_t), intent(in) :: flv1, flv2 endfunction flv_structure_equivalent_with_tag <>= module function flv_structure_equivalent_no_tag (flv1, flv2) result(equiv) logical :: equiv type(flv_structure_t), intent(in) :: flv1, flv2 equiv = flv_structure_equivalent (flv1, flv2, .false.) end function flv_structure_equivalent_no_tag module function flv_structure_equivalent_with_tag (flv1, flv2) result(equiv) logical :: equiv type(flv_structure_t), intent(in) :: flv1, flv2 equiv = flv_structure_equivalent (flv1, flv2, .true.) end function flv_structure_equivalent_with_tag @ %def flv_structure_equivalent_no_tag, flv_structure_equivalent_with_tag @ <>= pure module subroutine flv_structure_assign_flv (flv_out, flv_in) type(flv_structure_t), intent(out) :: flv_out type(flv_structure_t), intent(in) :: flv_in end subroutine flv_structure_assign_flv <>= pure module subroutine flv_structure_assign_flv (flv_out, flv_in) type(flv_structure_t), intent(out) :: flv_out type(flv_structure_t), intent(in) :: flv_in flv_out%nlegs = flv_in%nlegs flv_out%n_in = flv_in%n_in flv_out%prt_symm_fs = flv_in%prt_symm_fs if (allocated (flv_in%flst)) then allocate (flv_out%flst (size (flv_in%flst))) flv_out%flst = flv_in%flst end if if (allocated (flv_in%tag)) then allocate (flv_out%tag (size (flv_in%tag))) flv_out%tag = flv_in%tag end if if (allocated (flv_in%massive)) then allocate (flv_out%massive (size (flv_in%massive))) flv_out%massive = flv_in%massive end if if (allocated (flv_in%colored)) then allocate (flv_out%colored (size (flv_in%colored))) flv_out%colored = flv_in%colored end if end subroutine flv_structure_assign_flv @ %def flv_structure_assign_flv @ <>= pure module subroutine flv_structure_assign_integer (flv_out, iarray) type(flv_structure_t), intent(out) :: flv_out integer, intent(in), dimension(:) :: iarray end subroutine flv_structure_assign_integer <>= pure module subroutine flv_structure_assign_integer (flv_out, iarray) type(flv_structure_t), intent(out) :: flv_out integer, intent(in), dimension(:) :: iarray integer :: i flv_out%nlegs = size (iarray) allocate (flv_out%flst (flv_out%nlegs)) allocate (flv_out%tag (flv_out%nlegs)) flv_out%flst = iarray flv_out%tag = [(i, i = 1, flv_out%nlegs)] end subroutine flv_structure_assign_integer @ %def flv_structure_assign_integer @ Returs a new flavor array with the particle at position \texttt{index} removed. <>= procedure :: remove_particle => flv_structure_remove_particle <>= module function flv_structure_remove_particle (flv, index) result (flv_new) type(flv_structure_t) :: flv_new class(flv_structure_t), intent(in) :: flv integer, intent(in) :: index end function flv_structure_remove_particle <>= module function flv_structure_remove_particle (flv, index) result (flv_new) type(flv_structure_t) :: flv_new class(flv_structure_t), intent(in) :: flv integer, intent(in) :: index integer :: n1, n2 integer :: i, removed_tag n1 = size (flv%flst); n2 = n1 - 1 allocate (flv_new%flst (n2), flv_new%tag (n2)) flv_new%nlegs = n2 flv_new%n_in = flv%n_in removed_tag = flv%tag(index) if (index == 1) then flv_new%flst(1 : n2) = flv%flst(2 : n1) flv_new%tag(1 : n2) = flv%tag(2 : n1) else if (index == n1) then flv_new%flst(1 : n2) = flv%flst(1 : n2) flv_new%tag(1 : n2) = flv%tag(1 : n2) else flv_new%flst(1 : index - 1) = flv%flst(1 : index - 1) flv_new%flst(index : n2) = flv%flst(index + 1 : n1) flv_new%tag(1 : index - 1) = flv%tag(1 : index - 1) flv_new%tag(index : n2) = flv%tag(index + 1 : n1) end if do i = 1, n2 if (flv_new%tag(i) > removed_tag) & flv_new%tag(i) = flv_new%tag(i) - 1 end do call flv_new%compute_prt_symm_fs (flv_new%n_in) end function flv_structure_remove_particle @ %def flv_structure_remove_particle @ Removes the particles at position i1 and i2 and inserts a new particle of matching flavor at position i1. <>= procedure :: insert_particle_fsr => flv_structure_insert_particle_fsr <>= module function flv_structure_insert_particle_fsr & (flv, i1, i2, flv_add) result (flv_new) type(flv_structure_t) :: flv_new class(flv_structure_t), intent(in) :: flv integer, intent(in) :: i1, i2, flv_add end function flv_structure_insert_particle_fsr <>= module function flv_structure_insert_particle_fsr & (flv, i1, i2, flv_add) result (flv_new) type(flv_structure_t) :: flv_new class(flv_structure_t), intent(in) :: flv integer, intent(in) :: i1, i2, flv_add if (flv%flst(i1) + flv_add == 0 .or. flv%flst(i2) + flv_add == 0) then flv_new = flv%insert_particle (i1, i2, -flv_add) else flv_new = flv%insert_particle (i1, i2, flv_add) end if end function flv_structure_insert_particle_fsr @ %def flv_structure_insert_particle_fsr @ Same as [[insert_particle_fsr]] but for ISR, the two particles are not exchangeable. <>= procedure :: insert_particle_isr => flv_structure_insert_particle_isr <>= module function flv_structure_insert_particle_isr & (flv, i_in, i_out, flv_add) result (flv_new) type(flv_structure_t) :: flv_new class(flv_structure_t), intent(in) :: flv integer, intent(in) :: i_in, i_out, flv_add end function flv_structure_insert_particle_isr <>= module function flv_structure_insert_particle_isr & (flv, i_in, i_out, flv_add) result (flv_new) type(flv_structure_t) :: flv_new class(flv_structure_t), intent(in) :: flv integer, intent(in) :: i_in, i_out, flv_add if (flv%flst(i_in) + flv_add == 0) then flv_new = flv%insert_particle (i_in, i_out, -flv_add) else flv_new = flv%insert_particle (i_in, i_out, flv_add) end if end function flv_structure_insert_particle_isr @ %def flv_structure_insert_particle_isr @ Removes the particles at position i1 and i2 and inserts a new particle at position i1. <>= procedure :: insert_particle => flv_structure_insert_particle <>= module function flv_structure_insert_particle & (flv, i1, i2, particle) result (flv_new) type(flv_structure_t) :: flv_new class(flv_structure_t), intent(in) :: flv integer, intent(in) :: i1, i2, particle end function flv_structure_insert_particle <>= module function flv_structure_insert_particle & (flv, i1, i2, particle) result (flv_new) type(flv_structure_t) :: flv_new class(flv_structure_t), intent(in) :: flv integer, intent(in) :: i1, i2, particle type(flv_structure_t) :: flv_tmp integer :: n1, n2 integer :: new_tag n1 = size (flv%flst); n2 = n1 - 1 allocate (flv_new%flst (n2), flv_new%tag (n2)) flv_new%nlegs = n2 flv_new%n_in = flv%n_in new_tag = maxval(flv%tag) + 1 if (i1 < i2) then flv_tmp = flv%remove_particle (i1) flv_tmp = flv_tmp%remove_particle (i2 - 1) else if(i2 < i1) then flv_tmp = flv%remove_particle(i2) flv_tmp = flv_tmp%remove_particle(i1 - 1) else call msg_fatal ("flv_structure_insert_particle: Indices are identical!") end if if (i1 == 1) then flv_new%flst(1) = particle flv_new%flst(2 : n2) = flv_tmp%flst(1 : n2 - 1) flv_new%tag(1) = new_tag flv_new%tag(2 : n2) = flv_tmp%tag(1 : n2 - 1) else if (i1 == n1 .or. i1 == n2) then flv_new%flst(1 : n2 - 1) = flv_tmp%flst(1 : n2 - 1) flv_new%flst(n2) = particle flv_new%tag(1 : n2 - 1) = flv_tmp%tag(1 : n2 - 1) flv_new%tag(n2) = new_tag else flv_new%flst(1 : i1 - 1) = flv_tmp%flst(1 : i1 - 1) flv_new%flst(i1) = particle flv_new%flst(i1 + 1 : n2) = flv_tmp%flst(i1 : n2 - 1) flv_new%tag(1 : i1 - 1) = flv_tmp%tag(1 : i1 - 1) flv_new%tag(i1) = new_tag flv_new%tag(i1 + 1 : n2) = flv_tmp%tag(i1 : n2 - 1) end if call flv_new%compute_prt_symm_fs (flv_new%n_in) end function flv_structure_insert_particle @ %def flv_structure_insert_particle @ Counts the number of occurances of a particle in a flavor array <>= procedure :: count_particle => flv_structure_count_particle <>= module function flv_structure_count_particle (flv, part) result (n) class(flv_structure_t), intent(in) :: flv integer, intent(in) :: part integer :: n end function flv_structure_count_particle <>= module function flv_structure_count_particle (flv, part) result (n) class(flv_structure_t), intent(in) :: flv integer, intent(in) :: part integer :: n n = count (flv%flst == part) end function flv_structure_count_particle @ %def flv_structure_count_particle @ Initializer for flavor structures <>= procedure :: init => flv_structure_init <>= module subroutine flv_structure_init (flv, aval, n_in, tags) class(flv_structure_t), intent(inout) :: flv integer, intent(in), dimension(:) :: aval integer, intent(in) :: n_in integer, intent(in), dimension(:), optional :: tags end subroutine flv_structure_init <>= module subroutine flv_structure_init (flv, aval, n_in, tags) class(flv_structure_t), intent(inout) :: flv integer, intent(in), dimension(:) :: aval integer, intent(in) :: n_in integer, intent(in), dimension(:), optional :: tags integer :: i, n integer, dimension(:), allocatable :: aval_unique integer, dimension(:), allocatable :: mult n = size (aval) allocate (flv%flst (n), flv%tag (n)) flv%flst = aval if (present (tags)) then flv%tag = tags else do i = 1, n flv%tag(i) = i end do end if flv%nlegs = n flv%n_in = n_in call flv%compute_prt_symm_fs (flv%n_in) end subroutine flv_structure_init @ %def flv_structure_init @ <>= procedure :: compute_prt_symm_fs => flv_structure_compute_prt_symm_fs <>= module subroutine flv_structure_compute_prt_symm_fs (flv, n_in) class(flv_structure_t), intent(inout) :: flv integer, intent(in) :: n_in end subroutine flv_structure_compute_prt_symm_fs <>= module subroutine flv_structure_compute_prt_symm_fs (flv, n_in) class(flv_structure_t), intent(inout) :: flv integer, intent(in) :: n_in integer, dimension(:), allocatable :: flst_unique integer, dimension(:), allocatable :: mult integer :: i flst_unique = remove_duplicates_from_int_array (flv%flst(n_in + 1 :)) allocate (mult(size (flst_unique))) do i = 1, size (flst_unique) mult(i) = count (flv%flst(n_in + 1 :) == flst_unique(i)) end do flv%prt_symm_fs = one / product (gamma (real (mult + 1, default))) end subroutine flv_structure_compute_prt_symm_fs @ %def flv_structure_compute_prt_symm_fs @ <>= procedure :: write => flv_structure_write <>= module subroutine flv_structure_write (flv, unit) class(flv_structure_t), intent(in) :: flv integer, intent(in), optional :: unit end subroutine flv_structure_write <>= module subroutine flv_structure_write (flv, unit) class(flv_structure_t), intent(in) :: flv integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit); if (u < 0) return write (u, '(A)') char (flv%to_string ()) end subroutine flv_structure_write @ %def flv_structure_write @ <>= procedure :: to_string => flv_structure_to_string <>= module function flv_structure_to_string (flv) result (flv_string) type(string_t) :: flv_string class(flv_structure_t), intent(in) :: flv end function flv_structure_to_string <>= module function flv_structure_to_string (flv) result (flv_string) type(string_t) :: flv_string class(flv_structure_t), intent(in) :: flv integer :: i, n if (allocated (flv%flst)) then flv_string = var_str ("[") n = size (flv%flst) do i = 1, n - 1 flv_string = flv_string // str (flv%flst(i)) // var_str(",") end do flv_string = flv_string // str (flv%flst(n)) // var_str("]") else flv_string = var_str ("[not allocated]") end if end function flv_structure_to_string @ %def flv_structure_to_string @ Creates the underlying Born flavor structure for a given real flavor structure if the particle at position \texttt{emitter} is removed <>= procedure :: create_uborn => flv_structure_create_uborn <>= module function flv_structure_create_uborn & (flv, emitter, nlo_correction_type) result(flv_uborn) type(flv_structure_t) :: flv_uborn class(flv_structure_t), intent(in) :: flv type(string_t), intent(in) :: nlo_correction_type integer, intent(in) :: emitter end function flv_structure_create_uborn <>= module function flv_structure_create_uborn & (flv, emitter, nlo_correction_type) result(flv_uborn) type(flv_structure_t) :: flv_uborn class(flv_structure_t), intent(in) :: flv type(string_t), intent(in) :: nlo_correction_type integer, intent(in) :: emitter integer n_legs integer :: f1, f2 integer :: gauge_boson n_legs = size(flv%flst) allocate (flv_uborn%flst (n_legs - 1), flv_uborn%tag (n_legs - 1)) gauge_boson = determine_gauge_boson_to_be_inserted () if (emitter > flv%n_in) then f1 = flv%flst(n_legs); f2 = flv%flst(n_legs - 1) if (is_massless_vector (f1)) then !!! Emitted particle is a gluon or photon => just remove it flv_uborn = flv%remove_particle(n_legs) else if (is_fermion (f1) .and. is_fermion (f2) .and. f1 + f2 == 0) then !!! Emission type is a gauge boson splitting into two fermions flv_uborn = flv%insert_particle(n_legs - 1, n_legs, gauge_boson) else call msg_error ("Create underlying Born: Unsupported splitting type.") call msg_error (char (str (flv%flst))) call msg_fatal ("FKS - FAIL") end if else if (emitter > 0) then f1 = flv%flst(n_legs); f2 = flv%flst(emitter) if (is_massless_vector (f1)) then flv_uborn = flv%remove_particle(n_legs) else if (is_fermion (f1) .and. is_massless_vector (f2)) then flv_uborn = flv%insert_particle (emitter, n_legs, -f1) else if (is_fermion (f1) .and. is_fermion (f2) .and. f1 == f2) then flv_uborn = flv%insert_particle(emitter, n_legs, gauge_boson) end if else flv_uborn = flv%remove_particle (n_legs) end if contains integer function determine_gauge_boson_to_be_inserted () select case (char (nlo_correction_type)) case ("QCD") determine_gauge_boson_to_be_inserted = GLUON case ("EW") determine_gauge_boson_to_be_inserted = PHOTON case ("Full") call msg_fatal ("NLO correction type 'Full' not yet implemented!") case default call msg_fatal ("Invalid NLO correction type! Valid inputs " // & "are: QCD, EW and Full (default: QCD)") end select end function determine_gauge_boson_to_be_inserted end function flv_structure_create_uborn @ %def flv_structure_create_uborn @ <>= procedure :: init_mass_color_and_charge => & flv_structure_init_mass_color_and_charge <>= module subroutine flv_structure_init_mass_color_and_charge (flv, model) class(flv_structure_t), intent(inout) :: flv type(model_t), intent(in) :: model end subroutine flv_structure_init_mass_color_and_charge <>= module subroutine flv_structure_init_mass_color_and_charge (flv, model) class(flv_structure_t), intent(inout) :: flv type(model_t), intent(in) :: model integer :: i type(flavor_t) :: flavor allocate (flv%massive (flv%nlegs), flv%colored(flv%nlegs), & flv%charge(flv%nlegs)) do i = 1, flv%nlegs call flavor%init (flv%flst(i), model) flv%massive(i) = flavor%get_mass () > 0 flv%colored(i) = & is_quark (flv%flst(i)) .or. is_gluon (flv%flst(i)) flv%charge(i) = flavor%get_charge () end do end subroutine flv_structure_init_mass_color_and_charge @ %def flv_structure_init_mass_color_and_charge @ <>= procedure :: get_last_two => flv_structure_get_last_two <>= module function flv_structure_get_last_two (flv, n) result (flst_last) integer, dimension(2) :: flst_last class(flv_structure_t), intent(in) :: flv integer, intent(in) :: n end function flv_structure_get_last_two <>= module function flv_structure_get_last_two (flv, n) result (flst_last) integer, dimension(2) :: flst_last class(flv_structure_t), intent(in) :: flv integer, intent(in) :: n flst_last = [flv%flst(n - 1), flv%flst(n)] end function flv_structure_get_last_two @ %def flv_structure_get_last_two @ <>= procedure :: final => flv_structure_final <>= module subroutine flv_structure_final (flv) class(flv_structure_t), intent(inout) :: flv end subroutine flv_structure_final <>= module subroutine flv_structure_final (flv) class(flv_structure_t), intent(inout) :: flv if (allocated (flv%flst)) deallocate (flv%flst) if (allocated (flv%tag)) deallocate (flv%tag) if (allocated (flv%massive)) deallocate (flv%massive) if (allocated (flv%colored)) deallocate (flv%colored) if (allocated (flv%charge)) deallocate (flv%charge) end subroutine flv_structure_final @ %def flv_structure_final @ <>= type :: flv_perm_t integer, dimension(:,:), allocatable :: perms contains <> end type flv_perm_t @ %def flv_perm_t @ <>= procedure :: init => flv_perm_init <>= module subroutine flv_perm_init & (perm, flv_in, flv_ref, n_first, n_last, with_tag) class(flv_perm_t), intent(out) :: perm type(flv_structure_t), intent(in) :: flv_in, flv_ref integer, intent(in) :: n_first, n_last logical, intent(in) :: with_tag end subroutine flv_perm_init <>= module subroutine flv_perm_init & (perm, flv_in, flv_ref, n_first, n_last, with_tag) class(flv_perm_t), intent(out) :: perm type(flv_structure_t), intent(in) :: flv_in, flv_ref integer, intent(in) :: n_first, n_last logical, intent(in) :: with_tag integer :: flv1, flv2, tmp integer :: tag1, tag2 integer :: i, j, j_min, i_perm integer, dimension(:,:), allocatable :: perm_list_tmp type(flv_structure_t) :: flv_copy logical :: condition logical, dimension(:), allocatable :: already_correct flv_copy = flv_in allocate (perm_list_tmp (factorial (n_last - n_first - 1), 2)) allocate (already_correct (flv_in%nlegs)) already_correct = flv_in%flst == flv_ref%flst if (with_tag) & already_correct = already_correct .and. (flv_in%tag == flv_ref%tag) j_min = n_first + 1 i_perm = 0 do i = n_first + 1, n_last flv1 = flv_ref%flst(i) tag1 = flv_ref%tag(i) do j = j_min, n_last if (already_correct(i) .or. already_correct(j)) cycle flv2 = flv_copy%flst(j) tag2 = flv_copy%tag(j) condition = (flv1 == flv2) .and. i /= j if (with_tag) condition = condition .and. (tag1 == tag2) if (condition) then i_perm = i_perm + 1 tmp = flv_copy%flst(i) flv_copy%flst(i) = flv2 flv_copy%flst(j) = tmp tmp = flv_copy%tag(i) flv_copy%tag(i) = tag2 flv_copy%tag(j) = tmp perm_list_tmp (i_perm, 1) = i perm_list_tmp (i_perm, 2) = j exit end if end do j_min = j_min + 1 end do allocate (perm%perms (i_perm, 2)) perm%perms = perm_list_tmp (1 : i_perm, :) deallocate (perm_list_tmp) call flv_copy%final () end subroutine flv_perm_init @ %def flv_perm_init @ <>= procedure :: write => flv_perm_write <>= module subroutine flv_perm_write (perm, unit) class(flv_perm_t), intent(in) :: perm integer, intent(in), optional :: unit end subroutine flv_perm_write <>= module subroutine flv_perm_write (perm, unit) class(flv_perm_t), intent(in) :: perm integer, intent(in), optional :: unit integer :: i, n, u u = given_output_unit (unit); if (u < 0) return write (u, "(A)") "Flavor permutation list: " n = size (perm%perms, dim = 1) if (n > 0) then do i = 1, n write (u, "(A1,I1,1X,I1,A1)", advance = "no") "[", & perm%perms(i,1), perm%perms(i,2), "]" if (i < n) write (u, "(A4)", advance = "no") " // " end do write (u, "(A)") "" else write (u, "(A)") "[Empty]" end if end subroutine flv_perm_write @ %def flv_perm_write @ <>= procedure :: reset => flv_perm_final procedure :: final => flv_perm_final <>= module subroutine flv_perm_final (perm) class(flv_perm_t), intent(inout) :: perm end subroutine flv_perm_final <>= module subroutine flv_perm_final (perm) class(flv_perm_t), intent(inout) :: perm if (allocated (perm%perms)) deallocate (perm%perms) end subroutine flv_perm_final @ %def flv_perm_final @ <>= generic :: apply => & apply_flv_structure, apply_index, apply_ftuple procedure :: apply_flv_structure => flv_perm_apply_flv_structure procedure :: apply_index => flv_perm_apply_index procedure :: apply_ftuple => flv_perm_apply_ftuple <>= elemental module function flv_perm_apply_flv_structure & (perm, flv_in, invert) result (flv_out) type(flv_structure_t) :: flv_out class(flv_perm_t), intent(in) :: perm type(flv_structure_t), intent(in) :: flv_in logical, intent(in), optional :: invert end function flv_perm_apply_flv_structure <>= elemental module function flv_perm_apply_flv_structure & (perm, flv_in, invert) result (flv_out) type(flv_structure_t) :: flv_out class(flv_perm_t), intent(in) :: perm type(flv_structure_t), intent(in) :: flv_in logical, intent(in), optional :: invert integer :: i, i1, i2 integer :: p1, p2, incr integer :: flv_tmp, tag_tmp logical :: inv inv = .false.; if (present(invert)) inv = invert flv_out = flv_in if (inv) then p1 = 1 p2 = size (perm%perms, dim = 1) incr = 1 else p1 = size (perm%perms, dim = 1) p2 = 1 incr = -1 end if do i = p1, p2, incr i1 = perm%perms(i,1) i2 = perm%perms(i,2) flv_tmp = flv_out%flst(i1) tag_tmp = flv_out%tag(i1) flv_out%flst(i1) = flv_out%flst(i2) flv_out%flst(i2) = flv_tmp flv_out%tag(i1) = flv_out%tag(i2) flv_out%tag(i2) = tag_tmp end do end function flv_perm_apply_flv_structure @ %def flv_perm_apply_flv_structure @ <>= elemental module function flv_perm_apply_index & (perm, i_in) result (i_out) integer :: i_out class(flv_perm_t), intent(in) :: perm integer, intent(in) :: i_in end function flv_perm_apply_index <>= elemental module function flv_perm_apply_index & (perm, i_in) result (i_out) integer :: i_out class(flv_perm_t), intent(in) :: perm integer, intent(in) :: i_in integer :: i, i1, i2 i_out = i_in do i = size (perm%perms(:,1)), 1, -1 i1 = perm%perms(i,1) i2 = perm%perms(i,2) if (i_out == i1) then i_out = i2 else if (i_out == i2) then i_out = i1 end if end do end function flv_perm_apply_index @ %def flv_perm_apply_index @ <>= elemental module function flv_perm_apply_ftuple & (perm, f_in) result (f_out) type(ftuple_t) :: f_out class(flv_perm_t), intent(in) :: perm type(ftuple_t), intent(in) :: f_in end function flv_perm_apply_ftuple <>= elemental module function flv_perm_apply_ftuple & (perm, f_in) result (f_out) type(ftuple_t) :: f_out class(flv_perm_t), intent(in) :: perm type(ftuple_t), intent(in) :: f_in integer :: i, i1, i2 f_out = f_in do i = size (perm%perms, dim = 1), 1, -1 i1 = perm%perms(i,1) i2 = perm%perms(i,2) if (f_out%ireg(1) == i1) then f_out%ireg(1) = i2 else if (f_out%ireg(1) == i2) then f_out%ireg(1) = i1 end if if (f_out%ireg(2) == i1) then f_out%ireg(2) = i2 else if (f_out%ireg(2) == i2) then f_out%ireg(2) = i1 end if end do if (f_out%ireg(1) > f_out%ireg(2)) f_out%ireg = f_out%ireg([2,1]) end function flv_perm_apply_ftuple @ %def flv_perm_apply_ftuple @ <>= procedure :: eqv => flv_perm_eqv <>= module function flv_perm_eqv & (perm, flv1, flv2, with_tag) result (valid) logical :: valid class(flv_perm_t), intent(in) :: perm type(flv_structure_t), intent(in) :: flv1, flv2 logical, intent(in) :: with_tag end function flv_perm_eqv <>= module function flv_perm_eqv & (perm, flv1, flv2, with_tag) result (valid) logical :: valid class(flv_perm_t), intent(in) :: perm type(flv_structure_t), intent(in) :: flv1, flv2 logical, intent(in) :: with_tag type(flv_structure_t) :: flv_tmp flv_tmp = perm%apply (flv2, invert = .true.) valid = all (flv_tmp%flst == flv1%flst) if (with_tag) valid = valid .and. all (flv_tmp%tag == flv1%tag) call flv_tmp%final () end function flv_perm_eqv @ %def flv_perm_eqv @ A singular region is a partition of phase space which is associated with an individual emitter and, if relevant, resonance. It is associated with an $\alpha_r$- and resonance-index, with a real flavor structure and its underlying Born flavor structure. To compute the FKS weights, it is relevant to know all the other particle indices which can result in a divergenent phase space configuration, which are collected in the [[ftuples]]-array. Some singular regions might behave physically identical. E.g. a real flavor structure associated with three-jet production is $[11,-11,2,-2,21,21]$. Here, there are two possible [[ftuples]] which contribute to the same $u \rightarrow u g$ splitting, namely $(3,5)$ and $(3,6)$. The resulting singular regions will be identical. To avoid this, one singular region is associated with the multiplicity factor [[mult]]. When computing the subtraction terms for each singular region, the result is then simply multiplied by this factor.\\ The [[double_fsr]]-flag indicates whether the singular region should also be supplied by a symmetry factor, explained below. <>= public :: singular_region_t <>= type :: singular_region_t integer :: alr integer :: i_res type(flv_structure_t) :: flst_real type(flv_structure_t) :: flst_uborn integer :: mult integer :: emitter integer :: nregions integer :: real_index type(ftuple_t), dimension(:), allocatable :: ftuples integer :: uborn_index logical :: double_fsr = .false. logical :: soft_divergence = .false. logical :: coll_divergence = .false. type(string_t) :: nlo_correction_type integer, dimension(:), allocatable :: i_reg_to_i_con logical :: pseudo_isr = .false. logical :: sc_required = .false. integer :: eqv_index = 0 contains <> end type singular_region_t @ %def singular_region_t @ <>= procedure :: init => singular_region_init <>= module subroutine singular_region_init (sregion, alr, mult, i_res, & flst_real, flst_uborn, flv_born, emitter, ftuples, equivalences, & nlo_correction_type) class(singular_region_t), intent(out) :: sregion integer, intent(in) :: alr, mult, i_res type(flv_structure_t), intent(in) :: flst_real type(flv_structure_t), intent(in) :: flst_uborn type(flv_structure_t), dimension(:), intent(in) :: flv_born integer, intent(in) :: emitter type(ftuple_t), intent(inout), dimension(:) :: ftuples logical, intent(inout), dimension(:,:) :: equivalences type(string_t), intent(in) :: nlo_correction_type end subroutine singular_region_init <>= module subroutine singular_region_init (sregion, alr, mult, i_res, & flst_real, flst_uborn, flv_born, emitter, ftuples, equivalences, & nlo_correction_type) class(singular_region_t), intent(out) :: sregion integer, intent(in) :: alr, mult, i_res type(flv_structure_t), intent(in) :: flst_real type(flv_structure_t), intent(in) :: flst_uborn type(flv_structure_t), dimension(:), intent(in) :: flv_born integer, intent(in) :: emitter type(ftuple_t), intent(inout), dimension(:) :: ftuples logical, intent(inout), dimension(:,:) :: equivalences type(string_t), intent(in) :: nlo_correction_type integer :: i call debug_input_values () sregion%alr = alr sregion%mult = mult sregion%i_res = i_res sregion%flst_real = flst_real sregion%flst_uborn = flst_uborn sregion%emitter = emitter sregion%nlo_correction_type = nlo_correction_type sregion%nregions = size (ftuples) allocate (sregion%ftuples (sregion%nregions)) sregion%ftuples = ftuples do i = 1, size(flv_born) if (flv_born (i) .equiv. sregion%flst_uborn) then sregion%uborn_index = i exit end if end do sregion%sc_required = any (sregion%flst_uborn%flst == GLUON) .or. & any (sregion%flst_uborn%flst == PHOTON) contains subroutine debug_input_values() if (debug_on) call msg_debug2 (D_SUBTRACTION, "singular_region_init") if (debug2_active (D_SUBTRACTION)) then print *, 'alr = ', alr print *, 'mult = ', mult print *, 'i_res = ', i_res call flst_real%write () call flst_uborn%write () print *, 'emitter = ', emitter call print_equivalence_matrix (ftuples, equivalences) end if end subroutine debug_input_values end subroutine singular_region_init @ %def singular_region_init <>= procedure :: write => singular_region_write <>= module subroutine singular_region_write (sregion, unit, maxnregions) class(singular_region_t), intent(in) :: sregion integer, intent(in), optional :: unit integer, intent(in), optional :: maxnregions end subroutine singular_region_write <>= module subroutine singular_region_write (sregion, unit, maxnregions) class(singular_region_t), intent(in) :: sregion integer, intent(in), optional :: unit integer, intent(in), optional :: maxnregions character(len=7), parameter :: flst_format = "(I3,A1)" character(len=7), parameter :: ireg_space_format = "(7X,A1)" integer :: nreal, nborn, i, u, mr integer :: nleft, nright, nreg, nreg_diff u = given_output_unit (unit); if (u < 0) return mr = sregion%nregions; if (present (maxnregions)) mr = maxnregions nreal = size (sregion%flst_real%flst) nborn = size (sregion%flst_uborn%flst) call write_vline (u) write (u, '(A1)', advance = 'no') '[' do i = 1, nreal - 1 write (u, flst_format, advance = 'no') sregion%flst_real%flst(i), ',' end do write (u, flst_format, advance = 'no') sregion%flst_real%flst(nreal), ']' call write_vline (u) write (u, '(I6)', advance = 'no') sregion%real_index call write_vline (u) write (u, '(I3)', advance = 'no') sregion%emitter call write_vline (u) write (u, '(I3)', advance = 'no') sregion%mult call write_vline (u) write (u, '(I4)', advance = 'no') sregion%nregions call write_vline (u) if (sregion%i_res > 0) then write (u, '(I3)', advance = 'no') sregion%i_res call write_vline (u) end if nreg = sregion%nregions if (nreg == mr) then nleft = 0 nright = 0 else nreg_diff = mr - nreg nleft = nreg_diff / 2 if (mod(nreg_diff , 2) == 0) then nright = nleft else nright = nleft + 1 end if end if if (nleft > 0) then do i = 1, nleft write(u, ireg_space_format, advance='no') ' ' end do end if write (u, '(A)', advance = 'no') char (ftuple_string (sregion%ftuples, .false.)) call write_vline (u) write (u,'(A1)',advance = 'no') '[' do i = 1, nborn - 1 write(u, flst_format, advance = 'no') sregion%flst_uborn%flst(i), ',' end do write (u, flst_format, advance = 'no') sregion%flst_uborn%flst(nborn), ']' call write_vline (u) write (u, '(I7)', advance = 'no') sregion%uborn_index call write_vline (u) if (sregion%nlo_correction_type == "EW") then write (u, '(A3)', advance = 'no') 'ew' else if (sregion%nlo_correction_type == "QCD") then write (u, '(A4)', advance = 'no') 'qcd' else write (u, '(A5)', advance = 'no') 'none' end if write (u, '(A)') end subroutine singular_region_write @ %def singular_region_write @ <>= procedure :: write_latex => singular_region_write_latex <>= module subroutine singular_region_write_latex (region, unit) class(singular_region_t), intent(in) :: region integer, intent(in), optional :: unit end subroutine singular_region_write_latex <>= module subroutine singular_region_write_latex (region, unit) class(singular_region_t), intent(in) :: region integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit); if (u < 0) return write (u, "(I2,A3,A,A3,I2,A3,I1,A3,I1,A3,A,A3,I2,A3,A,A3)") & region%alr, " & ", char (region%flst_real%to_string ()), & " & ", region%real_index, " & ", region%emitter, " & ", & region%mult, " & ", char (ftuple_string (region%ftuples, .true.)), & " & ", region%uborn_index, " & ", char (region%flst_uborn%to_string ()), & " \\" end subroutine singular_region_write_latex @ %def singular_region_write_latex @ In case of a $g \rightarrow gg$ splitting, the factor \begin{equation*} \frac{2E_{\rm{em}}}{E_{\rm{em}} + E_{\rm{rad}}} \end{equation*} is multiplied to the real matrix element. This way, the symmetry of the splitting is used and only one singular region has to be taken into account. However, the factor ensures that there is only a soft singularity if the radiated parton becomes soft. <>= procedure :: set_splitting_info => singular_region_set_splitting_info <>= module subroutine singular_region_set_splitting_info (region, n_in) class(singular_region_t), intent(inout) :: region integer, intent(in) :: n_in end subroutine singular_region_set_splitting_info <>= module subroutine singular_region_set_splitting_info (region, n_in) class(singular_region_t), intent(inout) :: region integer, intent(in) :: n_in integer :: i1, i2 integer :: reg region%double_fsr = .false. region%soft_divergence = .false. associate (ftuple => region%ftuples) do reg = 1, region%nregions call ftuple(reg)%get (i1, i2) if (i1 /= region%emitter .or. i2 /= region%flst_real%nlegs) then cycle else if (ftuple(reg)%splitting_type == V_TO_VV .or. & ftuple(reg)%splitting_type == F_TO_FV ) then region%soft_divergence = .true. end if if (i1 == 0) then region%coll_divergence = & .not. all (region%flst_real%massive(1:n_in)) else region%coll_divergence = .not. region%flst_real%massive(i1) end if if (ftuple(reg)%splitting_type == V_TO_VV) then if (all (ftuple(reg)%ireg > n_in)) & region%double_fsr = & all (is_gluon (region%flst_real%flst(ftuple(reg)%ireg))) exit else if (ftuple(reg)%splitting_type == UNDEFINED_SPLITTING) then call msg_fatal ("All splittings should be defined!") end if end if end do if (.not. region%soft_divergence .and. .not. region%coll_divergence) & call msg_fatal ("Singular region defined without divergence!") end associate end subroutine singular_region_set_splitting_info @ %def singular_region_set_splitting_info @ <>= procedure :: double_fsr_factor => singular_region_double_fsr_factor <>= module function singular_region_double_fsr_factor (region, p) result (val) class(singular_region_t), intent(in) :: region type(vector4_t), intent(in), dimension(:) :: p real(default) :: val end function singular_region_double_fsr_factor <>= module function singular_region_double_fsr_factor (region, p) result (val) class(singular_region_t), intent(in) :: region type(vector4_t), intent(in), dimension(:) :: p real(default) :: val real(default) :: E_rad, E_em if (region%double_fsr) then E_em = energy (p(region%emitter)) E_rad = energy (p(region%flst_real%nlegs)) val = two * E_em / (E_em + E_rad) else val = one end if end function singular_region_double_fsr_factor @ %def singular_region_double_fsr_factor @ <>= procedure :: has_soft_divergence => singular_region_has_soft_divergence <>= module function singular_region_has_soft_divergence (region) result (div) logical :: div class(singular_region_t), intent(in) :: region end function singular_region_has_soft_divergence <>= module function singular_region_has_soft_divergence (region) result (div) logical :: div class(singular_region_t), intent(in) :: region div = region%soft_divergence end function singular_region_has_soft_divergence @ %def singular_region_has_soft_divergence @ <>= procedure :: has_collinear_divergence => & singular_region_has_collinear_divergence <>= module function singular_region_has_collinear_divergence & (region) result (div) logical :: div class(singular_region_t), intent(in) :: region end function singular_region_has_collinear_divergence <>= module function singular_region_has_collinear_divergence & (region) result (div) logical :: div class(singular_region_t), intent(in) :: region div = region%coll_divergence end function singular_region_has_collinear_divergence @ %def singular_region_has_collinear_divergence @ <>= procedure :: has_identical_ftuples => singular_region_has_identical_ftuples <>= elemental module function singular_region_has_identical_ftuples & (sregion) result (value) logical :: value class(singular_region_t), intent(in) :: sregion end function singular_region_has_identical_ftuples <>= elemental module function singular_region_has_identical_ftuples & (sregion) result (value) logical :: value class(singular_region_t), intent(in) :: sregion integer :: alr value = .false. do alr = 1, sregion%nregions value = value .or. (count (sregion%ftuples(alr) == sregion%ftuples) > 1) end do end function singular_region_has_identical_ftuples @ %def singular_region_has_identical_ftuples @ <>= interface assignment(=) module procedure singular_region_assign end interface <>= module subroutine singular_region_assign (reg_out, reg_in) type(singular_region_t), intent(out) :: reg_out type(singular_region_t), intent(in) :: reg_in end subroutine singular_region_assign <>= module subroutine singular_region_assign (reg_out, reg_in) type(singular_region_t), intent(out) :: reg_out type(singular_region_t), intent(in) :: reg_in reg_out%alr = reg_in%alr reg_out%i_res = reg_in%i_res reg_out%flst_real = reg_in%flst_real reg_out%flst_uborn = reg_in%flst_uborn reg_out%mult = reg_in%mult reg_out%emitter = reg_in%emitter reg_out%nregions = reg_in%nregions reg_out%real_index = reg_in%real_index reg_out%uborn_index = reg_in%uborn_index reg_out%double_fsr = reg_in%double_fsr reg_out%soft_divergence = reg_in%soft_divergence reg_out%coll_divergence = reg_in%coll_divergence reg_out%nlo_correction_type = reg_in%nlo_correction_type if (allocated (reg_in%ftuples)) then allocate (reg_out%ftuples (size (reg_in%ftuples))) reg_out%ftuples = reg_in%ftuples else call msg_bug ("singular_region_assign: Trying to copy a " // & "singular region without allocated ftuples!") end if end subroutine singular_region_assign @ %def singular_region_assign @ Two singular regions match if they would produce the same amplitude. For this we have to check that their real and underlying Born flavor structures are equivalent, as determined by the [[prc_core]]. However, since there are more aspects of a singular region that make it unique, we have to check other attributes as well. <>= interface operator(.match.) module procedure singular_region_match end interface <>= module function singular_region_match (reg1, reg2) result (match) type(singular_region_t), intent(in) :: reg1, reg2 logical :: match end function singular_region_match <>= module function singular_region_match (reg1, reg2) result (match) type(singular_region_t), intent(in) :: reg1, reg2 logical :: match match = all ([reg1%flst_real%eqv_index, reg2%flst_real%eqv_index] > 0) match = match .and. (reg1%flst_real%eqv_index == reg2%flst_real%eqv_index) match = match .and. (reg1%flst_uborn%eqv_index == reg2%flst_uborn%eqv_index) match = match .and. (reg1%mult == reg2%mult) match = match .and. (reg1%emitter == reg2%emitter) match = match .and. (reg1%nregions == reg2%nregions) match = match .and. (reg1%double_fsr .eqv. reg2%double_fsr) match = match .and. (reg1%soft_divergence .eqv. reg2%soft_divergence) match = match .and. (reg1%coll_divergence .eqv. reg2%coll_divergence) match = match .and. (char (reg1%nlo_correction_type) == char (reg2%nlo_correction_type)) if (match) match = match .and. (all (reg1%ftuples == reg2%ftuples)) end function singular_region_match @ %def singular_region_match @ <>= type :: resonance_mapping_t type(resonance_history_t), dimension(:), allocatable :: res_histories integer, dimension(:), allocatable :: alr_to_i_res integer, dimension(:,:), allocatable :: i_res_to_alr type(vector4_t), dimension(:), allocatable :: p_res contains <> end type resonance_mapping_t @ %def resonance_mapping_t @ Testing: Init resonance mapping for $\mu \mu b b$ final state. <>= procedure :: init => resonance_mapping_init <>= module subroutine resonance_mapping_init (res_map, res_hist) class(resonance_mapping_t), intent(inout) :: res_map type(resonance_history_t), intent(in), dimension(:) :: res_hist end subroutine resonance_mapping_init <>= module subroutine resonance_mapping_init (res_map, res_hist) class(resonance_mapping_t), intent(inout) :: res_map type(resonance_history_t), intent(in), dimension(:) :: res_hist integer :: n_hist, i_hist1, i_hist2, n_contributors n_contributors = 0 n_hist = size (res_hist) allocate (res_map%res_histories (n_hist)) do i_hist1 = 1, n_hist if (i_hist1 + 1 <= n_hist) then do i_hist2 = i_hist1 + 1, n_hist if (.not. (res_hist(i_hist1) .contains. res_hist(i_hist2))) & n_contributors = n_contributors + & res_hist(i_hist2)%n_resonances end do else n_contributors = n_contributors + res_hist(i_hist1)%n_resonances end if end do allocate (res_map%p_res (n_contributors)) res_map%res_histories = res_hist res_map%p_res = vector4_null end subroutine resonance_mapping_init @ %def resonance_mapping_init @ <>= procedure :: set_alr_to_i_res => resonance_mapping_set_alr_to_i_res <>= module subroutine resonance_mapping_set_alr_to_i_res & (res_map, regions, alr_new_to_old) class(resonance_mapping_t), intent(inout) :: res_map type(singular_region_t), intent(in), dimension(:) :: regions integer, intent(out), dimension(:), allocatable :: alr_new_to_old end subroutine resonance_mapping_set_alr_to_i_res <>= module subroutine resonance_mapping_set_alr_to_i_res & (res_map, regions, alr_new_to_old) class(resonance_mapping_t), intent(inout) :: res_map type(singular_region_t), intent(in), dimension(:) :: regions integer, intent(out), dimension(:), allocatable :: alr_new_to_old integer :: alr, i_res integer :: alr_new, n_alr_res integer :: k if (debug_on) call msg_debug & (D_SUBTRACTION, "resonance_mapping_set_alr_to_i_res") n_alr_res = 0 do alr = 1, size (regions) do i_res = 1, size (res_map%res_histories) if (res_map%res_histories(i_res)%contains_leg & (regions(alr)%emitter)) & n_alr_res = n_alr_res + 1 end do end do allocate (res_map%alr_to_i_res (n_alr_res)) allocate (res_map%i_res_to_alr (size (res_map%res_histories), 10)) res_map%i_res_to_alr = 0 allocate (alr_new_to_old (n_alr_res)) alr_new = 1 do alr = 1, size (regions) do i_res = 1, size (res_map%res_histories) if (res_map%res_histories(i_res)%contains_leg & (regions(alr)%emitter)) then res_map%alr_to_i_res (alr_new) = i_res alr_new_to_old (alr_new) = alr alr_new = alr_new + 1 end if end do end do do i_res = 1, size (res_map%res_histories) k = 1 do alr = 1, size (regions) if (res_map%res_histories(i_res)%contains_leg & (regions(alr)%emitter)) then res_map%i_res_to_alr (i_res, k) = alr k = k + 1 end if end do end do if (debug_active (D_SUBTRACTION)) then print *, 'i_res_to_alr:' do i_res = 1, size(res_map%i_res_to_alr, dim=1) print *, res_map%i_res_to_alr (i_res, :) end do print *, 'alr_new_to_old:', alr_new_to_old end if end subroutine resonance_mapping_set_alr_to_i_res @ %def resonance_mapping_set_alr_to_i_res @ <>= procedure :: get_resonance_history => resonance_mapping_get_resonance_history <>= module function resonance_mapping_get_resonance_history & (res_map, alr) result (res_hist) type(resonance_history_t) :: res_hist class(resonance_mapping_t), intent(in) :: res_map integer, intent(in) :: alr end function resonance_mapping_get_resonance_history <>= module function resonance_mapping_get_resonance_history & (res_map, alr) result (res_hist) type(resonance_history_t) :: res_hist class(resonance_mapping_t), intent(in) :: res_map integer, intent(in) :: alr res_hist = res_map%res_histories(res_map%alr_to_i_res (alr)) end function resonance_mapping_get_resonance_history @ %def resonance_mapping_get_resonance_history @ <>= procedure :: write => resonance_mapping_write <>= module subroutine resonance_mapping_write (res_map) class(resonance_mapping_t), intent(in) :: res_map end subroutine resonance_mapping_write <>= module subroutine resonance_mapping_write (res_map) class(resonance_mapping_t), intent(in) :: res_map integer :: i_res do i_res = 1, size (res_map%res_histories) call res_map%res_histories(i_res)%write () end do end subroutine resonance_mapping_write @ %def resonance_mapping_write @ <>= procedure :: get_resonance_value => resonance_mapping_get_resonance_value <>= module function resonance_mapping_get_resonance_value & (res_map, i_res, p, i_gluon) result (p_map) real(default) :: p_map class(resonance_mapping_t), intent(in) :: res_map integer, intent(in) :: i_res type(vector4_t), intent(in), dimension(:) :: p integer, intent(in), optional :: i_gluon end function resonance_mapping_get_resonance_value <>= module function resonance_mapping_get_resonance_value & (res_map, i_res, p, i_gluon) result (p_map) real(default) :: p_map class(resonance_mapping_t), intent(in) :: res_map integer, intent(in) :: i_res type(vector4_t), intent(in), dimension(:) :: p integer, intent(in), optional :: i_gluon p_map = res_map%res_histories(i_res)%mapping (p, i_gluon) end function resonance_mapping_get_resonance_value @ %def resonance_mapping_get_resonance_value @ <>= procedure :: get_resonance_all => resonance_mapping_get_resonance_all <>= module function resonance_mapping_get_resonance_all & (res_map, alr, p, i_gluon) result (p_map) real(default) :: p_map class(resonance_mapping_t), intent(in) :: res_map integer, intent(in) :: alr type(vector4_t), intent(in), dimension(:) :: p integer, intent(in), optional :: i_gluon end function resonance_mapping_get_resonance_all <>= module function resonance_mapping_get_resonance_all & (res_map, alr, p, i_gluon) result (p_map) real(default) :: p_map class(resonance_mapping_t), intent(in) :: res_map integer, intent(in) :: alr type(vector4_t), intent(in), dimension(:) :: p integer, intent(in), optional :: i_gluon integer :: i_res p_map = zero do i_res = 1, size (res_map%res_histories) associate (res => res_map%res_histories(i_res)) if (any (res_map%i_res_to_alr (i_res, :) == alr)) & p_map = p_map + res%mapping (p, i_gluon) end associate end do end function resonance_mapping_get_resonance_all @ %def resonance_mapping_get_resonance_all @ <>= procedure :: get_weight => resonance_mapping_get_weight <>= module function resonance_mapping_get_weight (res_map, alr, p) result (pfr) real(default) :: pfr class(resonance_mapping_t), intent(in) :: res_map integer, intent(in) :: alr type(vector4_t), intent(in), dimension(:) :: p end function resonance_mapping_get_weight <>= module function resonance_mapping_get_weight (res_map, alr, p) result (pfr) real(default) :: pfr class(resonance_mapping_t), intent(in) :: res_map integer, intent(in) :: alr type(vector4_t), intent(in), dimension(:) :: p real(default) :: sumpfr integer :: i_res sumpfr = zero do i_res = 1, size (res_map%res_histories) sumpfr = sumpfr + res_map%get_resonance_value (i_res, p) end do pfr = res_map%get_resonance_value (res_map%alr_to_i_res (alr), p) / sumpfr end function resonance_mapping_get_weight @ %def resonance_mapping_get_weight @ <>= procedure :: get_resonance_alr => resonance_mapping_get_resonance_alr <>= module function resonance_mapping_get_resonance_alr & (res_map, alr, p, i_gluon) result (p_map) real(default) :: p_map class(resonance_mapping_t), intent(in) :: res_map integer, intent(in) :: alr type(vector4_t), intent(in), dimension(:) :: p integer, intent(in), optional :: i_gluon end function resonance_mapping_get_resonance_alr <>= module function resonance_mapping_get_resonance_alr & (res_map, alr, p, i_gluon) result (p_map) real(default) :: p_map class(resonance_mapping_t), intent(in) :: res_map integer, intent(in) :: alr type(vector4_t), intent(in), dimension(:) :: p integer, intent(in), optional :: i_gluon integer :: i_res i_res = res_map%alr_to_i_res (alr) p_map = res_map%res_histories(i_res)%mapping (p, i_gluon) end function resonance_mapping_get_resonance_alr @ %def resonance_mapping_get_resonance_alr @ <>= interface assignment(=) module procedure resonance_mapping_assign end interface <>= module subroutine resonance_mapping_assign (res_map_out, res_map_in) type(resonance_mapping_t), intent(out) :: res_map_out type(resonance_mapping_t), intent(in) :: res_map_in end subroutine resonance_mapping_assign <>= module subroutine resonance_mapping_assign (res_map_out, res_map_in) type(resonance_mapping_t), intent(out) :: res_map_out type(resonance_mapping_t), intent(in) :: res_map_in if (allocated (res_map_in%res_histories)) then allocate (res_map_out%res_histories (size (res_map_in%res_histories))) res_map_out%res_histories = res_map_in%res_histories end if if (allocated (res_map_in%alr_to_i_res)) then allocate (res_map_out%alr_to_i_res (size (res_map_in%alr_to_i_res))) res_map_out%alr_to_i_res = res_map_in%alr_to_i_res end if if (allocated (res_map_in%i_res_to_alr)) then allocate (res_map_out%i_res_to_alr (size (res_map_in%i_res_to_alr, 1), & size (res_map_in%i_res_to_alr, 2))) res_map_out%i_res_to_alr = res_map_in%i_res_to_alr end if if (allocated (res_map_in%p_res)) then allocate (res_map_out%p_res (size (res_map_in%p_res))) res_map_out%p_res = res_map_in%p_res end if end subroutine resonance_mapping_assign @ %def resonance_mapping_assign @ Every FKS mapping should store the $\sum_\alpha d_{ij}^{-1}$ and $\sum_\alpha d_{ij,\rm{soft}}^{-1}$. Also we keep the option open to use a normlization factor, which ensures $\sum_\alpha S_\alpha = 1$. <>= type, abstract :: fks_mapping_t real(default) :: sumdij real(default) :: sumdij_soft logical :: pseudo_isr = .false. real(default) :: normalization_factor = one contains <> end type fks_mapping_t @ %def fks_mapping_t @ <>= public :: fks_mapping_default_t <>= type, extends (fks_mapping_t) :: fks_mapping_default_t real(default) :: exp_1, exp_2 integer :: n_in contains <> end type fks_mapping_default_t @ %def fks_mapping_default_t @ <>= public :: fks_mapping_resonances_t <>= type, extends (fks_mapping_t) :: fks_mapping_resonances_t real(default) :: exp_1, exp_2 type(resonance_mapping_t) :: res_map integer :: i_con = 0 contains <> end type fks_mapping_resonances_t @ %def fks_mapping_resonances_t @ <>= public :: operator(.equiv.) public :: operator(.equivtag.) <>= interface operator(.equiv.) module procedure flv_structure_equivalent_no_tag end interface interface operator(.equivtag.) module procedure flv_structure_equivalent_with_tag end interface interface assignment(=) module procedure flv_structure_assign_flv module procedure flv_structure_assign_integer end interface @ %def operator_equiv @ <>= public :: region_data_t <>= type :: region_data_t type(singular_region_t), dimension(:), allocatable :: regions type(flv_structure_t), dimension(:), allocatable :: flv_born type(flv_structure_t), dimension(:), allocatable :: flv_real integer, dimension(:), allocatable :: eqv_flv_index_born integer, dimension(:), allocatable :: eqv_flv_index_real integer, dimension(:), allocatable :: emitters integer :: n_regions = 0 integer :: n_emitters = 0 integer :: n_flv_born = 0 integer :: n_flv_real = 0 integer :: n_in = 0 integer :: n_legs_born = 0 integer :: n_legs_real = 0 integer :: n_phs = 0 integer :: alpha_power = 0 integer :: alphas_power = 0 type(string_t) :: nlo_correction_type class(fks_mapping_t), allocatable :: fks_mapping integer, dimension(:), allocatable :: resonances type(resonance_contributors_t), dimension(:), allocatable :: alr_contributors integer, dimension(:), allocatable :: alr_to_i_contributor integer, dimension(:), allocatable :: i_phs_to_i_con contains <> end type region_data_t @ %def region_data_t @ Gfortran 7/8/9/ bug, has to remain in the main module: <>= procedure :: allocate_fks_mappings => region_data_allocate_fks_mappings <>= subroutine region_data_allocate_fks_mappings (reg_data, mapping_type) class(region_data_t), intent(inout) :: reg_data integer, intent(in) :: mapping_type select case (mapping_type) case (FKS_DEFAULT) allocate (fks_mapping_default_t :: reg_data%fks_mapping) case (FKS_RESONANCES) allocate (fks_mapping_resonances_t :: reg_data%fks_mapping) case default call msg_fatal ("Init region_data: FKS mapping not implemented!") end select end subroutine region_data_allocate_fks_mappings @ %def region_data_allocate_fks_mappings @ <>= procedure :: init => region_data_init <>= module subroutine region_data_init (reg_data, n_in, model, flavor_born, & flavor_real, nlo_correction_type, alpha_pow, alphas_pow) class(region_data_t), intent(out) :: reg_data integer, intent(in) :: n_in, alpha_pow, alphas_pow type(model_t), intent(in) :: model integer, intent(in), dimension(:,:) :: flavor_born, flavor_real type(string_t), intent(in) :: nlo_correction_type end subroutine region_data_init <>= module subroutine region_data_init (reg_data, n_in, model, flavor_born, & flavor_real, nlo_correction_type, alpha_pow, alphas_pow) class(region_data_t), intent(out) :: reg_data integer, intent(in) :: n_in, alpha_pow, alphas_pow type(model_t), intent(in) :: model integer, intent(in), dimension(:,:) :: flavor_born, flavor_real type(string_t), intent(in) :: nlo_correction_type integer, dimension(:,:), allocatable :: flv_real_tmp type(ftuple_list_t), dimension(:), allocatable :: ftuples integer, dimension(:), allocatable :: emitter type(flv_structure_t), dimension(:), allocatable :: flst_alr integer :: i, n_real integer :: n_flv_real_before_check reg_data%n_in = n_in reg_data%alpha_power = alpha_pow reg_data%alphas_power = alphas_pow reg_data%n_flv_born = size (flavor_born, dim = 2) reg_data%n_legs_born = size (flavor_born, dim = 1) reg_data%n_legs_real = reg_data%n_legs_born + 1 reg_data%nlo_correction_type = nlo_correction_type n_flv_real_before_check = size (flavor_real, dim = 2) allocate (reg_data%flv_born (reg_data%n_flv_born)) allocate (flv_real_tmp (reg_data%n_legs_real, n_flv_real_before_check)) do i = 1, reg_data%n_flv_born call reg_data%flv_born(i)%init (flavor_born (:, i), n_in) end do n_real = 0 do i = 1, n_flv_real_before_check if (nlo_correction_type == "EW") then if (.not. (query_coupling_powers & (flavor_real (:, i), reg_data%alpha_power + 1, & reg_data%alphas_power))) cycle end if n_real = n_real + 1 flv_real_tmp (:, n_real) = flavor_real (:, i) end do allocate (reg_data%flv_real (n_real)) do i = 1, n_real call reg_data%flv_real(i)%init (flv_real_tmp (:, i), n_in) end do call reg_data%find_regions (model, ftuples, emitter, flst_alr) call reg_data%init_singular_regions (ftuples, emitter, & flst_alr, nlo_correction_type) reg_data%n_flv_real = maxval (reg_data%regions%real_index) call reg_data%find_emitters () call reg_data%set_mass_color_and_charge (model) call reg_data%set_splitting_info () end subroutine region_data_init @ %def region_data_init @ <>= procedure :: init_resonance_information => & region_data_init_resonance_information <>= module subroutine region_data_init_resonance_information (reg_data) class(region_data_t), intent(inout) :: reg_data end subroutine region_data_init_resonance_information <>= module subroutine region_data_init_resonance_information (reg_data) class(region_data_t), intent(inout) :: reg_data call reg_data%enlarge_singular_regions_with_resonances () call reg_data%find_resonances () end subroutine region_data_init_resonance_information @ %def region_data_init_resonance_information @ <>= procedure :: set_resonance_mappings => region_data_set_resonance_mappings <>= module subroutine region_data_set_resonance_mappings & (reg_data, resonance_histories) class(region_data_t), intent(inout) :: reg_data type(resonance_history_t), intent(in), dimension(:) :: resonance_histories end subroutine region_data_set_resonance_mappings <>= module subroutine region_data_set_resonance_mappings & (reg_data, resonance_histories) class(region_data_t), intent(inout) :: reg_data type(resonance_history_t), intent(in), dimension(:) :: resonance_histories select type (map => reg_data%fks_mapping) type is (fks_mapping_resonances_t) call map%res_map%init (resonance_histories) end select end subroutine region_data_set_resonance_mappings @ %def region_data_set_resonance_mappings @ <>= procedure :: setup_fks_mappings => region_data_setup_fks_mappings <>= module subroutine region_data_setup_fks_mappings (reg_data, template, n_in) class(region_data_t), intent(inout) :: reg_data type(fks_template_t), intent(in) :: template integer, intent(in) :: n_in end subroutine region_data_setup_fks_mappings <>= module subroutine region_data_setup_fks_mappings (reg_data, template, n_in) class(region_data_t), intent(inout) :: reg_data type(fks_template_t), intent(in) :: template integer, intent(in) :: n_in call reg_data%allocate_fks_mappings (template%mapping_type) select type (map => reg_data%fks_mapping) type is (fks_mapping_default_t) call map%set_parameter (n_in, template%fks_dij_exp1, & template%fks_dij_exp2) end select end subroutine region_data_setup_fks_mappings @ %def region_data_setup_fks_mappings @ So far, we have only created singular regions for a non-resonant case. When resonance mappings are required, we have more singular regions, since they must now be identified by their emitter-resonance pair index, where the emitter must be compatible with the resonance. <>= procedure :: enlarge_singular_regions_with_resonances & => region_data_enlarge_singular_regions_with_resonances <>= module subroutine region_data_enlarge_singular_regions_with_resonances & (reg_data) class(region_data_t), intent(inout) :: reg_data end subroutine region_data_enlarge_singular_regions_with_resonances <>= module subroutine region_data_enlarge_singular_regions_with_resonances & (reg_data) class(region_data_t), intent(inout) :: reg_data integer :: alr integer, dimension(:), allocatable :: alr_new_to_old integer :: n_alr_new type(singular_region_t), dimension(:), allocatable :: save_regions if (debug_on) call msg_debug & (D_SUBTRACTION, "region_data_enlarge_singular_regions_with_resonances") call debug_input_values () select type (fks_mapping => reg_data%fks_mapping) type is (fks_mapping_default_t) return type is (fks_mapping_resonances_t) allocate (save_regions (reg_data%n_regions)) do alr = 1, reg_data%n_regions save_regions(alr) = reg_data%regions(alr) end do associate (res_map => fks_mapping%res_map) call res_map%set_alr_to_i_res (reg_data%regions, alr_new_to_old) deallocate (reg_data%regions) n_alr_new = size (alr_new_to_old) reg_data%n_regions = n_alr_new allocate (reg_data%regions (n_alr_new)) do alr = 1, n_alr_new reg_data%regions(alr) = save_regions(alr_new_to_old (alr)) reg_data%regions(alr)%i_res = res_map%alr_to_i_res (alr) end do end associate end select contains subroutine debug_input_values () if (debug2_active (D_SUBTRACTION)) then call reg_data%write () end if end subroutine debug_input_values end subroutine region_data_enlarge_singular_regions_with_resonances @ %def region_data_enlarge_singular_regions_with_resonances @ <>= procedure :: set_isr_pseudo_regions => region_data_set_isr_pseudo_regions <>= module subroutine region_data_set_isr_pseudo_regions (reg_data) class(region_data_t), intent(inout) :: reg_data end subroutine region_data_set_isr_pseudo_regions <>= module subroutine region_data_set_isr_pseudo_regions (reg_data) class(region_data_t), intent(inout) :: reg_data integer :: alr integer :: n_alr_new !!! Subroutine called for threshold factorization -> !!! Size of singular regions at this point is fixed type(singular_region_t), dimension(2) :: save_regions integer, dimension(4) :: alr_new_to_old do alr = 1, reg_data%n_regions save_regions(alr) = reg_data%regions(alr) end do n_alr_new = reg_data%n_regions * 2 alr_new_to_old = [1, 1, 2, 2] deallocate (reg_data%regions) allocate (reg_data%regions (n_alr_new)) reg_data%n_regions = n_alr_new do alr = 1, n_alr_new reg_data%regions(alr) = save_regions(alr_new_to_old (alr)) call add_pseudo_emitters (reg_data%regions(alr)) if (mod (alr, 2) == 0) reg_data%regions(alr)%pseudo_isr = .true. end do contains subroutine add_pseudo_emitters (sregion) type(singular_region_t), intent(inout) :: sregion type(ftuple_t), dimension(2) :: ftuples_save integer :: alr do alr = 1, 2 ftuples_save(alr) = sregion%ftuples(alr) end do deallocate (sregion%ftuples) sregion%nregions = sregion%nregions * 2 allocate (sregion%ftuples (sregion%nregions)) do alr = 1, sregion%nregions sregion%ftuples(alr) = ftuples_save (alr_new_to_old(alr)) if (mod (alr, 2) == 0) sregion%ftuples(alr)%pseudo_isr = .true. end do end subroutine add_pseudo_emitters end subroutine region_data_set_isr_pseudo_regions @ %def region_data_set_isr_pseudo_regions @ This subroutine splits up the ftuple-list of the singular regions into interference-free lists, i.e. lists which only contain the same emitter. This is relevant for factorized NLO calculations. In the current implementation, it is hand-tailored for the threshold computation, but should be generalized further in the future. <>= procedure :: split_up_interference_regions_for_threshold => & region_data_split_up_interference_regions_for_threshold <>= module subroutine region_data_split_up_interference_regions_for_threshold & (reg_data) class(region_data_t), intent(inout) :: reg_data end subroutine region_data_split_up_interference_regions_for_threshold <>= module subroutine region_data_split_up_interference_regions_for_threshold & (reg_data) class(region_data_t), intent(inout) :: reg_data integer :: alr, i_ftuple integer :: current_emitter integer :: i1, i2 integer :: n_new_reg type(ftuple_t), dimension(2) :: ftuples do alr = 1, reg_data%n_regions associate (region => reg_data%regions(alr)) current_emitter = region%emitter n_new_reg = 0 do i_ftuple = 1, region%nregions call region%ftuples(i_ftuple)%get (i1, i2) if (i1 == current_emitter) then n_new_reg = n_new_reg + 1 ftuples(n_new_reg) = region%ftuples(i_ftuple) end if end do deallocate (region%ftuples) allocate (region%ftuples(n_new_reg)) region%ftuples = ftuples (1 : n_new_reg) region%nregions = n_new_reg end associate end do reg_data%fks_mapping%normalization_factor = 0.5_default end subroutine region_data_split_up_interference_regions_for_threshold @ %def region_data_split_up_interference_regions_for_threshold @ <>= procedure :: set_mass_color_and_charge => & region_data_set_mass_color_and_charge <>= module subroutine region_data_set_mass_color_and_charge (reg_data, model) class(region_data_t), intent(inout) :: reg_data type(model_t), intent(in) :: model end subroutine region_data_set_mass_color_and_charge <>= module subroutine region_data_set_mass_color_and_charge (reg_data, model) class(region_data_t), intent(inout) :: reg_data type(model_t), intent(in) :: model integer :: i do i = 1, reg_data%n_regions associate (region => reg_data%regions(i)) call region%flst_uborn%init_mass_color_and_charge (model) call region%flst_real%init_mass_color_and_charge (model) end associate end do do i = 1, reg_data%n_flv_born call reg_data%flv_born(i)%init_mass_color_and_charge (model) end do do i = 1, size (reg_data%flv_real) call reg_data%flv_real(i)%init_mass_color_and_charge (model) end do end subroutine region_data_set_mass_color_and_charge @ %def region_data_set_mass_color_and_charge @ <>= procedure :: uses_resonances => region_data_uses_resonances <>= module function region_data_uses_resonances (reg_data) result (val) logical :: val class(region_data_t), intent(in) :: reg_data end function region_data_uses_resonances <>= module function region_data_uses_resonances (reg_data) result (val) logical :: val class(region_data_t), intent(in) :: reg_data select type (fks_mapping => reg_data%fks_mapping) type is (fks_mapping_resonances_t) val = .true. class default val = .false. end select end function region_data_uses_resonances @ %def region_data_uses_resonances @ Creates a list containing the emitter of each singular region. <>= procedure :: get_emitter_list => region_data_get_emitter_list <>= pure module function region_data_get_emitter_list & (reg_data) result (emitters) class(region_data_t), intent(in) :: reg_data integer, dimension(:), allocatable :: emitters end function region_data_get_emitter_list <>= pure module function region_data_get_emitter_list (reg_data) result (emitters) class(region_data_t), intent(in) :: reg_data integer, dimension(:), allocatable :: emitters integer :: i allocate (emitters (reg_data%n_regions)) do i = 1, reg_data%n_regions emitters(i) = reg_data%regions(i)%emitter end do end function region_data_get_emitter_list @ %def region_data_get_emitter_list @ Returns the number of emitters not equal to 0 to avoid double counting between emitters 0, 1 and 2. <>= procedure :: get_n_emitters_sc => region_data_get_n_emitters_sc <>= module function region_data_get_n_emitters_sc & (reg_data) result (n_emitters_sc) class(region_data_t), intent(in) :: reg_data integer :: n_emitters_sc end function region_data_get_n_emitters_sc <>= module function region_data_get_n_emitters_sc & (reg_data) result (n_emitters_sc) class(region_data_t), intent(in) :: reg_data integer :: n_emitters_sc n_emitters_sc = count (reg_data%emitters /= 0) end function region_data_get_n_emitters_sc @ %def region_data_get_n_emitters_sc @ <>= procedure :: get_associated_resonances => & region_data_get_associated_resonances <>= module function region_data_get_associated_resonances & (reg_data, emitter) result (res) integer, dimension(:), allocatable :: res class(region_data_t), intent(in) :: reg_data integer, intent(in) :: emitter end function region_data_get_associated_resonances <>= module function region_data_get_associated_resonances & (reg_data, emitter) result (res) integer, dimension(:), allocatable :: res class(region_data_t), intent(in) :: reg_data integer, intent(in) :: emitter integer :: alr, i integer :: n_res select type (fks_mapping => reg_data%fks_mapping) type is (fks_mapping_resonances_t) n_res = 0 do alr = 1, reg_data%n_regions if (reg_data%regions(alr)%emitter == emitter) & n_res = n_res + 1 end do if (n_res > 0) then allocate (res (n_res)) else return end if i = 1 do alr = 1, reg_data%n_regions if (reg_data%regions(alr)%emitter == emitter) then res (i) = fks_mapping%res_map%alr_to_i_res (alr) i = i + 1 end if end do end select end function region_data_get_associated_resonances @ %def region_data_get_associated_resonances @ <>= procedure :: emitter_is_compatible_with_resonance => & region_data_emitter_is_compatible_with_resonance <>= module function region_data_emitter_is_compatible_with_resonance & (reg_data, i_res, emitter) result (compatible) logical :: compatible class(region_data_t), intent(in) :: reg_data integer, intent(in) :: i_res, emitter end function region_data_emitter_is_compatible_with_resonance <>= module function region_data_emitter_is_compatible_with_resonance & (reg_data, i_res, emitter) result (compatible) logical :: compatible class(region_data_t), intent(in) :: reg_data integer, intent(in) :: i_res, emitter integer :: i_res_alr, alr compatible = .false. select type (fks_mapping => reg_data%fks_mapping) type is (fks_mapping_resonances_t) do alr = 1, reg_data%n_regions i_res_alr = fks_mapping%res_map%alr_to_i_res (alr) if (i_res_alr == i_res .and. reg_data%get_emitter(alr) == emitter) then compatible = .true. exit end if end do end select end function region_data_emitter_is_compatible_with_resonance @ %def region_data_emitter_is_compatible_with_resonance @ <>= procedure :: emitter_is_in_resonance => region_data_emitter_is_in_resonance <>= module function region_data_emitter_is_in_resonance & (reg_data, i_res, emitter) result (exist) logical :: exist class(region_data_t), intent(in) :: reg_data integer, intent(in) :: i_res, emitter end function region_data_emitter_is_in_resonance <>= module function region_data_emitter_is_in_resonance & (reg_data, i_res, emitter) result (exist) logical :: exist class(region_data_t), intent(in) :: reg_data integer, intent(in) :: i_res, emitter integer :: i exist = .false. select type (fks_mapping => reg_data%fks_mapping) type is (fks_mapping_resonances_t) associate (res_history => fks_mapping%res_map%res_histories(i_res)) do i = 1, res_history%n_resonances exist = exist .or. & any (res_history%resonances(i)%contributors%c == emitter) end do end associate end select end function region_data_emitter_is_in_resonance @ %def region_data_emitter_is_in_resonance @ <>= procedure :: get_contributors => region_data_get_contributors <>= module subroutine region_data_get_contributors & (reg_data, i_res, emitter, c, success) class(region_data_t), intent(in) :: reg_data integer, intent(in) :: i_res, emitter integer, intent(inout), dimension(:), allocatable :: c logical, intent(out) :: success end subroutine region_data_get_contributors <>= module subroutine region_data_get_contributors & (reg_data, i_res, emitter, c, success) class(region_data_t), intent(in) :: reg_data integer, intent(in) :: i_res, emitter integer, intent(inout), dimension(:), allocatable :: c logical, intent(out) :: success integer :: i success = .false. select type (fks_mapping => reg_data%fks_mapping) type is (fks_mapping_resonances_t) associate (res_history => fks_mapping%res_map%res_histories (i_res)) do i = 1, res_history%n_resonances if (any (res_history%resonances(i)%contributors%c == emitter)) then allocate (c (size (res_history%resonances(i)%contributors%c))) c = res_history%resonances(i)%contributors%c success = .true. exit end if end do end associate end select end subroutine region_data_get_contributors @ %def region_data_get_contributors @ <>= procedure :: get_emitter => region_data_get_emitter <>= pure module function region_data_get_emitter & (reg_data, alr) result (emitter) class(region_data_t), intent(in) :: reg_data integer, intent(in) :: alr integer :: emitter end function region_data_get_emitter <>= pure module function region_data_get_emitter (reg_data, alr) result (emitter) class(region_data_t), intent(in) :: reg_data integer, intent(in) :: alr integer :: emitter emitter = reg_data%regions(alr)%emitter end function region_data_get_emitter @ %def region_data_get_emitter @ <>= procedure :: map_real_to_born_index => region_data_map_real_to_born_index <>= module function region_data_map_real_to_born_index & (reg_data, real_index) result (uborn_index) integer :: uborn_index class(region_data_t), intent(in) :: reg_data integer, intent(in) :: real_index end function region_data_map_real_to_born_index <>= module function region_data_map_real_to_born_index & (reg_data, real_index) result (uborn_index) integer :: uborn_index class(region_data_t), intent(in) :: reg_data integer, intent(in) :: real_index integer :: alr uborn_index = 0 do alr = 1, size (reg_data%regions) if (reg_data%regions(alr)%real_index == real_index) then uborn_index = reg_data%regions(alr)%uborn_index exit end if end do end function region_data_map_real_to_born_index @ %def region_data_map_real_to_born_index @ <>= generic :: get_flv_states_born => get_flv_states_born_single, & get_flv_states_born_array procedure :: get_flv_states_born_single => & region_data_get_flv_states_born_single procedure :: get_flv_states_born_array => & region_data_get_flv_states_born_array <>= module function region_data_get_flv_states_born_array & (reg_data) result (flv_states) integer, dimension(:,:), allocatable :: flv_states class(region_data_t), intent(in) :: reg_data end function region_data_get_flv_states_born_array module function region_data_get_flv_states_born_single & (reg_data, i_flv) result (flv_states) integer, dimension(:), allocatable :: flv_states class(region_data_t), intent(in) :: reg_data integer, intent(in) :: i_flv end function region_data_get_flv_states_born_single <>= module function region_data_get_flv_states_born_array & (reg_data) result (flv_states) integer, dimension(:,:), allocatable :: flv_states class(region_data_t), intent(in) :: reg_data integer :: i_flv allocate (flv_states (reg_data%n_legs_born, reg_data%n_flv_born)) do i_flv = 1, reg_data%n_flv_born flv_states (:, i_flv) = reg_data%flv_born(i_flv)%flst end do end function region_data_get_flv_states_born_array module function region_data_get_flv_states_born_single & (reg_data, i_flv) result (flv_states) integer, dimension(:), allocatable :: flv_states class(region_data_t), intent(in) :: reg_data integer, intent(in) :: i_flv allocate (flv_states (reg_data%n_legs_born)) flv_states = reg_data%flv_born(i_flv)%flst end function region_data_get_flv_states_born_single @ %def region_data_get_flv_states_born @ <>= generic :: get_flv_states_real => & get_flv_states_real_single, get_flv_states_real_array procedure :: get_flv_states_real_single => & region_data_get_flv_states_real_single procedure :: get_flv_states_real_array => & region_data_get_flv_states_real_array <>= module function region_data_get_flv_states_real_single & (reg_data, i_flv) result (flv_states) integer, dimension(:), allocatable :: flv_states class(region_data_t), intent(in) :: reg_data integer, intent(in) :: i_flv end function region_data_get_flv_states_real_single module function region_data_get_flv_states_real_array & (reg_data) result (flv_states) integer, dimension(:,:), allocatable :: flv_states class(region_data_t), intent(in) :: reg_data end function region_data_get_flv_states_real_array <>= module function region_data_get_flv_states_real_single & (reg_data, i_flv) result (flv_states) integer, dimension(:), allocatable :: flv_states class(region_data_t), intent(in) :: reg_data integer, intent(in) :: i_flv integer :: i_reg allocate (flv_states (reg_data%n_legs_real)) do i_reg = 1, reg_data%n_regions if (i_flv == reg_data%regions(i_reg)%real_index) then flv_states = reg_data%regions(i_reg)%flst_real%flst exit end if end do end function region_data_get_flv_states_real_single module function region_data_get_flv_states_real_array & (reg_data) result (flv_states) integer, dimension(:,:), allocatable :: flv_states class(region_data_t), intent(in) :: reg_data integer :: i_flv allocate (flv_states (reg_data%n_legs_real, reg_data%n_flv_real)) do i_flv = 1, reg_data%n_flv_real flv_states (:, i_flv) = reg_data%get_flv_states_real (i_flv) end do end function region_data_get_flv_states_real_array @ %def region_data_get_flv_states_real @ <>= procedure :: get_all_flv_states => region_data_get_all_flv_states <>= module subroutine region_data_get_all_flv_states & (reg_data, flv_born, flv_real) class(region_data_t), intent(in) :: reg_data integer, dimension(:,:), allocatable, intent(out) :: flv_born, flv_real end subroutine region_data_get_all_flv_states <>= module subroutine region_data_get_all_flv_states & (reg_data, flv_born, flv_real) class(region_data_t), intent(in) :: reg_data integer, dimension(:,:), allocatable, intent(out) :: flv_born, flv_real allocate (flv_born (reg_data%n_legs_born, reg_data%n_flv_born)) flv_born = reg_data%get_flv_states_born () allocate (flv_real (reg_data%n_legs_real, reg_data%n_flv_real)) flv_real = reg_data%get_flv_states_real () end subroutine region_data_get_all_flv_states @ %def region_data_get_all_flv_states @ <>= procedure :: get_n_in => region_data_get_n_in <>= module function region_data_get_n_in (reg_data) result (n_in) integer :: n_in class(region_data_t), intent(in) :: reg_data end function region_data_get_n_in <>= module function region_data_get_n_in (reg_data) result (n_in) integer :: n_in class(region_data_t), intent(in) :: reg_data n_in = reg_data%n_in end function region_data_get_n_in @ %def region_data_get_n_in @ <>= procedure :: get_n_legs_real => region_data_get_n_legs_real <>= module function region_data_get_n_legs_real (reg_data) result (n_legs) integer :: n_legs class(region_data_t), intent(in) :: reg_data end function region_data_get_n_legs_real <>= module function region_data_get_n_legs_real (reg_data) result (n_legs) integer :: n_legs class(region_data_t), intent(in) :: reg_data n_legs = reg_data%n_legs_real end function region_data_get_n_legs_real @ %def region_data_get_n_legs_real <>= procedure :: get_n_legs_born => region_data_get_n_legs_born <>= module function region_data_get_n_legs_born (reg_data) result (n_legs) integer :: n_legs class(region_data_t), intent(in) :: reg_data end function region_data_get_n_legs_born <>= module function region_data_get_n_legs_born (reg_data) result (n_legs) integer :: n_legs class(region_data_t), intent(in) :: reg_data n_legs = reg_data%n_legs_born end function region_data_get_n_legs_born @ %def region_data_get_n_legs_born <>= procedure :: get_n_flv_real => region_data_get_n_flv_real <>= module function region_data_get_n_flv_real (reg_data) result (n_flv) integer :: n_flv class(region_data_t), intent(in) :: reg_data end function region_data_get_n_flv_real <>= module function region_data_get_n_flv_real (reg_data) result (n_flv) integer :: n_flv class(region_data_t), intent(in) :: reg_data n_flv = reg_data%n_flv_real end function region_data_get_n_flv_real @ %def region_data_get_n_flv_real <>= procedure :: get_n_flv_born => region_data_get_n_flv_born <>= module function region_data_get_n_flv_born (reg_data) result (n_flv) integer :: n_flv class(region_data_t), intent(in) :: reg_data end function region_data_get_n_flv_born <>= module function region_data_get_n_flv_born (reg_data) result (n_flv) integer :: n_flv class(region_data_t), intent(in) :: reg_data n_flv = reg_data%n_flv_born end function region_data_get_n_flv_born @ %def region_data_get_n_flv_born @ Returns $S_i = \frac{1}{\mathcal{D}d_i}$ or $S_{ij} = \frac{1}{\mathcal{D}d_{ij}}$ for one particular singular region. At this point, the flavor array should be rearranged in such a way that the emitted particle is at the last position of the flavor structure list. <>= generic :: get_svalue => get_svalue_last_pos, get_svalue_ij procedure :: get_svalue_last_pos => region_data_get_svalue_last_pos procedure :: get_svalue_ij => region_data_get_svalue_ij <>= module function region_data_get_svalue_ij & (reg_data, p_real, alr, i, j, i_res) result (sval) class(region_data_t), intent(inout) :: reg_data type(vector4_t), intent(in), dimension(:) :: p_real integer, intent(in) :: alr, i, j integer, intent(in) :: i_res real(default) :: sval end function region_data_get_svalue_ij module function region_data_get_svalue_last_pos & (reg_data, p, alr, emitter, i_res) result (sval) class(region_data_t), intent(inout) :: reg_data type(vector4_t), intent(in), dimension(:) :: p integer, intent(in) :: alr, emitter integer, intent(in) :: i_res real(default) :: sval end function region_data_get_svalue_last_pos <>= module function region_data_get_svalue_ij & (reg_data, p_real, alr, i, j, i_res) result (sval) class(region_data_t), intent(inout) :: reg_data type(vector4_t), intent(in), dimension(:) :: p_real integer, intent(in) :: alr, i, j integer, intent(in) :: i_res real(default) :: sval associate (map => reg_data%fks_mapping) call map%compute_sumdij (reg_data%regions(alr), p_real) select type (map) type is (fks_mapping_resonances_t) map%i_con = reg_data%alr_to_i_contributor (alr) end select map%pseudo_isr = reg_data%regions(alr)%pseudo_isr sval = map%svalue (p_real, i, j, i_res) * map%normalization_factor end associate end function region_data_get_svalue_ij module function region_data_get_svalue_last_pos & (reg_data, p, alr, emitter, i_res) result (sval) class(region_data_t), intent(inout) :: reg_data type(vector4_t), intent(in), dimension(:) :: p integer, intent(in) :: alr, emitter integer, intent(in) :: i_res real(default) :: sval sval = reg_data%get_svalue (p, alr, emitter, reg_data%n_legs_real, i_res) end function region_data_get_svalue_last_pos @ %def region_data_get_svalue @ The same as above, but for the soft limit. <>= procedure :: get_svalue_soft => region_data_get_svalue_soft <>= module function region_data_get_svalue_soft & (reg_data, p_born, p_soft, alr, emitter, i_res) result (sval) class(region_data_t), intent(inout) :: reg_data type(vector4_t), intent(in), dimension(:) :: p_born type(vector4_t), intent(in) :: p_soft integer, intent(in) :: alr, emitter, i_res real(default) :: sval end function region_data_get_svalue_soft <>= module function region_data_get_svalue_soft & (reg_data, p_born, p_soft, alr, emitter, i_res) result (sval) class(region_data_t), intent(inout) :: reg_data type(vector4_t), intent(in), dimension(:) :: p_born type(vector4_t), intent(in) :: p_soft integer, intent(in) :: alr, emitter, i_res real(default) :: sval associate (map => reg_data%fks_mapping) call map%compute_sumdij_soft (reg_data%regions(alr), p_born, p_soft) select type (map) type is (fks_mapping_resonances_t) map%i_con = reg_data%alr_to_i_contributor (alr) end select map%pseudo_isr = reg_data%regions(alr)%pseudo_isr sval = map%svalue_soft (p_born, p_soft, emitter, i_res) * & map%normalization_factor end associate end function region_data_get_svalue_soft @ %def region_data_get_svalue_soft @ This subroutine starts with a specification of $N$- and $N+1$-particle configurations, [[flst_born]] and [[flst_real]], saved in [[reg_data]]. From these, it creates a list of fundamental tuples, a list of emitters and a list containing the $N+1$-particle configuration, rearranged in such a way that the emitter-radiation pair is last ([[flst_alr]]). For the $e^+ \, e^- \, \rightarrow u \, \bar{u} \, g$- example, the generated objects are shown in table \ref{table:ftuples and flavors}. Note that at this point, [[flst_alr]] is arranged in such a way that the emitter can only be equal to $n_{legs}-1$ for final-state radiation or 0, 1, or 2 for initial-state radiation. Further, it occurs that regions can be equivalent. For example in table \ref{table:ftuples and flavors} the regions corresponding to \texttt{alr} = 1 and \texttt{alr} = 3 as well as \texttt{alr} = 2 and \texttt{alr} = 4 describe the same physics and are therefore equivalent. @ <>= procedure :: find_regions => region_data_find_regions <>= module subroutine region_data_find_regions & (reg_data, model, ftuples, emitters, flst_alr) class(region_data_t), intent(in) :: reg_data type(model_t), intent(in) :: model type(ftuple_list_t), intent(out), dimension(:), allocatable :: ftuples integer, intent(out), dimension(:), allocatable :: emitters type(flv_structure_t), intent(out), dimension(:), allocatable :: flst_alr end subroutine region_data_find_regions <>= module subroutine region_data_find_regions & (reg_data, model, ftuples, emitters, flst_alr) class(region_data_t), intent(in) :: reg_data type(model_t), intent(in) :: model type(ftuple_list_t), intent(out), dimension(:), allocatable :: ftuples integer, intent(out), dimension(:), allocatable :: emitters type(flv_structure_t), intent(out), dimension(:), allocatable :: flst_alr type(ftuple_list_t), dimension(:,:), allocatable :: ftuples_tmp integer, dimension(:,:), allocatable :: ftuple_index integer :: n_born, n_real integer :: n_legreal integer :: i_born, i_real, i_ftuple integer :: last_registered_i_born, last_registered_i_real n_born = size (reg_data%flv_born) n_real = size (reg_data%flv_real) n_legreal = size (reg_data%flv_real(1)%flst) allocate (emitters (0)) allocate (flst_alr (0)) allocate (ftuples (0)) i_ftuple = 0 last_registered_i_born = 0; last_registered_i_real = 0 do i_real = 1, n_real do i_born = 1, n_born call setup_flsts_emitters_and_ftuples_fsr & (i_real, i_born, i_ftuple, flst_alr, emitters, ftuples) call setup_flsts_emitters_and_ftuples_isr & (i_real, i_born, i_ftuple, flst_alr, emitters, ftuples) end do end do contains function incr_i_ftuple_if_required (i_born, i_real, i_ftuple_in) result (i_ftuple) integer :: i_ftuple integer, intent(in) :: i_born, i_real, i_ftuple_in if (last_registered_i_born /= i_born .or. last_registered_i_real /= i_real) then last_registered_i_born = i_born last_registered_i_real = i_real i_ftuple = i_ftuple_in + 1 else i_ftuple = i_ftuple_in end if end function incr_i_ftuple_if_required subroutine setup_flsts_emitters_and_ftuples_fsr & (i_real, i_born, i_ftuple, flst_alr, emitters, ftuples) integer, intent(in) :: i_real, i_born integer, intent(inout) :: i_ftuple type(flv_structure_t), intent(inout), dimension(:), allocatable :: flst_alr integer, intent(inout), dimension(:), allocatable :: emitters type(ftuple_list_t), intent(inout), dimension(:), allocatable :: ftuples type(ftuple_list_t) :: ftuples_tmp type(flv_structure_t) :: flst_alr_tmp type(ftuple_t) :: current_ftuple integer :: leg1, leg2 logical :: valid associate (flv_born => reg_data%flv_born(i_born), & flv_real => reg_data%flv_real(i_real)) do leg1 = reg_data%n_in + 1, n_legreal do leg2 = leg1 + 1, n_legreal valid = flv_real%valid_pair(leg1, leg2, flv_born, model) if (valid) then if (is_vector(flv_real%flst(leg1)) .and. & is_fermion(flv_real%flst(leg2))) then flst_alr_tmp = create_alr (flv_real, & reg_data%n_in, leg2, leg1) else flst_alr_tmp = create_alr (flv_real, & reg_data%n_in, leg1, leg2) end if flst_alr = [flst_alr, flst_alr_tmp] emitters = [emitters, n_legreal - 1] call current_ftuple%set (leg1, leg2) call current_ftuple%determine_splitting_type_fsr & (flv_real, leg1, leg2) call current_ftuple%determine_sub_correction_type & (flv_born, flv_real, leg1, leg2) i_ftuple = incr_i_ftuple_if_required (i_born, i_real, i_ftuple) if (i_ftuple > size (ftuples)) then call ftuples_tmp%append (current_ftuple) ftuples = [ftuples, ftuples_tmp] else call ftuples(i_ftuple)%append (current_ftuple) end if end if end do end do end associate end subroutine setup_flsts_emitters_and_ftuples_fsr subroutine setup_flsts_emitters_and_ftuples_isr & (i_real, i_born, i_ftuple, flst_alr, emitters, ftuples) integer, intent(in) :: i_real, i_born integer, intent(inout) :: i_ftuple type(flv_structure_t), intent(inout), dimension(:), allocatable :: flst_alr integer, intent(inout), dimension(:), allocatable :: emitters type(ftuple_list_t), intent(inout), dimension(:), allocatable :: ftuples type(ftuple_list_t) :: ftuples_tmp type(flv_structure_t) :: flst_alr_tmp type(ftuple_t) :: current_ftuple integer :: leg, emitter logical :: valid1, valid2 associate (flv_born => reg_data%flv_born(i_born), & flv_real => reg_data%flv_real(i_real)) do leg = reg_data%n_in + 1, n_legreal valid1 = flv_real%valid_pair(1, leg, flv_born, model) if (reg_data%n_in > 1) then valid2 = flv_real%valid_pair(2, leg, flv_born, model) else valid2 = .false. end if if (valid1 .and. valid2) then emitter = 0 else if (valid1 .and. .not. valid2) then emitter = 1 else if (.not. valid1 .and. valid2) then emitter = 2 else emitter = -1 end if if (valid1 .or. valid2) then flst_alr_tmp = create_alr (flv_real, reg_data%n_in, emitter, leg) flst_alr = [flst_alr, flst_alr_tmp] emitters = [emitters, emitter] call current_ftuple%set(emitter, leg) call current_ftuple%determine_splitting_type_isr & (flv_real, emitter, leg) call current_ftuple%determine_sub_correction_type & (flv_born, flv_real, emitter, leg) i_ftuple = incr_i_ftuple_if_required (i_born, i_real, i_ftuple) if (i_ftuple > size (ftuples)) then call ftuples_tmp%append (current_ftuple) ftuples = [ftuples, ftuples_tmp] else call ftuples(i_ftuple)%append (current_ftuple) end if end if end do end associate end subroutine setup_flsts_emitters_and_ftuples_isr end subroutine region_data_find_regions @ %def region_data_find_regions @ We transfer the mapping of flavor structures that lead to the same amplitude (with structure functions already accounted for!) to the Born and real [[flv_structure]] of each [[singular_region]]. We then use this information, besides other data of each [[singular_region]], to determine which produce the same amplitude for the non-subtracted real and real subtraction terms and set up the equivalence index mapping for each region. <>= procedure :: find_eqv_regions => region_data_find_eqv_regions <>= module subroutine region_data_find_eqv_regions (reg_data, optimize) class(region_data_t), intent(inout) :: reg_data logical, intent(in) :: optimize end subroutine region_data_find_eqv_regions <>= module subroutine region_data_find_eqv_regions (reg_data, optimize) class(region_data_t), intent(inout) :: reg_data logical, intent(in) :: optimize integer :: n_reg, alr1, alr2 n_reg = reg_data%n_regions if (optimize) then do alr1 = 1, n_reg reg_data%regions(alr1)%flst_uborn%eqv_index = & reg_data%eqv_flv_index_born(reg_data%regions(alr1)%uborn_index) reg_data%regions(alr1)%flst_real%eqv_index = & reg_data%eqv_flv_index_real(reg_data%regions(alr1)%real_index) end do do alr1 = 1, n_reg do alr2 = 1, alr1 if (reg_data%regions(alr2) .match. reg_data%regions(alr1)) then reg_data%regions(alr1)%eqv_index = alr2 exit end if end do end do else do alr1 = 1, n_reg reg_data%regions(alr1)%eqv_index = alr1 end do end if end subroutine region_data_find_eqv_regions @ %def region_data_find_eqv_regions @ Creates singular regions according to table \ref{table:singular regions}. It scans all regions in table \ref{table:ftuples and flavors} and records the real flavor structures. If they are equivalent, the flavor structure is not recorded, but the multiplicity of the present one is increased. <>= procedure :: init_singular_regions => region_data_init_singular_regions <>= module subroutine region_data_init_singular_regions & (reg_data, ftuples, emitter, flv_alr, nlo_correction_type) class(region_data_t), intent(inout) :: reg_data type(ftuple_list_t), intent(inout), dimension(:), allocatable :: ftuples type(string_t), intent(in) :: nlo_correction_type integer, intent(in), dimension(:) :: emitter type(flv_structure_t), intent(in), dimension(:) :: flv_alr end subroutine region_data_init_singular_regions <>= module subroutine region_data_init_singular_regions & (reg_data, ftuples, emitter, flv_alr, nlo_correction_type) class(region_data_t), intent(inout) :: reg_data type(ftuple_list_t), intent(inout), dimension(:), allocatable :: ftuples type(string_t), intent(in) :: nlo_correction_type type(string_t), dimension(:), allocatable :: nlo_correction_type_dyn integer, intent(in), dimension(:) :: emitter integer :: n_independent_flv type(flv_structure_t), intent(in), dimension(:) :: flv_alr type(flv_structure_t), dimension(:), allocatable :: flv_uborn, & flv_alr_registered integer, dimension(:), allocatable :: mult integer, dimension(:), allocatable :: flst_emitter integer :: n_regions, maxregions integer, dimension(:), allocatable :: index integer :: i, i_flv, n_legs logical :: equiv, valid_fs_splitting, pure_corr_type, & corr_type_valid, non_singular_reg integer :: i_first, i_reg, i_reg_prev integer, dimension(:), allocatable :: region_to_ftuple, alr_limits integer, dimension(:), allocatable :: equiv_index maxregions = size (emitter) n_legs = flv_alr(1)%nlegs allocate (flv_uborn (maxregions)) allocate (flv_alr_registered (maxregions)) allocate (mult (maxregions)) mult = 0 allocate (flst_emitter (maxregions)) allocate (index (0)) allocate (region_to_ftuple (maxregions)) allocate (equiv_index (maxregions)) allocate (nlo_correction_type_dyn (maxregions)) call setup_region_mappings (n_independent_flv, alr_limits, region_to_ftuple) nlo_correction_type_dyn = nlo_correction_type i_first = 1 i_reg = 1 SCAN_FLAVORS: do i_flv = 1, n_independent_flv SCAN_FTUPLES: do i = i_first, i_first + alr_limits (i_flv) - 1 equiv = .false. corr_type_valid = .true. non_singular_reg = .false. if (i == i_first) then flv_alr_registered(i_reg) = flv_alr(i) if (nlo_correction_type == "EW" .and. & reg_data%alphas_power > 0) then nlo_correction_type_dyn (i_reg) = & set_dynamic_correction_type (i) end if flv_uborn(i_reg) = flv_alr(i)%create_uborn (emitter(i), & nlo_correction_type_dyn (i_reg)) flst_emitter(i_reg) = emitter(i) equiv_index(i_reg) = region_to_ftuple(i) if (nlo_correction_type == "EW" .and. reg_data%alphas_power > 0) then corr_type_valid = (nlo_correction_type_dyn (i_reg) == "EW" .and. & query_coupling_powers (flv_uborn(i_reg)%flst, & reg_data%alpha_power, reg_data%alphas_power)) & .or. (nlo_correction_type_dyn (i_reg) == "QCD" .and. & query_coupling_powers (flv_uborn(i_reg)%flst, & reg_data%alpha_power + 1, reg_data%alphas_power - 1)) non_singular_reg = .not. corr_type_valid .and. & qcd_ew_interferences (flv_alr_registered(i_reg)%flst) & .and. query_coupling_powers (flv_alr_registered(i_reg)%flst, & reg_data%alpha_power+2, reg_data%alphas_power-1) & .and. .not. qcd_ew_interferences (flv_uborn(i_reg)%flst) & .and. nlo_correction_type_dyn (i_reg) == "QCD" if (non_singular_reg) nlo_correction_type_dyn (i_reg) = "none" end if if (corr_type_valid .or. non_singular_reg) then mult(i_reg) = mult(i_reg) + 1 index = [index, region_to_real_index(ftuples, i)] i_reg = i_reg + 1 end if else !!! Check for equivalent flavor structures do i_reg_prev = 1, i_reg - 1 if (emitter(i) == flst_emitter(i_reg_prev) .and. emitter(i) > reg_data%n_in) then valid_fs_splitting = check_fs_splitting & (flv_alr(i)%get_last_two(n_legs), & flv_alr_registered(i_reg_prev)%get_last_two(n_legs), & flv_alr(i)%tag(n_legs - 1), & flv_alr_registered(i_reg_prev)%tag(n_legs - 1)) if (nlo_correction_type == "EW" .and. reg_data%alphas_power > 0) then nlo_correction_type_dyn (i_reg) = set_dynamic_correction_type (i) end if pure_corr_type = nlo_correction_type_dyn (i_reg) & == nlo_correction_type_dyn (i_reg_prev) if ((flv_alr(i) .equiv. flv_alr_registered(i_reg_prev)) & .and. valid_fs_splitting .and. pure_corr_type) then mult(i_reg_prev) = mult(i_reg_prev) + 1 equiv = .true. call ftuples(region_to_real_index(ftuples, i))%set_equiv & (equiv_index(i_reg_prev), region_to_ftuple(i)) exit end if else if (emitter(i) == flst_emitter(i_reg_prev) .and. emitter(i) <= reg_data%n_in) then if (nlo_correction_type == "EW" .and. reg_data%alphas_power > 0) then nlo_correction_type_dyn (i_reg) = set_dynamic_correction_type (i) end if pure_corr_type = nlo_correction_type_dyn (i_reg) & == nlo_correction_type_dyn (i_reg_prev) if ((flv_alr(i) .equiv. flv_alr_registered(i_reg_prev)) & .and. pure_corr_type) then mult(i_reg_prev) = mult(i_reg_prev) + 1 equiv = .true. call ftuples(region_to_real_index(ftuples, i))%set_equiv & (equiv_index(i_reg_prev), region_to_ftuple(i)) exit end if end if end do if (.not. equiv) then flv_alr_registered(i_reg) = flv_alr(i) if (nlo_correction_type == "EW" .and. reg_data%alphas_power > 0) then nlo_correction_type_dyn (i_reg) = set_dynamic_correction_type (i) end if flv_uborn(i_reg) = flv_alr(i)%create_uborn (emitter(i), & nlo_correction_type_dyn (i_reg)) flst_emitter(i_reg) = emitter(i) equiv_index (i_reg) = region_to_ftuple(i) if (nlo_correction_type == "EW" .and. reg_data%alphas_power > 0) then corr_type_valid = (nlo_correction_type_dyn (i_reg) == "EW" .and. & query_coupling_powers (flv_uborn(i_reg)%flst, & reg_data%alpha_power, reg_data%alphas_power)) & .or. (nlo_correction_type_dyn (i_reg) == "QCD" .and. & query_coupling_powers (flv_uborn(i_reg)%flst, & reg_data%alpha_power + 1, reg_data%alphas_power - 1)) non_singular_reg = .not. corr_type_valid .and. & qcd_ew_interferences (flv_alr_registered(i_reg)%flst) & .and. query_coupling_powers (flv_alr_registered(i_reg)%flst, & reg_data%alpha_power+2, reg_data%alphas_power-1) & .and. .not. qcd_ew_interferences (flv_uborn(i_reg)%flst) & .and. nlo_correction_type_dyn (i_reg) == "QCD" if (non_singular_reg) nlo_correction_type_dyn (i_reg) = "none" end if if (corr_type_valid .or. non_singular_reg) then mult(i_reg) = mult(i_reg) + 1 index = [index, region_to_real_index(ftuples, i)] i_reg = i_reg + 1 end if end if end if end do SCAN_FTUPLES i_first = i_first + alr_limits(i_flv) end do SCAN_FLAVORS n_regions = i_reg - 1 allocate (reg_data%regions (n_regions)) reg_data%n_regions = n_regions call account_for_regions_from_other_uborns (ftuples) call init_regions_with_permuted_flavors () call assign_real_indices () deallocate (flv_uborn) deallocate (flv_alr_registered) deallocate (mult) deallocate (flst_emitter) deallocate (index) deallocate (region_to_ftuple) deallocate (equiv_index) contains subroutine account_for_regions_from_other_uborns (ftuples) type(ftuple_list_t), intent(inout), dimension(:), allocatable :: ftuples integer :: alr1, alr2, i type(ftuple_t), dimension(:), allocatable :: ftuples_alr1, ftuples_alr2 logical, dimension(:,:), allocatable :: equivalences do alr1 = 1, n_regions do alr2 = 1, n_regions if (index(alr1) == index(alr2)) cycle if (flv_alr_registered(alr1) .equiv. flv_alr_registered(alr2)) then call ftuples(index(alr1))%to_array (ftuples_alr1, equivalences, .false.) call ftuples(index(alr2))%to_array (ftuples_alr2, equivalences, .false.) do i = 1, size (ftuples_alr2) if (.not. any (ftuple_equal_ireg (ftuples_alr1, ftuples_alr2(i)))) then call ftuples(index(alr1))%append (ftuples_alr2(i)) end if end do end if end do end do end subroutine account_for_regions_from_other_uborns subroutine setup_region_mappings (n_independent_flv, & alr_limits, region_to_ftuple) integer, intent(inout) :: n_independent_flv integer, intent(inout), dimension(:), allocatable :: alr_limits integer, intent(inout), dimension(:), allocatable :: region_to_ftuple integer :: i, j, i_flv if (any (ftuples%get_n_tuples() == 0)) & call msg_fatal ("Inconsistent collection of FKS pairs!") n_independent_flv = size (ftuples) alr_limits = ftuples%get_n_tuples() if (.not. (sum (alr_limits) == maxregions)) & call msg_fatal ("Too many regions!") j = 1 do i_flv = 1, n_independent_flv do i = 1, alr_limits(i_flv) region_to_ftuple(j) = i j = j + 1 end do end do end subroutine setup_region_mappings subroutine check_permutation (perm, flv_perm, flv_orig, i_reg) type(flv_perm_t), intent(in) :: perm type(flv_structure_t), intent(in) :: flv_perm, flv_orig integer, intent(in) :: i_reg type(flv_structure_t) :: flv_tmp flv_tmp = perm%apply (flv_orig, invert = .true.) if (.not. all (flv_tmp%flst == flv_perm%flst)) then print *, 'Fail at: ', i_reg print *, 'Original flavor structure: ', flv_orig%flst call perm%write () print *, 'Permuted flavor: ', flv_perm%flst print *, 'Should be: ', flv_tmp%flst call msg_fatal ("Permutation does not reproduce original flavor!") end if end subroutine check_permutation subroutine init_regions_with_permuted_flavors () type(flv_perm_t) :: perm_list type(ftuple_t), dimension(:), allocatable :: ftuple_array logical, dimension(:,:), allocatable :: equivalences integer :: i, j do j = 1, n_regions do i = 1, reg_data%n_flv_born if (reg_data%flv_born (i) .equiv. flv_uborn (j)) then call perm_list%reset () call perm_list%init (reg_data%flv_born(i), flv_uborn(j), & reg_data%n_in, reg_data%n_legs_born, .true.) flv_uborn(j) = perm_list%apply (flv_uborn(j)) flv_alr_registered(j) = perm_list%apply (flv_alr_registered(j)) flst_emitter(j) = perm_list%apply (flst_emitter(j)) end if end do call ftuples(index(j))%to_array (ftuple_array, equivalences, .false.) do i = 1, size (reg_data%flv_real) if (reg_data%flv_real(i) .equiv. flv_alr_registered(j)) then call perm_list%reset () call perm_list%init (flv_alr_registered(j), reg_data%flv_real(i), & reg_data%n_in, reg_data%n_legs_real, .false.) if (debug_active (D_SUBTRACTION)) call check_permutation & (perm_list, reg_data%flv_real(i), flv_alr_registered(j), j) ftuple_array = perm_list%apply (ftuple_array) call ftuple_sort_array (ftuple_array, equivalences) end if end do call reg_data%regions(j)%init (j, mult(j), 0, flv_alr_registered(j), & flv_uborn(j), reg_data%flv_born, flst_emitter(j), ftuple_array, & equivalences, nlo_correction_type_dyn (j)) if (allocated (ftuple_array)) deallocate (ftuple_array) if (allocated (equivalences)) deallocate (equivalences) end do end subroutine init_regions_with_permuted_flavors subroutine assign_real_indices () type(flv_structure_t) :: current_flv_real type(flv_structure_t), dimension(:), allocatable :: these_flv integer :: i_real, current_uborn_index integer :: i, j, this_i_real allocate (these_flv (size (flv_alr_registered))) i_real = 1 associate (regions => reg_data%regions) do i = 1, reg_data%n_regions do j = 1, size (these_flv) if (.not. allocated (these_flv(j)%flst)) then this_i_real = i_real call these_flv(i_real)%init (flv_alr_registered(i)%flst, reg_data%n_in) i_real = i_real + 1 exit else if (all (these_flv(j)%flst == flv_alr_registered(i)%flst)) then this_i_real = j exit end if end do regions(i)%real_index = this_i_real end do end associate deallocate (these_flv) end subroutine assign_real_indices function check_fs_splitting (flv1, flv2, tag1, tag2) result (valid) logical :: valid integer, intent(in), dimension(2) :: flv1, flv2 integer, intent(in) :: tag1, tag2 if (flv1(1) + flv1(2) == 0) then valid = abs(flv1(1)) == abs(flv2(1)) .and. abs(flv1(2)) == abs(flv2(2)) else valid = flv1(1) == flv2(1) .and. flv1(2) == flv2(2) .and. tag1 == tag2 end if end function check_fs_splitting function set_dynamic_correction_type (i_flv_alr) result (nlo_corr_type_dyn) type(string_t) :: nlo_corr_type_dyn type(ftuple_t) :: ftuple_tmp integer, intent(in) :: i_flv_alr ftuple_tmp = ftuples (region_to_real_index(ftuples, i_flv_alr))%get_ftuple & (region_to_ftuple(i_flv_alr)) if (ftuple_tmp%qcd_split) then nlo_corr_type_dyn = var_str ("QCD") else nlo_corr_type_dyn = var_str ("EW") end if end function set_dynamic_correction_type end subroutine region_data_init_singular_regions @ %def region_data_init_singular_regions @ Create an array containing all emitters and resonances of [[region_data]]. <>= procedure :: find_emitters => region_data_find_emitters <>= module subroutine region_data_find_emitters (reg_data) class(region_data_t), intent(inout) :: reg_data end subroutine region_data_find_emitters <>= module subroutine region_data_find_emitters (reg_data) class(region_data_t), intent(inout) :: reg_data integer :: alr, j, n_em, em integer, dimension(:), allocatable :: em_count allocate (em_count(reg_data%n_regions)) em_count = -1 n_em = 0 !!!Count the number of different emitters do alr = 1, reg_data%n_regions em = reg_data%regions(alr)%emitter if (.not. any (em_count == em)) then n_em = n_em + 1 em_count(alr) = em end if end do if (n_em < 1) call msg_fatal ("region_data_find_emitters: No emitters found!") reg_data%n_emitters = n_em allocate (reg_data%emitters (reg_data%n_emitters)) reg_data%emitters = -1 j = 1 do alr = 1, size (reg_data%regions) em = reg_data%regions(alr)%emitter if (.not. any (reg_data%emitters == em)) then reg_data%emitters(j) = em j = j + 1 end if end do end subroutine region_data_find_emitters @ %def region_data_find_emitters @ <>= procedure :: find_resonances => region_data_find_resonances <>= module subroutine region_data_find_resonances (reg_data) class(region_data_t), intent(inout) :: reg_data end subroutine region_data_find_resonances <>= module subroutine region_data_find_resonances (reg_data) class(region_data_t), intent(inout) :: reg_data integer :: alr, j, k, n_res, n_contr integer :: res integer, dimension(10) :: res_count type(resonance_contributors_t), dimension(10) :: contributors_count type(resonance_contributors_t) :: contributors integer :: i_res, emitter logical :: share_emitter res_count = -1 n_res = 0; n_contr = 0 !!! Count the number of different resonances do alr = 1, reg_data%n_regions select type (fks_mapping => reg_data%fks_mapping) type is (fks_mapping_resonances_t) res = fks_mapping%res_map%alr_to_i_res (alr) if (.not. any (res_count == res)) then n_res = n_res + 1 res_count(alr) = res end if end select end do if (n_res > 0) allocate (reg_data%resonances (n_res)) j = 1 select type (fks_mapping => reg_data%fks_mapping) type is (fks_mapping_resonances_t) do alr = 1, size (reg_data%regions) res = fks_mapping%res_map%alr_to_i_res (alr) if (.not. any (reg_data%resonances == res)) then reg_data%resonances(j) = res j = j + 1 end if end do allocate (reg_data%alr_to_i_contributor (size (reg_data%regions))) do alr = 1, size (reg_data%regions) i_res = fks_mapping%res_map%alr_to_i_res (alr) emitter = reg_data%regions(alr)%emitter call reg_data%get_contributors (i_res, emitter, contributors%c, share_emitter) if (.not. share_emitter) cycle if (.not. any (contributors_count == contributors)) then n_contr = n_contr + 1 contributors_count(alr) = contributors end if if (allocated (contributors%c)) deallocate (contributors%c) end do allocate (reg_data%alr_contributors (n_contr)) j = 1 do alr = 1, size (reg_data%regions) i_res = fks_mapping%res_map%alr_to_i_res (alr) emitter = reg_data%regions(alr)%emitter call reg_data%get_contributors (i_res, emitter, contributors%c, share_emitter) if (.not. share_emitter) cycle if (.not. any (reg_data%alr_contributors == contributors)) then reg_data%alr_contributors(j) = contributors reg_data%alr_to_i_contributor (alr) = j j = j + 1 else do k = 1, size (reg_data%alr_contributors) if (reg_data%alr_contributors(k) == contributors) exit end do reg_data%alr_to_i_contributor (alr) = k end if if (allocated (contributors%c)) deallocate (contributors%c) end do end select call reg_data%extend_ftuples (n_res) call reg_data%set_contributors () end subroutine region_data_find_resonances @ %def region_data_find_resonances @ <>= procedure :: set_i_phs_to_i_con => region_data_set_i_phs_to_i_con <>= module subroutine region_data_set_i_phs_to_i_con (reg_data) class(region_data_t), intent(inout) :: reg_data end subroutine region_data_set_i_phs_to_i_con <>= module subroutine region_data_set_i_phs_to_i_con (reg_data) class(region_data_t), intent(inout) :: reg_data integer :: alr integer :: i_res, emitter, i_con, i_phs, i_em type(phs_identifier_t), dimension(:), allocatable :: phs_id_tmp logical :: share_emitter, phs_exist type(resonance_contributors_t) :: contributors allocate (phs_id_tmp (reg_data%n_phs)) if (allocated (reg_data%resonances)) then allocate (reg_data%i_phs_to_i_con (reg_data%n_phs)) do i_em = 1, size (reg_data%emitters) emitter = reg_data%emitters(i_em) do i_res = 1, size (reg_data%resonances) if (reg_data%emitter_is_compatible_with_resonance (i_res, emitter)) then alr = find_alr (emitter, i_res) if (alr == 0) call msg_fatal ("Could not find requested alpha region!") i_con = reg_data%alr_to_i_contributor (alr) call reg_data%get_contributors (i_res, emitter, contributors%c, share_emitter) if (.not. share_emitter) cycle call check_for_phs_identifier & (phs_id_tmp, reg_data%n_in, emitter, contributors%c, phs_exist, i_phs) if (phs_id_tmp(i_phs)%emitter < 0) then phs_id_tmp(i_phs)%emitter = emitter allocate (phs_id_tmp(i_phs)%contributors (size (contributors%c))) phs_id_tmp(i_phs)%contributors = contributors%c end if reg_data%i_phs_to_i_con (i_phs) = i_con end if if (allocated (contributors%c)) deallocate (contributors%c) end do end do end if contains function find_alr (emitter, i_res) result (alr) integer :: alr integer, intent(in) :: emitter, i_res integer :: i do i = 1, reg_data%n_regions if (reg_data%regions(i)%emitter == emitter .and. & reg_data%regions(i)%i_res == i_res) then alr = i return end if end do alr = 0 end function find_alr end subroutine region_data_set_i_phs_to_i_con @ %def region_data_set_i_phs_to_i_con @ <>= procedure :: set_alr_to_i_phs => region_data_set_alr_to_i_phs <>= module subroutine region_data_set_alr_to_i_phs & (reg_data, phs_identifiers, alr_to_i_phs) class(region_data_t), intent(inout) :: reg_data type(phs_identifier_t), intent(in), dimension(:) :: phs_identifiers integer, intent(out), dimension(:) :: alr_to_i_phs end subroutine region_data_set_alr_to_i_phs <>= module subroutine region_data_set_alr_to_i_phs & (reg_data, phs_identifiers, alr_to_i_phs) class(region_data_t), intent(inout) :: reg_data type(phs_identifier_t), intent(in), dimension(:) :: phs_identifiers integer, intent(out), dimension(:) :: alr_to_i_phs integer :: alr, i_phs integer :: emitter, i_res type(resonance_contributors_t) :: contributors logical :: share_emitter, phs_exist do alr = 1, reg_data%n_regions associate (region => reg_data%regions(alr)) emitter = region%emitter i_res = region%i_res if (i_res /= 0) then call reg_data%get_contributors (i_res, emitter, & contributors%c, share_emitter) if (.not. share_emitter) cycle end if if (allocated (contributors%c)) then call check_for_phs_identifier (phs_identifiers, reg_data%n_in, & emitter, contributors%c, phs_exist = phs_exist, i_phs = i_phs) else call check_for_phs_identifier (phs_identifiers, reg_data%n_in, & emitter, phs_exist = phs_exist, i_phs = i_phs) end if if (.not. phs_exist) & call msg_fatal ("phs identifiers are not set up correctly!") alr_to_i_phs(alr) = i_phs end associate if (allocated (contributors%c)) deallocate (contributors%c) end do end subroutine region_data_set_alr_to_i_phs @ %def region_data_set_alr_to_i_phs @ <>= procedure :: set_contributors => region_data_set_contributors <>= module subroutine region_data_set_contributors (reg_data) class(region_data_t), intent(inout) :: reg_data end subroutine region_data_set_contributors <>= module subroutine region_data_set_contributors (reg_data) class(region_data_t), intent(inout) :: reg_data integer :: alr, i_res, i_reg, i_con integer :: i1, i2, i_em integer, dimension(:), allocatable :: contributors logical :: share_emitter do alr = 1, size (reg_data%regions) associate (sregion => reg_data%regions(alr)) allocate (sregion%i_reg_to_i_con (sregion%nregions)) do i_reg = 1, sregion%nregions call sregion%ftuples(i_reg)%get (i1, i2) i_em = get_emitter_index (i1, i2, reg_data%n_legs_real) i_res = sregion%ftuples(i_reg)%i_res call reg_data%get_contributors & (i_res, i_em, contributors, share_emitter) !!! Lookup contributor index do i_con = 1, size (reg_data%alr_contributors) if (all (reg_data%alr_contributors(i_con)%c == contributors)) & then sregion%i_reg_to_i_con (i_reg) = i_con exit end if end do deallocate (contributors) end do end associate end do contains function get_emitter_index (i1, i2, n) result (i_em) integer :: i_em integer, intent(in) :: i1, i2, n if (i1 == n) then i_em = i2 else i_em = i1 end if end function get_emitter_index end subroutine region_data_set_contributors @ %def region_data_set_contributors @ This extension of the ftuples is still too naive as it assumes that the same resonances are possible for all ftuples <>= procedure :: extend_ftuples => region_data_extend_ftuples <>= module subroutine region_data_extend_ftuples (reg_data, n_res) class(region_data_t), intent(inout) :: reg_data integer, intent(in) :: n_res end subroutine region_data_extend_ftuples <>= module subroutine region_data_extend_ftuples (reg_data, n_res) class(region_data_t), intent(inout) :: reg_data integer, intent(in) :: n_res integer :: alr, n_reg_save integer :: i_reg, i_res, i_em, k type(ftuple_t), dimension(:), allocatable :: ftuple_save integer :: n_new do alr = 1, size (reg_data%regions) associate (sregion => reg_data%regions(alr)) n_reg_save = sregion%nregions allocate (ftuple_save (n_reg_save)) ftuple_save = sregion%ftuples n_new = count_n_new_ftuples (sregion, n_res) deallocate (sregion%ftuples) sregion%nregions = n_new allocate (sregion%ftuples (n_new)) k = 1 do i_res = 1, n_res do i_reg = 1, n_reg_save associate (ftuple_new => sregion%ftuples(k)) i_em = ftuple_save(i_reg)%ireg(1) if (reg_data%emitter_is_in_resonance (i_res, i_em)) then call ftuple_new%set (i_em, ftuple_save(i_reg)%ireg(2)) ftuple_new%i_res = i_res ftuple_new%splitting_type = ftuple_save(i_reg)%splitting_type k = k + 1 end if end associate end do end do end associate deallocate (ftuple_save) end do contains function count_n_new_ftuples (sregion, n_res) result (n_new) integer :: n_new type(singular_region_t), intent(in) :: sregion integer, intent(in) :: n_res integer :: i_reg, i_res, i_em n_new = 0 do i_reg = 1, sregion%nregions do i_res = 1, n_res i_em = sregion%ftuples(i_reg)%ireg(1) if (reg_data%emitter_is_in_resonance (i_res, i_em)) & n_new = n_new + 1 end do end do end function count_n_new_ftuples end subroutine region_data_extend_ftuples @ %def region_data_extend_ftuples @ <>= procedure :: get_flavor_indices => region_data_get_flavor_indices <>= module function region_data_get_flavor_indices & (reg_data, born) result (i_flv) integer, dimension(:), allocatable :: i_flv class(region_data_t), intent(in) :: reg_data logical, intent(in) :: born end function region_data_get_flavor_indices <>= module function region_data_get_flavor_indices (reg_data, born) result (i_flv) integer, dimension(:), allocatable :: i_flv class(region_data_t), intent(in) :: reg_data logical, intent(in) :: born allocate (i_flv (reg_data%n_regions)) if (born) then i_flv = reg_data%regions%uborn_index else i_flv = reg_data%regions%real_index end if end function region_data_get_flavor_indices @ %def region_data_get_flavor_indices @ <>= procedure :: get_matrix_element_index => region_data_get_matrix_element_index <>= module function region_data_get_matrix_element_index & (reg_data, i_reg) result (i_me) integer :: i_me class(region_data_t), intent(in) :: reg_data integer, intent(in) :: i_reg end function region_data_get_matrix_element_index <>= module function region_data_get_matrix_element_index & (reg_data, i_reg) result (i_me) integer :: i_me class(region_data_t), intent(in) :: reg_data integer, intent(in) :: i_reg i_me = reg_data%regions(i_reg)%real_index end function region_data_get_matrix_element_index @ %def region_data_get_matrix_element_index @ <>= procedure :: compute_number_of_phase_spaces & => region_data_compute_number_of_phase_spaces <>= module subroutine region_data_compute_number_of_phase_spaces (reg_data) class(region_data_t), intent(inout) :: reg_data end subroutine region_data_compute_number_of_phase_spaces <>= module subroutine region_data_compute_number_of_phase_spaces (reg_data) class(region_data_t), intent(inout) :: reg_data integer :: i_em, i_res, i_phs integer :: emitter type(resonance_contributors_t) :: contributors integer, parameter :: n_max_phs = 10 type(phs_identifier_t), dimension(n_max_phs) :: phs_id_tmp logical :: share_emitter, phs_exist if (allocated (reg_data%resonances)) then reg_data%n_phs = 0 do i_em = 1, size (reg_data%emitters) emitter = reg_data%emitters(i_em) do i_res = 1, size (reg_data%resonances) if (reg_data%emitter_is_compatible_with_resonance (i_res, emitter)) then call reg_data%get_contributors & (i_res, emitter, contributors%c, share_emitter) if (.not. share_emitter) cycle call check_for_phs_identifier (phs_id_tmp, reg_data%n_in, & emitter, contributors%c, phs_exist, i_phs) if (.not. phs_exist) then reg_data%n_phs = reg_data%n_phs + 1 if (reg_data%n_phs > n_max_phs) call msg_fatal & ("Buffer of phase space identifieres: Too much phase spaces!") call phs_id_tmp(i_phs)%init (emitter, contributors%c) end if end if if (allocated (contributors%c)) deallocate (contributors%c) end do end do else reg_data%n_phs = size (remove_duplicates_from_int_array & (reg_data%emitters)) end if end subroutine region_data_compute_number_of_phase_spaces @ %def region_data_compute_number_of_phase_spaces @ <>= procedure :: get_n_phs => region_data_get_n_phs <>= module function region_data_get_n_phs (reg_data) result (n_phs) integer :: n_phs class(region_data_t), intent(in) :: reg_data end function region_data_get_n_phs <>= module function region_data_get_n_phs (reg_data) result (n_phs) integer :: n_phs class(region_data_t), intent(in) :: reg_data n_phs = reg_data%n_phs end function region_data_get_n_phs @ %def region_data_get_n_phs @ <>= procedure :: set_splitting_info => region_data_set_splitting_info <>= module subroutine region_data_set_splitting_info (reg_data) class(region_data_t), intent(inout) :: reg_data end subroutine region_data_set_splitting_info <>= module subroutine region_data_set_splitting_info (reg_data) class(region_data_t), intent(inout) :: reg_data integer :: alr do alr = 1, reg_data%n_regions call reg_data%regions(alr)%set_splitting_info (reg_data%n_in) end do end subroutine region_data_set_splitting_info @ %def region_data_set_splitting_info @ <>= procedure :: init_phs_identifiers => region_data_init_phs_identifiers <>= module subroutine region_data_init_phs_identifiers (reg_data, phs_id) class(region_data_t), intent(in) :: reg_data type(phs_identifier_t), intent(out), dimension(:), allocatable :: phs_id end subroutine region_data_init_phs_identifiers <>= module subroutine region_data_init_phs_identifiers (reg_data, phs_id) class(region_data_t), intent(in) :: reg_data type(phs_identifier_t), intent(out), dimension(:), allocatable :: phs_id integer :: i_em, i_res, i_phs integer :: emitter type(resonance_contributors_t) :: contributors logical :: share_emitter, phs_exist allocate (phs_id (reg_data%n_phs)) do i_em = 1, size (reg_data%emitters) emitter = reg_data%emitters(i_em) if (allocated (reg_data%resonances)) then do i_res = 1, size (reg_data%resonances) call reg_data%get_contributors (i_res, emitter, & contributors%c, share_emitter) if (.not. share_emitter) cycle call check_for_phs_identifier & (phs_id, reg_data%n_in, emitter, contributors%c, & phs_exist, i_phs) if (.not. phs_exist) & call phs_id(i_phs)%init (emitter, contributors%c) if (allocated (contributors%c)) deallocate (contributors%c) end do else call check_for_phs_identifier (phs_id, reg_data%n_in, emitter, & phs_exist = phs_exist, i_phs = i_phs) if (.not. phs_exist) call phs_id(i_phs)%init (emitter) end if end do end subroutine region_data_init_phs_identifiers @ %def region_data_init_phs_identifiers @ Gathers all ftuples from all ALRs. There are at most $n \cdot (n-1)$ ftuples with $i$ and $j$ in the final state and up to $3n$ ftuples with $i$ in the initial state. <>= procedure :: get_all_ftuples => region_data_get_all_ftuples <>= module subroutine region_data_get_all_ftuples (reg_data, ftuples) class(region_data_t), intent(in) :: reg_data type(ftuple_t), intent(inout), dimension(:), allocatable :: ftuples end subroutine region_data_get_all_ftuples <>= module subroutine region_data_get_all_ftuples (reg_data, ftuples) class(region_data_t), intent(in) :: reg_data type(ftuple_t), intent(inout), dimension(:), allocatable :: ftuples type(ftuple_t), dimension(:), allocatable :: ftuple_tmp integer :: i, j, alr, n_fs j = 0 n_fs = reg_data%n_legs_real - reg_data%n_in allocate (ftuple_tmp (n_fs * (n_fs - 1) + 3 * n_fs)) do i = 1, reg_data%n_regions associate (region => reg_data%regions(i)) do alr = 1, region%nregions if (.not. any & (ftuple_equal_ireg (region%ftuples(alr), ftuple_tmp))) then j = j + 1 ftuple_tmp(j) = region%ftuples(alr) end if end do end associate end do allocate (ftuples (j)) ftuples = ftuple_tmp(1:j) deallocate (ftuple_tmp) end subroutine region_data_get_all_ftuples @ %def region_data_get_all_ftuples @ <>= procedure :: write_to_file => region_data_write_to_file <>= module subroutine region_data_write_to_file & (reg_data, proc_id, latex, os_data) class(region_data_t), intent(inout) :: reg_data type(string_t), intent(in) :: proc_id logical, intent(in) :: latex type(os_data_t), intent(in) :: os_data end subroutine region_data_write_to_file <>= module subroutine region_data_write_to_file & (reg_data, proc_id, latex, os_data) class(region_data_t), intent(inout) :: reg_data type(string_t), intent(in) :: proc_id logical, intent(in) :: latex type(os_data_t), intent(in) :: os_data type(string_t) :: filename integer :: u integer :: status if (latex) then filename = proc_id // "_fks_regions.tex" else filename = proc_id // "_fks_regions.out" end if u = free_unit () open (u, file=char(filename), action = "write", status="replace") if (latex) then call reg_data%write_latex (u) close (u) call os_data%build_latex_file & (proc_id // "_fks_regions", stat_out = status) if (status /= 0) & call msg_error (char ("Failed to compile " // filename)) else call reg_data%write (u) close (u) end if end subroutine region_data_write_to_file @ %def region_data_write_to_file @ <>= procedure :: write_latex => region_data_write_latex <>= module subroutine region_data_write_latex (reg_data, unit) class(region_data_t), intent(in) :: reg_data integer, intent(in), optional :: unit end subroutine region_data_write_latex <>= module subroutine region_data_write_latex (reg_data, unit) class(region_data_t), intent(in) :: reg_data integer, intent(in), optional :: unit integer :: i, u u = given_output_unit (); if (present (unit)) u = unit write (u, "(A)") "\documentclass{article}" write (u, "(A)") "\begin{document}" write (u, "(A)") "%FKS region data, automatically created by WHIZARD" write (u, "(A)") "\begin{table}" write (u, "(A)") "\begin{center}" write (u, "(A)") "\begin{tabular} {|c|c|c|c|c|c|c|c|}" write (u, "(A)") "\hline" write (u, "(A)") "$\alpha_r$ & $f_r$ & $i_r$ & $\varepsilon$ & " // & "$\varsigma$ & $\mathcal{P}_{\rm{FKS}}$ & $i_b$ & $f_b$ \\" write (u, "(A)") "\hline" do i = 1, reg_data%n_regions call reg_data%regions(i)%write_latex (u) end do write (u, "(A)") "\hline" write (u, "(A)") "\end{tabular}" write (u, "(A)") "\caption{List of singular regions}" write (u, "(A)") "\begin{description}" write (u, "(A)") "\item[$\alpha_r$] Index of the singular region" write (u, "(A)") "\item[$f_r$] Real flavor structure" write (u, "(A)") "\item[$i_r$] Index of the associated real flavor structure" write (u, "(A)") "\item[$\varepsilon$] Emitter" write (u, "(A)") "\item[$\varsigma$] Multiplicity" !!! The symbol used by 0908.4272 for multiplicities write (u, "(A)") "\item[$\mathcal{P}_{\rm{FKS}}$] The set of singular FKS-pairs" write (u, "(A)") "\item[$i_b$] Underlying Born index" write (u, "(A)") "\item[$f_b$] Underlying Born flavor structure" write (u, "(A)") "\end{description}" write (u, "(A)") "\end{center}" write (u, "(A)") "\end{table}" write (u, "(A)") "\end{document}" end subroutine region_data_write_latex @ %def region_data_write_latex @ Creates a table with information about all singular regions and writes it to a file. <>= procedure :: write => region_data_write <>= module subroutine region_data_write (reg_data, unit) class(region_data_t), intent(in) :: reg_data integer, intent(in), optional :: unit end subroutine region_data_write <>= module subroutine region_data_write (reg_data, unit) class(region_data_t), intent(in) :: reg_data integer, intent(in), optional :: unit integer :: j integer :: maxnregions, i_reg_max type(string_t) :: flst_title, ftuple_title integer :: n_res, u u = given_output_unit (unit); if (u < 0) return maxnregions = 1; i_reg_max = 1 do j = 1, reg_data%n_regions if (size (reg_data%regions(j)%ftuples) > maxnregions) then maxnregions = reg_data%regions(j)%nregions i_reg_max = j end if end do flst_title = '(A' // flst_title_format(reg_data%n_legs_real) // ')' ftuple_title = '(A' // ftuple_title_format() // ')' write (u,'(A,1X,I4)') 'Total number of regions: ', size(reg_data%regions) write (u, '(A4)', advance = 'no') ' alr' call write_vline (u) write (u, char (flst_title), advance = 'no') 'flst_real' call write_vline (u) write (u, '(A6)', advance = 'no') 'i_real' call write_vline (u) write (u, '(A3)', advance = 'no') 'em' call write_vline (u) write (u, '(A3)', advance = 'no') 'mult' call write_vline (u) write (u, '(A4)', advance = 'no') 'nreg' call write_vline (u) if (allocated (reg_data%fks_mapping)) then select type (fks_mapping => reg_data%fks_mapping) type is (fks_mapping_resonances_t) write (u, '(A3)', advance = 'no') 'res' call write_vline (u) end select end if write (u, char (ftuple_title), advance = 'no') 'ftuples' call write_vline (u) flst_title = '(A' // flst_title_format(reg_data%n_legs_born) // ')' write (u, char (flst_title), advance = 'no') 'flst_born' call write_vline (u) write (u, '(A7)', advance = 'no') 'i_born' call write_vline (u) write (u, '(A4)') 'corr' do j = 1, reg_data%n_regions write (u, '(I4)', advance = 'no') j call reg_data%regions(j)%write (u, maxnregions) end do call write_separator (u) if (allocated (reg_data%fks_mapping)) then select type (fks_mapping => reg_data%fks_mapping) type is (fks_mapping_resonances_t) write (u, '(A)') write (u, '(A)') & "The FKS regions are combined with resonance information: " n_res = size (fks_mapping%res_map%res_histories) write (u, '(A,1X,I1)') "Number of QCD resonance histories: ", n_res do j = 1, n_res write (u, '(A,1X,I1)') "i_res = ", j call fks_mapping%res_map%res_histories(j)%write (u) call write_separator (u) end do end select end if contains function flst_title_format (n) result (frmt) integer, intent(in) :: n type(string_t) :: frmt character(len=2) :: frmt_char write (frmt_char, '(I2)') 4 * n + 1 frmt = var_str (frmt_char) end function flst_title_format function ftuple_title_format () result (frmt) type(string_t) :: frmt integer :: n_ftuple_char !!! An ftuple (x,x) consists of five characters. In the string, they !!! are separated by maxregions - 1 commas. In total these are !!! 5 * maxnregions + maxnregions - 1 = 6 * maxnregions - 1 characters. !!! The {} brackets at add two additional characters. n_ftuple_char = 6 * maxnregions + 1 !!! If there are resonances, each ftuple with a resonance adds a ";x" !!! to the ftuple n_ftuple_char = n_ftuple_char + & 2 * count (reg_data%regions(i_reg_max)%ftuples%i_res > 0) !!! Pseudo-ISR regions are denoted with a * at the end n_ftuple_char = n_ftuple_char + & count (reg_data%regions(i_reg_max)%ftuples%pseudo_isr) frmt = str (n_ftuple_char) end function ftuple_title_format end subroutine region_data_write @ %def region_data_write @ <>= subroutine write_vline (u) integer, intent(in) :: u character(len=10), parameter :: sep_format = "(1X,A2,1X)" write (u, sep_format, advance = 'no') '||' end subroutine write_vline @ %def write_vline @ <>= public :: assignment(=) <>= interface assignment(=) module procedure region_data_assign end interface <>= module subroutine region_data_assign (reg_data_out, reg_data_in) type(region_data_t), intent(out) :: reg_data_out type(region_data_t), intent(in) :: reg_data_in end subroutine region_data_assign <>= module subroutine region_data_assign (reg_data_out, reg_data_in) type(region_data_t), intent(out) :: reg_data_out type(region_data_t), intent(in) :: reg_data_in integer :: i if (allocated (reg_data_in%regions)) then allocate (reg_data_out%regions (size (reg_data_in%regions))) do i = 1, size (reg_data_in%regions) reg_data_out%regions(i) = reg_data_in%regions(i) end do else call msg_warning & ("Copying region data without allocated singular regions!") end if if (allocated (reg_data_in%flv_born)) then allocate (reg_data_out%flv_born (size (reg_data_in%flv_born))) do i = 1, size (reg_data_in%flv_born) reg_data_out%flv_born(i) = reg_data_in%flv_born(i) end do else call msg_warning & ("Copying region data without allocated born flavor structure!") end if if (allocated (reg_data_in%flv_real)) then allocate (reg_data_out%flv_real (size (reg_data_in%flv_real))) do i = 1, size (reg_data_in%flv_real) reg_data_out%flv_real(i) = reg_data_in%flv_real(i) end do else call msg_warning ("Copying region data without allocated real flavor structure!") end if if (allocated (reg_data_in%emitters)) then allocate (reg_data_out%emitters (size (reg_data_in%emitters))) do i = 1, size (reg_data_in%emitters) reg_data_out%emitters(i) = reg_data_in%emitters(i) end do else call msg_warning ("Copying region data without allocated emitters!") end if reg_data_out%n_regions = reg_data_in%n_regions reg_data_out%n_emitters = reg_data_in%n_emitters reg_data_out%n_flv_born = reg_data_in%n_flv_born reg_data_out%n_flv_real = reg_data_in%n_flv_real reg_data_out%n_in = reg_data_in%n_in reg_data_out%n_legs_born = reg_data_in%n_legs_born reg_data_out%n_legs_real = reg_data_in%n_legs_real if (allocated (reg_data_in%fks_mapping)) then select type (fks_mapping_in => reg_data_in%fks_mapping) type is (fks_mapping_default_t) allocate (fks_mapping_default_t :: reg_data_out%fks_mapping) select type (fks_mapping_out => reg_data_out%fks_mapping) type is (fks_mapping_default_t) fks_mapping_out = fks_mapping_in end select type is (fks_mapping_resonances_t) allocate (fks_mapping_resonances_t :: reg_data_out%fks_mapping) select type (fks_mapping_out => reg_data_out%fks_mapping) type is (fks_mapping_resonances_t) fks_mapping_out = fks_mapping_in end select end select else call msg_warning ("Copying region data without allocated FKS regions!") end if if (allocated (reg_data_in%resonances)) then allocate (reg_data_out%resonances (size (reg_data_in%resonances))) reg_data_out%resonances = reg_data_in%resonances end if reg_data_out%n_phs = reg_data_in%n_phs if (allocated (reg_data_in%alr_contributors)) then allocate (reg_data_out%alr_contributors (size (reg_data_in%alr_contributors))) reg_data_out%alr_contributors = reg_data_in%alr_contributors end if if (allocated (reg_data_in%alr_to_i_contributor)) then allocate (reg_data_out%alr_to_i_contributor & (size (reg_data_in%alr_to_i_contributor))) reg_data_out%alr_to_i_contributor = reg_data_in%alr_to_i_contributor end if end subroutine region_data_assign @ %def region_data_assign @ Returns the index of the real flavor structure an ftuple belogs to. <>= function region_to_real_index (list, i) result(index) type(ftuple_list_t), intent(in), dimension(:), allocatable :: list integer, intent(in) :: i integer, dimension(:), allocatable :: nreg integer :: index, j allocate (nreg (0)) index = 0 do j = 1, size (list) nreg = [nreg, sum (list(:j)%get_n_tuples ())] if (j == 1) then if (i <= nreg(j)) then index = j exit end if else if (i > nreg(j - 1) .and. i <= nreg(j)) then index = j exit end if end if end do end function region_to_real_index @ %def region_to_real_index @ Final state emission: Rearrange the flavor array in such a way that the emitted particle is last and the emitter is second last. [[i1]] is the index of the emitter, [[i2]] is the index of the emitted particle. Initial state emission: Just put the emitted particle to the last position. <>= function create_alr (flv1, n_in, i_em, i_rad) result(flv2) type(flv_structure_t), intent(in) :: flv1 integer, intent(in) :: n_in integer, intent(in) :: i_em, i_rad type(flv_structure_t) :: flv2 integer :: n n = size (flv1%flst) allocate (flv2%flst (n), flv2%tag (n)) flv2%nlegs = n flv2%n_in = n_in if (i_em > n_in) then flv2%flst(1 : n_in) = flv1%flst(1 : n_in) flv2%flst(n - 1) = flv1%flst(i_em) flv2%flst(n) = flv1%flst(i_rad) flv2%tag(1 : n_in) = flv1%tag(1 : n_in) flv2%tag(n - 1) = flv1%tag(i_em) flv2%tag(n) = flv1%tag(i_rad) call fill_remaining_flavors (n_in, .true.) else flv2%flst(1 : n_in) = flv1%flst(1 : n_in) flv2%flst(n) = flv1%flst(i_rad) flv2%tag(1 : n_in) = flv1%tag(1 : n_in) flv2%tag(n) = flv1%tag(i_rad) call fill_remaining_flavors (n_in, .false.) end if call flv2%compute_prt_symm_fs (flv2%n_in) contains @ Order remaining particles according to their original position <>= subroutine fill_remaining_flavors (n_in, final_final) integer, intent(in) :: n_in logical, intent(in) :: final_final integer :: i, j logical :: check j = n_in + 1 do i = n_in + 1, n if (final_final) then check = (i /= i_em .and. i /= i_rad) else check = (i /= i_rad) end if if (check) then flv2%flst(j) = flv1%flst(i) flv2%tag(j) = flv1%tag(i) j = j + 1 end if end do end subroutine fill_remaining_flavors end function create_alr @ %def create_alr @ <>= procedure :: has_pseudo_isr => region_data_has_pseudo_isr <>= module function region_data_has_pseudo_isr (reg_data) result (flag) logical :: flag class(region_data_t), intent(in) :: reg_data end function region_data_has_pseudo_isr <>= module function region_data_has_pseudo_isr (reg_data) result (flag) logical :: flag class(region_data_t), intent(in) :: reg_data flag = any (reg_data%regions%pseudo_isr) end function region_data_has_pseudo_isr @ %def region_data_has_pseudo_isr @ Performs consistency checks on [[region_data]]. Up to now only checks that no [[ftuple]] appears more than once. <>= procedure :: check_consistency => region_data_check_consistency <>= module subroutine region_data_check_consistency (reg_data, fail_fatal, unit) class(region_data_t), intent(in) :: reg_data logical, intent(in) :: fail_fatal integer, intent(in), optional :: unit end subroutine region_data_check_consistency <>= module subroutine region_data_check_consistency (reg_data, fail_fatal, unit) class(region_data_t), intent(in) :: reg_data logical, intent(in) :: fail_fatal integer, intent(in), optional :: unit integer :: u integer :: i_reg, alr integer :: i1, f1, f2 logical :: undefined_ftuples, same_ftuple_indices, valid_splitting logical, dimension(4) :: no_fail u = given_output_unit(unit); if (u < 0) return no_fail = .true. call msg_message ("Check that no negative ftuple indices occur", unit = u) do i_reg = 1, reg_data%n_regions if (any (reg_data%regions(i_reg)%ftuples%has_negative_elements ())) then !!! This error is so severe that we stop immediately call msg_fatal ("Negative ftuple indices!") end if end do call msg_message ("Success!", unit = u) call msg_message ("Check that there is no ftuple with identical elements", unit = u) do i_reg = 1, reg_data%n_regions if (any (reg_data%regions(i_reg)%ftuples%has_identical_elements ())) then !!! This error is so severe that we stop immediately call msg_fatal ("Identical ftuple indices!") end if end do call msg_message ("Success!", unit = u) call msg_message ("Check that there are no duplicate ftuples in a region", unit = u) do i_reg = 1, reg_data%n_regions if (reg_data%regions(i_reg)%has_identical_ftuples ()) then if (no_fail(1)) then call msg_error ("FAIL: ", unit = u) no_fail(1) = .false. end if write (u, '(A,1x,I3)') 'i_reg:', i_reg end if end do if (no_fail(1)) call msg_message ("Success!", unit = u) call msg_message ("Check that ftuples add up to a valid splitting", unit = u) do i_reg = 1, reg_data%n_regions do alr = 1, reg_data%regions(i_reg)%nregions associate (region => reg_data%regions(i_reg)) i1 = region%ftuples(alr)%ireg(1) if (i1 == 0) i1 = 1 !!! Gluon emission from both initial-state particles f1 = region%flst_real%flst(i1) f2 = region%flst_real%flst(region%ftuples(alr)%ireg(2)) ! Flip PDG sign of IS fermions to allow a q -> g q splitting ! in which the ftuple has the flavors (q,q). if (i1 <= reg_data%n_in .and. is_fermion(f1)) then f1 = -f1 end if valid_splitting = f1 + f2 == 0 & .or. (is_gluon(f1) .and. is_gluon(f2)) & .or. (is_massive_vector(f1) .and. is_photon(f2)) & .or. is_fermion_vector_splitting (f1, f2) if (.not. valid_splitting) then if (no_fail(2)) then call msg_error ("FAIL: ", unit = u) no_fail(2) = .false. end if write (u, '(A,1x,I3)') 'i_reg:', i_reg exit end if end associate end do end do if (no_fail(2)) call msg_message ("Success!", unit = u) call msg_message ("Check that at least one ftuple contains the emitter", unit = u) do i_reg = 1, reg_data%n_regions associate (region => reg_data%regions(i_reg)) if (.not. any (region%emitter == region%ftuples%ireg(1))) then if (no_fail(3)) then call msg_error ("FAIL: ", unit = u) no_fail(3) = .false. end if write (u, '(A,1x,I3)') 'i_reg:', i_reg end if end associate end do if (no_fail(3)) call msg_message ("Success!", unit = u) call msg_message ("Check that each region has at least one ftuple & &with index n + 1", unit = u) do i_reg = 1, reg_data%n_regions if (.not. any (reg_data%regions(i_reg)%ftuples%ireg(2) == reg_data%n_legs_real)) then if (no_fail(4)) then call msg_error ("FAIL: ", unit = u) no_fail(4) = .false. end if write (u, '(A,1x,I3)') 'i_reg:', i_reg end if end do if (no_fail(4)) call msg_message ("Success!", unit = u) if (.not. all (no_fail)) & call abort_with_message ("Stop due to inconsistent region data!") contains subroutine abort_with_message (msg) character(len=*), intent(in) :: msg if (fail_fatal) then call msg_fatal (msg) else call msg_error (msg, unit = u) end if end subroutine abort_with_message function is_fermion_vector_splitting (pdg_1, pdg_2) result (value) logical :: value integer, intent(in) :: pdg_1, pdg_2 value = (is_fermion (pdg_1) .and. is_massless_vector (pdg_2)) .or. & (is_fermion (pdg_2) .and. is_massless_vector (pdg_1)) end function end subroutine region_data_check_consistency @ %def region_data_check_consistency @ <>= procedure :: requires_spin_correlations => & region_data_requires_spin_correlations <>= module function region_data_requires_spin_correlations & (reg_data) result (flag) class(region_data_t), intent(in) :: reg_data logical :: flag end function region_data_requires_spin_correlations <>= module function region_data_requires_spin_correlations & (reg_data) result (flag) class(region_data_t), intent(in) :: reg_data logical :: flag integer :: alr flag = .false. do alr = 1, reg_data%n_regions flag = reg_data%regions(alr)%sc_required if (flag) return end do end function region_data_requires_spin_correlations @ %def region_data_requires_spin_correlations @ We have to apply the symmetry factor for identical particles of the real flavor structure to the born squared matrix element. The corresponding factor from the born flavor structure has to be cancelled. <>= procedure :: born_to_real_symm_factor_fs => & region_data_born_to_real_symm_factor_fs <>= module function region_data_born_to_real_symm_factor_fs & (reg_data, alr) result (factor) class(region_data_t), intent(in) :: reg_data integer, intent(in) :: alr real(default) :: factor end function region_data_born_to_real_symm_factor_fs <>= module function region_data_born_to_real_symm_factor_fs & (reg_data, alr) result (factor) class(region_data_t), intent(in) :: reg_data integer, intent(in) :: alr real(default) :: factor associate (flv_real => reg_data%regions(alr)%flst_real, & flv_uborn => reg_data%regions(alr)%flst_uborn) factor = flv_real%prt_symm_fs / flv_uborn%prt_symm_fs end associate end function region_data_born_to_real_symm_factor_fs @ %def region_data_born_to_real_symm_factor_fs @ <>= procedure :: final => region_data_final <>= module subroutine region_data_final (reg_data) class(region_data_t), intent(inout) :: reg_data end subroutine region_data_final <>= module subroutine region_data_final (reg_data) class(region_data_t), intent(inout) :: reg_data if (allocated (reg_data%regions)) deallocate (reg_data%regions) if (allocated (reg_data%flv_born)) deallocate (reg_data%flv_born) if (allocated (reg_data%flv_real)) deallocate (reg_data%flv_real) if (allocated (reg_data%emitters)) deallocate (reg_data%emitters) if (allocated (reg_data%fks_mapping)) deallocate (reg_data%fks_mapping) if (allocated (reg_data%resonances)) deallocate (reg_data%resonances) if (allocated (reg_data%alr_contributors)) & deallocate (reg_data%alr_contributors) if (allocated (reg_data%alr_to_i_contributor)) & deallocate (reg_data%alr_to_i_contributor) end subroutine region_data_final @ %def region_data_final @ <>= procedure (fks_mapping_dij), deferred :: dij <>= abstract interface function fks_mapping_dij (map, p, i, j, i_con) result (d) import real(default) :: d class(fks_mapping_t), intent(in) :: map type(vector4_t), intent(in), dimension(:) :: p integer, intent(in) :: i, j integer, intent(in), optional :: i_con end function fks_mapping_dij end interface @ %def fks_mapping_dij @ <>= procedure (fks_mapping_compute_sumdij), deferred :: compute_sumdij <>= abstract interface subroutine fks_mapping_compute_sumdij (map, sregion, p_real) import class(fks_mapping_t), intent(inout) :: map type(singular_region_t), intent(in) :: sregion type(vector4_t), intent(in), dimension(:) :: p_real end subroutine fks_mapping_compute_sumdij end interface @ %def fks_mapping_compute_sumdij @ <>= procedure (fks_mapping_svalue), deferred :: svalue <>= abstract interface function fks_mapping_svalue (map, p, i, j, i_res) result (value) import real(default) :: value class(fks_mapping_t), intent(in) :: map type(vector4_t), intent(in), dimension(:) :: p integer, intent(in) :: i, j integer, intent(in), optional :: i_res end function fks_mapping_svalue end interface @ %def fks_mapping_svalue <>= procedure (fks_mapping_dij_soft), deferred :: dij_soft <>= abstract interface function fks_mapping_dij_soft (map, p_born, p_soft, em, i_con) result (d) import real(default) :: d class(fks_mapping_t), intent(in) :: map type(vector4_t), intent(in), dimension(:) :: p_born type(vector4_t), intent(in) :: p_soft integer, intent(in) :: em integer, intent(in), optional :: i_con end function fks_mapping_dij_soft end interface @ %def fks_mapping_dij_soft @ <>= procedure (fks_mapping_compute_sumdij_soft), deferred :: compute_sumdij_soft <>= abstract interface subroutine fks_mapping_compute_sumdij_soft (map, sregion, p_born, p_soft) import class(fks_mapping_t), intent(inout) :: map type(singular_region_t), intent(in) :: sregion type(vector4_t), intent(in), dimension(:) :: p_born type(vector4_t), intent(in) :: p_soft end subroutine fks_mapping_compute_sumdij_soft end interface @ %def fks_mapping_compute_sumdij_soft @ <>= procedure (fks_mapping_svalue_soft), deferred :: svalue_soft <>= abstract interface function fks_mapping_svalue_soft (map, p_born, p_soft, em, i_res) result (value) import real(default) :: value class(fks_mapping_t), intent(in) :: map type(vector4_t), intent(in), dimension(:) :: p_born type(vector4_t), intent(in) :: p_soft integer, intent(in) :: em integer, intent(in), optional :: i_res end function fks_mapping_svalue_soft end interface @ %def fks_mapping_svalue_soft @ <>= procedure :: set_parameter => fks_mapping_default_set_parameter <>= module subroutine fks_mapping_default_set_parameter & (map, n_in, dij_exp1, dij_exp2) class(fks_mapping_default_t), intent(inout) :: map integer, intent(in) :: n_in real(default), intent(in) :: dij_exp1, dij_exp2 end subroutine fks_mapping_default_set_parameter <>= module subroutine fks_mapping_default_set_parameter & (map, n_in, dij_exp1, dij_exp2) class(fks_mapping_default_t), intent(inout) :: map integer, intent(in) :: n_in real(default), intent(in) :: dij_exp1, dij_exp2 map%n_in = n_in map%exp_1 = dij_exp1 map%exp_2 = dij_exp2 end subroutine fks_mapping_default_set_parameter @ %def fks_mapping_default_set_parameter @ Computes the $d_{ij}$-quantities defined als follows: \begin{align*} d_{0i} &= \left[E_i^2\left(1-y_i\right)\right]^{p_2}\\, d_{1i} &= \left[2E_i^2\left(1-y_i\right)\right]^{p_2}\\, d_{2i} &= \left[2E_i^2\left(1+y_i\right)\right]^{p_2}\\, \end{align*} for initial state regions and \begin{align*} d_{ij} = \left[2(k_i \cdot k_j) \frac{E_i E_j}{(E_i+E_j)^2}\right]^{p_1} \end{align*} for final state regions, c.f. [1002.2581, Eq. 4.23f]. The exponents $p_1$ and $p_2$ can be used for tuning the efficiency of the mapping and are set to $1$ per default. <>= procedure :: dij => fks_mapping_default_dij <>= module function fks_mapping_default_dij (map, p, i, j, i_con) result (d) real(default) :: d class(fks_mapping_default_t), intent(in) :: map type(vector4_t), intent(in), dimension(:) :: p integer, intent(in) :: i, j integer, intent(in), optional :: i_con end function fks_mapping_default_dij <>= module function fks_mapping_default_dij (map, p, i, j, i_con) result (d) real(default) :: d class(fks_mapping_default_t), intent(in) :: map type(vector4_t), intent(in), dimension(:) :: p integer, intent(in) :: i, j integer, intent(in), optional :: i_con d = zero if (map%pseudo_isr) then d = dij_threshold_gluon_from_top (i, j, p, map%exp_1) else if (i > map%n_in .and. j > map%n_in) then d = dij_fsr (p(i), p(j), map%exp_1) else d = dij_isr (map%n_in, i, j, p, map%exp_2) end if contains function dij_fsr (p1, p2, expo) result (d_ij) real(default) :: d_ij type(vector4_t), intent(in) :: p1, p2 real(default), intent(in) :: expo real(default) :: E1, E2 E1 = p1%p(0); E2 = p2%p(0) d_ij = (two * p1 * p2 * E1 * E2 / (E1 + E2)**2)**expo end function dij_fsr function dij_threshold_gluon_from_top (i, j, p, expo) result (d_ij) real(default) :: d_ij integer, intent(in) :: i, j type(vector4_t), intent(in), dimension(:) :: p real(default), intent(in) :: expo type(vector4_t) :: p_top if (i == THR_POS_B) then p_top = p(THR_POS_WP) + p(THR_POS_B) else p_top = p(THR_POS_WM) + p(THR_POS_BBAR) end if d_ij = dij_fsr (p_top, p(j), expo) end function dij_threshold_gluon_from_top function dij_isr (n_in, i, j, p, expo) result (d_ij) real(default) :: d_ij integer, intent(in) :: n_in, i, j type(vector4_t), intent(in), dimension(:) :: p real(default), intent(in) :: expo real(default) :: E, y select case (n_in) case (1) call get_emitter_variables (1, i, j, p, E, y) d_ij = (E**2 * (one - y**2))**expo case (2) if ((i == 0 .and. j > 2) .or. (j == 0 .and. i > 2)) then call get_emitter_variables (0, i, j, p, E, y) d_ij = (E**2 * (one - y**2))**expo else if ((i == 1 .and. j > 2) .or. (j == 1 .and. i > 2)) then call get_emitter_variables (1, i, j, p, E, y) d_ij = (two * E**2 * (one - y))**expo else if ((i == 2 .and. j > 2) .or. (j == 2 .and. i > 2)) then call get_emitter_variables (2, i, j, p, E, y) d_ij = (two * E**2 * (one + y))**expo end if end select end function dij_isr subroutine get_emitter_variables (i_check, i, j, p, E, y) integer, intent(in) :: i_check, i, j type(vector4_t), intent(in), dimension(:) :: p real(default), intent(out) :: E, y if (j == i_check) then E = energy (p(i)) y = polar_angle_ct (p(i)) else E = energy (p(j)) y = polar_angle_ct(p(j)) end if end subroutine get_emitter_variables end function fks_mapping_default_dij @ %def fks_mapping_default_dij @ Computes the quantity \begin{equation*} \mathcal{D} = \sum_k \frac{1}{d_{0k}} + \sum_{kl} \frac{1}{d_{kl}}. \end{equation*} where the sum goes over all ftuples of a single singular region. <>= procedure :: compute_sumdij => fks_mapping_default_compute_sumdij <>= module subroutine fks_mapping_default_compute_sumdij (map, sregion, p_real) class(fks_mapping_default_t), intent(inout) :: map type(singular_region_t), intent(in) :: sregion type(vector4_t), intent(in), dimension(:) :: p_real end subroutine fks_mapping_default_compute_sumdij <>= module subroutine fks_mapping_default_compute_sumdij (map, sregion, p_real) class(fks_mapping_default_t), intent(inout) :: map type(singular_region_t), intent(in) :: sregion type(vector4_t), intent(in), dimension(:) :: p_real real(default) :: d integer :: i_ftuple, i, j associate (ftuples => sregion%ftuples) d = zero do i_ftuple = 1, sregion%nregions call ftuples(i_ftuple)%get (i, j) map%pseudo_isr = ftuples(i_ftuple)%pseudo_isr d = d + one / map%dij (p_real, i, j) end do end associate map%sumdij = d end subroutine fks_mapping_default_compute_sumdij @ %def fks_mapping_default_compute_sumdij @ Computes \begin{equation*} S_i = \frac{1}{\mathcal{D} d_{0i}} \end{equation*} or \begin{equation*} S_{ij} = \frac{1}{\mathcal{D} d_{ij}}, \end{equation*} respectively. <>= procedure :: svalue => fks_mapping_default_svalue <>= module function fks_mapping_default_svalue & (map, p, i, j, i_res) result (value) real(default) :: value class(fks_mapping_default_t), intent(in) :: map type(vector4_t), intent(in), dimension(:) :: p integer, intent(in) :: i, j integer, intent(in), optional :: i_res end function fks_mapping_default_svalue <>= module function fks_mapping_default_svalue & (map, p, i, j, i_res) result (value) real(default) :: value class(fks_mapping_default_t), intent(in) :: map type(vector4_t), intent(in), dimension(:) :: p integer, intent(in) :: i, j integer, intent(in), optional :: i_res value = one / (map%dij (p, i, j) * map%sumdij) end function fks_mapping_default_svalue @ %def fks_mapping_default_svalue @ In the soft limit, our treatment of the divergencies requires a modification of the mapping functions. Recall that there, the ratios of the $d$-functions must approach either $1$ or $0$. This means \begin{equation*} \frac{d_{lm}}{d_{0m}} = \frac{(2k_l \cdot k_m) \left[E_lE_m /(E_l + E_m)^2\right]}{E_m^2 (1-y^2)} \overset {k_m = E_m \hat{k}} {=} \frac{E_l E_m^2}{(E_l + E_m)^2} \frac{2k_l \cdot \hat{k}}{E_m^2 (1-y^2)} \overset {E_m \to 0}{=} \frac{2k_l \cdot \hat{k}}{E_l}{(1-y^2)}, \end{equation*} where we have written the gluon momentum in terms of the soft momentum $\hat{k}$. In the same limit \begin{equation*} \frac{d_{lm}}{d_{nm}} = \frac{k_l \cdot \hat{k}}{k_n \cdot \hat{k}} \frac{E_n}{E_l}. \end{equation*} From these equations we can deduce the soft limit of $d$: \begin{align*} d_0^{\rm{soft}} &= 1 - y^2,\\ d_1^{\rm{soft}} &= 2(1-y),\\ d_2^{\rm{soft}} &= 2(1+y),\\ d_i^{\rm{soft}} &= \frac{2 k_i \cdot \hat{k}}{E_i}. \end{align*} <>= procedure :: dij_soft => fks_mapping_default_dij_soft <>= module function fks_mapping_default_dij_soft & (map, p_born, p_soft, em, i_con) result (d) real(default) :: d class(fks_mapping_default_t), intent(in) :: map type(vector4_t), intent(in), dimension(:) :: p_born type(vector4_t), intent(in) :: p_soft integer, intent(in) :: em integer, intent(in), optional :: i_con end function fks_mapping_default_dij_soft <>= module function fks_mapping_default_dij_soft & (map, p_born, p_soft, em, i_con) result (d) real(default) :: d class(fks_mapping_default_t), intent(in) :: map type(vector4_t), intent(in), dimension(:) :: p_born type(vector4_t), intent(in) :: p_soft integer, intent(in) :: em integer, intent(in), optional :: i_con if (map%pseudo_isr) then d = dij_soft_threshold_gluon_from_top (em, p_born, p_soft, map%exp_1) else if (em <= map%n_in) then d = dij_soft_isr (map%n_in, p_soft, map%exp_2) else d = dij_soft_fsr (p_born(em), p_soft, map%exp_1) end if contains function dij_soft_threshold_gluon_from_top & (em, p_born, p_soft, expo) result (dij_soft) real(default) :: dij_soft integer, intent(in) :: em type(vector4_t), intent(in), dimension(:) :: p_born type(vector4_t), intent(in) :: p_soft real(default), intent(in) :: expo type(vector4_t) :: p_top if (em == THR_POS_B) then p_top = p_born(THR_POS_WP) + p_born(THR_POS_B) else p_top = p_born(THR_POS_WM) + p_born(THR_POS_BBAR) end if dij_soft = dij_soft_fsr (p_top, p_soft, expo) end function dij_soft_threshold_gluon_from_top function dij_soft_fsr (p_em, p_soft, expo) result (dij_soft) real(default) :: dij_soft type(vector4_t), intent(in) :: p_em, p_soft real(default), intent(in) :: expo dij_soft = (two * p_em * p_soft / p_em%p(0))**expo end function dij_soft_fsr function dij_soft_isr (n_in, p_soft, expo) result (dij_soft) real(default) :: dij_soft integer, intent(in) :: n_in type(vector4_t), intent(in) :: p_soft real(default), intent(in) :: expo real(default) :: y y = polar_angle_ct (p_soft) select case (n_in) case (1) dij_soft = one - y**2 case (2) select case (em) case (0) dij_soft = one - y**2 case (1) dij_soft = two * (one - y) case (2) dij_soft = two * (one + y) case default dij_soft = zero call msg_fatal ("fks_mappings_default_dij_soft: n_in > 2") end select case default dij_soft = zero call msg_fatal ("fks_mappings_default_dij_soft: n_in > 2") end select dij_soft = dij_soft**expo end function dij_soft_isr end function fks_mapping_default_dij_soft @ %def fks_mapping_default_dij_soft @ Computes the sum of all soft [[dij]]s required to normalize the soft $S$ functions [[s_alpha_soft]] similar to [[fks_mapping_default_compute_sumdij]]. In the soft limit however, we need to skip all ftuples $(i,j)$ in which $j$ does not correspond to the emitted particle because those $d_{ij}$s are finite and thus their contribution to the soft S function vanishes in the limit of soft radiation. Technically, they would not vanish if computed here because the fixed [[p_soft]] at this point would not fit their actual emitter. <>= procedure :: compute_sumdij_soft => fks_mapping_default_compute_sumdij_soft <>= module subroutine fks_mapping_default_compute_sumdij_soft & (map, sregion, p_born, p_soft) class(fks_mapping_default_t), intent(inout) :: map type(singular_region_t), intent(in) :: sregion type(vector4_t), intent(in), dimension(:) :: p_born type(vector4_t), intent(in) :: p_soft end subroutine fks_mapping_default_compute_sumdij_soft <>= module subroutine fks_mapping_default_compute_sumdij_soft & (map, sregion, p_born, p_soft) class(fks_mapping_default_t), intent(inout) :: map type(singular_region_t), intent(in) :: sregion type(vector4_t), intent(in), dimension(:) :: p_born type(vector4_t), intent(in) :: p_soft real(default) :: d integer :: i_ftuple, i, j integer :: nlegs d = zero nlegs = size (sregion%flst_real%flst) associate (ftuples => sregion%ftuples) do i_ftuple = 1, sregion%nregions call ftuples(i_ftuple)%get (i ,j) if (j == nlegs) then map%pseudo_isr = ftuples(i_ftuple)%pseudo_isr d = d + one / map%dij_soft (p_born, p_soft, i) end if end do end associate map%sumdij_soft = d end subroutine fks_mapping_default_compute_sumdij_soft @ %def fks_mapping_default_compute_sumdij_soft @ <>= procedure :: svalue_soft => fks_mapping_default_svalue_soft <>= module function fks_mapping_default_svalue_soft & (map, p_born, p_soft, em, i_res) result (value) real(default) :: value class(fks_mapping_default_t), intent(in) :: map type(vector4_t), intent(in), dimension(:) :: p_born type(vector4_t), intent(in) :: p_soft integer, intent(in) :: em integer, intent(in), optional :: i_res end function fks_mapping_default_svalue_soft <>= module function fks_mapping_default_svalue_soft & (map, p_born, p_soft, em, i_res) result (value) real(default) :: value class(fks_mapping_default_t), intent(in) :: map type(vector4_t), intent(in), dimension(:) :: p_born type(vector4_t), intent(in) :: p_soft integer, intent(in) :: em integer, intent(in), optional :: i_res value = one / (map%sumdij_soft * map%dij_soft (p_born, p_soft, em)) end function fks_mapping_default_svalue_soft @ %def fks_mapping_default_svalue_soft @ <>= interface assignment(=) module procedure fks_mapping_default_assign end interface <>= module subroutine fks_mapping_default_assign (fks_map_out, fks_map_in) type(fks_mapping_default_t), intent(out) :: fks_map_out type(fks_mapping_default_t), intent(in) :: fks_map_in end subroutine fks_mapping_default_assign <>= module subroutine fks_mapping_default_assign (fks_map_out, fks_map_in) type(fks_mapping_default_t), intent(out) :: fks_map_out type(fks_mapping_default_t), intent(in) :: fks_map_in fks_map_out%exp_1 = fks_map_in%exp_1 fks_map_out%exp_2 = fks_map_in%exp_2 fks_map_out%n_in = fks_map_in%n_in end subroutine fks_mapping_default_assign @ %def fks_mapping_default_assign @ The $d_{ij,k}$-functions for the resonance mapping are basically the same as in the default case, but the kinematical values here must be evaluated in the resonance frame of reference. The energy of parton $i$ in a given resonance frame with momentum $p_{res}$ is \begin{equation*} E_i = \frac{p_i^0 \cdot p_{res}}{m_{res}}. \end{equation*} However, since the expressions only depend on ratios of four-momenta, we leave out the denominator because it will cancel out anyway. <>= procedure :: dij => fks_mapping_resonances_dij <>= module function fks_mapping_resonances_dij (map, p, i, j, i_con) result (d) real(default) :: d class(fks_mapping_resonances_t), intent(in) :: map type(vector4_t), intent(in), dimension(:) :: p integer, intent(in) :: i, j integer, intent(in), optional :: i_con end function fks_mapping_resonances_dij <>= module function fks_mapping_resonances_dij (map, p, i, j, i_con) result (d) real(default) :: d class(fks_mapping_resonances_t), intent(in) :: map type(vector4_t), intent(in), dimension(:) :: p integer, intent(in) :: i, j integer, intent(in), optional :: i_con real(default) :: E1, E2 integer :: ii_con if (present (i_con)) then ii_con = i_con else call msg_fatal ("Resonance mappings require resonance index as input!") end if d = 0 if (i /= j) then if (i > 2 .and. j > 2) then associate (p_res => map%res_map%p_res (ii_con)) E1 = p(i) * p_res E2 = p(j) * p_res d = two * p(i) * p(j) * E1 * E2 / (E1 + E2)**2 end associate else call msg_fatal ("Resonance mappings are not implemented for ISR") end if end if end function fks_mapping_resonances_dij @ %def fks_mapping_resonances_dij @ Computes \begin{equation*} S_\alpha = \frac{P^{f_r(\alpha)}d^{-1}(\alpha)} {\sum_{f_r' \in T(F_r(\alpha))}P^{f_r'}\sum_{\alpha' \in Sr(f_r')}d^{-1}(\alpha)}. \end{equation*} <>= procedure :: compute_sumdij => fks_mapping_resonances_compute_sumdij <>= module subroutine fks_mapping_resonances_compute_sumdij & (map, sregion, p_real) class(fks_mapping_resonances_t), intent(inout) :: map type(singular_region_t), intent(in) :: sregion type(vector4_t), intent(in), dimension(:) :: p_real end subroutine fks_mapping_resonances_compute_sumdij <>= module subroutine fks_mapping_resonances_compute_sumdij (map, sregion, p_real) class(fks_mapping_resonances_t), intent(inout) :: map type(singular_region_t), intent(in) :: sregion type(vector4_t), intent(in), dimension(:) :: p_real real(default) :: d, pfr integer :: i_res, i_reg, i, j, i_con integer :: nlegreal nlegreal = size (p_real) d = zero do i_reg = 1, sregion%nregions associate (ftuple => sregion%ftuples(i_reg)) call ftuple%get (i, j) i_res = ftuple%i_res end associate pfr = map%res_map%get_resonance_value (i_res, p_real, nlegreal) i_con = sregion%i_reg_to_i_con (i_reg) d = d + pfr / map%dij (p_real, i, j, i_con) end do map%sumdij = d end subroutine fks_mapping_resonances_compute_sumdij @ %def fks_mapping_resonances_compute_sumdij @ <>= procedure :: svalue => fks_mapping_resonances_svalue <>= module function fks_mapping_resonances_svalue & (map, p, i, j, i_res) result (value) real(default) :: value class(fks_mapping_resonances_t), intent(in) :: map type(vector4_t), intent(in), dimension(:) :: p integer, intent(in) :: i, j integer, intent(in), optional :: i_res end function fks_mapping_resonances_svalue <>= module function fks_mapping_resonances_svalue & (map, p, i, j, i_res) result (value) real(default) :: value class(fks_mapping_resonances_t), intent(in) :: map type(vector4_t), intent(in), dimension(:) :: p integer, intent(in) :: i, j integer, intent(in), optional :: i_res real(default) :: pfr integer :: i_gluon i_gluon = size (p) pfr = map%res_map%get_resonance_value (i_res, p, i_gluon) value = pfr / (map%dij (p, i, j, map%i_con) * map%sumdij) end function fks_mapping_resonances_svalue @ %def fks_mapping_resonances_svalue @ <>= procedure :: get_resonance_weight => & fks_mapping_resonances_get_resonance_weight <>= module function fks_mapping_resonances_get_resonance_weight & (map, alr, p) result (pfr) real(default) :: pfr class(fks_mapping_resonances_t), intent(in) :: map integer, intent(in) :: alr type(vector4_t), intent(in), dimension(:) :: p end function fks_mapping_resonances_get_resonance_weight <>= module function fks_mapping_resonances_get_resonance_weight & (map, alr, p) result (pfr) real(default) :: pfr class(fks_mapping_resonances_t), intent(in) :: map integer, intent(in) :: alr type(vector4_t), intent(in), dimension(:) :: p pfr = map%res_map%get_weight (alr, p) end function fks_mapping_resonances_get_resonance_weight @ %def fks_mapping_resonances_get_resonance_weight @ As above, the soft limit of $d_{ij,k}$ must be computed in the resonance frame of reference. <>= procedure :: dij_soft => fks_mapping_resonances_dij_soft <>= module function fks_mapping_resonances_dij_soft & (map, p_born, p_soft, em, i_con) result (d) real(default) :: d class(fks_mapping_resonances_t), intent(in) :: map type(vector4_t), intent(in), dimension(:) :: p_born type(vector4_t), intent(in) :: p_soft integer, intent(in) :: em integer, intent(in), optional :: i_con end function fks_mapping_resonances_dij_soft <>= module function fks_mapping_resonances_dij_soft & (map, p_born, p_soft, em, i_con) result (d) real(default) :: d class(fks_mapping_resonances_t), intent(in) :: map type(vector4_t), intent(in), dimension(:) :: p_born type(vector4_t), intent(in) :: p_soft integer, intent(in) :: em integer, intent(in), optional :: i_con real(default) :: E1, E2 integer :: ii_con type(vector4_t) :: pb if (present (i_con)) then ii_con = i_con else call msg_fatal ("fks_mapping_resonances requires resonance index") end if associate (p_res => map%res_map%p_res(ii_con)) pb = p_born(em) E1 = pb * p_res E2 = p_soft * p_res d = two * pb * p_soft * E1 * E2 / E1**2 end associate end function fks_mapping_resonances_dij_soft @ %def fks_mapping_resonances_dij_soft @ <>= procedure :: compute_sumdij_soft => fks_mapping_resonances_compute_sumdij_soft <>= module subroutine fks_mapping_resonances_compute_sumdij_soft & (map, sregion, p_born, p_soft) class(fks_mapping_resonances_t), intent(inout) :: map type(singular_region_t), intent(in) :: sregion type(vector4_t), intent(in), dimension(:) :: p_born type(vector4_t), intent(in) :: p_soft end subroutine fks_mapping_resonances_compute_sumdij_soft <>= module subroutine fks_mapping_resonances_compute_sumdij_soft & (map, sregion, p_born, p_soft) class(fks_mapping_resonances_t), intent(inout) :: map type(singular_region_t), intent(in) :: sregion type(vector4_t), intent(in), dimension(:) :: p_born type(vector4_t), intent(in) :: p_soft real(default) :: d real(default) :: pfr integer :: i_res, i, j, i_reg, i_con integer :: nlegs d = zero nlegs = size (sregion%flst_real%flst) do i_reg = 1, sregion%nregions associate (ftuple => sregion%ftuples(i_reg)) call ftuple%get(i, j) i_res = ftuple%i_res end associate pfr = map%res_map%get_resonance_value (i_res, p_born) i_con = sregion%i_reg_to_i_con (i_reg) if (j == nlegs) d = d + pfr / map%dij_soft (p_born, p_soft, i, i_con) end do map%sumdij_soft = d end subroutine fks_mapping_resonances_compute_sumdij_soft @ %def fks_mapping_resonances_ompute_sumdij_soft @ <>= procedure :: svalue_soft => fks_mapping_resonances_svalue_soft <>= module function fks_mapping_resonances_svalue_soft & (map, p_born, p_soft, em, i_res) result (value) real(default) :: value class(fks_mapping_resonances_t), intent(in) :: map type(vector4_t), intent(in), dimension(:) :: p_born type(vector4_t), intent(in) :: p_soft integer, intent(in) :: em integer, intent(in), optional :: i_res end function fks_mapping_resonances_svalue_soft <>= module function fks_mapping_resonances_svalue_soft & (map, p_born, p_soft, em, i_res) result (value) real(default) :: value class(fks_mapping_resonances_t), intent(in) :: map type(vector4_t), intent(in), dimension(:) :: p_born type(vector4_t), intent(in) :: p_soft integer, intent(in) :: em integer, intent(in), optional :: i_res real(default) :: pfr pfr = map%res_map%get_resonance_value (i_res, p_born) value = pfr / (map%sumdij_soft * map%dij_soft & (p_born, p_soft, em, map%i_con)) end function fks_mapping_resonances_svalue_soft @ %def fks_mapping_resonances_svalue_soft @ <>= procedure :: set_resonance_momentum => & fks_mapping_resonances_set_resonance_momentum <>= module subroutine fks_mapping_resonances_set_resonance_momentum (map, p) class(fks_mapping_resonances_t), intent(inout) :: map type(vector4_t), intent(in) :: p end subroutine fks_mapping_resonances_set_resonance_momentum <>= module subroutine fks_mapping_resonances_set_resonance_momentum (map, p) class(fks_mapping_resonances_t), intent(inout) :: map type(vector4_t), intent(in) :: p map%res_map%p_res = p end subroutine fks_mapping_resonances_set_resonance_momentum @ %def fks_mapping_resonances_set_resonance_momentum @ <>= procedure :: set_resonance_momenta => & fks_mapping_resonances_set_resonance_momenta <>= module subroutine fks_mapping_resonances_set_resonance_momenta (map, p) class(fks_mapping_resonances_t), intent(inout) :: map type(vector4_t), intent(in), dimension(:) :: p end subroutine fks_mapping_resonances_set_resonance_momenta <>= module subroutine fks_mapping_resonances_set_resonance_momenta (map, p) class(fks_mapping_resonances_t), intent(inout) :: map type(vector4_t), intent(in), dimension(:) :: p map%res_map%p_res = p end subroutine fks_mapping_resonances_set_resonance_momenta @ %def fks_mapping_resonances_set_resonance_momenta @ <>= interface assignment(=) module procedure fks_mapping_resonances_assign end interface <>= module subroutine fks_mapping_resonances_assign (fks_map_out, fks_map_in) type(fks_mapping_resonances_t), intent(out) :: fks_map_out type(fks_mapping_resonances_t), intent(in) :: fks_map_in end subroutine fks_mapping_resonances_assign <>= module subroutine fks_mapping_resonances_assign (fks_map_out, fks_map_in) type(fks_mapping_resonances_t), intent(out) :: fks_map_out type(fks_mapping_resonances_t), intent(in) :: fks_map_in fks_map_out%exp_1 = fks_map_in%exp_1 fks_map_out%exp_2 = fks_map_in%exp_2 fks_map_out%res_map = fks_map_in%res_map end subroutine fks_mapping_resonances_assign @ %def fks_mapping_resonances_assign @ <>= public :: create_resonance_histories_for_threshold <>= module function create_resonance_histories_for_threshold & () result (res_history) type(resonance_history_t) :: res_history end function create_resonance_histories_for_threshold <>= module function create_resonance_histories_for_threshold & () result (res_history) type(resonance_history_t) :: res_history res_history%n_resonances = 2 allocate (res_history%resonances (2)) allocate (res_history%resonances(1)%contributors%c(2)) allocate (res_history%resonances(2)%contributors%c(2)) res_history%resonances(1)%contributors%c = [THR_POS_WP, THR_POS_B] res_history%resonances(2)%contributors%c = [THR_POS_WM, THR_POS_BBAR] end function create_resonance_histories_for_threshold @ %def create_resonance_histories_for_threshold @ <>= public :: setup_region_data_for_test <>= module subroutine setup_region_data_for_test (n_in, flv_born, flv_real, reg_data, & nlo_corr_type, alpha_pow, alphas_pow) integer, intent(in) :: n_in, alpha_pow, alphas_pow integer, intent(in), dimension(:,:) :: flv_born, flv_real type(string_t), intent(in) :: nlo_corr_type type(region_data_t), intent(out) :: reg_data end subroutine setup_region_data_for_test <>= module subroutine setup_region_data_for_test (n_in, flv_born, flv_real, reg_data, & nlo_corr_type, alpha_pow, alphas_pow) integer, intent(in) :: n_in, alpha_pow, alphas_pow integer, intent(in), dimension(:,:) :: flv_born, flv_real type(string_t), intent(in) :: nlo_corr_type type(region_data_t), intent(out) :: reg_data type(model_t), pointer :: test_model => null () call create_test_model (var_str ("SM"), test_model) call test_model%set_real (var_str ("me"), 0._default) call test_model%set_real (var_str ("mmu"), 0._default) call test_model%set_real (var_str ("mtau"), 0._default) call test_model%set_real (var_str ("ms"), 0._default) call test_model%set_real (var_str ("mc"), 0._default) call test_model%set_real (var_str ("mb"), 0._default) call reg_data%init (n_in, test_model, flv_born, flv_real, nlo_corr_type, alpha_pow, & alphas_pow) end subroutine setup_region_data_for_test @ %def setup_region_data_for_test @ \clearpage %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \subsection{Unit tests} \clearpage <<[[fks_regions_ut.f90]]>>= <> module fks_regions_ut use unit_tests use fks_regions_uti <> <> contains <> end module fks_regions_ut @ %def fks_regions_ut @ <<[[fks_regions_uti.f90]]>>= <> module fks_regions_uti <> use format_utils, only: write_separator use os_interface use models use fks_regions <> <> contains <> end module fks_regions_uti @ %def fks_regions_uti @ <>= public :: fks_regions_test <>= subroutine fks_regions_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results call test(fks_regions_1, "fks_regions_1", & "Test flavor structure utilities", u, results) call test(fks_regions_2, "fks_regions_2", & "Test singular regions for final-state radiation for n = 2", & u, results) call test(fks_regions_3, "fks_regions_3", & "Test singular regions for final-state radiation for n = 3", & u, results) call test(fks_regions_4, "fks_regions_4", & "Test singular regions for final-state radiation for n = 4", & u, results) call test(fks_regions_5, "fks_regions_5", & "Test singular regions for final-state radiation for n = 5", & u, results) call test(fks_regions_6, "fks_regions_6", & "Test singular regions for initial-state radiation", & u, results) call test(fks_regions_7, "fks_regions_7", & "Check Latex output", u, results) call test(fks_regions_8, "fks_regions_8", & "Test singular regions for initial-state photon contributions", & u, results) end subroutine fks_regions_test @ %def fks_regions_test @ <>= public :: fks_regions_1 <>= subroutine fks_regions_1 (u) integer, intent(in) :: u type(flv_structure_t) :: flv_born, flv_real type(model_t), pointer :: test_model => null () write (u, "(A)") "* Test output: fks_regions_1" write (u, "(A)") "* Purpose: Test utilities of flavor structure manipulation" write (u, "(A)") call create_test_model (var_str ("SM"), test_model) flv_born = [11, -11, 2, -2] flv_real = [11, -11, 2, -2, 21] flv_born%n_in = 2; flv_real%n_in = 2 write (u, "(A)") "* Valid splittings of ee -> uu" write (u, "(A)") "Born Flavors: " call flv_born%write (u) write (u, "(A)") "Real Flavors: " call flv_real%write (u) write (u, "(A,L1)") "3, 4 (2, -2) : ", flv_real%valid_pair (3, 4, flv_born, test_model) write (u, "(A,L1)") "4, 3 (-2, 2) : ", flv_real%valid_pair (4, 3, flv_born, test_model) write (u, "(A,L1)") "3, 5 (2, 21) : ", flv_real%valid_pair (3, 5, flv_born, test_model) write (u, "(A,L1)") "5, 3 (21, 2) : ", flv_real%valid_pair (5, 3, flv_born, test_model) write (u, "(A,L1)") "4, 5 (-2, 21): ", flv_real%valid_pair (4, 5, flv_born, test_model) write (u, "(A,L1)") "5, 4 (21, -2): ", flv_real%valid_pair (5, 4, flv_born, test_model) call write_separator (u) call flv_born%final () call flv_real%final () flv_born = [2, -2, 11, -11] flv_real = [2, -2, 11, -11, 21] flv_born%n_in = 2; flv_real%n_in = 2 write (u, "(A)") "* Valid splittings of uu -> ee" write (u, "(A)") "Born Flavors: " call flv_born%write (u) write (u, "(A)") "Real Flavors: " call flv_real%write (u) write (u, "(A,L1)") "1, 2 (2, -2) : " , flv_real%valid_pair (1, 2, flv_born, test_model) write (u, "(A,L1)") "2, 1 (-2, 2) : " , flv_real%valid_pair (2, 1, flv_born, test_model) write (u, "(A,L1)") "5, 2 (21, -2): " , flv_real%valid_pair (5, 2, flv_born, test_model) write (u, "(A,L1)") "2, 5 (-2, 21): " , flv_real%valid_pair (2, 5, flv_born, test_model) write (u, "(A,L1)") "1, 5 (21, 2) : " , flv_real%valid_pair (5, 1, flv_born, test_model) write (u, "(A,L1)") "5, 1 (2, 21) : " , flv_real%valid_pair (1, 5, flv_born, test_model) call flv_real%final () flv_real = [21, -2, 11, -11, -2] flv_real%n_in = 2 write (u, "(A)") "Real Flavors: " call flv_real%write (u) write (u, "(A,L1)") "1, 2 (21, -2): " , flv_real%valid_pair (1, 2, flv_born, test_model) write (u, "(A,L1)") "2, 1 (-2, 21): " , flv_real%valid_pair (2, 1, flv_born, test_model) write (u, "(A,L1)") "5, 2 (-2, -2): " , flv_real%valid_pair (5, 2, flv_born, test_model) write (u, "(A,L1)") "2, 5 (-2, -2): " , flv_real%valid_pair (2, 5, flv_born, test_model) write (u, "(A,L1)") "5, 1 (-2, 21): " , flv_real%valid_pair (5, 1, flv_born, test_model) write (u, "(A,L1)") "1, 5 (21, -2): " , flv_real%valid_pair (1, 5, flv_born, test_model) call flv_real%final () flv_real = [2, 21, 11, -11, 2] flv_real%n_in = 2 write (u, "(A)") "Real Flavors: " call flv_real%write (u) write (u, "(A,L1)") "1, 2 (2, 21) : " , flv_real%valid_pair (1, 2, flv_born, test_model) write (u, "(A,L1)") "2, 1 (21, 2) : " , flv_real%valid_pair (2, 1, flv_born, test_model) write (u, "(A,L1)") "5, 2 (2, 21) : " , flv_real%valid_pair (5, 2, flv_born, test_model) write (u, "(A,L1)") "2, 5 (21, 2) : " , flv_real%valid_pair (2, 5, flv_born, test_model) write (u, "(A,L1)") "5, 1 (2, 2) : " , flv_real%valid_pair (5, 1, flv_born, test_model) write (u, "(A,L1)") "1, 5 (2, 2) : " , flv_real%valid_pair (1, 5, flv_born, test_model) call write_separator (u) call flv_born%final () call flv_real%final () flv_born = [11, -11, 2, -2, 21] flv_real = [11, -11, 2, -2, 21, 21] flv_born%n_in = 2; flv_real%n_in = 2 write (u, "(A)") "* Valid splittings of ee -> uug" write (u, "(A)") "Born Flavors: " call flv_born%write (u) write (u, "(A)") "Real Flavors: " call flv_real%write (u) write (u, "(A,L1)") "3, 4 (2, -2) : " , flv_real%valid_pair (3, 4, flv_born, test_model) write (u, "(A,L1)") "4, 3 (-2, 2) : " , flv_real%valid_pair (4, 3, flv_born, test_model) write (u, "(A,L1)") "3, 5 (2, 21) : " , flv_real%valid_pair (3, 5, flv_born, test_model) write (u, "(A,L1)") "5, 3 (21, 2) : " , flv_real%valid_pair (5, 3, flv_born, test_model) write (u, "(A,L1)") "4, 5 (-2, 21): " , flv_real%valid_pair (4, 5, flv_born, test_model) write (u, "(A,L1)") "5, 4 (21, -2): " , flv_real%valid_pair (5, 4, flv_born, test_model) write (u, "(A,L1)") "3, 6 (2, 21) : " , flv_real%valid_pair (3, 6, flv_born, test_model) write (u, "(A,L1)") "6, 3 (21, 2) : " , flv_real%valid_pair (6, 3, flv_born, test_model) write (u, "(A,L1)") "4, 6 (-2, 21): " , flv_real%valid_pair (4, 6, flv_born, test_model) write (u, "(A,L1)") "6, 4 (21, -2): " , flv_real%valid_pair (6, 4, flv_born, test_model) write (u, "(A,L1)") "5, 6 (21, 21): " , flv_real%valid_pair (5, 6, flv_born, test_model) write (u, "(A,L1)") "6, 5 (21, 21): " , flv_real%valid_pair (6, 5, flv_born, test_model) call flv_real%final () flv_real = [11, -11, 2, -2, 1, -1] flv_real%n_in = 2 write (u, "(A)") "Real Flavors (exemplary g -> dd splitting): " call flv_real%write (u) write (u, "(A,L1)") "3, 4 (2, -2) : " , flv_real%valid_pair (3, 4, flv_born, test_model) write (u, "(A,L1)") "4, 3 (-2, 2) : " , flv_real%valid_pair (4, 3, flv_born, test_model) write (u, "(A,L1)") "3, 5 (2, 1) : " , flv_real%valid_pair (3, 5, flv_born, test_model) write (u, "(A,L1)") "5, 3 (1, 2) : " , flv_real%valid_pair (5, 3, flv_born, test_model) write (u, "(A,L1)") "4, 5 (-2, 1) : " , flv_real%valid_pair (4, 5, flv_born, test_model) write (u, "(A,L1)") "5, 4 (1, -2) : " , flv_real%valid_pair (5, 4, flv_born, test_model) write (u, "(A,L1)") "3, 6 (2, -1) : " , flv_real%valid_pair (3, 6, flv_born, test_model) write (u, "(A,L1)") "6, 3 (-1, 2) : " , flv_real%valid_pair (6, 3, flv_born, test_model) write (u, "(A,L1)") "4, 6 (-2, -1): " , flv_real%valid_pair (4, 6, flv_born, test_model) write (u, "(A,L1)") "6, 4 (-1, -2): " , flv_real%valid_pair (6, 4, flv_born, test_model) write (u, "(A,L1)") "5, 6 (1, -1) : " , flv_real%valid_pair (5, 6, flv_born, test_model) write (u, "(A,L1)") "6, 5 (-1, 1) : " , flv_real%valid_pair (6, 5, flv_born, test_model) call write_separator (u) call flv_born%final () call flv_real%final () flv_born = [6, -5, 2, -1 ] flv_real = [6, -5, 2, -1, 21] flv_born%n_in = 1; flv_real%n_in = 1 write (u, "(A)") "* Valid splittings of t -> b u d~" write (u, "(A)") "Born Flavors: " call flv_born%write (u) write (u, "(A)") "Real Flavors: " call flv_real%write (u) write (u, "(A,L1)") "1, 2 (6, -5) : " , flv_real%valid_pair (1, 2, flv_born, test_model) write (u, "(A,L1)") "1, 3 (6, 2) : " , flv_real%valid_pair (1, 3, flv_born, test_model) write (u, "(A,L1)") "1, 4 (6, -1) : " , flv_real%valid_pair (1, 4, flv_born, test_model) write (u, "(A,L1)") "2, 1 (-5, 6) : " , flv_real%valid_pair (2, 1, flv_born, test_model) write (u, "(A,L1)") "3, 1 (2, 6) : " , flv_real%valid_pair (3, 1, flv_born, test_model) write (u, "(A,L1)") "4, 1 (-1, 6) : " , flv_real%valid_pair (4, 1, flv_born, test_model) write (u, "(A,L1)") "2, 3 (-5, 2) : " , flv_real%valid_pair (2, 3, flv_born, test_model) write (u, "(A,L1)") "2, 4 (-5, -1): " , flv_real%valid_pair (2, 4, flv_born, test_model) write (u, "(A,L1)") "3, 2 (2, -5) : " , flv_real%valid_pair (3, 2, flv_born, test_model) write (u, "(A,L1)") "4, 2 (-1, -5): " , flv_real%valid_pair (4, 2, flv_born, test_model) write (u, "(A,L1)") "3, 4 (2, -1) : " , flv_real%valid_pair (3, 4, flv_born, test_model) write (u, "(A,L1)") "4, 3 (-1, 2) : " , flv_real%valid_pair (4, 3, flv_born, test_model) write (u, "(A,L1)") "1, 5 (6, 21) : " , flv_real%valid_pair (1, 5, flv_born, test_model) write (u, "(A,L1)") "5, 1 (21, 6) : " , flv_real%valid_pair (5, 1, flv_born, test_model) write (u, "(A,L1)") "2, 5 (-5, 21): " , flv_real%valid_pair (2, 5, flv_born, test_model) write (u, "(A,L1)") "5, 2 (21, 5) : " , flv_real%valid_pair (5, 2, flv_born, test_model) write (u, "(A,L1)") "3, 5 (2, 21) : " , flv_real%valid_pair (3, 5, flv_born, test_model) write (u, "(A,L1)") "5, 3 (21, 2) : " , flv_real%valid_pair (5, 3, flv_born, test_model) write (u, "(A,L1)") "4, 5 (-1, 21): " , flv_real%valid_pair (4, 5, flv_born, test_model) write (u, "(A,L1)") "5, 4 (21, -1): " , flv_real%valid_pair (5, 4, flv_born, test_model) call flv_born%final () call flv_real%final () end subroutine fks_regions_1 @ %def fks_regions_1 @ <>= public :: fks_regions_2 <>= subroutine fks_regions_2 (u) integer, intent(in) :: u integer :: n_flv_born, n_flv_real integer :: n_legs_born, n_legs_real integer :: n_in integer, dimension(:,:), allocatable :: flv_born, flv_real type(region_data_t) :: reg_data write (u, "(A)") "* Test output: fks_regions_2" write (u, "(A)") "* Create singular regions for processes with up to four singular regions" write (u, "(A)") "* ee -> qq with QCD corrections" write (u, "(A)") n_flv_born = 1; n_flv_real = 1 n_legs_born = 4; n_legs_real = 5 n_in = 2 allocate (flv_born (n_legs_born, n_flv_born)) allocate (flv_real (n_legs_real, n_flv_real)) flv_born (:, 1) = [11, -11, 2, -2] flv_real (:, 1) = [11, -11, 2, -2, 21] call setup_region_data_for_test (n_in, flv_born, flv_real, reg_data, var_str ("QCD"), 2, 0) call reg_data%check_consistency (.false., u) call reg_data%write (u) deallocate (flv_born, flv_real) call reg_data%final () call write_separator (u) write (u, "(A)") "* ee -> qq with EW corrections" write (u, "(A)") allocate (flv_born (n_legs_born, n_flv_born)) allocate (flv_real (n_legs_real, n_flv_real)) flv_born (:, 1) = [11, -11, 2, -2] flv_real (:, 1) = [11, -11, 2, -2, 22] call setup_region_data_for_test (n_in, flv_born, flv_real, reg_data, var_str ("EW"), 2, 0) call reg_data%check_consistency (.false., u) call reg_data%write (u) deallocate (flv_born, flv_real) call reg_data%final () call write_separator (u) write (u, "(A)") "* ee -> tt" write (u, "(A)") write (u, "(A)") "* This process has four singular regions because they are not equivalent." n_flv_born = 1; n_flv_real = 1 n_legs_born = 6; n_legs_real = 7 n_in = 2 allocate (flv_born (n_legs_born, n_flv_born)) allocate (flv_real (n_legs_real, n_flv_real)) flv_born (:, 1) = [11, -11, 6, -6, 6, -6] flv_real (:, 1) = [11, -11, 6, -6, 6, -6, 21] call setup_region_data_for_test (n_in, flv_born, flv_real, reg_data, var_str ("QCD"), 4, 0) call reg_data%check_consistency (.false., u) call reg_data%write (u) deallocate (flv_born, flv_real) call reg_data%final () end subroutine fks_regions_2 @ %def fks_regions_2 @ <>= public :: fks_regions_3 <>= subroutine fks_regions_3 (u) integer, intent(in) :: u integer :: n_flv_born, n_flv_real integer :: n_legs_born, n_legs_real integer :: n_in, i, j integer, dimension(:,:), allocatable :: flv_born, flv_real type(region_data_t) :: reg_data write (u, "(A)") "* Test output: fks_regions_3" write (u, "(A)") "* Create singular regions for processes with three final-state particles" write (u, "(A)") "* ee -> qqg" write (u, "(A)") n_flv_born = 1; n_flv_real = 2 n_legs_born = 5; n_legs_real = 6 n_in = 2 allocate (flv_born (n_legs_born, n_flv_born)) allocate (flv_real (n_legs_real, n_flv_real)) flv_born (:, 1) = [11, -11, 2, -2, 21] flv_real (:, 1) = [11, -11, 2, -2, 21, 21] flv_real (:, 2) = [11, -11, 2, -2, 1, -1] call setup_region_data_for_test (n_in, flv_born, flv_real, reg_data, var_str ("QCD"), 2, 1) call reg_data%check_consistency (.false., u) call reg_data%write (u) deallocate (flv_born, flv_real) call reg_data%final () call write_separator (u) write (u, "(A)") "* ee -> qqA" write (u, "(A)") n_flv_born = 1; n_flv_real = 2 n_legs_born = 5; n_legs_real = 6 n_in = 2 allocate (flv_born (n_legs_born, n_flv_born)) allocate (flv_real (n_legs_real, n_flv_real)) flv_born (:, 1) = [11, -11, 2, -2, 22] flv_real (:, 1) = [11, -11, 2, -2, 22, 22] flv_real (:, 2) = [11, -11, 2, -2, 11, -11] call setup_region_data_for_test (n_in, flv_born, flv_real, reg_data, var_str ("EW"), 3, 0) call reg_data%check_consistency (.false., u) call reg_data%write (u) deallocate (flv_born, flv_real) call reg_data%final () call write_separator (u) write (u, "(A)") "* ee -> jet jet jet" write (u, "(A)") "* with jet = u:U:d:D:s:S:c:C:b:B:gl" write (u, "(A)") n_flv_born = 5; n_flv_real = 22 n_legs_born = 5; n_legs_real = 6 n_in = 2 allocate (flv_born (n_legs_born, n_flv_born)) allocate (flv_real (n_legs_real, n_flv_real)) flv_born (:, 1) = [11, -11, -4, 4, 21] flv_born (:, 2) = [11, -11, -2, 2, 21] flv_born (:, 3) = [11, -11, -5, 5, 21] flv_born (:, 4) = [11, -11, -3, 3, 21] flv_born (:, 5) = [11, -11, -1, 1, 21] flv_real (:, 1) = [11, -11, -4, -4, 4, 4] flv_real (:, 2) = [11, -11, -4, -2, 2, 4] flv_real (:, 3) = [11, -11, -4, 4, 21, 21] flv_real (:, 4) = [11, -11, -4, -5, 4, 5] flv_real (:, 5) = [11, -11, -4, -3, 4, 3] flv_real (:, 6) = [11, -11, -4, -1, 2, 3] flv_real (:, 7) = [11, -11, -4, -1, 4, 1] flv_real (:, 8) = [11, -11, -2, -2, 2, 2] flv_real (:, 9) = [11, -11, -2, 2, 21, 21] flv_real (:, 10) = [11, -11, -2, -5, 2, 5] flv_real (:, 11) = [11, -11, -2, -3, 2, 3] flv_real (:, 12) = [11, -11, -2, -3, 4, 1] flv_real (:, 13) = [11, -11, -2, -1, 2, 1] flv_real (:, 14) = [11, -11, -5, -5, 5, 5] flv_real (:, 15) = [11, -11, -5, -3, 3, 5] flv_real (:, 16) = [11, -11, -5, -1, 1, 5] flv_real (:, 17) = [11, -11, -5, 5, 21, 21] flv_real (:, 18) = [11, -11, -3, -3, 3, 3] flv_real (:, 19) = [11, -11, -3, -1, 1, 3] flv_real (:, 20) = [11, -11, -3, 3, 21, 21] flv_real (:, 21) = [11, -11, -1, -1, 1, 1] flv_real (:, 22) = [11, -11, -1, 1, 21, 21] call setup_region_data_for_test (n_in, flv_born, flv_real, reg_data, var_str ("QCD"), 2, 1) call reg_data%check_consistency (.false., u) call reg_data%write (u) deallocate (flv_born, flv_real) call reg_data%final () call write_separator (u) write (u, "(A)") "* ee -> L L A" write (u, "(A)") "* with L = e2:E2:e3:E3" write (u, "(A)") n_flv_born = 2; n_flv_real = 6 n_legs_born = 5; n_legs_real = 6 n_in = 2 allocate (flv_born (n_legs_born, n_flv_born)) allocate (flv_real (n_legs_real, n_flv_real)) flv_born (:, 1) = [11, -11, -15, 15, 22] flv_born (:, 2) = [11, -11, -13, 13, 22] flv_real (:, 1) = [11, -11, -15, -15, 15, 15] flv_real (:, 2) = [11, -11, -15, -13, 13, 13] flv_real (:, 3) = [11, -11, -13, -15, 13, 15] flv_real (:, 4) = [11, -11, -15, 15, 22, 22] flv_real (:, 5) = [11, -11, -13, -13, 13, 13] flv_real (:, 6) = [11, -11, -13, 13, 22, 22] call setup_region_data_for_test (n_in, flv_born, flv_real, reg_data, var_str ("EW"), 3, 0) call reg_data%check_consistency (.false., u) call reg_data%write (u) deallocate (flv_born, flv_real) call reg_data%final () end subroutine fks_regions_3 @ %def fks_regions_3 @ <>= public :: fks_regions_4 <>= subroutine fks_regions_4 (u) integer, intent(in) :: u integer :: n_flv_born, n_flv_real integer :: n_legs_born, n_legs_real integer :: n_in integer, dimension(:,:), allocatable :: flv_born, flv_real type(region_data_t) :: reg_data write (u, "(A)") "* Test output: fks_regions_4" write (u, "(A)") "* Create singular regions for processes with four final-state particles" write (u, "(A)") "* ee -> 4 jet" write (u, "(A)") "* with jet = u:U:d:D:s:S:c:C:b:B:gl" write (u, "(A)") n_flv_born = 22; n_flv_real = 22 n_legs_born = 6; n_legs_real = 7 n_in = 2 allocate (flv_born (n_legs_born, n_flv_born)) allocate (flv_real (n_legs_real, n_flv_real)) flv_born (:, 1) = [11, -11, -4, -4, 4, 4] flv_born (:, 2) = [11, -11, -4, -2, 2, 4] flv_born (:, 3) = [11, -11, -4, 4, 21, 21] flv_born (:, 4) = [11, -11, -4, -5, 4, 5] flv_born (:, 5) = [11, -11, -4, -3, 4, 3] flv_born (:, 6) = [11, -11, -4, -1, 2, 3] flv_born (:, 7) = [11, -11, -4, -1, 4, 1] flv_born (:, 8) = [11, -11, -2, -2, 2, 2] flv_born (:, 9) = [11, -11, -2, 2, 21, 21] flv_born (:, 10) = [11, -11, -2, -5, 2, 5] flv_born (:, 11) = [11, -11, -2, -3, 2, 3] flv_born (:, 12) = [11, -11, -2, -3, 4, 1] flv_born (:, 13) = [11, -11, -2, -1, 2, 1] flv_born (:, 14) = [11, -11, -5, -5, 5, 5] flv_born (:, 15) = [11, -11, -5, -3, 3, 5] flv_born (:, 16) = [11, -11, -5, -1, 1, 5] flv_born (:, 17) = [11, -11, -5, 5, 21, 21] flv_born (:, 18) = [11, -11, -3, -3, 3, 3] flv_born (:, 19) = [11, -11, -3, -1, 1, 3] flv_born (:, 20) = [11, -11, -3, -3, 21, 21] flv_born (:, 21) = [11, -11, -1, -1, 1, 1] flv_born (:, 22) = [11, -11, -1, 1, 21, 21] flv_real (:, 1) = [11, -11, -4, -4, 4, 4, 21] flv_real (:, 2) = [11, -11, -4, -2, 2, 4, 21] flv_real (:, 3) = [11, -11, -4, 4, 21, 21, 21] flv_real (:, 4) = [11, -11, -4, -5, 4, 5, 21] flv_real (:, 5) = [11, -11, -4, -3, 4, 3, 21] flv_real (:, 6) = [11, -11, -4, -1, 2, 3, 21] flv_real (:, 7) = [11, -11, -4, -1, 4, 1, 21] flv_real (:, 8) = [11, -11, -2, -2, 2, 2, 21] flv_real (:, 9) = [11, -11, -2, 2, 21, 21, 21] flv_real (:, 10) = [11, -11, -2, -5, 2, 5, 21] flv_real (:, 11) = [11, -11, -2, -3, 2, 3, 21] flv_real (:, 12) = [11, -11, -2, -3, 4, 1, 21] flv_real (:, 13) = [11, -11, -2, -1, 2, 1, 21] flv_real (:, 14) = [11, -11, -5, -5, 5, 5, 21] flv_real (:, 15) = [11, -11, -5, -3, 3, 5, 21] flv_real (:, 16) = [11, -11, -5, -1, 1, 5, 21] flv_real (:, 17) = [11, -11, -5, 5, 21, 21, 21] flv_real (:, 18) = [11, -11, -3, -3, 3, 3, 21] flv_real (:, 19) = [11, -11, -3, -1, 1, 3, 21] flv_real (:, 20) = [11, -11, -3, 3, 21, 21, 21] flv_real (:, 21) = [11, -11, -1, -1, 1, 1, 21] flv_real (:, 22) = [11, -11, -1, 1, 21, 21, 21] call setup_region_data_for_test (n_in, flv_born, flv_real, reg_data, var_str ("QCD"), 2, 2) call reg_data%check_consistency (.false., u) call reg_data%write (u) deallocate (flv_born, flv_real) call reg_data%final () call write_separator (u) write (u, "(A)") "* ee -> bbmumu with QCD corrections" write (u, "(A)") n_flv_born = 1; n_flv_real = 1 n_legs_born = 6; n_legs_real = 7 n_in = 2 allocate (flv_born (n_legs_born, n_flv_born)) allocate (flv_real (n_legs_real, n_flv_real)) flv_born (:, 1) = [11, -11, -5, 5, -13, 13] flv_real (:, 1) = [11, -11, -5, 5, -13, 13, 21] call setup_region_data_for_test (n_in, flv_born, flv_real, reg_data, var_str ("QCD"), 4, 0) call reg_data%check_consistency (.false., u) call reg_data%write (u) deallocate (flv_born, flv_real) call reg_data%final () call write_separator (u) write (u, "(A)") "* ee -> bbmumu with EW corrections" write (u, "(A)") n_flv_born = 1; n_flv_real = 1 n_legs_born = 6; n_legs_real = 7 n_in = 2 allocate (flv_born (n_legs_born, n_flv_born)) allocate (flv_real (n_legs_real, n_flv_real)) flv_born (:, 1) = [11, -11, -5, 5, -13, 13] flv_real (:, 1) = [11, -11, -5, 5, -13, 13, 22] call setup_region_data_for_test (n_in, flv_born, flv_real, reg_data, var_str ("QCD"), 4, 0) call reg_data%check_consistency (.false., u) call reg_data%write (u) deallocate (flv_born, flv_real) call reg_data%final () end subroutine fks_regions_4 @ %def fks_regions_4 @ <>= public :: fks_regions_5 <>= subroutine fks_regions_5 (u) integer, intent(in) :: u integer :: n_flv_born, n_flv_real integer :: n_legs_born, n_legs_real integer :: n_in integer, dimension(:,:), allocatable :: flv_born, flv_real type(region_data_t) :: reg_data write (u, "(A)") "* Test output: fks_regions_5" write (u, "(A)") "* Create singular regions for processes with five final-state particles" write (u, "(A)") "* ee -> 5 jet" write (u, "(A)") "* with jet = u:U:d:D:s:S:c:C:b:B:gl" write (u, "(A)") n_flv_born = 22; n_flv_real = 67 n_legs_born = 7; n_legs_real = 8 n_in = 2 allocate (flv_born (n_legs_born, n_flv_born)) allocate (flv_real (n_legs_real, n_flv_real)) flv_born (:,1) = [11,-11,-4,-4,4,4,21] flv_born (:,2) = [11,-11,-4,-2,2,4,21] flv_born (:,3) = [11,-11,-4,4,21,21,21] flv_born (:,4) = [11,-11,-4,-5,4,5,21] flv_born (:,5) = [11,-11,-4,-3,4,3,21] flv_born (:,6) = [11,-11,-4,-1,2,3,21] flv_born (:,7) = [11,-11,-4,-1,4,1,21] flv_born (:,8) = [11,-11,-2,-2,2,2,21] flv_born (:,9) = [11,-11,-2,2,21,21,21] flv_born (:,10) = [11,-11,-2,-5,2,5,21] flv_born (:,11) = [11,-11,-2,-3,2,3,21] flv_born (:,12) = [11,-11,-2,-3,4,1,21] flv_born (:,13) = [11,-11,-2,-1,2,1,21] flv_born (:,14) = [11,-11,-5,-5,5,5,21] flv_born (:,15) = [11,-11,-5,-3,3,5,21] flv_born (:,16) = [11,-11,-5,-1,1,5,21] flv_born (:,17) = [11,-11,-5,5,21,21,21] flv_born (:,18) = [11,-11,-3,-3,3,3,21] flv_born (:,19) = [11,-11,-3,-1,1,3,21] flv_born (:,20) = [11,-11,-3,3,21,21,21] flv_born (:,21) = [11,-11,-1,-1,1,1,21] flv_born (:,22) = [11,-11,-1,1,21,21,21] flv_real (:,1) = [11,-11,-4,-4,-4,4,4,4] flv_real (:,2) = [11,-11,-4,-4,-2,2,4,4] flv_real (:,3) = [11,-11,-4,-4,4,4,21,21] flv_real (:,4) = [11,-11,-4,-4,-5,4,4,5] flv_real (:,5) = [11,-11,-4,-4,-3,4,4,3] flv_real (:,6) = [11,-11,-4,-4,-1,2,4,3] flv_real (:,7) = [11,-11,-4,-4,-1,4,4,1] flv_real (:,8) = [11,-11,-4,-2,-2,2,2,4] flv_real (:,9) = [11,-11,-4,-2,2,4,21,21] flv_real (:,10) = [11,-11,-4,-2,-5,2,4,5] flv_real (:,11) = [11,-11,-4,-2,-3,2,4,3] flv_real (:,12) = [11,-11,-4,-2,-3,4,4,1] flv_real (:,13) = [11,-11,-4,-2,-1,2,2,3] flv_real (:,14) = [11,-11,-4,-2,-1,2,4,1] flv_real (:,15) = [11,-11,-4,4,21,21,21,21] flv_real (:,16) = [11,-11,-4,-5,4,5,21,21] flv_real (:,17) = [11,-11,-4,-5,-5,4,5,5] flv_real (:,18) = [11,-11,-4,-5,-3,4,3,5] flv_real (:,19) = [11,-11,-4,-5,-1,2,3,5] flv_real (:,20) = [11,-11,-4,-5,-1,4,1,5] flv_real (:,21) = [11,-11,-4,-3,4,3,21,21] flv_real (:,22) = [11,-11,-4,-3,-3,4,3,3] flv_real (:,23) = [11,-11,-4,-3,-1,2,3,3] flv_real (:,24) = [11,-11,-4,-3,-1,4,1,3] flv_real (:,25) = [11,-11,-4,-1,2,3,21,21] flv_real (:,26) = [11,-11,-4,-1,4,1,21,21] flv_real (:,27) = [11,-11,-4,-1,-1,2,1,3] flv_real (:,28) = [11,-11,-4,-1,-1,4,1,1] flv_real (:,29) = [11,-11,-2,-2,-2,2,2,2] flv_real (:,30) = [11,-11,-2,-2,2,2,21,21] flv_real (:,31) = [11,-11,-2,-2,-5,2,2,5] flv_real (:,32) = [11,-11,-2,-2,-3,2,2,3] flv_real (:,33) = [11,-11,-2,-2,-3,2,4,1] flv_real (:,34) = [11,-11,-2,-2,-1,2,2,1] flv_real (:,35) = [11,-11,-2,2,21,21,21,21] flv_real (:,36) = [11,-11,-2,-5,2,5,21,21] flv_real (:,37) = [11,-11,-2,-5,-5,2,5,5] flv_real (:,38) = [11,-11,-2,-5,-3,2,3,5] flv_real (:,39) = [11,-11,-2,-5,-3,4,1,5] flv_real (:,40) = [11,-11,-2,-5,-1,2,1,5] flv_real (:,41) = [11,-11,-2,-3,2,3,21,21] flv_real (:,42) = [11,-11,-2,-3,4,1,21,21] flv_real (:,43) = [11,-11,-2,-3,-3,2,3,3] flv_real (:,44) = [11,-11,-2,-3,-3,4,1,3] flv_real (:,45) = [11,-11,-2,-3,-1,2,1,3] flv_real (:,46) = [11,-11,-2,-3,-1,4,1,1] flv_real (:,47) = [11,-11,-2,-1,2,1,21,21] flv_real (:,48) = [11,-11,-2,-1,-1,2,1,1] flv_real (:,49) = [11,-11,-5,-5,-5,5,5,5] flv_real (:,50) = [11,-11,-5,-5,-3,3,5,5] flv_real (:,51) = [11,-11,-5,-5,-1,1,5,5] flv_real (:,52) = [11,-11,-5,-5,5,5,21,21] flv_real (:,53) = [11,-11,-5,-3,-3,3,3,5] flv_real (:,54) = [11,-11,-5,-3,-1,1,3,5] flv_real (:,55) = [11,-11,-5,-3,3,5,21,21] flv_real (:,56) = [11,-11,-5,-1,-1,1,1,5] flv_real (:,57) = [11,-11,-5,-1,1,5,21,21] flv_real (:,58) = [11,-11,-5,5,21,21,21,21] flv_real (:,59) = [11,-11,-3,-3,-3,3,3,3] flv_real (:,60) = [11,-11,-3,-3,-1,1,3,3] flv_real (:,61) = [11,-11,-3,-3,3,3,21,21] flv_real (:,62) = [11,-11,-3,-1,-1,1,1,3] flv_real (:,63) = [11,-11,-3,-1,1,3,21,21] flv_real (:,64) = [11,-11,-3,3,21,21,21,21] flv_real (:,65) = [11,-11,-1,-1,-1,1,1,1] flv_real (:,66) = [11,-11,-1,-1,1,1,21,21] flv_real (:,67) = [11,-11,-1,1,21,21,21,21] call setup_region_data_for_test (n_in, flv_born, flv_real, reg_data, var_str ("QCD"), 2, 3) call reg_data%check_consistency (.false., u) call reg_data%write (u) deallocate (flv_born, flv_real) call reg_data%final () end subroutine fks_regions_5 @ %def fks_regions_5 @ <>= public :: fks_regions_6 <>= subroutine fks_regions_6 (u) integer, intent(in) :: u integer :: n_flv_born, n_flv_real integer :: n_legs_born, n_legs_real integer :: n_in integer, dimension(:,:), allocatable :: flv_born, flv_real type(region_data_t) :: reg_data integer :: i, j integer, dimension(10) :: flavors write (u, "(A)") "* Test output: fks_regions_6" write (u, "(A)") "* Create table of singular regions for Drell Yan" write (u, "(A)") n_flv_born = 10; n_flv_real = 30 n_legs_born = 4; n_legs_real = 5 n_in = 2 allocate (flv_born (n_legs_born, n_flv_born)) allocate (flv_real (n_legs_real, n_flv_real)) flavors = [-5, -4, -3, -2, -1, 1, 2, 3, 4, 5] do i = 1, n_flv_born flv_born (3:4, i) = [11, -11] end do do j = 1, n_flv_born flv_born (1, j) = flavors (j) flv_born (2, j) = -flavors (j) end do do i = 1, n_flv_real flv_real (3:4, i) = [11, -11] end do i = 1 do j = 1, n_flv_real if (mod (j, 3) == 1) then flv_real (1, j) = flavors (i) flv_real (2, j) = -flavors (i) flv_real (5, j) = 21 else if (mod (j, 3) == 2) then flv_real (1, j) = flavors (i) flv_real (2, j) = 21 flv_real (5, j) = flavors (i) else flv_real (1, j) = 21 flv_real (2, j) = -flavors (i) flv_real (5, j) = -flavors (i) i = i + 1 end if end do call setup_region_data_for_test (n_in, flv_born, flv_real, reg_data, var_str ("QCD"), 2, 0) call reg_data%check_consistency (.false., u) call reg_data%write (u) call write_separator (u) deallocate (flv_born, flv_real) call reg_data%final () write (u, "(A)") "* Create table of singular regions for hadronic top decay" write (u, "(A)") n_flv_born = 1; n_flv_real = 1 n_legs_born = 4; n_legs_real = 5 n_in = 1 allocate (flv_born (n_legs_born, n_flv_born)) allocate (flv_real (n_legs_real, n_flv_real)) flv_born (:, 1) = [6, -5, 2, -1] flv_real (:, 1) = [6, -5, 2, -1, 21] call setup_region_data_for_test (n_in, flv_born, flv_real, reg_data, var_str ("QCD"), 0, 2) call reg_data%check_consistency (.false., u) call reg_data%write (u) call write_separator (u) deallocate (flv_born, flv_real) call reg_data%final () write (u, "(A)") "* Create table of singular regions for dijet s sbar -> jet jet" write (u, "(A)") "* With jet = u:d:gl" write (u, "(A)") n_flv_born = 3; n_flv_real = 3 n_legs_born = 4; n_legs_real = 5 n_in = 2 allocate (flv_born (n_legs_born, n_flv_born)) allocate (flv_real (n_legs_real, n_flv_real)) do i = 1, n_flv_born flv_born (1:2, i) = [3, -3] end do flv_born (3, :) = [1, 2, 21] flv_born (4, :) = [-1, -2, 21] do i = 1, n_flv_real flv_real (1:2, i) = [3, -3] end do flv_real (3, :) = [1, 2, 21] flv_real (4, :) = [-1, -2, 21] flv_real (5, :) = [21, 21, 21] call setup_region_data_for_test (n_in, flv_born, flv_real, reg_data, var_str ("QCD"), 0, 2) call reg_data%check_consistency (.false., u) call reg_data%write (u) call reg_data%final () end subroutine fks_regions_6 @ %def fks_regions_6 @ <>= public :: fks_regions_7 <>= subroutine fks_regions_7 (u) integer, intent(in) :: u integer :: n_flv_born, n_flv_real integer :: n_legs_born, n_legs_real integer :: n_in integer, dimension(:,:), allocatable :: flv_born, flv_real type(region_data_t) :: reg_data write (u, "(A)") "* Test output: fks_regions_7" write (u, "(A)") "* Create table of singular regions for ee -> qq" write (u, "(A)") n_flv_born = 1; n_flv_real = 1 n_legs_born = 4; n_legs_real = 5 n_in = 2 allocate (flv_born (n_legs_born, n_flv_born)) allocate (flv_real (n_legs_real, n_flv_real)) flv_born (:, 1) = [11, -11, 2, -2] flv_real (:, 1) = [11, -11, 2, -2, 21] call setup_region_data_for_test (n_in, flv_born, flv_real, reg_data, var_str ("QCD"), 2, 0) call reg_data%write_latex (u) call reg_data%final () end subroutine fks_regions_7 @ %def fks_regions_7 @ <>= public :: fks_regions_8 <>= subroutine fks_regions_8 (u) integer, intent(in) :: u integer :: n_flv_born, n_flv_real integer :: n_legs_born, n_legs_real integer :: n_in integer, dimension(:,:), allocatable :: flv_born, flv_real type(region_data_t) :: reg_data integer :: i, j integer, dimension(10) :: flavors write (u, "(A)") "* Test output: fks_regions_8" write (u, "(A)") "* Create table of singular regions for ee -> ee" write (u, "(A)") n_flv_born = 1; n_flv_real = 3 n_legs_born = 4; n_legs_real = 5 n_in = 2 allocate (flv_born (n_legs_born, n_flv_born)) allocate (flv_real (n_legs_real, n_flv_real)) flv_born (:, 1) = [11, -11, -11, 11] flv_real (:, 1) = [11, -11, -11, 11, 22] flv_real (:, 2) = [11, 22, -11, 11, 11] flv_real (:, 3) = [22, -11, 11, -11, -11] call setup_region_data_for_test (n_in, flv_born, flv_real, reg_data, var_str ("EW"), 2, 0) call reg_data%check_consistency (.false., u) call reg_data%write (u) call reg_data%final () end subroutine fks_regions_8 @ %def fks_regions_8 @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{NLO infrastructure and data} This module contains the settings and data infrastructure. <<[[nlo_data.f90]]>>= <> module nlo_data <> <> use constants, only: zero use lorentz use variables, only: var_list_t use physics_defs, only: NO_FACTORIZATION, FACTORIZATION_THRESHOLD <> <> <> <> interface <> end interface end module nlo_data @ %def nlo_data @ <<[[nlo_data_sub.f90]]>>= <> submodule (nlo_data) nlo_data_s use diagnostics use string_utils, only: split_string, read_ival, string_contains_word use io_units use format_defs, only: FMT_15 use physics_defs, only: THR_POS_WP, THR_POS_WM use physics_defs, only: THR_POS_B, THR_POS_BBAR implicit none contains <> end submodule nlo_data_s @ %def nlo_data_s @ <>= integer, parameter, public :: FKS_DEFAULT = 1 integer, parameter, public :: FKS_RESONANCES = 2 integer, dimension(2), parameter, public :: ASSOCIATED_LEG_PAIR = [1, 3] @ %def parameters @ <>= public :: fks_template_t <>= type :: fks_template_t logical :: subtraction_disabled = .false. integer :: mapping_type = FKS_DEFAULT logical :: count_kinematics = .false. real(default) :: fks_dij_exp1 real(default) :: fks_dij_exp2 real(default) :: xi_min real(default) :: y_max real(default) :: xi_cut, delta_o, delta_i type(string_t), dimension(:), allocatable :: excluded_resonances integer :: n_f contains <> end type fks_template_t @ %def fks_template_t @ <>= procedure :: write => fks_template_write <>= module subroutine fks_template_write (template, unit) class(fks_template_t), intent(in) :: template integer, intent(in), optional :: unit end subroutine fks_template_write <>= module subroutine fks_template_write (template, unit) class(fks_template_t), intent(in) :: template integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u,'(1x,A)') 'FKS Template: ' write (u,'(1x,A)', advance = 'no') 'Mapping Type: ' select case (template%mapping_type) case (FKS_DEFAULT) write (u,'(A)') 'Default' case (FKS_RESONANCES) write (u,'(A)') 'Resonances' case default write (u,'(A)') 'Unkown' end select write (u,'(1x,A,ES4.3,ES4.3)') 'd_ij exponentials: ', & template%fks_dij_exp1, template%fks_dij_exp2 write (u, '(1x,A,ES4.3,ES4.3)') 'xi_cut: ', & template%xi_cut write (u, '(1x,A,ES4.3,ES4.3)') 'delta_o: ', & template%delta_o write (u, '(1x,A,ES4.3,ES4.3)') 'delta_i: ', & template%delta_i end subroutine fks_template_write @ %def fks_template_write @ Set FKS parameters. $\xi_{\text{cut}}, \delta_o$ and $\delta_{\mathrm{I}}$ steer the ratio of the integrated and real subtraction. <>= procedure :: set_parameters => fks_template_set_parameters <>= module subroutine fks_template_set_parameters (template, & exp1, exp2, xi_min, y_max, xi_cut, delta_o, delta_i) class(fks_template_t), intent(inout) :: template real(default), intent(in) :: exp1, exp2 real(default), intent(in) :: xi_min, y_max, & xi_cut, delta_o, delta_i end subroutine fks_template_set_parameters <>= module subroutine fks_template_set_parameters (template, & exp1, exp2, xi_min, y_max, xi_cut, delta_o, delta_i) class(fks_template_t), intent(inout) :: template real(default), intent(in) :: exp1, exp2 real(default), intent(in) :: xi_min, y_max, & xi_cut, delta_o, delta_i template%fks_dij_exp1 = exp1 template%fks_dij_exp2 = exp2 template%xi_min = xi_min template%y_max = y_max template%xi_cut = xi_cut template%delta_o = delta_o template%delta_i = delta_i end subroutine fks_template_set_parameters @ %def fks_template_set_parameters <>= procedure :: set_mapping_type => fks_template_set_mapping_type <>= module subroutine fks_template_set_mapping_type (template, val) class(fks_template_t), intent(inout) :: template integer, intent(in) :: val end subroutine fks_template_set_mapping_type <>= module subroutine fks_template_set_mapping_type (template, val) class(fks_template_t), intent(inout) :: template integer, intent(in) :: val template%mapping_type = val end subroutine fks_template_set_mapping_type @ %def fks_template_set_mapping_type @ <>= procedure :: set_counter => fks_template_set_counter <>= module subroutine fks_template_set_counter (template) class(fks_template_t), intent(inout) :: template end subroutine fks_template_set_counter <>= module subroutine fks_template_set_counter (template) class(fks_template_t), intent(inout) :: template template%count_kinematics = .true. end subroutine fks_template_set_counter @ %def fks_template_set_counter @ <>= public :: get_threshold_momenta <>= module function get_threshold_momenta (p) result (p_thr) type(vector4_t), dimension(4) :: p_thr type(vector4_t), intent(in), dimension(:) :: p end function get_threshold_momenta <>= module function get_threshold_momenta (p) result (p_thr) type(vector4_t), dimension(4) :: p_thr type(vector4_t), intent(in), dimension(:) :: p p_thr(1) = p(THR_POS_WP) + p(THR_POS_B) p_thr(2) = p(THR_POS_B) p_thr(3) = p(THR_POS_WM) + p(THR_POS_BBAR) p_thr(4) = p(THR_POS_BBAR) end function get_threshold_momenta @ %def get_threshold_momenta @ \subsection{NLO settings and steering} <>= public :: nlo_settings_t <>= type :: nlo_settings_t logical :: use_internal_color_correlations = .true. logical :: use_internal_spin_correlations = .false. logical :: use_resonance_mappings = .false. logical :: combined_integration = .false. logical :: fixed_order_nlo = .false. logical :: test_soft_limit = .false. logical :: test_coll_limit = .false. logical :: test_anti_coll_limit = .false. integer, dimension(:), allocatable :: selected_alr integer :: factorization_mode = NO_FACTORIZATION !!! Probably not the right place for this. Revisit after refactoring real(default) :: powheg_damping_scale = zero type(fks_template_t) :: fks_template type(string_t) :: virtual_selection logical :: virtual_resonance_aware_collinear = .true. logical :: use_born_scale = .false. logical :: cut_all_real_sqmes = .false. type(string_t) :: nlo_correction_type logical :: reuse_amplitudes_fks = .false. contains <> end type nlo_settings_t @ %def nlo_settings_t @ <>= procedure :: init => nlo_settings_init <>= module subroutine nlo_settings_init (nlo_settings, var_list, fks_template) class(nlo_settings_t), intent(inout) :: nlo_settings type(var_list_t), intent(in) :: var_list type(fks_template_t), intent(in), optional :: fks_template end subroutine nlo_settings_init <>= module subroutine nlo_settings_init (nlo_settings, var_list, fks_template) class(nlo_settings_t), intent(inout) :: nlo_settings type(var_list_t), intent(in) :: var_list type(fks_template_t), intent(in), optional :: fks_template type(string_t) :: color_method if (present (fks_template)) nlo_settings%fks_template = fks_template color_method = var_list%get_sval (var_str ('$correlation_me_method')) if (color_method == "") & color_method = var_list%get_sval (var_str ('$method')) nlo_settings%use_internal_color_correlations = color_method == 'omega' & .or. color_method == 'threshold' nlo_settings%combined_integration = var_list%get_lval & (var_str ("?combined_nlo_integration")) nlo_settings%fixed_order_nlo = var_list%get_lval & (var_str ("?fixed_order_nlo_events")) nlo_settings%test_soft_limit = & var_list%get_lval (var_str ('?test_soft_limit')) nlo_settings%test_coll_limit = & var_list%get_lval (var_str ('?test_coll_limit')) nlo_settings%test_anti_coll_limit = & var_list%get_lval (var_str ('?test_anti_coll_limit')) call setup_alr_selection () nlo_settings%virtual_selection = & var_list%get_sval (var_str ('$virtual_selection')) nlo_settings%virtual_resonance_aware_collinear = & var_list%get_lval (var_str ('?virtual_collinear_resonance_aware')) nlo_settings%powheg_damping_scale = & var_list%get_rval (var_str ('powheg_damping_scale')) nlo_settings%use_born_scale = & var_list%get_lval (var_str ("?nlo_use_born_scale")) nlo_settings%cut_all_real_sqmes = & var_list%get_lval (var_str ("?nlo_cut_all_real_sqmes")) nlo_settings%nlo_correction_type = & var_list%get_sval (var_str ('$nlo_correction_type')) nlo_settings%reuse_amplitudes_fks = & var_list%get_lval (var_str ('?nlo_reuse_amplitudes_fks')) contains subroutine setup_alr_selection () type(string_t) :: alr_selection type(string_t), dimension(:), allocatable :: alr_split integer :: i, i1, i2 alr_selection = var_list%get_sval (var_str ('$select_alpha_regions')) if (string_contains_word (alr_selection, var_str (","))) then call split_string (alr_selection, var_str (","), alr_split) allocate (nlo_settings%selected_alr (size (alr_split))) do i = 1, size (alr_split) nlo_settings%selected_alr(i) = read_ival(alr_split(i)) end do else if (string_contains_word (alr_selection, var_str (":"))) then call split_string (alr_selection, var_str (":"), alr_split) if (size (alr_split) == 2) then i1 = read_ival (alr_split(1)) i2 = read_ival (alr_split(2)) allocate (nlo_settings%selected_alr (i2 - i1 + 1)) do i = 1, i2 - i1 + 1 nlo_settings%selected_alr(i) = read_ival (alr_split(i)) end do else call msg_fatal ("select_alpha_regions: ':' specifies a range!") end if else if (len(alr_selection) == 1) then allocate (nlo_settings%selected_alr (1)) nlo_settings%selected_alr(1) = read_ival (alr_selection) end if if (allocated (alr_split)) deallocate (alr_split) end subroutine setup_alr_selection end subroutine nlo_settings_init @ %def nlo_settings_init @ <>= procedure :: write => nlo_settings_write <>= module subroutine nlo_settings_write (nlo_settings, unit) class(nlo_settings_t), intent(in) :: nlo_settings integer, intent(in), optional :: unit end subroutine nlo_settings_write <>= module subroutine nlo_settings_write (nlo_settings, unit) class(nlo_settings_t), intent(in) :: nlo_settings integer, intent(in), optional :: unit integer :: i, u u = given_output_unit (unit); if (u < 0) return write (u, '(A)') 'nlo_settings:' write (u, '(3X,A,L1)') 'internal_color_correlations = ', & nlo_settings%use_internal_color_correlations write (u, '(3X,A,L1)') 'internal_spin_correlations = ', & nlo_settings%use_internal_spin_correlations write (u, '(3X,A,L1)') 'use_resonance_mappings = ', & nlo_settings%use_resonance_mappings write (u, '(3X,A,L1)') 'combined_integration = ', & nlo_settings%combined_integration write (u, '(3X,A,L1)') 'test_soft_limit = ', & nlo_settings%test_soft_limit write (u, '(3X,A,L1)') 'test_coll_limit = ', & nlo_settings%test_coll_limit write (u, '(3X,A,L1)') 'test_anti_coll_limit = ', & nlo_settings%test_anti_coll_limit if (allocated (nlo_settings%selected_alr)) then write (u, '(3x,A)', advance = "no") 'selected alpha regions = [' do i = 1, size (nlo_settings%selected_alr) write (u, '(A,I0)', advance = "no") ",", & nlo_settings%selected_alr(i) end do write (u, '(A)') "]" end if write (u, '(3X,A,' // FMT_15 // ')') 'powheg_damping_scale = ', & nlo_settings%powheg_damping_scale write (u, '(3X,A,A)') 'virtual_selection = ', & char (nlo_settings%virtual_selection) write (u, '(3X,A,A)') 'Real factorization mode = ', & char (factorization_mode (nlo_settings%factorization_mode)) contains function factorization_mode (fm) type(string_t) :: factorization_mode integer, intent(in) :: fm select case (fm) case (NO_FACTORIZATION) factorization_mode = var_str ("None") case (FACTORIZATION_THRESHOLD) factorization_mode = var_str ("Threshold") case default factorization_mode = var_str ("Undefined!") end select end function factorization_mode end subroutine nlo_settings_write @ %def nlo_settings_write @ \clearpage %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Virtual contribution to the cross section} This module implements the UV-finite virtual contribution of an NLO calculation together with the integrated (FKS) subtraction terms. <<[[virtual.f90]]>>= <> module virtual <> <> use pdg_arrays use models use model_data, only: model_data_t, field_data_t use lorentz use nlo_data, only: nlo_settings_t use fks_regions <> <> <> interface <> end interface end module virtual @ %def virtual @ <<[[virtual_sub.f90]]>>= <> submodule (virtual) virtual_s <> use constants use numeric_utils use diagnostics use physics_defs use sm_physics use flavors use nlo_data, only: ASSOCIATED_LEG_PAIR, get_threshold_momenta implicit none contains <> end submodule virtual_s @ %def virtual_s @ <>= public :: virtual_t <>= type :: virtual_t type(nlo_settings_t) :: settings real(default), dimension(:,:,:), allocatable :: gamma_0, gamma_p, c_flv real(default) :: fac_scale real(default), allocatable :: ren_scale real(default), allocatable :: es_scale2 integer, dimension(:), allocatable :: n_is_neutrinos integer :: n_in, n_legs, n_flv logical :: bad_point = .false. type(string_t) :: selection real(default), dimension(:), allocatable :: sqme_born real(default), dimension(:), allocatable :: sqme_virt_fin real(default), dimension(:,:,:), allocatable :: sqme_color_c real(default), dimension(:,:,:), allocatable :: sqme_charge_c logical :: has_pdfs = .false. contains <> end type virtual_t @ %def virtual_t @ <>= procedure :: init => virtual_init <>= module subroutine virtual_init & (virt, flv_born, n_in, settings, model, has_pdfs) class(virtual_t), intent(inout) :: virt integer, intent(in), dimension(:,:) :: flv_born integer, intent(in) :: n_in type(nlo_settings_t), intent(in) :: settings class(model_data_t), intent(in) :: model logical, intent(in) :: has_pdfs end subroutine virtual_init <>= module subroutine virtual_init & (virt, flv_born, n_in, settings, model, has_pdfs) class(virtual_t), intent(inout) :: virt integer, intent(in), dimension(:,:) :: flv_born integer, intent(in) :: n_in type(nlo_settings_t), intent(in) :: settings class(model_data_t), intent(in) :: model logical, intent(in) :: has_pdfs integer :: i_flv, n_corr n_corr = 2 virt%n_legs = size (flv_born, 1); virt%n_flv = size (flv_born, 2) virt%n_in = n_in allocate (virt%sqme_born (virt%n_flv)) allocate (virt%sqme_virt_fin (virt%n_flv)) allocate (virt%sqme_color_c (virt%n_legs, virt%n_legs, virt%n_flv)) allocate (virt%sqme_charge_c (virt%n_legs, virt%n_legs, virt%n_flv)) allocate (virt%gamma_0 (virt%n_legs, virt%n_flv, n_corr), & virt%gamma_p (virt%n_legs, virt%n_flv, n_corr), & virt%c_flv (virt%n_legs, virt%n_flv, n_corr)) call virt%init_constants (flv_born, settings%fks_template%n_f, model) allocate (virt%n_is_neutrinos (virt%n_flv)) virt%n_is_neutrinos = 0 do i_flv = 1, virt%n_flv if (is_neutrino (flv_born(1, i_flv))) & virt%n_is_neutrinos(i_flv) = virt%n_is_neutrinos(i_flv) + 1 if (is_neutrino (flv_born(2, i_flv))) & virt%n_is_neutrinos(i_flv) = virt%n_is_neutrinos(i_flv) + 1 end do select case (char (settings%virtual_selection)) case ("Full", "OLP", "Subtraction") virt%selection = settings%virtual_selection case default call msg_fatal ('Virtual selection: Possible values are "Full", "OLP" or "Subtraction') end select virt%settings = settings virt%has_pdfs = has_pdfs contains function is_neutrino (flv) result (neutrino) integer, intent(in) :: flv logical :: neutrino neutrino = (abs(flv) == 12 .or. abs(flv) == 14 .or. abs(flv) == 16) end function is_neutrino end subroutine virtual_init @ %def virtual_init @ The virtual subtraction terms contain Casimir operators and derived constants, listed below: \begin{align} \label{eqn:C(q)} C(q) = C(\bar{q}) &= C_F, \\ \label{eqn:C(g)} C(g) &= C_A,\\ \label{eqn:gamma(q)} \gamma(q) = \gamma(\bar{q}) &= \frac{3}{2} C_F,\\ \label{eqn:gamma(g)} \gamma(g) &= \frac{11}{6} C_A - \frac{2}{3} T_F N_f,\\ \label{eqn:gammap(q)} \gamma'(q) = \gamma'(\bar{q}) &= \left(\frac{13}{2} - \frac{2\pi^2}{3}\right) C_F, \\ \label{eqn:gammap(g)} \gamma'(g) &= \left(\frac{67}{9} - \frac{2\pi^2}{3}\right) C_A - \frac{23}{9} T_F N_f. \end{align} For uncolored particles, [[virtual_init_constants]] sets $C$, $\gamma$ and $\gamma'$ to zero. <>= procedure :: init_constants => virtual_init_constants <>= module subroutine virtual_init_constants (virt, flv_born, nf_input, model) class(virtual_t), intent(inout) :: virt integer, intent(in), dimension(:,:) :: flv_born integer, intent(in) :: nf_input type(string_t), dimension(2) :: corr_type class(model_data_t), intent(in) :: model end subroutine virtual_init_constants <>= module subroutine virtual_init_constants (virt, flv_born, nf_input, model) class(virtual_t), intent(inout) :: virt integer, intent(in), dimension(:,:) :: flv_born integer, intent(in) :: nf_input type(string_t), dimension(2) :: corr_type class(model_data_t), intent(in) :: model type(field_data_t), pointer :: field integer :: i_part, i_flv, pdg, i_corr real(default) :: nf, CA_factor, TR_sum real(default), dimension(:,:), allocatable :: CF_factor, TR_factor type(flavor_t) :: flv allocate (CF_factor (size (flv_born, 1), size (flv_born, 2)), & TR_factor (size (flv_born, 1), size (flv_born, 2))) corr_type (1) = "QCD"; corr_type (2) = "EW" do i_corr = 1, 2 TR_sum = 0 if (i_corr == 1) then CA_factor = CA; CF_factor = CF; TR_factor = TR nf = real(nf_input, default) TR_sum = nf * TR else CA_factor = zero do i_flv = 1, size (flv_born, 2) do i_part = 1, size (flv_born, 1) call flv%init (flv_born(i_part, i_flv), model) CF_factor(i_part, i_flv) = (flv%get_charge ())**2 TR_factor(i_part, i_flv) = (flv%get_charge ())**2 if (is_quark (flv_born (i_part, i_flv))) & TR_factor(i_part, i_flv) = NC * TR_factor(i_part, i_flv) end do end do do pdg = 1, nf_input field => model%get_field_ptr (pdg) TR_sum = TR_sum + NC*field%get_charge()**2 end do do pdg = 11, 15, 2 field => model%get_field_ptr (pdg) if (field%get_mass() > 0) exit TR_sum = TR_sum + field%get_charge()**2 end do end if do i_flv = 1, size (flv_born, 2) do i_part = 1, size (flv_born, 1) if (is_massless_vectorboson (flv_born(i_part, i_flv), corr_type (i_corr))) then virt%gamma_0(i_part, i_flv, i_corr) = 11._default / 6._default * CA_factor & - two / three * TR_sum virt%gamma_p(i_part, i_flv, i_corr) = (67._default / 9._default & - two * pi**2 / three) * CA_factor & - 23._default / 9._default * TR_sum virt%c_flv(i_part, i_flv, i_corr) = CA_factor else if (is_corresponding_fermion (flv_born(i_part, i_flv), corr_type (i_corr))) then virt%gamma_0(i_part, i_flv, i_corr) = 1.5_default * CF_factor(i_part, i_flv) virt%gamma_p(i_part, i_flv, i_corr) = (6.5_default - two * pi**2 / three) * CF_factor(i_part, i_flv) virt%c_flv(i_part, i_flv, i_corr) = CF_factor(i_part, i_flv) else if (is_massive_vectorboson (flv_born(i_part, i_flv), corr_type (i_corr))) then virt%gamma_0(i_part, i_flv, i_corr) = zero virt%gamma_p(i_part, i_flv, i_corr) = zero virt%c_flv(i_part, i_flv, i_corr) = CF_factor(i_part, i_flv) else virt%gamma_0(i_part, i_flv, i_corr) = zero virt%gamma_p(i_part, i_flv, i_corr) = zero virt%c_flv(i_part, i_flv, i_corr) = zero end if end do end do end do contains function is_massless_vectorboson (pdg_nr, nlo_corr_type) logical :: is_massless_vectorboson integer, intent(in) :: pdg_nr type(string_t), intent(in) :: nlo_corr_type is_massless_vectorboson = .false. if (nlo_corr_type == "QCD") then is_massless_vectorboson = is_gluon (pdg_nr) else if (nlo_corr_type == "EW") then is_massless_vectorboson = is_photon (pdg_nr) end if end function is_massless_vectorboson function is_corresponding_fermion (pdg_nr, nlo_corr_type) logical :: is_corresponding_fermion integer, intent(in) :: pdg_nr type(string_t), intent(in) :: nlo_corr_type is_corresponding_fermion = .false. if (nlo_corr_type == "QCD") then is_corresponding_fermion = is_quark (pdg_nr) else if (nlo_corr_type == "EW") then is_corresponding_fermion = is_fermion (pdg_nr) end if end function is_corresponding_fermion function is_massive_vectorboson (pdg_nr, nlo_corr_type) logical :: is_massive_vectorboson integer, intent(in) :: pdg_nr type(string_t), intent(in) :: nlo_corr_type is_massive_vectorboson = .false. if (nlo_corr_type == "EW") then is_massive_vectorboson = is_massive_vector (pdg_nr) end if end function is_massive_vectorboson end subroutine virtual_init_constants @ %def virtual_init_constants @ Set the renormalization scale. If the input is zero, use the center-of-mass energy. <>= procedure :: set_ren_scale => virtual_set_ren_scale <>= module subroutine virtual_set_ren_scale (virt, ren_scale) class(virtual_t), intent(inout) :: virt real(default), allocatable, intent(in) :: ren_scale end subroutine virtual_set_ren_scale <>= module subroutine virtual_set_ren_scale (virt, ren_scale) class(virtual_t), intent(inout) :: virt real(default), allocatable, intent(in) :: ren_scale if (allocated (ren_scale)) then if (allocated (virt%ren_scale)) then virt%ren_scale = ren_scale else allocate (virt%ren_scale, source=ren_scale) end if end if end subroutine virtual_set_ren_scale @ %def virtual_set_ren_scale @ <>= procedure :: set_fac_scale => virtual_set_fac_scale <>= module subroutine virtual_set_fac_scale (virt, p, fac_scale) class(virtual_t), intent(inout) :: virt type(vector4_t), dimension(:), intent(in) :: p real(default), intent(in), optional :: fac_scale end subroutine virtual_set_fac_scale <>= module subroutine virtual_set_fac_scale (virt, p, fac_scale) class(virtual_t), intent(inout) :: virt type(vector4_t), dimension(:), intent(in) :: p real(default), intent(in), optional :: fac_scale if (present (fac_scale)) then virt%fac_scale = fac_scale else virt%fac_scale = (p(1) + p(2))**1 end if end subroutine virtual_set_fac_scale @ %def virtual_set_fac_scale <>= procedure :: set_ellis_sexton_scale => virtual_set_ellis_sexton_scale <>= module subroutine virtual_set_ellis_sexton_scale (virt, Q) class(virtual_t), intent(inout) :: virt real(default), allocatable, intent(in) :: Q end subroutine virtual_set_ellis_sexton_scale <>= module subroutine virtual_set_ellis_sexton_scale (virt, Q) class(virtual_t), intent(inout) :: virt real(default), allocatable, intent(in) :: Q if (allocated (Q)) then if (allocated (virt%es_scale2)) then virt%es_scale2 = Q * Q else allocate (virt%es_scale2, source=Q*Q) end if end if end subroutine virtual_set_ellis_sexton_scale @ %def virtual_set_ellis_sexton_scale @ The virtual-subtracted matrix element is given by the equation \begin{equation} \label{eqn:virt_sub} \mathcal{V} = \frac{\alpha_s}{2\pi}\left(\mathcal{Q}\mathcal{B} + \sum \mathcal{I}_{ij}\mathcal{B}_{ij} + \mathcal{V}_{fin}\right), \end{equation} The expressions for $\mathcal{Q}$ can be found in equations \ref{eqn:virt_Q_isr} and \ref{eqn:virt_Q_fsr}. The expressions for $\mathcal{I}_{ij}$ can be found in equations (\ref{I_00}), (\ref{I_mm}), (\ref{I_0m}), depending on whether the particles involved in the radiation process are massive or massless. If two or more flavor structures would produce the same amplitude we only compute one and use the [[eqv_index]] to copy the result to the others (if [[reuse_amplitudes_fks]] is true). The Ellis-Sexton scale is set when explicitly allocated; if not it first is set to the renormalization scale; if that it is not set it will be set to the factorization scale which is the scale used for the virtual corrections. <>= procedure :: evaluate => virtual_evaluate <>= module subroutine virtual_evaluate (virt, reg_data, alpha_coupling, & p_born, separate_uborns, sqme_virt) class(virtual_t), intent(inout) :: virt type(region_data_t), intent(in) :: reg_data real(default), dimension(2), intent(in) :: alpha_coupling type(vector4_t), intent(in), dimension(:) :: p_born logical, intent(in) :: separate_uborns real(default), dimension(:), intent(inout) :: sqme_virt end subroutine virtual_evaluate <>= module subroutine virtual_evaluate (virt, reg_data, alpha_coupling, & p_born, separate_uborns, sqme_virt) class(virtual_t), intent(inout) :: virt type(region_data_t), intent(in) :: reg_data real(default), dimension(2), intent(in) :: alpha_coupling type(vector4_t), intent(in), dimension(:) :: p_born logical, intent(in) :: separate_uborns real(default), dimension(:), intent(inout) :: sqme_virt integer, dimension(:), allocatable :: eqv_flv_index real(default), dimension(:), allocatable :: sqme_virt_arr real(default) :: s, s_o_Q2, es_scale2 real(default), dimension(reg_data%n_flv_born) :: QB, BI integer :: i_flv, ii_flv, alr, i_corr logical, dimension(:), allocatable :: flv_evaluated integer, dimension(:), allocatable :: corr_index logical :: alr_qcd, alr_ew allocate (flv_evaluated(reg_data%n_flv_born)) allocate (sqme_virt_arr(reg_data%n_flv_born)) sqme_virt_arr = zero flv_evaluated = .false. if (virt%bad_point) return if (allocated (virt%es_scale2)) then es_scale2 = virt%es_scale2 else if (allocated (virt%ren_scale)) then es_scale2 = virt%ren_scale**2 else es_scale2 = virt%fac_scale**2 end if end if if (debug2_active (D_VIRTUAL)) then print *, 'Compute virtual component using alpha = ', alpha_coupling print *, 'Virtual selection: ', char (virt%selection) print *, 'virt%es_scale2 = ', es_scale2 !!! Debugging end if s = sum (p_born(1 : virt%n_in))**2 if (virt%settings%factorization_mode == FACTORIZATION_THRESHOLD) & call set_s_for_threshold () s_o_Q2 = s / es_scale2 * virt%settings%fks_template%xi_cut**2 eqv_flv_index = reg_data%eqv_flv_index_born do i_flv = 1, reg_data%n_flv_born alr_qcd = .false.; alr_ew = .false. do alr = 1, reg_data%n_regions if (i_flv == reg_data%regions(alr)%uborn_index) then if (reg_data%regions(alr)%nlo_correction_type == "QCD") then alr_qcd = .true. else if (reg_data%regions(alr)%nlo_correction_type == "EW") then alr_ew = .true. end if end if end do if (alr_qcd .and. alr_ew) then allocate (corr_index (2)) corr_index (1) = 1; corr_index (2) = 2 else allocate (corr_index (1)) corr_index (1) = 0 if (alr_qcd) then corr_index (1) = 1 else if (alr_ew) then corr_index (1) = 2 end if end if if (.not. flv_evaluated(eqv_flv_index(i_flv)) .and. corr_index(1) > 0) then if (virt%selection == var_str ("Full") .or. virt%selection == var_str ("OLP")) then !!! A factor of alpha_coupling/twopi is assumed to be included in vfin sqme_virt_arr(i_flv) = sqme_virt_arr(i_flv) + virt%sqme_virt_fin(i_flv) end if do i_corr = 1, size (corr_index) QB = zero; BI = zero if (virt%selection == var_str ("Full") .or. & virt%selection == var_str ("Subtraction")) then call virt%evaluate_initial_state (i_flv, corr_index (i_corr), reg_data, QB) call virt%compute_collinear_contribution & (i_flv, corr_index (i_corr), p_born, sqrt(s), reg_data, QB) select case (virt%settings%factorization_mode) case (FACTORIZATION_THRESHOLD) call virt%compute_eikonals_threshold (i_flv, p_born, s_o_Q2, QB, BI) case default call virt%compute_massive_self_eikonals & (i_flv, corr_index (i_corr), p_born, s_o_Q2, reg_data, QB) call virt%compute_eikonals & (i_flv, corr_index (i_corr), p_born, s_o_Q2, reg_data, BI) end select if (debug2_active (D_VIRTUAL)) then if (corr_index (i_corr) == 1) then print *, 'Correction type: QCD' else print *, 'Correction type: EW' end if print *, 'Evaluate i_flv: ', i_flv print *, 'sqme_born: ', virt%sqme_born (i_flv) print *, 'Q * sqme_born: ', alpha_coupling / twopi * QB(i_flv) print *, 'BI: ', alpha_coupling / twopi * BI(i_flv) print *, 'vfin: ', virt%sqme_virt_fin (i_flv) end if sqme_virt_arr(i_flv) = sqme_virt_arr(i_flv) & + alpha_coupling (corr_index (i_corr))/ twopi * (QB(i_flv) + BI(i_flv)) end if end do if (.not. (debug_active (D_VIRTUAL) .or. & debug2_active (D_VIRTUAL))) flv_evaluated(eqv_flv_index(i_flv)) = .true. else sqme_virt_arr(i_flv) = sqme_virt_arr(eqv_flv_index(i_flv)) end if if (separate_uborns) then sqme_virt(i_flv) = sqme_virt(i_flv) + sqme_virt_arr(i_flv) else sqme_virt(1) = sqme_virt(1) + sqme_virt_arr(i_flv) end if deallocate (corr_index) end do if (debug2_active (D_VIRTUAL)) then call msg_debug2 (D_VIRTUAL, "virtual-subtracted matrix element(s): ") print *, sqme_virt end if do i_flv = 1, reg_data%n_flv_born if (virt%n_is_neutrinos(i_flv) > 0) & sqme_virt = sqme_virt * virt%n_is_neutrinos(i_flv) * two end do contains subroutine set_s_for_threshold () use ttv_formfactors, only: m1s_to_mpole real(default) :: mtop2 mtop2 = m1s_to_mpole (sqrt(s))**2 if (s < four * mtop2) s = four * mtop2 end subroutine set_s_for_threshold end subroutine virtual_evaluate @ %def virtual_evaluate @ <>= procedure :: compute_eikonals => virtual_compute_eikonals <>= module subroutine virtual_compute_eikonals (virtual, i_flv, i_corr, & p_born, s_o_Q2, reg_data, BI) class(virtual_t), intent(inout) :: virtual integer, intent(in) :: i_flv, i_corr type(vector4_t), intent(in), dimension(:) :: p_born real(default), intent(in) :: s_o_Q2 type(region_data_t), intent(in) :: reg_data real(default), intent(inout), dimension(:) :: BI end subroutine virtual_compute_eikonals <>= module subroutine virtual_compute_eikonals (virtual, i_flv, i_corr, & p_born, s_o_Q2, reg_data, BI) class(virtual_t), intent(inout) :: virtual integer, intent(in) :: i_flv, i_corr type(vector4_t), intent(in), dimension(:) :: p_born real(default), intent(in) :: s_o_Q2 type(region_data_t), intent(in) :: reg_data real(default), intent(inout), dimension(:) :: BI integer :: i, j real(default) :: I_ij, BI_tmp BI_tmp = zero ! TODO vincent_r: Split the procedure into one computing QCD eikonals ! and one computing QED eikonals. ! TODO vincent_r: In the best case, remove the dependency on ! reg_data completely. associate (flst_born => reg_data%flv_born(i_flv)) do i = 1, virtual%n_legs do j = 1, virtual%n_legs if (i /= j) then if (i_corr == 1) then if (flst_born%colored(i) .and. flst_born%colored(j)) then I_ij = compute_eikonal_factor & (p_born, flst_born%massive, i, j, s_o_Q2) BI_tmp = BI_tmp + & virtual%sqme_color_c (i, j, i_flv) * I_ij if (debug2_active (D_VIRTUAL)) & print *, 'b_ij: ', i, j, & virtual%sqme_color_c (i, j, i_flv), 'I_ij: ', I_ij end if else if (i_corr == 2) then I_ij = compute_eikonal_factor (p_born, flst_born%massive, & i, j, s_o_Q2) BI_tmp = BI_tmp + virtual%sqme_charge_c (i, j, i_flv) * I_ij if (debug2_active (D_VIRTUAL)) & print *, 'b_ij: ', & virtual%sqme_charge_c (i, j, i_flv), 'I_ij: ', I_ij end if else if (debug2_active (D_VIRTUAL)) then if (i_corr == 1) then print *, 'b_ij: ', i, j, & virtual%sqme_color_c (i, j, i_flv), 'I_ij: ', I_ij else if (i_corr == 2) then print *, 'b_ij: ', i, j, & virtual%sqme_charge_c (i, j, i_flv), 'I_ij: ', I_ij end if end if end do end do if (virtual%settings%use_internal_color_correlations .or. i_corr == 2) & BI_tmp = BI_tmp * virtual%sqme_born (i_flv) end associate BI(i_flv) = BI(i_flv) + BI_tmp end subroutine virtual_compute_eikonals @ %def virtual_compute_eikonals @ <>= procedure :: compute_eikonals_threshold => virtual_compute_eikonals_threshold <>= module subroutine virtual_compute_eikonals_threshold (virtual, i_flv, & p_born, s_o_Q2, QB, BI) class(virtual_t), intent(in) :: virtual integer, intent(in) :: i_flv type(vector4_t), intent(in), dimension(:) :: p_born real(default), intent(in) :: s_o_Q2 real(default), intent(inout), dimension(:) :: QB real(default), intent(inout), dimension(:) :: BI end subroutine virtual_compute_eikonals_threshold <>= module subroutine virtual_compute_eikonals_threshold (virtual, i_flv, & p_born, s_o_Q2, QB, BI) class(virtual_t), intent(in) :: virtual integer, intent(in) :: i_flv type(vector4_t), intent(in), dimension(:) :: p_born real(default), intent(in) :: s_o_Q2 real(default), intent(inout), dimension(:) :: QB real(default), intent(inout), dimension(:) :: BI type(vector4_t), dimension(4) :: p_thr integer :: leg BI = zero; p_thr = get_threshold_momenta (p_born) call compute_massive_self_eikonals (virtual%sqme_born(i_flv), QB(i_flv)) do leg = 1, 2 BI(i_flv) = BI(i_flv) + evaluate_leg_pair (ASSOCIATED_LEG_PAIR(leg), i_flv) end do contains subroutine compute_massive_self_eikonals (sqme_born, QB) real(default), intent(in) :: sqme_born real(default), intent(inout) :: QB integer :: i if (debug_on) call msg_debug2 (D_VIRTUAL, "compute_massive_self_eikonals") if (debug_on) call msg_debug2 (D_VIRTUAL, "s_o_Q2", s_o_Q2) if (debug_on) call msg_debug2 (D_VIRTUAL, "log (s_o_Q2)", log (s_o_Q2)) do i = 1, 4 QB = QB - (cf * (log (s_o_Q2) - 0.5_default * I_m_eps (p_thr(i)))) & * sqme_born end do end subroutine compute_massive_self_eikonals function evaluate_leg_pair (i_start, i_flv) result (b_ij_times_I) real(default) :: b_ij_times_I integer, intent(in) :: i_start, i_flv real(default) :: I_ij integer :: i, j b_ij_times_I = zero do i = i_start, i_start + 1 do j = i_start, i_start + 1 if (i /= j) then I_ij = compute_eikonal_factor & (p_thr, [.true., .true., .true., .true.], i, j, s_o_Q2) b_ij_times_I = b_ij_times_I + & virtual%sqme_color_c (i, j, i_flv) * I_ij if (debug2_active (D_VIRTUAL)) & print *, 'b_ij: ', virtual%sqme_color_c (i, j, i_flv), 'I_ij: ', I_ij end if end do end do if (virtual%settings%use_internal_color_correlations) & b_ij_times_I = b_ij_times_I * virtual%sqme_born (i_flv) if (debug2_active (D_VIRTUAL)) then print *, 'internal color: ', virtual%settings%use_internal_color_correlations print *, 'b_ij_times_I = ', b_ij_times_I print *, 'QB = ', QB end if end function evaluate_leg_pair end subroutine virtual_compute_eikonals_threshold @ %def virtual_compute_eikonals_threshold @ <>= procedure :: set_bad_point => virtual_set_bad_point <>= module subroutine virtual_set_bad_point (virt, value) class(virtual_t), intent(inout) :: virt logical, intent(in) :: value end subroutine virtual_set_bad_point <>= module subroutine virtual_set_bad_point (virt, value) class(virtual_t), intent(inout) :: virt logical, intent(in) :: value virt%bad_point = value end subroutine virtual_set_bad_point @ %def virtual_set_bad_point @ The collinear limit of $\tilde{\mathcal{R}}$ can be integrated over the radiation degrees of freedom, giving the collinear contribution to the virtual component. Its general structure is $\mathcal{Q} \cdot \mathcal{B}$. The initial-state contribution to $\mathcal{Q}$ is simply given by \begin{equation} \label{eqn:virt_Q_isr} \mathcal{Q} = -\log\frac{\mu_F^2}{Q^2} \left(\gamma(\mathcal{I}_1) + 2 C (\mathcal{I}_1) \log(\xi_{\text{cut}}) + \gamma(\mathcal{I}_2) + 2 C (\mathcal{I}_2) \log(\xi_{\text{cut}}) \right), \end{equation} where $Q^2$ is the Ellis-Sexton scale and $\gamma$ is as in eqns. \ref{eqn:gamma(q)} and \ref{eqn:gamma(g)}.\\ [[virtual_evaluate_initial_state]] computes this quantity. The loop over the initial-state particles is only executed if we are dealing with a scattering process, because for decays there are no virtual initial-initial interactions. <>= procedure :: evaluate_initial_state => virtual_evaluate_initial_state <>= module subroutine virtual_evaluate_initial_state & (virt, i_flv, i_corr, reg_data, QB) class(virtual_t), intent(inout) :: virt type(region_data_t), intent(in) :: reg_data integer, intent(in) :: i_flv, i_corr real(default), intent(inout), dimension(:) :: QB end subroutine virtual_evaluate_initial_state <>= module subroutine virtual_evaluate_initial_state & (virt, i_flv, i_corr, reg_data, QB) class(virtual_t), intent(inout) :: virt type(region_data_t), intent(in) :: reg_data integer, intent(in) :: i_flv, i_corr real(default), intent(inout), dimension(:) :: QB real(default) :: sqme_born_virt, es_scale2 integer :: i if (allocated (virt%es_scale2)) then es_scale2 = virt%es_scale2 else if (allocated (virt%ren_scale)) then es_scale2 = virt%ren_scale**2 else es_scale2 = virt%fac_scale**2 end if end if sqme_born_virt = zero if (reg_data%nlo_correction_type == "EW" .and. i_corr == 1 & .and. qcd_ew_interferences (reg_data%flv_born(i_flv)%flst)) then do i = 1, size (reg_data%flv_born(i_flv)%flst) if (is_quark (reg_data%flv_born(i_flv)%flst (i))) then sqme_born_virt = -virt%sqme_color_c (i, i, i_flv)/CF exit end if end do else sqme_born_virt = virt%sqme_born (i_flv) end if if (virt%n_in == 2) then do i = 1, virt%n_in QB(i_flv) = QB(i_flv) - (virt%gamma_0 (i, i_flv, i_corr) & + two * virt%c_flv(i, i_flv, i_corr) & * log (virt%settings%fks_template%xi_cut)) & * log(virt%fac_scale**2 / es_scale2) * sqme_born_virt end do end if end subroutine virtual_evaluate_initial_state @ %def virtual_evaluate_initial_state @ Same as above, but for final-state particles. The collinear limit for final-state particles follows from the integral \begin{equation*} I_{+,\alpha_r} = \int d\Phi_{n+1} \frac{\xi_+^{-1-2\epsilon}}{\xi^{-1-2\epsilon}} \mathcal{R}_{\alpha_r}. \end{equation*} We can distinguish three situations: \begin{enumerate} \item $\alpha_r$ contains a massive emitter. In this case, no collinear subtraction term is required and the integral above is irrelevant. \item $\alpha_r$ contains a massless emitter, but resonances are not taken into account in the subtraction. Here, $\xi_{max} = \frac{2E_{em}}{\sqrt{s}}$ is the upper bound on $\xi$. \item $\alpha_r$ contains a massless emitter and resonance-aware subtraction is used. Here, $\xi_{max} = \frac{2E_{em}}{\sqrt{k_{res}^2}}$. \end{enumerate} Before version 2.4, only situations 1 and 2 were covered. The difference between situation 2 and 3 comes from the expansion of the plus-distribution in the integral above, \begin{equation*} \xi_+^{-1-2\epsilon} = \xi^{-1-2\epsilon} + \frac{1}{2\epsilon}\delta(\xi) = \xi_{max}^{-1-2\epsilon}\left[(1-z)^{-1-2\epsilon} + \frac{\xi_{max}^{2\epsilon}}{2\epsilon}\delta(1-z)\right]. \end{equation*} The expression from the standard FKS literature is given by $\mathcal{Q}$ is given by \begin{equation} \label{eqn:virt_Q_fsr_old} \begin{split} \mathcal{Q} = \sum_{k=n_{in}}^{n_L^{(B)}} \left[\gamma'(\mathcal{I}_k) - \log\frac{s\delta_o}{2Q^2}\left(\gamma(\mathcal{I}_k) - 2C(\mathcal{I}_k) \log\frac{2E_k}{\xi_{\text{cut}}\sqrt{s}}\right) \right.\\ + \left. 2C(\mathcal{I}_k) \left( \log^2\frac{2E_k}{\sqrt{s}} - \log^2 \xi_{\text{cut}} \right) - 2\gamma(\mathcal{I}_k)\log\frac{2E_k}{\sqrt{s}}\right]. \end{split} \end{equation} $n_L^{(B)}$ is the number of legs at Born level. Here, $\xi_{max}$ is implicitly present in the ratios in the logarithms. Using the resonance-aware $\xi_{max}$ yields \begin{equation} \label{eqn:virt_Q_fsr} \begin{split} \mathcal{Q} = \sum_{k=n_{in}}^{n_L^{(B)}} \left[\gamma'(\mathcal{I}_k) + 2\left(\log\frac{\sqrt{s}}{2E_{em}} + \log\xi_{max}\right) \left(\log\frac{\sqrt{s}}{2E_{em}} + \log\xi_{max} + \log\frac{Q^2}{s}\right) C(\mathcal{I}_k) \right.\\ + \left. 2 \log\xi_{max} \left(\log\xi_{max} - \log\frac{Q^2}{k_{res}^2}\right) C(\mathcal{I}_k) + \left(\log\frac{Q^2}{k_{res}^2} - 2 \log\xi_{max}\right) \gamma(\mathcal{I}_k)\right]. \end{split} \end{equation} Equation \ref{eqn:virt_Q_fsr} leads to \ref{eqn:virt_Q_fsr_old} with the substitutions $\xi_{max} \rightarrow \frac{2E_{em}}{\sqrt{s}}$ and $k_{res}^2 \rightarrow s$. [[virtual_compute_collinear_contribution]] only implements the second one. <>= procedure :: compute_collinear_contribution & => virtual_compute_collinear_contribution <>= module subroutine virtual_compute_collinear_contribution & (virt, i_flv, i_corr, p_born, sqrts, reg_data, QB) class(virtual_t), intent(inout) :: virt integer, intent(in) :: i_flv, i_corr type(vector4_t), dimension(:), intent(in) :: p_born real(default), intent(in) :: sqrts type(region_data_t), intent(in) :: reg_data real(default), intent(inout), dimension(:) :: QB end subroutine virtual_compute_collinear_contribution <>= module subroutine virtual_compute_collinear_contribution & (virt, i_flv, i_corr, p_born, sqrts, reg_data, QB) class(virtual_t), intent(inout) :: virt integer, intent(in) :: i_flv, i_corr type(vector4_t), dimension(:), intent(in) :: p_born real(default), intent(in) :: sqrts type(region_data_t), intent(in) :: reg_data real(default), intent(inout), dimension(:) :: QB real(default) :: s1, s2, s3, s4, s5 real(default) :: sqme_born_virt integer :: alr, em, i real(default) :: E_em, xi_max, log_xi_max, E_tot2, es_scale2 logical, dimension(virt%n_flv, virt%n_legs) :: evaluated integer :: i_contr type(vector4_t) :: k_res type(lorentz_transformation_t) :: L_to_resonance evaluated = .false. if (allocated (virt%es_scale2)) then es_scale2 = virt%es_scale2 else if (allocated (virt%ren_scale)) then es_scale2 = virt%ren_scale**2 else es_scale2 = virt%fac_scale**2 end if end if sqme_born_virt = zero if (reg_data%nlo_correction_type == "EW" .and. i_corr == 1 & .and. qcd_ew_interferences (reg_data%flv_born(i_flv)%flst)) then do i = 1, size (reg_data%flv_born(i_flv)%flst) if (is_quark (reg_data%flv_born(i_flv)%flst (i))) then sqme_born_virt = -virt%sqme_color_c (i, i, i_flv)/CF exit end if end do else sqme_born_virt = virt%sqme_born (i_flv) end if do alr = 1, reg_data%n_regions if (i_flv /= reg_data%regions(alr)%uborn_index) cycle em = reg_data%regions(alr)%emitter if (em <= virt%n_in) cycle if (evaluated(i_flv, em)) cycle !!! Collinear terms only for massless particles if (reg_data%regions(alr)%flst_uborn%massive(em)) cycle E_em = p_born(em)%p(0) if (allocated (reg_data%alr_contributors)) then i_contr = reg_data%alr_to_i_contributor (alr) k_res = get_resonance_momentum (p_born, reg_data%alr_contributors(i_contr)%c) E_tot2 = k_res%p(0)**2 L_to_resonance = inverse (boost (k_res, k_res**1)) xi_max = two * space_part_norm (L_to_resonance * p_born(em)) / k_res%p(0) else E_tot2 = sqrts**2 xi_max = two * E_em / sqrts end if log_xi_max = log (xi_max) associate (xi_cut => virt%settings%fks_template%xi_cut, delta_o => virt%settings%fks_template%delta_o) if (virt%settings%virtual_resonance_aware_collinear) then if (debug_active (D_VIRTUAL)) & call msg_debug (D_VIRTUAL, "Using resonance-aware collinear subtraction") s1 = virt%gamma_p(em, i_flv, i_corr) s2 = two * (log (sqrts / (two * E_em)) + log_xi_max) * & (log (sqrts / (two * E_em)) + log_xi_max + log (es_scale2 / sqrts**2)) & * virt%c_flv(em, i_flv, i_corr) s3 = two * log_xi_max * & (log_xi_max - log (es_scale2 / E_tot2)) * virt%c_flv(em, i_flv, i_corr) s4 = (log (es_scale2 / E_tot2) - two * log_xi_max) & * virt%gamma_0(em, i_flv, i_corr) QB(i_flv) = QB(i_flv) + (s1 + s2 + s3 + s4) * sqme_born_virt else if (debug_active (D_VIRTUAL)) & call msg_debug (D_VIRTUAL, "Using old-fashioned collinear subtraction") s1 = virt%gamma_p(em, i_flv, i_corr) s2 = log (delta_o * sqrts**2 / (two * es_scale2)) & * virt%gamma_0(em,i_flv, i_corr) s3 = log (delta_o * sqrts**2 / (two * es_scale2)) * two & * virt%c_flv(em,i_flv, i_corr) * log (two * E_em / (xi_cut * sqrts)) ! s4 = two * virt%c_flv(em,i_flv, i_corr) * (log (two * E_em / sqrts)**2 - log (xi_cut)**2) s4 = two * virt%c_flv(em,i_flv, i_corr) * & ! a**2 - b**2 = (a - b) * (a + b), for better numerical performance (log (two * E_em / sqrts) + log (xi_cut)) * (log (two * E_em / sqrts) - log (xi_cut)) s5 = two * virt%gamma_0(em,i_flv, i_corr) * log (two * E_em / sqrts) QB(i_flv) = QB(i_flv) + (s1 - s2 + s3 + s4 - s5) * sqme_born_virt end if end associate evaluated(i_flv, em) = .true. end do end subroutine virtual_compute_collinear_contribution @ %def virtual_compute_collinear_contribution @ For the massless-massive case and $i = j$ we get the massive self-eikonal of (A.10) in arXiv:0908.4272, given as \begin{equation} \mathcal{I}_{ii} = \log \frac{\xi^2_{\text{cut}}s}{Q^2} - \frac{1}{\beta} \log \frac{1 + \beta}{1 - \beta}. \end{equation} <>= procedure :: compute_massive_self_eikonals => & virtual_compute_massive_self_eikonals <>= module subroutine virtual_compute_massive_self_eikonals (virt, & i_flv, i_corr, p_born, s_over_Q2, reg_data, QB) class(virtual_t), intent(inout) :: virt integer, intent(in) :: i_flv, i_corr type(vector4_t), intent(in), dimension(:) :: p_born real(default), intent(in) :: s_over_Q2 type(region_data_t), intent(in) :: reg_data real(default), intent(inout), dimension(:) :: QB end subroutine virtual_compute_massive_self_eikonals <>= module subroutine virtual_compute_massive_self_eikonals (virt, & i_flv, i_corr, p_born, s_over_Q2, reg_data, QB) class(virtual_t), intent(inout) :: virt integer, intent(in) :: i_flv, i_corr type(vector4_t), intent(in), dimension(:) :: p_born real(default), intent(in) :: s_over_Q2 type(region_data_t), intent(in) :: reg_data real(default), intent(inout), dimension(:) :: QB real(default) :: sqme_born_virt integer :: i logical :: massive sqme_born_virt = zero if (reg_data%nlo_correction_type == "EW" .and. i_corr == 1 & .and. qcd_ew_interferences (reg_data%flv_born(i_flv)%flst)) then do i = 1, size (reg_data%flv_born(i_flv)%flst) if (is_quark (reg_data%flv_born(i_flv)%flst (i))) then sqme_born_virt = -virt%sqme_color_c (i, i, i_flv)/CF exit end if end do else sqme_born_virt = virt%sqme_born (i_flv) end if do i = 1, virt%n_legs massive = reg_data%flv_born(i_flv)%massive(i) if (massive) then QB(i_flv) = QB(i_flv) - (virt%c_flv (i, i_flv, i_corr) & * (log (s_over_Q2) - 0.5_default * I_m_eps (p_born(i)))) & * sqme_born_virt end if end do end subroutine virtual_compute_massive_self_eikonals @ %def virtual_compute_massive_self_eikonals @ The following code implements the $\mathcal{I}_{ij}$-function. The complete formulas can be found in arXiv:0908.4272 (A.1-A.17) and are also discussed in arXiv:1002.2581 in Appendix A. The implementation may differ in the detail from the formulas presented in the above paper. The parameter $\xi_{\text{cut}}$ is unphysically and cancels with appropriate factors in the real subtraction. We keep the additional parameter for debug usage. The implemented formulas are then defined as follows: \begin{itemize} \item[massless-massless case] $p^2 = 0, k^2 = 0,$ \begin{equation} \begin{split} \mathcal{I}_{ij} &= \frac{1}{2}\log^2\frac{\xi^2_{\text{cut}}s}{Q^2} + \log\frac{\xi^2_{\text{cut}}s}{Q^2}\log\frac{k_ik_j}{2E_iE_j} - \rm{Li}_2\left(\frac{k_ik_j}{2E_iE_j}\right) \\ &+ \frac{1}{2}\log^2\frac{k_ik_j}{2E_iE_j} - \log\left(1-\frac{k_ik_j}{2E_iE_j}\right) \log\frac{k_ik_j}{2E_iE_j}. \end{split} \label{I_00} \end{equation} \item[massive-massive case] $p^2 \neq 0, k^2 \neq 0,$ \begin{equation} \mathcal{I}_{ij} = \frac{1}{2}I_0(k_i, k_j)\log\frac{\xi^2_{\text{cut}}s}{Q^2} - \frac{1}{2}I_\epsilon(k_i,k_j) \label{I_mm} \end{equation} with \begin{equation} I_0(k_i, k_j) = \frac{1}{\beta}\log\frac{1+\beta}{1-\beta}, \qquad \beta = \sqrt{1-\frac{k_i^2k_j^2}{(k_i \cdot k_j)^2}} \end{equation} and a rather involved expression for $I_\epsilon$: \begin{align} \allowdisplaybreaks I_\epsilon(k_i, k_j) &= \left(K(z_j)-K(z_i)\right) \frac{1-\vec{\beta_i}\cdot\vec{\beta_j}}{\sqrt{a(1-b)}}, \\ \vec{\beta_i} &= \frac{\vec{k}_i}{k_i^0}, \\ a &= \beta_i^2 + \beta_j^2 - 2\vec{\beta}_i \cdot \vec{\beta}_j, \\ x_i &= \frac{\beta_i^2 -\vec{\beta}_i \cdot \vec{\beta}_j}{a}, \\ x_j &= \frac{\beta_j^2 -\vec{\beta}_i \cdot \vec{\beta}_j}{a} = 1-x_j, \\ b &= \frac{\beta_i^2\beta_j^2 - (\vec{\beta}_i\cdot\vec{\beta}_j)^2}{a}, \\ c &= \sqrt{\frac{b}{4a}}, \\ z_+ &= \frac{1+\sqrt{1-b}}{\sqrt{b}}, \\ z_- &= \frac{1-\sqrt{1-b}}{\sqrt{b}}, \\ z_i &= \frac{\sqrt{x_i^2 + 4c^2} - x_i}{2c}, \\ z_j &= \frac{\sqrt{x_j^2 + 4c^2} + x_j}{2c}, \\ K(z) = &-\frac{1}{2}\log^2\frac{(z-z_-)(z_+-z)}{(z_++z)(z_-+z)} - 2Li_2\left(\frac{2z_-(z_+-z)}{(z_+-z_-)(z_-+z)}\right) \\ &-2Li_2\left(-\frac{2z_+(z_-+z)}{(z_+-z_-)(z_+-z)}\right) \end{align} \item[massless-massive case] $p^2 = 0, k^2 \neq 0,$ \begin{equation} \mathcal{I}_{ij} = \frac{1}{2}\left[\frac{1}{2}\log^2\frac{\xi^2_{\text{cut}}s}{Q^2} - \frac{\pi^2}{6}\right] + \frac{1}{2}I_0(k_i,k_j)\log\frac{\xi^2_{\text{cut}}s}{Q^2} - \frac{1}{2}I_\epsilon(k_i,k_j) \label{I_0m} \end{equation} with \begin{align} I_0(p,k) &= \log\frac{(\hat{p}\cdot\hat{k})^2}{\hat{k}^2}, \\ I_\varepsilon(p,k) &= -2\left[\frac{1}{4}\log^2\frac{1-\beta}{1+\beta} + \log\frac{\hat{p}\cdot\hat{k}}{1+\beta}\log\frac{\hat{p}\cdot\hat{k}}{1-\beta} + \rm{Li}_2\left(1-\frac{\hat{p}\cdot\hat{k}}{1+\beta}\right) + \rm{Li}_2\left(1-\frac{\hat{p}\cdot\hat{k}}{1-\beta}\right)\right], \end{align} using \begin{align} \hat{p} = \frac{p}{p^0}, \quad \hat{k} = \frac{k}{k^0}, \quad \beta = \frac{|\vec{k}|}{k_0}, \\ \rm{Li}_2(1 - x) + \rm{Li}_2(1 - x^{-1}) = -\frac{1}{2} \log^2 x. \end{align} \end{itemize} <>= function compute_eikonal_factor (p_born, massive, i, j, s_o_Q2) result (I_ij) real(default) :: I_ij type(vector4_t), intent(in), dimension(:) :: p_born logical, dimension(:), intent(in) :: massive integer, intent(in) :: i, j real(default), intent(in) :: s_o_Q2 if (massive(i) .and. massive(j)) then I_ij = compute_Imm (p_born(i), p_born(j), s_o_Q2) else if (.not. massive(i) .and. massive(j)) then I_ij = compute_I0m (p_born(i), p_born(j), s_o_Q2) else if (massive(i) .and. .not. massive(j)) then I_ij = compute_I0m (p_born(j), p_born(i), s_o_Q2) else I_ij = compute_I00 (p_born(i), p_born(j), s_o_Q2) end if end function compute_eikonal_factor function compute_I00 (pi, pj, s_o_Q2) result (I) type(vector4_t), intent(in) :: pi, pj real(default), intent(in) :: s_o_Q2 real(default) :: I real(default) :: Ei, Ej real(default) :: pij, Eij real(default) :: s1, s2, s3, s4, s5 real(default) :: arglog real(default), parameter :: tiny_value = epsilon(1.0) s1 = 0; s2 = 0; s3 = 0; s4 = 0; s5 = 0 Ei = pi%p(0); Ej = pj%p(0) pij = pi * pj; Eij = Ei * Ej s1 = 0.5_default * log(s_o_Q2)**2 s2 = log(s_o_Q2) * log(pij / (two * Eij)) s3 = Li2 (pij / (two * Eij)) s4 = 0.5_default * log (pij / (two * Eij))**2 arglog = one - pij / (two * Eij) if (arglog > tiny_value) then s5 = log(arglog) * log(pij / (two * Eij)) else s5 = zero end if I = s1 + s2 - s3 + s4 - s5 end function compute_I00 function compute_I0m (ki, kj, s_o_Q2) result (I) type(vector4_t), intent(in) :: ki, kj real(default), intent(in) :: s_o_Q2 real(default) :: I real(default) :: logsomu real(default) :: s1, s2, s3 s1 = 0; s2 = 0; s3 = 0 logsomu = log(s_o_Q2) s1 = 0.5 * (0.5 * logsomu**2 - pi**2 / 6) s2 = 0.5 * I_0m_0 (ki, kj) * logsomu s3 = 0.5 * I_0m_eps (ki, kj) I = s1 + s2 - s3 end function compute_I0m function compute_Imm (pi, pj, s_o_Q2) result (I) type(vector4_t), intent(in) :: pi, pj real(default), intent(in) :: s_o_Q2 real(default) :: I real(default) :: s1, s2 s1 = 0.5 * log(s_o_Q2) * I_mm_0(pi, pj) s2 = 0.5 * I_mm_eps(pi, pj) I = s1 - s2 end function compute_Imm function I_m_eps (p) result (I) type(vector4_t), intent(in) :: p real(default) :: I real(default) :: beta beta = space_part_norm (p)/p%p(0) if (beta < tiny_07) then I = four * (one + beta**2/3 + beta**4/5 + beta**6/7) else I = two * log((one + beta) / (one - beta)) / beta end if end function I_m_eps function I_0m_eps (p, k) result (I) type(vector4_t), intent(in) :: p, k real(default) :: I type(vector4_t) :: pp, kp real(default) :: beta pp = p / p%p(0); kp = k / k%p(0) beta = sqrt (one - kp*kp) I = -2*(log((one - beta) / (one + beta))**2/4 + log((pp*kp) / (one + beta))*log((pp*kp) / (one - beta)) & + Li2(one - (pp*kp) / (one + beta)) + Li2(one - (pp*kp) / (one - beta))) end function I_0m_eps function I_0m_0 (p, k) result (I) type(vector4_t), intent(in) :: p, k real(default) :: I type(vector4_t) :: pp, kp pp = p / p%p(0); kp = k / k%p(0) I = log((pp*kp)**2 / kp**2) end function I_0m_0 function I_mm_eps (p1, p2) result (I) type(vector4_t), intent(in) :: p1, p2 real(default) :: I type(vector3_t) :: beta1, beta2 real(default) :: a, b, b2 real(default) :: zp, zm, z1, z2, x1, x2 real(default) :: zmb, z1b real(default) :: K1, K2 beta1 = space_part (p1) / energy(p1) beta2 = space_part (p2) / energy(p2) a = beta1**2 + beta2**2 - 2 * beta1 * beta2 b = beta1**2 * beta2**2 - (beta1 * beta2)**2 if (beta1**1 > beta2**1) call switch_beta (beta1, beta2) if (beta1 == vector3_null) then b2 = beta2**1 I = (-0.5 * log ((one - b2) / (one + b2))**2 - two * Li2 (-two * b2 / (one - b2))) & * one / sqrt (a - b) return end if x1 = beta1**2 - beta1 * beta2 x2 = beta2**2 - beta1 * beta2 zp = sqrt (a) + sqrt (a - b) zm = sqrt (a) - sqrt (a - b) zmb = one / zp z1 = sqrt (x1**2 + b) - x1 z2 = sqrt (x2**2 + b) + x2 z1b = one / (sqrt (x1**2 + b) + x1) K1 = - 0.5 * log (((z1b - zmb) * (zp - z1)) / ((zp + z1) * (z1b + zmb)))**2 & - two * Li2 ((two * zmb * (zp - z1)) / ((zp - zm) * (zmb + z1b))) & - two * Li2 ((-two * zp * (zm + z1)) / ((zp - zm) * (zp - z1))) K2 = - 0.5 * log ((( z2 - zm) * (zp - z2)) / ((zp + z2) * (z2 + zm)))**2 & - two * Li2 ((two * zm * (zp - z2)) / ((zp - zm) * (zm + z2))) & - two * Li2 ((-two * zp * (zm + z2)) / ((zp - zm) * (zp - z2))) I = (K2 - K1) * (one - beta1 * beta2) / sqrt (a - b) contains subroutine switch_beta (beta1, beta2) type(vector3_t), intent(inout) :: beta1, beta2 type(vector3_t) :: beta_tmp beta_tmp = beta1 beta1 = beta2 beta2 = beta_tmp end subroutine switch_beta end function I_mm_eps function I_mm_0 (k1, k2) result (I) type(vector4_t), intent(in) :: k1, k2 real(default) :: I - real(default) :: beta - beta = sqrt (one - k1**2 * k2**2 / (k1 * k2)**2) - I = log ((one + beta) / (one - beta)) / beta + real(default) :: beta, kquotient + kquotient = k1**2 * k2**2 / (k1 * k2)**2 + if (kquotient > tiny_13) then + beta = sqrt (one - kquotient) + I = log ((one + beta) / (one - beta)) / beta + else + beta = one - kquotient / two + I = log (two * (one + beta) / kquotient) / beta + end if end function I_mm_0 @ %def I_mm_0 @ <>= procedure :: final => virtual_final <>= module subroutine virtual_final (virtual) class(virtual_t), intent(inout) :: virtual end subroutine virtual_final <>= module subroutine virtual_final (virtual) class(virtual_t), intent(inout) :: virtual if (allocated (virtual%gamma_0)) deallocate (virtual%gamma_0) if (allocated (virtual%gamma_p)) deallocate (virtual%gamma_p) if (allocated (virtual%c_flv)) deallocate (virtual%c_flv) if (allocated (virtual%n_is_neutrinos)) deallocate (virtual%n_is_neutrinos) end subroutine virtual_final @ %def virtual_final @ \clearpage %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Real Subtraction} <<[[real_subtraction.f90]]>>= <> module real_subtraction <> <> use physics_defs use lorentz use flavors use phs_fks, only: real_kinematics_t, isr_kinematics_t use phs_fks, only: I_PLUS, I_MINUS use phs_fks, only: SQRTS_VAR, SQRTS_FIXED use phs_fks, only: phs_point_set_t use fks_regions use nlo_data <> <> <> <> <> interface <> end interface end module real_subtraction @ %def real_subtraction @ <<[[real_subtraction_sub.f90]]>>= <> submodule (real_subtraction) real_subtraction_s <> use io_units use format_defs, only: FMT_15 use string_utils use constants use numeric_utils use diagnostics use pdg_arrays use sm_physics use models use ttv_formfactors, only: m1s_to_mpole implicit none contains <> end submodule real_subtraction_s @ %def real_subtraction_s @ \subsubsection{Soft subtraction terms} <>= integer, parameter, public :: INTEGRATION = 0 integer, parameter, public :: FIXED_ORDER_EVENTS = 1 integer, parameter, public :: POWHEG = 2 @ %def real subtraction parameters @ Translates the NLO purpose into a string. However, this purpose is never set and this routine is nowhere used. <>= function nlo_purpose (purpose) result (of_purpose) type(string_t) :: of_purpose integer, intent(in) :: purpose select case (purpose) case (INTEGRATION) of_purpose = var_str ("Integration") case (FIXED_ORDER_EVENTS) of_purpose = var_str ("Fixed order NLO events") case (POWHEG) of_purpose = var_str ("Powheg events") case default of_purpose = var_str ("Undefined!") end select end function nlo_purpose @ %def nlo_purpose @ In the soft limit, the real matrix element behaves as \begin{equation*} \mathcal{R}_{\rm{soft}} = 4\pi\alpha_s \left[\sum_{i \neq j} \mathcal{B}_{ij} \frac{k_i \cdot k_j}{(k_i \cdot k)(k_j \cdot k)} - \mathcal{B} \sum_{i} \frac{k_i^2}{(k_i \cdot k)^2}C_i\right], \end{equation*} where $k$ denotes the momentum of the emitted parton. The quantity $\mathcal{B}_{ij}$ is called the color-correlated Born matrix element defined as \begin{equation*} \mathcal{B}_{ij} = \frac{1}{2s} \sum_{\stackrel{colors}{spins}} \mathcal{M}_{\{c_k\}}\left(\mathcal{M}^\dagger_{\{c_k\}}\right)_{\stackrel{c_i \rightarrow c_i'}{c_j \rightarrow c_j'}} T^a_{c_i,c_i'} T^a_{c_j,c_j'}. \end{equation*} <>= type :: soft_subtraction_t type(region_data_t), pointer :: reg_data => null () real(default), dimension(:,:), allocatable :: momentum_matrix logical :: use_resonance_mappings = .false. type(vector4_t) :: p_soft = vector4_null logical :: use_internal_color_correlations = .true. logical :: use_internal_spin_correlations = .false. logical :: xi2_expanded = .true. integer :: factorization_mode = NO_FACTORIZATION contains <> end type soft_subtraction_t @ %def soft_subtraction_t @ <>= procedure :: init => soft_subtraction_init <>= module subroutine soft_subtraction_init (sub_soft, reg_data) class(soft_subtraction_t), intent(inout) :: sub_soft type(region_data_t), intent(in), target :: reg_data end subroutine soft_subtraction_init <>= module subroutine soft_subtraction_init (sub_soft, reg_data) class(soft_subtraction_t), intent(inout) :: sub_soft type(region_data_t), intent(in), target :: reg_data sub_soft%reg_data => reg_data allocate (sub_soft%momentum_matrix (reg_data%n_legs_born, & reg_data%n_legs_born)) end subroutine soft_subtraction_init @ %def soft_subtraction_init @ <>= procedure :: requires_boost => soft_subtraction_requires_boost <>= module function soft_subtraction_requires_boost & (sub_soft, sqrts) result (requires_boost) logical :: requires_boost class(soft_subtraction_t), intent(in) :: sub_soft real(default), intent(in) :: sqrts end function soft_subtraction_requires_boost <>= module function soft_subtraction_requires_boost & (sub_soft, sqrts) result (requires_boost) logical :: requires_boost class(soft_subtraction_t), intent(in) :: sub_soft real(default), intent(in) :: sqrts real(default) :: mtop logical :: above_threshold if (sub_soft%factorization_mode == FACTORIZATION_THRESHOLD) then mtop = m1s_to_mpole (sqrts) above_threshold = sqrts**2 - four * mtop**2 > zero else above_threshold = .false. end if requires_boost = sub_soft%use_resonance_mappings .or. above_threshold end function soft_subtraction_requires_boost @ %def soft_subtraction_requires_boost @ The treatment of the momentum $k$ follows the discussion about the soft limit of the partition functions (see [1002.2581], p. 29 and C. Weiss' PhD Thesis, p. 24). The parton momentum is pulled out, $k = E \hat{k}$. In fact, we will substitute $\hat{k}$ for $k$ throughout the code, because the energy will factor out of the equation when the soft $\mathcal{S}$-function is multiplied. The momentum [[p_soft]] represents the soft limit of the radiated particle divided by its energy. It is a unit vector, because $k^2 = \left(k^0\right)^2 - \left(k^0\right)^2\hat{\vec{k}}^2 = 0$. The soft momentum is constructed by first creating a unit vector parallel to the emitter's Born momentum. This unit vector is then rotated about the corresponding angles $y$ and $\phi$ to match the direction of the real radiation in the soft limit. <>= procedure :: create_softvec_fsr => soft_subtraction_create_softvec_fsr <>= module subroutine soft_subtraction_create_softvec_fsr & (sub_soft, p_born, y, phi, emitter, xi_ref_momentum) class(soft_subtraction_t), intent(inout) :: sub_soft type(vector4_t), intent(in), dimension(:) :: p_born real(default), intent(in) :: y, phi integer, intent(in) :: emitter type(vector4_t), intent(in) :: xi_ref_momentum end subroutine soft_subtraction_create_softvec_fsr <>= module subroutine soft_subtraction_create_softvec_fsr & (sub_soft, p_born, y, phi, emitter, xi_ref_momentum) class(soft_subtraction_t), intent(inout) :: sub_soft type(vector4_t), intent(in), dimension(:) :: p_born real(default), intent(in) :: y, phi integer, intent(in) :: emitter type(vector4_t), intent(in) :: xi_ref_momentum type(vector3_t) :: dir type(vector4_t) :: p_em type(lorentz_transformation_t) :: rot type(lorentz_transformation_t) :: boost_to_rest_frame logical :: requires_boost associate (p_soft => sub_soft%p_soft) p_soft%p(0) = one requires_boost = sub_soft%requires_boost (two * p_born(1)%p(0)) if (requires_boost) then boost_to_rest_frame = inverse (boost (xi_ref_momentum, xi_ref_momentum**1)) p_em = boost_to_rest_frame * p_born(emitter) else p_em = p_born(emitter) end if p_soft%p(1:3) = p_em%p(1:3) / space_part_norm (p_em) dir = create_orthogonal (space_part (p_em)) rot = rotation (y, sqrt(one - y**2), dir) p_soft = rot * p_soft if (.not. vanishes (phi)) then dir = space_part (p_em) / space_part_norm (p_em) rot = rotation (cos(phi), sin(phi), dir) p_soft = rot * p_soft end if if (requires_boost) p_soft = inverse (boost_to_rest_frame) * p_soft end associate end subroutine soft_subtraction_create_softvec_fsr @ %def soft_subtraction_create_softvec_fsr @ For initial-state emissions, the soft vector is just a unit vector with the same direction as the radiated particle. As $y$ for ISR is defined independently of the emitter, also [[p_soft]] is the same for all initial state emitters. <>= procedure :: create_softvec_isr => soft_subtraction_create_softvec_isr <>= module subroutine soft_subtraction_create_softvec_isr (sub_soft, y, phi) class(soft_subtraction_t), intent(inout) :: sub_soft real(default), intent(in) :: y, phi end subroutine soft_subtraction_create_softvec_isr <>= module subroutine soft_subtraction_create_softvec_isr (sub_soft, y, phi) class(soft_subtraction_t), intent(inout) :: sub_soft real(default), intent(in) :: y, phi real(default) :: sin_theta sin_theta = sqrt(one - y**2) associate (p => sub_soft%p_soft%p) p(0) = one p(1) = sin_theta * sin(phi) p(2) = sin_theta * cos(phi) p(3) = y end associate end subroutine soft_subtraction_create_softvec_isr @ %def soft_subtraction_create_softvec_isr @ The soft vector for the real mismatch is basically the same as for usual FSR, except for the scaling with the total gluon energy. Moreover, the resulting vector is rotated into the frame where the 3-axis points along the direction of the emitter. This is necessary because in the collinear limit, the approximation \begin{equation*} k_i = \frac{k_i^0}{\bar{k}_j^0} \bar{k}_j = \frac{\xi\sqrt{s}}{2\bar{k}_j^0}\bar{k}_j \end{equation*} is used. The collinear limit is not included in the soft mismatch yet, but we keep the rotation for future usage here already (the performance loss is negligible). <>= procedure :: create_softvec_mismatch => & soft_subtraction_create_softvec_mismatch <>= module subroutine soft_subtraction_create_softvec_mismatch & (sub_soft, E, y, phi, p_em) class(soft_subtraction_t), intent(inout) :: sub_soft real(default), intent(in) :: E, phi, y type(vector4_t), intent(in) :: p_em end subroutine soft_subtraction_create_softvec_mismatch <>= module subroutine soft_subtraction_create_softvec_mismatch & (sub_soft, E, y, phi, p_em) class(soft_subtraction_t), intent(inout) :: sub_soft real(default), intent(in) :: E, phi, y type(vector4_t), intent(in) :: p_em real(default) :: sin_theta type(lorentz_transformation_t) :: rot_em_off_3_axis sin_theta = sqrt (one - y**2) associate (p => sub_soft%p_soft%p) p(0) = E p(1) = E * sin_theta * sin(phi) p(2) = E * sin_theta * cos(phi) p(3) = E * y end associate rot_em_off_3_axis = rotation_to_2nd (3, space_part (p_em)) sub_soft%p_soft = rot_em_off_3_axis * sub_soft%p_soft end subroutine soft_subtraction_create_softvec_mismatch @ %def soft_subtraction_create_softvec_mismatch @ Computation of the soft limit of $R_\alpha$. Note that what we are actually integrating (in the case of final-state radiation) is the quantity $f(0,y) / \xi$, where \begin{equation*} f(\xi,y) = \frac{J(\xi,y,\phi)}{\xi} \xi^2 R_\alpha. \end{equation*} $J/\xi$ is computed by the phase space generator. The additional factor of $\xi^{-1}$ is supplied in the [[evaluate_region_fsr]]-routine. Thus, we are left with a factor of $\xi^2$. A look on the expression for the soft limit of $R_\alpha$ below reveals that we are factoring out the gluon energy $E_i$ in the denominator. Therefore, we have a factor $\xi^2 / E_i^2 = 4 / q^2$. Note that the same routine is used also for the computation of the soft mismatch. There, the gluon energy is not factored out from the soft vector, so that we are left with the $\xi^2$-factor, which will eventually be cancelled out again. So, we just multiply with 1. Both cases are distinguished by the flag [[xi2_expanded]]. Note that for the soft subtraction term, also the S functions are computed in the soft limit. The input momenta are thus the real momenta in the soft limit, i.e. the Born momenta given by [[p_born]]. <>= procedure :: compute => soft_subtraction_compute <>= module function soft_subtraction_compute (sub_soft, p_born, & born_ij, y, q2, alpha_coupling, alr, emitter, i_res) result (sqme) real(default) :: sqme class(soft_subtraction_t), intent(inout) :: sub_soft type(vector4_t), intent(in), dimension(:) :: p_born real(default), intent(in), dimension(:,:) :: born_ij real(default), intent(in) :: y real(default), intent(in) :: q2, alpha_coupling integer, intent(in) :: alr, emitter, i_res end function soft_subtraction_compute <>= module function soft_subtraction_compute (sub_soft, p_born, & born_ij, y, q2, alpha_coupling, alr, emitter, i_res) result (sqme) real(default) :: sqme class(soft_subtraction_t), intent(inout) :: sub_soft type(vector4_t), intent(in), dimension(:) :: p_born real(default), intent(in), dimension(:,:) :: born_ij real(default), intent(in) :: y real(default), intent(in) :: q2, alpha_coupling integer, intent(in) :: alr, emitter, i_res real(default) :: s_alpha_soft real(default) :: kb real(default) :: xi2_factor if (.not. vector_set_is_cms (p_born, sub_soft%reg_data%n_in)) then call vector4_write_set (p_born, show_mass = .true., & check_conservation = .true.) call msg_fatal ("Soft subtraction: phase space point must be in CMS") end if if (debug2_active (D_SUBTRACTION)) then select case (char (sub_soft%reg_data%regions(alr)%nlo_correction_type)) case ("QCD") print *, 'Compute soft subtraction using alpha_s = ', alpha_coupling case ("EW") print *, 'Compute soft subtraction using alpha_qed = ', alpha_coupling end select end if s_alpha_soft = sub_soft%reg_data%get_svalue_soft (p_born, & sub_soft%p_soft, alr, emitter, i_res) if (s_alpha_soft > one + tiny_07) call msg_fatal ("s_alpha_soft > 1!") if (debug2_active (D_SUBTRACTION)) & call msg_print_color ('s_alpha_soft', s_alpha_soft, COL_YELLOW) select case (sub_soft%factorization_mode) case (NO_FACTORIZATION) kb = sub_soft%evaluate_factorization_default (p_born, born_ij) case (FACTORIZATION_THRESHOLD) kb = sub_soft%evaluate_factorization_threshold (thr_leg(emitter), p_born, born_ij) end select if (debug_on) call msg_debug2 (D_SUBTRACTION, 'KB', kb) sqme = four * pi * alpha_coupling * s_alpha_soft * kb if (sub_soft%xi2_expanded) then xi2_factor = four / q2 else xi2_factor = one end if if (emitter <= sub_soft%reg_data%n_in) then sqme = xi2_factor * (one - y**2) * sqme else sqme = xi2_factor * (one - y) * sqme end if if (sub_soft%reg_data%regions(alr)%double_fsr) sqme = sqme * two end function soft_subtraction_compute @ %def soft_subtraction_compute @ We loop over all external legs and do not take care to leave out non-colored ones because [[born_ij]] is constructed in such a way that it is only non-zero for colored entries. <>= procedure :: evaluate_factorization_default => & soft_subtraction_evaluate_factorization_default <>= module function soft_subtraction_evaluate_factorization_default & (sub_soft, p, born_ij) result (kb) real(default) :: kb class(soft_subtraction_t), intent(inout) :: sub_soft type(vector4_t), intent(in), dimension(:) :: p real(default), intent(in), dimension(:,:) :: born_ij end function soft_subtraction_evaluate_factorization_default <>= module function soft_subtraction_evaluate_factorization_default & (sub_soft, p, born_ij) result (kb) real(default) :: kb class(soft_subtraction_t), intent(inout) :: sub_soft type(vector4_t), intent(in), dimension(:) :: p real(default), intent(in), dimension(:,:) :: born_ij integer :: i, j kb = zero call sub_soft%compute_momentum_matrix (p) do i = 1, size (p) do j = 1, size (p) kb = kb + sub_soft%momentum_matrix (i, j) * born_ij (i, j) end do end do end function soft_subtraction_evaluate_factorization_default @ %def soft_subtraction_evaluate_factorization_default @ We have to multiply this with $\xi^2(1-y)$. Further, when applying the soft $\mathcal{S}$-function, the energy of the radiated particle is factored out. Thus we have $\xi^2/E_{em}^2(1-y) = 4/q_0^2(1-y)$. Computes the quantity $\mathcal{K}_{ij} = \frac{k_i \cdot k_j}{(k_i\cdot k)(k_j\cdot k)}$. <>= procedure :: compute_momentum_matrix => & soft_subtraction_compute_momentum_matrix <>= module subroutine soft_subtraction_compute_momentum_matrix & (sub_soft, p_born) class(soft_subtraction_t), intent(inout) :: sub_soft type(vector4_t), intent(in), dimension(:) :: p_born end subroutine soft_subtraction_compute_momentum_matrix <>= module subroutine soft_subtraction_compute_momentum_matrix & (sub_soft, p_born) class(soft_subtraction_t), intent(inout) :: sub_soft type(vector4_t), intent(in), dimension(:) :: p_born real(default) :: num, deno1, deno2 integer :: i, j do i = 1, sub_soft%reg_data%n_legs_born do j = 1, sub_soft%reg_data%n_legs_born if (i <= j) then num = p_born(i) * p_born(j) deno1 = p_born(i) * sub_soft%p_soft deno2 = p_born(j) * sub_soft%p_soft sub_soft%momentum_matrix(i, j) = num / (deno1 * deno2) else !!! momentum matrix is symmetric. sub_soft%momentum_matrix(i, j) = sub_soft%momentum_matrix(j, i) end if end do end do end subroutine soft_subtraction_compute_momentum_matrix @ %def soft_subtraction_compute_momentum_matrx @ <>= procedure :: evaluate_factorization_threshold => & soft_subtraction_evaluate_factorization_threshold <>= module function soft_subtraction_evaluate_factorization_threshold & (sub_soft, leg, p_born, born_ij) result (kb) real(default) :: kb class(soft_subtraction_t), intent(inout) :: sub_soft integer, intent(in) :: leg type(vector4_t), intent(in), dimension(:) :: p_born real(default), intent(in), dimension(:,:) :: born_ij end function soft_subtraction_evaluate_factorization_threshold <>= module function soft_subtraction_evaluate_factorization_threshold & (sub_soft, leg, p_born, born_ij) result (kb) real(default) :: kb class(soft_subtraction_t), intent(inout) :: sub_soft integer, intent(in) :: leg type(vector4_t), intent(in), dimension(:) :: p_born real(default), intent(in), dimension(:,:) :: born_ij type(vector4_t), dimension(4) :: p p = get_threshold_momenta (p_born) kb = evaluate_leg_pair (ASSOCIATED_LEG_PAIR (leg)) if (debug2_active (D_SUBTRACTION)) call show_debug () contains function evaluate_leg_pair (i_start) result (kbb) real(default) :: kbb integer, intent(in) :: i_start integer :: i1, i2 real(default) :: numerator, deno1, deno2 kbb = zero do i1 = i_start, i_start + 1 do i2 = i_start, i_start + 1 numerator = p(i1) * p(i2) deno1 = p(i1) * sub_soft%p_soft deno2 = p(i2) * sub_soft%p_soft kbb = kbb + numerator * born_ij (i1, i2) / deno1 / deno2 end do end do if (debug2_active (D_SUBTRACTION)) then do i1 = i_start, i_start + 1 do i2 = i_start, i_start + 1 call msg_print_color('i1', i1, COL_PEACH) call msg_print_color('i2', i2, COL_PEACH) call msg_print_color('born_ij (i1,i2)', born_ij (i1,i2), & COL_PINK) print *, 'Top momentum: ', p(1)%p end do end do end if end function evaluate_leg_pair subroutine show_debug () integer :: i call msg_print_color & ('soft_subtraction_evaluate_factorization_threshold', COL_GREEN) do i = 1, 4 print *, 'sqrt(p(i)**2) = ', sqrt(p(i)**2) end do end subroutine show_debug end function soft_subtraction_evaluate_factorization_threshold @ %def soft_subtraction_evaluate_factorization_threshold @ <>= procedure :: i_xi_ref => soft_subtraction_i_xi_ref <>= module function soft_subtraction_i_xi_ref & (sub_soft, alr, i_phs) result (i_xi_ref) integer :: i_xi_ref class(soft_subtraction_t), intent(in) :: sub_soft integer, intent(in) :: alr, i_phs end function soft_subtraction_i_xi_ref <>= module function soft_subtraction_i_xi_ref & (sub_soft, alr, i_phs) result (i_xi_ref) integer :: i_xi_ref class(soft_subtraction_t), intent(in) :: sub_soft integer, intent(in) :: alr, i_phs if (sub_soft%use_resonance_mappings) then i_xi_ref = sub_soft%reg_data%alr_to_i_contributor (alr) else if (sub_soft%factorization_mode == FACTORIZATION_THRESHOLD) then i_xi_ref = i_phs else i_xi_ref = 1 end if end function soft_subtraction_i_xi_ref @ %def soft_subtraction_i_xi_ref @ <>= procedure :: final => soft_subtraction_final <>= module subroutine soft_subtraction_final (sub_soft) class(soft_subtraction_t), intent(inout) :: sub_soft end subroutine soft_subtraction_final <>= module subroutine soft_subtraction_final (sub_soft) class(soft_subtraction_t), intent(inout) :: sub_soft if (associated (sub_soft%reg_data)) nullify (sub_soft%reg_data) if (allocated (sub_soft%momentum_matrix)) & deallocate (sub_soft%momentum_matrix) end subroutine soft_subtraction_final @ %def soft_subtraction_final @ \subsection{Soft mismatch} <>= public :: soft_mismatch_t <>= type :: soft_mismatch_t type(region_data_t), pointer :: reg_data => null () real(default), dimension(:), allocatable :: sqme_born real(default), dimension(:,:,:), allocatable :: sqme_born_color_c real(default), dimension(:,:,:), allocatable :: sqme_born_charge_c type(real_kinematics_t), pointer :: real_kinematics => null () type(soft_subtraction_t) :: sub_soft contains <> end type soft_mismatch_t @ %def soft_mismatch_t @ <>= procedure :: init => soft_mismatch_init <>= module subroutine soft_mismatch_init (soft_mismatch, reg_data, & real_kinematics, factorization_mode) class(soft_mismatch_t), intent(inout) :: soft_mismatch type(region_data_t), intent(in), target :: reg_data type(real_kinematics_t), intent(in), target :: real_kinematics integer, intent(in) :: factorization_mode end subroutine soft_mismatch_init <>= module subroutine soft_mismatch_init (soft_mismatch, reg_data, & real_kinematics, factorization_mode) class(soft_mismatch_t), intent(inout) :: soft_mismatch type(region_data_t), intent(in), target :: reg_data type(real_kinematics_t), intent(in), target :: real_kinematics integer, intent(in) :: factorization_mode soft_mismatch%reg_data => reg_data allocate (soft_mismatch%sqme_born (reg_data%n_flv_born)) allocate (soft_mismatch%sqme_born_color_c (reg_data%n_legs_born, & reg_data%n_legs_born, reg_data%n_flv_born)) allocate (soft_mismatch%sqme_born_charge_c (reg_data%n_legs_born, & reg_data%n_legs_born, reg_data%n_flv_born)) call soft_mismatch%sub_soft%init (reg_data) soft_mismatch%sub_soft%xi2_expanded = .false. soft_mismatch%real_kinematics => real_kinematics soft_mismatch%sub_soft%factorization_mode = factorization_mode end subroutine soft_mismatch_init @ %def soft_mismatch_init @ Main routine to compute the soft mismatch. Loops over all singular regions. There, it first creates the soft vector, then the necessary soft real matrix element. These inputs are then used to get the numerical value of the soft mismatch. <>= procedure :: evaluate => soft_mismatch_evaluate <>= module function soft_mismatch_evaluate & (soft_mismatch, alpha_s) result (sqme_mismatch) real(default) :: sqme_mismatch class(soft_mismatch_t), intent(inout) :: soft_mismatch real(default), intent(in) :: alpha_s end function soft_mismatch_evaluate <>= module function soft_mismatch_evaluate & (soft_mismatch, alpha_s) result (sqme_mismatch) real(default) :: sqme_mismatch class(soft_mismatch_t), intent(inout) :: soft_mismatch real(default), intent(in) :: alpha_s integer :: alr, i_born, emitter, i_res, i_phs, i_con real(default) :: xi, y, q2, s real(default) :: E_gluon type(vector4_t) :: p_em real(default) :: sqme_alr, sqme_soft type(vector4_t), dimension(:), allocatable :: p_born sqme_mismatch = zero associate (real_kinematics => soft_mismatch%real_kinematics) xi = real_kinematics%xi_mismatch y = real_kinematics%y_mismatch s = real_kinematics%cms_energy2 E_gluon = sqrt (s) * xi / two if (debug_active (D_MISMATCH)) then print *, 'Evaluating soft mismatch: ' print *, 'Phase space: ' call vector4_write_set (real_kinematics%p_born_cms%get_momenta(1), & show_mass = .true.) print *, 'xi: ', xi, 'y: ', y, 's: ', s, 'E_gluon: ', E_gluon end if allocate (p_born (soft_mismatch%reg_data%n_legs_born)) do alr = 1, soft_mismatch%reg_data%n_regions i_phs = real_kinematics%alr_to_i_phs (alr) if (soft_mismatch%reg_data%has_pseudo_isr ()) then i_con = 1 p_born = & soft_mismatch%real_kinematics%p_born_onshell%get_momenta(1) else i_con = soft_mismatch%reg_data%alr_to_i_contributor (alr) p_born = soft_mismatch%real_kinematics%p_born_cms%get_momenta(1) end if q2 = real_kinematics%xi_ref_momenta(i_con)**2 emitter = soft_mismatch%reg_data%regions(alr)%emitter p_em = p_born (emitter) i_res = soft_mismatch%reg_data%regions(alr)%i_res i_born = soft_mismatch%reg_data%regions(alr)%uborn_index call print_debug_alr () call soft_mismatch%sub_soft%create_softvec_mismatch & (E_gluon, y, real_kinematics%phi, p_em) if (debug_active (D_MISMATCH)) & print *, 'Created soft vector: ', & soft_mismatch%sub_soft%p_soft%p select type (fks_mapping => soft_mismatch%reg_data%fks_mapping) type is (fks_mapping_resonances_t) call fks_mapping%set_resonance_momentum & (real_kinematics%xi_ref_momenta(i_con)) end select sqme_soft = soft_mismatch%sub_soft%compute & (p_born, soft_mismatch%sqme_born_color_c(:,:,i_born), y, & q2, alpha_s, alr, emitter, i_res) sqme_alr = soft_mismatch%compute (alr, xi, y, p_em, & real_kinematics%xi_ref_momenta(i_con), & soft_mismatch%sub_soft%p_soft, & soft_mismatch%sqme_born(i_born), sqme_soft, & alpha_s, s) if (debug_on) call msg_debug (D_MISMATCH, 'sqme_alr: ', sqme_alr) sqme_mismatch = sqme_mismatch + sqme_alr end do end associate contains subroutine print_debug_alr () if (debug_active (D_MISMATCH)) then print *, 'alr: ', alr print *, 'i_phs: ', i_phs, 'i_con: ', i_con, 'i_res: ', i_res print *, 'emitter: ', emitter, 'i_born: ', i_born print *, 'emitter momentum: ', p_em%p print *, 'resonance momentum: ', & soft_mismatch%real_kinematics%xi_ref_momenta(i_con)%p print *, 'q2: ', q2 end if end subroutine print_debug_alr end function soft_mismatch_evaluate @ %def soft_mismatch_evaluate @ Computes the soft mismatch in a given $\alpha_r$, \begin{align*} I_{s+,\alpha_r} &= \int d\Phi_B \int_0^\infty d\xi \int_{-1}^1 dy \int_0^{2\pi} d\phi \frac{s\xi}{(4\pi)^3} \\ &\times \left\lbrace\tilde{R}_{\alpha_r} \left(e^{-\frac{2k_\gamma \cdot k_{res}}{k_{res}}^2} - e^{-\xi}\right) - \frac{32 \pi \alpha_s C_{em}}{s\xi^2} B_{f_b(\alpha_r)} (1-y)^{-1} \left[e^{-\frac{2\bar{k}_{em} \cdot k_{res}}{k_{res}^2} \frac{k_\gamma^0}{k_{em}^0}} - e^{-\xi}\right]\right\rbrace. \end{align*} <>= procedure :: compute => soft_mismatch_compute <>= module function soft_mismatch_compute & (soft_mismatch, alr, xi, y, p_em, p_res, p_soft, & sqme_born, sqme_soft, alpha_s, s) result (sqme_mismatch) real(default) :: sqme_mismatch class(soft_mismatch_t), intent(in) :: soft_mismatch integer, intent(in) :: alr real(default), intent(in) :: xi, y type(vector4_t), intent(in) :: p_em, p_res, p_soft real(default), intent(in) :: sqme_born, sqme_soft real(default), intent(in) :: alpha_s, s end function soft_mismatch_compute <>= module function soft_mismatch_compute & (soft_mismatch, alr, xi, y, p_em, p_res, p_soft, & sqme_born, sqme_soft, alpha_s, s) result (sqme_mismatch) real(default) :: sqme_mismatch class(soft_mismatch_t), intent(in) :: soft_mismatch integer, intent(in) :: alr real(default), intent(in) :: xi, y type(vector4_t), intent(in) :: p_em, p_res, p_soft real(default), intent(in) :: sqme_born, sqme_soft real(default), intent(in) :: alpha_s, s real(default) :: q2, expo, sm1, sm2, jacobian q2 = p_res**2 expo = - two * p_soft * p_res / q2 !!! Divide by 1 - y to factor out the corresponding !!! factor in the soft matrix element sm1 = sqme_soft / (one - y) * ( exp(expo) - exp(- xi) ) if (debug_on) call msg_debug2 & (D_MISMATCH, 'sqme_soft in mismatch ', sqme_soft) sm2 = zero if (soft_mismatch%reg_data%regions(alr)%has_collinear_divergence ()) then expo = - two * p_em * p_res / q2 * & p_soft%p(0) / p_em%p(0) sm2 = 32 * pi * alpha_s * cf / (s * xi**2) * sqme_born * & ( exp(expo) - exp(- xi) ) / (one - y) end if jacobian = soft_mismatch%real_kinematics%jac_mismatch * & s * xi / (8 * twopi3) sqme_mismatch = (sm1 - sm2) * jacobian end function soft_mismatch_compute @ %def soft_mismatch_compute @ <>= procedure :: final => soft_mismatch_final <>= module subroutine soft_mismatch_final (soft_mismatch) class(soft_mismatch_t), intent(inout) :: soft_mismatch end subroutine soft_mismatch_final <>= module subroutine soft_mismatch_final (soft_mismatch) class(soft_mismatch_t), intent(inout) :: soft_mismatch call soft_mismatch%sub_soft%final () if (associated (soft_mismatch%reg_data)) nullify (soft_mismatch%reg_data) if (allocated (soft_mismatch%sqme_born)) & deallocate (soft_mismatch%sqme_born) if (allocated (soft_mismatch%sqme_born_color_c)) & deallocate (soft_mismatch%sqme_born_color_c) if (allocated (soft_mismatch%sqme_born_charge_c)) & deallocate (soft_mismatch%sqme_born_charge_c) if (associated (soft_mismatch%real_kinematics)) & nullify (soft_mismatch%real_kinematics) end subroutine soft_mismatch_final @ %def soft_mismatch_final @ \subsection{Collinear and soft-collinear subtraction terms} This data type deals with the calculation of the collinear and soft-collinear contribution to the cross section. <>= public :: coll_subtraction_t <>= type :: coll_subtraction_t integer :: n_in, n_alr logical :: use_resonance_mappings = .false. real(default) :: CA = 0, CF = 0, TR = 0 contains <> end type coll_subtraction_t @ %def coll_subtraction_t @ <>= procedure :: init => coll_subtraction_init <>= module subroutine coll_subtraction_init (coll_sub, n_alr, n_in) class(coll_subtraction_t), intent(inout) :: coll_sub integer, intent(in) :: n_alr, n_in end subroutine coll_subtraction_init <>= module subroutine coll_subtraction_init (coll_sub, n_alr, n_in) class(coll_subtraction_t), intent(inout) :: coll_sub integer, intent(in) :: n_alr, n_in coll_sub%n_in = n_in coll_sub%n_alr = n_alr end subroutine coll_subtraction_init @ %def coll_subtraction_init @ Set the corresponding algebra parameters of the underlying gauge group of the correction. <>= procedure :: set_parameters => coll_subtraction_set_parameters <>= module subroutine coll_subtraction_set_parameters (coll_sub, CA, CF, TR) class(coll_subtraction_t), intent(inout) :: coll_sub real(default), intent(in) :: CA, CF, TR end subroutine coll_subtraction_set_parameters <>= module subroutine coll_subtraction_set_parameters (coll_sub, CA, CF, TR) class(coll_subtraction_t), intent(inout) :: coll_sub real(default), intent(in) :: CA, CF, TR coll_sub%CA = CA coll_sub%CF = CF coll_sub%TR = TR end subroutine coll_subtraction_set_parameters @ %def coll_subtraction_set_parameters @ This subroutine computes the collinear limit of $g^\alpha(\xi,y)$ introduced in eq.~\ref{fks: sub: real}. Care is given to also enable the usage for the soft-collinear limit. This, we write all formulas in terms of soft-finite quantities. We have to compute \begin{equation*} \frac{J(\Phi_n,\xi,y,\phi)}{\xi} \left[(1-y)\xi^2\mathcal{R}^\alpha(\Phi_{n+1})\right]|_{y = 1}. \end{equation*} The Jacobian $J$ is proportional to $\xi$, due to the $d^3 k_{n+1} / k_{n+1}^0$ factor in the integration measure. It cancels the factor of $\xi$ in the denominator. The remaining part of the Jacobian is multiplied in [[evaluate_region_fsr]] and is not relevant here. Inserting the splitting functions exemplarily for $q \to qg$ yields \begin{equation*} g^\alpha = \frac{8\pi\alpha_s}{k_{\mathrm{em}}^2} C_F (1-y) \xi^2 \frac{1+(1-z)^2}{z} \mathcal{B}, \end{equation*} where we have chosen $z = E_\mathrm{rad} / \bar{E}_\mathrm{em}$ and $\bar{E}_\mathrm{em}$ denotes the emitter energy in the Born frame. The collinear final state imposes $\bar{k}_n = k_{n} + k_{n + 1}$ for the connection between $\Phi_n$- and $\Phi_{n+1}$-phasepace and we get $1 - z = E_\mathrm{em} / \bar{E}_\mathrm{em}$. The denominator can be rewritten by the constraint $\bar{k}_n^2 = (k_n + k_{n+1})^2 = 0$ to \begin{equation*} k_{\mathrm{em}}^2 = 2 E_\mathrm{rad} E_\mathrm{em} (1-y) \end{equation*} which cancels the $(1-y)$ factor in the numerator, thus showing that the whole expression is indeed collinear-finite. We can further transform \begin{equation*} E_\mathrm{rad} E_\mathrm{em} = z (1-z) \bar{E}_\mathrm{em}^2 \end{equation*} so that in total we have \begin{equation*} g^\alpha = \frac{4\pi\alpha_s}{1-z} \frac{1}{\bar{k}_{\text{em}}^2} C_F \left(\frac{\xi}{z}\right)^2 (1 + (1-z)^2) \mathcal{B} \end{equation*} Follow up calculations give us \begin{align*} g^{\alpha, g \rightarrow gg} & = \frac{4\pi\alpha_s}{1-z}\frac{1}{\bar{k}_{\text{em}}^2} C_{\mathrm{A}} \frac{\xi}{z} \left\lbrace 2 \left( \frac{z}{1 - z} \xi + \frac{1 - z}{\frac{z}{\xi}} \right) \mathcal{B} + 4\xi z(1 - z) \hat{k}_{\perp}^{\mu} \hat{k}_{\perp}^{\nu} \mathcal{B}_{\mu\nu} \right\rbrace, \\ g^{\alpha, g \rightarrow qq} & = \frac{4\pi\alpha_s}{1-z} \frac{1}{\bar{k}_{\text{em}}^2} T_{\mathrm{R}} \frac{\xi}{z} \left\lbrace \xi \mathcal{B} - 4\xi z(1 - z) \hat{k}_{\perp}^{\mu} \hat{k}_{\perp}^{\nu} \mathcal{B}_{\mu\nu} \right\rbrace. \end{align*} The ratio $z / \xi$ is finite in the soft limit \begin{equation*} \frac{z}{\xi} = \frac{q^0}{2\bar{E}_\mathrm{em}} \end{equation*} so that $\xi$ does not appear explicitly in the computation. The argumentation above is valid for $q \to qg$--splittings, but the general factorization is valid for general splittings, also for those involving spin correlations and QED splittings. Note that care has to be given to the definition of $z$. Further, we have factored out a factor of $z$ to include in the ratio $z/\xi$, which has to be taken into account in the implementation of the splitting functions. <>= procedure :: compute_fsr => coll_subtraction_compute_fsr <>= module function coll_subtraction_compute_fsr (coll_sub, emitter, & flst, p_res, p_born, sqme_born, mom_times_sqme_spin_c, & xi, alpha_coupling, double_fsr) result (sqme) real(default) :: sqme class(coll_subtraction_t), intent(in) :: coll_sub integer, intent(in) :: emitter integer, dimension(:), intent(in) :: flst type(vector4_t), intent(in) :: p_res type(vector4_t), intent(in), dimension(:) :: p_born real(default), intent(in) :: sqme_born, mom_times_sqme_spin_c real(default), intent(in) :: xi, alpha_coupling logical, intent(in) :: double_fsr end function coll_subtraction_compute_fsr <>= module function coll_subtraction_compute_fsr (coll_sub, emitter, & flst, p_res, p_born, sqme_born, mom_times_sqme_spin_c, & xi, alpha_coupling, double_fsr) result (sqme) real(default) :: sqme class(coll_subtraction_t), intent(in) :: coll_sub integer, intent(in) :: emitter integer, dimension(:), intent(in) :: flst type(vector4_t), intent(in) :: p_res type(vector4_t), intent(in), dimension(:) :: p_born real(default), intent(in) :: sqme_born, mom_times_sqme_spin_c real(default), intent(in) :: xi, alpha_coupling logical, intent(in) :: double_fsr real(default) :: q0, z, p0, z_o_xi, onemz integer :: nlegs, flv_em, flv_rad nlegs = size (flst) flv_rad = flst(nlegs); flv_em = flst(emitter) q0 = p_res**1 p0 = p_res * p_born(emitter) / q0 !!! Here, z corresponds to 1-z in the formulas of arXiv:1002.2581; !!! the integrand is symmetric under this variable change z_o_xi = q0 / (two * p0) z = xi * z_o_xi; onemz = one - z if (is_gluon (flv_em) .and. is_gluon (flv_rad)) then sqme = coll_sub%CA * ( two * ( z / onemz * xi + onemz / z_o_xi ) * sqme_born & + four * xi * z * onemz * mom_times_sqme_spin_c ) else if (is_fermion (flv_em) .and. is_fermion (flv_rad)) then sqme = coll_sub%TR * xi * (sqme_born - four * z * onemz * mom_times_sqme_spin_c) else if (is_fermion (flv_em) .and. is_massless_vector (flv_rad)) then sqme = sqme_born * coll_sub%CF * (one + onemz**2) / z_o_xi else sqme = zero end if sqme = sqme / (p0**2 * onemz * z_o_xi) sqme = sqme * four * pi * alpha_coupling if (double_fsr) sqme = sqme * onemz * two end function coll_subtraction_compute_fsr @ %def coll_subtraction_compute_fsr @ Like in the context of [[coll_subtraction_compute_fsr]] we compute the quantity \begin{equation*} \lim_{y\to\pm1}{\left\{\frac{J(\Phi_n,\xi,y,\phi)}{\xi} \left[(1-y^2)\xi^2\mathcal{R}^\alpha(\Phi_{n+1})\right]\right\}}, \end{equation*} where the $(1-y^2)$ accounts for both $y=\pm1$. Again, the Jacobian is proportional to $\xi$, so we drop the $J / \xi$ factor. Note that it is important to take into account this missing factor of $\xi$ in the computation of the Jacobian during phase-space generation both for fixed-beam and structure ISR. We consider only a $q \to qg$ splitting arguing that other splittings are identical in terms of the factors which cancel. It is given by \begin{equation*} g^\alpha = \frac{8\pi\alpha_s}{-k_{\mathrm{em}}^2} C_F (1-y^2) \xi^2 \frac{1+z^2}{1-z} \mathcal{B}, \end{equation*} where $g^\alpha$ is defined akin to the one for FSR in eq.~\ref{fks: sub: real}. Note the negative sign of $k_\mathrm{em}^2$ to compensate the negative virtuality of the initial-state emitter. For ISR, $z$ is defined with respect to the emitter energy entering the hard interaction, i.e. \begin{equation*} z = \frac{E_\mathrm{beam} - E_\mathrm{rad}}{E_\mathrm{beam}} = 1 - \frac{E_\mathrm{rad}}{E_\mathrm{beam}}. \end{equation*} Because $E_\mathrm{rad} = E_\mathrm{beam} \cdot \xi$, it is $z = 1 - \xi$, thus one factor of $\xi$ is cancelled by $(1-z)$ in the denominator of $g^\alpha$. The factor $k_\mathrm{em}^2$ in the denominator is rewritten as \begin{equation*} k_\mathrm{em}^2 = \left(p_\mathrm{beam} - p_\mathrm{rad}\right)^2 = - 2 p_\mathrm{beam} \cdot p_\mathrm{rad} = - 2 E_\mathrm{beam} E_\mathrm{rad} (1\pm y) = - 2 E_\mathrm{beam}^2 (1-z) (1\pm y), \end{equation*} where we used \begin{equation*} E_\mathrm{beam} E_\mathrm{rad} = E_\mathrm{beam}^2 (1-z). \end{equation*} This leads to the cancellation of the corresponding $(1\pm y)$ factor in $(1-y^2)$, with the other factor becoming a simple factor of $2$, and the remaining factor of $\xi$ in the numerator. We thus end up with \begin{equation*} g^\alpha = \frac{8\pi\alpha_s}{E_\mathrm{beam}^2} C_F \left(1 + z^2\right)\mathcal{B}, \end{equation*} which is soft-finite. Note that here in [[compute_isr]], [[sqme_born]] is supposed to be the squared Born matrix element convoluted with the real PDF. <>= procedure :: compute_isr => coll_subtraction_compute_isr <>= module function coll_subtraction_compute_isr & (coll_sub, emitter, flst, p_born, sqme_born, mom_times_sqme_spin_c, & xi, alpha_coupling, isr_mode) result (sqme) real(default) :: sqme class(coll_subtraction_t), intent(in) :: coll_sub integer, intent(in) :: emitter integer, dimension(:), intent(in) :: flst type(vector4_t), intent(in), dimension(:) :: p_born real(default), intent(in) :: sqme_born real(default), intent(in) :: mom_times_sqme_spin_c real(default), intent(in) :: xi, alpha_coupling integer, intent(in) :: isr_mode end function coll_subtraction_compute_isr <>= module function coll_subtraction_compute_isr & (coll_sub, emitter, flst, p_born, sqme_born, mom_times_sqme_spin_c, & xi, alpha_coupling, isr_mode) result (sqme) real(default) :: sqme class(coll_subtraction_t), intent(in) :: coll_sub integer, intent(in) :: emitter integer, dimension(:), intent(in) :: flst type(vector4_t), intent(in), dimension(:) :: p_born real(default), intent(in) :: sqme_born real(default), intent(in) :: mom_times_sqme_spin_c real(default), intent(in) :: xi, alpha_coupling integer, intent(in) :: isr_mode real(default) :: z, onemz, p02 integer :: nlegs, flv_em, flv_rad !!! p_born must be in lab frame. nlegs = size (flst) flv_rad = flst(nlegs); flv_em = flst(emitter) !!! No need to pay attention to n_in = 1, because this case always has a !!! massive initial-state particle and thus no collinear divergence. p02 = p_born(1)%p(0) * p_born(2)%p(0) / two z = one - xi; onemz = xi if (is_massless_vector (flv_em) .and. is_massless_vector (flv_rad)) then sqme = coll_sub%CA * (two * (z + z * onemz**2) * sqme_born + four * onemz**2 & / z * mom_times_sqme_spin_c) else if (is_fermion (flv_em) .and. is_massless_vector (flv_rad)) then sqme = coll_sub%CF * (one + z**2) * sqme_born else if (is_fermion (flv_em) .and. is_fermion (flv_rad)) then sqme = coll_sub%CF * (z * onemz * sqme_born + four * onemz**2 / z * mom_times_sqme_spin_c) else if (is_massless_vector (flv_em) .and. is_fermion (flv_rad)) then sqme = coll_sub%TR * (z**2 + onemz**2) * onemz * sqme_born else sqme = zero end if if (isr_mode == SQRTS_VAR) then sqme = sqme / p02 * z else !!! We have no idea why this seems to work as there should be no factor !!! of z for the fixed-beam settings. This should definitely be understood in the !!! future! sqme = sqme / p02 / z end if sqme = sqme * four * pi * alpha_coupling end function coll_subtraction_compute_isr @ %def coll_subtraction_compute_isr @ <>= procedure :: final => coll_subtraction_final <>= module subroutine coll_subtraction_final (sub_coll) class(coll_subtraction_t), intent(inout) :: sub_coll end subroutine coll_subtraction_final <>= module subroutine coll_subtraction_final (sub_coll) class(coll_subtraction_t), intent(inout) :: sub_coll sub_coll%use_resonance_mappings = .false. end subroutine coll_subtraction_final @ %def coll_subtraction_final @ \subsection{Real Subtraction} We store a pointer to the [[nlo_settings_t]] object which holds tuning parameters, e.g. cutoffs for the subtraction terms. <>= public :: real_subtraction_t <>= type :: real_subtraction_t type(nlo_settings_t), pointer :: settings => null () type(region_data_t), pointer :: reg_data => null () type(real_kinematics_t), pointer :: real_kinematics => null () type(isr_kinematics_t), pointer :: isr_kinematics => null () real(default), dimension(:,:), allocatable :: sqme_real_non_sub real(default), dimension(:), allocatable :: sqme_born real(default), dimension(:,:), allocatable :: sf_factors real(default), dimension(:,:,:), allocatable :: sqme_born_color_c real(default), dimension(:,:,:), allocatable :: sqme_born_charge_c real(default), dimension(:,:,:,:), allocatable :: sqme_born_spin_c type(soft_subtraction_t) :: sub_soft type(coll_subtraction_t) :: sub_coll logical, dimension(:), allocatable :: sc_required logical :: subtraction_deactivated = .false. integer :: purpose = INTEGRATION logical :: radiation_event = .true. logical :: subtraction_event = .false. integer, dimension(:), allocatable :: selected_alr contains <> end type real_subtraction_t @ %def real_subtraction_t @ Initializer <>= procedure :: init => real_subtraction_init <>= module subroutine real_subtraction_init (rsub, reg_data, settings) class(real_subtraction_t), intent(inout), target :: rsub type(region_data_t), intent(in), target :: reg_data type(nlo_settings_t), intent(in), target :: settings end subroutine real_subtraction_init <>= module subroutine real_subtraction_init (rsub, reg_data, settings) class(real_subtraction_t), intent(inout), target :: rsub type(region_data_t), intent(in), target :: reg_data type(nlo_settings_t), intent(in), target :: settings integer :: alr if (debug_on) call msg_debug (D_SUBTRACTION, "real_subtraction_init") if (debug_on) call msg_debug (D_SUBTRACTION, "n_in", reg_data%n_in) if (debug_on) call msg_debug & (D_SUBTRACTION, "nlegs_born", reg_data%n_legs_born) if (debug_on) call msg_debug & (D_SUBTRACTION, "nlegs_real", reg_data%n_legs_real) if (debug_on) call msg_debug & (D_SUBTRACTION, "reg_data%n_regions", reg_data%n_regions) if (debug2_active (D_SUBTRACTION)) call reg_data%write () rsub%reg_data => reg_data allocate (rsub%sqme_born (reg_data%n_flv_born)) rsub%sqme_born = zero allocate (rsub%sf_factors (reg_data%n_regions, 0:reg_data%n_in)) rsub%sf_factors = zero allocate (rsub%sqme_born_color_c & (reg_data%n_legs_born, reg_data%n_legs_born, reg_data%n_flv_born)) rsub%sqme_born_color_c = zero allocate (rsub%sqme_born_charge_c & (reg_data%n_legs_born, reg_data%n_legs_born, reg_data%n_flv_born)) rsub%sqme_born_charge_c = zero allocate (rsub%sqme_real_non_sub (reg_data%n_flv_real, reg_data%n_phs)) rsub%sqme_real_non_sub = zero allocate (rsub%sc_required (reg_data%n_regions)) do alr = 1, reg_data%n_regions rsub%sc_required(alr) = reg_data%regions(alr)%sc_required end do if (rsub%requires_spin_correlations ()) then allocate (rsub%sqme_born_spin_c & (1:3, 1:3, reg_data%n_legs_born, reg_data%n_flv_born)) rsub%sqme_born_spin_c = zero end if call rsub%sub_soft%init (reg_data) call rsub%sub_coll%init (reg_data%n_regions, reg_data%n_in) rsub%settings => settings rsub%sub_soft%use_resonance_mappings = settings%use_resonance_mappings rsub%sub_coll%use_resonance_mappings = settings%use_resonance_mappings rsub%sub_soft%factorization_mode = settings%factorization_mode end subroutine real_subtraction_init @ %def real_subtraction_init @ <>= procedure :: set_real_kinematics => real_subtraction_set_real_kinematics <>= module subroutine real_subtraction_set_real_kinematics & (rsub, real_kinematics) class(real_subtraction_t), intent(inout) :: rsub type(real_kinematics_t), intent(in), target :: real_kinematics end subroutine real_subtraction_set_real_kinematics <>= module subroutine real_subtraction_set_real_kinematics (rsub, real_kinematics) class(real_subtraction_t), intent(inout) :: rsub type(real_kinematics_t), intent(in), target :: real_kinematics rsub%real_kinematics => real_kinematics end subroutine real_subtraction_set_real_kinematics @ %def real_subtraction_set_real_kinematics @ <>= procedure :: set_isr_kinematics => real_subtraction_set_isr_kinematics <>= module subroutine real_subtraction_set_isr_kinematics (rsub, fractions) class(real_subtraction_t), intent(inout) :: rsub type(isr_kinematics_t), intent(in), target :: fractions end subroutine real_subtraction_set_isr_kinematics <>= module subroutine real_subtraction_set_isr_kinematics (rsub, fractions) class(real_subtraction_t), intent(inout) :: rsub type(isr_kinematics_t), intent(in), target :: fractions rsub%isr_kinematics => fractions end subroutine real_subtraction_set_isr_kinematics @ %def real_subtraction_set_isr_kinematics @ <>= procedure :: get_i_res => real_subtraction_get_i_res <>= module function real_subtraction_get_i_res (rsub, alr) result (i_res) integer :: i_res class(real_subtraction_t), intent(inout) :: rsub integer, intent(in) :: alr end function real_subtraction_get_i_res <>= module function real_subtraction_get_i_res (rsub, alr) result (i_res) integer :: i_res class(real_subtraction_t), intent(inout) :: rsub integer, intent(in) :: alr select type (fks_mapping => rsub%reg_data%fks_mapping) type is (fks_mapping_resonances_t) i_res = fks_mapping%res_map%alr_to_i_res (alr) class default i_res = 0 end select end function real_subtraction_get_i_res @ %def real_subtraction_get_i_res @ \subsection{The real contribution to the cross section} In each singular region $\alpha$, the real contribution to $\sigma$ is given by the second summand of eqn. \ref{fks: sub: complete}, \begin{equation} \label{fks: sub: real} \sigma^\alpha_{\text{real}} = \int d\Phi_n \int_0^{2\pi} d\phi \int_{-1}^1 dy \int_0^{\xi_{\text{max}}} d\xi \left(\frac{1}{\xi}\right)_+ \left(\frac{1}{1-y}\right)_+ \underbrace{\frac{J(\Phi_n, \xi, y, \phi)}{\xi} \left[(1-y)\xi^2\mathcal{R}^\alpha(\Phi_{n+1})\right]}_{g^\alpha(\xi,y)}. \end{equation} Writing out the plus-distribution and introducing $\tilde{\xi} = \xi/\xi_{\text{max}}$ to set the upper integration limit to 1, this turns out to be equal to \begin{equation} \begin{split} \sigma^\alpha_{\rm{real}} &= \int d\Phi_n \int_0^{2\pi}d\phi \int_{-1}^1 \frac{dy}{1-y} \Bigg\{\int_0^1 d\tilde{\xi}\Bigg[\frac{g^\alpha(\tilde{\xi}\xi_{\rm{max}},y)}{\tilde{\xi}} - \underbrace{\frac{g^\alpha(0,y)}{\tilde{\xi}}}_{\text{soft}} - \underbrace{\frac{g^\alpha(\tilde{\xi}\xi_{\rm{max}},1)}{\tilde{\xi}}}_{\text{coll.}} + \underbrace{\frac{g^\alpha(0,1)}{\tilde{\xi}}}_{\text{coll.+soft}}\Bigg] \\ &+ \left[\log\xi_{\rm{max}}(y)g^\alpha(0,y) - \log\xi_{\rm{max}}(1)g^\alpha(0,1)\right]\Bigg\}. \end{split} \end{equation} This formula is implemented in \texttt{compute\_sqme\_real\_fin} If two or more singular regions would produce the same amplitude we only compute one and use the [[eqv_index]] to copy the result to the others (if [[reuse_amplitudes_fks]] is true). <>= procedure :: compute => real_subtraction_compute <>= module subroutine real_subtraction_compute (rsub, emitter, & i_phs, alpha_s, alpha_qed, separate_alrs, sqme) class(real_subtraction_t), intent(inout) :: rsub integer, intent(in) :: emitter, i_phs logical, intent(in) :: separate_alrs real(default), intent(inout), dimension(:) :: sqme real(default), intent(in) :: alpha_s, alpha_qed end subroutine real_subtraction_compute <>= module subroutine real_subtraction_compute (rsub, emitter, & i_phs, alpha_s, alpha_qed, separate_alrs, sqme) class(real_subtraction_t), intent(inout) :: rsub integer, intent(in) :: emitter, i_phs logical, intent(in) :: separate_alrs real(default), intent(inout), dimension(:) :: sqme real(default), dimension(:), allocatable :: sqme_alr_arr real(default), intent(in) :: alpha_s, alpha_qed real(default) :: sqme_alr, alpha_coupling integer :: alr, i_con, i_res, this_emitter logical :: same_emitter logical, dimension(:), allocatable :: alr_evaluated allocate (alr_evaluated(rsub%reg_data%n_regions)) allocate (sqme_alr_arr(rsub%reg_data%n_regions)) sqme_alr_arr = zero alr_evaluated = .false. do alr = 1, rsub%reg_data%n_regions if (.not. alr_evaluated(rsub%reg_data%regions(alr)%eqv_index)) then if (allocated (rsub%selected_alr)) then if (.not. any (rsub%selected_alr == alr)) cycle end if sqme_alr = zero if (emitter > rsub%isr_kinematics%n_in) then same_emitter = emitter == rsub%reg_data%regions(alr)%emitter else same_emitter = rsub%reg_data%regions(alr)%emitter <= rsub%isr_kinematics%n_in end if select case (char(rsub%reg_data%regions(alr)%nlo_correction_type)) case ("QCD") alpha_coupling = alpha_s case ("EW") alpha_coupling = alpha_qed end select if (same_emitter .and. i_phs == rsub%real_kinematics%alr_to_i_phs (alr)) then i_res = rsub%get_i_res (alr) this_emitter = rsub%reg_data%regions(alr)%emitter sqme_alr = rsub%evaluate_emitter_region (alr, this_emitter, i_phs, i_res, & alpha_coupling) if (rsub%purpose == INTEGRATION .or. rsub%purpose == FIXED_ORDER_EVENTS) then i_con = rsub%get_i_contributor (alr) sqme_alr = sqme_alr * rsub%get_phs_factor (i_con) end if end if sqme_alr_arr(alr) = sqme_alr_arr(alr) + sqme_alr if (.not. (debug_active (D_SUBTRACTION) .or. debug2_active (D_SUBTRACTION))) then if (.not. allocated (rsub%selected_alr)) & alr_evaluated(rsub%reg_data%regions(alr)%eqv_index) = .true. end if else sqme_alr_arr(alr) = sqme_alr_arr(rsub%reg_data%regions(alr)%eqv_index) end if if (separate_alrs) then sqme(alr) = sqme(alr) + sqme_alr_arr(alr) else sqme(1) = sqme(1) + sqme_alr_arr(alr) end if end do if (debug_on) then if (debug2_active (D_SUBTRACTION)) call check_s_alpha_consistency () end if contains subroutine check_s_alpha_consistency () real(default) :: sum_s_alpha, sum_s_alpha_soft integer :: i_ftuple if (debug_on) call msg_debug2 (D_SUBTRACTION, "Check consistency of s_alpha: ") do alr = 1, rsub%reg_data%n_regions sum_s_alpha = rsub%sum_up_s_alpha(alr, i_phs) call msg_debug2 (D_SUBTRACTION, 'sum_s_alpha', sum_s_alpha) if (.not. nearly_equal(sum_s_alpha, one)) then call msg_bug ("The sum of all S functions should be equal to one!") end if sum_s_alpha_soft = rsub%sum_up_s_alpha_soft(alr, i_phs) call msg_debug2 (D_SUBTRACTION, 'sum_s_alpha_soft', sum_s_alpha_soft) if (.not. nearly_equal(sum_s_alpha_soft, one)) then call msg_bug ("The sum of all soft S functions should be equal to one!") end if end do end subroutine check_s_alpha_consistency end subroutine real_subtraction_compute @ %def real_subtraction_compute @ The emitter is fixed. We now have to decide whether we evaluate in ISR or FSR region, and also if resonances are used. <>= procedure :: evaluate_emitter_region => & real_subtraction_evaluate_emitter_region <>= module function real_subtraction_evaluate_emitter_region (rsub, alr, & emitter, i_phs, i_res, alpha_coupling) result (sqme) real(default) :: sqme class(real_subtraction_t), intent(inout) :: rsub integer, intent(in) :: alr, emitter, i_phs, i_res real(default), intent(in) :: alpha_coupling end function real_subtraction_evaluate_emitter_region <>= module function real_subtraction_evaluate_emitter_region (rsub, alr, & emitter, i_phs, i_res, alpha_coupling) result (sqme) real(default) :: sqme class(real_subtraction_t), intent(inout) :: rsub integer, intent(in) :: alr, emitter, i_phs, i_res real(default), intent(in) :: alpha_coupling if (emitter <= rsub%isr_kinematics%n_in) then sqme = rsub%evaluate_region_isr & (alr, emitter, i_phs, i_res, alpha_coupling) else select type (fks_mapping => rsub%reg_data%fks_mapping) type is (fks_mapping_resonances_t) call fks_mapping%set_resonance_momenta & (rsub%real_kinematics%xi_ref_momenta) end select sqme = rsub%evaluate_region_fsr (alr, emitter, i_phs, i_res, alpha_coupling) end if end function real_subtraction_evaluate_emitter_region @ %def real_subtraction_evaluate_emitter_region @ Sums up $\sum_{i_1, i_2} S_{i_1 i_2}$ for the given [[alr]]. <>= procedure :: sum_up_s_alpha => real_subtraction_sum_up_s_alpha <>= module function real_subtraction_sum_up_s_alpha & (rsub, alr, i_phs) result (sum_s_alpha) real(default) :: sum_s_alpha class(real_subtraction_t), intent(inout) :: rsub integer, intent(in) :: alr, i_phs end function real_subtraction_sum_up_s_alpha <>= module function real_subtraction_sum_up_s_alpha & (rsub, alr, i_phs) result (sum_s_alpha) real(default) :: sum_s_alpha class(real_subtraction_t), intent(inout) :: rsub integer, intent(in) :: alr, i_phs type(vector4_t), dimension(:), allocatable :: p_real integer :: i_res, i_ftuple, i1, i2 allocate (p_real (rsub%reg_data%n_legs_real)) if (rsub%reg_data%has_pseudo_isr ()) then p_real = rsub%real_kinematics%p_real_onshell(i_phs)%get_momenta (i_phs) else p_real = rsub%real_kinematics%p_real_cms%get_momenta (i_phs) end if i_res = rsub%get_i_res (alr) sum_s_alpha = zero do i_ftuple = 1, rsub%reg_data%regions(alr)%nregions call rsub%reg_data%regions(alr)%ftuples(i_ftuple)%get (i1, i2) sum_s_alpha = sum_s_alpha + rsub%reg_data%get_svalue (p_real, alr, i1, i2, i_res) end do end function real_subtraction_sum_up_s_alpha @ %def real_subtraction_sum_up_s_alpha @ Sums up $\sum_{i_1, i_2} S_{i_1 i_2}$ for the given [[alr]]. The soft S functions take the real momenta in the soft limit, i.e. the Born momenta. For each summand of [[sum_s_alpha_soft]] we take [[p_soft]] constructed from the emitter of the given alpha region also for ftuples in which the first integer [[i1]] does not coincide with the emitter. This is necessary because only if we keep [[p_soft]] fixed, all soft S functions are computed with the same denominator and thus add up to 1. <>= procedure :: sum_up_s_alpha_soft => real_subtraction_sum_up_s_alpha_soft <>= module function real_subtraction_sum_up_s_alpha_soft & (rsub, alr, i_phs) result (sum_s_alpha_soft) real(default) :: sum_s_alpha_soft class(real_subtraction_t), intent(inout) :: rsub integer, intent(in) :: alr, i_phs end function real_subtraction_sum_up_s_alpha_soft <>= module function real_subtraction_sum_up_s_alpha_soft & (rsub, alr, i_phs) result (sum_s_alpha_soft) real(default) :: sum_s_alpha_soft class(real_subtraction_t), intent(inout) :: rsub integer, intent(in) :: alr, i_phs type(vector4_t), dimension(:), allocatable :: p_born integer :: i_res, i_ftuple, i1, i2, emitter, nlegs allocate (p_born (rsub%reg_data%n_legs_born)) if (rsub%reg_data%has_pseudo_isr ()) then p_born = rsub%real_kinematics%p_born_onshell%get_momenta (1) else p_born = rsub%real_kinematics%p_born_cms%get_momenta (1) end if i_res = rsub%get_i_res (alr) emitter = rsub%reg_data%regions(alr)%emitter associate (r => rsub%real_kinematics) if (emitter > rsub%sub_soft%reg_data%n_in) then call rsub%sub_soft%create_softvec_fsr (p_born, r%y_soft(i_phs), r%phi, & emitter, r%xi_ref_momenta(rsub%sub_soft%i_xi_ref (alr, i_phs))) else call rsub%sub_soft%create_softvec_isr (r%y_soft(i_phs), r%phi) end if end associate nlegs = rsub%reg_data%n_legs_real sum_s_alpha_soft = zero do i_ftuple = 1, rsub%reg_data%regions(alr)%nregions call rsub%reg_data%regions(alr)%ftuples(i_ftuple)%get (i1, i2) if (i2 == nlegs) then sum_s_alpha_soft = sum_s_alpha_soft + rsub%reg_data%get_svalue_soft & (p_born, rsub%sub_soft%p_soft, alr, i1, i_res) end if end do end function real_subtraction_sum_up_s_alpha_soft @ %def real_subtraction_sum_up_s_alpha_soft @ This subroutine computes the finite part of the real matrix element in an individual singular region. First, the radiation variables are fetched and $\mathcal{R}$ is multiplied by the appropriate $S_\alpha$-factors, region multiplicities and double-FSR factors. Then, it computes the soft, collinear, soft-collinear and remnant matrix elements and supplies the corresponding factor $1/\xi/(1-y)$ as well as the corresponding Jacobians. <>= procedure :: evaluate_region_fsr => real_subtraction_evaluate_region_fsr <>= module function real_subtraction_evaluate_region_fsr (rsub, alr, & emitter, i_phs, i_res, alpha_coupling) result (sqme_tot) real(default) :: sqme_tot class(real_subtraction_t), intent(inout) :: rsub integer, intent(in) :: alr, emitter, i_phs, i_res real(default), intent(in) :: alpha_coupling end function real_subtraction_evaluate_region_fsr <>= module function real_subtraction_evaluate_region_fsr (rsub, alr, & emitter, i_phs, i_res, alpha_coupling) result (sqme_tot) real(default) :: sqme_tot class(real_subtraction_t), intent(inout) :: rsub integer, intent(in) :: alr, emitter, i_phs, i_res real(default), intent(in) :: alpha_coupling real(default) :: sqme_rad, sqme_soft, sqme_coll, sqme_cs, sqme_remn sqme_rad = zero; sqme_soft = zero; sqme_coll = zero sqme_cs = zero; sqme_remn = zero associate (region => rsub%reg_data%regions(alr), & template => rsub%settings%fks_template) if (rsub%radiation_event) then sqme_rad = rsub%sqme_real_non_sub & (rsub%reg_data%get_matrix_element_index (alr), i_phs) call evaluate_fks_factors (sqme_rad, rsub%reg_data, & rsub%real_kinematics, alr, i_phs, emitter, i_res) call apply_kinematic_factors_radiation (sqme_rad, rsub%purpose, & rsub%real_kinematics, i_phs) end if if (rsub%subtraction_event .and. .not. (rsub%subtraction_deactivated & .or. region%nlo_correction_type == "none")) then if (debug2_active (D_SUBTRACTION)) then print *, "[real_subtraction_evaluate_region_fsr]" print *, "xi: ", rsub%real_kinematics%xi_max(i_phs) * & rsub%real_kinematics%xi_tilde print *, "y: ", rsub%real_kinematics%y(i_phs) end if call rsub%evaluate_subtraction_terms_fsr (alr, emitter, i_phs, & i_res, alpha_coupling, sqme_soft, sqme_coll, sqme_cs) call apply_kinematic_factors_subtraction_fsr (sqme_soft, & sqme_coll, sqme_cs, rsub%real_kinematics, i_phs) associate (symm_factor_fs => & rsub%reg_data%born_to_real_symm_factor_fs (alr)) sqme_soft = sqme_soft * symm_factor_fs sqme_coll = sqme_coll * symm_factor_fs sqme_cs = sqme_cs * symm_factor_fs end associate sqme_remn = compute_sqme_remnant_fsr (sqme_soft, sqme_cs, & rsub%real_kinematics%xi_max(i_phs), template%xi_cut, & rsub%real_kinematics%xi_tilde) sqme_tot = - sqme_soft - sqme_coll + sqme_cs + sqme_remn else sqme_tot = sqme_rad end if sqme_tot = sqme_tot * rsub%real_kinematics%jac_rand(i_phs) sqme_tot = sqme_tot * rsub%reg_data%regions(alr)%mult end associate if (debug_active (D_SUBTRACTION) .and. .not. & debug2_active (D_SUBTRACTION)) then call real_subtraction_register_debug_sqme (rsub, alr, emitter, & i_phs, sqme_rad, sqme_soft, sqme_coll=sqme_coll, sqme_cs=sqme_cs) else if (debug2_active (D_SUBTRACTION)) then call write_computation_status_fsr () end if contains <> subroutine write_computation_status_fsr (passed, total, region_type, full) integer, intent(in), optional :: passed, total character(*), intent(in), optional :: region_type integer :: i_born integer :: u real(default) :: xi logical :: yorn logical, intent(in), optional :: full yorn = .true. if (present (full)) yorn = full if (debug_on) call msg_debug & (D_SUBTRACTION, "real_subtraction_evaluate_region_fsr") u = given_output_unit (); if (u < 0) return i_born = rsub%reg_data%regions(alr)%uborn_index xi = rsub%real_kinematics%xi_max (i_phs) * rsub%real_kinematics%xi_tilde write (u,'(A,I2)') 'rsub%purpose: ', rsub%purpose write (u,'(A,I4)') 'alr: ', alr write (u,'(A,I3)') 'emitter: ', emitter write (u,'(A,I3)') 'i_phs: ', i_phs write (u,'(A,F6.4)') 'xi_max: ', rsub%real_kinematics%xi_max (i_phs) write (u,'(A,F6.4)') 'xi_cut: ', rsub%real_kinematics%xi_max(i_phs) * & rsub%settings%fks_template%xi_cut write (u,'(A,F6.4,2X,A,F6.4)') 'xi: ', xi, 'y: ', & rsub%real_kinematics%y (i_phs) if (yorn) then write (u,'(A,ES16.9)') 'sqme_born: ', rsub%sqme_born(i_born) write (u,'(A,ES16.9)') 'sqme_real: ', sqme_rad write (u,'(A,ES16.9)') 'sqme_soft: ', sqme_soft write (u,'(A,ES16.9)') 'sqme_coll: ', sqme_coll write (u,'(A,ES16.9)') 'sqme_coll-soft: ', sqme_cs write (u,'(A,ES16.9)') 'sqme_remn: ', sqme_remn write (u,'(A,ES16.9)') 'sqme_tot: ', sqme_tot if (present (passed) .and. present (total) .and. & present (region_type)) & write (u,'(A)') char (str (passed) // " of " // str (total) // & " " // region_type // " points passed in total") end if write (u,'(A,ES16.9)') 'jacobian - real: ', & rsub%real_kinematics%jac(i_phs)%jac(1) write (u,'(A,ES16.9)') 'jacobian - soft: ', & rsub%real_kinematics%jac(i_phs)%jac(2) write (u,'(A,ES16.9)') 'jacobian - coll: ', & rsub%real_kinematics%jac(i_phs)%jac(3) end subroutine write_computation_status_fsr end function real_subtraction_evaluate_region_fsr @ %def real_subtraction_evalute_region_fsr @ Compares the real matrix element to the subtraction terms in the soft, the collinear or the soft-collinear limits. Used for debug purposes if [[?test_anti_coll_limit]], [[?test_coll_limit]] and/or [[?test_soft_limit]] are set in the Sindarin. [[sqme_soft]] and [[sqme_cs]] need to be provided if called for FSR and [[sqme_coll_plus]], [[sqme_coll_minus]], [[sqme_cs_plus]] as well as [[sqme_cs_minus]] need to be provided if called for ISR. <>= subroutine real_subtraction_register_debug_sqme (rsub, alr, emitter, i_phs, sqme_rad, sqme_soft,& sqme_coll, sqme_cs, sqme_coll_plus, sqme_coll_minus, sqme_cs_plus, sqme_cs_minus) class(real_subtraction_t), intent(in) :: rsub integer, intent(in) :: alr, emitter, i_phs real(default), intent(in) :: sqme_rad, sqme_soft real(default), intent(in), optional :: sqme_coll, sqme_cs, sqme_coll_plus, sqme_coll_minus, sqme_cs_plus, sqme_cs_minus real(default), dimension(:), allocatable, save :: sqme_rad_store logical :: is_soft, is_collinear_plus, is_collinear_minus, is_fsr real(default), parameter :: soft_threshold = 0.001_default real(default), parameter :: coll_threshold = 0.99_default real(default), parameter :: rel_smallness = 0.01_default real(default) :: sqme_dummy, this_sqme_rad, y, xi_tilde logical, dimension(:), allocatable, save :: count_alr if (.not. allocated (sqme_rad_store)) then allocate (sqme_rad_store (rsub%reg_data%n_regions)) sqme_rad_store = zero end if if (rsub%radiation_event) then sqme_rad_store(alr) = sqme_rad else if (.not. allocated (count_alr)) then allocate (count_alr (rsub%reg_data%n_regions)) count_alr = .false. end if if (is_massless_vector (rsub%reg_data%regions(alr)%flst_real%flst(rsub%reg_data%n_legs_real))) then xi_tilde = rsub%real_kinematics%xi_tilde is_soft = xi_tilde < soft_threshold else is_soft = .false. end if y = rsub%real_kinematics%y(i_phs) is_collinear_plus = y > coll_threshold .and. & rsub%reg_data%regions(alr)%has_collinear_divergence() is_collinear_minus = -y > coll_threshold .and. & rsub%reg_data%regions(alr)%has_collinear_divergence() is_fsr = emitter > rsub%isr_kinematics%n_in if (is_fsr) then if (.not. present(sqme_coll) .or. .not. present(sqme_cs)) & call msg_error ("real_subtraction_register_debug_sqme: Wrong arguments for FSR") else if (.not. present(sqme_coll_plus) .or. .not. present(sqme_coll_minus) & .or. .not. present(sqme_cs_plus) .or. .not. present(sqme_cs_minus)) & call msg_error ("real_subtraction_register_debug_sqme: Wrong arguments for ISR") end if this_sqme_rad = sqme_rad_store(alr) if (is_soft .and. .not. is_collinear_plus .and. .not. is_collinear_minus) then if ( .not. nearly_equal (this_sqme_rad, sqme_soft, & abs_smallness=tiny(1._default), rel_smallness=rel_smallness)) then call msg_print_color (char ("Soft MEs do not match in region " // str (alr)), COL_RED) else call msg_print_color (char ("sqme_soft OK in region " // str (alr)), COL_GREEN) end if print *, 'this_sqme_rad, sqme_soft = ', this_sqme_rad, sqme_soft end if if (is_collinear_plus .and. .not. is_soft) then if (is_fsr) then if ( .not. nearly_equal (this_sqme_rad, sqme_coll, & abs_smallness=tiny(1._default), rel_smallness=rel_smallness)) then call msg_print_color (char ("Collinear MEs do not match in region " // str (alr)), COL_RED) else call msg_print_color (char ("sqme_coll OK in region " // str (alr)), COL_GREEN) end if print *, 'this_sqme_rad, sqme_coll = ', this_sqme_rad, sqme_coll else if ( .not. nearly_equal (this_sqme_rad, sqme_coll_plus, & abs_smallness=tiny(1._default), rel_smallness=rel_smallness)) then call msg_print_color (char ("Collinear MEs do not match in region " // str (alr)), COL_RED) else call msg_print_color (char ("sqme_coll_plus OK in region " // str (alr)), COL_GREEN) end if print *, 'this_sqme_rad, sqme_coll_plus = ', this_sqme_rad, sqme_coll_plus end if end if if (is_collinear_minus .and. .not. is_soft) then if (.not. is_fsr) then if ( .not. nearly_equal (this_sqme_rad, sqme_coll_minus, & abs_smallness=tiny(1._default), rel_smallness=rel_smallness)) then call msg_print_color (char ("Collinear MEs do not match in region " // str (alr)), COL_RED) else call msg_print_color (char ("sqme_coll_minus OK in region " // str (alr)), COL_GREEN) end if print *, 'this_sqme_rad, sqme_coll_minus = ', this_sqme_rad, sqme_coll_minus end if end if if (is_soft .and. is_collinear_plus) then if (is_fsr) then if ( .not. nearly_equal (this_sqme_rad, sqme_cs, & abs_smallness=tiny(1._default), rel_smallness=rel_smallness)) then call msg_print_color (char ("Soft-collinear MEs do not match in region " // str (alr)), COL_RED) else call msg_print_color (char ("sqme_cs OK in region " // str (alr)), COL_GREEN) end if print *, 'this_sqme_rad, sqme_cs = ', this_sqme_rad, sqme_cs else if ( .not. nearly_equal (this_sqme_rad, sqme_cs_plus, & abs_smallness=tiny(1._default), rel_smallness=rel_smallness)) then call msg_print_color (char ("Soft-collinear MEs do not match in region " // str (alr)), COL_RED) else call msg_print_color (char ("sqme_cs_plus OK in region " // str (alr)), COL_GREEN) end if print *, 'this_sqme_rad, sqme_cs_plus = ', this_sqme_rad, sqme_cs_plus end if end if if (is_soft .and. is_collinear_minus) then if (.not. is_fsr) then if ( .not. nearly_equal (this_sqme_rad, sqme_cs_minus, & abs_smallness=tiny(1._default), rel_smallness=rel_smallness)) then call msg_print_color (char ("Soft-collinear MEs do not match in region " // str (alr)), COL_RED) else call msg_print_color (char ("sqme_cs_minus OK in region " // str (alr)), COL_GREEN) end if print *, 'this_sqme_rad, sqme_cs_minus = ', this_sqme_rad, sqme_cs_minus end if end if count_alr (alr) = .true. if (all (count_alr)) then deallocate (count_alr) deallocate (sqme_rad_store) end if end if end subroutine real_subtraction_register_debug_sqme @ %def real_subtraction_register_debug_sqme @ For final state radiation, the subtraction remnant cross section is \begin{equation} \sigma_{\text{remn}} = \left(\sigma_{\text{soft}} - \sigma_{\text{soft-coll}}\right) \log (\xi_{\text{max}}) \cdot \frac{\tilde{\xi}}{\xi_{\text{cut}}}. \end{equation} There is only one factor of $\log (\xi_{\text{max}})$ for both limits as $\xi_{\text{max}}$ does not depend on $y$ in the case of FSR. We use the already computed [[sqme_soft]] and [[sqme_cs]] with a factor of $\tilde{\xi}$ which we have to compensate. We also need a factor $1/\xi_{\text{cut}}$ here to assure that the cross section is independent of this free cutoff parameter. However, it still remains to be motivated analytically. <>= function compute_sqme_remnant_fsr (sqme_soft, sqme_cs, xi_max, xi_cut, xi_tilde) result (sqme_remn) real(default) :: sqme_remn real(default), intent(in) :: sqme_soft, sqme_cs, xi_max, xi_cut, xi_tilde if (debug_on) call msg_debug (D_SUBTRACTION, "compute_sqme_remnant_fsr") sqme_remn = (sqme_soft - sqme_cs) * log (xi_max) * xi_tilde / xi_cut end function compute_sqme_remnant_fsr @ %def compute_sqme_remnant_fsr @ <>= procedure :: evaluate_region_isr => real_subtraction_evaluate_region_isr <>= module function real_subtraction_evaluate_region_isr (rsub, alr, & emitter, i_phs, i_res, alpha_coupling) result (sqme_tot) real(default) :: sqme_tot class(real_subtraction_t), intent(inout) :: rsub integer, intent(in) :: alr, emitter, i_phs, i_res real(default), intent(in) :: alpha_coupling end function real_subtraction_evaluate_region_isr <>= module function real_subtraction_evaluate_region_isr (rsub, alr, & emitter, i_phs, i_res, alpha_coupling) result (sqme_tot) real(default) :: sqme_tot class(real_subtraction_t), intent(inout) :: rsub integer, intent(in) :: alr, emitter, i_phs, i_res real(default), intent(in) :: alpha_coupling real(default) :: sqme_rad, sqme_soft, sqme_coll_plus, sqme_coll_minus real(default) :: sqme_cs_plus, sqme_cs_minus real(default) :: sqme_remn sqme_rad = zero; sqme_soft = zero; sqme_coll_plus = zero; sqme_coll_minus = zero sqme_cs_plus = zero; sqme_cs_minus = zero sqme_remn = zero associate (region => rsub%reg_data%regions(alr), template => rsub%settings%fks_template) if (rsub%radiation_event) then sqme_rad = rsub%sqme_real_non_sub (rsub%reg_data%get_matrix_element_index (alr), i_phs) call evaluate_fks_factors (sqme_rad, rsub%reg_data, rsub%real_kinematics, & alr, i_phs, emitter, i_res) call apply_kinematic_factors_radiation (sqme_rad, rsub%purpose, rsub%real_kinematics, i_phs) end if if (rsub%subtraction_event .and. .not. (rsub%subtraction_deactivated & .or. region%nlo_correction_type == "none")) then call rsub%evaluate_subtraction_terms_isr (alr, emitter, i_phs, i_res, alpha_coupling, & sqme_soft, sqme_coll_plus, sqme_coll_minus, sqme_cs_plus, sqme_cs_minus) call apply_kinematic_factors_subtraction_isr (sqme_soft, sqme_coll_plus, & sqme_coll_minus, sqme_cs_plus, sqme_cs_minus, rsub%real_kinematics, i_phs) associate (symm_factor_fs => rsub%reg_data%born_to_real_symm_factor_fs (alr)) sqme_soft = sqme_soft * symm_factor_fs sqme_coll_plus = sqme_coll_plus * symm_factor_fs sqme_coll_minus = sqme_coll_minus * symm_factor_fs sqme_cs_plus = sqme_cs_plus * symm_factor_fs sqme_cs_minus = sqme_cs_minus * symm_factor_fs end associate sqme_remn = compute_sqme_remnant_isr (rsub%isr_kinematics%isr_mode, & sqme_soft, sqme_cs_plus, sqme_cs_minus, & rsub%isr_kinematics, rsub%real_kinematics, i_phs, template%xi_cut) sqme_tot = - sqme_soft - sqme_coll_plus - sqme_coll_minus & + sqme_cs_plus + sqme_cs_minus + sqme_remn else sqme_tot = sqme_rad end if end associate sqme_tot = sqme_tot * rsub%real_kinematics%jac_rand (i_phs) sqme_tot = sqme_tot * rsub%reg_data%regions(alr)%mult if (debug_active (D_SUBTRACTION) .and. .not. debug2_active (D_SUBTRACTION)) then call real_subtraction_register_debug_sqme (rsub, alr, emitter, i_phs, sqme_rad,& sqme_soft, sqme_coll_plus=sqme_coll_plus, sqme_coll_minus=sqme_coll_minus,& sqme_cs_plus=sqme_cs_plus, sqme_cs_minus=sqme_cs_minus) else if (debug2_active (D_SUBTRACTION)) then call write_computation_status_isr () end if contains <> subroutine write_computation_status_isr (unit) integer, intent(in), optional :: unit integer :: i_born integer :: u real(default) :: xi u = given_output_unit (unit); if (u < 0) return i_born = rsub%reg_data%regions(alr)%uborn_index xi = rsub%real_kinematics%xi_max (i_phs) * rsub%real_kinematics%xi_tilde write (u,'(A,I4)') 'alr: ', alr write (u,'(A,I2)') 'emitter: ', emitter write (u,'(A,F4.2)') 'xi_max: ', rsub%real_kinematics%xi_max (i_phs) print *, 'xi: ', xi, 'y: ', rsub%real_kinematics%y (i_phs) print *, 'xb1: ', rsub%isr_kinematics%x(1), 'xb2: ', rsub%isr_kinematics%x(2) print *, 'random jacobian: ', rsub%real_kinematics%jac_rand (i_phs) write (u,'(A,ES16.9)') 'sqme_born: ', rsub%sqme_born(i_born) write (u,'(A,ES16.9)') 'sqme_real: ', sqme_rad write (u,'(A,ES16.9)') 'sqme_soft: ', sqme_soft write (u,'(A,ES16.9)') 'sqme_coll_plus: ', sqme_coll_plus write (u,'(A,ES16.9)') 'sqme_coll_minus: ', sqme_coll_minus write (u,'(A,ES16.9)') 'sqme_cs_plus: ', sqme_cs_plus write (u,'(A,ES16.9)') 'sqme_cs_minus: ', sqme_cs_minus write (u,'(A,ES16.9)') 'sqme_remn: ', sqme_remn write (u,'(A,ES16.9)') 'sqme_tot: ', sqme_tot write (u,'(A,ES16.9)') 'jacobian - real: ', rsub%real_kinematics%jac(i_phs)%jac(1) write (u,'(A,ES16.9)') 'jacobian - soft: ', rsub%real_kinematics%jac(i_phs)%jac(2) write (u,'(A,ES16.9)') 'jacobian - collplus: ', rsub%real_kinematics%jac(i_phs)%jac(3) write (u,'(A,ES16.9)') 'jacobian - collminus: ', rsub%real_kinematics%jac(i_phs)%jac(4) end subroutine write_computation_status_isr end function real_subtraction_evaluate_region_isr @ %def real_subtraction_evaluate_region_isr @ Computes the soft remnant for ISR. The formulas can be found in arXiv:1002.2581, eq. 4.21. and arXiv:0709.2092, sec. 5.1.2. This results in \begin{equation} \sigma_{\text{remn}}^{\text{ISR}} = \log(\xi_{\text{max}}(y)) \sigma_{\text{soft}} - \frac{1}{2} \log(\xi_{\text{max}}(1)) \sigma^{\text{soft-coll}}_{\oplus} - \frac{1}{2} \log(\xi_{\text{max}}(-1)) \sigma^{\text{soft-coll}}_{\ominus} \end{equation} where for ISR, $\xi_{\text{max}}$ does explicitly depend on $y$ due to the rescaling of the $x$ values from the Born to the real partonic system according to \begin{equation} x_\oplus = \frac{\overline{x}_\oplus}{\sqrt{1-\xi}} \sqrt{\frac{2-\xi(1-y)}{2-\xi(1+y)}} , \qquad x_\ominus = \frac{\overline{x}_\ominus}{\sqrt{1-\xi}} \sqrt{\frac{2-\xi(1+y)}{2-\xi(1-y)}} \end{equation} As $\xi_{\text{max}}$ is determined by the fact that the real $x_\oplus,x_\ominus$ have to stay in a physically meaningful regime, i.e. $x_\oplus,x_\ominus < 1$, this leads to \begin{align} \label{eqn:xi_max_isr} \xi_\text{max} = 1 - \text{max} &\left\{\frac{2(1+y)\overline{x}_\oplus^2}{\sqrt{(1+\overline{x}_\oplus^2)^2(1-y)^2 + 16y\overline{x}_\oplus^2} + (1-y)(1-\overline{x}_\oplus^2)}\right., \\ &\left.\frac{2(1-y)\overline{x}_\oplus^2}{\sqrt{(1+\overline{x}_\oplus^2)^2(1+y)^2 - 16y\overline{x}_\oplus^2} + (1+y)(1-\overline{x}_\oplus^2)}\right\} \end{align} and thus \begin{align} \xi_{\text{max}}(y=1) &= 1 - \overline{x}_\oplus \\ \xi_{\text{max}}(y=-1) &= 1 - \overline{x}_\ominus \end{align} So we need to use the unrescaled $\overline{x}_\oplus,\overline{x}_\ominus$ here. Factors of $\frac{1}{2}$ and $\frac{1}{\tilde{\xi}}$ are already included in the matrix elements from [[apply_kinematic_factors_subtraction_isr]]. We keep the former and remove the latter by multiplying with $\tilde{\xi}$. The factor $1/\xi_{\text{cut}}$ is probably needed to assure that the cross section is independent of this free cutoff parameter in analogy to the FSR case. However, it still remains to be motivated analytically and to be validated. <>= function compute_sqme_remnant_isr (isr_mode, sqme_soft, sqme_cs_plus, sqme_cs_minus, & isr_kinematics, real_kinematics, i_phs, xi_cut) result (sqme_remn) real(default) :: sqme_remn integer, intent(in) :: isr_mode real(default), intent(in) :: sqme_soft, sqme_cs_plus, sqme_cs_minus type(isr_kinematics_t), intent(in) :: isr_kinematics type(real_kinematics_t), intent(in) :: real_kinematics integer, intent(in) :: i_phs real(default), intent(in) :: xi_cut real(default) :: xi_tilde, xi_max, xi_max_plus, xi_max_minus, xb_plus, xb_minus xi_max = real_kinematics%xi_max (i_phs) xi_tilde = real_kinematics%xi_tilde select case (isr_mode) case (SQRTS_VAR) xb_plus = isr_kinematics%x(I_PLUS) xb_minus = isr_kinematics%x(I_MINUS) xi_max_plus = one - xb_plus xi_max_minus = one - xb_minus case (SQRTS_FIXED) xi_max_plus = real_kinematics%xi_max (i_phs) xi_max_minus = real_kinematics%xi_max (i_phs) end select sqme_remn = log (xi_max) * xi_tilde * sqme_soft & - log (xi_max_plus) * xi_tilde * sqme_cs_plus & - log (xi_max_minus) * xi_tilde * sqme_cs_minus sqme_remn = sqme_remn / xi_cut end function compute_sqme_remnant_isr @ %def compute_sqme_remnant_isr @ <>= procedure :: evaluate_subtraction_terms_fsr => & real_subtraction_evaluate_subtraction_terms_fsr <>= module subroutine real_subtraction_evaluate_subtraction_terms_fsr & (rsub, alr, emitter, i_phs, i_res, alpha_coupling, sqme_soft, & sqme_coll, sqme_cs) class(real_subtraction_t), intent(inout) :: rsub integer, intent(in) :: alr, emitter, i_phs, i_res real(default), intent(in) :: alpha_coupling real(default), intent(out) :: sqme_soft, sqme_coll, sqme_cs end subroutine real_subtraction_evaluate_subtraction_terms_fsr <>= module subroutine real_subtraction_evaluate_subtraction_terms_fsr & (rsub, alr, emitter, i_phs, i_res, alpha_coupling, sqme_soft, & sqme_coll, sqme_cs) class(real_subtraction_t), intent(inout) :: rsub integer, intent(in) :: alr, emitter, i_phs, i_res real(default), intent(in) :: alpha_coupling real(default), intent(out) :: sqme_soft, sqme_coll, sqme_cs if (debug_on) call msg_debug & (D_SUBTRACTION, "real_subtraction_evaluate_subtraction_terms_fsr") sqme_soft = zero; sqme_coll = zero; sqme_cs = zero associate (xi_tilde => rsub%real_kinematics%xi_tilde, & y => rsub%real_kinematics%y(i_phs), & template => rsub%settings%fks_template) if (template%xi_cut > xi_tilde) & sqme_soft = rsub%compute_sub_soft & (alr, emitter, i_phs, i_res, alpha_coupling) if (y - 1 + template%delta_o > 0) & sqme_coll = rsub%compute_sub_coll & (alr, emitter, i_phs, alpha_coupling) if (template%xi_cut > xi_tilde .and. y - 1 + template%delta_o > 0) & sqme_cs = rsub%compute_sub_coll_soft & (alr, emitter, i_phs, alpha_coupling) if (debug2_active (D_SUBTRACTION)) then print *, "FSR Cutoff:" print *, "sub_soft: ", & template%xi_cut > xi_tilde, "(ME: ", sqme_soft, ")" print *, "sub_coll: ", & (y - 1 + template%delta_o) > 0, "(ME: ", sqme_coll, ")" print *, "sub_coll_soft: ", & template%xi_cut > xi_tilde .and. (y - 1 + template%delta_o) > 0, & "(ME: ", sqme_cs, ")" end if end associate end subroutine real_subtraction_evaluate_subtraction_terms_fsr @ %def real_subtraction_evaluate_subtraction_terms_fsr @ <>= subroutine evaluate_fks_factors (sqme, reg_data, real_kinematics, & alr, i_phs, emitter, i_res) real(default), intent(inout) :: sqme type(region_data_t), intent(inout) :: reg_data type(real_kinematics_t), intent(in), target :: real_kinematics integer, intent(in) :: alr, i_phs, emitter, i_res real(default) :: s_alpha type(phs_point_set_t), pointer :: p_real => null () if (reg_data%has_pseudo_isr ()) then p_real => real_kinematics%p_real_onshell (i_phs) else p_real => real_kinematics%p_real_cms end if s_alpha = reg_data%get_svalue (p_real%get_momenta(i_phs), alr, emitter, i_res) if (debug2_active (D_SUBTRACTION)) call msg_print_color('s_alpha', s_alpha, COL_YELLOW) if (s_alpha > one + tiny_07) call msg_fatal ("s_alpha > 1!") sqme = sqme * s_alpha associate (region => reg_data%regions(alr)) if (emitter > reg_data%n_in) then if (debug2_active (D_SUBTRACTION)) & print *, 'Double FSR: ', region%double_fsr_factor (p_real%get_momenta(i_phs)) sqme = sqme * region%double_fsr_factor (p_real%get_momenta(i_phs)) end if end associate end subroutine evaluate_fks_factors @ %def evaluate_fks_factors @ Applies the Jacobian to the squared matrix element. During integration and when generating fixed order events, the non-kinematic part $\frac{s}{(4\pi)^3}$ is applied in [[real_subtraction_compute]] via [[get_phs_factor]]. For the purpose of generating POWHEG events, we do it here. The additional factor $\frac{\xi}{\tilde\xi}$ during integration comes from eq.~(4.19f) in arXiv:1002.2581. During integration, we sample $\tilde\xi \in [0,1]$ while we sample $\xi \in [p_T^2,\xi_\text{max}]$ for POWHEG matching. Thus, we are taking into account that $d\xi = d\tilde\xi \frac{\xi}{\tilde\xi}$. <>= subroutine apply_kinematic_factors_radiation (sqme, purpose, & real_kinematics, i_phs) real(default), intent(inout) :: sqme integer, intent(in) :: purpose type(real_kinematics_t), intent(in) :: real_kinematics integer, intent(in) :: i_phs real(default) :: xi, xi_tilde, s_b xi_tilde = real_kinematics%xi_tilde xi = xi_tilde * real_kinematics%xi_max (i_phs) select case (purpose) case (INTEGRATION, FIXED_ORDER_EVENTS) sqme = sqme * xi**2 / xi_tilde * real_kinematics%jac(i_phs)%jac(1) case (POWHEG) s_b = real_kinematics%cms_energy2 sqme = sqme * xi * s_b / (8 * twopi3) * real_kinematics%jac(i_phs)%jac(1) end select end subroutine apply_kinematic_factors_radiation @ %def apply_kinematic_factors_radiation @ This routine applies the factors in the integrand of eq. 4.20 in arXiv:1002.2581 to the matrix elements. <>= subroutine apply_kinematic_factors_subtraction_fsr & (sqme_soft, sqme_coll, sqme_cs, real_kinematics, i_phs) real(default), intent(inout) :: sqme_soft, sqme_coll, sqme_cs type(real_kinematics_t), intent(in) :: real_kinematics integer, intent(in) :: i_phs real(default) :: xi_tilde, onemy xi_tilde = real_kinematics%xi_tilde onemy = one - real_kinematics%y(i_phs) sqme_soft = sqme_soft / onemy / xi_tilde sqme_coll = sqme_coll / onemy / xi_tilde sqme_cs = sqme_cs / onemy / xi_tilde associate (jac => real_kinematics%jac(i_phs)%jac) sqme_soft = sqme_soft * jac(2) sqme_coll = sqme_coll * jac(3) sqme_cs = sqme_cs * jac(2) end associate end subroutine apply_kinematic_factors_subtraction_fsr @ %def apply_kinematic_factors_subtraction_fsr @ This routine applies the factors in the integrand of eq. 4.21 in arXiv:1002.2581 to the matrix elements. <>= subroutine apply_kinematic_factors_subtraction_isr & (sqme_soft, sqme_coll_plus, sqme_coll_minus, sqme_cs_plus, & sqme_cs_minus, real_kinematics, i_phs) real(default), intent(inout) :: sqme_soft, sqme_coll_plus, sqme_coll_minus real(default), intent(inout) :: sqme_cs_plus, sqme_cs_minus type(real_kinematics_t), intent(in) :: real_kinematics integer, intent(in) :: i_phs real(default) :: xi_tilde, y, onemy, onepy xi_tilde = real_kinematics%xi_tilde y = real_kinematics%y (i_phs) onemy = one - y; onepy = one + y associate (jac => real_kinematics%jac(i_phs)%jac) sqme_soft = sqme_soft / (one - y**2) / xi_tilde * jac(2) sqme_coll_plus = sqme_coll_plus / onemy / xi_tilde / two * jac(3) sqme_coll_minus = sqme_coll_minus / onepy / xi_tilde / two * jac(4) sqme_cs_plus = sqme_cs_plus / onemy / xi_tilde / two * jac(2) sqme_cs_minus = sqme_cs_minus / onepy / xi_tilde / two * jac(2) end associate end subroutine apply_kinematic_factors_subtraction_isr @ %def apply_kinematic_factors_subtraction_isr @ This subroutine evaluates the soft and collinear subtraction terms for ISR. References: \begin{itemize} \item arXiv:0709.2092, sec. 2.4.2 \item arXiv:0908.4272, sec. 4.2 \end{itemize} For the collinear terms, the procedure is as follows: If the emitter is 0, then a gluon was radiated from one of the incoming partons. Gluon emissions require two counter terms: One for emission in the direction of the first incoming parton $\oplus$ and a second for emission in the direction of the second incoming parton $\ominus$ because in both cases, there are divergent diagrams contributing to the matrix element. So in this case both, [[sqme_coll_plus]] and [[sqme_coll_minus]], are non-zero. If the emitter is 1 or 2, then a quark was emitted instead of a gluon. This only leads to a divergence collinear to the emitter because for anti-collinear quark emission, there are simply no divergent diagrams in the same region as two collinear quarks that cannot originate in the same splitting are non-divergent. This means that in case the emitter is 1, we need non-zero [[sqme_coll_plus]] and in case the emitter is 2, we need non-zero [[sqme_coll_minus]]. At this point, we want to remind ourselves that in case of initial state divergences, $y$ is just the polar angle, so the [[sqme_coll_minus]] terms are there to counter emissions in the direction of the second incoming parton $\ominus$ and {\em not} to counter in general anti-collinear divergences. <>= procedure :: evaluate_subtraction_terms_isr => & real_subtraction_evaluate_subtraction_terms_isr <>= module subroutine real_subtraction_evaluate_subtraction_terms_isr (rsub, & alr, emitter, i_phs, i_res, alpha_coupling, sqme_soft, sqme_coll_plus, & sqme_coll_minus, sqme_cs_plus, sqme_cs_minus) class(real_subtraction_t), intent(inout) :: rsub integer, intent(in) :: alr, emitter, i_phs, i_res real(default), intent(in) :: alpha_coupling real(default), intent(out) :: sqme_soft real(default), intent(out) :: sqme_coll_plus, sqme_coll_minus real(default), intent(out) :: sqme_cs_plus, sqme_cs_minus end subroutine real_subtraction_evaluate_subtraction_terms_isr <>= module subroutine real_subtraction_evaluate_subtraction_terms_isr (rsub, & alr, emitter, i_phs, i_res, alpha_coupling, sqme_soft, sqme_coll_plus, & sqme_coll_minus, sqme_cs_plus, sqme_cs_minus) class(real_subtraction_t), intent(inout) :: rsub integer, intent(in) :: alr, emitter, i_phs, i_res real(default), intent(in) :: alpha_coupling real(default), intent(out) :: sqme_soft real(default), intent(out) :: sqme_coll_plus, sqme_coll_minus real(default), intent(out) :: sqme_cs_plus, sqme_cs_minus sqme_coll_plus = zero; sqme_cs_plus = zero sqme_coll_minus = zero; sqme_cs_minus = zero associate (xi_tilde => rsub%real_kinematics%xi_tilde, & y => rsub%real_kinematics%y(i_phs), & template => rsub%settings%fks_template) if (template%xi_cut > xi_tilde) & sqme_soft = rsub%compute_sub_soft & (alr, emitter, i_phs, i_res, alpha_coupling) if (emitter /= 2) then if (y - 1 + template%delta_i > 0) then sqme_coll_plus = & rsub%compute_sub_coll (alr, 1, i_phs, alpha_coupling) if (template%xi_cut > xi_tilde) then sqme_cs_plus = & rsub%compute_sub_coll_soft (alr, 1, i_phs, alpha_coupling) end if end if end if if (emitter /= 1) then if (-y - 1 + template%delta_i > 0) then sqme_coll_minus = & rsub%compute_sub_coll (alr, 2, i_phs, alpha_coupling) if (template%xi_cut > xi_tilde) then sqme_cs_minus = & rsub%compute_sub_coll_soft (alr, 2, i_phs, alpha_coupling) end if end if end if if (debug2_active (D_SUBTRACTION)) then print *, "ISR Cutoff:" print *, "y: ", y print *, "delta_i: ", template%delta_i print *, "emitter: ", emitter print *, "sub_soft: ", & template%xi_cut > xi_tilde, "(ME: ", sqme_soft, ")" print *, "sub_coll_plus: ", & (y - 1 + template%delta_i) > 0, "(ME: ", sqme_coll_plus, ")" print *, "sub_coll_minus: ", & (-y - 1 + template%delta_i) > 0, "(ME: ", sqme_coll_minus, ")" print *, "sub_coll_soft_plus: ", template%xi_cut > xi_tilde .and. & (y - 1 + template%delta_i) > 0, "(ME: ", sqme_cs_plus, ")" print *, "sub_coll_soft_minus: ", template%xi_cut > xi_tilde .and. & (-y - 1 + template%delta_i) > 0, "(ME: ", sqme_cs_minus, ")" end if end associate end subroutine real_subtraction_evaluate_subtraction_terms_isr @ %def real_subtraction_evaluate_subtraction_terms_isr @ This is basically the global part of the real Jacobian corresponding to \begin{equation*} \frac{q^2}{8 (2\pi)^3}. \end{equation*} We interpret it as the additional phase space factor of the real component, to be more consistent with the evaluation of the Born phase space. We specifically use the Born center-of-mass energy here. The real center-of-mass energy is only different from the Born center-of-mass energy in case of ISR. The missing factor $\frac{1}{1 - \xi}$ for this conversion is supplied in [[phs_fks_generator_generate_isr]]. <>= procedure :: get_phs_factor => real_subtraction_get_phs_factor <>= module function real_subtraction_get_phs_factor & (rsub, i_con) result (factor) real(default) :: factor class(real_subtraction_t), intent(in) :: rsub integer, intent(in) :: i_con end function real_subtraction_get_phs_factor <>= module function real_subtraction_get_phs_factor (rsub, i_con) result (factor) real(default) :: factor class(real_subtraction_t), intent(in) :: rsub integer, intent(in) :: i_con real(default) :: s s = rsub%real_kinematics%xi_ref_momenta (i_con)**2 factor = s / (8 * twopi3) end function real_subtraction_get_phs_factor @ %def real_subtraction_get_phs_factor @ <>= procedure :: get_i_contributor => real_subtraction_get_i_contributor <>= module function real_subtraction_get_i_contributor & (rsub, alr) result (i_con) integer :: i_con class(real_subtraction_t), intent(in) :: rsub integer, intent(in) :: alr end function real_subtraction_get_i_contributor <>= module function real_subtraction_get_i_contributor (rsub, alr) result (i_con) integer :: i_con class(real_subtraction_t), intent(in) :: rsub integer, intent(in) :: alr if (allocated (rsub%reg_data%alr_to_i_contributor)) then i_con = rsub%reg_data%alr_to_i_contributor (alr) else i_con = 1 end if end function real_subtraction_get_i_contributor @ %def real_subtraction_get_i_contributor @ Computes the soft subtraction term. If there is an initial state emission having a soft divergence, then a gluon has to have been emitted. A gluon can always be emitted from both IS partons and thus, we can take the [[sf_factor]] for emitter $0$ in this case. Be aware that this approach will not work for $pe$ collisions. <>= procedure :: compute_sub_soft => real_subtraction_compute_sub_soft <>= module function real_subtraction_compute_sub_soft (rsub, alr, emitter, & i_phs, i_res, alpha_coupling) result (sqme_soft) real(default) :: sqme_soft class(real_subtraction_t), intent(inout) :: rsub integer, intent(in) :: alr, emitter, i_phs, i_res real(default), intent(in) :: alpha_coupling end function real_subtraction_compute_sub_soft <>= module function real_subtraction_compute_sub_soft (rsub, alr, emitter, & i_phs, i_res, alpha_coupling) result (sqme_soft) real(default) :: sqme_soft class(real_subtraction_t), intent(inout) :: rsub integer, intent(in) :: alr, emitter, i_phs, i_res real(default), intent(in) :: alpha_coupling integer :: i_xi_ref, i_born real(default) :: q2, sf_factor type(vector4_t), dimension(:), allocatable :: p_born associate (real_kinematics => rsub%real_kinematics, & nlo_corr_type => rsub%reg_data%regions(alr)%nlo_correction_type, & sregion => rsub%reg_data%regions(alr)) sqme_soft = zero if (sregion%has_soft_divergence ()) then i_xi_ref = rsub%sub_soft%i_xi_ref (alr, i_phs) q2 = real_kinematics%xi_ref_momenta (i_xi_ref)**2 allocate (p_born (rsub%reg_data%n_legs_born)) if (rsub%reg_data%has_pseudo_isr ()) then p_born = real_kinematics%p_born_onshell%get_momenta (1) else p_born = real_kinematics%p_born_cms%get_momenta (1) end if if (emitter > rsub%sub_soft%reg_data%n_in) then call rsub%sub_soft%create_softvec_fsr & (p_born, real_kinematics%y_soft(i_phs), & real_kinematics%phi, emitter, & real_kinematics%xi_ref_momenta(i_xi_ref)) sf_factor = one else call rsub%sub_soft%create_softvec_isr & (real_kinematics%y_soft(i_phs), real_kinematics%phi) sf_factor = rsub%sf_factors(alr, 0) end if i_born = sregion%uborn_index select case (char (nlo_corr_type)) case ("QCD") sqme_soft = rsub%sub_soft%compute & (p_born, rsub%sqme_born_color_c(:,:,i_born) * & sf_factor, real_kinematics%y(i_phs), & q2, alpha_coupling, alr, emitter, i_res) case ("EW") sqme_soft = rsub%sub_soft%compute & (p_born, rsub%sqme_born_charge_c(:,:,i_born) * & sf_factor, real_kinematics%y(i_phs), & q2, alpha_coupling, alr, emitter, i_res) end select end if end associate if (debug2_active (D_SUBTRACTION)) call check_soft_vector () contains subroutine check_soft_vector () !!! p_soft = p_gluon / E_gluon only in the soft limit !!! This check only has to be passed for ISR or for FSR if ?test_soft_limit = true is set. type(vector4_t) :: p_gluon if (debug_on) call msg_debug2 (D_SUBTRACTION, "Compare soft vector: ") print *, 'p_soft: ', rsub%sub_soft%p_soft%p print *, 'Normalized gluon momentum: ' if (rsub%reg_data%has_pseudo_isr ()) then p_gluon = rsub%real_kinematics%p_real_onshell(thr_leg(emitter))%get_momentum & (i_phs, rsub%reg_data%n_legs_real) else p_gluon = rsub%real_kinematics%p_real_cms%get_momentum & (i_phs, rsub%reg_data%n_legs_real) end if call vector4_write (p_gluon / p_gluon%p(0), show_mass = .true.) end subroutine check_soft_vector end function real_subtraction_compute_sub_soft @ %def real_subtraction_compute_sub_soft @ <>= procedure :: get_spin_correlation_term => & real_subtraction_get_spin_correlation_term <>= module function real_subtraction_get_spin_correlation_term & (rsub, alr, i_born, emitter) result (mom_times_sqme) real(default) :: mom_times_sqme class(real_subtraction_t), intent(in) :: rsub integer, intent(in) :: alr, i_born, emitter end function real_subtraction_get_spin_correlation_term <>= module function real_subtraction_get_spin_correlation_term & (rsub, alr, i_born, emitter) result (mom_times_sqme) real(default) :: mom_times_sqme class(real_subtraction_t), intent(in) :: rsub integer, intent(in) :: alr, i_born, emitter real(default), dimension(0:3) :: k_perp integer :: mu, nu if (rsub%sc_required(alr)) then if (debug2_active(D_SUBTRACTION)) call check_me_consistency () associate (real_kin => rsub%real_kinematics) if (emitter > rsub%reg_data%n_in) then k_perp = real_subtraction_compute_k_perp_fsr ( & real_kin%p_born_lab%get_momentum(1, emitter), & rsub%real_kinematics%phi) else k_perp = real_subtraction_compute_k_perp_isr ( & real_kin%p_born_lab%get_momentum(1, emitter), & rsub%real_kinematics%phi) end if end associate mom_times_sqme = zero do mu = 1, 3 do nu = 1, 3 mom_times_sqme = mom_times_sqme + & k_perp(mu) * k_perp(nu) * rsub%sqme_born_spin_c (mu, nu, emitter, i_born) end do end do else mom_times_sqme = zero end if contains subroutine check_me_consistency () real(default) :: sqme_sum if (debug_on) call msg_debug2 (D_SUBTRACTION, "Spin-correlation: Consistency check") sqme_sum = & - rsub%sqme_born_spin_c(1,1,emitter,i_born) & - rsub%sqme_born_spin_c(2,2,emitter,i_born) & - rsub%sqme_born_spin_c(3,3,emitter,i_born) if (.not. nearly_equal (sqme_sum, -rsub%sqme_born(i_born))) then print *, 'Spin-correlated matrix elements are not consistent: ' print *, 'emitter: ', emitter print *, 'g^{mu,nu} B_{mu,nu}: ', -sqme_sum print *, 'all Born matrix elements: ', rsub%sqme_born call msg_fatal ("FAIL") else call msg_print_color ("Success", COL_GREEN) end if end subroutine check_me_consistency end function real_subtraction_get_spin_correlation_term @ %def real_subtraction_get_spin_correlation_term @ Construct a normalised momentum perpendicular to momentum [[p]] and rotate by an arbitrary angle [[phi]]. The angular conventions we use here are equivalent to those used by POWHEG. <>= public :: real_subtraction_compute_k_perp_fsr public :: real_subtraction_compute_k_perp_isr <>= module function real_subtraction_compute_k_perp_fsr & (p, phi) result (k_perp_fsr) real(default), dimension(0:3) :: k_perp_fsr type(vector4_t), intent(in) :: p real(default), intent(in) :: phi end function real_subtraction_compute_k_perp_fsr module function real_subtraction_compute_k_perp_isr & (p, phi) result (k_perp_isr) real(default), dimension(0:3) :: k_perp_isr type(vector4_t), intent(in) :: p real(default), intent(in) :: phi end function real_subtraction_compute_k_perp_isr <>= module function real_subtraction_compute_k_perp_fsr & (p, phi) result (k_perp_fsr) real(default), dimension(0:3) :: k_perp_fsr type(vector4_t), intent(in) :: p real(default), intent(in) :: phi type(vector4_t) :: k type(vector3_t) :: vec type(lorentz_transformation_t) :: rot vec = p%p(1:3) / p%p(0) k%p(0) = zero k%p(1) = p%p(1); k%p(2) = p%p(2) k%p(3) = - (p%p(1)**2 + p%p(2)**2) / p%p(3) rot = rotation (cos(phi), sin(phi), vec) k = rot * k k%p(1:3) = k%p(1:3) / space_part_norm (k) k_perp_fsr = k%p end function real_subtraction_compute_k_perp_fsr module function real_subtraction_compute_k_perp_isr & (p, phi) result (k_perp_isr) real(default), dimension(0:3) :: k_perp_isr type(vector4_t), intent(in) :: p real(default), intent(in) :: phi k_perp_isr(0) = zero k_perp_isr(1) = sin(phi) k_perp_isr(2) = cos(phi) k_perp_isr(3) = zero end function real_subtraction_compute_k_perp_isr @ %def real_subtraction_compute_k_perp_fsr, real_subtraction_compute_k_perp_isr @ <>= procedure :: compute_sub_coll => real_subtraction_compute_sub_coll <>= module function real_subtraction_compute_sub_coll & (rsub, alr, em, i_phs, alpha_coupling) result (sqme_coll) real(default) :: sqme_coll class(real_subtraction_t), intent(inout) :: rsub integer, intent(in) :: alr, em, i_phs real(default), intent(in) :: alpha_coupling end function real_subtraction_compute_sub_coll <>= module function real_subtraction_compute_sub_coll & (rsub, alr, em, i_phs, alpha_coupling) result (sqme_coll) real(default) :: sqme_coll class(real_subtraction_t), intent(inout) :: rsub integer, intent(in) :: alr, em, i_phs real(default), intent(in) :: alpha_coupling real(default) :: xi, xi_max real(default) :: mom_times_sqme_spin_c, sqme_born_coll real(default) :: N_col integer :: i_con, i real(default) :: pfr associate (sregion => rsub%reg_data%regions(alr)) sqme_coll = zero sqme_born_coll = zero N_col = 1 if (sregion%has_collinear_divergence ()) then xi = rsub%real_kinematics%xi_tilde * rsub%real_kinematics%xi_max(i_phs) if (rsub%sub_coll%use_resonance_mappings) then i_con = rsub%reg_data%alr_to_i_contributor (alr) else i_con = 1 end if mom_times_sqme_spin_c = & rsub%get_spin_correlation_term (alr, sregion%uborn_index, em) if (rsub%reg_data%nlo_correction_type == "EW" .and. & sregion%nlo_correction_type == "QCD" .and. & qcd_ew_interferences (sregion%flst_uborn%flst)) then do i = 1, size (sregion%flst_uborn%flst) if (is_quark (sregion%flst_uborn%flst (i))) then sqme_born_coll = & -rsub%sqme_born_color_c (i, i, sregion%uborn_index)/CF exit end if end do else sqme_born_coll = rsub%sqme_born(sregion%uborn_index) end if if (em <= rsub%sub_coll%n_in) then select case (rsub%isr_kinematics%isr_mode) case (SQRTS_FIXED) xi_max = rsub%real_kinematics%xi_max(i_phs) case (SQRTS_VAR) xi_max = one - rsub%isr_kinematics%x(em) end select xi = rsub%real_kinematics%xi_tilde * xi_max if (sregion%nlo_correction_type == "QCD") then call rsub%sub_coll%set_parameters (CA = CA, CF = CF, TR = TR) else if (sregion%nlo_correction_type == "EW") then if (is_quark (sregion%flst_real%flst(size(sregion%flst_real%flst)))) N_col = 3 call rsub%sub_coll%set_parameters (CA = zero, & CF = sregion%flst_real%charge(em)**2, & TR = N_col*sregion%flst_real%charge(size(sregion%flst_real%flst))**2) end if sqme_coll = rsub%sub_coll%compute_isr (em, sregion%flst_real%flst, & rsub%real_kinematics%p_born_lab%phs_point(1)%get (), & sqme_born_coll * rsub%sf_factors(alr, em), & mom_times_sqme_spin_c * rsub%sf_factors(alr, em), & xi, alpha_coupling, rsub%isr_kinematics%isr_mode) else if (sregion%nlo_correction_type == "QCD") then call rsub%sub_coll%set_parameters (CA = CA, CF = CF, TR = TR) else if (sregion%nlo_correction_type == "EW") then if (is_quark (sregion%flst_real%flst(sregion%emitter))) N_col = 3 call rsub%sub_coll%set_parameters (CA = zero, & CF = sregion%flst_real%charge(sregion%emitter)**2, & TR = N_col*sregion%flst_real%charge(sregion%emitter)**2) end if sqme_coll = rsub%sub_coll%compute_fsr (sregion%emitter, & sregion%flst_real%flst, & rsub%real_kinematics%xi_ref_momenta (i_con), & rsub%real_kinematics%p_born_lab%get_momenta(1), & sqme_born_coll, & mom_times_sqme_spin_c, & xi, alpha_coupling, sregion%double_fsr) if (rsub%sub_coll%use_resonance_mappings) then select type (fks_mapping => rsub%reg_data%fks_mapping) type is (fks_mapping_resonances_t) pfr = fks_mapping%get_resonance_weight (alr, & rsub%real_kinematics%p_born_cms%get_momenta(1)) end select sqme_coll = sqme_coll * pfr end if end if end if end associate end function real_subtraction_compute_sub_coll @ %def real_subtraction_compute_sub_coll @ Computes the soft-collinear subtraction term. For alpha regions with emitter $0$, this routine is called with [[em == 1]] and [[em == 2]] separately. To still be able to use the unrescaled pdf factors stored in [[sf_factors(alr, 0)]] in this case, we need to differentiate between [[em]] and [[em_pdf = 0]]. <>= procedure :: compute_sub_coll_soft => real_subtraction_compute_sub_coll_soft <>= module function real_subtraction_compute_sub_coll_soft & (rsub, alr, em, i_phs, alpha_coupling) result (sqme_cs) real(default) :: sqme_cs class(real_subtraction_t), intent(inout) :: rsub integer, intent(in) :: alr, em, i_phs real(default), intent(in) :: alpha_coupling end function real_subtraction_compute_sub_coll_soft <>= module function real_subtraction_compute_sub_coll_soft & (rsub, alr, em, i_phs, alpha_coupling) result (sqme_cs) real(default) :: sqme_cs class(real_subtraction_t), intent(inout) :: rsub integer, intent(in) :: alr, em, i_phs real(default), intent(in) :: alpha_coupling real(default) :: mom_times_sqme_spin_c, sqme_born_coll real(default) :: N_col integer :: i_con, em_pdf, i associate (sregion => rsub%reg_data%regions(alr)) sqme_cs = zero sqme_born_coll = zero N_col = 1 if (sregion%has_collinear_divergence ()) then if (rsub%sub_coll%use_resonance_mappings) then i_con = rsub%reg_data%alr_to_i_contributor (alr) else i_con = 1 end if mom_times_sqme_spin_c = rsub%get_spin_correlation_term (alr, sregion%uborn_index, em) if (rsub%reg_data%nlo_correction_type == "EW" .and. & sregion%nlo_correction_type == "QCD" .and. & qcd_ew_interferences (sregion%flst_uborn%flst)) then do i = 1, size (sregion%flst_uborn%flst) if (is_quark (sregion%flst_uborn%flst (i))) then sqme_born_coll = -rsub%sqme_born_color_c (i, i, sregion%uborn_index)/CF exit end if end do else sqme_born_coll = rsub%sqme_born(sregion%uborn_index) end if if (em <= rsub%sub_coll%n_in) then em_pdf = 0 if (sregion%nlo_correction_type == "QCD") then call rsub%sub_coll%set_parameters (CA = CA, CF = CF, TR = TR) else if (sregion%nlo_correction_type == "EW") then if (is_quark (sregion%flst_real%flst(size(sregion%flst_real%flst)))) N_col = 3 call rsub%sub_coll%set_parameters (CA = zero, & CF = sregion%flst_real%charge(em)**2, & TR = N_col*sregion%flst_real%charge(size(sregion%flst_real%flst))**2) end if sqme_cs = rsub%sub_coll%compute_isr (em, sregion%flst_real%flst, & rsub%real_kinematics%p_born_lab%phs_point(1)%get (), & sqme_born_coll * rsub%sf_factors(alr, em_pdf), & mom_times_sqme_spin_c * rsub%sf_factors(alr, em_pdf), & zero, alpha_coupling, rsub%isr_kinematics%isr_mode) else if (sregion%nlo_correction_type == "QCD") then call rsub%sub_coll%set_parameters (CA = CA, CF = CF, TR = TR) else if (sregion%nlo_correction_type == "EW") then if (is_quark (sregion%flst_real%flst(sregion%emitter))) N_col = 3 call rsub%sub_coll%set_parameters (CA = zero, & CF = sregion%flst_real%charge(sregion%emitter)**2, & TR = N_col*sregion%flst_real%charge(sregion%emitter)**2) end if sqme_cs = rsub%sub_coll%compute_fsr (sregion%emitter, sregion%flst_real%flst, & rsub%real_kinematics%xi_ref_momenta(i_con), & rsub%real_kinematics%p_born_lab%phs_point(1)%get (), & sqme_born_coll, & mom_times_sqme_spin_c, & zero, alpha_coupling, sregion%double_fsr) end if end if end associate end function real_subtraction_compute_sub_coll_soft @ %def real_subtraction_compute_sub_coll_soft <>= procedure :: requires_spin_correlations => & real_subtraction_requires_spin_correlations <>= module function real_subtraction_requires_spin_correlations & (rsub) result (val) logical :: val class(real_subtraction_t), intent(in) :: rsub end function real_subtraction_requires_spin_correlations <>= module function real_subtraction_requires_spin_correlations & (rsub) result (val) logical :: val class(real_subtraction_t), intent(in) :: rsub val = any (rsub%sc_required) end function real_subtraction_requires_spin_correlations @ %def real_subtraction_requires_spin_correlations @ <>= procedure :: final => real_subtraction_final <>= module subroutine real_subtraction_final (rsub) class(real_subtraction_t), intent(inout) :: rsub end subroutine real_subtraction_final <>= module subroutine real_subtraction_final (rsub) class(real_subtraction_t), intent(inout) :: rsub call rsub%sub_soft%final () call rsub%sub_coll%final () !!! Finalization of region data is done in pcm_nlo_final if (associated (rsub%reg_data)) nullify (rsub%reg_data) !!! Finalization of real kinematics is done in pcm_instance_nlo_final if (associated (rsub%real_kinematics)) nullify (rsub%real_kinematics) if (associated (rsub%isr_kinematics)) nullify (rsub%isr_kinematics) if (allocated (rsub%sqme_real_non_sub)) deallocate (rsub%sqme_real_non_sub) if (allocated (rsub%sqme_born)) deallocate (rsub%sqme_born) if (allocated (rsub%sf_factors)) deallocate (rsub%sf_factors) if (allocated (rsub%sqme_born_color_c)) deallocate (rsub%sqme_born_color_c) if (allocated (rsub%sqme_born_charge_c)) deallocate (rsub%sqme_born_charge_c) if (allocated (rsub%sc_required)) deallocate (rsub%sc_required) if (allocated (rsub%selected_alr)) deallocate (rsub%selected_alr) end subroutine real_subtraction_final @ %def real_subtraction_final @ \subsubsection{Partitions of the real matrix element and Powheg damping} <>= public :: real_partition_t <>= type, abstract :: real_partition_t contains <> end type real_partition_t @ %def real partition_t @ <>= procedure (real_partition_init), deferred :: init <>= abstract interface subroutine real_partition_init (partition, scale, reg_data) import class(real_partition_t), intent(out) :: partition real(default), intent(in) :: scale type(region_data_t), intent(in) :: reg_data end subroutine real_partition_init end interface @ %def real_partition_init @ <>= procedure (real_partition_write), deferred :: write <>= abstract interface subroutine real_partition_write (partition, unit) import class(real_partition_t), intent(in) :: partition integer, intent(in), optional :: unit end subroutine real_partition_write end interface @ %def real_partition_write @ To allow really arbitrary damping functions, [[get_f]] should get the full real phase space as argument and not just some [[pt2]] that is extracted higher up. <>= procedure (real_partition_get_f), deferred :: get_f <>= abstract interface function real_partition_get_f (partition, p) result (f) import real(default) :: f class(real_partition_t), intent(in) :: partition type(vector4_t), intent(in), dimension(:) :: p end function real_partition_get_f end interface @ %def real_partition_get_f @ <>= public :: powheg_damping_simple_t <>= type, extends (real_partition_t) :: powheg_damping_simple_t real(default) :: h2 = 5._default integer :: emitter contains <> end type powheg_damping_simple_t @ %def powheg_damping_simple_t @ <>= procedure :: get_f => powheg_damping_simple_get_f <>= module function powheg_damping_simple_get_f (partition, p) result (f) real(default) :: f class(powheg_damping_simple_t), intent(in) :: partition type(vector4_t), intent(in), dimension(:) :: p end function powheg_damping_simple_get_f <>= module function powheg_damping_simple_get_f (partition, p) result (f) real(default) :: f class(powheg_damping_simple_t), intent(in) :: partition type(vector4_t), intent(in), dimension(:) :: p !!! real(default) :: pt2 f = 1 call msg_bug ("Simple damping currently not available") !!! TODO (cw-2017-03-01) Compute pt2 from emitter) !!! f = partition%h2 / (pt2 + partition%h2) end function powheg_damping_simple_get_f @ %def powheg_damping_simple_get_f @ <>= procedure :: init => powheg_damping_simple_init <>= module subroutine powheg_damping_simple_init (partition, scale, reg_data) class(powheg_damping_simple_t), intent(out) :: partition real(default), intent(in) :: scale type(region_data_t), intent(in) :: reg_data end subroutine powheg_damping_simple_init <>= module subroutine powheg_damping_simple_init (partition, scale, reg_data) class(powheg_damping_simple_t), intent(out) :: partition real(default), intent(in) :: scale type(region_data_t), intent(in) :: reg_data partition%h2 = scale**2 end subroutine powheg_damping_simple_init @ %def powheg_damping_simple_init @ <>= procedure :: write => powheg_damping_simple_write <>= module subroutine powheg_damping_simple_write (partition, unit) class(powheg_damping_simple_t), intent(in) :: partition integer, intent(in), optional :: unit end subroutine powheg_damping_simple_write <>= module subroutine powheg_damping_simple_write (partition, unit) class(powheg_damping_simple_t), intent(in) :: partition integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit); if (u < 0) return write (u, "(1x,A)") "Powheg damping simple: " write (u, "(1x,A, "// FMT_15 // ")") "scale h2: ", partition%h2 end subroutine powheg_damping_simple_write @ %def powheg_damping_simple_write @ <>= public :: real_partition_fixed_order_t <>= type, extends (real_partition_t) :: real_partition_fixed_order_t real(default) :: scale type(ftuple_t), dimension(:), allocatable :: fks_pairs contains <> end type real_partition_fixed_order_t @ %def real_partition_fixed_order_t @ <>= procedure :: init => real_partition_fixed_order_init <>= module subroutine real_partition_fixed_order_init & (partition, scale, reg_data) class(real_partition_fixed_order_t), intent(out) :: partition real(default), intent(in) :: scale type(region_data_t), intent(in) :: reg_data end subroutine real_partition_fixed_order_init <>= module subroutine real_partition_fixed_order_init (partition, scale, reg_data) class(real_partition_fixed_order_t), intent(out) :: partition real(default), intent(in) :: scale type(region_data_t), intent(in) :: reg_data end subroutine real_partition_fixed_order_init @ %def real_partition_fixed_order_init @ <>= procedure :: write => real_partition_fixed_order_write <>= module subroutine real_partition_fixed_order_write (partition, unit) class(real_partition_fixed_order_t), intent(in) :: partition integer, intent(in), optional :: unit end subroutine real_partition_fixed_order_write <>= module subroutine real_partition_fixed_order_write (partition, unit) class(real_partition_fixed_order_t), intent(in) :: partition integer, intent(in), optional :: unit end subroutine real_partition_fixed_order_write @ %def real_partition_fixed_order_write @ Implements the suppression factor \begin{equation} F(\Phi_{n+1}) = 1 - \prod_{(i,j) \in P_{FKS}} \theta \left[ m_i + m_j + h - \sqrt{(p_j + p_j)^2} \right] \end{equation} to split the real matrix element into singular and finite part. <>= procedure :: get_f => real_partition_fixed_order_get_f <>= module function real_partition_fixed_order_get_f (partition, p) result (f) real(default) :: f class(real_partition_fixed_order_t), intent(in) :: partition type(vector4_t), intent(in), dimension(:) :: p end function real_partition_fixed_order_get_f <>= module function real_partition_fixed_order_get_f (partition, p) result (f) real(default) :: f class(real_partition_fixed_order_t), intent(in) :: partition type(vector4_t), intent(in), dimension(:) :: p integer :: i, em f = zero PAIRS: do i = 1, size (partition%fks_pairs) associate (ii => partition%fks_pairs(i)%ireg) if (ii(1) == 0) then IS: do em = 1, 2 if ((p(em) + p(ii(2)))**1 < p(em)**1 + p(ii(2))**1 + & partition%scale) then f = one exit PAIRS end if end do IS else if ((p(ii(1)) + p(ii(2)))**1 < p(ii(1))**1 + p(ii(2))**1 + & partition%scale) then f = one exit PAIRS end if end if end associate end do PAIRS end function real_partition_fixed_order_get_f @ %def real_partition_fixed_order_get_f @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[real_subtraction_ut.f90]]>>= <> module real_subtraction_ut use unit_tests use real_subtraction_uti <> <> contains <> end module real_subtraction_ut @ %def real_subtraction_ut @ <<[[real_subtraction_uti.f90]]>>= <> module real_subtraction_uti <> use physics_defs use lorentz use numeric_utils use real_subtraction <> <> contains <> end module real_subtraction_uti @ %def real_subtraction_ut @ API: driver for the unit tests below. <>= public :: real_subtraction_test <>= subroutine real_subtraction_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine real_subtraction_test @ %def real_subtraction_test @ Test the final-state collinear subtraction. <>= call test (real_subtraction_1, "real_subtraction_1", & "final-state collinear subtraction", & u, results) <>= public :: real_subtraction_1 <>= subroutine real_subtraction_1 (u) integer, intent(in) :: u type(coll_subtraction_t) :: coll_sub real(default) :: sqme_coll type(vector4_t) :: p_res type(vector4_t), dimension(5) :: p_born real(default), dimension(4) :: k_perp real(default), dimension(4,4) :: b_munu integer :: mu, nu real(default) :: born, born_c integer, dimension(6) :: flst p_born(1)%p = [500, 0, 0, 500] p_born(2)%p = [500, 0, 0, -500] p_born(3)%p = [3.7755E+02, 2.2716E+02, -95.4172, 2.8608E+02] p_born(4)%p = [4.9529E+02, -2.739E+02, 84.8535, -4.0385E+02] p_born(5)%p = [1.2715E+02, 46.7375, 10.5637, 1.1778E+02] p_res = p_born(1) + p_born(2) flst = [11, -11 , -2, 2, -2, 2] b_munu(1, :) = [0., 0., 0., 0.] b_munu(2, :) = [0., 1., 1., 1.] b_munu(3, :) = [0., 1., 1., 1.] b_munu(4, :) = [0., 1., 1., 1.] k_perp = real_subtraction_compute_k_perp_fsr (p = p_born(5), phi = 0.5_default) born = - b_munu(1, 1) + b_munu(2, 2) + b_munu(3, 3) + b_munu(4, 4) born_c = 0. do mu = 1, 4 do nu = 1, 4 born_c = born_c + k_perp(mu) * k_perp(nu) * b_munu(mu, nu) end do end do write (u, "(A)") "* Test output: real_subtraction_1" write (u, "(A)") "* Purpose: final-state collinear subtraction" write (u, "(A)") write (u, "(A, L1)") "* vanishing scalar-product of 3-momenta k_perp and p_born(emitter): ", & nearly_equal (dot_product (p_born(5)%p(1:3), k_perp(2:4)), 0._default) call coll_sub%init (n_alr = 1, n_in = 2) call coll_sub%set_parameters (CA, CF, TR) write (u, "(A)") write (u, "(A)") "* g -> qq splitting" write (u, "(A)") sqme_coll = coll_sub%compute_fsr(5, flst, p_res, p_born, & born, born_c, 0.5_default, 0.25_default, .false.) write (u, "(A,F15.12)") "ME: ", sqme_coll write (u, "(A)") write (u, "(A)") "* g -> gg splitting" write (u, "(A)") b_munu(1, :) = [0., 0., 0., 0.] b_munu(2, :) = [0., 0., 0., 1.] b_munu(3, :) = [0., 0., 1., 1.] b_munu(4, :) = [0., 0., 1., 1.] k_perp = real_subtraction_compute_k_perp_fsr (p = p_born(5), phi = 0.5_default) born = - b_munu(1, 1) + b_munu(2, 2) + b_munu(3, 3) + b_munu(4, 4) born_c = 0. do mu = 1, 4 do nu = 1, 4 born_c = born_c + k_perp(mu) * k_perp(nu) * b_munu(mu, nu) end do end do flst = [11, -11, 2, -2, 21, 21] sqme_coll = coll_sub%compute_fsr(5, flst, p_res, p_born, & born, born_c, 0.5_default, 0.25_default, .true.) write (u, "(A,F15.12)") "ME: ", sqme_coll write (u, "(A)") write (u, "(A)") "* Test output end: real_subtraction_1" write (u, "(A)") end subroutine real_subtraction_1 @ %def real_subtraction_1 @ \clearpage %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Contribution of divergencies due to PDF Evolution} References: \begin{itemize} \item arXiv:hep-ph/9512328, (2.1)-(2.5), (4.29)-(4.53) \item arXiv:0709.2092, (2.102)-(2.106) \end{itemize} The parton distrubition densities have to be evaluated at NLO, too. The NLO PDF evolution is given by \begin{equation} \label{eqn:pdf_nlo} f (\bar{x}) = \int_0^1 \int_0^1 dx dz f(x) \Gamma(z) \delta (\bar{x} - x z), \end{equation} where $\Gamma$ are the DGLAP evolution kernels for an $a \to d$ splitting, \begin{equation} \label{eqn:dglap} \Gamma_a^{(d)} = \delta_{ad}\delta(1-x) - \frac{\alpha_s}{2\pi} \left(\frac{1}{\epsilon} P_{ad}(x,0) - K_{ad}(x)\right) + \mathcal{O}(\alpha_s^2). \end{equation} $K_{ad}$ is a renormalization scheme matching factor, which is exactly zero in $\overline{\text{MS}}$. Let the leading-order hadronic cross section be given by \begin{equation} \label{eqn:xsec_hadro_lo} d\sigma^{(0)}(s) = \int dx_\oplus dx_\ominus f_\oplus (x_\oplus) f_\ominus (x_\ominus) d\tilde{\sigma}^{(0)} (x_\oplus x_\ominus s), \end{equation} then the NLO hadronic cross section is \begin{equation} \label{eqn:xsec_hadro_nlo} d\sigma^{(1)}(s) = \int dx_\oplus dx_\ominus dz_\oplus dz_\ominus f_\oplus (x_\oplus) f_\ominus (x_\ominus) \underbrace{\Gamma_\oplus (z_\oplus) \Gamma_\ominus (z_\ominus) d\tilde{\sigma}^{(1)} (z_\oplus z_\ominus s)}_{d\hat{\sigma}^{(1)}}. \end{equation} $d\hat{\sigma}$ is called the subtracted partonic cross section. Expanding in $\alpha_s$ we find \begin{align} d\hat{\sigma}^{(0)}_{ab}(k_1, k_2) &= d\tilde{\sigma}_{ab}^{(0)} (k_1, k_2), \\ d\hat{\sigma}^{(1)}_{ab}(k_1, k_2) &= d\tilde{\sigma}_{ab}^{(1)} (k_1, k_2) \\ &+ \frac{\alpha_s}{2\pi} \sum_d \int dx \left (\frac{1}{\epsilon} P_{da}(x,0) - K_{da}(x)\right) d\tilde{\sigma}_{db}^{(0)}(xk_1, k_2)\\ &+ \frac{\alpha_s}{2\pi} \sum_d \int \left (\frac{1}{\epsilon} P_{db} (x, 0) - K_{db}(x)\right) d\tilde{\sigma}_{ad}^{(0)}(k_1, xk_2).\\ &= d\tilde{\sigma}_{ab}^{(1)} + d\tilde{\sigma}_{ab}^{(cnt,+)} + d\tilde{\sigma}_{ab}^{(cnt,-)} \end{align} Let us now turn to the soft-subtracted real part of the cross section. For ease of notation, it is constrained to one singular region, \begin{align*} \label{eqn:R-in} d\sigma^{(in)}_\alpha &= \left[\left(\frac{1}{\xi}\right)_{c} - 2\epsilon\left(\frac{\log \xi}{\xi}\right)_{c}\right] (1-y^2)\xi^2 \mathcal{R}_\alpha \mathcal{S}_\alpha \\ &\times \frac{1}{2(2\pi)^{3-2\epsilon}} \left(\frac{\sqrt{s}}{2}\right)^{2-2\epsilon} \left( 1 - y^2\right)^{-1-\epsilon} d\phi d\xi dy d\Omega^{2-2\epsilon}, \end{align*} where we regularize collinear divergencies using the identity \begin{equation*} \left (1 - y^2 \right)^{-1-\epsilon} = -\frac{2^{-\epsilon}}{2\epsilon} \left (\delta(1-y) + \delta(1+y)\right) + \underbrace{\frac{1}{2} \left[ \left (\frac {1}{1-y}\right)_{c} + \left (\frac{1}{1+y}\right)_{c} \right]}_{\mathcal{P}(y)}. \end{equation*} This enables us to split the cross section into a finite and a singular part. The latter can further be separated into a contribution of the incoming and of the outgoing particles, \begin{equation*} d\sigma^{(in)}_\alpha = d\sigma^{(in,+)}_\alpha + d\sigma^{(in,-)}_\alpha + d\sigma^{(in,f)}_\alpha. \end{equation*} They are given by \begin{align} d\sigma^{(in,f)}_\alpha = & \mathcal{P}(y) \left[\left(\frac{1}{\xi}\right)_{c} - 2\epsilon \left(\frac{\log\xi}{\xi}\right)_{c}\right] \frac{1}{2(2\pi)^{3-2\epsilon}} \left(\frac{\sqrt{s}}{2}\right)^{2-2\epsilon} \nonumber\\ & \times (1-y^2)\xi^2 \mathcal{R}_\alpha \mathcal{S}_\alpha d\phi d\xi dy d\Omega^{2-2\epsilon} \label{eqn:sigma-f} \end{align} and \begin{align} d\sigma^{(in,\pm)}_\alpha &= -\frac{2^{-\epsilon}}{2\epsilon} \delta (1 \mp y) \left[ \left( \frac{1}{\xi}\right)_{c} - 2\epsilon \left(\frac{\log\xi}{\xi}\right)_{c}\right] \nonumber\\ & \times \frac{1}{2(2\pi)^{3-2\epsilon}} \left( \frac{\sqrt{s}}{2}\right)^{2-2\epsilon} (1-y^2)\xi^2 \mathcal{R}_\alpha \mathcal{S}_\alpha d\phi d\xi dy d\Omega^{2-2\epsilon}. \label{eqn:sigma-pm} \end{align} Equation \ref{eqn:sigma-f} is the contribution to the real cross section which is computed in [[evaluate_region_isr]]. It is regularized both in the soft and collinear limit via the plus distributions. Equation \ref{eqn:sigma-pm} is a different contribution. It is only present exactly in the collinear limit, due to the delta function. The divergences present in this term do not completely cancel out divergences in the virtual matrix element, because the beam axis is distinguished. Thus, the conditions in which the KLN theorem applies are not met. To see this, we carry out the collinear limit, obtaining \begin{equation*} \lim_{y \to 1} (1-y^2)\xi^2\mathcal{R}_\alpha = 8\pi\alpha_s \mu^{2\epsilon} \left(\frac{2}{\sqrt{s}}\right)^2 \xi P^<(1-\xi, \epsilon) \mathcal{R}_\alpha, \end{equation*} with the Altarelli-Parisi splitting kernel for $z < 1$, $P^<(z,\epsilon)$. Moreover, $\lim_{\vec{k} \parallel \vec{k}_1} d\phi = d\phi_3$ violates spatial averaging. The integration over the spherical angle $d\Omega$ can be carried out easily, yielding a factor of $2\pi^{1-\epsilon} / \Gamma(1-\epsilon)$. This allows us to redefine $\epsilon$, \begin{equation} \frac{1}{\epsilon} - \gamma_E + \log(4\pi) \to \frac{1}{\epsilon}. \end{equation} Coming back to $d\tilde{\sigma}_{ab}^{(cnt,+)}$ in order to make a connection to $d{\sigma}^{(in,+)}_\alpha$, we relate $P_{ab}(z,0)$ to $P^<_{ab}(z,0)$ via the equation \begin{equation*} P_{ab}(z,0) = (1-z)P_{ab}^<(z,0)\left(\frac{1}{1-z}\right)_+ + \gamma(a)\delta_{ab}\delta(1-z), \end{equation*} which yields \begin{equation} \label{eqn:sigma-cnt} d\tilde{\sigma}^{(cnt,+)}_{\alpha} = \frac{\alpha_s}{2\pi} \sum_d \left\lbrace -K_{da}(1-\xi) + \frac{1}{\epsilon} \left[\left(\frac{1}{\xi}\right)_+ \xi P_{da}^<(1-\xi,0) + \delta_{da}\delta(\xi)\gamma(d)\right]\right\rbrace \mathcal{R}_\alpha \mathcal{S}_\alpha d\phi d\xi dy. \end{equation} This term has the same pole structure as eqn. \ref{eqn:sigma-pm}. This makes clear that the quantity \begin{equation} d\hat{\sigma}^{(in,+)} = d\tilde{\sigma}^{(in,+)} + d\tilde{\sigma}^{(cnt,+)} \end{equation} has no collinear poles. Therefore, our task is to add up eqns. \ref{eqn:sigma-pm} and \ref{eqn:sigma-cnt} in order to compute the finite remainder. This is the integrand which is evaluated in the [[dglap_remnant]] component. So, we have to perform an expansion of $d\hat{\sigma}^{(in,+)}$ in $\epsilon$. Hereby, we must not neglect the implicit $\epsilon$-dependence of $P^<$, which leads to additional terms involving the first derivative, \begin{equation*} P_{ab}^<(z,\epsilon) = P_{ab}^<(z,0) + \epsilon \frac{\partial P_{ab}^<(z,\epsilon)}{\partial \epsilon}|_{\epsilon = 0} + \mathcal{O}(\alpha_s^2). \end{equation*} This finally gives us the equation for the collinear remnant. Note that there is still one soft $1/\epsilon$-pole, which cancels out with the corresponding expression in the soft-virtual terms. \begin{align} \label{eqn:sigma-in-p-final} d\hat{\sigma}^{(in,+)} &= \frac{\alpha_s}{2\pi} \frac{1}{\epsilon} \gamma(a) \mathcal{R}_\alpha \mathcal{S}_\alpha \nonumber\\ &+ \frac{\alpha_s}{2\pi} \sum_d \left\lbrace (1-z) P_{da}^<(z,0)\left[\left(\frac{1}{1-z}\right)_{c} \log\frac{s\delta_{\mathrm{I}}}{2\mu^2} + 2 \left(\frac{\log(1-z)}{1-z}\right)_{c}\right] \right. \nonumber\\ &\left . -(1-z)\frac{\partial P_{da}^<(z,\epsilon)}{\partial \epsilon} \left(\frac{1}{1-z}\right)_{c} - K_{da}(z)\right\rbrace \mathcal{R}_\alpha \mathcal{S}_\alpha d\phi d\xi dy \end{align} <<[[dglap_remnant.f90]]>>= <> module dglap_remnant <> <> use phs_fks, only: isr_kinematics_t use fks_regions, only: region_data_t use nlo_data <> <> <> interface <> end interface end module dglap_remnant @ %def module dglap_remnant @ <<[[dglap_remnant_sub.f90]]>>= <> submodule (dglap_remnant) dglap_remnant_s use numeric_utils use diagnostics use constants use physics_defs use pdg_arrays implicit none contains <> end submodule dglap_remnant_s @ %def dglap_remnant_s @ <>= public :: dglap_remnant_t <>= type :: dglap_remnant_t type(nlo_settings_t), pointer :: settings => null () type(region_data_t), pointer :: reg_data => null () type(isr_kinematics_t), pointer :: isr_kinematics => null () real(default) :: CA = 0, CF = 0, TR = 0 real(default), dimension(:), allocatable :: sqme_born real(default), dimension(:,:), allocatable :: sf_factors real(default), dimension(:,:,:), allocatable :: sqme_color_c_extra contains <> end type dglap_remnant_t @ %def dglap_remnant_t @ <>= procedure :: init => dglap_remnant_init <>= module subroutine dglap_remnant_init & (dglap, settings, reg_data, isr_kinematics) class(dglap_remnant_t), intent(inout) :: dglap type(nlo_settings_t), intent(in), target :: settings type(region_data_t), intent(in), target :: reg_data type(isr_kinematics_t), intent(in), target :: isr_kinematics end subroutine dglap_remnant_init <>= module subroutine dglap_remnant_init & (dglap, settings, reg_data, isr_kinematics) class(dglap_remnant_t), intent(inout) :: dglap type(nlo_settings_t), intent(in), target :: settings type(region_data_t), intent(in), target :: reg_data integer :: n_flv_born type(isr_kinematics_t), intent(in), target :: isr_kinematics dglap%reg_data => reg_data n_flv_born = reg_data%get_n_flv_born () allocate (dglap%sf_factors (reg_data%n_regions, 0:reg_data%n_in)) dglap%sf_factors = zero dglap%settings => settings allocate (dglap%sqme_born(n_flv_born)) dglap%sqme_born = zero allocate (dglap%sqme_color_c_extra (reg_data%n_legs_born, & reg_data%n_legs_born, reg_data%n_flv_born)) dglap%sqme_color_c_extra = zero dglap%isr_kinematics => isr_kinematics end subroutine dglap_remnant_init @ %def dglap_remnant_init <>= procedure :: set_parameters => dglap_remnant_set_parameters <>= module subroutine dglap_remnant_set_parameters (dglap, CA, CF, TR) class(dglap_remnant_t), intent(inout) :: dglap real(default), intent(in) :: CA, CF, TR end subroutine dglap_remnant_set_parameters <>= module subroutine dglap_remnant_set_parameters (dglap, CA, CF, TR) class(dglap_remnant_t), intent(inout) :: dglap real(default), intent(in) :: CA, CF, TR dglap%CA = CA dglap%CF = CF dglap%TR = TR end subroutine dglap_remnant_set_parameters @ %def dglap_remnant_set_parameters @ Evaluates formula \ref{eqn:sigma-in-p-final}. Note that, as also in the case for the real subtraction, we have to take into account an additional term, occuring because the integral the plus distribution is evaluated over is not constrained on the interval $[0,1]$. Explicitly, this means (see JHEP 06(2010)043, (4.11)-(4.12)) \begin{align} \int_{\bar{x}_\oplus}^1 dz \left( \frac{1}{1-z} \right)_{\xi_{\text{cut}}} & = \log \frac{1-\bar{x}_\oplus}{\xi_{\text{cut}}} f(1) + \int_{\bar{x}_\oplus}^1 \frac{f(z) - f(1)}{1-z}, \\ \int_{\bar{x}_\oplus}^1 dz \left(\frac{\log(1-z)}{1-z}\right)_{\xi_{\text{cut}}} f(z) & = \frac{1}{2}\left( \log^2(1-\bar{x}_\oplus) - \log^2 (\xi_{\text{cut}}) \right)f(1) + \int_{\bar{x}_\oplus}^1 \frac{\log(1-z)[f(z) - f(1)]}{1-z}, \end{align} and the same of course for $\bar{x}_\ominus$. These two terms are stored in the [[plus_dist_remnant]] variable below. The option [[separate_uborns]] allows to compute the contribution of the DGLAP remnant separately for each underlying Born flavor structure. We need this option during event generation to generate counter events with a specific Born flavor structure. <>= procedure :: evaluate => dglap_remnant_evaluate <>= module subroutine dglap_remnant_evaluate & (dglap, alpha_coupling, separate_uborns, sqme_dglap) class(dglap_remnant_t), intent(inout) :: dglap real(default), dimension(2), intent(in) :: alpha_coupling logical, intent(in) :: separate_uborns real(default), intent(inout), dimension(:) :: sqme_dglap end subroutine dglap_remnant_evaluate <>= module subroutine dglap_remnant_evaluate & (dglap, alpha_coupling, separate_uborns, sqme_dglap) class(dglap_remnant_t), intent(inout) :: dglap real(default), dimension(2), intent(in) :: alpha_coupling logical, intent(in) :: separate_uborns real(default), intent(inout), dimension(:) :: sqme_dglap integer :: alr, emitter, i_corr real(default) :: sqme_alr logical, dimension(:,:,:), allocatable :: evaluated real(default) :: sb, fac_scale2 sb = dglap%isr_kinematics%sqrts_born**2 fac_scale2 = dglap%isr_kinematics%fac_scale**2 allocate (evaluated(dglap%reg_data%get_n_flv_born (), & dglap%reg_data%get_n_flv_real (), dglap%reg_data%n_in)) evaluated = .false. do alr = 1, dglap%reg_data%n_regions i_corr = 0 if (dglap%reg_data%regions(alr)%nlo_correction_type == "QCD") then i_corr = 1 else if (dglap%reg_data%regions(alr)%nlo_correction_type == "EW") then i_corr = 2 end if if (allocated (dglap%settings%selected_alr)) then if (.not. any (dglap%settings%selected_alr == alr)) cycle end if sqme_alr = zero emitter = dglap%reg_data%regions(alr)%emitter if (emitter > dglap%reg_data%n_in .or. i_corr == 0) cycle associate (i_flv_born => dglap%reg_data%regions(alr)%uborn_index, & i_flv_real => dglap%reg_data%regions(alr)%real_index) if (emitter == 0) then do emitter = 1, 2 if (evaluated(i_flv_born, i_flv_real, emitter)) cycle call evaluate_alr (alr, emitter, i_flv_born, & i_flv_real, sqme_alr, evaluated) end do else if (emitter > 0) then if (evaluated(i_flv_born, i_flv_real, emitter)) cycle call evaluate_alr (alr, emitter, i_flv_born, & i_flv_real, sqme_alr, evaluated) end if if (separate_uborns) then sqme_dglap(i_flv_born) = sqme_dglap(i_flv_born) & + alpha_coupling (i_corr)/ twopi * sqme_alr else sqme_dglap(1) = sqme_dglap(1) & + alpha_coupling (i_corr) / twopi * sqme_alr end if end associate end do contains <> end subroutine dglap_remnant_evaluate @ %def dglap_remnant_evaluate @ We introduce $\hat{P}(z, \epsilon) = (1 - z) P(z, \epsilon)$ and have \begin{align} \hat{P}_{g\to gg}(z) & = 2C_A \left[z + \frac{(1-z)^2}{z} + z(1-z)^2\right], \\ \hat{P}_{g\to qq}(z) & = C_F (1-z) \frac{1 + (1-z)^2}{z}, \\ \hat{P}_{q\to gq}(z) & = T_F (1 - z - 2z(1-z)^2), \\ \hat{P}_{q\to qg}(z) & = C_F (1 + z^2). \end{align} <>= function p_hat_gtogg (z) real(default) :: p_hat_gtogg <

> p_hat_gtogg = two * dglap%CA * (z + onemz**2 / z + z * onemz**2) end function p_hat_gtogg function p_hat_gtoqq (z) real(default) :: p_hat_gtoqq <

> p_hat_gtoqq = dglap%CF * onemz / z * (one + onemz**2) end function p_hat_gtoqq function p_hat_qtogq (z) real(default) :: p_hat_qtogq <

> p_hat_qtogq = dglap%TR * (onemz - two * z * onemz**2) end function p_hat_qtogq function p_hat_qtoqg (z) real(default) :: p_hat_qtoqg real(default), intent(in) :: z p_hat_qtoqg = dglap%CF * (one + z**2) end function p_hat_qtoqg @ %def p_hat_qtoqg, p_hat_qtogq, p_hat_gtoqq, p_hat_gtogg @ \begin{align} \frac{\partial P_{g\to gg}(z,\epsilon)}{\partial \epsilon}|_{\epsilon = 0} & = 0, \\ \frac{\partial P_{g\to qq}(z,\epsilon)}{\partial \epsilon}|_{\epsilon = 0} & = -C_F z, \\ \frac{\partial P_{q\to gq}(z,\epsilon)}{\partial \epsilon}|_{\epsilon = 0} & = - 2 T_F z (1-z), \\ \frac{\partial P_{q\to qg}(z,\epsilon)}{\partial \epsilon}|_{\epsilon = 0} & = -C_F (1-z).\\ \end{align} <>= function p_derived_gtogg (z) real(default) :: p_derived_gtogg real(default), intent(in) :: z p_derived_gtogg = zero end function p_derived_gtogg function p_derived_gtoqq (z) real(default) :: p_derived_gtoqq real(default), intent(in) :: z p_derived_gtoqq = -dglap%CF * z end function p_derived_gtoqq function p_derived_qtogq (z) real(default) :: p_derived_qtogq <

> p_derived_qtogq = -two * dglap%TR * z * onemz end function p_derived_qtogq function p_derived_qtoqg (z) real(default) :: p_derived_qtoqg <

> p_derived_qtoqg = -dglap%CF * onemz end function p_derived_qtoqg @ %def p_derived_gtogg, p_derived_gtoqq, p_derived_qtogq, p_derived_qtoqg @ <>= subroutine evaluate_alr (alr, emitter, i_flv_born, i_flv_real, sqme_alr, evaluated) integer, intent(in) :: alr, emitter, i_flv_born, i_flv_real real(default), intent(inout) :: sqme_alr logical, intent(inout), dimension(:,:,:) :: evaluated real(default) :: z, jac real(default) :: factor, factor_soft, plus_dist_remnant real(default) :: xb, onemz real(default) :: sqme_scaled, sqme_born_dglap real(default) :: charge_rad2, charge_em2 integer :: flv_em, flv_rad, N_col, i N_col = 1 sqme_born_dglap = zero associate (template => dglap%settings%fks_template) z = dglap%isr_kinematics%z(emitter) flv_rad = dglap%reg_data%regions(alr)%flst_real%flst(dglap%reg_data%n_legs_real) flv_em = dglap%reg_data%regions(alr)%flst_real%flst(emitter) charge_rad2 = dglap%reg_data%regions(alr)%flst_real%charge(dglap%reg_data%n_legs_real)**2 charge_em2 = dglap%reg_data%regions(alr)%flst_real%charge(emitter)**2 if (dglap%reg_data%regions(alr)%nlo_correction_type == "QCD") then call dglap%set_parameters (CA = CA, CF = CF, TR = TR) else if (dglap%reg_data%regions(alr)%nlo_correction_type == "EW") then if (is_quark(flv_rad)) N_col = NC call dglap%set_parameters (CA = zero, CF = charge_em2, TR = N_col*charge_rad2) end if jac = dglap%isr_kinematics%jacobian(emitter) onemz = one - z factor = log (sb * template%delta_i / two / z / fac_scale2) / & onemz + two * log (onemz) / onemz factor_soft = log (sb * template%delta_i / two / fac_scale2) / & onemz + two * log (onemz) / onemz xb = dglap%isr_kinematics%x(emitter) plus_dist_remnant = log ((one - xb) / template%xi_cut) * log (sb * template%delta_i / & two / fac_scale2) + (log (one - xb)**2 - log (template%xi_cut)**2) end associate if (dglap%reg_data%nlo_correction_type == "EW" .and. & dglap%reg_data%regions(alr)%nlo_correction_type == "QCD" .and. & qcd_ew_interferences (dglap%reg_data%regions(alr)%flst_uborn%flst)) then do i = 1, size (dglap%reg_data%regions(alr)%flst_uborn%flst) if (is_quark (dglap%reg_data%regions(alr)%flst_uborn%flst (i))) then sqme_born_dglap = -dglap%sqme_color_c_extra (i, i, i_flv_born)/CF exit end if end do else sqme_born_dglap = dglap%sqme_born(i_flv_born) end if sqme_scaled = sqme_born_dglap * dglap%sf_factors(alr, emitter) if (is_massless_vector (flv_em) .and. is_massless_vector (flv_rad)) then sqme_alr = sqme_alr + p_hat_gtogg(z) * factor / z * sqme_scaled * jac & - p_hat_gtogg(one) * factor_soft * sqme_born_dglap * jac & + p_hat_gtogg(one) * plus_dist_remnant * sqme_born_dglap else if (is_fermion (flv_em) .and. is_massless_vector (flv_rad)) then sqme_alr = sqme_alr + p_hat_qtoqg(z) * factor / z * sqme_scaled * jac & - p_derived_qtoqg(z) / z * sqme_scaled * jac & - p_hat_qtoqg(one) * factor_soft * sqme_born_dglap * jac & + p_hat_qtoqg(one) * plus_dist_remnant * sqme_born_dglap else if (is_fermion (flv_em) .and. is_fermion (flv_rad)) then sqme_alr = sqme_alr + (p_hat_gtoqq(z) * factor - p_derived_gtoqq(z)) / z * jac * & sqme_scaled else if (is_massless_vector (flv_em) .and. is_fermion (flv_rad)) then sqme_alr = sqme_alr + (p_hat_qtogq(z) * factor - p_derived_qtogq(z)) / z * sqme_scaled * jac else sqme_alr = sqme_alr + zero end if evaluated(i_flv_born, i_flv_real, emitter) = .true. end subroutine evaluate_alr @ %dglap_remnant_evaluate_alr @ <

>= real(default), intent(in) :: z real(default) :: onemz onemz = one - z @ %def variables @ <>= procedure :: final => dglap_remnant_final <>= module subroutine dglap_remnant_final (dglap) class(dglap_remnant_t), intent(inout) :: dglap end subroutine dglap_remnant_final <>= module subroutine dglap_remnant_final (dglap) class(dglap_remnant_t), intent(inout) :: dglap if (associated (dglap%isr_kinematics)) nullify (dglap%isr_kinematics) if (associated (dglap%reg_data)) nullify (dglap%reg_data) if (associated (dglap%settings)) nullify (dglap%settings) if (allocated (dglap%sqme_born)) deallocate (dglap%sqme_born) if (allocated (dglap%sf_factors)) deallocate (dglap%sf_factors) end subroutine dglap_remnant_final @ %def dglap_remnant_final @ \section{Dispatch} @ <<[[dispatch_fks.f90]]>>= <> module dispatch_fks <> <> use variables, only: var_list_t use nlo_data, only: fks_template_t, FKS_DEFAULT, FKS_RESONANCES <> <> interface <> end interface end module dispatch_fks @ %def dispatch_fks @ <<[[dispatch_fks_sub.f90]]>>= <> submodule (dispatch_fks) dispatch_fks_s use string_utils, only: split_string implicit none contains <> end submodule dispatch_fks_s @ %def dispatch_fks_s @ Initialize parameters used to optimize FKS calculations. <>= public :: dispatch_fks_setup <>= module subroutine dispatch_fks_setup (fks_template, var_list) type(fks_template_t), intent(inout) :: fks_template type(var_list_t), intent(in) :: var_list end subroutine dispatch_fks_setup <>= module subroutine dispatch_fks_setup (fks_template, var_list) type(fks_template_t), intent(inout) :: fks_template type(var_list_t), intent(in) :: var_list real(default) :: fks_dij_exp1, fks_dij_exp2 type(string_t) :: fks_mapping_type logical :: subtraction_disabled type(string_t) :: exclude_from_resonance fks_dij_exp1 = & var_list%get_rval (var_str ("fks_dij_exp1")) fks_dij_exp2 = & var_list%get_rval (var_str ("fks_dij_exp2")) fks_mapping_type = & var_list%get_sval (var_str ("$fks_mapping_type")) subtraction_disabled = & var_list%get_lval (var_str ("?disable_subtraction")) exclude_from_resonance = & var_list%get_sval (var_str ("$resonances_exclude_particles")) if (exclude_from_resonance /= var_str ("default")) & call split_string (exclude_from_resonance, var_str (":"), & fks_template%excluded_resonances) call fks_template%set_parameters ( & exp1 = fks_dij_exp1, exp2 = fks_dij_exp2, & xi_min = var_list%get_rval (var_str ("fks_xi_min")), & y_max = var_list%get_rval (var_str ("fks_y_max")), & xi_cut = var_list%get_rval (var_str ("fks_xi_cut")), & delta_o = var_list%get_rval (var_str ("fks_delta_o")), & delta_i = var_list%get_rval (var_str ("fks_delta_i"))) select case (char (fks_mapping_type)) case ("default") call fks_template%set_mapping_type (FKS_DEFAULT) case ("resonances") call fks_template%set_mapping_type (FKS_RESONANCES) end select fks_template%subtraction_disabled = subtraction_disabled fks_template%n_f = var_list%get_ival (var_str ("alphas_nf")) end subroutine dispatch_fks_setup @ %def dispatch_fks_setup @ Index: trunk/src/types/types.nw =================================================================== --- trunk/src/types/types.nw (revision 8817) +++ trunk/src/types/types.nw (revision 8818) @@ -1,9213 +1,9251 @@ %% -*- ess-noweb-default-code-mode: f90-mode; noweb-default-code-mode: f90-mode; -*- % WHIZARD code as NOWEB source: common types and objects %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \chapter{Sindarin Built-In Types} \includemodulegraph{types} Here, we define a couple of types and objects which are useful both internally for \whizard, and visible to the user, so they correspond to Sindarin types. \begin{description} \item[particle\_specifiers] Expressions for particles and particle alternatives, involving particle names. \item[pdg\_arrays] Integer (PDG) codes for particles. Useful for particle aliases (e.g., 'quark' for $u,d,s$ etc.). \item[jets] Define (pseudo)jets as objects. Functional only if the [[fastjet]] library is linked. (This may change in the future.) \item[subevents] Particle collections built from event records, for use in analysis and other Sindarin expressions \item[analysis] Observables, histograms, and plots. \end{description} %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Particle Specifiers} In this module we introduce a type for specifying a particle or particle alternative. In addition to the particle specifiers (strings separated by colons), the type contains an optional flag [[polarized]] and a string [[decay]]. If the [[polarized]] flag is set, particle polarization information should be kept when generating events for this process. If the [[decay]] string is set, it is the ID of a decay process which should be applied to this particle when generating events. In input/output form, the [[polarized]] flag is indicated by an asterisk [[(*)]] in brackets, and the [[decay]] is indicated by its ID in brackets. The [[read]] and [[write]] procedures in this module are not type-bound but generic procedures which handle scalar and array arguments. <<[[particle_specifiers.f90]]>>= <> module particle_specifiers <> <> <> <> <> interface <> end interface contains <> end module particle_specifiers @ %def particle_specifiers @ <<[[particle_specifiers_sub.f90]]>>= <> submodule (particle_specifiers) particle_specifiers_s use io_units use diagnostics implicit none contains <> end submodule particle_specifiers_s @ %def particle_specifiers_s @ \subsection{Base type} This is an abstract type which can hold a single particle or an expression. <>= type, abstract :: prt_spec_expr_t contains <> end type prt_spec_expr_t @ %def prt_expr_t @ Output, as a string. <>= procedure (prt_spec_expr_to_string), deferred :: to_string <>= abstract interface function prt_spec_expr_to_string (object) result (string) import class(prt_spec_expr_t), intent(in) :: object type(string_t) :: string end function prt_spec_expr_to_string end interface @ %def prt_spec_expr_to_string @ Call an [[expand]] method for all enclosed subexpressions (before handling the current expression). <>= procedure (prt_spec_expr_expand_sub), deferred :: expand_sub <>= abstract interface subroutine prt_spec_expr_expand_sub (object) import class(prt_spec_expr_t), intent(inout) :: object end subroutine prt_spec_expr_expand_sub end interface @ %def prt_spec_expr_expand_sub @ \subsection{Wrapper type} This wrapper can hold a particle expression of any kind. We need it so we can make variadic arrays. <>= public :: prt_expr_t <>= type :: prt_expr_t class(prt_spec_expr_t), allocatable :: x contains <> end type prt_expr_t @ %def prt_expr_t @ Output as a string: delegate. <>= procedure :: to_string => prt_expr_to_string <>= recursive module function prt_expr_to_string (object) result (string) class(prt_expr_t), intent(in) :: object type(string_t) :: string end function prt_expr_to_string <>= recursive module function prt_expr_to_string (object) result (string) class(prt_expr_t), intent(in) :: object type(string_t) :: string if (allocated (object%x)) then string = object%x%to_string () else string = "" end if end function prt_expr_to_string @ %def prt_expr_to_string @ Allocate the expression as a particle specifier and copy the value. Due to compiler bugs in gfortran 7-9 not in submodule. <>= procedure :: init_spec => prt_expr_init_spec <>= subroutine prt_expr_init_spec (object, spec) class(prt_expr_t), intent(out) :: object type(prt_spec_t), intent(in) :: spec allocate (prt_spec_t :: object%x) select type (x => object%x) type is (prt_spec_t) x = spec end select end subroutine prt_expr_init_spec @ %def prt_expr_init_spec @ Allocate as a list/sum and allocate for a given length Due to compiler bugs in gfortran 7-9 not in submodule. <>= procedure :: init_list => prt_expr_init_list procedure :: init_sum => prt_expr_init_sum <>= subroutine prt_expr_init_list (object, n) class(prt_expr_t), intent(out) :: object integer, intent(in) :: n allocate (prt_spec_list_t :: object%x) select type (x => object%x) type is (prt_spec_list_t) allocate (x%expr (n)) end select end subroutine prt_expr_init_list subroutine prt_expr_init_sum (object, n) class(prt_expr_t), intent(out) :: object integer, intent(in) :: n allocate (prt_spec_sum_t :: object%x) select type (x => object%x) type is (prt_spec_sum_t) allocate (x%expr (n)) end select end subroutine prt_expr_init_sum @ %def prt_expr_init_list @ %def prt_expr_init_sum @ Return the number of terms. This is unity, except if the expression is a sum. <>= procedure :: get_n_terms => prt_expr_get_n_terms <>= module function prt_expr_get_n_terms (object) result (n) class(prt_expr_t), intent(in) :: object integer :: n end function prt_expr_get_n_terms <>= module function prt_expr_get_n_terms (object) result (n) class(prt_expr_t), intent(in) :: object integer :: n if (allocated (object%x)) then select type (x => object%x) type is (prt_spec_sum_t) n = size (x%expr) class default n = 1 end select else n = 0 end if end function prt_expr_get_n_terms @ %def prt_expr_get_n_terms @ Transform one of the terms, as returned by the previous method, to an array of particle specifiers. The array has more than one entry if the selected term is a list. This makes sense only if the expression has been completely expanded, so the list contains only atoms. <>= procedure :: term_to_array => prt_expr_term_to_array <>= recursive module subroutine prt_expr_term_to_array (object, array, i) class(prt_expr_t), intent(in) :: object type(prt_spec_t), dimension(:), intent(inout), allocatable :: array integer, intent(in) :: i end subroutine prt_expr_term_to_array <>= recursive module subroutine prt_expr_term_to_array (object, array, i) class(prt_expr_t), intent(in) :: object type(prt_spec_t), dimension(:), intent(inout), allocatable :: array integer, intent(in) :: i integer :: j if (allocated (array)) deallocate (array) select type (x => object%x) type is (prt_spec_t) allocate (array (1)) array(1) = x type is (prt_spec_list_t) allocate (array (size (x%expr))) do j = 1, size (array) select type (y => x%expr(j)%x) type is (prt_spec_t) array(j) = y end select end do type is (prt_spec_sum_t) call x%expr(i)%term_to_array (array, 1) end select end subroutine prt_expr_term_to_array @ %def prt_expr_term_to_array @ \subsection{The atomic type} The trivial case is a single particle, including optional decay and polarization attributes. \subsubsection{Definition} The particle is unstable if the [[decay]] array is allocated. The [[polarized]] flag and decays may not be set simultaneously. <>= public :: prt_spec_t <>= type, extends (prt_spec_expr_t) :: prt_spec_t private type(string_t) :: name logical :: polarized = .false. type(string_t), dimension(:), allocatable :: decay contains <> end type prt_spec_t @ %def prt_spec_t @ \subsubsection{I/O} Output. Old-style subroutines. <>= public :: prt_spec_write <>= interface prt_spec_write module procedure prt_spec_write1 module procedure prt_spec_write2 end interface prt_spec_write <>= module subroutine prt_spec_write1 (object, unit, advance) type(prt_spec_t), intent(in) :: object integer, intent(in), optional :: unit character(len=*), intent(in), optional :: advance end subroutine prt_spec_write1 <>= module subroutine prt_spec_write1 (object, unit, advance) type(prt_spec_t), intent(in) :: object integer, intent(in), optional :: unit character(len=*), intent(in), optional :: advance character(3) :: adv integer :: u u = given_output_unit (unit) adv = "yes"; if (present (advance)) adv = advance write (u, "(A)", advance = adv) char (object%to_string ()) end subroutine prt_spec_write1 @ %def prt_spec_write1 @ Write an array as a list of particle specifiers. <>= module subroutine prt_spec_write2 (prt_spec, unit, advance) type(prt_spec_t), dimension(:), intent(in) :: prt_spec integer, intent(in), optional :: unit character(len=*), intent(in), optional :: advance end subroutine prt_spec_write2 <>= module subroutine prt_spec_write2 (prt_spec, unit, advance) type(prt_spec_t), dimension(:), intent(in) :: prt_spec integer, intent(in), optional :: unit character(len=*), intent(in), optional :: advance character(3) :: adv integer :: u, i u = given_output_unit (unit) adv = "yes"; if (present (advance)) adv = advance do i = 1, size (prt_spec) if (i > 1) write (u, "(A)", advance="no") ", " call prt_spec_write (prt_spec(i), u, advance="no") end do write (u, "(A)", advance = adv) end subroutine prt_spec_write2 @ %def prt_spec_write2 @ Read. Input may be string or array of strings. <>= public :: prt_spec_read <>= interface prt_spec_read module procedure prt_spec_read1 module procedure prt_spec_read2 end interface prt_spec_read @ Read a single particle specifier <>= pure module subroutine prt_spec_read1 (prt_spec, string) type(prt_spec_t), intent(out) :: prt_spec type(string_t), intent(in) :: string end subroutine prt_spec_read1 <>= pure module subroutine prt_spec_read1 (prt_spec, string) type(prt_spec_t), intent(out) :: prt_spec type(string_t), intent(in) :: string type(string_t) :: arg, buffer integer :: b1, b2, c, n, i b1 = scan (string, "(") b2 = scan (string, ")") if (b1 == 0) then prt_spec%name = trim (adjustl (string)) else prt_spec%name = trim (adjustl (extract (string, 1, b1-1))) arg = trim (adjustl (extract (string, b1+1, b2-1))) if (arg == "*") then prt_spec%polarized = .true. else n = 0 buffer = arg do if (verify (buffer, " ") == 0) exit n = n + 1 c = scan (buffer, "+") if (c == 0) exit buffer = extract (buffer, c+1) end do allocate (prt_spec%decay (n)) buffer = arg do i = 1, n c = scan (buffer, "+") if (c == 0) c = len (buffer) + 1 prt_spec%decay(i) = trim (adjustl (extract (buffer, 1, c-1))) buffer = extract (buffer, c+1) end do end if end if end subroutine prt_spec_read1 @ %def prt_spec_read1 @ Read a particle specifier array, given as a single string. The array is allocated to the correct size. <>= pure module subroutine prt_spec_read2 (prt_spec, string) type(prt_spec_t), dimension(:), intent(out), allocatable :: prt_spec type(string_t), intent(in) :: string end subroutine prt_spec_read2 <>= pure module subroutine prt_spec_read2 (prt_spec, string) type(prt_spec_t), dimension(:), intent(out), allocatable :: prt_spec type(string_t), intent(in) :: string type(string_t) :: buffer integer :: c, i, n n = 0 buffer = string do n = n + 1 c = scan (buffer, ",") if (c == 0) exit buffer = extract (buffer, c+1) end do allocate (prt_spec (n)) buffer = string do i = 1, size (prt_spec) c = scan (buffer, ",") if (c == 0) c = len (buffer) + 1 call prt_spec_read (prt_spec(i), & trim (adjustl (extract (buffer, 1, c-1)))) buffer = extract (buffer, c+1) end do end subroutine prt_spec_read2 @ %def prt_spec_read2 @ \subsubsection{Constructor} Initialize a particle specifier. <>= public :: new_prt_spec <>= interface new_prt_spec module procedure new_prt_spec_ module procedure new_prt_spec_polarized module procedure new_prt_spec_unstable end interface new_prt_spec <>= elemental module function new_prt_spec_ (name) result (prt_spec) type(string_t), intent(in) :: name type(prt_spec_t) :: prt_spec end function new_prt_spec_ elemental module function new_prt_spec_polarized (name, polarized) result (prt_spec) type(string_t), intent(in) :: name logical, intent(in) :: polarized type(prt_spec_t) :: prt_spec end function new_prt_spec_polarized pure module function new_prt_spec_unstable (name, decay) result (prt_spec) type(string_t), intent(in) :: name type(string_t), dimension(:), intent(in) :: decay type(prt_spec_t) :: prt_spec end function new_prt_spec_unstable <>= elemental module function new_prt_spec_ (name) result (prt_spec) type(string_t), intent(in) :: name type(prt_spec_t) :: prt_spec prt_spec%name = name end function new_prt_spec_ elemental module function new_prt_spec_polarized (name, polarized) result (prt_spec) type(string_t), intent(in) :: name logical, intent(in) :: polarized type(prt_spec_t) :: prt_spec prt_spec%name = name prt_spec%polarized = polarized end function new_prt_spec_polarized pure module function new_prt_spec_unstable (name, decay) result (prt_spec) type(string_t), intent(in) :: name type(string_t), dimension(:), intent(in) :: decay type(prt_spec_t) :: prt_spec prt_spec%name = name allocate (prt_spec%decay (size (decay))) prt_spec%decay = decay end function new_prt_spec_unstable @ %def new_prt_spec @ \subsubsection{Access Methods} Return the particle name without qualifiers <>= procedure :: get_name => prt_spec_get_name <>= elemental module function prt_spec_get_name (prt_spec) result (name) class(prt_spec_t), intent(in) :: prt_spec type(string_t) :: name end function prt_spec_get_name <>= elemental module function prt_spec_get_name (prt_spec) result (name) class(prt_spec_t), intent(in) :: prt_spec type(string_t) :: name name = prt_spec%name end function prt_spec_get_name @ %def prt_spec_get_name @ Return the name with qualifiers <>= procedure :: to_string => prt_spec_to_string <>= module function prt_spec_to_string (object) result (string) class(prt_spec_t), intent(in) :: object type(string_t) :: string end function prt_spec_to_string <>= module function prt_spec_to_string (object) result (string) class(prt_spec_t), intent(in) :: object type(string_t) :: string integer :: i string = object%name if (allocated (object%decay)) then string = string // "(" do i = 1, size (object%decay) if (i > 1) string = string // " + " string = string // object%decay(i) end do string = string // ")" else if (object%polarized) then string = string // "(*)" end if end function prt_spec_to_string @ %def prt_spec_to_string @ Return the polarization flag <>= procedure :: is_polarized => prt_spec_is_polarized <>= elemental module function prt_spec_is_polarized (prt_spec) result (flag) class(prt_spec_t), intent(in) :: prt_spec logical :: flag end function prt_spec_is_polarized <>= elemental module function prt_spec_is_polarized (prt_spec) result (flag) class(prt_spec_t), intent(in) :: prt_spec logical :: flag flag = prt_spec%polarized end function prt_spec_is_polarized @ %def prt_spec_is_polarized @ The particle is unstable if there is a decay array. <>= procedure :: is_unstable => prt_spec_is_unstable <>= elemental module function prt_spec_is_unstable (prt_spec) result (flag) class(prt_spec_t), intent(in) :: prt_spec logical :: flag end function prt_spec_is_unstable <>= elemental module function prt_spec_is_unstable (prt_spec) result (flag) class(prt_spec_t), intent(in) :: prt_spec logical :: flag flag = allocated (prt_spec%decay) end function prt_spec_is_unstable @ %def prt_spec_is_unstable @ Return the number of decay channels <>= procedure :: get_n_decays => prt_spec_get_n_decays <>= elemental module function prt_spec_get_n_decays (prt_spec) result (n) class(prt_spec_t), intent(in) :: prt_spec integer :: n end function prt_spec_get_n_decays <>= elemental module function prt_spec_get_n_decays (prt_spec) result (n) class(prt_spec_t), intent(in) :: prt_spec integer :: n if (allocated (prt_spec%decay)) then n = size (prt_spec%decay) else n = 0 end if end function prt_spec_get_n_decays @ %def prt_spec_get_n_decays @ Return the decay channels <>= procedure :: get_decays => prt_spec_get_decays <>= module subroutine prt_spec_get_decays (prt_spec, decay) class(prt_spec_t), intent(in) :: prt_spec type(string_t), dimension(:), allocatable, intent(out) :: decay end subroutine prt_spec_get_decays <>= module subroutine prt_spec_get_decays (prt_spec, decay) class(prt_spec_t), intent(in) :: prt_spec type(string_t), dimension(:), allocatable, intent(out) :: decay if (allocated (prt_spec%decay)) then allocate (decay (size (prt_spec%decay))) decay = prt_spec%decay else allocate (decay (0)) end if end subroutine prt_spec_get_decays @ %def prt_spec_get_decays @ \subsubsection{Miscellaneous} There is nothing to expand here: <>= procedure :: expand_sub => prt_spec_expand_sub <>= module subroutine prt_spec_expand_sub (object) class(prt_spec_t), intent(inout) :: object end subroutine prt_spec_expand_sub <>= module subroutine prt_spec_expand_sub (object) class(prt_spec_t), intent(inout) :: object end subroutine prt_spec_expand_sub @ %def prt_spec_expand_sub @ \subsection{List} A list of particle specifiers, indicating, e.g., the final state of a process. <>= public :: prt_spec_list_t <>= type, extends (prt_spec_expr_t) :: prt_spec_list_t type(prt_expr_t), dimension(:), allocatable :: expr contains <> end type prt_spec_list_t @ %def prt_spec_list_t @ Output: Concatenate the components. Insert brackets if the component is also a list. The components of the [[expr]] array, if any, should all be filled. <>= procedure :: to_string => prt_spec_list_to_string <>= recursive module function prt_spec_list_to_string (object) result (string) class(prt_spec_list_t), intent(in) :: object type(string_t) :: string end function prt_spec_list_to_string <>= recursive module function prt_spec_list_to_string (object) result (string) class(prt_spec_list_t), intent(in) :: object type(string_t) :: string integer :: i string = "" if (allocated (object%expr)) then do i = 1, size (object%expr) if (i > 1) string = string // ", " select type (x => object%expr(i)%x) type is (prt_spec_list_t) string = string // "(" // x%to_string () // ")" class default string = string // x%to_string () end select end do end if end function prt_spec_list_to_string @ %def prt_spec_list_to_string @ Flatten: if there is a subexpression which is also a list, include the components as direct members of the current list. <>= procedure :: flatten => prt_spec_list_flatten <>= module subroutine prt_spec_list_flatten (object) class(prt_spec_list_t), intent(inout) :: object end subroutine prt_spec_list_flatten <>= module subroutine prt_spec_list_flatten (object) class(prt_spec_list_t), intent(inout) :: object type(prt_expr_t), dimension(:), allocatable :: tmp_expr integer :: i, n_flat, i_flat n_flat = 0 do i = 1, size (object%expr) select type (y => object%expr(i)%x) type is (prt_spec_list_t) n_flat = n_flat + size (y%expr) class default n_flat = n_flat + 1 end select end do if (n_flat > size (object%expr)) then allocate (tmp_expr (n_flat)) i_flat = 0 do i = 1, size (object%expr) select type (y => object%expr(i)%x) type is (prt_spec_list_t) tmp_expr (i_flat + 1 : i_flat + size (y%expr)) = y%expr i_flat = i_flat + size (y%expr) class default tmp_expr (i_flat + 1) = object%expr(i) i_flat = i_flat + 1 end select end do end if if (allocated (tmp_expr)) & call move_alloc (from = tmp_expr, to = object%expr) end subroutine prt_spec_list_flatten @ %def prt_spec_list_flatten @ Convert a list of sums into a sum of lists. (Subexpressions which are not sums are left untouched.) Due to compiler bug in gfortran 7-9 not in submodule. <>= subroutine distribute_prt_spec_list (object) class(prt_spec_expr_t), intent(inout), allocatable :: object class(prt_spec_expr_t), allocatable :: new_object integer, dimension(:), allocatable :: n, ii integer :: k, n_expr, n_terms, i_term select type (object) type is (prt_spec_list_t) n_expr = size (object%expr) allocate (n (n_expr), source = 1) allocate (ii (n_expr), source = 1) do k = 1, size (object%expr) select type (y => object%expr(k)%x) type is (prt_spec_sum_t) n(k) = size (y%expr) end select end do n_terms = product (n) if (n_terms > 1) then allocate (prt_spec_sum_t :: new_object) select type (new_object) type is (prt_spec_sum_t) allocate (new_object%expr (n_terms)) do i_term = 1, n_terms allocate (prt_spec_list_t :: new_object%expr(i_term)%x) select type (x => new_object%expr(i_term)%x) type is (prt_spec_list_t) allocate (x%expr (n_expr)) do k = 1, n_expr select type (y => object%expr(k)%x) type is (prt_spec_sum_t) x%expr(k) = y%expr(ii(k)) class default x%expr(k) = object%expr(k) end select end do end select INCR_INDEX: do k = n_expr, 1, -1 if (ii(k) < n(k)) then ii(k) = ii(k) + 1 exit INCR_INDEX else ii(k) = 1 end if end do INCR_INDEX end do end select end if end select if (allocated (new_object)) call move_alloc (from = new_object, to = object) end subroutine distribute_prt_spec_list @ %def distribute_prt_spec_list @ Apply [[expand]] to all components of the list. <>= procedure :: expand_sub => prt_spec_list_expand_sub <>= recursive module subroutine prt_spec_list_expand_sub (object) class(prt_spec_list_t), intent(inout) :: object end subroutine prt_spec_list_expand_sub <>= recursive module subroutine prt_spec_list_expand_sub (object) class(prt_spec_list_t), intent(inout) :: object integer :: i if (allocated (object%expr)) then do i = 1, size (object%expr) call object%expr(i)%expand () end do end if end subroutine prt_spec_list_expand_sub @ %def prt_spec_list_expand_sub @ \subsection{Sum} A sum of particle specifiers, indicating, e.g., a sum of final states. <>= public :: prt_spec_sum_t <>= type, extends (prt_spec_expr_t) :: prt_spec_sum_t type(prt_expr_t), dimension(:), allocatable :: expr contains <> end type prt_spec_sum_t @ %def prt_spec_sum_t @ Output: Concatenate the components. Insert brackets if the component is a list or also a sum. The components of the [[expr]] array, if any, should all be filled. <>= procedure :: to_string => prt_spec_sum_to_string <>= recursive module function prt_spec_sum_to_string (object) result (string) class(prt_spec_sum_t), intent(in) :: object type(string_t) :: string end function prt_spec_sum_to_string <>= recursive module function prt_spec_sum_to_string (object) result (string) class(prt_spec_sum_t), intent(in) :: object type(string_t) :: string integer :: i string = "" if (allocated (object%expr)) then do i = 1, size (object%expr) if (i > 1) string = string // " + " select type (x => object%expr(i)%x) type is (prt_spec_list_t) string = string // "(" // x%to_string () // ")" type is (prt_spec_sum_t) string = string // "(" // x%to_string () // ")" class default string = string // x%to_string () end select end do end if end function prt_spec_sum_to_string @ %def prt_spec_sum_to_string @ Flatten: if there is a subexpression which is also a sum, include the components as direct members of the current sum. This is identical to [[prt_spec_list_flatten]] above, except for the type. <>= procedure :: flatten => prt_spec_sum_flatten <>= module subroutine prt_spec_sum_flatten (object) class(prt_spec_sum_t), intent(inout) :: object end subroutine prt_spec_sum_flatten <>= module subroutine prt_spec_sum_flatten (object) class(prt_spec_sum_t), intent(inout) :: object type(prt_expr_t), dimension(:), allocatable :: tmp_expr integer :: i, n_flat, i_flat n_flat = 0 do i = 1, size (object%expr) select type (y => object%expr(i)%x) type is (prt_spec_sum_t) n_flat = n_flat + size (y%expr) class default n_flat = n_flat + 1 end select end do if (n_flat > size (object%expr)) then allocate (tmp_expr (n_flat)) i_flat = 0 do i = 1, size (object%expr) select type (y => object%expr(i)%x) type is (prt_spec_sum_t) tmp_expr (i_flat + 1 : i_flat + size (y%expr)) = y%expr i_flat = i_flat + size (y%expr) class default tmp_expr (i_flat + 1) = object%expr(i) i_flat = i_flat + 1 end select end do end if if (allocated (tmp_expr)) & call move_alloc (from = tmp_expr, to = object%expr) end subroutine prt_spec_sum_flatten @ %def prt_spec_sum_flatten @ Apply [[expand]] to all terms in the sum. <>= procedure :: expand_sub => prt_spec_sum_expand_sub <>= recursive module subroutine prt_spec_sum_expand_sub (object) class(prt_spec_sum_t), intent(inout) :: object end subroutine prt_spec_sum_expand_sub <>= recursive module subroutine prt_spec_sum_expand_sub (object) class(prt_spec_sum_t), intent(inout) :: object integer :: i if (allocated (object%expr)) then do i = 1, size (object%expr) call object%expr(i)%expand () end do end if end subroutine prt_spec_sum_expand_sub @ %def prt_spec_sum_expand_sub @ \subsection{Expression Expansion} The [[expand]] method transforms each particle specifier expression into a sum of lists, according to the rules \begin{align} a, (b, c) &\to a, b, c \\ a + (b + c) &\to a + b + c \\ a, b + c &\to (a, b) + (a, c) \end{align} Note that the precedence of comma and plus are opposite to this expansion, so the parentheses in the final expression are necessary. We assume that subexpressions are filled, i.e., arrays are allocated. Do to compiler bug in gfortran 7-9 not in submodule. <>= procedure :: expand => prt_expr_expand <>= recursive subroutine prt_expr_expand (expr) class(prt_expr_t), intent(inout) :: expr if (allocated (expr%x)) then call distribute_prt_spec_list (expr%x) call expr%x%expand_sub () select type (x => expr%x) type is (prt_spec_list_t) call x%flatten () type is (prt_spec_sum_t) call x%flatten () end select end if end subroutine prt_expr_expand @ %def prt_expr_expand @ \subsection{Unit Tests} Test module, followed by the corresponding implementation module. <<[[particle_specifiers_ut.f90]]>>= <> module particle_specifiers_ut use unit_tests use particle_specifiers_uti <> <> contains <> end module particle_specifiers_ut @ %def particle_specifiers_ut @ <<[[particle_specifiers_uti.f90]]>>= <> module particle_specifiers_uti <> use particle_specifiers <> <> contains <> end module particle_specifiers_uti @ %def particle_specifiers_ut @ API: driver for the unit tests below. <>= public :: particle_specifiers_test <>= subroutine particle_specifiers_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine particle_specifiers_test @ %def particle_specifiers_test @ \subsubsection{Particle specifier array} Define, read and write an array of particle specifiers. <>= call test (particle_specifiers_1, "particle_specifiers_1", & "Handle particle specifiers", & u, results) <>= public :: particle_specifiers_1 <>= subroutine particle_specifiers_1 (u) integer, intent(in) :: u type(prt_spec_t), dimension(:), allocatable :: prt_spec type(string_t), dimension(:), allocatable :: decay type(string_t), dimension(0) :: no_decay integer :: i, j write (u, "(A)") "* Test output: particle_specifiers_1" write (u, "(A)") "* Purpose: Read and write a particle specifier array" write (u, "(A)") allocate (prt_spec (5)) prt_spec = [ & new_prt_spec (var_str ("a")), & new_prt_spec (var_str ("b"), .true.), & new_prt_spec (var_str ("c"), [var_str ("dec1")]), & new_prt_spec (var_str ("d"), [var_str ("dec1"), var_str ("dec2")]), & new_prt_spec (var_str ("e"), no_decay) & ] do i = 1, size (prt_spec) write (u, "(A)") char (prt_spec(i)%to_string ()) end do write (u, "(A)") call prt_spec_read (prt_spec, & var_str (" a, b( *), c( dec1), d (dec1 + dec2 ), e()")) call prt_spec_write (prt_spec, u) do i = 1, size (prt_spec) write (u, "(A)") write (u, "(A,A)") char (prt_spec(i)%get_name ()), ":" write (u, "(A,L1)") "polarized = ", prt_spec(i)%is_polarized () write (u, "(A,L1)") "unstable = ", prt_spec(i)%is_unstable () write (u, "(A,I0)") "n_decays = ", prt_spec(i)%get_n_decays () call prt_spec(i)%get_decays (decay) write (u, "(A)", advance="no") "decays =" do j = 1, size (decay) write (u, "(1x,A)", advance="no") char (decay(j)) end do write (u, "(A)") end do write (u, "(A)") write (u, "(A)") "* Test output end: particle_specifiers_1" end subroutine particle_specifiers_1 @ %def particle_specifiers_1 @ \subsubsection{Particle specifier expressions} Nested expressions (only basic particles, no decay specs). <>= call test (particle_specifiers_2, "particle_specifiers_2", & "Particle specifier expressions", & u, results) <>= public :: particle_specifiers_2 <>= subroutine particle_specifiers_2 (u) integer, intent(in) :: u type(prt_spec_t) :: a, b, c, d, e, f type(prt_expr_t) :: pe1, pe2, pe3 type(prt_expr_t) :: pe4, pe5, pe6, pe7, pe8, pe9 integer :: i type(prt_spec_t), dimension(:), allocatable :: pa write (u, "(A)") "* Test output: particle_specifiers_2" write (u, "(A)") "* Purpose: Create and display particle expressions" write (u, "(A)") write (u, "(A)") "* Basic expressions" write (u, *) a = new_prt_spec (var_str ("a")) b = new_prt_spec (var_str ("b")) c = new_prt_spec (var_str ("c")) d = new_prt_spec (var_str ("d")) e = new_prt_spec (var_str ("e")) f = new_prt_spec (var_str ("f")) call pe1%init_spec (a) write (u, "(A)") char (pe1%to_string ()) call pe2%init_sum (2) select type (x => pe2%x) type is (prt_spec_sum_t) call x%expr(1)%init_spec (a) call x%expr(2)%init_spec (b) end select write (u, "(A)") char (pe2%to_string ()) call pe3%init_list (2) select type (x => pe3%x) type is (prt_spec_list_t) call x%expr(1)%init_spec (a) call x%expr(2)%init_spec (b) end select write (u, "(A)") char (pe3%to_string ()) write (u, *) write (u, "(A)") "* Nested expressions" write (u, *) call pe4%init_list (2) select type (x => pe4%x) type is (prt_spec_list_t) call x%expr(1)%init_sum (2) select type (y => x%expr(1)%x) type is (prt_spec_sum_t) call y%expr(1)%init_spec (a) call y%expr(2)%init_spec (b) end select call x%expr(2)%init_spec (c) end select write (u, "(A)") char (pe4%to_string ()) call pe5%init_list (2) select type (x => pe5%x) type is (prt_spec_list_t) call x%expr(1)%init_list (2) select type (y => x%expr(1)%x) type is (prt_spec_list_t) call y%expr(1)%init_spec (a) call y%expr(2)%init_spec (b) end select call x%expr(2)%init_spec (c) end select write (u, "(A)") char (pe5%to_string ()) call pe6%init_sum (2) select type (x => pe6%x) type is (prt_spec_sum_t) call x%expr(1)%init_spec (a) call x%expr(2)%init_sum (2) select type (y => x%expr(2)%x) type is (prt_spec_sum_t) call y%expr(1)%init_spec (b) call y%expr(2)%init_spec (c) end select end select write (u, "(A)") char (pe6%to_string ()) call pe7%init_list (2) select type (x => pe7%x) type is (prt_spec_list_t) call x%expr(1)%init_sum (2) select type (y => x%expr(1)%x) type is (prt_spec_sum_t) call y%expr(1)%init_spec (a) call y%expr(2)%init_list (2) select type (z => y%expr(2)%x) type is (prt_spec_list_t) call z%expr(1)%init_spec (b) call z%expr(2)%init_spec (c) end select end select call x%expr(2)%init_spec (d) end select write (u, "(A)") char (pe7%to_string ()) call pe8%init_sum (2) select type (x => pe8%x) type is (prt_spec_sum_t) call x%expr(1)%init_list (2) select type (y => x%expr(1)%x) type is (prt_spec_list_t) call y%expr(1)%init_spec (a) call y%expr(2)%init_spec (b) end select call x%expr(2)%init_list (2) select type (y => x%expr(2)%x) type is (prt_spec_list_t) call y%expr(1)%init_spec (c) call y%expr(2)%init_spec (d) end select end select write (u, "(A)") char (pe8%to_string ()) call pe9%init_list (3) select type (x => pe9%x) type is (prt_spec_list_t) call x%expr(1)%init_sum (2) select type (y => x%expr(1)%x) type is (prt_spec_sum_t) call y%expr(1)%init_spec (a) call y%expr(2)%init_spec (b) end select call x%expr(2)%init_spec (c) call x%expr(3)%init_sum (3) select type (y => x%expr(3)%x) type is (prt_spec_sum_t) call y%expr(1)%init_spec (d) call y%expr(2)%init_spec (e) call y%expr(3)%init_spec (f) end select end select write (u, "(A)") char (pe9%to_string ()) write (u, *) write (u, "(A)") "* Expand as sum" write (u, *) call pe1%expand () write (u, "(A)") char (pe1%to_string ()) call pe4%expand () write (u, "(A)") char (pe4%to_string ()) call pe5%expand () write (u, "(A)") char (pe5%to_string ()) call pe6%expand () write (u, "(A)") char (pe6%to_string ()) call pe7%expand () write (u, "(A)") char (pe7%to_string ()) call pe8%expand () write (u, "(A)") char (pe8%to_string ()) call pe9%expand () write (u, "(A)") char (pe9%to_string ()) write (u, *) write (u, "(A)") "* Transform to arrays:" write (u, "(A)") "* Atomic specifier" do i = 1, pe1%get_n_terms () call pe1%term_to_array (pa, i) call prt_spec_write (pa, u) end do write (u, *) write (u, "(A)") "* List" do i = 1, pe5%get_n_terms () call pe5%term_to_array (pa, i) call prt_spec_write (pa, u) end do write (u, *) write (u, "(A)") "* Sum of atoms" do i = 1, pe6%get_n_terms () call pe6%term_to_array (pa, i) call prt_spec_write (pa, u) end do write (u, *) write (u, "(A)") "* Sum of lists" do i = 1, pe9%get_n_terms () call pe9%term_to_array (pa, i) call prt_spec_write (pa, u) end do write (u, "(A)") write (u, "(A)") "* Test output end: particle_specifiers_2" end subroutine particle_specifiers_2 @ %def particle_specifiers_2 @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{PDG arrays} For defining aliases, we introduce a special type which holds a set of (integer) PDG codes. <<[[pdg_arrays.f90]]>>= <> module pdg_arrays <> <> <> <> interface <> end interface end module pdg_arrays @ %def pdg_arrays @ <<[[pdg_arrays_sub.f90]]>>= <> submodule (pdg_arrays) pdg_arrays_s use io_units use sorting use physics_defs implicit none contains <> end submodule pdg_arrays_s @ %def pdg_arrays_s @ \subsection{Type definition} Using an allocatable array eliminates the need for initializer and/or finalizer. <>= public :: pdg_array_t <>= type :: pdg_array_t private integer, dimension(:), allocatable :: pdg contains <> end type pdg_array_t @ %def pdg_array_t @ Output. <>= procedure :: write => pdg_array_write <>= module subroutine pdg_array_write (aval, unit) class(pdg_array_t), intent(in) :: aval integer, intent(in), optional :: unit end subroutine pdg_array_write <>= module subroutine pdg_array_write (aval, unit) class(pdg_array_t), intent(in) :: aval integer, intent(in), optional :: unit integer :: u, i u = given_output_unit (unit); if (u < 0) return write (u, "(A)", advance="no") "PDG(" if (allocated (aval%pdg)) then do i = 1, size (aval%pdg) if (i > 1) write (u, "(A)", advance="no") ", " write (u, "(I0)", advance="no") aval%pdg(i) end do end if write (u, "(A)", advance="no") ")" end subroutine pdg_array_write @ %def pdg_array_write @ <>= public :: pdg_array_write_set <>= module subroutine pdg_array_write_set (aval, unit) type(pdg_array_t), intent(in), dimension(:) :: aval integer, intent(in), optional :: unit end subroutine pdg_array_write_set <>= module subroutine pdg_array_write_set (aval, unit) type(pdg_array_t), intent(in), dimension(:) :: aval integer, intent(in), optional :: unit integer :: i do i = 1, size (aval) call aval(i)%write (unit) print *, '' end do end subroutine pdg_array_write_set @ %def pdg_array_write_set @ \subsection{Basic operations} Assignment. We define assignment from and to an integer array. Note that the integer array, if it is the l.h.s., must be declared allocatable by the caller. <>= public :: assignment(=) <>= interface assignment(=) module procedure pdg_array_from_int_array module procedure pdg_array_from_int module procedure int_array_from_pdg_array end interface <>= module subroutine pdg_array_from_int_array (aval, iarray) type(pdg_array_t), intent(out) :: aval integer, dimension(:), intent(in) :: iarray end subroutine pdg_array_from_int_array elemental module subroutine pdg_array_from_int (aval, int) type(pdg_array_t), intent(out) :: aval integer, intent(in) :: int end subroutine pdg_array_from_int module subroutine int_array_from_pdg_array (iarray, aval) integer, dimension(:), allocatable, intent(out) :: iarray type(pdg_array_t), intent(in) :: aval end subroutine int_array_from_pdg_array <>= module subroutine pdg_array_from_int_array (aval, iarray) type(pdg_array_t), intent(out) :: aval integer, dimension(:), intent(in) :: iarray allocate (aval%pdg (size (iarray))) aval%pdg = iarray end subroutine pdg_array_from_int_array elemental module subroutine pdg_array_from_int (aval, int) type(pdg_array_t), intent(out) :: aval integer, intent(in) :: int allocate (aval%pdg (1)) aval%pdg = int end subroutine pdg_array_from_int module subroutine int_array_from_pdg_array (iarray, aval) integer, dimension(:), allocatable, intent(out) :: iarray type(pdg_array_t), intent(in) :: aval if (allocated (aval%pdg)) then allocate (iarray (size (aval%pdg))) iarray = aval%pdg else allocate (iarray (0)) end if end subroutine int_array_from_pdg_array @ %def pdg_array_from_int_array pdg_array_from_int int_array_from_pdg_array @ Allocate space for a PDG array <>= procedure :: init => pdg_array_init <>= module subroutine pdg_array_init (aval, n_elements) class(pdg_array_t), intent(inout) :: aval integer, intent(in) :: n_elements end subroutine pdg_array_init <>= module subroutine pdg_array_init (aval, n_elements) class(pdg_array_t), intent(inout) :: aval integer, intent(in) :: n_elements allocate(aval%pdg(n_elements)) end subroutine pdg_array_init @ %def pdg_array_init @ Deallocate a previously allocated pdg array <>= procedure :: delete => pdg_array_delete <>= module subroutine pdg_array_delete (aval) class(pdg_array_t), intent(inout) :: aval end subroutine pdg_array_delete <>= module subroutine pdg_array_delete (aval) class(pdg_array_t), intent(inout) :: aval if (allocated (aval%pdg)) deallocate (aval%pdg) end subroutine pdg_array_delete @ %def pdg_array_delete @ Merge two pdg arrays, i.e. append a particle string to another leaving out doublettes <>= procedure :: merge => pdg_array_merge <>= module subroutine pdg_array_merge (aval1, aval2) class(pdg_array_t), intent(inout) :: aval1 type(pdg_array_t), intent(in) :: aval2 end subroutine pdg_array_merge <>= module subroutine pdg_array_merge (aval1, aval2) class(pdg_array_t), intent(inout) :: aval1 type(pdg_array_t), intent(in) :: aval2 type(pdg_array_t) :: aval if (allocated (aval1%pdg) .and. allocated (aval2%pdg)) then if (.not. any (aval1%pdg == aval2%pdg)) aval = aval1 // aval2 else if (allocated (aval1%pdg)) then aval = aval1 else if (allocated (aval2%pdg)) then aval = aval2 end if call pdg_array_delete (aval1) call pdg_array_from_int_array (aval1, aval%pdg) end subroutine pdg_array_merge @ %def pdg_array_merge @ Length of the array. <>= procedure :: get_length => pdg_array_get_length <>= elemental module function pdg_array_get_length (aval) result (n) class(pdg_array_t), intent(in) :: aval integer :: n end function pdg_array_get_length <>= elemental module function pdg_array_get_length (aval) result (n) class(pdg_array_t), intent(in) :: aval integer :: n if (allocated (aval%pdg)) then n = size (aval%pdg) else n = 0 end if end function pdg_array_get_length @ %def pdg_array_get_length @ Return the element with index i. <>= procedure :: get => pdg_array_get <>= elemental module function pdg_array_get (aval, i) result (pdg) class(pdg_array_t), intent(in) :: aval integer, intent(in), optional :: i integer :: pdg end function pdg_array_get <>= elemental module function pdg_array_get (aval, i) result (pdg) class(pdg_array_t), intent(in) :: aval integer, intent(in), optional :: i integer :: pdg if (present (i)) then pdg = aval%pdg(i) else pdg = aval%pdg(1) end if end function pdg_array_get @ %def pdg_array_get @ Explicitly set the element with index i. <>= procedure :: set => pdg_array_set <>= module subroutine pdg_array_set (aval, i, pdg) class(pdg_array_t), intent(inout) :: aval integer, intent(in) :: i integer, intent(in) :: pdg end subroutine pdg_array_set <>= module subroutine pdg_array_set (aval, i, pdg) class(pdg_array_t), intent(inout) :: aval integer, intent(in) :: i integer, intent(in) :: pdg aval%pdg(i) = pdg end subroutine pdg_array_set @ %def pdg_array_set @ <>= procedure :: add => pdg_array_add <>= module function pdg_array_add (aval, aval_add) result (aval_out) type(pdg_array_t) :: aval_out class(pdg_array_t), intent(in) :: aval type(pdg_array_t), intent(in) :: aval_add end function pdg_array_add <>= module function pdg_array_add (aval, aval_add) result (aval_out) type(pdg_array_t) :: aval_out class(pdg_array_t), intent(in) :: aval type(pdg_array_t), intent(in) :: aval_add integer :: n, n_add, i n = size (aval%pdg) n_add = size (aval_add%pdg) allocate (aval_out%pdg (n + n_add)) aval_out%pdg(1:n) = aval%pdg do i = 1, n_add aval_out%pdg(n+i) = aval_add%pdg(i) end do end function pdg_array_add @ %def pdg_array_add @ Replace element with index [[i]] by a new array of elements. <>= procedure :: replace => pdg_array_replace <>= module function pdg_array_replace (aval, i, pdg_new) result (aval_new) class(pdg_array_t), intent(in) :: aval integer, intent(in) :: i integer, dimension(:), intent(in) :: pdg_new type(pdg_array_t) :: aval_new end function pdg_array_replace <>= module function pdg_array_replace (aval, i, pdg_new) result (aval_new) class(pdg_array_t), intent(in) :: aval integer, intent(in) :: i integer, dimension(:), intent(in) :: pdg_new type(pdg_array_t) :: aval_new integer :: n, l n = size (aval%pdg) l = size (pdg_new) allocate (aval_new%pdg (n + l - 1)) aval_new%pdg(:i-1) = aval%pdg(:i-1) aval_new%pdg(i:i+l-1) = pdg_new aval_new%pdg(i+l:) = aval%pdg(i+1:) end function pdg_array_replace @ %def pdg_array_replace @ Concatenate two PDG arrays <>= public :: operator(//) <>= interface operator(//) module procedure concat_pdg_arrays end interface <>= module function concat_pdg_arrays (aval1, aval2) result (aval) type(pdg_array_t) :: aval type(pdg_array_t), intent(in) :: aval1, aval2 end function concat_pdg_arrays <>= module function concat_pdg_arrays (aval1, aval2) result (aval) type(pdg_array_t) :: aval type(pdg_array_t), intent(in) :: aval1, aval2 integer :: n1, n2 if (allocated (aval1%pdg) .and. allocated (aval2%pdg)) then n1 = size (aval1%pdg) n2 = size (aval2%pdg) allocate (aval%pdg (n1 + n2)) aval%pdg(:n1) = aval1%pdg aval%pdg(n1+1:) = aval2%pdg else if (allocated (aval1%pdg)) then aval = aval1 else if (allocated (aval2%pdg)) then aval = aval2 end if end function concat_pdg_arrays @ %def concat_pdg_arrays @ \subsection{Matching} A PDG array matches a given PDG code if the code is present within the array. If either one is zero (UNDEFINED), the match also succeeds. <>= public :: operator(.match.) <>= interface operator(.match.) module procedure pdg_array_match_integer module procedure pdg_array_match_pdg_array end interface @ %def .match. @ Match a single code against the array. <>= elemental module function pdg_array_match_integer (aval, pdg) result (flag) logical :: flag type(pdg_array_t), intent(in) :: aval integer, intent(in) :: pdg end function pdg_array_match_integer <>= elemental module function pdg_array_match_integer (aval, pdg) result (flag) logical :: flag type(pdg_array_t), intent(in) :: aval integer, intent(in) :: pdg if (allocated (aval%pdg)) then flag = pdg == UNDEFINED & .or. any (aval%pdg == UNDEFINED) & .or. any (aval%pdg == pdg) else flag = .false. end if end function pdg_array_match_integer @ %def pdg_array_match_integer @ Check if the pdg-number corresponds to a quark <>= public :: is_quark <>= elemental module function is_quark (pdg_nr) logical :: is_quark integer, intent(in) :: pdg_nr end function is_quark <>= elemental module function is_quark (pdg_nr) logical :: is_quark integer, intent(in) :: pdg_nr if (abs (pdg_nr) >= 1 .and. abs (pdg_nr) <= 6) then is_quark = .true. else is_quark = .false. end if end function is_quark @ %def is_quark @ Check if pdg-number corresponds to a gluon <>= public :: is_gluon <>= elemental module function is_gluon (pdg_nr) logical :: is_gluon integer, intent(in) :: pdg_nr end function is_gluon <>= elemental module function is_gluon (pdg_nr) logical :: is_gluon integer, intent(in) :: pdg_nr if (pdg_nr == GLUON) then is_gluon = .true. else is_gluon = .false. end if end function is_gluon @ %def is_gluon @ Check if pdg-number corresponds to a photon <>= public :: is_photon <>= elemental module function is_photon (pdg_nr) logical :: is_photon integer, intent(in) :: pdg_nr end function is_photon <>= elemental module function is_photon (pdg_nr) logical :: is_photon integer, intent(in) :: pdg_nr if (pdg_nr == PHOTON) then is_photon = .true. else is_photon = .false. end if end function is_photon @ %def is_photon @ Check if pdg-number corresponds to a colored particle <>= public :: is_colored <>= elemental module function is_colored (pdg_nr) logical :: is_colored integer, intent(in) :: pdg_nr end function is_colored <>= elemental module function is_colored (pdg_nr) logical :: is_colored integer, intent(in) :: pdg_nr is_colored = is_quark (pdg_nr) .or. is_gluon (pdg_nr) end function is_colored @ %def is_colored @ Check if the pdg-number corresponds to a lepton <>= public :: is_lepton <>= elemental module function is_lepton (pdg_nr) logical :: is_lepton integer, intent(in) :: pdg_nr end function is_lepton <>= elemental module function is_lepton (pdg_nr) logical :: is_lepton integer, intent(in) :: pdg_nr if (abs (pdg_nr) >= ELECTRON .and. & abs (pdg_nr) <= TAU_NEUTRINO) then is_lepton = .true. else is_lepton = .false. end if end function is_lepton @ %def is_lepton @ +@ Check if the pdg-number corresponds to a charged lepton +<>= + public :: is_charged_lepton +<>= + elemental module function is_charged_lepton (pdg_nr) + logical :: is_charged_lepton + integer, intent(in) :: pdg_nr + end function is_charged_lepton +<>= + elemental module function is_charged_lepton (pdg_nr) + logical :: is_charged_lepton + integer, intent(in) :: pdg_nr + if (abs (pdg_nr) == ELECTRON .or. & + abs (pdg_nr) == MUON .or. & + abs (pdg_nr) == TAU) then + is_charged_lepton = .true. + else + is_charged_lepton = .false. + end if + end function is_charged_lepton +@ %def is_charged_lepton +@ <>= public :: is_fermion <>= elemental module function is_fermion (pdg_nr) logical :: is_fermion integer, intent(in) :: pdg_nr end function is_fermion <>= elemental module function is_fermion (pdg_nr) logical :: is_fermion integer, intent(in) :: pdg_nr is_fermion = is_lepton(pdg_nr) .or. is_quark(pdg_nr) end function is_fermion @ %def is_fermion @ Check if the pdg-number corresponds to a massless vector boson <>= public :: is_massless_vector <>= elemental module function is_massless_vector (pdg_nr) integer, intent(in) :: pdg_nr logical :: is_massless_vector end function is_massless_vector <>= elemental module function is_massless_vector (pdg_nr) integer, intent(in) :: pdg_nr logical :: is_massless_vector if (pdg_nr == GLUON .or. pdg_nr == PHOTON) then is_massless_vector = .true. else is_massless_vector = .false. end if end function is_massless_vector @ %def is_massless_vector @ Check if pdg-number corresponds to a massive vector boson <>= public :: is_massive_vector <>= elemental module function is_massive_vector (pdg_nr) integer, intent(in) :: pdg_nr logical :: is_massive_vector end function is_massive_vector <>= elemental module function is_massive_vector (pdg_nr) integer, intent(in) :: pdg_nr logical :: is_massive_vector if (abs (pdg_nr) == Z_BOSON .or. abs (pdg_nr) == W_BOSON) then is_massive_vector = .true. else is_massive_vector = .false. end if end function is_massive_vector @ %def is massive_vector @ Check if pdg-number corresponds to a vector boson <>= public :: is_vector <>= elemental module function is_vector (pdg_nr) integer, intent(in) :: pdg_nr logical :: is_vector end function is_vector <>= elemental module function is_vector (pdg_nr) integer, intent(in) :: pdg_nr logical :: is_vector if (is_massless_vector (pdg_nr) .or. is_massive_vector (pdg_nr)) then is_vector = .true. else is_vector = .false. end if end function is_vector @ %def is vector @ Check if particle is elementary. <>= public :: is_elementary <>= elemental module function is_elementary (pdg_nr) integer, intent(in) :: pdg_nr logical :: is_elementary end function is_elementary <>= elemental module function is_elementary (pdg_nr) integer, intent(in) :: pdg_nr logical :: is_elementary if (is_vector (pdg_nr) .or. is_fermion (pdg_nr) .or. pdg_nr == 25) then is_elementary = .true. else is_elementary = .false. end if end function is_elementary @ %def is_elementary @ Check if particle is an EW boson or scalar. <>= public :: is_ew_boson_scalar <>= elemental module function is_ew_boson_scalar (pdg_nr) integer, intent(in) :: pdg_nr logical :: is_ew_boson_scalar end function is_ew_boson_scalar <>= elemental module function is_ew_boson_scalar (pdg_nr) integer, intent(in) :: pdg_nr logical :: is_ew_boson_scalar if (is_photon (pdg_nr) .or. is_massive_vector (pdg_nr) .or. pdg_nr == 25) then is_ew_boson_scalar = .true. else is_ew_boson_scalar = .false. end if end function is_ew_boson_scalar @ %def is_ew_boson_scalar @ Check if particle is strongly interacting <>= procedure :: has_colored_particles => pdg_array_has_colored_particles <>= module function pdg_array_has_colored_particles (pdg) result (colored) class(pdg_array_t), intent(in) :: pdg logical :: colored end function pdg_array_has_colored_particles <>= module function pdg_array_has_colored_particles (pdg) result (colored) class(pdg_array_t), intent(in) :: pdg logical :: colored integer :: i, pdg_nr colored = .false. do i = 1, size (pdg%pdg) pdg_nr = pdg%pdg(i) if (is_quark (pdg_nr) .or. is_gluon (pdg_nr)) then colored = .true. exit end if end do end function pdg_array_has_colored_particles @ %def pdg_array_has_colored_particles This function is a convenience function for the determination of possible compatibility of flavor structures of processes with certain orders of QCD and QED/EW coupling constants. It assumes the Standard Model (SM) as underlying physics model. The function is based on a naive counting of external particles which are connected to the process by the specific kind of couplings depending on the underlying theory (QCD and/or QED/EW) of which the corresponding particle is a part of. It is constructed in a way that the exclusion of coupling power combinations is well-defined. <>= public :: query_coupling_powers <>= module function query_coupling_powers (flv, a_power, as_power) result (valid) integer, intent(in), dimension(:) :: flv integer, intent(in) :: a_power, as_power logical :: valid end function query_coupling_powers <>= module function query_coupling_powers (flv, a_power, as_power) result (valid) integer, intent(in), dimension(:) :: flv integer, dimension(:, :), allocatable :: power_pair_array integer, dimension(2) :: power_pair_ref integer, intent(in) :: a_power, as_power integer :: i, n_legs, n_gluons, n_quarks, n_gamWZH, n_leptons logical, dimension(:), allocatable :: pairs_included logical :: valid integer :: n_bound power_pair_ref = [a_power, as_power] n_legs = size (flv) allocate (power_pair_array (2, n_legs - 1)) do i = 1, n_legs - 1 power_pair_array (1, i) = n_legs - 1 - i power_pair_array (2, i) = i - 1 end do allocate (pairs_included (n_legs - 1)) pairs_included = .true. n_gluons = count (is_gluon (flv)) n_gamWZH = count (is_ew_boson_scalar (flv)) n_quarks = count (is_quark (flv)) n_leptons = count (is_lepton (flv)) if (n_gluons >= 1 .and. n_gluons <= 3) then do i = 1, n_gluons pairs_included (i) = .false. end do else if (n_gluons > 2 .and. n_quarks <= 2 .and. n_gluons + n_quarks == n_legs) then do i = 1, n_legs - 2 pairs_included (i) = .false. end do end if n_bound = 0 if (n_gamWZH + n_leptons == n_legs) then n_bound = n_gamWZH + n_leptons - 2 else if (n_quarks == 2 .and. n_leptons + n_quarks + n_gamWZH == n_legs) then n_bound = n_legs - 2 else if (n_gamWZH + n_leptons > 0) then n_bound = n_leptons/2 + n_gamWZH end if if (n_bound > 0) then do i = 1, n_bound pairs_included (n_legs - i) = .false. end do end if if (n_quarks == 4 .and. .not. qcd_ew_interferences (flv)) then do i = 1, 2 pairs_included (n_legs - i) = .false. end do end if valid = .false. do i = 1, n_legs - 1 if (all (power_pair_array (:, i) == power_pair_ref) .and. pairs_included (i)) then valid = .true. exit end if end do end function query_coupling_powers @ %def query_coupling_powers This functions checks if there is a flavor structure which possibly can induce QCD-EW interference amplitudes. It evaluates to [[true]] if there are at least 2 quark pairs whereby the quarks of at least one quark pair must have the same flavor. <>= public :: qcd_ew_interferences <>= module function qcd_ew_interferences (flv) result (valid) integer, intent(in), dimension(:) :: flv logical :: valid end function qcd_ew_interferences <>= module function qcd_ew_interferences (flv) result (valid) integer, intent(in), dimension(:) :: flv integer :: i, n_pairs logical :: valid, qqbar_pair n_pairs = 0 valid = .false. qqbar_pair = .false. if (count (is_quark (flv)) >= 4) then do i = DOWN_Q, TOP_Q qqbar_pair = count (abs (flv) == i) >= 2 if (qqbar_pair) n_pairs = n_pairs + 1 if (n_pairs > 0) then valid = .true. exit end if end do end if end function qcd_ew_interferences @ %def qcd_ew_interferences +@ Assign equivalent cut expression class to PDG code. +<>= + public :: flv_eqv_expr_class +<>= + module function flv_eqv_expr_class (flv) result (assign_qgA) + integer, intent(in) :: flv + logical, dimension(3) :: assign_qgA + end function flv_eqv_expr_class +<>= + module function flv_eqv_expr_class (flv) result (assign_qgA) + integer, intent(in) :: flv + logical, dimension(3) :: assign_qgA + assign_qgA = [is_quark (flv), is_gluon (flv), is_photon (flv)] + end function flv_eqv_expr_class + +@ %def flv_eqv_expr_class @ Match two arrays. Succeeds if any pair of entries matches. <>= module function pdg_array_match_pdg_array (aval1, aval2) result (flag) logical :: flag type(pdg_array_t), intent(in) :: aval1, aval2 end function pdg_array_match_pdg_array <>= module function pdg_array_match_pdg_array (aval1, aval2) result (flag) logical :: flag type(pdg_array_t), intent(in) :: aval1, aval2 if (allocated (aval1%pdg) .and. allocated (aval2%pdg)) then flag = any (aval1 .match. aval2%pdg) else flag = .false. end if end function pdg_array_match_pdg_array @ %def pdg_array_match_pdg_array @ Comparison. Here, we take the PDG arrays as-is, assuming that they are sorted. The ordering is a bit odd: first, we look only at the absolute values of the PDG codes. If they all match, the particle comes before the antiparticle, scanning from left to right. <>= public :: operator(<) public :: operator(>) public :: operator(<=) public :: operator(>=) public :: operator(==) public :: operator(/=) <>= interface operator(<) module procedure pdg_array_lt end interface interface operator(>) module procedure pdg_array_gt end interface interface operator(<=) module procedure pdg_array_le end interface interface operator(>=) module procedure pdg_array_ge end interface interface operator(==) module procedure pdg_array_eq end interface interface operator(/=) module procedure pdg_array_ne end interface <>= elemental module function pdg_array_lt (aval1, aval2) result (flag) type(pdg_array_t), intent(in) :: aval1, aval2 logical :: flag end function pdg_array_lt elemental module function pdg_array_gt (aval1, aval2) result (flag) type(pdg_array_t), intent(in) :: aval1, aval2 logical :: flag end function pdg_array_gt elemental module function pdg_array_le (aval1, aval2) result (flag) type(pdg_array_t), intent(in) :: aval1, aval2 logical :: flag end function pdg_array_le elemental module function pdg_array_ge (aval1, aval2) result (flag) type(pdg_array_t), intent(in) :: aval1, aval2 logical :: flag end function pdg_array_ge elemental module function pdg_array_eq (aval1, aval2) result (flag) type(pdg_array_t), intent(in) :: aval1, aval2 logical :: flag end function pdg_array_eq elemental module function pdg_array_ne (aval1, aval2) result (flag) type(pdg_array_t), intent(in) :: aval1, aval2 logical :: flag end function pdg_array_ne <>= elemental module function pdg_array_lt (aval1, aval2) result (flag) type(pdg_array_t), intent(in) :: aval1, aval2 logical :: flag integer :: i if (size (aval1%pdg) /= size (aval2%pdg)) then flag = size (aval1%pdg) < size (aval2%pdg) else do i = 1, size (aval1%pdg) if (abs (aval1%pdg(i)) /= abs (aval2%pdg(i))) then flag = abs (aval1%pdg(i)) < abs (aval2%pdg(i)) return end if end do do i = 1, size (aval1%pdg) if (aval1%pdg(i) /= aval2%pdg(i)) then flag = aval1%pdg(i) > aval2%pdg(i) return end if end do flag = .false. end if end function pdg_array_lt elemental module function pdg_array_gt (aval1, aval2) result (flag) type(pdg_array_t), intent(in) :: aval1, aval2 logical :: flag flag = .not. (aval1 < aval2 .or. aval1 == aval2) end function pdg_array_gt elemental module function pdg_array_le (aval1, aval2) result (flag) type(pdg_array_t), intent(in) :: aval1, aval2 logical :: flag flag = aval1 < aval2 .or. aval1 == aval2 end function pdg_array_le elemental module function pdg_array_ge (aval1, aval2) result (flag) type(pdg_array_t), intent(in) :: aval1, aval2 logical :: flag flag = .not. (aval1 < aval2) end function pdg_array_ge elemental module function pdg_array_eq (aval1, aval2) result (flag) type(pdg_array_t), intent(in) :: aval1, aval2 logical :: flag if (size (aval1%pdg) /= size (aval2%pdg)) then flag = .false. else flag = all (aval1%pdg == aval2%pdg) end if end function pdg_array_eq elemental module function pdg_array_ne (aval1, aval2) result (flag) type(pdg_array_t), intent(in) :: aval1, aval2 logical :: flag flag = .not. (aval1 == aval2) end function pdg_array_ne @ Equivalence. Two PDG arrays are equivalent if either one contains [[UNDEFINED]] or if each element of array 1 is present in array 2, and vice versa. <>= public :: operator(.eqv.) public :: operator(.neqv.) <>= interface operator(.eqv.) module procedure pdg_array_equivalent end interface interface operator(.neqv.) module procedure pdg_array_inequivalent end interface <>= elemental module function pdg_array_equivalent (aval1, aval2) result (eq) logical :: eq type(pdg_array_t), intent(in) :: aval1, aval2 end function pdg_array_equivalent elemental module function pdg_array_inequivalent (aval1, aval2) result (neq) logical :: neq type(pdg_array_t), intent(in) :: aval1, aval2 end function pdg_array_inequivalent <>= elemental module function pdg_array_equivalent (aval1, aval2) result (eq) logical :: eq type(pdg_array_t), intent(in) :: aval1, aval2 logical, dimension(:), allocatable :: match1, match2 integer :: i if (allocated (aval1%pdg) .and. allocated (aval2%pdg)) then eq = any (aval1%pdg == UNDEFINED) & .or. any (aval2%pdg == UNDEFINED) if (.not. eq) then allocate (match1 (size (aval1%pdg))) allocate (match2 (size (aval2%pdg))) match1 = .false. match2 = .false. do i = 1, size (aval1%pdg) match2 = match2 .or. aval1%pdg(i) == aval2%pdg end do do i = 1, size (aval2%pdg) match1 = match1 .or. aval2%pdg(i) == aval1%pdg end do eq = all (match1) .and. all (match2) end if else eq = .false. end if end function pdg_array_equivalent elemental module function pdg_array_inequivalent (aval1, aval2) result (neq) logical :: neq type(pdg_array_t), intent(in) :: aval1, aval2 neq = .not. pdg_array_equivalent (aval1, aval2) end function pdg_array_inequivalent @ %def pdg_array_equivalent @ \subsection{Sorting} Sort a PDG array by absolute value, particle before antiparticle. After sorting, we eliminate double entries. <>= public :: sort_abs <>= interface sort_abs module procedure pdg_array_sort_abs end interface <>= procedure :: sort_abs => pdg_array_sort_abs <>= module function pdg_array_sort_abs (aval1, unique) result (aval2) class(pdg_array_t), intent(in) :: aval1 logical, intent(in), optional :: unique type(pdg_array_t) :: aval2 end function pdg_array_sort_abs <>= module function pdg_array_sort_abs (aval1, unique) result (aval2) class(pdg_array_t), intent(in) :: aval1 logical, intent(in), optional :: unique type(pdg_array_t) :: aval2 integer, dimension(:), allocatable :: tmp logical, dimension(:), allocatable :: mask integer :: i, n logical :: uni uni = .false.; if (present (unique)) uni = unique n = size (aval1%pdg) if (uni) then allocate (tmp (n), mask(n)) tmp = sort_abs (aval1%pdg) mask(1) = .true. do i = 2, n mask(i) = tmp(i) /= tmp(i-1) end do allocate (aval2%pdg (count (mask))) aval2%pdg = pack (tmp, mask) else allocate (aval2%pdg (n)) aval2%pdg = sort_abs (aval1%pdg) end if end function pdg_array_sort_abs @ %def sort_abs @ <>= procedure :: intersect => pdg_array_intersect <>= module function pdg_array_intersect (aval1, match) result (aval2) class(pdg_array_t), intent(in) :: aval1 integer, dimension(:) :: match type(pdg_array_t) :: aval2 end function pdg_array_intersect <>= module function pdg_array_intersect (aval1, match) result (aval2) class(pdg_array_t), intent(in) :: aval1 integer, dimension(:) :: match type(pdg_array_t) :: aval2 integer, dimension(:), allocatable :: isec integer :: i isec = pack (aval1%pdg, [(any(aval1%pdg(i) == match), i=1,size(aval1%pdg))]) call pdg_array_from_int_array (aval2, isec) end function pdg_array_intersect @ %def pdg_array_intersect @ <>= procedure :: search_for_particle => pdg_array_search_for_particle <>= elemental module function pdg_array_search_for_particle (pdg, i_part) result (found) class(pdg_array_t), intent(in) :: pdg integer, intent(in) :: i_part logical :: found end function pdg_array_search_for_particle <>= elemental module function pdg_array_search_for_particle (pdg, i_part) result (found) class(pdg_array_t), intent(in) :: pdg integer, intent(in) :: i_part logical :: found found = any (pdg%pdg == i_part) end function pdg_array_search_for_particle @ %def pdg_array_search_for_particle @ <>= procedure :: invert => pdg_array_invert <>= module function pdg_array_invert (pdg) result (pdg_inverse) class(pdg_array_t), intent(in) :: pdg type(pdg_array_t) :: pdg_inverse end function pdg_array_invert <>= module function pdg_array_invert (pdg) result (pdg_inverse) class(pdg_array_t), intent(in) :: pdg type(pdg_array_t) :: pdg_inverse integer :: i, n n = size (pdg%pdg) allocate (pdg_inverse%pdg (n)) do i = 1, n select case (pdg%pdg(i)) case (GLUON, PHOTON, Z_BOSON, 25) pdg_inverse%pdg(i) = pdg%pdg(i) case default pdg_inverse%pdg(i) = -pdg%pdg(i) end select end do end function pdg_array_invert @ %def pdg_array_invert @ \subsection{PDG array list} A PDG array list, or PDG list, is an array of PDG-array objects with some convenience methods. <>= public :: pdg_list_t <>= type :: pdg_list_t type(pdg_array_t), dimension(:), allocatable :: a contains <> end type pdg_list_t @ %def pdg_list_t @ Output, as a comma-separated list without advancing I/O. <>= procedure :: write => pdg_list_write <>= module subroutine pdg_list_write (object, unit) class(pdg_list_t), intent(in) :: object integer, intent(in), optional :: unit end subroutine pdg_list_write <>= module subroutine pdg_list_write (object, unit) class(pdg_list_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u, i u = given_output_unit (unit) if (allocated (object%a)) then do i = 1, size (object%a) if (i > 1) write (u, "(A)", advance="no") ", " call object%a(i)%write (u) end do end if end subroutine pdg_list_write @ %def pdg_list_write @ Initialize for a certain size. The entries are initially empty PDG arrays. <>= generic :: init => pdg_list_init_size procedure, private :: pdg_list_init_size <>= module subroutine pdg_list_init_size (pl, n) class(pdg_list_t), intent(out) :: pl integer, intent(in) :: n end subroutine pdg_list_init_size <>= module subroutine pdg_list_init_size (pl, n) class(pdg_list_t), intent(out) :: pl integer, intent(in) :: n allocate (pl%a (n)) end subroutine pdg_list_init_size @ %def pdg_list_init_size @ Initialize with a definite array of PDG codes. That is, each entry in the list becomes a single-particle PDG array. <>= generic :: init => pdg_list_init_int_array procedure, private :: pdg_list_init_int_array <>= module subroutine pdg_list_init_int_array (pl, pdg) class(pdg_list_t), intent(out) :: pl integer, dimension(:), intent(in) :: pdg end subroutine pdg_list_init_int_array <>= module subroutine pdg_list_init_int_array (pl, pdg) class(pdg_list_t), intent(out) :: pl integer, dimension(:), intent(in) :: pdg integer :: i allocate (pl%a (size (pdg))) do i = 1, size (pdg) call pdg_array_from_int (pl%a(i), pdg(i)) end do end subroutine pdg_list_init_int_array @ %def pdg_list_init_array @ Set one of the entries. No bounds-check. <>= generic :: set => pdg_list_set_int generic :: set => pdg_list_set_int_array generic :: set => pdg_list_set_pdg_array procedure, private :: pdg_list_set_int procedure, private :: pdg_list_set_int_array procedure, private :: pdg_list_set_pdg_array <>= module subroutine pdg_list_set_int (pl, i, pdg) class(pdg_list_t), intent(inout) :: pl integer, intent(in) :: i integer, intent(in) :: pdg end subroutine pdg_list_set_int module subroutine pdg_list_set_int_array (pl, i, pdg) class(pdg_list_t), intent(inout) :: pl integer, intent(in) :: i integer, dimension(:), intent(in) :: pdg end subroutine pdg_list_set_int_array module subroutine pdg_list_set_pdg_array (pl, i, pa) class(pdg_list_t), intent(inout) :: pl integer, intent(in) :: i type(pdg_array_t), intent(in) :: pa end subroutine pdg_list_set_pdg_array <>= module subroutine pdg_list_set_int (pl, i, pdg) class(pdg_list_t), intent(inout) :: pl integer, intent(in) :: i integer, intent(in) :: pdg call pdg_array_from_int (pl%a(i), pdg) end subroutine pdg_list_set_int module subroutine pdg_list_set_int_array (pl, i, pdg) class(pdg_list_t), intent(inout) :: pl integer, intent(in) :: i integer, dimension(:), intent(in) :: pdg call pdg_array_from_int_array (pl%a(i), pdg) end subroutine pdg_list_set_int_array module subroutine pdg_list_set_pdg_array (pl, i, pa) class(pdg_list_t), intent(inout) :: pl integer, intent(in) :: i type(pdg_array_t), intent(in) :: pa pl%a(i) = pa end subroutine pdg_list_set_pdg_array @ %def pdg_list_set @ Array size, not the length of individual entries <>= procedure :: get_size => pdg_list_get_size <>= module function pdg_list_get_size (pl) result (n) class(pdg_list_t), intent(in) :: pl integer :: n end function pdg_list_get_size <>= module function pdg_list_get_size (pl) result (n) class(pdg_list_t), intent(in) :: pl integer :: n if (allocated (pl%a)) then n = size (pl%a) else n = 0 end if end function pdg_list_get_size @ %def pdg_list_get_size @ Return an entry, as a PDG array. <>= procedure :: get => pdg_list_get <>= module function pdg_list_get (pl, i) result (pa) type(pdg_array_t) :: pa class(pdg_list_t), intent(in) :: pl integer, intent(in) :: i end function pdg_list_get <>= module function pdg_list_get (pl, i) result (pa) type(pdg_array_t) :: pa class(pdg_list_t), intent(in) :: pl integer, intent(in) :: i pa = pl%a(i) end function pdg_list_get @ %def pdg_list_get @ Check if the list entries are all either mutually disjoint or identical. The individual entries (PDG arrays) should already be sorted, so we can test for equality. <>= procedure :: is_regular => pdg_list_is_regular <>= module function pdg_list_is_regular (pl) result (flag) class(pdg_list_t), intent(in) :: pl logical :: flag end function pdg_list_is_regular <>= module function pdg_list_is_regular (pl) result (flag) class(pdg_list_t), intent(in) :: pl logical :: flag integer :: i, j, s s = pl%get_size () flag = .true. do i = 1, s do j = i + 1, s if (pl%a(i) .match. pl%a(j)) then if (pl%a(i) /= pl%a(j)) then flag = .false. return end if end if end do end do end function pdg_list_is_regular @ %def pdg_list_is_regular @ Sort the list. First, each entry gets sorted, including elimination of doublers. Then, we sort the list, using the first member of each PDG array as the marker. No removal of doublers at this stage. If [[n_in]] is supplied, we do not reorder the first [[n_in]] particle entries. <>= procedure :: sort_abs => pdg_list_sort_abs <>= module function pdg_list_sort_abs (pl, n_in) result (pl_sorted) class(pdg_list_t), intent(in) :: pl integer, intent(in), optional :: n_in type(pdg_list_t) :: pl_sorted end function pdg_list_sort_abs <>= module function pdg_list_sort_abs (pl, n_in) result (pl_sorted) class(pdg_list_t), intent(in) :: pl integer, intent(in), optional :: n_in type(pdg_list_t) :: pl_sorted type(pdg_array_t), dimension(:), allocatable :: pa integer, dimension(:), allocatable :: pdg, map integer :: i, n0 call pl_sorted%init (pl%get_size ()) if (allocated (pl%a)) then allocate (pa (size (pl%a))) do i = 1, size (pl%a) pa(i) = pl%a(i)%sort_abs (unique = .true.) end do allocate (pdg (size (pa)), source = 0) do i = 1, size (pa) if (allocated (pa(i)%pdg)) then if (size (pa(i)%pdg) > 0) then pdg(i) = pa(i)%pdg(1) end if end if end do if (present (n_in)) then n0 = n_in else n0 = 0 end if allocate (map (size (pdg))) map(:n0) = [(i, i = 1, n0)] map(n0+1:) = n0 + order_abs (pdg(n0+1:)) do i = 1, size (pa) call pl_sorted%set (i, pa(map(i))) end do end if end function pdg_list_sort_abs @ %def pdg_list_sort_abs @ Compare sorted lists: equality. The result is undefined if some entries are not allocated. <>= generic :: operator (==) => pdg_list_eq procedure, private :: pdg_list_eq <>= module function pdg_list_eq (pl1, pl2) result (flag) class(pdg_list_t), intent(in) :: pl1, pl2 logical :: flag end function pdg_list_eq <>= module function pdg_list_eq (pl1, pl2) result (flag) class(pdg_list_t), intent(in) :: pl1, pl2 logical :: flag integer :: i flag = .false. if (allocated (pl1%a) .and. allocated (pl2%a)) then if (size (pl1%a) == size (pl2%a)) then do i = 1, size (pl1%a) associate (a1 => pl1%a(i), a2 => pl2%a(i)) if (allocated (a1%pdg) .and. allocated (a2%pdg)) then if (size (a1%pdg) == size (a2%pdg)) then if (size (a1%pdg) > 0) then if (a1%pdg(1) /= a2%pdg(1)) return end if else return end if else return end if end associate end do flag = .true. end if end if end function pdg_list_eq @ %def pdg_list_eq @ Compare sorted lists. The result is undefined if some entries are not allocated. The ordering is quite complicated. First, a shorter list comes before a longer list. Comparing entry by entry, a shorter entry comes first. Next, we check the first PDG code within corresponding entries. This is compared by absolute value. If equal, particle comes before antiparticle. Finally, if all is equal, the result is false. <>= generic :: operator (<) => pdg_list_lt procedure, private :: pdg_list_lt <>= module function pdg_list_lt (pl1, pl2) result (flag) class(pdg_list_t), intent(in) :: pl1, pl2 logical :: flag end function pdg_list_lt <>= module function pdg_list_lt (pl1, pl2) result (flag) class(pdg_list_t), intent(in) :: pl1, pl2 logical :: flag integer :: i flag = .false. if (allocated (pl1%a) .and. allocated (pl2%a)) then if (size (pl1%a) < size (pl2%a)) then flag = .true.; return else if (size (pl1%a) > size (pl2%a)) then return else do i = 1, size (pl1%a) associate (a1 => pl1%a(i), a2 => pl2%a(i)) if (allocated (a1%pdg) .and. allocated (a2%pdg)) then if (size (a1%pdg) < size (a2%pdg)) then flag = .true.; return else if (size (a1%pdg) > size (a2%pdg)) then return else if (size (a1%pdg) > 0) then if (abs (a1%pdg(1)) < abs (a2%pdg(1))) then flag = .true.; return else if (abs (a1%pdg(1)) > abs (a2%pdg(1))) then return else if (a1%pdg(1) > 0 .and. a2%pdg(1) < 0) then flag = .true.; return else if (a1%pdg(1) < 0 .and. a2%pdg(1) > 0) then return end if end if end if else return end if end associate end do flag = .false. end if end if end function pdg_list_lt @ %def pdg_list_lt @ Replace an entry. In the result, the entry [[#i]] is replaced by the contents of the second argument. The result is not sorted. If [[n_in]] is also set and [[i]] is less or equal to [[n_in]], replace [[#i]] only by the first entry of [[pl_insert]], and insert the remainder after entry [[n_in]]. <>= procedure :: replace => pdg_list_replace <>= module function pdg_list_replace (pl, i, pl_insert, n_in) result (pl_out) type(pdg_list_t) :: pl_out class(pdg_list_t), intent(in) :: pl integer, intent(in) :: i class(pdg_list_t), intent(in) :: pl_insert integer, intent(in), optional :: n_in end function pdg_list_replace <>= module function pdg_list_replace (pl, i, pl_insert, n_in) result (pl_out) type(pdg_list_t) :: pl_out class(pdg_list_t), intent(in) :: pl integer, intent(in) :: i class(pdg_list_t), intent(in) :: pl_insert integer, intent(in), optional :: n_in integer :: n, n_insert, n_out, k n = pl%get_size () n_insert = pl_insert%get_size () n_out = n + n_insert - 1 call pl_out%init (n_out) ! if (allocated (pl%a)) then do k = 1, i - 1 pl_out%a(k) = pl%a(k) end do ! end if if (present (n_in)) then pl_out%a(i) = pl_insert%a(1) do k = i + 1, n_in pl_out%a(k) = pl%a(k) end do do k = 1, n_insert - 1 pl_out%a(n_in+k) = pl_insert%a(1+k) end do do k = 1, n - n_in pl_out%a(n_in+k+n_insert-1) = pl%a(n_in+k) end do else ! if (allocated (pl_insert%a)) then do k = 1, n_insert pl_out%a(i-1+k) = pl_insert%a(k) end do ! end if ! if (allocated (pl%a)) then do k = 1, n - i pl_out%a(i+n_insert-1+k) = pl%a(i+k) end do end if ! end if end function pdg_list_replace @ %def pdg_list_replace @ <>= procedure :: fusion => pdg_list_fusion <>= module function pdg_list_fusion (pl, pl_insert, i, check_if_existing) result (pl_out) type(pdg_list_t) :: pl_out class(pdg_list_t), intent(in) :: pl type(pdg_list_t), intent(in) :: pl_insert integer, intent(in) :: i logical, intent(in) :: check_if_existing end function pdg_list_fusion <>= module function pdg_list_fusion (pl, pl_insert, i, check_if_existing) result (pl_out) type(pdg_list_t) :: pl_out class(pdg_list_t), intent(in) :: pl type(pdg_list_t), intent(in) :: pl_insert integer, intent(in) :: i logical, intent(in) :: check_if_existing integer :: n, n_insert, k, n_out logical :: new_pdg n = pl%get_size () n_insert = pl_insert%get_size () new_pdg = .not. check_if_existing .or. & (.not. any (pl%search_for_particle (pl_insert%a(1)%pdg))) call pl_out%init (n + n_insert - 1) do k = 1, n if (new_pdg .and. k == i) then pl_out%a(k) = pl%a(k)%add (pl_insert%a(1)) else pl_out%a(k) = pl%a(k) end if end do do k = n + 1, n + n_insert - 1 pl_out%a(k) = pl_insert%a(k-n) end do end function pdg_list_fusion @ %def pdg_list_fusion @ <>= procedure :: get_pdg_sizes => pdg_list_get_pdg_sizes <>= module function pdg_list_get_pdg_sizes (pl) result (i_size) integer, dimension(:), allocatable :: i_size class(pdg_list_t), intent(in) :: pl end function pdg_list_get_pdg_sizes <>= module function pdg_list_get_pdg_sizes (pl) result (i_size) integer, dimension(:), allocatable :: i_size class(pdg_list_t), intent(in) :: pl integer :: i, n n = pl%get_size () allocate (i_size (n)) do i = 1, n i_size(i) = size (pl%a(i)%pdg) end do end function pdg_list_get_pdg_sizes @ %def pdg_list_get_pdg_sizes @ Replace the entries of [[pl]] by the matching entries of [[pl_match]], one by one. This is done in-place. If there is no match, return failure. <>= procedure :: match_replace => pdg_list_match_replace <>= module subroutine pdg_list_match_replace (pl, pl_match, success) class(pdg_list_t), intent(inout) :: pl class(pdg_list_t), intent(in) :: pl_match logical, intent(out) :: success end subroutine pdg_list_match_replace <>= module subroutine pdg_list_match_replace (pl, pl_match, success) class(pdg_list_t), intent(inout) :: pl class(pdg_list_t), intent(in) :: pl_match logical, intent(out) :: success integer :: i, j success = .true. SCAN_ENTRIES: do i = 1, size (pl%a) do j = 1, size (pl_match%a) if (pl%a(i) .match. pl_match%a(j)) then pl%a(i) = pl_match%a(j) cycle SCAN_ENTRIES end if end do success = .false. return end do SCAN_ENTRIES end subroutine pdg_list_match_replace @ %def pdg_list_match_replace @ Just check if a PDG array matches any entry in the PDG list. The second version returns the position of the match within the list. An optional mask indicates the list elements that should be checked. <>= generic :: operator (.match.) => pdg_list_match_pdg_array procedure, private :: pdg_list_match_pdg_array procedure :: find_match => pdg_list_find_match_pdg_array <>= module function pdg_list_match_pdg_array (pl, pa) result (flag) class(pdg_list_t), intent(in) :: pl type(pdg_array_t), intent(in) :: pa logical :: flag end function pdg_list_match_pdg_array module function pdg_list_find_match_pdg_array (pl, pa, mask) result (i) class(pdg_list_t), intent(in) :: pl type(pdg_array_t), intent(in) :: pa logical, dimension(:), intent(in), optional :: mask integer :: i end function pdg_list_find_match_pdg_array <>= module function pdg_list_match_pdg_array (pl, pa) result (flag) class(pdg_list_t), intent(in) :: pl type(pdg_array_t), intent(in) :: pa logical :: flag flag = pl%find_match (pa) /= 0 end function pdg_list_match_pdg_array module function pdg_list_find_match_pdg_array (pl, pa, mask) result (i) class(pdg_list_t), intent(in) :: pl type(pdg_array_t), intent(in) :: pa logical, dimension(:), intent(in), optional :: mask integer :: i do i = 1, size (pl%a) if (present (mask)) then if (.not. mask(i)) cycle end if if (pl%a(i) .match. pa) return end do i = 0 end function pdg_list_find_match_pdg_array @ %def pdg_list_match_pdg_array @ %def pdg_list_find_match_pdg_array @ Some old compilers have problems with allocatable arrays as intent(out) or as function result, so be conservative here: <>= procedure :: create_pdg_array => pdg_list_create_pdg_array <>= module subroutine pdg_list_create_pdg_array (pl, pdg) class(pdg_list_t), intent(in) :: pl type(pdg_array_t), dimension(:), intent(inout), allocatable :: pdg end subroutine pdg_list_create_pdg_array <>= module subroutine pdg_list_create_pdg_array (pl, pdg) class(pdg_list_t), intent(in) :: pl type(pdg_array_t), dimension(:), intent(inout), allocatable :: pdg integer :: n_elements integer :: i associate (a => pl%a) n_elements = size (a) if (allocated (pdg)) deallocate (pdg) allocate (pdg (n_elements)) do i = 1, n_elements pdg(i) = a(i) end do end associate end subroutine pdg_list_create_pdg_array @ %def pdg_list_create_pdg_array @ <>= procedure :: create_antiparticles => pdg_list_create_antiparticles <>= module subroutine pdg_list_create_antiparticles (pl, pl_anti, n_new_particles) class(pdg_list_t), intent(in) :: pl type(pdg_list_t), intent(out) :: pl_anti integer, intent(out) :: n_new_particles end subroutine pdg_list_create_antiparticles <>= module subroutine pdg_list_create_antiparticles (pl, pl_anti, n_new_particles) class(pdg_list_t), intent(in) :: pl type(pdg_list_t), intent(out) :: pl_anti integer, intent(out) :: n_new_particles type(pdg_list_t) :: pl_inverse integer :: i, n integer :: n_identical logical, dimension(:), allocatable :: collect n = pl%get_size (); n_identical = 0 allocate (collect (n)); collect = .true. call pl_inverse%init (n) do i = 1, n pl_inverse%a(i) = pl%a(i)%invert() end do do i = 1, n if (any (pl_inverse%a(i) == pl%a)) then collect(i) = .false. n_identical = n_identical + 1 end if end do n_new_particles = n - n_identical if (n_new_particles > 0) then call pl_anti%init (n_new_particles) do i = 1, n if (collect (i)) pl_anti%a(i) = pl_inverse%a(i) end do end if end subroutine pdg_list_create_antiparticles @ %def pdg_list_create_antiparticles @ <>= procedure :: search_for_particle => pdg_list_search_for_particle <>= elemental module function pdg_list_search_for_particle (pl, i_part) result (found) logical :: found class(pdg_list_t), intent(in) :: pl integer, intent(in) :: i_part end function pdg_list_search_for_particle <>= elemental module function pdg_list_search_for_particle (pl, i_part) result (found) logical :: found class(pdg_list_t), intent(in) :: pl integer, intent(in) :: i_part integer :: i_pl do i_pl = 1, size (pl%a) found = pl%a(i_pl)%search_for_particle (i_part) if (found) return end do end function pdg_list_search_for_particle @ %def pdg_list_search_for_particle @ <>= procedure :: contains_colored_particles => pdg_list_contains_colored_particles <>= module function pdg_list_contains_colored_particles (pl) result (colored) class(pdg_list_t), intent(in) :: pl logical :: colored end function pdg_list_contains_colored_particles <>= module function pdg_list_contains_colored_particles (pl) result (colored) class(pdg_list_t), intent(in) :: pl logical :: colored integer :: i colored = .false. do i = 1, size (pl%a) if (pl%a(i)%has_colored_particles()) then colored = .true. exit end if end do end function pdg_list_contains_colored_particles @ %def pdg_list_contains_colored_particles @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[pdg_arrays_ut.f90]]>>= <> module pdg_arrays_ut use unit_tests use pdg_arrays_uti <> <> contains <> end module pdg_arrays_ut @ %def pdg_arrays_ut @ <<[[pdg_arrays_uti.f90]]>>= <> module pdg_arrays_uti use pdg_arrays <> <> contains <> end module pdg_arrays_uti @ %def pdg_arrays_ut @ API: driver for the unit tests below. <>= public :: pdg_arrays_test <>= subroutine pdg_arrays_test (u, results) integer, intent(in) :: u type (test_results_t), intent(inout) :: results <> end subroutine pdg_arrays_test @ %def pdg_arrays_test @ Basic functionality. <>= call test (pdg_arrays_1, "pdg_arrays_1", & "create and sort PDG array", & u, results) <>= public :: pdg_arrays_1 <>= subroutine pdg_arrays_1 (u) integer, intent(in) :: u type(pdg_array_t) :: pa, pa1, pa2, pa3, pa4, pa5, pa6 integer, dimension(:), allocatable :: pdg write (u, "(A)") "* Test output: pdg_arrays_1" write (u, "(A)") "* Purpose: create and sort PDG arrays" write (u, "(A)") write (u, "(A)") "* Assignment" write (u, "(A)") call pa%write (u) write (u, *) write (u, "(A,I0)") "length = ", pa%get_length () pdg = pa write (u, "(A,3(1x,I0))") "contents = ", pdg write (u, *) pa = 1 call pa%write (u) write (u, *) write (u, "(A,I0)") "length = ", pa%get_length () pdg = pa write (u, "(A,3(1x,I0))") "contents = ", pdg write (u, *) pa = [1, 2, 3] call pa%write (u) write (u, *) write (u, "(A,I0)") "length = ", pa%get_length () pdg = pa write (u, "(A,3(1x,I0))") "contents = ", pdg write (u, "(A,I0)") "element #2 = ", pa%get (2) write (u, *) write (u, "(A)") "* Replace" write (u, *) pa = pa%replace (2, [-5, 5, -7]) call pa%write (u) write (u, *) write (u, *) write (u, "(A)") "* Sort" write (u, *) pa = [1, -7, 3, -5, 5, 3] call pa%write (u) write (u, *) pa1 = pa%sort_abs () pa2 = pa%sort_abs (unique = .true.) call pa1%write (u) write (u, *) call pa2%write (u) write (u, *) write (u, *) write (u, "(A)") "* Compare" write (u, *) pa1 = [1, 3] pa2 = [1, 2, -2] pa3 = [1, 2, 4] pa4 = [1, 2, 4] pa5 = [1, 2, -4] pa6 = [1, 2, -3] write (u, "(A,6(1x,L1))") "< ", & pa1 < pa2, pa2 < pa3, pa3 < pa4, pa4 < pa5, pa5 < pa6, pa6 < pa1 write (u, "(A,6(1x,L1))") "> ", & pa1 > pa2, pa2 > pa3, pa3 > pa4, pa4 > pa5, pa5 > pa6, pa6 > pa1 write (u, "(A,6(1x,L1))") "<=", & pa1 <= pa2, pa2 <= pa3, pa3 <= pa4, pa4 <= pa5, pa5 <= pa6, pa6 <= pa1 write (u, "(A,6(1x,L1))") ">=", & pa1 >= pa2, pa2 >= pa3, pa3 >= pa4, pa4 >= pa5, pa5 >= pa6, pa6 >= pa1 write (u, "(A,6(1x,L1))") "==", & pa1 == pa2, pa2 == pa3, pa3 == pa4, pa4 == pa5, pa5 == pa6, pa6 == pa1 write (u, "(A,6(1x,L1))") "/=", & pa1 /= pa2, pa2 /= pa3, pa3 /= pa4, pa4 /= pa5, pa5 /= pa6, pa6 /= pa1 write (u, *) pa1 = [0] pa2 = [1, 2] pa3 = [1, -2] write (u, "(A,6(1x,L1))") "eqv ", & pa1 .eqv. pa1, pa1 .eqv. pa2, & pa2 .eqv. pa2, pa2 .eqv. pa3 write (u, "(A,6(1x,L1))") "neqv", & pa1 .neqv. pa1, pa1 .neqv. pa2, & pa2 .neqv. pa2, pa2 .neqv. pa3 write (u, *) write (u, "(A,6(1x,L1))") "match", & pa1 .match. 0, pa1 .match. 1, & pa2 .match. 0, pa2 .match. 1, pa2 .match. 3 write (u, "(A)") write (u, "(A)") "* Test output end: pdg_arrays_1" end subroutine pdg_arrays_1 @ %def pdg_arrays_1 @ PDG array list, i.e., arrays of arrays. <>= call test (pdg_arrays_2, "pdg_arrays_2", & "create and sort PDG lists", & u, results) <>= public :: pdg_arrays_2 <>= subroutine pdg_arrays_2 (u) integer, intent(in) :: u type(pdg_array_t) :: pa type(pdg_list_t) :: pl, pl1 write (u, "(A)") "* Test output: pdg_arrays_2" write (u, "(A)") "* Purpose: create and sort PDG lists" write (u, "(A)") write (u, "(A)") "* Assignment" write (u, "(A)") call pl%init (3) call pl%set (1, 42) call pl%set (2, [3, 2]) pa = [5, -5] call pl%set (3, pa) call pl%write (u) write (u, *) write (u, "(A,I0)") "size = ", pl%get_size () write (u, "(A)") write (u, "(A)") "* Sort" write (u, "(A)") pl = pl%sort_abs () call pl%write (u) write (u, *) write (u, "(A)") write (u, "(A)") "* Extract item #3" write (u, "(A)") pa = pl%get (3) call pa%write (u) write (u, *) write (u, "(A)") write (u, "(A)") "* Replace item #3" write (u, "(A)") call pl1%init (2) call pl1%set (1, [2, 4]) call pl1%set (2, -7) pl = pl%replace (3, pl1) call pl%write (u) write (u, *) write (u, "(A)") write (u, "(A)") "* Test output end: pdg_arrays_2" end subroutine pdg_arrays_2 @ %def pdg_arrays_2 @ Check if a (sorted) PDG array lists is regular. The entries (PDG arrays) must not overlap, unless they are identical. <>= call test (pdg_arrays_3, "pdg_arrays_3", & "check PDG lists", & u, results) <>= public :: pdg_arrays_3 <>= subroutine pdg_arrays_3 (u) integer, intent(in) :: u type(pdg_list_t) :: pl write (u, "(A)") "* Test output: pdg_arrays_3" write (u, "(A)") "* Purpose: check for regular PDG lists" write (u, "(A)") write (u, "(A)") "* Regular list" write (u, "(A)") call pl%init (4) call pl%set (1, [1, 2]) call pl%set (2, [1, 2]) call pl%set (3, [5, -5]) call pl%set (4, 42) call pl%write (u) write (u, *) write (u, "(L1)") pl%is_regular () write (u, "(A)") write (u, "(A)") "* Irregular list" write (u, "(A)") call pl%init (4) call pl%set (1, [1, 2]) call pl%set (2, [1, 2]) call pl%set (3, [2, 5, -5]) call pl%set (4, 42) call pl%write (u) write (u, *) write (u, "(L1)") pl%is_regular () write (u, "(A)") write (u, "(A)") "* Test output end: pdg_arrays_3" end subroutine pdg_arrays_3 @ %def pdg_arrays_3 @ Compare PDG array lists. The lists must be regular, i.e., sorted and with non-overlapping (or identical) entries. <>= call test (pdg_arrays_4, "pdg_arrays_4", & "compare PDG lists", & u, results) <>= public :: pdg_arrays_4 <>= subroutine pdg_arrays_4 (u) integer, intent(in) :: u type(pdg_list_t) :: pl1, pl2, pl3 write (u, "(A)") "* Test output: pdg_arrays_4" write (u, "(A)") "* Purpose: check for regular PDG lists" write (u, "(A)") write (u, "(A)") "* Create lists" write (u, "(A)") call pl1%init (4) call pl1%set (1, [1, 2]) call pl1%set (2, [1, 2]) call pl1%set (3, [5, -5]) call pl1%set (4, 42) write (u, "(I1,1x)", advance = "no") 1 call pl1%write (u) write (u, *) call pl2%init (2) call pl2%set (1, 3) call pl2%set (2, [5, -5]) write (u, "(I1,1x)", advance = "no") 2 call pl2%write (u) write (u, *) call pl3%init (2) call pl3%set (1, 4) call pl3%set (2, [5, -5]) write (u, "(I1,1x)", advance = "no") 3 call pl3%write (u) write (u, *) write (u, "(A)") write (u, "(A)") "* a == b" write (u, "(A)") write (u, "(2x,A)") "123" write (u, *) write (u, "(I1,1x,4L1)") 1, pl1 == pl1, pl1 == pl2, pl1 == pl3 write (u, "(I1,1x,4L1)") 2, pl2 == pl1, pl2 == pl2, pl2 == pl3 write (u, "(I1,1x,4L1)") 3, pl3 == pl1, pl3 == pl2, pl3 == pl3 write (u, "(A)") write (u, "(A)") "* a < b" write (u, "(A)") write (u, "(2x,A)") "123" write (u, *) write (u, "(I1,1x,4L1)") 1, pl1 < pl1, pl1 < pl2, pl1 < pl3 write (u, "(I1,1x,4L1)") 2, pl2 < pl1, pl2 < pl2, pl2 < pl3 write (u, "(I1,1x,4L1)") 3, pl3 < pl1, pl3 < pl2, pl3 < pl3 write (u, "(A)") write (u, "(A)") "* Test output end: pdg_arrays_4" end subroutine pdg_arrays_4 @ %def pdg_arrays_4 @ Match-replace: translate all entries in the first list into the matching entries of the second list, if there is a match. <>= call test (pdg_arrays_5, "pdg_arrays_5", & "match PDG lists", & u, results) <>= public :: pdg_arrays_5 <>= subroutine pdg_arrays_5 (u) integer, intent(in) :: u type(pdg_list_t) :: pl1, pl2, pl3 logical :: success write (u, "(A)") "* Test output: pdg_arrays_5" write (u, "(A)") "* Purpose: match-replace" write (u, "(A)") write (u, "(A)") "* Create lists" write (u, "(A)") call pl1%init (2) call pl1%set (1, [1, 2]) call pl1%set (2, 42) call pl1%write (u) write (u, *) call pl3%init (2) call pl3%set (1, [42, -42]) call pl3%set (2, [1, 2, 3, 4]) call pl1%match_replace (pl3, success) call pl3%write (u) write (u, "(1x,A,1x,L1,':',1x)", advance="no") "=>", success call pl1%write (u) write (u, *) write (u, *) call pl2%init (2) call pl2%set (1, 9) call pl2%set (2, 42) call pl2%write (u) write (u, *) call pl2%match_replace (pl3, success) call pl3%write (u) write (u, "(1x,A,1x,L1,':',1x)", advance="no") "=>", success call pl2%write (u) write (u, *) write (u, "(A)") write (u, "(A)") "* Test output end: pdg_arrays_5" end subroutine pdg_arrays_5 @ %def pdg_arrays_5 @ \clearpage %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Jets} The FastJet library is linked externally, if available. The wrapper code is also in a separate directory. Here, we define \whizard-specific procedures and tests. <<[[jets.f90]]>>= <> module jets use fastjet !NODEP! <> <> contains <> end module jets @ %def jets @ \subsection{Re-exported symbols} We use this module as a proxy for the FastJet interface, therefore we re-export some symbols. <>= public :: fastjet_available public :: fastjet_init public :: jet_definition_t public :: pseudojet_t public :: pseudojet_vector_t public :: cluster_sequence_t public :: assignment (=) @ %def jet_definition_t pseudojet_t pseudojet_vector_t cluster_sequence_t @ The initialization routine prints the banner. <>= subroutine fastjet_init () call print_banner () end subroutine fastjet_init @ %def fastjet_init @ The jet algorithm codes (actually, integers) <>= public :: kt_algorithm public :: cambridge_algorithm public :: antikt_algorithm public :: genkt_algorithm public :: cambridge_for_passive_algorithm public :: genkt_for_passive_algorithm public :: ee_kt_algorithm public :: ee_genkt_algorithm public :: plugin_algorithm public :: undefined_jet_algorithm @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[jets_ut.f90]]>>= <> module jets_ut use unit_tests use jets_uti <> <> contains <> end module jets_ut @ %def jets_ut @ <<[[jets_uti.f90]]>>= <> module jets_uti <> use fastjet !NODEP! use jets <> <> contains <> end module jets_uti @ %def jets_ut @ API: driver for the unit tests below. <>= public :: jets_test <>= subroutine jets_test (u, results) integer, intent(in) :: u type (test_results_t), intent(inout) :: results <> end subroutine jets_test @ %def jets_test @ This test is actually the minimal example from the FastJet manual, translated to Fortran. Note that FastJet creates pseudojet vectors, which we mirror in the [[pseudojet_vector_t]], but immediately assign to pseudojet arrays. Without automatic finalization available in the compilers, we should avoid this in actual code and rather introduce intermediate variables for those objects, which we can finalize explicitly. <>= call test (jets_1, "jets_1", & "basic FastJet functionality", & u, results) <>= public :: jets_1 <>= subroutine jets_1 (u) integer, intent(in) :: u type(pseudojet_t), dimension(:), allocatable :: prt, jets, constituents type(jet_definition_t) :: jet_def type(cluster_sequence_t) :: cs integer, parameter :: dp = default integer :: i, j write (u, "(A)") "* Test output: jets_1" write (u, "(A)") "* Purpose: test basic FastJet functionality" write (u, "(A)") write (u, "(A)") "* Print banner" call print_banner () write (u, *) write (u, "(A)") "* Prepare input particles" allocate (prt (3)) call prt(1)%init ( 99._dp, 0.1_dp, 0._dp, 100._dp) call prt(2)%init ( 4._dp,-0.1_dp, 0._dp, 5._dp) call prt(3)%init (-99._dp, 0._dp, 0._dp, 99._dp) write (u, *) write (u, "(A)") "* Define jet algorithm" call jet_def%init (antikt_algorithm, 0.7_dp) write (u, *) write (u, "(A)") "* Cluster particles according to jet algorithm" write (u, *) write (u, "(A,A)") "Clustering with ", jet_def%description () call cs%init (pseudojet_vector (prt), jet_def) write (u, *) write (u, "(A)") "* Sort output jets" jets = sorted_by_pt (cs%inclusive_jets ()) write (u, *) write (u, "(A)") "* Print jet observables and constituents" write (u, *) write (u, "(4x,3(7x,A3))") "pt", "y", "phi" do i = 1, size (jets) write (u, "(A,1x,I0,A,3(1x,F9.5))") & "jet", i, ":", jets(i)%perp (), jets(i)%rap (), jets(i)%phi () constituents = jets(i)%constituents () do j = 1, size (constituents) write (u, "(4x,A,1x,I0,A,F9.5)") & "constituent", j, "'s pt:", constituents(j)%perp () end do do j = 1, size (constituents) call constituents(j)%final () end do end do write (u, *) write (u, "(A)") "* Cleanup" do i = 1, size (prt) call prt(i)%final () end do do i = 1, size (jets) call jets(i)%final () end do call jet_def%final () call cs%final () write (u, "(A)") write (u, "(A)") "* Test output end: jets_1" end subroutine jets_1 @ %def jets_1 @ \clearpage %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Subevents} The purpose of subevents is to store the relevant part of the physical event (either partonic or hadronic), and to hold particle selections and combinations which are constructed in cut or analysis expressions. <<[[subevents.f90]]>>= <> module subevents use, intrinsic :: iso_c_binding !NODEP! <> use numeric_utils, only: pacify use c_particles use lorentz use pdg_arrays use jets <> <> <> <> <> interface <> end interface end module subevents @ %def subevents @ <<[[subevents_sub.f90]]>>= <> submodule (subevents) subevents_s use io_units use format_defs, only: FMT_14, FMT_19 use format_utils, only: pac_fmt use physics_defs use sorting implicit none contains <> end submodule subevents_s @ %def subevents_s @ \subsection{Particles} For the purpose of this module, a particle has a type which can indicate a beam, incoming, outgoing, or composite particle, flavor and helicity codes (integer, undefined for composite), four-momentum and invariant mass squared. (Other particles types are used in extended event types, but also defined here.) Furthermore, each particle has an allocatable array of ancestors -- particle indices which indicate the building blocks of a composite particle. For an incoming/outgoing particle, the array contains only the index of the particle itself. For incoming particles, the momentum is inverted before storing it in the particle object. <>= integer, parameter, public :: PRT_UNDEFINED = 0 integer, parameter, public :: PRT_BEAM = -9 integer, parameter, public :: PRT_INCOMING = 1 integer, parameter, public :: PRT_OUTGOING = 2 integer, parameter, public :: PRT_COMPOSITE = 3 integer, parameter, public :: PRT_VIRTUAL = 4 integer, parameter, public :: PRT_RESONANT = 5 integer, parameter, public :: PRT_BEAM_REMNANT = 9 @ %def PRT_UNDEFINED PRT_BEAM @ %def PRT_INCOMING PRT_OUTGOING PRT_COMPOSITE @ %def PRT_COMPOSITE PRT_VIRTUAL PRT_RESONANT @ %def PRT_BEAM_REMNANT @ \subsubsection{The type} We initialize only the type here and mark as unpolarized. The initializers below do the rest. The logicals [[is_b_jet]] and [[is_c_jet]] are true only if [[prt_t]] comes out of the [[subevt_cluster]] routine and fulfils the correct flavor content. <>= public :: prt_t <>= type :: prt_t private integer :: type = PRT_UNDEFINED integer :: pdg logical :: polarized = .false. logical :: colorized = .false. logical :: clustered = .false. logical :: is_b_jet = .false. logical :: is_c_jet = .false. integer :: h type(vector4_t) :: p real(default) :: p2 integer, dimension(:), allocatable :: src integer, dimension(:), allocatable :: col integer, dimension(:), allocatable :: acl end type prt_t @ %def prt_t @ Initializers. Polarization is set separately. Finalizers are not needed. <>= subroutine prt_init_beam (prt, pdg, p, p2, src) type(prt_t), intent(out) :: prt integer, intent(in) :: pdg type(vector4_t), intent(in) :: p real(default), intent(in) :: p2 integer, dimension(:), intent(in) :: src prt%type = PRT_BEAM call prt_set (prt, pdg, - p, p2, src) end subroutine prt_init_beam subroutine prt_init_incoming (prt, pdg, p, p2, src) type(prt_t), intent(out) :: prt integer, intent(in) :: pdg type(vector4_t), intent(in) :: p real(default), intent(in) :: p2 integer, dimension(:), intent(in) :: src prt%type = PRT_INCOMING call prt_set (prt, pdg, - p, p2, src) end subroutine prt_init_incoming subroutine prt_init_outgoing (prt, pdg, p, p2, src) type(prt_t), intent(out) :: prt integer, intent(in) :: pdg type(vector4_t), intent(in) :: p real(default), intent(in) :: p2 integer, dimension(:), intent(in) :: src prt%type = PRT_OUTGOING call prt_set (prt, pdg, p, p2, src) end subroutine prt_init_outgoing subroutine prt_init_composite (prt, p, src) type(prt_t), intent(out) :: prt type(vector4_t), intent(in) :: p integer, dimension(:), intent(in) :: src prt%type = PRT_COMPOSITE call prt_set (prt, 0, p, p**2, src) end subroutine prt_init_composite @ %def prt_init_beam prt_init_incoming prt_init_outgoing prt_init_composite @ This version is for temporary particle objects, so the [[src]] array is not set. <>= public :: prt_init_combine <>= module subroutine prt_init_combine (prt, prt1, prt2) type(prt_t), intent(out) :: prt type(prt_t), intent(in) :: prt1, prt2 end subroutine prt_init_combine <>= module subroutine prt_init_combine (prt, prt1, prt2) type(prt_t), intent(out) :: prt type(prt_t), intent(in) :: prt1, prt2 type(vector4_t) :: p integer, dimension(0) :: src prt%type = PRT_COMPOSITE p = prt1%p + prt2%p call prt_set (prt, 0, p, p**2, src) end subroutine prt_init_combine @ %def prt_init_combine @ Init from a pseudojet object. <>= subroutine prt_init_pseudojet (prt, jet, src, pdg, is_b_jet, is_c_jet) type(prt_t), intent(out) :: prt type(pseudojet_t), intent(in) :: jet integer, dimension(:), intent(in) :: src integer, intent(in) :: pdg logical, intent(in) :: is_b_jet, is_c_jet type(vector4_t) :: p prt%type = PRT_COMPOSITE p = vector4_moving (jet%e(), & vector3_moving ([jet%px(), jet%py(), jet%pz()])) call prt_set (prt, pdg, p, p**2, src) prt%is_b_jet = is_b_jet prt%is_c_jet = is_c_jet prt%clustered = .true. end subroutine prt_init_pseudojet @ %def prt_init_pseudojet @ \subsubsection{Accessing contents} <>= public :: prt_get_pdg <>= elemental module function prt_get_pdg (prt) result (pdg) integer :: pdg type(prt_t), intent(in) :: prt end function prt_get_pdg <>= elemental module function prt_get_pdg (prt) result (pdg) integer :: pdg type(prt_t), intent(in) :: prt pdg = prt%pdg end function prt_get_pdg @ %def prt_get_pdg <>= public :: prt_get_momentum <>= elemental module function prt_get_momentum (prt) result (p) type(vector4_t) :: p type(prt_t), intent(in) :: prt end function prt_get_momentum <>= elemental module function prt_get_momentum (prt) result (p) type(vector4_t) :: p type(prt_t), intent(in) :: prt p = prt%p end function prt_get_momentum @ %def prt_get_momentum <>= public :: prt_get_msq <>= elemental module function prt_get_msq (prt) result (msq) real(default) :: msq type(prt_t), intent(in) :: prt end function prt_get_msq <>= elemental module function prt_get_msq (prt) result (msq) real(default) :: msq type(prt_t), intent(in) :: prt msq = prt%p2 end function prt_get_msq @ %def prt_get_msq <>= public :: prt_is_polarized <>= elemental module function prt_is_polarized (prt) result (flag) logical :: flag type(prt_t), intent(in) :: prt end function prt_is_polarized <>= elemental module function prt_is_polarized (prt) result (flag) logical :: flag type(prt_t), intent(in) :: prt flag = prt%polarized end function prt_is_polarized @ %def prt_is_polarized <>= public :: prt_get_helicity <>= elemental module function prt_get_helicity (prt) result (h) integer :: h type(prt_t), intent(in) :: prt end function prt_get_helicity <>= elemental module function prt_get_helicity (prt) result (h) integer :: h type(prt_t), intent(in) :: prt h = prt%h end function prt_get_helicity @ %def prt_get_helicity <>= public :: prt_is_colorized <>= elemental module function prt_is_colorized (prt) result (flag) logical :: flag type(prt_t), intent(in) :: prt end function prt_is_colorized <>= elemental module function prt_is_colorized (prt) result (flag) logical :: flag type(prt_t), intent(in) :: prt flag = prt%colorized end function prt_is_colorized @ %def prt_is_colorized <>= public :: prt_is_clustered <>= elemental module function prt_is_clustered (prt) result (flag) logical :: flag type(prt_t), intent(in) :: prt end function prt_is_clustered <>= elemental module function prt_is_clustered (prt) result (flag) logical :: flag type(prt_t), intent(in) :: prt flag = prt%clustered end function prt_is_clustered @ %def prt_is_clustered <>= public :: prt_is_recombinable <>= elemental module function prt_is_recombinable (prt) result (flag) logical :: flag type(prt_t), intent(in) :: prt end function prt_is_recombinable <>= elemental module function prt_is_recombinable (prt) result (flag) logical :: flag type(prt_t), intent(in) :: prt flag = prt_is_parton (prt) .or. & abs(prt%pdg) == TOP_Q .or. & prt_is_lepton (prt) .or. & prt_is_photon (prt) end function prt_is_recombinable @ %def prt_is_recombinable <>= public :: prt_is_photon <>= elemental module function prt_is_photon (prt) result (flag) logical :: flag type(prt_t), intent(in) :: prt end function prt_is_photon <>= elemental module function prt_is_photon (prt) result (flag) logical :: flag type(prt_t), intent(in) :: prt flag = prt%pdg == PHOTON end function prt_is_photon @ %def prt_is_photon We do not take the top quark into account here. <>= public :: prt_is_parton <>= elemental module function prt_is_parton (prt) result (flag) logical :: flag type(prt_t), intent(in) :: prt end function prt_is_parton <>= elemental module function prt_is_parton (prt) result (flag) logical :: flag type(prt_t), intent(in) :: prt flag = abs(prt%pdg) == DOWN_Q .or. & abs(prt%pdg) == UP_Q .or. & abs(prt%pdg) == STRANGE_Q .or. & abs(prt%pdg) == CHARM_Q .or. & abs(prt%pdg) == BOTTOM_Q .or. & prt%pdg == GLUON end function prt_is_parton @ %def prt_is_parton <>= public :: prt_is_lepton <>= elemental module function prt_is_lepton (prt) result (flag) logical :: flag type(prt_t), intent(in) :: prt end function prt_is_lepton <>= elemental module function prt_is_lepton (prt) result (flag) logical :: flag type(prt_t), intent(in) :: prt flag = abs(prt%pdg) == ELECTRON .or. & abs(prt%pdg) == MUON .or. & abs(prt%pdg) == TAU end function prt_is_lepton @ %def prt_is_lepton <>= public :: prt_is_b_jet <>= elemental module function prt_is_b_jet (prt) result (flag) logical :: flag type(prt_t), intent(in) :: prt end function prt_is_b_jet <>= elemental module function prt_is_b_jet (prt) result (flag) logical :: flag type(prt_t), intent(in) :: prt flag = prt%is_b_jet end function prt_is_b_jet @ %def prt_is_b_jet <>= public :: prt_is_c_jet <>= elemental module function prt_is_c_jet (prt) result (flag) logical :: flag type(prt_t), intent(in) :: prt end function prt_is_c_jet <>= elemental module function prt_is_c_jet (prt) result (flag) logical :: flag type(prt_t), intent(in) :: prt flag = prt%is_c_jet end function prt_is_c_jet @ %def prt_is_c_jet @ The number of open color (anticolor) lines. We inspect the list of color (anticolor) lines and count the entries that do not appear in the list of anticolors (colors). (There is no check against duplicates; we assume that color line indices are unique.) <>= public :: prt_get_n_col public :: prt_get_n_acl <>= elemental module function prt_get_n_col (prt) result (n) integer :: n type(prt_t), intent(in) :: prt end function prt_get_n_col elemental module function prt_get_n_acl (prt) result (n) integer :: n type(prt_t), intent(in) :: prt end function prt_get_n_acl <>= elemental module function prt_get_n_col (prt) result (n) integer :: n type(prt_t), intent(in) :: prt integer, dimension(:), allocatable :: col, acl integer :: i n = 0 if (prt%colorized) then do i = 1, size (prt%col) if (all (prt%col(i) /= prt%acl)) n = n + 1 end do end if end function prt_get_n_col elemental module function prt_get_n_acl (prt) result (n) integer :: n type(prt_t), intent(in) :: prt integer, dimension(:), allocatable :: col, acl integer :: i n = 0 if (prt%colorized) then do i = 1, size (prt%acl) if (all (prt%acl(i) /= prt%col)) n = n + 1 end do end if end function prt_get_n_acl @ %def prt_get_n_col @ %def prt_get_n_acl @ Return the color and anticolor-flow line indices explicitly. <>= public :: prt_get_color_indices <>= module subroutine prt_get_color_indices (prt, col, acl) type(prt_t), intent(in) :: prt integer, dimension(:), allocatable, intent(out) :: col, acl end subroutine prt_get_color_indices <>= module subroutine prt_get_color_indices (prt, col, acl) type(prt_t), intent(in) :: prt integer, dimension(:), allocatable, intent(out) :: col, acl if (prt%colorized) then col = prt%col acl = prt%acl else col = [integer::] acl = [integer::] end if end subroutine prt_get_color_indices @ %def prt_get_color_indices @ \subsubsection{Setting data} Set the PDG, momentum and momentum squared, and ancestors. If allocate-on-assignment is available, this can be simplified. <>= subroutine prt_set (prt, pdg, p, p2, src) type(prt_t), intent(inout) :: prt integer, intent(in) :: pdg type(vector4_t), intent(in) :: p real(default), intent(in) :: p2 integer, dimension(:), intent(in) :: src prt%pdg = pdg prt%p = p prt%p2 = p2 if (allocated (prt%src)) then if (size (src) /= size (prt%src)) then deallocate (prt%src) allocate (prt%src (size (src))) end if else allocate (prt%src (size (src))) end if prt%src = src end subroutine prt_set @ %def prt_set @ Set the particle PDG code separately. <>= elemental subroutine prt_set_pdg (prt, pdg) type(prt_t), intent(inout) :: prt integer, intent(in) :: pdg prt%pdg = pdg end subroutine prt_set_pdg @ %def prt_set_pdg @ Set the momentum separately. <>= elemental subroutine prt_set_p (prt, p) type(prt_t), intent(inout) :: prt type(vector4_t), intent(in) :: p prt%p = p end subroutine prt_set_p @ %def prt_set_p @ Set the squared invariant mass separately. <>= elemental subroutine prt_set_p2 (prt, p2) type(prt_t), intent(inout) :: prt real(default), intent(in) :: p2 prt%p2 = p2 end subroutine prt_set_p2 @ %def prt_set_p2 @ Set helicity (optional). <>= subroutine prt_polarize (prt, h) type(prt_t), intent(inout) :: prt integer, intent(in) :: h prt%polarized = .true. prt%h = h end subroutine prt_polarize @ %def prt_polarize @ Set color-flow indices (optional). <>= subroutine prt_colorize (prt, col, acl) type(prt_t), intent(inout) :: prt integer, dimension(:), intent(in) :: col, acl prt%colorized = .true. prt%col = col prt%acl = acl end subroutine prt_colorize @ %def prt_colorize @ \subsubsection{Conversion} Transform a [[prt_t]] object into a [[c_prt_t]] object. <>= public :: c_prt <>= interface c_prt module procedure c_prt_from_prt end interface @ %def c_prt <>= elemental module function c_prt_from_prt (prt) result (c_prt) type(c_prt_t) :: c_prt type(prt_t), intent(in) :: prt end function c_prt_from_prt <>= elemental module function c_prt_from_prt (prt) result (c_prt) type(c_prt_t) :: c_prt type(prt_t), intent(in) :: prt c_prt = prt%p c_prt%type = prt%type c_prt%pdg = prt%pdg if (prt%polarized) then c_prt%polarized = 1 else c_prt%polarized = 0 end if c_prt%h = prt%h end function c_prt_from_prt @ %def c_prt_from_prt @ \subsubsection{Output} <>= public :: prt_write <>= module subroutine prt_write (prt, unit, testflag) type(prt_t), intent(in) :: prt integer, intent(in), optional :: unit logical, intent(in), optional :: testflag end subroutine prt_write <>= module subroutine prt_write (prt, unit, testflag) type(prt_t), intent(in) :: prt integer, intent(in), optional :: unit logical, intent(in), optional :: testflag logical :: pacified type(prt_t) :: tmp character(len=7) :: fmt integer :: u, i call pac_fmt (fmt, FMT_19, FMT_14, testflag) u = given_output_unit (unit); if (u < 0) return pacified = .false. ; if (present (testflag)) pacified = testflag tmp = prt if (pacified) call pacify (tmp) write (u, "(1x,A)", advance="no") "prt(" select case (prt%type) case (PRT_UNDEFINED); write (u, "('?')", advance="no") case (PRT_BEAM); write (u, "('b:')", advance="no") case (PRT_INCOMING); write (u, "('i:')", advance="no") case (PRT_OUTGOING); write (u, "('o:')", advance="no") case (PRT_COMPOSITE); write (u, "('c:')", advance="no") end select select case (prt%type) case (PRT_BEAM, PRT_INCOMING, PRT_OUTGOING) if (prt%polarized) then write (u, "(I0,'/',I0,'|')", advance="no") prt%pdg, prt%h else write (u, "(I0,'|')", advance="no") prt%pdg end if end select select case (prt%type) case (PRT_BEAM, PRT_INCOMING, PRT_OUTGOING, PRT_COMPOSITE) if (prt%colorized) then write (u, "(*(I0,:,','))", advance="no") prt%col write (u, "('/')", advance="no") write (u, "(*(I0,:,','))", advance="no") prt%acl write (u, "('|')", advance="no") end if end select select case (prt%type) case (PRT_BEAM, PRT_INCOMING, PRT_OUTGOING, PRT_COMPOSITE) write (u, "(" // FMT_14 // ",';'," // FMT_14 // ",','," // & FMT_14 // ",','," // FMT_14 // ")", advance="no") tmp%p write (u, "('|'," // fmt // ")", advance="no") tmp%p2 end select if (allocated (prt%src)) then write (u, "('|')", advance="no") do i = 1, size (prt%src) write (u, "(1x,I0)", advance="no") prt%src(i) end do end if if (prt%is_b_jet) then write (u, "('|b jet')", advance="no") end if if (prt%is_c_jet) then write (u, "('|c jet')", advance="no") end if write (u, "(A)") ")" end subroutine prt_write @ %def prt_write @ \subsubsection{Tools} Two particles match if their [[src]] arrays are the same. <>= public :: operator(.match.) <>= interface operator(.match.) module procedure prt_match end interface @ %def .match. <>= elemental module function prt_match (prt1, prt2) result (match) logical :: match type(prt_t), intent(in) :: prt1, prt2 end function prt_match <>= elemental module function prt_match (prt1, prt2) result (match) logical :: match type(prt_t), intent(in) :: prt1, prt2 if (size (prt1%src) == size (prt2%src)) then match = all (prt1%src == prt2%src) else match = .false. end if end function prt_match @ %def prt_match @ The combine operation makes a pseudoparticle whose momentum is the result of adding (the momenta of) the pair of input particles. We trace the particles from which a particle is built by storing a [[src]] array. Each particle entry in the [[src]] list contains a list of indices which indicates its building blocks. The indices refer to an original list of particles. Index lists are sorted, and they contain no element more than once. We thus require that in a given pseudoparticle, each original particle occurs at most once. The result is intent(inout), so it will not be initialized when the subroutine is entered. If the particles carry color, we recall that the combined particle is a composite which is understood as outgoing. If one of the arguments is an incoming particle, is color entries must be reversed. <>= subroutine prt_combine (prt, prt_in1, prt_in2, ok) type(prt_t), intent(inout) :: prt type(prt_t), intent(in) :: prt_in1, prt_in2 logical :: ok integer, dimension(:), allocatable :: src integer, dimension(:), allocatable :: col1, acl1, col2, acl2 call combine_index_lists (src, prt_in1%src, prt_in2%src) ok = allocated (src) if (ok) then call prt_init_composite (prt, prt_in1%p + prt_in2%p, src) if (prt_in1%colorized .or. prt_in2%colorized) then select case (prt_in1%type) case default call prt_get_color_indices (prt_in1, col1, acl1) case (PRT_BEAM, PRT_INCOMING) call prt_get_color_indices (prt_in1, acl1, col1) end select select case (prt_in2%type) case default call prt_get_color_indices (prt_in2, col2, acl2) case (PRT_BEAM, PRT_INCOMING) call prt_get_color_indices (prt_in2, acl2, col2) end select call prt_colorize (prt, [col1, col2], [acl1, acl2]) end if end if end subroutine prt_combine @ %def prt_combine @ This variant does not produce the combined particle, it just checks whether the combination is valid (no common [[src]] entry). <>= public :: are_disjoint <>= module function are_disjoint (prt_in1, prt_in2) result (flag) logical :: flag type(prt_t), intent(in) :: prt_in1, prt_in2 end function are_disjoint <>= module function are_disjoint (prt_in1, prt_in2) result (flag) logical :: flag type(prt_t), intent(in) :: prt_in1, prt_in2 flag = index_lists_are_disjoint (prt_in1%src, prt_in2%src) end function are_disjoint @ %def are_disjoint @ [[src]] Lists with length $>1$ are built by a [[combine]] operation which merges the lists in a sorted manner. If the result would have a duplicate entry, it is discarded, and the result is unallocated. <>= subroutine combine_index_lists (res, src1, src2) integer, dimension(:), intent(in) :: src1, src2 integer, dimension(:), allocatable :: res integer :: i1, i2, i allocate (res (size (src1) + size (src2))) if (size (src1) == 0) then res = src2 return else if (size (src2) == 0) then res = src1 return end if i1 = 1 i2 = 1 LOOP: do i = 1, size (res) if (src1(i1) < src2(i2)) then res(i) = src1(i1); i1 = i1 + 1 if (i1 > size (src1)) then res(i+1:) = src2(i2:) exit LOOP end if else if (src1(i1) > src2(i2)) then res(i) = src2(i2); i2 = i2 + 1 if (i2 > size (src2)) then res(i+1:) = src1(i1:) exit LOOP end if else deallocate (res) exit LOOP end if end do LOOP end subroutine combine_index_lists @ %def combine_index_lists @ This function is similar, but it does not actually merge the list, it just checks whether they are disjoint (no common [[src]] entry). <>= function index_lists_are_disjoint (src1, src2) result (flag) logical :: flag integer, dimension(:), intent(in) :: src1, src2 integer :: i1, i2, i flag = .true. i1 = 1 i2 = 1 LOOP: do i = 1, size (src1) + size (src2) if (src1(i1) < src2(i2)) then i1 = i1 + 1 if (i1 > size (src1)) then exit LOOP end if else if (src1(i1) > src2(i2)) then i2 = i2 + 1 if (i2 > size (src2)) then exit LOOP end if else flag = .false. exit LOOP end if end do LOOP end function index_lists_are_disjoint @ %def index_lists_are_disjoint @ \subsection{subevents} Particles are collected in subevents. This type is implemented as a dynamically allocated array, which need not be completely filled. The value [[n_active]] determines the number of meaningful entries. \subsubsection{Type definition} <>= public :: subevt_t <>= type :: subevt_t private integer :: n_active = 0 type(prt_t), dimension(:), allocatable :: prt contains <> end type subevt_t @ %def subevt_t @ Initialize, allocating with size zero (default) or given size. The number of contained particles is set equal to the size. <>= public :: subevt_init <>= module subroutine subevt_init (subevt, n_active) type(subevt_t), intent(out) :: subevt integer, intent(in), optional :: n_active end subroutine subevt_init <>= module subroutine subevt_init (subevt, n_active) type(subevt_t), intent(out) :: subevt integer, intent(in), optional :: n_active if (present (n_active)) subevt%n_active = n_active allocate (subevt%prt (subevt%n_active)) end subroutine subevt_init @ %def subevt_init @ (Re-)allocate the subevent with some given size. If the size is greater than the previous one, do a real reallocation. Otherwise, just reset the recorded size. Contents are untouched, but become invalid. <>= procedure :: reset => subevt_reset <>= module subroutine subevt_reset (subevt, n_active) class(subevt_t), intent(inout) :: subevt integer, intent(in) :: n_active end subroutine subevt_reset <>= module subroutine subevt_reset (subevt, n_active) class(subevt_t), intent(inout) :: subevt integer, intent(in) :: n_active subevt%n_active = n_active if (subevt%n_active > size (subevt%prt)) then deallocate (subevt%prt) allocate (subevt%prt (subevt%n_active)) end if end subroutine subevt_reset @ %def subevt_reset @ Output. No prefix for the headline 'subevt', because this will usually be printed appending to a previous line. <>= procedure :: write => subevt_write <>= module subroutine subevt_write (object, unit, prefix, pacified) class(subevt_t), intent(in) :: object integer, intent(in), optional :: unit character(*), intent(in), optional :: prefix logical, intent(in), optional :: pacified end subroutine subevt_write <>= module subroutine subevt_write (object, unit, prefix, pacified) class(subevt_t), intent(in) :: object integer, intent(in), optional :: unit character(*), intent(in), optional :: prefix logical, intent(in), optional :: pacified integer :: u, i u = given_output_unit (unit); if (u < 0) return write (u, "(1x,A)") "subevent:" do i = 1, object%n_active if (present (prefix)) write (u, "(A)", advance="no") prefix write (u, "(1x,I0)", advance="no") i call prt_write (object%prt(i), unit = unit, testflag = pacified) end do end subroutine subevt_write @ %def subevt_write @ Defined assignment: transfer only meaningful entries. This is a deep copy (as would be default assignment). <>= interface assignment(=) module procedure subevt_assign end interface @ %def = <>= module subroutine subevt_assign (subevt, subevt_in) type(subevt_t), intent(inout) :: subevt type(subevt_t), intent(in) :: subevt_in end subroutine subevt_assign <>= module subroutine subevt_assign (subevt, subevt_in) type(subevt_t), intent(inout) :: subevt type(subevt_t), intent(in) :: subevt_in if (.not. allocated (subevt%prt)) then call subevt_init (subevt, subevt_in%n_active) else call subevt%reset (subevt_in%n_active) end if subevt%prt(:subevt%n_active) = subevt_in%prt(:subevt%n_active) end subroutine subevt_assign @ %def subevt_assign @ \subsubsection{Fill contents} Store incoming/outgoing particles which are completely defined. <>= <>= procedure :: set_beam => subevt_set_beam procedure :: set_composite => subevt_set_composite procedure :: set_incoming => subevt_set_incoming procedure :: set_outgoing => subevt_set_outgoing <>= module subroutine subevt_set_beam (subevt, i, pdg, p, p2, src) class(subevt_t), intent(inout) :: subevt integer, intent(in) :: i integer, intent(in) :: pdg type(vector4_t), intent(in) :: p real(default), intent(in) :: p2 integer, dimension(:), intent(in), optional :: src end subroutine subevt_set_beam module subroutine subevt_set_incoming (subevt, i, pdg, p, p2, src) class(subevt_t), intent(inout) :: subevt integer, intent(in) :: i integer, intent(in) :: pdg type(vector4_t), intent(in) :: p real(default), intent(in) :: p2 integer, dimension(:), intent(in), optional :: src end subroutine subevt_set_incoming module subroutine subevt_set_outgoing (subevt, i, pdg, p, p2, src) class(subevt_t), intent(inout) :: subevt integer, intent(in) :: i integer, intent(in) :: pdg type(vector4_t), intent(in) :: p real(default), intent(in) :: p2 integer, dimension(:), intent(in), optional :: src end subroutine subevt_set_outgoing module subroutine subevt_set_composite (subevt, i, p, src) class(subevt_t), intent(inout) :: subevt integer, intent(in) :: i type(vector4_t), intent(in) :: p integer, dimension(:), intent(in) :: src end subroutine subevt_set_composite <>= module subroutine subevt_set_beam (subevt, i, pdg, p, p2, src) class(subevt_t), intent(inout) :: subevt integer, intent(in) :: i integer, intent(in) :: pdg type(vector4_t), intent(in) :: p real(default), intent(in) :: p2 integer, dimension(:), intent(in), optional :: src if (present (src)) then call prt_init_beam (subevt%prt(i), pdg, p, p2, src) else call prt_init_beam (subevt%prt(i), pdg, p, p2, [i]) end if end subroutine subevt_set_beam module subroutine subevt_set_incoming (subevt, i, pdg, p, p2, src) class(subevt_t), intent(inout) :: subevt integer, intent(in) :: i integer, intent(in) :: pdg type(vector4_t), intent(in) :: p real(default), intent(in) :: p2 integer, dimension(:), intent(in), optional :: src if (present (src)) then call prt_init_incoming (subevt%prt(i), pdg, p, p2, src) else call prt_init_incoming (subevt%prt(i), pdg, p, p2, [i]) end if end subroutine subevt_set_incoming module subroutine subevt_set_outgoing (subevt, i, pdg, p, p2, src) class(subevt_t), intent(inout) :: subevt integer, intent(in) :: i integer, intent(in) :: pdg type(vector4_t), intent(in) :: p real(default), intent(in) :: p2 integer, dimension(:), intent(in), optional :: src if (present (src)) then call prt_init_outgoing (subevt%prt(i), pdg, p, p2, src) else call prt_init_outgoing (subevt%prt(i), pdg, p, p2, [i]) end if end subroutine subevt_set_outgoing module subroutine subevt_set_composite (subevt, i, p, src) class(subevt_t), intent(inout) :: subevt integer, intent(in) :: i type(vector4_t), intent(in) :: p integer, dimension(:), intent(in) :: src call prt_init_composite (subevt%prt(i), p, src) end subroutine subevt_set_composite @ %def subevt_set_incoming subevt_set_outgoing subevt_set_composite @ Separately assign flavors, simultaneously for all incoming/outgoing particles. <>= procedure :: set_pdg_beam => subevt_set_pdg_beam procedure :: set_pdg_incoming => subevt_set_pdg_incoming procedure :: set_pdg_outgoing => subevt_set_pdg_outgoing <>= module subroutine subevt_set_pdg_beam (subevt, pdg) class(subevt_t), intent(inout) :: subevt integer, dimension(:), intent(in) :: pdg end subroutine subevt_set_pdg_beam module subroutine subevt_set_pdg_incoming (subevt, pdg) class(subevt_t), intent(inout) :: subevt integer, dimension(:), intent(in) :: pdg end subroutine subevt_set_pdg_incoming module subroutine subevt_set_pdg_outgoing (subevt, pdg) class(subevt_t), intent(inout) :: subevt integer, dimension(:), intent(in) :: pdg end subroutine subevt_set_pdg_outgoing <>= module subroutine subevt_set_pdg_beam (subevt, pdg) class(subevt_t), intent(inout) :: subevt integer, dimension(:), intent(in) :: pdg integer :: i, j j = 1 do i = 1, subevt%n_active if (subevt%prt(i)%type == PRT_BEAM) then call prt_set_pdg (subevt%prt(i), pdg(j)) j = j + 1 if (j > size (pdg)) exit end if end do end subroutine subevt_set_pdg_beam module subroutine subevt_set_pdg_incoming (subevt, pdg) class(subevt_t), intent(inout) :: subevt integer, dimension(:), intent(in) :: pdg integer :: i, j j = 1 do i = 1, subevt%n_active if (subevt%prt(i)%type == PRT_INCOMING) then call prt_set_pdg (subevt%prt(i), pdg(j)) j = j + 1 if (j > size (pdg)) exit end if end do end subroutine subevt_set_pdg_incoming module subroutine subevt_set_pdg_outgoing (subevt, pdg) class(subevt_t), intent(inout) :: subevt integer, dimension(:), intent(in) :: pdg integer :: i, j j = 1 do i = 1, subevt%n_active if (subevt%prt(i)%type == PRT_OUTGOING) then call prt_set_pdg (subevt%prt(i), pdg(j)) j = j + 1 if (j > size (pdg)) exit end if end do end subroutine subevt_set_pdg_outgoing @ %def subevt_set_pdg_beam @ %def subevt_set_pdg_incoming @ %def subevt_set_pdg_outgoing @ Separately assign momenta, simultaneously for all incoming/outgoing particles. <>= procedure :: set_p_beam => subevt_set_p_beam procedure :: set_p_incoming => subevt_set_p_incoming procedure :: set_p_outgoing => subevt_set_p_outgoing <>= module subroutine subevt_set_p_beam (subevt, p) class(subevt_t), intent(inout) :: subevt type(vector4_t), dimension(:), intent(in) :: p end subroutine subevt_set_p_beam module subroutine subevt_set_p_incoming (subevt, p) class(subevt_t), intent(inout) :: subevt type(vector4_t), dimension(:), intent(in) :: p end subroutine subevt_set_p_incoming module subroutine subevt_set_p_outgoing (subevt, p) class(subevt_t), intent(inout) :: subevt type(vector4_t), dimension(:), intent(in) :: p end subroutine subevt_set_p_outgoing <>= module subroutine subevt_set_p_beam (subevt, p) class(subevt_t), intent(inout) :: subevt type(vector4_t), dimension(:), intent(in) :: p integer :: i, j j = 1 do i = 1, subevt%n_active if (subevt%prt(i)%type == PRT_BEAM) then call prt_set_p (subevt%prt(i), p(j)) j = j + 1 if (j > size (p)) exit end if end do end subroutine subevt_set_p_beam module subroutine subevt_set_p_incoming (subevt, p) class(subevt_t), intent(inout) :: subevt type(vector4_t), dimension(:), intent(in) :: p integer :: i, j j = 1 do i = 1, subevt%n_active if (subevt%prt(i)%type == PRT_INCOMING) then call prt_set_p (subevt%prt(i), p(j)) j = j + 1 if (j > size (p)) exit end if end do end subroutine subevt_set_p_incoming module subroutine subevt_set_p_outgoing (subevt, p) class(subevt_t), intent(inout) :: subevt type(vector4_t), dimension(:), intent(in) :: p integer :: i, j j = 1 do i = 1, subevt%n_active if (subevt%prt(i)%type == PRT_OUTGOING) then call prt_set_p (subevt%prt(i), p(j)) j = j + 1 if (j > size (p)) exit end if end do end subroutine subevt_set_p_outgoing @ %def subevt_set_p_beam @ %def subevt_set_p_incoming @ %def subevt_set_p_outgoing @ Separately assign the squared invariant mass, simultaneously for all incoming/outgoing particles. <>= procedure :: set_p2_beam => subevt_set_p2_beam procedure :: set_p2_incoming => subevt_set_p2_incoming procedure :: set_p2_outgoing => subevt_set_p2_outgoing <>= module subroutine subevt_set_p2_beam (subevt, p2) class(subevt_t), intent(inout) :: subevt real(default), dimension(:), intent(in) :: p2 end subroutine subevt_set_p2_beam module subroutine subevt_set_p2_incoming (subevt, p2) class(subevt_t), intent(inout) :: subevt real(default), dimension(:), intent(in) :: p2 end subroutine subevt_set_p2_incoming module subroutine subevt_set_p2_outgoing (subevt, p2) class(subevt_t), intent(inout) :: subevt real(default), dimension(:), intent(in) :: p2 end subroutine subevt_set_p2_outgoing <>= module subroutine subevt_set_p2_beam (subevt, p2) class(subevt_t), intent(inout) :: subevt real(default), dimension(:), intent(in) :: p2 integer :: i, j j = 1 do i = 1, subevt%n_active if (subevt%prt(i)%type == PRT_BEAM) then call prt_set_p2 (subevt%prt(i), p2(j)) j = j + 1 if (j > size (p2)) exit end if end do end subroutine subevt_set_p2_beam module subroutine subevt_set_p2_incoming (subevt, p2) class(subevt_t), intent(inout) :: subevt real(default), dimension(:), intent(in) :: p2 integer :: i, j j = 1 do i = 1, subevt%n_active if (subevt%prt(i)%type == PRT_INCOMING) then call prt_set_p2 (subevt%prt(i), p2(j)) j = j + 1 if (j > size (p2)) exit end if end do end subroutine subevt_set_p2_incoming module subroutine subevt_set_p2_outgoing (subevt, p2) class(subevt_t), intent(inout) :: subevt real(default), dimension(:), intent(in) :: p2 integer :: i, j j = 1 do i = 1, subevt%n_active if (subevt%prt(i)%type == PRT_OUTGOING) then call prt_set_p2 (subevt%prt(i), p2(j)) j = j + 1 if (j > size (p2)) exit end if end do end subroutine subevt_set_p2_outgoing @ %def subevt_set_p2_beam @ %def subevt_set_p2_incoming @ %def subevt_set_p2_outgoing @ Set polarization for an entry <>= public :: subevt_polarize <>= module subroutine subevt_polarize (subevt, i, h) type(subevt_t), intent(inout) :: subevt integer, intent(in) :: i, h end subroutine subevt_polarize <>= module subroutine subevt_polarize (subevt, i, h) type(subevt_t), intent(inout) :: subevt integer, intent(in) :: i, h call prt_polarize (subevt%prt(i), h) end subroutine subevt_polarize @ %def subevt_polarize @ Set color-flow indices for an entry <>= public :: subevt_colorize <>= module subroutine subevt_colorize (subevt, i, col, acl) type(subevt_t), intent(inout) :: subevt integer, intent(in) :: i, col, acl end subroutine subevt_colorize <>= module subroutine subevt_colorize (subevt, i, col, acl) type(subevt_t), intent(inout) :: subevt integer, intent(in) :: i, col, acl if (col > 0 .and. acl > 0) then call prt_colorize (subevt%prt(i), [col], [acl]) else if (col > 0) then call prt_colorize (subevt%prt(i), [col], [integer ::]) else if (acl > 0) then call prt_colorize (subevt%prt(i), [integer ::], [acl]) else call prt_colorize (subevt%prt(i), [integer ::], [integer ::]) end if end subroutine subevt_colorize @ %def subevt_colorize @ \subsubsection{Accessing contents} Return true if the subevent has entries. <>= procedure :: is_nonempty => subevt_is_nonempty <>= module function subevt_is_nonempty (subevt) result (flag) logical :: flag class(subevt_t), intent(in) :: subevt end function subevt_is_nonempty <>= module function subevt_is_nonempty (subevt) result (flag) logical :: flag class(subevt_t), intent(in) :: subevt flag = subevt%n_active /= 0 end function subevt_is_nonempty @ %def subevt_is_nonempty @ Return the number of entries <>= procedure :: get_length => subevt_get_length <>= module function subevt_get_length (subevt) result (length) integer :: length class(subevt_t), intent(in) :: subevt end function subevt_get_length <>= module function subevt_get_length (subevt) result (length) integer :: length class(subevt_t), intent(in) :: subevt length = subevt%n_active end function subevt_get_length @ %def subevt_get_length @ Return a specific particle. The index is not checked for validity. <>= procedure :: get_prt => subevt_get_prt <>= module function subevt_get_prt (subevt, i) result (prt) type(prt_t) :: prt class(subevt_t), intent(in) :: subevt integer, intent(in) :: i end function subevt_get_prt <>= module function subevt_get_prt (subevt, i) result (prt) type(prt_t) :: prt class(subevt_t), intent(in) :: subevt integer, intent(in) :: i prt = subevt%prt(i) end function subevt_get_prt @ %def subevt_get_prt @ Return the partonic energy squared. We take the particles with flag [[PRT_INCOMING]] and compute their total invariant mass. <>= procedure :: get_sqrts_hat => subevt_get_sqrts_hat <>= module function subevt_get_sqrts_hat (subevt) result (sqrts_hat) class(subevt_t), intent(in) :: subevt real(default) :: sqrts_hat end function subevt_get_sqrts_hat <>= module function subevt_get_sqrts_hat (subevt) result (sqrts_hat) class(subevt_t), intent(in) :: subevt real(default) :: sqrts_hat type(vector4_t) :: p integer :: i do i = 1, subevt%n_active if (subevt%prt(i)%type == PRT_INCOMING) then p = p + prt_get_momentum (subevt%prt(i)) end if end do sqrts_hat = p ** 1 end function subevt_get_sqrts_hat @ %def subevt_get_sqrts_hat @ Return the number of incoming (outgoing) particles, respectively. Beam particles or composites are not counted. <>= procedure :: get_n_in => subevt_get_n_in procedure :: get_n_out => subevt_get_n_out <>= module function subevt_get_n_in (subevt) result (n_in) class(subevt_t), intent(in) :: subevt integer :: n_in end function subevt_get_n_in module function subevt_get_n_out (subevt) result (n_out) class(subevt_t), intent(in) :: subevt integer :: n_out end function subevt_get_n_out <>= module function subevt_get_n_in (subevt) result (n_in) class(subevt_t), intent(in) :: subevt integer :: n_in n_in = count (subevt%prt(:subevt%n_active)%type == PRT_INCOMING) end function subevt_get_n_in module function subevt_get_n_out (subevt) result (n_out) class(subevt_t), intent(in) :: subevt integer :: n_out n_out = count (subevt%prt(:subevt%n_active)%type == PRT_OUTGOING) end function subevt_get_n_out @ %def subevt_get_n_in @ %def subevt_get_n_out @ <>= interface c_prt module procedure c_prt_from_subevt module procedure c_prt_array_from_subevt end interface @ %def c_prt <>= module function c_prt_from_subevt (subevt, i) result (c_prt) type(c_prt_t) :: c_prt type(subevt_t), intent(in) :: subevt integer, intent(in) :: i end function c_prt_from_subevt module function c_prt_array_from_subevt (subevt) result (c_prt_array) type(subevt_t), intent(in) :: subevt type(c_prt_t), dimension(subevt%n_active) :: c_prt_array end function c_prt_array_from_subevt <>= module function c_prt_from_subevt (subevt, i) result (c_prt) type(c_prt_t) :: c_prt type(subevt_t), intent(in) :: subevt integer, intent(in) :: i c_prt = c_prt_from_prt (subevt%prt(i)) end function c_prt_from_subevt module function c_prt_array_from_subevt (subevt) result (c_prt_array) type(subevt_t), intent(in) :: subevt type(c_prt_t), dimension(subevt%n_active) :: c_prt_array c_prt_array = c_prt_from_prt (subevt%prt(1:subevt%n_active)) end function c_prt_array_from_subevt @ %def c_prt_from_subevt @ %def c_prt_array_from_subevt @ \subsubsection{Operations with subevents} The join operation joins two subevents. When appending the elements of the second list, we check for each particle whether it is already in the first list. If yes, it is discarded. The result list should be initialized already. If a mask is present, it refers to the second subevent. Particles where the mask is not set are discarded. <>= public :: subevt_join <>= module subroutine subevt_join (subevt, pl1, pl2, mask2) type(subevt_t), intent(inout) :: subevt type(subevt_t), intent(in) :: pl1, pl2 logical, dimension(:), intent(in), optional :: mask2 end subroutine subevt_join <>= module subroutine subevt_join (subevt, pl1, pl2, mask2) type(subevt_t), intent(inout) :: subevt type(subevt_t), intent(in) :: pl1, pl2 logical, dimension(:), intent(in), optional :: mask2 integer :: n1, n2, i, n n1 = pl1%n_active n2 = pl2%n_active call subevt%reset (n1 + n2) subevt%prt(:n1) = pl1%prt(:n1) n = n1 if (present (mask2)) then do i = 1, pl2%n_active if (mask2(i)) then if (disjoint (i)) then n = n + 1 subevt%prt(n) = pl2%prt(i) end if end if end do else do i = 1, pl2%n_active if (disjoint (i)) then n = n + 1 subevt%prt(n) = pl2%prt(i) end if end do end if subevt%n_active = n contains function disjoint (i) result (flag) integer, intent(in) :: i logical :: flag integer :: j do j = 1, pl1%n_active if (.not. are_disjoint (pl1%prt(j), pl2%prt(i))) then flag = .false. return end if end do flag = .true. end function disjoint end subroutine subevt_join @ %def subevt_join @ The combine operation makes a subevent whose entries are the result of adding (the momenta of) each pair of particles in the input lists. We trace the particles from which a particles is built by storing a [[src]] array. Each particle entry in the [[src]] list contains a list of indices which indicates its building blocks. The indices refer to an original list of particles. Index lists are sorted, and they contain no element more than once. We thus require that in a given pseudoparticle, each original particle occurs at most once. <>= public :: subevt_combine <>= module subroutine subevt_combine (subevt, pl1, pl2, mask12) type(subevt_t), intent(inout) :: subevt type(subevt_t), intent(in) :: pl1, pl2 logical, dimension(:,:), intent(in), optional :: mask12 end subroutine subevt_combine <>= module subroutine subevt_combine (subevt, pl1, pl2, mask12) type(subevt_t), intent(inout) :: subevt type(subevt_t), intent(in) :: pl1, pl2 logical, dimension(:,:), intent(in), optional :: mask12 integer :: n1, n2, i1, i2, n, j logical :: ok n1 = pl1%n_active n2 = pl2%n_active call subevt%reset (n1 * n2) n = 1 do i1 = 1, n1 do i2 = 1, n2 if (present (mask12)) then ok = mask12(i1,i2) else ok = .true. end if if (ok) call prt_combine & (subevt%prt(n), pl1%prt(i1), pl2%prt(i2), ok) if (ok) then CHECK_DOUBLES: do j = 1, n - 1 if (subevt%prt(n) .match. subevt%prt(j)) then ok = .false.; exit CHECK_DOUBLES end if end do CHECK_DOUBLES if (ok) n = n + 1 end if end do end do subevt%n_active = n - 1 end subroutine subevt_combine @ %def subevt_combine @ The collect operation makes a single-entry subevent which results from combining (the momenta of) all particles in the input list. As above, the result does not contain an original particle more than once; this is checked for each particle when it is collected. Furthermore, each entry has a mask; where the mask is false, the entry is dropped. (Thus, if the input particles are already composite, there is some chance that the result depends on the order of the input list and is not as expected. This situation should be avoided.) <>= public :: subevt_collect <>= module subroutine subevt_collect (subevt, pl1, mask1) type(subevt_t), intent(inout) :: subevt type(subevt_t), intent(in) :: pl1 logical, dimension(:), intent(in) :: mask1 end subroutine subevt_collect <>= module subroutine subevt_collect (subevt, pl1, mask1) type(subevt_t), intent(inout) :: subevt type(subevt_t), intent(in) :: pl1 logical, dimension(:), intent(in) :: mask1 type(prt_t) :: prt integer :: i logical :: ok call subevt%reset (1) subevt%n_active = 0 do i = 1, pl1%n_active if (mask1(i)) then if (subevt%n_active == 0) then subevt%n_active = 1 subevt%prt(1) = pl1%prt(i) else call prt_combine (prt, subevt%prt(1), pl1%prt(i), ok) if (ok) subevt%prt(1) = prt end if end if end do end subroutine subevt_collect @ %def subevt_collect @ The cluster operation is similar to [[collect]], but applies a jet algorithm. The result is a subevent consisting of jets and, possibly, unclustered extra particles. As above, the result does not contain an original particle more than once; this is checked for each particle when it is collected. Furthermore, each entry has a mask; where the mask is false, the entry is dropped. The algorithm: first determine the (pseudo)particles that participate in the clustering. They should not overlap, and the mask entry must be set. We then cluster the particles, using the given jet definition. The result particles are retrieved from the cluster sequence. We still have to determine the source indices for each jet: for each input particle, we get the jet index. Accumulating the source entries for all particles that are part of a given jet, we derive the jet source entries. Finally, we delete the C structures that have been constructed by FastJet and its interface. <>= public :: subevt_cluster <>= module subroutine subevt_cluster (subevt, pl1, dcut, mask1, jet_def, & keep_jets, exclusive) type(subevt_t), intent(inout) :: subevt type(subevt_t), intent(in) :: pl1 real(default), intent(in) :: dcut logical, dimension(:), intent(in) :: mask1 type(jet_definition_t), intent(in) :: jet_def logical, intent(in) :: keep_jets, exclusive end subroutine subevt_cluster <>= module subroutine subevt_cluster (subevt, pl1, dcut, mask1, jet_def, & keep_jets, exclusive) type(subevt_t), intent(inout) :: subevt type(subevt_t), intent(in) :: pl1 real(default), intent(in) :: dcut logical, dimension(:), intent(in) :: mask1 type(jet_definition_t), intent(in) :: jet_def logical, intent(in) :: keep_jets, exclusive integer, dimension(:), allocatable :: map, jet_index type(pseudojet_t), dimension(:), allocatable :: jet_in, jet_out type(pseudojet_vector_t) :: jv_in, jv_out type(cluster_sequence_t) :: cs integer :: i, n_src, n_active call map_prt_index (pl1, mask1, n_src, map) n_active = count (map /= 0) allocate (jet_in (n_active)) allocate (jet_index (n_active)) do i = 1, n_active call jet_in(i)%init (prt_get_momentum (pl1%prt(map(i)))) end do call jv_in%init (jet_in) call cs%init (jv_in, jet_def) if (exclusive) then jv_out = cs%exclusive_jets (dcut) else jv_out = cs%inclusive_jets () end if call cs%assign_jet_indices (jv_out, jet_index) allocate (jet_out (jv_out%size ())) jet_out = jv_out call fill_pseudojet (subevt, pl1, jet_out, jet_index, n_src, map) do i = 1, size (jet_out) call jet_out(i)%final () end do call jv_out%final () call cs%final () call jv_in%final () do i = 1, size (jet_in) call jet_in(i)%final () end do contains ! Uniquely combine sources and add map those new indices to the old ones subroutine map_prt_index (pl1, mask1, n_src, map) type(subevt_t), intent(in) :: pl1 logical, dimension(:), intent(in) :: mask1 integer, intent(out) :: n_src integer, dimension(:), allocatable, intent(out) :: map integer, dimension(:), allocatable :: src, src_tmp integer :: i allocate (src(0)) allocate (map (pl1%n_active), source = 0) n_active = 0 do i = 1, pl1%n_active if (.not. mask1(i)) cycle call combine_index_lists (src_tmp, src, pl1%prt(i)%src) if (.not. allocated (src_tmp)) cycle call move_alloc (from=src_tmp, to=src) n_active = n_active + 1 map(n_active) = i end do n_src = size (src) end subroutine map_prt_index ! Retrieve source(s) of a jet and fill corresponding subevent subroutine fill_pseudojet (subevt, pl1, jet_out, jet_index, n_src, map) type(subevt_t), intent(inout) :: subevt type(subevt_t), intent(in) :: pl1 type(pseudojet_t), dimension(:), intent(in) :: jet_out integer, dimension(:), intent(in) :: jet_index integer, dimension(:), intent(in) :: map integer, intent(in) :: n_src integer, dimension(n_src) :: src_fill integer :: i, jet, k, combined_pdg, pdg, n_quarks, n_src_fill logical :: is_b, is_c call subevt%reset (size (jet_out)) do jet = 1, size (jet_out) pdg = 0; src_fill = 0; n_src_fill = 0; combined_pdg = 0; n_quarks = 0 is_b = .false.; is_c = .false. PARTICLE: do i = 1, size (jet_index) if (jet_index(i) /= jet) cycle PARTICLE associate (prt => pl1%prt(map(i)), n_src_prt => size(pl1%prt(map(i))%src)) do k = 1, n_src_prt src_fill(n_src_fill + k) = prt%src(k) end do n_src_fill = n_src_fill + n_src_prt if (is_quark (prt%pdg)) then n_quarks = n_quarks + 1 if (.not. is_b) then if (abs (prt%pdg) == 5) then is_b = .true. is_c = .false. else if (abs (prt%pdg) == 4) then is_c = .true. end if end if if (combined_pdg == 0) combined_pdg = prt%pdg end if end associate end do PARTICLE if (keep_jets .and. n_quarks == 1) pdg = combined_pdg call prt_init_pseudojet (subevt%prt(jet), jet_out(jet), & src_fill(:n_src_fill), pdg, is_b, is_c) end do end subroutine fill_pseudojet end subroutine subevt_cluster @ %def subevt_cluster @ Do recombination. The incoming subevent [[pl]] is left unchanged if it either does not contain photons at all, or consists just of a single photon and nothing else or the photon does have a larger $R>R_0$ distance to the nearest other particle or does not fulfill the [[mask1]] condition. Otherwise, the subevent is one entry shorter and contains a single recombined particle whose original flavor is kept depending on the setting [[keep_flv]]. When this subroutine is called, it is explicitly assumed that there is only one photon. For the moment, we take here the first photon from the subevent to possibly recombine and leave this open for generalization. <>= public :: subevt_recombine <>= module subroutine subevt_recombine (subevt, pl, mask1, reco_r0, keep_flv) type(subevt_t), intent(inout) :: subevt type(subevt_t), intent(in) :: pl logical, dimension(:), intent(in) :: mask1 logical, intent(in) :: keep_flv real(default), intent(in) :: reco_r0 end subroutine subevt_recombine <>= module subroutine subevt_recombine (subevt, pl, mask1, reco_r0, keep_flv) type(subevt_t), intent(inout) :: subevt type(subevt_t), intent(in) :: pl type(prt_t), dimension(:), allocatable :: prt_rec logical, dimension(:), intent(in) :: mask1 logical, intent(in) :: keep_flv real(default), intent(in) :: reco_r0 real(default), dimension(:), allocatable :: del_rij integer, dimension(:), allocatable :: i_sortr type(prt_t) :: prt_gam, prt_comb logical :: recombine, ok integer :: i, n, i_gam, n_gam, n_rec, pdg_orig n = pl%get_length () n_gam = 0 FIND_FIRST_PHOTON: do i = 1, n if (prt_is_photon (pl%prt (i))) then n_gam = n_gam + 1 prt_gam = pl%prt (i) i_gam = i exit FIND_FIRST_PHOTON end if end do FIND_FIRST_PHOTON n_rec = n - n_gam if (n_gam == 0) then subevt = pl else if (n_rec > 0) then allocate (prt_rec (n_rec)) do i = 1, n_rec if (i == i_gam) cycle if (i < i_gam) then prt_rec(i) = pl%prt(i) else prt_rec(i) = pl%prt(i+n_gam) end if end do allocate (del_rij (n_rec), i_sortr (n_rec)) del_rij(1:n_rec) = eta_phi_distance(prt_get_momentum (prt_gam), & prt_get_momentum (prt_rec(1:n_rec))) i_sortr = order (del_rij) recombine = del_rij (i_sortr (1)) <= reco_r0 .and. mask1(i_gam) if (recombine) then call subevt%reset (pl%n_active-n_gam) do i = 1, n_rec if (i == i_sortr(1)) then pdg_orig = prt_get_pdg (prt_rec(i_sortr (1))) call prt_combine (prt_comb, prt_gam, prt_rec(i_sortr (1)), ok) if (ok) then subevt%prt(i_sortr (1)) = prt_comb if (keep_flv) call prt_set_pdg & (subevt%prt(i_sortr (1)), pdg_orig) end if else subevt%prt(i) = prt_rec(i) end if end do else subevt = pl end if else subevt = pl end if end if end subroutine subevt_recombine @ %def subevt_recombine @ Return a list of all particles for which the mask is true. <>= public :: subevt_select <>= module subroutine subevt_select (subevt, pl, mask1) type(subevt_t), intent(inout) :: subevt type(subevt_t), intent(in) :: pl logical, dimension(:), intent(in) :: mask1 end subroutine subevt_select <>= module subroutine subevt_select (subevt, pl, mask1) type(subevt_t), intent(inout) :: subevt type(subevt_t), intent(in) :: pl logical, dimension(:), intent(in) :: mask1 integer :: i, n call subevt%reset (pl%n_active) n = 0 do i = 1, pl%n_active if (mask1(i)) then n = n + 1 subevt%prt(n) = pl%prt(i) end if end do subevt%n_active = n end subroutine subevt_select @ %def subevt_select @ Return a subevent which consists of the single particle with specified [[index]]. If [[index]] is negative, count from the end. If it is out of bounds, return an empty list. <>= public :: subevt_extract <>= module subroutine subevt_extract (subevt, pl, index) type(subevt_t), intent(inout) :: subevt type(subevt_t), intent(in) :: pl integer, intent(in) :: index end subroutine subevt_extract <>= module subroutine subevt_extract (subevt, pl, index) type(subevt_t), intent(inout) :: subevt type(subevt_t), intent(in) :: pl integer, intent(in) :: index if (index > 0) then if (index <= pl%n_active) then call subevt%reset (1) subevt%prt(1) = pl%prt(index) else call subevt%reset (0) end if else if (index < 0) then if (abs (index) <= pl%n_active) then call subevt%reset (1) subevt%prt(1) = pl%prt(pl%n_active + 1 + index) else call subevt%reset (0) end if else call subevt%reset (0) end if end subroutine subevt_extract @ %def subevt_extract @ Return the list of particles sorted according to increasing values of the provided integer or real array. If no array is given, sort by PDG value. <>= public :: subevt_sort <>= interface subevt_sort module procedure subevt_sort_pdg module procedure subevt_sort_int module procedure subevt_sort_real end interface <>= module subroutine subevt_sort_pdg (subevt, pl) type(subevt_t), intent(inout) :: subevt type(subevt_t), intent(in) :: pl end subroutine subevt_sort_pdg module subroutine subevt_sort_int (subevt, pl, ival) type(subevt_t), intent(inout) :: subevt type(subevt_t), intent(in) :: pl integer, dimension(:), intent(in) :: ival end subroutine subevt_sort_int module subroutine subevt_sort_real (subevt, pl, rval) type(subevt_t), intent(inout) :: subevt type(subevt_t), intent(in) :: pl real(default), dimension(:), intent(in) :: rval end subroutine subevt_sort_real <>= module subroutine subevt_sort_pdg (subevt, pl) type(subevt_t), intent(inout) :: subevt type(subevt_t), intent(in) :: pl integer :: n n = subevt%n_active call subevt_sort_int (subevt, pl, abs (3 * subevt%prt(:n)%pdg - 1)) end subroutine subevt_sort_pdg module subroutine subevt_sort_int (subevt, pl, ival) type(subevt_t), intent(inout) :: subevt type(subevt_t), intent(in) :: pl integer, dimension(:), intent(in) :: ival call subevt%reset (pl%n_active) subevt%n_active = pl%n_active subevt%prt = pl%prt( order (ival) ) end subroutine subevt_sort_int module subroutine subevt_sort_real (subevt, pl, rval) type(subevt_t), intent(inout) :: subevt type(subevt_t), intent(in) :: pl real(default), dimension(:), intent(in) :: rval integer :: i integer, dimension(size(rval)) :: idx call subevt%reset (pl%n_active) subevt%n_active = pl%n_active if (allocated (subevt%prt)) deallocate (subevt%prt) allocate (subevt%prt (size(pl%prt))) idx = order (rval) do i = 1, size (idx) subevt%prt(i) = pl%prt (idx(i)) end do end subroutine subevt_sort_real @ %def subevt_sort @ Return the list of particles which have any of the specified PDG codes (and optionally particle type: beam, incoming, outgoing). <>= public :: subevt_select_pdg_code <>= module subroutine subevt_select_pdg_code (subevt, aval, subevt_in, prt_type) type(subevt_t), intent(inout) :: subevt type(pdg_array_t), intent(in) :: aval type(subevt_t), intent(in) :: subevt_in integer, intent(in), optional :: prt_type end subroutine subevt_select_pdg_code <>= module subroutine subevt_select_pdg_code (subevt, aval, subevt_in, prt_type) type(subevt_t), intent(inout) :: subevt type(pdg_array_t), intent(in) :: aval type(subevt_t), intent(in) :: subevt_in integer, intent(in), optional :: prt_type integer :: n_active, n_match logical, dimension(:), allocatable :: mask integer :: i, j n_active = subevt_in%n_active allocate (mask (n_active)) forall (i = 1:n_active) & mask(i) = aval .match. subevt_in%prt(i)%pdg if (present (prt_type)) & mask = mask .and. subevt_in%prt(:n_active)%type == prt_type n_match = count (mask) call subevt%reset (n_match) j = 0 do i = 1, n_active if (mask(i)) then j = j + 1 subevt%prt(j) = subevt_in%prt(i) end if end do end subroutine subevt_select_pdg_code @ %def subevt_select_pdg_code @ \subsection{Eliminate numerical noise} This is useful for testing purposes: set entries to zero that are smaller in absolute values than a given tolerance parameter. Note: instead of setting the tolerance in terms of EPSILON (kind-dependent), we fix it to $10^{-16}$, which is the typical value for double precision. The reason is that there are situations where intermediate representations (external libraries, files) are limited to double precision, even if the main program uses higher precision. <>= public :: pacify <>= interface pacify module procedure pacify_prt module procedure pacify_subevt end interface pacify @ %def pacify <>= module subroutine pacify_prt (prt) class(prt_t), intent(inout) :: prt end subroutine pacify_prt module subroutine pacify_subevt (subevt) class(subevt_t), intent(inout) :: subevt end subroutine pacify_subevt <>= module subroutine pacify_prt (prt) class(prt_t), intent(inout) :: prt real(default) :: e e = max (1E-10_default * energy (prt%p), 1E-13_default) call pacify (prt%p, e) call pacify (prt%p2, 1E3_default * e) end subroutine pacify_prt module subroutine pacify_subevt (subevt) class(subevt_t), intent(inout) :: subevt integer :: i do i = 1, subevt%n_active call pacify (subevt%prt(i)) end do end subroutine pacify_subevt @ %def pacify_prt @ %def pacify_subevt @ \clearpage %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Analysis tools} This module defines structures useful for data analysis. These include observables, histograms, and plots. Observables are quantities that are calculated and summed up event by event. At the end, one can compute the average and error. Histograms have their bins in addition to the observable properties. Histograms are usually written out in tables and displayed graphically. In plots, each record creates its own entry in a table. This can be used for scatter plots if called event by event, or for plotting dependencies on parameters if called once per integration run. Graphs are container for histograms and plots, which carry their own graphics options. The type layout is still somewhat obfuscated. This would become much simpler if type extension could be used. <<[[analysis.f90]]>>= <> module analysis <> <> use os_interface <> <> <> <> <> <> interface <> end interface end module analysis @ %def analysis @ <<[[analysis_sub.f90]]>>= <> submodule (analysis) analysis_s use io_units use format_utils, only: quote_underscore, tex_format use system_defs, only: TAB use diagnostics use ifiles implicit none contains <> end submodule analysis_s @ %def analysis_s @ \subsection{Output formats} These formats share a common field width (alignment). <>= character(*), parameter, public :: HISTOGRAM_HEAD_FORMAT = "1x,A15,3x" character(*), parameter, public :: HISTOGRAM_INTG_FORMAT = "3x,I9,3x" character(*), parameter, public :: HISTOGRAM_DATA_FORMAT = "ES19.12" @ %def HISTOGRAM_HEAD_FORMAT HISTOGRAM_INTG_FORMAT HISTOGRAM_DATA_FORMAT @ \subsection{Graph options} These parameters are used for displaying data. They apply to a whole graph, which may contain more than one plot element. The GAMELAN code chunks are part of both [[graph_options]] and [[drawing_options]]. The [[drawing_options]] copy is used in histograms and plots, also as graph elements. The [[graph_options]] copy is used for [[graph]] objects as a whole. Both copies are usually identical. <>= public :: graph_options_t <>= type :: graph_options_t private type(string_t) :: id type(string_t) :: title type(string_t) :: description type(string_t) :: x_label type(string_t) :: y_label integer :: width_mm = 130 integer :: height_mm = 90 logical :: x_log = .false. logical :: y_log = .false. real(default) :: x_min = 0 real(default) :: x_max = 1 real(default) :: y_min = 0 real(default) :: y_max = 1 logical :: x_min_set = .false. logical :: x_max_set = .false. logical :: y_min_set = .false. logical :: y_max_set = .false. type(string_t) :: gmlcode_bg type(string_t) :: gmlcode_fg contains <> end type graph_options_t @ %def graph_options_t @ Initialize the record, all strings are empty. The limits are undefined. <>= procedure :: init => graph_options_init <>= module subroutine graph_options_init (graph_options) class(graph_options_t), intent(out) :: graph_options end subroutine graph_options_init <>= module subroutine graph_options_init (graph_options) class(graph_options_t), intent(out) :: graph_options graph_options%id = "" graph_options%title = "" graph_options%description = "" graph_options%x_label = "" graph_options%y_label = "" graph_options%gmlcode_bg = "" graph_options%gmlcode_fg = "" end subroutine graph_options_init @ %def graph_options_init @ Set individual options. <>= procedure :: set => graph_options_set <>= module subroutine graph_options_set (graph_options, id, & title, description, x_label, y_label, width_mm, height_mm, & x_log, y_log, x_min, x_max, y_min, y_max, & gmlcode_bg, gmlcode_fg) class(graph_options_t), intent(inout) :: graph_options type(string_t), intent(in), optional :: id type(string_t), intent(in), optional :: title type(string_t), intent(in), optional :: description type(string_t), intent(in), optional :: x_label, y_label integer, intent(in), optional :: width_mm, height_mm logical, intent(in), optional :: x_log, y_log real(default), intent(in), optional :: x_min, x_max, y_min, y_max type(string_t), intent(in), optional :: gmlcode_bg, gmlcode_fg end subroutine graph_options_set <>= module subroutine graph_options_set (graph_options, id, & title, description, x_label, y_label, width_mm, height_mm, & x_log, y_log, x_min, x_max, y_min, y_max, & gmlcode_bg, gmlcode_fg) class(graph_options_t), intent(inout) :: graph_options type(string_t), intent(in), optional :: id type(string_t), intent(in), optional :: title type(string_t), intent(in), optional :: description type(string_t), intent(in), optional :: x_label, y_label integer, intent(in), optional :: width_mm, height_mm logical, intent(in), optional :: x_log, y_log real(default), intent(in), optional :: x_min, x_max, y_min, y_max type(string_t), intent(in), optional :: gmlcode_bg, gmlcode_fg if (present (id)) graph_options%id = id if (present (title)) graph_options%title = title if (present (description)) graph_options%description = description if (present (x_label)) graph_options%x_label = x_label if (present (y_label)) graph_options%y_label = y_label if (present (width_mm)) graph_options%width_mm = width_mm if (present (height_mm)) graph_options%height_mm = height_mm if (present (x_log)) graph_options%x_log = x_log if (present (y_log)) graph_options%y_log = y_log if (present (x_min)) graph_options%x_min = x_min if (present (x_max)) graph_options%x_max = x_max if (present (y_min)) graph_options%y_min = y_min if (present (y_max)) graph_options%y_max = y_max if (present (x_min)) graph_options%x_min_set = .true. if (present (x_max)) graph_options%x_max_set = .true. if (present (y_min)) graph_options%y_min_set = .true. if (present (y_max)) graph_options%y_max_set = .true. if (present (gmlcode_bg)) graph_options%gmlcode_bg = gmlcode_bg if (present (gmlcode_fg)) graph_options%gmlcode_fg = gmlcode_fg end subroutine graph_options_set @ %def graph_options_set @ Write a simple account of all options. <>= procedure :: write => graph_options_write <>= module subroutine graph_options_write (gro, unit) class(graph_options_t), intent(in) :: gro integer, intent(in), optional :: unit end subroutine graph_options_write <>= module subroutine graph_options_write (gro, unit) class(graph_options_t), intent(in) :: gro integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) 1 format (A,1x,'"',A,'"') 2 format (A,1x,L1) 3 format (A,1x,ES19.12) 4 format (A,1x,I0) 5 format (A,1x,'[undefined]') write (u, 1) "title =", char (gro%title) write (u, 1) "description =", char (gro%description) write (u, 1) "x_label =", char (gro%x_label) write (u, 1) "y_label =", char (gro%y_label) write (u, 2) "x_log =", gro%x_log write (u, 2) "y_log =", gro%y_log if (gro%x_min_set) then write (u, 3) "x_min =", gro%x_min else write (u, 5) "x_min =" end if if (gro%x_max_set) then write (u, 3) "x_max =", gro%x_max else write (u, 5) "x_max =" end if if (gro%y_min_set) then write (u, 3) "y_min =", gro%y_min else write (u, 5) "y_min =" end if if (gro%y_max_set) then write (u, 3) "y_max =", gro%y_max else write (u, 5) "y_max =" end if write (u, 4) "width_mm =", gro%width_mm write (u, 4) "height_mm =", gro%height_mm write (u, 1) "gmlcode_bg =", char (gro%gmlcode_bg) write (u, 1) "gmlcode_fg =", char (gro%gmlcode_fg) end subroutine graph_options_write @ %def graph_options_write @ Write a \LaTeX\ header/footer for the analysis file. <>= subroutine graph_options_write_tex_header (gro, unit) type(graph_options_t), intent(in) :: gro integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) if (gro%title /= "") then write (u, "(A)") write (u, "(A)") "\section{" // char (gro%title) // "}" else write (u, "(A)") "\section{" // char (quote_underscore (gro%id)) // "}" end if if (gro%description /= "") then write (u, "(A)") char (gro%description) write (u, *) write (u, "(A)") "\vspace*{\baselineskip}" end if write (u, "(A)") "\vspace*{\baselineskip}" write (u, "(A)") "\unitlength 1mm" write (u, "(A,I0,',',I0,A)") & "\begin{gmlgraph*}(", & gro%width_mm, gro%height_mm, & ")[dat]" end subroutine graph_options_write_tex_header subroutine graph_options_write_tex_footer (gro, unit) type(graph_options_t), intent(in) :: gro integer, intent(in), optional :: unit integer :: u, width, height width = gro%width_mm - 10 height = gro%height_mm - 10 u = given_output_unit (unit) write (u, "(A)") " begingmleps ""Whizard-Logo.eps"";" write (u, "(A,I0,A,I0,A)") & " base := (", width, "*unitlength,", height, "*unitlength);" write (u, "(A)") " height := 9.6*unitlength;" write (u, "(A)") " width := 11.2*unitlength;" write (u, "(A)") " endgmleps;" write (u, "(A)") "\end{gmlgraph*}" end subroutine graph_options_write_tex_footer @ %def graph_options_write_tex_header @ %def graph_options_write_tex_footer @ Return the analysis object ID. <>= function graph_options_get_id (gro) result (id) type(string_t) :: id type(graph_options_t), intent(in) :: gro id = gro%id end function graph_options_get_id @ %def graph_options_get_id @ Create an appropriate [[setup]] command (linear/log). <>= function graph_options_get_gml_setup (gro) result (cmd) type(string_t) :: cmd type(graph_options_t), intent(in) :: gro type(string_t) :: x_str, y_str if (gro%x_log) then x_str = "log" else x_str = "linear" end if if (gro%y_log) then y_str = "log" else y_str = "linear" end if cmd = "setup (" // x_str // ", " // y_str // ");" end function graph_options_get_gml_setup @ %def graph_options_get_gml_setup @ Return the labels in GAMELAN form. <>= function graph_options_get_gml_x_label (gro) result (cmd) type(string_t) :: cmd type(graph_options_t), intent(in) :: gro cmd = 'label.bot (<' // '<' // gro%x_label // '>' // '>, out);' end function graph_options_get_gml_x_label function graph_options_get_gml_y_label (gro) result (cmd) type(string_t) :: cmd type(graph_options_t), intent(in) :: gro cmd = 'label.ulft (<' // '<' // gro%y_label // '>' // '>, out);' end function graph_options_get_gml_y_label @ %def graph_options_get_gml_x_label @ %def graph_options_get_gml_y_label @ Create an appropriate [[graphrange]] statement for the given graph options. Where the graph options are not set, use the supplied arguments, if any, otherwise set the undefined value. <>= function graph_options_get_gml_graphrange & (gro, x_min, x_max, y_min, y_max) result (cmd) type(string_t) :: cmd type(graph_options_t), intent(in) :: gro real(default), intent(in), optional :: x_min, x_max, y_min, y_max type(string_t) :: x_min_str, x_max_str, y_min_str, y_max_str character(*), parameter :: fmt = "(ES15.8)" if (gro%x_min_set) then x_min_str = "#" // trim (adjustl (real2string (gro%x_min, fmt))) else if (present (x_min)) then x_min_str = "#" // trim (adjustl (real2string (x_min, fmt))) else x_min_str = "??" end if if (gro%x_max_set) then x_max_str = "#" // trim (adjustl (real2string (gro%x_max, fmt))) else if (present (x_max)) then x_max_str = "#" // trim (adjustl (real2string (x_max, fmt))) else x_max_str = "??" end if if (gro%y_min_set) then y_min_str = "#" // trim (adjustl (real2string (gro%y_min, fmt))) else if (present (y_min)) then y_min_str = "#" // trim (adjustl (real2string (y_min, fmt))) else y_min_str = "??" end if if (gro%y_max_set) then y_max_str = "#" // trim (adjustl (real2string (gro%y_max, fmt))) else if (present (y_max)) then y_max_str = "#" // trim (adjustl (real2string (y_max, fmt))) else y_max_str = "??" end if cmd = "graphrange (" // x_min_str // ", " // y_min_str // "), " & // "(" // x_max_str // ", " // y_max_str // ");" end function graph_options_get_gml_graphrange @ %def graph_options_get_gml_graphrange @ Get extra GAMELAN code to be executed before and after the usual drawing commands. <>= function graph_options_get_gml_bg_command (gro) result (cmd) type(string_t) :: cmd type(graph_options_t), intent(in) :: gro cmd = gro%gmlcode_bg end function graph_options_get_gml_bg_command function graph_options_get_gml_fg_command (gro) result (cmd) type(string_t) :: cmd type(graph_options_t), intent(in) :: gro cmd = gro%gmlcode_fg end function graph_options_get_gml_fg_command @ %def graph_options_get_gml_bg_command @ %def graph_options_get_gml_fg_command @ Append the header for generic data output in ifile format. We print only labels, not graphics parameters. <>= subroutine graph_options_get_header (pl, header, comment) type(graph_options_t), intent(in) :: pl type(ifile_t), intent(inout) :: header type(string_t), intent(in), optional :: comment type(string_t) :: c if (present (comment)) then c = comment else c = "" end if call ifile_append (header, & c // "ID: " // pl%id) call ifile_append (header, & c // "title: " // pl%title) call ifile_append (header, & c // "description: " // pl%description) call ifile_append (header, & c // "x axis label: " // pl%x_label) call ifile_append (header, & c // "y axis label: " // pl%y_label) end subroutine graph_options_get_header @ %def graph_options_get_header @ \subsection{Drawing options} These options apply to an individual graph element (histogram or plot). <>= public :: drawing_options_t <>= type :: drawing_options_t type(string_t) :: dataset logical :: with_hbars = .false. logical :: with_base = .false. logical :: piecewise = .false. logical :: fill = .false. logical :: draw = .false. logical :: err = .false. logical :: symbols = .false. type(string_t) :: fill_options type(string_t) :: draw_options type(string_t) :: err_options type(string_t) :: symbol type(string_t) :: gmlcode_bg type(string_t) :: gmlcode_fg contains <> end type drawing_options_t @ %def drawing_options_t @ Write a simple account of all options. <>= procedure :: write => drawing_options_write <>= module subroutine drawing_options_write (dro, unit) class(drawing_options_t), intent(in) :: dro integer, intent(in), optional :: unit end subroutine drawing_options_write <>= module subroutine drawing_options_write (dro, unit) class(drawing_options_t), intent(in) :: dro integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) 1 format (A,1x,'"',A,'"') 2 format (A,1x,L1) write (u, 2) "with_hbars =", dro%with_hbars write (u, 2) "with_base =", dro%with_base write (u, 2) "piecewise =", dro%piecewise write (u, 2) "fill =", dro%fill write (u, 2) "draw =", dro%draw write (u, 2) "err =", dro%err write (u, 2) "symbols =", dro%symbols write (u, 1) "fill_options=", char (dro%fill_options) write (u, 1) "draw_options=", char (dro%draw_options) write (u, 1) "err_options =", char (dro%err_options) write (u, 1) "symbol =", char (dro%symbol) write (u, 1) "gmlcode_bg =", char (dro%gmlcode_bg) write (u, 1) "gmlcode_fg =", char (dro%gmlcode_fg) end subroutine drawing_options_write @ %def drawing_options_write @ Init with empty strings and default options, appropriate for either histogram or plot. <>= procedure :: init_histogram => drawing_options_init_histogram procedure :: init_plot => drawing_options_init_plot <>= module subroutine drawing_options_init_histogram (dro) class(drawing_options_t), intent(out) :: dro end subroutine drawing_options_init_histogram module subroutine drawing_options_init_plot (dro) class(drawing_options_t), intent(out) :: dro end subroutine drawing_options_init_plot <>= module subroutine drawing_options_init_histogram (dro) class(drawing_options_t), intent(out) :: dro dro%dataset = "dat" dro%with_hbars = .true. dro%with_base = .true. dro%piecewise = .true. dro%fill = .true. dro%draw = .true. dro%fill_options = "withcolor col.default" dro%draw_options = "" dro%err_options = "" dro%symbol = "fshape(circle scaled 1mm)()" dro%gmlcode_bg = "" dro%gmlcode_fg = "" end subroutine drawing_options_init_histogram module subroutine drawing_options_init_plot (dro) class(drawing_options_t), intent(out) :: dro dro%dataset = "dat" dro%draw = .true. dro%fill_options = "withcolor col.default" dro%draw_options = "" dro%err_options = "" dro%symbol = "fshape(circle scaled 1mm)()" dro%gmlcode_bg = "" dro%gmlcode_fg = "" end subroutine drawing_options_init_plot @ %def drawing_options_init_histogram @ %def drawing_options_init_plot @ Set individual options. <>= procedure :: set => drawing_options_set <>= module subroutine drawing_options_set (dro, dataset, & with_hbars, with_base, piecewise, fill, draw, err, symbols, & fill_options, draw_options, err_options, symbol, & gmlcode_bg, gmlcode_fg) class(drawing_options_t), intent(inout) :: dro type(string_t), intent(in), optional :: dataset logical, intent(in), optional :: with_hbars, with_base, piecewise logical, intent(in), optional :: fill, draw, err, symbols type(string_t), intent(in), optional :: fill_options, draw_options type(string_t), intent(in), optional :: err_options, symbol type(string_t), intent(in), optional :: gmlcode_bg, gmlcode_fg end subroutine drawing_options_set <>= module subroutine drawing_options_set (dro, dataset, & with_hbars, with_base, piecewise, fill, draw, err, symbols, & fill_options, draw_options, err_options, symbol, & gmlcode_bg, gmlcode_fg) class(drawing_options_t), intent(inout) :: dro type(string_t), intent(in), optional :: dataset logical, intent(in), optional :: with_hbars, with_base, piecewise logical, intent(in), optional :: fill, draw, err, symbols type(string_t), intent(in), optional :: fill_options, draw_options type(string_t), intent(in), optional :: err_options, symbol type(string_t), intent(in), optional :: gmlcode_bg, gmlcode_fg if (present (dataset)) dro%dataset = dataset if (present (with_hbars)) dro%with_hbars = with_hbars if (present (with_base)) dro%with_base = with_base if (present (piecewise)) dro%piecewise = piecewise if (present (fill)) dro%fill = fill if (present (draw)) dro%draw = draw if (present (err)) dro%err = err if (present (symbols)) dro%symbols = symbols if (present (fill_options)) dro%fill_options = fill_options if (present (draw_options)) dro%draw_options = draw_options if (present (err_options)) dro%err_options = err_options if (present (symbol)) dro%symbol = symbol if (present (gmlcode_bg)) dro%gmlcode_bg = gmlcode_bg if (present (gmlcode_fg)) dro%gmlcode_fg = gmlcode_fg end subroutine drawing_options_set @ %def drawing_options_set @ There are sepate commands for drawing the curve and for drawing errors. The symbols are applied to the latter. First of all, we may have to compute a baseline: <>= function drawing_options_get_calc_command (dro) result (cmd) type(string_t) :: cmd type(drawing_options_t), intent(in) :: dro if (dro%with_base) then cmd = "calculate " // dro%dataset // ".base (" // dro%dataset // ") " & // "(x, #0);" else cmd = "" end if end function drawing_options_get_calc_command @ %def drawing_options_get_calc_command @ Return the drawing command. <>= function drawing_options_get_draw_command (dro) result (cmd) type(string_t) :: cmd type(drawing_options_t), intent(in) :: dro if (dro%fill) then cmd = "fill" else if (dro%draw) then cmd = "draw" else cmd = "" end if if (dro%fill .or. dro%draw) then if (dro%piecewise) cmd = cmd // " piecewise" if (dro%draw .and. dro%with_base) cmd = cmd // " cyclic" cmd = cmd // " from (" // dro%dataset if (dro%with_base) then if (dro%piecewise) then cmd = cmd // ", " // dro%dataset // ".base/\" ! " else cmd = cmd // " ~ " // dro%dataset // ".base\" ! " end if end if cmd = cmd // ")" if (dro%fill) then cmd = cmd // " " // dro%fill_options if (dro%draw) cmd = cmd // " outlined" end if if (dro%draw) cmd = cmd // " " // dro%draw_options cmd = cmd // ";" end if end function drawing_options_get_draw_command @ %def drawing_options_get_draw_command @ The error command draws error bars, if any. <>= function drawing_options_get_err_command (dro) result (cmd) type(string_t) :: cmd type(drawing_options_t), intent(in) :: dro if (dro%err) then cmd = "draw piecewise " & // "from (" // dro%dataset // ".err)" & // " " // dro%err_options // ";" else cmd = "" end if end function drawing_options_get_err_command @ %def drawing_options_get_err_command @ The symbol command draws symbols, if any. <>= function drawing_options_get_symb_command (dro) result (cmd) type(string_t) :: cmd type(drawing_options_t), intent(in) :: dro if (dro%symbols) then cmd = "phantom" & // " from (" // dro%dataset // ")" & // " withsymbol (" // dro%symbol // ");" else cmd = "" end if end function drawing_options_get_symb_command @ %def drawing_options_get_symb_command @ Get extra GAMELAN code to be executed before and after the usual drawing commands. <>= function drawing_options_get_gml_bg_command (dro) result (cmd) type(string_t) :: cmd type(drawing_options_t), intent(in) :: dro cmd = dro%gmlcode_bg end function drawing_options_get_gml_bg_command function drawing_options_get_gml_fg_command (dro) result (cmd) type(string_t) :: cmd type(drawing_options_t), intent(in) :: dro cmd = dro%gmlcode_fg end function drawing_options_get_gml_fg_command @ %def drawing_options_get_gml_bg_command @ %def drawing_options_get_gml_fg_command @ \subsection{Observables} The observable type holds the accumulated observable values and weight sums which are necessary for proper averaging. <>= type :: observable_t private real(default) :: sum_values = 0 real(default) :: sum_squared_values = 0 real(default) :: sum_weights = 0 real(default) :: sum_squared_weights = 0 integer :: count = 0 type(string_t) :: obs_label type(string_t) :: obs_unit type(graph_options_t) :: graph_options end type observable_t @ %def observable_t @ Initialize with defined properties <>= subroutine observable_init (obs, obs_label, obs_unit, graph_options) type(observable_t), intent(out) :: obs type(string_t), intent(in), optional :: obs_label, obs_unit type(graph_options_t), intent(in), optional :: graph_options if (present (obs_label)) then obs%obs_label = obs_label else obs%obs_label = "" end if if (present (obs_unit)) then obs%obs_unit = obs_unit else obs%obs_unit = "" end if if (present (graph_options)) then obs%graph_options = graph_options else call obs%graph_options%init () end if end subroutine observable_init @ %def observable_init @ Reset all numeric entries. <>= subroutine observable_clear (obs) type(observable_t), intent(inout) :: obs obs%sum_values = 0 obs%sum_squared_values = 0 obs%sum_weights = 0 obs%sum_squared_weights = 0 obs%count = 0 end subroutine observable_clear @ %def observable_clear @ Record a value. Always successful for observables. <>= interface observable_record_value module procedure observable_record_value_unweighted module procedure observable_record_value_weighted end interface <>= module subroutine observable_record_value_unweighted (obs, value, success) type(observable_t), intent(inout) :: obs real(default), intent(in) :: value logical, intent(out), optional :: success end subroutine observable_record_value_unweighted module subroutine observable_record_value_weighted (obs, value, weight, success) type(observable_t), intent(inout) :: obs real(default), intent(in) :: value, weight logical, intent(out), optional :: success end subroutine observable_record_value_weighted <>= module subroutine observable_record_value_unweighted (obs, value, success) type(observable_t), intent(inout) :: obs real(default), intent(in) :: value logical, intent(out), optional :: success obs%sum_values = obs%sum_values + value obs%sum_squared_values = obs%sum_squared_values + value**2 obs%sum_weights = obs%sum_weights + 1 obs%sum_squared_weights = obs%sum_squared_weights + 1 obs%count = obs%count + 1 if (present (success)) success = .true. end subroutine observable_record_value_unweighted module subroutine observable_record_value_weighted (obs, value, weight, success) type(observable_t), intent(inout) :: obs real(default), intent(in) :: value, weight logical, intent(out), optional :: success obs%sum_values = obs%sum_values + value * weight obs%sum_squared_values = obs%sum_squared_values + value**2 * weight obs%sum_weights = obs%sum_weights + weight obs%sum_squared_weights = obs%sum_squared_weights + weight**2 obs%count = obs%count + 1 if (present (success)) success = .true. end subroutine observable_record_value_weighted @ %def observable_record_value @ Here are the statistics formulas: \begin{enumerate} \item Unweighted case: Given a sample of $n$ values $x_i$, the average is \begin{equation} \langle x \rangle = \frac{\sum x_i}{n} \end{equation} and the error estimate \begin{align} \Delta x &= \sqrt{\frac{1}{n-1}\langle{\sum(x_i - \langle x\rangle)^2}} \\ &= \sqrt{\frac{1}{n-1} \left(\frac{\sum x_i^2}{n} - \frac{(\sum x_i)^2}{n^2}\right)} \end{align} \item Weighted case: Instead of weight 1, each event comes with weight $w_i$. \begin{equation} \langle x \rangle = \frac{\sum x_i w_i}{\sum w_i} \end{equation} and \begin{equation} \Delta x = \sqrt{\frac{1}{n-1} \left(\frac{\sum x_i^2 w_i}{\sum w_i} - \frac{(\sum x_i w_i)^2}{(\sum w_i)^2}\right)} \end{equation} For $w_i=1$, this specializes to the previous formula. \end{enumerate} <>= function observable_get_n_entries (obs) result (n) integer :: n type(observable_t), intent(in) :: obs n = obs%count end function observable_get_n_entries function observable_get_average (obs) result (avg) real(default) :: avg type(observable_t), intent(in) :: obs if (obs%sum_weights /= 0) then avg = obs%sum_values / obs%sum_weights else avg = 0 end if end function observable_get_average function observable_get_error (obs) result (err) real(default) :: err type(observable_t), intent(in) :: obs real(default) :: var, n if (obs%sum_weights /= 0) then select case (obs%count) case (0:1) err = 0 case default n = obs%count var = obs%sum_squared_values / obs%sum_weights & - (obs%sum_values / obs%sum_weights) ** 2 err = sqrt (max (var, 0._default) / (n - 1)) end select else err = 0 end if end function observable_get_error @ %def observable_get_n_entries @ %def observable_get_sum @ %def observable_get_average @ %def observable_get_error @ Write label and/or physical unit to a string. <>= function observable_get_label (obs, wl, wu) result (string) type(string_t) :: string type(observable_t), intent(in) :: obs logical, intent(in) :: wl, wu type(string_t) :: obs_label, obs_unit if (wl) then if (obs%obs_label /= "") then obs_label = obs%obs_label else obs_label = "\textrm{Observable}" end if else obs_label = "" end if if (wu) then if (obs%obs_unit /= "") then if (wl) then obs_unit = "\;[" // obs%obs_unit // "]" else obs_unit = obs%obs_unit end if else obs_unit = "" end if else obs_unit = "" end if string = obs_label // obs_unit end function observable_get_label @ %def observable_get_label @ \subsection{Output} <>= subroutine observable_write (obs, unit) type(observable_t), intent(in) :: obs integer, intent(in), optional :: unit real(default) :: avg, err, relerr integer :: n integer :: u u = given_output_unit (unit); if (u < 0) return avg = observable_get_average (obs) err = observable_get_error (obs) if (avg /= 0) then relerr = err / abs (avg) else relerr = 0 end if n = observable_get_n_entries (obs) if (obs%graph_options%title /= "") then write (u, "(A,1x,3A)") & "title =", '"', char (obs%graph_options%title), '"' end if if (obs%graph_options%title /= "") then write (u, "(A,1x,3A)") & "description =", '"', char (obs%graph_options%description), '"' end if write (u, "(A,1x," // HISTOGRAM_DATA_FORMAT // ")", advance = "no") & "average =", avg call write_unit () write (u, "(A,1x," // HISTOGRAM_DATA_FORMAT // ")", advance = "no") & "error[abs] =", err call write_unit () write (u, "(A,1x," // HISTOGRAM_DATA_FORMAT // ")") & "error[rel] =", relerr write (u, "(A,1x,I0)") & "n_entries =", n contains subroutine write_unit () if (obs%obs_unit /= "") then write (u, "(1x,A)") char (obs%obs_unit) else write (u, *) end if end subroutine write_unit end subroutine observable_write @ %def observable_write @ \LaTeX\ output. <>= subroutine observable_write_driver (obs, unit, write_heading) type(observable_t), intent(in) :: obs integer, intent(in), optional :: unit logical, intent(in), optional :: write_heading real(default) :: avg, err integer :: n_digits logical :: heading integer :: u u = given_output_unit (unit); if (u < 0) return heading = .true.; if (present (write_heading)) heading = write_heading avg = observable_get_average (obs) err = observable_get_error (obs) if (avg /= 0 .and. err /= 0) then n_digits = max (2, 2 - int (log10 (abs (err / real (avg, default))))) else if (avg /= 0) then n_digits = 100 else n_digits = 1 end if if (heading) then write (u, "(A)") if (obs%graph_options%title /= "") then write (u, "(A)") "\section{" // char (obs%graph_options%title) & // "}" else write (u, "(A)") "\section{Observable}" end if if (obs%graph_options%description /= "") then write (u, "(A)") char (obs%graph_options%description) write (u, *) end if write (u, "(A)") "\begin{flushleft}" end if write (u, "(A)", advance="no") " $\langle{" ! $ sign write (u, "(A)", advance="no") char (observable_get_label (obs, wl=.true., wu=.false.)) write (u, "(A)", advance="no") "}\rangle = " write (u, "(A)", advance="no") char (tex_format (avg, n_digits)) write (u, "(A)", advance="no") "\pm" write (u, "(A)", advance="no") char (tex_format (err, 2)) write (u, "(A)", advance="no") "\;{" write (u, "(A)", advance="no") char (observable_get_label (obs, wl=.false., wu=.true.)) write (u, "(A)") "}" write (u, "(A)", advance="no") " \quad[n_{\text{entries}} = " write (u, "(I0)",advance="no") observable_get_n_entries (obs) write (u, "(A)") "]$" ! $ fool Emacs' noweb mode if (heading) then write (u, "(A)") "\end{flushleft}" end if end subroutine observable_write_driver @ %def observable_write_driver @ \subsection{Histograms} \subsubsection{Bins} <>= type :: bin_t private real(default) :: midpoint = 0 real(default) :: width = 0 real(default) :: sum_weights = 0 real(default) :: sum_squared_weights = 0 real(default) :: sum_excess_weights = 0 integer :: count = 0 end type bin_t @ %def bin_t <>= subroutine bin_init (bin, midpoint, width) type(bin_t), intent(out) :: bin real(default), intent(in) :: midpoint, width bin%midpoint = midpoint bin%width = width end subroutine bin_init @ %def bin_init <>= elemental subroutine bin_clear (bin) type(bin_t), intent(inout) :: bin bin%sum_weights = 0 bin%sum_squared_weights = 0 bin%sum_excess_weights = 0 bin%count = 0 end subroutine bin_clear @ %def bin_clear <>= subroutine bin_record_value (bin, normalize, weight, excess) type(bin_t), intent(inout) :: bin logical, intent(in) :: normalize real(default), intent(in) :: weight real(default), intent(in), optional :: excess real(default) :: w, e if (normalize) then if (bin%width /= 0) then w = weight / bin%width if (present (excess)) e = excess / bin%width else w = 0 if (present (excess)) e = 0 end if else w = weight if (present (excess)) e = excess end if bin%sum_weights = bin%sum_weights + w bin%sum_squared_weights = bin%sum_squared_weights + w ** 2 if (present (excess)) & bin%sum_excess_weights = bin%sum_excess_weights + abs (e) bin%count = bin%count + 1 end subroutine bin_record_value @ %def bin_record_value <>= function bin_get_midpoint (bin) result (x) real(default) :: x type(bin_t), intent(in) :: bin x = bin%midpoint end function bin_get_midpoint function bin_get_width (bin) result (w) real(default) :: w type(bin_t), intent(in) :: bin w = bin%width end function bin_get_width function bin_get_n_entries (bin) result (n) integer :: n type(bin_t), intent(in) :: bin n = bin%count end function bin_get_n_entries function bin_get_sum (bin) result (s) real(default) :: s type(bin_t), intent(in) :: bin s = bin%sum_weights end function bin_get_sum function bin_get_error (bin) result (err) real(default) :: err type(bin_t), intent(in) :: bin err = sqrt (bin%sum_squared_weights) end function bin_get_error function bin_get_excess (bin) result (excess) real(default) :: excess type(bin_t), intent(in) :: bin excess = bin%sum_excess_weights end function bin_get_excess @ %def bin_get_midpoint @ %def bin_get_width @ %def bin_get_n_entries @ %def bin_get_sum @ %def bin_get_error @ %def bin_get_excess <>= subroutine bin_write_header (unit) integer, intent(in), optional :: unit character(120) :: buffer integer :: u u = given_output_unit (unit); if (u < 0) return write (buffer, "(A,4(1x," //HISTOGRAM_HEAD_FORMAT // "),2x,A)") & "#", "bin midpoint", "value ", "error ", & "excess ", "n" write (u, "(A)") trim (buffer) end subroutine bin_write_header subroutine bin_write (bin, unit) type(bin_t), intent(in) :: bin integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit); if (u < 0) return write (u, "(1x,4(1x," // HISTOGRAM_DATA_FORMAT // "),2x,I0)") & bin_get_midpoint (bin), & bin_get_sum (bin), & bin_get_error (bin), & bin_get_excess (bin), & bin_get_n_entries (bin) end subroutine bin_write @ %def bin_write_header @ %def bin_write @ \subsubsection{Histograms} <>= type :: histogram_t private real(default) :: lower_bound = 0 real(default) :: upper_bound = 0 real(default) :: width = 0 integer :: n_bins = 0 logical :: normalize_bins = .false. type(observable_t) :: obs type(observable_t) :: obs_within_bounds type(bin_t) :: underflow type(bin_t), dimension(:), allocatable :: bin type(bin_t) :: overflow type(graph_options_t) :: graph_options type(drawing_options_t) :: drawing_options end type histogram_t @ %def histogram_t @ \subsubsection{Initializer/finalizer} Initialize a histogram. We may provide either the bin width or the number of bins. A finalizer is not needed, since the histogram contains no pointer (sub)components. <>= interface histogram_init module procedure histogram_init_n_bins module procedure histogram_init_bin_width end interface <>= module subroutine histogram_init_n_bins (h, id, & lower_bound, upper_bound, n_bins, normalize_bins, & obs_label, obs_unit, graph_options, drawing_options) type(histogram_t), intent(out) :: h type(string_t), intent(in) :: id real(default), intent(in) :: lower_bound, upper_bound integer, intent(in) :: n_bins logical, intent(in) :: normalize_bins type(string_t), intent(in), optional :: obs_label, obs_unit type(graph_options_t), intent(in), optional :: graph_options type(drawing_options_t), intent(in), optional :: drawing_options end subroutine histogram_init_n_bins module subroutine histogram_init_bin_width (h, id, & lower_bound, upper_bound, bin_width, normalize_bins, & obs_label, obs_unit, graph_options, drawing_options) type(histogram_t), intent(out) :: h type(string_t), intent(in) :: id real(default), intent(in) :: lower_bound, upper_bound, bin_width logical, intent(in) :: normalize_bins type(string_t), intent(in), optional :: obs_label, obs_unit type(graph_options_t), intent(in), optional :: graph_options type(drawing_options_t), intent(in), optional :: drawing_options end subroutine histogram_init_bin_width <>= module subroutine histogram_init_n_bins (h, id, & lower_bound, upper_bound, n_bins, normalize_bins, & obs_label, obs_unit, graph_options, drawing_options) type(histogram_t), intent(out) :: h type(string_t), intent(in) :: id real(default), intent(in) :: lower_bound, upper_bound integer, intent(in) :: n_bins logical, intent(in) :: normalize_bins type(string_t), intent(in), optional :: obs_label, obs_unit type(graph_options_t), intent(in), optional :: graph_options type(drawing_options_t), intent(in), optional :: drawing_options real(default) :: bin_width integer :: i call observable_init (h%obs_within_bounds, obs_label, obs_unit) call observable_init (h%obs, obs_label, obs_unit) h%lower_bound = lower_bound h%upper_bound = upper_bound h%n_bins = max (n_bins, 1) h%width = h%upper_bound - h%lower_bound h%normalize_bins = normalize_bins bin_width = h%width / h%n_bins allocate (h%bin (h%n_bins)) call bin_init (h%underflow, h%lower_bound, 0._default) do i = 1, h%n_bins call bin_init (h%bin(i), & h%lower_bound - bin_width/2 + i * bin_width, bin_width) end do call bin_init (h%overflow, h%upper_bound, 0._default) if (present (graph_options)) then h%graph_options = graph_options else call h%graph_options%init () end if call graph_options_set (h%graph_options, id = id) if (present (drawing_options)) then h%drawing_options = drawing_options else call h%drawing_options%init_histogram () end if end subroutine histogram_init_n_bins module subroutine histogram_init_bin_width (h, id, & lower_bound, upper_bound, bin_width, normalize_bins, & obs_label, obs_unit, graph_options, drawing_options) type(histogram_t), intent(out) :: h type(string_t), intent(in) :: id real(default), intent(in) :: lower_bound, upper_bound, bin_width logical, intent(in) :: normalize_bins type(string_t), intent(in), optional :: obs_label, obs_unit type(graph_options_t), intent(in), optional :: graph_options type(drawing_options_t), intent(in), optional :: drawing_options integer :: n_bins if (bin_width /= 0) then n_bins = nint ((upper_bound - lower_bound) / bin_width) else n_bins = 1 end if call histogram_init_n_bins (h, id, & lower_bound, upper_bound, n_bins, normalize_bins, & obs_label, obs_unit, graph_options, drawing_options) end subroutine histogram_init_bin_width @ %def histogram_init @ Initialize a histogram by copying another one. Since [[h]] has no pointer (sub)components, intrinsic assignment is sufficient. Optionally, we replace the drawing options. <>= subroutine histogram_init_histogram (h, h_in, drawing_options) type(histogram_t), intent(out) :: h type(histogram_t), intent(in) :: h_in type(drawing_options_t), intent(in), optional :: drawing_options h = h_in if (present (drawing_options)) then h%drawing_options = drawing_options end if end subroutine histogram_init_histogram @ %def histogram_init_histogram @ \subsubsection{Fill histograms} Clear the histogram contents, but do not modify the structure. <>= subroutine histogram_clear (h) type(histogram_t), intent(inout) :: h call observable_clear (h%obs) call observable_clear (h%obs_within_bounds) call bin_clear (h%underflow) if (allocated (h%bin)) call bin_clear (h%bin) call bin_clear (h%overflow) end subroutine histogram_clear @ %def histogram_clear @ Record a value. Successful if the value is within bounds, otherwise it is recorded as under-/overflow. Optionally, we may provide an excess weight that could be returned by the unweighting procedure. <>= subroutine histogram_record_value_unweighted (h, value, excess, success) type(histogram_t), intent(inout) :: h real(default), intent(in) :: value real(default), intent(in), optional :: excess logical, intent(out), optional :: success integer :: i_bin call observable_record_value (h%obs, value) if (h%width /= 0) then i_bin = floor (((value - h%lower_bound) / h%width) * h%n_bins) + 1 else i_bin = 0 end if if (i_bin <= 0) then call bin_record_value (h%underflow, .false., 1._default, excess) if (present (success)) success = .false. else if (i_bin <= h%n_bins) then call observable_record_value (h%obs_within_bounds, value) call bin_record_value & (h%bin(i_bin), h%normalize_bins, 1._default, excess) if (present (success)) success = .true. else call bin_record_value (h%overflow, .false., 1._default, excess) if (present (success)) success = .false. end if end subroutine histogram_record_value_unweighted @ %def histogram_record_value_unweighted @ Weighted events: analogous, but no excess weight. <>= subroutine histogram_record_value_weighted (h, value, weight, success) type(histogram_t), intent(inout) :: h real(default), intent(in) :: value, weight logical, intent(out), optional :: success integer :: i_bin call observable_record_value (h%obs, value, weight) if (h%width /= 0) then i_bin = floor (((value - h%lower_bound) / h%width) * h%n_bins) + 1 else i_bin = 0 end if if (i_bin <= 0) then call bin_record_value (h%underflow, .false., weight) if (present (success)) success = .false. else if (i_bin <= h%n_bins) then call observable_record_value (h%obs_within_bounds, value, weight) call bin_record_value (h%bin(i_bin), h%normalize_bins, weight) if (present (success)) success = .true. else call bin_record_value (h%overflow, .false., weight) if (present (success)) success = .false. end if end subroutine histogram_record_value_weighted @ %def histogram_record_value_weighted @ \subsubsection{Access contents} Inherited from the observable component (all-over average etc.) <>= function histogram_get_n_entries (h) result (n) integer :: n type(histogram_t), intent(in) :: h n = observable_get_n_entries (h%obs) end function histogram_get_n_entries function histogram_get_average (h) result (avg) real(default) :: avg type(histogram_t), intent(in) :: h avg = observable_get_average (h%obs) end function histogram_get_average function histogram_get_error (h) result (err) real(default) :: err type(histogram_t), intent(in) :: h err = observable_get_error (h%obs) end function histogram_get_error @ %def histogram_get_n_entries @ %def histogram_get_average @ %def histogram_get_error @ Analogous, but applied only to events within bounds. <>= function histogram_get_n_entries_within_bounds (h) result (n) integer :: n type(histogram_t), intent(in) :: h n = observable_get_n_entries (h%obs_within_bounds) end function histogram_get_n_entries_within_bounds function histogram_get_average_within_bounds (h) result (avg) real(default) :: avg type(histogram_t), intent(in) :: h avg = observable_get_average (h%obs_within_bounds) end function histogram_get_average_within_bounds function histogram_get_error_within_bounds (h) result (err) real(default) :: err type(histogram_t), intent(in) :: h err = observable_get_error (h%obs_within_bounds) end function histogram_get_error_within_bounds @ %def histogram_get_n_entries_within_bounds @ %def histogram_get_average_within_bounds @ %def histogram_get_error_within_bounds Get the number of bins <>= function histogram_get_n_bins (h) result (n) type(histogram_t), intent(in) :: h integer :: n n = h%n_bins end function histogram_get_n_bins @ %def histogram_get_n_bins @ Check bins. If the index is zero or above the limit, return the results for underflow or overflow, respectively. <>= function histogram_get_n_entries_for_bin (h, i) result (n) integer :: n type(histogram_t), intent(in) :: h integer, intent(in) :: i if (i <= 0) then n = bin_get_n_entries (h%underflow) else if (i <= h%n_bins) then n = bin_get_n_entries (h%bin(i)) else n = bin_get_n_entries (h%overflow) end if end function histogram_get_n_entries_for_bin function histogram_get_sum_for_bin (h, i) result (avg) real(default) :: avg type(histogram_t), intent(in) :: h integer, intent(in) :: i if (i <= 0) then avg = bin_get_sum (h%underflow) else if (i <= h%n_bins) then avg = bin_get_sum (h%bin(i)) else avg = bin_get_sum (h%overflow) end if end function histogram_get_sum_for_bin function histogram_get_error_for_bin (h, i) result (err) real(default) :: err type(histogram_t), intent(in) :: h integer, intent(in) :: i if (i <= 0) then err = bin_get_error (h%underflow) else if (i <= h%n_bins) then err = bin_get_error (h%bin(i)) else err = bin_get_error (h%overflow) end if end function histogram_get_error_for_bin function histogram_get_excess_for_bin (h, i) result (err) real(default) :: err type(histogram_t), intent(in) :: h integer, intent(in) :: i if (i <= 0) then err = bin_get_excess (h%underflow) else if (i <= h%n_bins) then err = bin_get_excess (h%bin(i)) else err = bin_get_excess (h%overflow) end if end function histogram_get_excess_for_bin @ %def histogram_get_n_entries_for_bin @ %def histogram_get_sum_for_bin @ %def histogram_get_error_for_bin @ %def histogram_get_excess_for_bin @ Return a pointer to the graph options. <>= function histogram_get_graph_options_ptr (h) result (ptr) type(graph_options_t), pointer :: ptr type(histogram_t), intent(in), target :: h ptr => h%graph_options end function histogram_get_graph_options_ptr @ %def histogram_get_graph_options_ptr @ Return a pointer to the drawing options. <>= function histogram_get_drawing_options_ptr (h) result (ptr) type(drawing_options_t), pointer :: ptr type(histogram_t), intent(in), target :: h ptr => h%drawing_options end function histogram_get_drawing_options_ptr @ %def histogram_get_drawing_options_ptr @ \subsubsection{Output} <>= subroutine histogram_write (h, unit) type(histogram_t), intent(in) :: h integer, intent(in), optional :: unit integer :: u, i u = given_output_unit (unit); if (u < 0) return call bin_write_header (u) if (allocated (h%bin)) then do i = 1, h%n_bins call bin_write (h%bin(i), u) end do end if write (u, "(A)") write (u, "(A,1x,A)") "#", "Underflow:" call bin_write (h%underflow, u) write (u, "(A)") write (u, "(A,1x,A)") "#", "Overflow:" call bin_write (h%overflow, u) write (u, "(A)") write (u, "(A,1x,A)") "#", "Summary: data within bounds" call observable_write (h%obs_within_bounds, u) write (u, "(A)") write (u, "(A,1x,A)") "#", "Summary: all data" call observable_write (h%obs, u) write (u, "(A)") end subroutine histogram_write @ %def histogram_write @ Write the GAMELAN reader for histogram contents. <>= subroutine histogram_write_gml_reader (h, filename, unit) type(histogram_t), intent(in) :: h type(string_t), intent(in) :: filename integer, intent(in), optional :: unit character(*), parameter :: fmt = "(ES15.8)" integer :: u u = given_output_unit (unit); if (u < 0) return write (u, "(2x,A)") 'fromfile "' // char (filename) // '":' write (u, "(4x,A)") 'key "# Histogram:";' write (u, "(4x,A)") 'dx := #' & // real2char (h%width / h%n_bins / 2, fmt) // ';' write (u, "(4x,A)") 'for i withinblock:' write (u, "(6x,A)") 'get x, y, y.d, y.n, y.e;' if (h%drawing_options%with_hbars) then write (u, "(6x,A)") 'plot (' // char (h%drawing_options%dataset) & // ') (x,y) hbar dx;' else write (u, "(6x,A)") 'plot (' // char (h%drawing_options%dataset) & // ') (x,y);' end if if (h%drawing_options%err) then write (u, "(6x,A)") 'plot (' // char (h%drawing_options%dataset) & // '.err) ' & // '(x,y) vbar y.d;' end if !!! Future excess options for plots ! write (u, "(6x,A)") 'if show_excess: ' // & ! & 'plot(dat.e)(x, y plus y.e) hbar dx; fi' write (u, "(4x,A)") 'endfor' write (u, "(2x,A)") 'endfrom' end subroutine histogram_write_gml_reader @ %def histogram_write_gml_reader @ \LaTeX\ and GAMELAN output. <>= subroutine histogram_write_gml_driver (h, filename, unit) type(histogram_t), intent(in) :: h type(string_t), intent(in) :: filename integer, intent(in), optional :: unit type(string_t) :: calc_cmd, bg_cmd, draw_cmd, err_cmd, symb_cmd, fg_cmd integer :: u u = given_output_unit (unit); if (u < 0) return call graph_options_write_tex_header (h%graph_options, unit) write (u, "(2x,A)") char (graph_options_get_gml_setup (h%graph_options)) write (u, "(2x,A)") char (graph_options_get_gml_graphrange & (h%graph_options, x_min=h%lower_bound, x_max=h%upper_bound)) call histogram_write_gml_reader (h, filename, unit) calc_cmd = drawing_options_get_calc_command (h%drawing_options) if (calc_cmd /= "") write (u, "(2x,A)") char (calc_cmd) bg_cmd = drawing_options_get_gml_bg_command (h%drawing_options) if (bg_cmd /= "") write (u, "(2x,A)") char (bg_cmd) draw_cmd = drawing_options_get_draw_command (h%drawing_options) if (draw_cmd /= "") write (u, "(2x,A)") char (draw_cmd) err_cmd = drawing_options_get_err_command (h%drawing_options) if (err_cmd /= "") write (u, "(2x,A)") char (err_cmd) symb_cmd = drawing_options_get_symb_command (h%drawing_options) if (symb_cmd /= "") write (u, "(2x,A)") char (symb_cmd) fg_cmd = drawing_options_get_gml_fg_command (h%drawing_options) if (fg_cmd /= "") write (u, "(2x,A)") char (fg_cmd) write (u, "(2x,A)") char (graph_options_get_gml_x_label (h%graph_options)) write (u, "(2x,A)") char (graph_options_get_gml_y_label (h%graph_options)) call graph_options_write_tex_footer (h%graph_options, unit) write (u, "(A)") "\vspace*{2\baselineskip}" write (u, "(A)") "\begin{flushleft}" write (u, "(A)") "\textbf{Data within bounds:} \\" call observable_write_driver (h%obs_within_bounds, unit, & write_heading=.false.) write (u, "(A)") "\\[0.5\baselineskip]" write (u, "(A)") "\textbf{All data:} \\" call observable_write_driver (h%obs, unit, write_heading=.false.) write (u, "(A)") "\end{flushleft}" end subroutine histogram_write_gml_driver @ %def histogram_write_gml_driver @ Return the header for generic data output as an ifile. <>= subroutine histogram_get_header (h, header, comment) type(histogram_t), intent(in) :: h type(ifile_t), intent(inout) :: header type(string_t), intent(in), optional :: comment type(string_t) :: c if (present (comment)) then c = comment else c = "" end if call ifile_append (header, c // "WHIZARD histogram data") call graph_options_get_header (h%graph_options, header, comment) call ifile_append (header, & c // "range: " // real2string (h%lower_bound) & // " - " // real2string (h%upper_bound)) call ifile_append (header, & c // "counts total: " & // int2char (histogram_get_n_entries_within_bounds (h))) call ifile_append (header, & c // "total average: " & // real2string (histogram_get_average_within_bounds (h)) // " +- " & // real2string (histogram_get_error_within_bounds (h))) end subroutine histogram_get_header @ %def histogram_get_header @ \subsection{Plots} \subsubsection{Points} <>= type :: point_t private real(default) :: x = 0 real(default) :: y = 0 real(default) :: yerr = 0 real(default) :: xerr = 0 type(point_t), pointer :: next => null () end type point_t @ %def point_t <>= interface point_init module procedure point_init_contents module procedure point_init_point end interface <>= module subroutine point_init_contents (point, x, y, yerr, xerr) type(point_t), intent(out) :: point real(default), intent(in) :: x, y real(default), intent(in), optional :: yerr, xerr end subroutine point_init_contents module subroutine point_init_point (point, point_in) type(point_t), intent(out) :: point type(point_t), intent(in) :: point_in end subroutine point_init_point <>= module subroutine point_init_contents (point, x, y, yerr, xerr) type(point_t), intent(out) :: point real(default), intent(in) :: x, y real(default), intent(in), optional :: yerr, xerr point%x = x point%y = y if (present (yerr)) point%yerr = yerr if (present (xerr)) point%xerr = xerr end subroutine point_init_contents module subroutine point_init_point (point, point_in) type(point_t), intent(out) :: point type(point_t), intent(in) :: point_in point%x = point_in%x point%y = point_in%y point%yerr = point_in%yerr point%xerr = point_in%xerr end subroutine point_init_point @ %def point_init <>= function point_get_x (point) result (x) real(default) :: x type(point_t), intent(in) :: point x = point%x end function point_get_x function point_get_y (point) result (y) real(default) :: y type(point_t), intent(in) :: point y = point%y end function point_get_y function point_get_xerr (point) result (xerr) real(default) :: xerr type(point_t), intent(in) :: point xerr = point%xerr end function point_get_xerr function point_get_yerr (point) result (yerr) real(default) :: yerr type(point_t), intent(in) :: point yerr = point%yerr end function point_get_yerr @ %def point_get_x @ %def point_get_y @ %def point_get_xerr @ %def point_get_yerr <>= subroutine point_write_header (unit) integer, intent(in) :: unit character(120) :: buffer integer :: u u = given_output_unit (unit); if (u < 0) return write (buffer, "(A,4(1x," // HISTOGRAM_HEAD_FORMAT // "))") & "#", "x ", "y ", "yerr ", "xerr " write (u, "(A)") trim (buffer) end subroutine point_write_header subroutine point_write (point, unit) type(point_t), intent(in) :: point integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit); if (u < 0) return write (u, "(1x,4(1x," // HISTOGRAM_DATA_FORMAT // "))") & point_get_x (point), & point_get_y (point), & point_get_yerr (point), & point_get_xerr (point) end subroutine point_write @ %def point_write @ \subsubsection{Plots} <>= type :: plot_t private type(point_t), pointer :: first => null () type(point_t), pointer :: last => null () integer :: count = 0 type(graph_options_t) :: graph_options type(drawing_options_t) :: drawing_options end type plot_t @ %def plot_t @ \subsubsection{Initializer/finalizer} Initialize a plot. We provide the lower and upper bound in the $x$ direction. <>= interface plot_init module procedure plot_init_empty module procedure plot_init_plot end interface <>= module subroutine plot_init_empty (p, id, graph_options, drawing_options) type(plot_t), intent(out) :: p type(string_t), intent(in) :: id type(graph_options_t), intent(in), optional :: graph_options type(drawing_options_t), intent(in), optional :: drawing_options end subroutine plot_init_empty <>= module subroutine plot_init_empty (p, id, graph_options, drawing_options) type(plot_t), intent(out) :: p type(string_t), intent(in) :: id type(graph_options_t), intent(in), optional :: graph_options type(drawing_options_t), intent(in), optional :: drawing_options if (present (graph_options)) then p%graph_options = graph_options else call p%graph_options%init () end if call p%graph_options%set (id = id) if (present (drawing_options)) then p%drawing_options = drawing_options else call p%drawing_options%init_plot () end if end subroutine plot_init_empty @ %def plot_init @ Initialize a plot by copying another one, optionally merging in a new set of drawing options. Since [[p]] has pointer (sub)components, we have to explicitly deep-copy the original. <>= module subroutine plot_init_plot (p, p_in, drawing_options) type(plot_t), intent(out) :: p type(plot_t), intent(in) :: p_in type(drawing_options_t), intent(in), optional :: drawing_options end subroutine plot_init_plot <>= module subroutine plot_init_plot (p, p_in, drawing_options) type(plot_t), intent(out) :: p type(plot_t), intent(in) :: p_in type(drawing_options_t), intent(in), optional :: drawing_options type(point_t), pointer :: current, new current => p_in%first do while (associated (current)) allocate (new) call point_init (new, current) if (associated (p%last)) then p%last%next => new else p%first => new end if p%last => new current => current%next end do p%count = p_in%count p%graph_options = p_in%graph_options if (present (drawing_options)) then p%drawing_options = drawing_options else p%drawing_options = p_in%drawing_options end if end subroutine plot_init_plot @ %def plot_init_plot @ Finalize the plot by deallocating the list of points. <>= subroutine plot_final (plot) type(plot_t), intent(inout) :: plot type(point_t), pointer :: current do while (associated (plot%first)) current => plot%first plot%first => current%next deallocate (current) end do plot%last => null () end subroutine plot_final @ %def plot_final @ \subsubsection{Fill plots} Clear the plot contents, but do not modify the structure. <>= subroutine plot_clear (plot) type(plot_t), intent(inout) :: plot plot%count = 0 call plot_final (plot) end subroutine plot_clear @ %def plot_clear @ Record a value. Successful if the value is within bounds, otherwise it is recorded as under-/overflow. <>= subroutine plot_record_value (plot, x, y, yerr, xerr, success) type(plot_t), intent(inout) :: plot real(default), intent(in) :: x, y real(default), intent(in), optional :: yerr, xerr logical, intent(out), optional :: success type(point_t), pointer :: point plot%count = plot%count + 1 allocate (point) call point_init (point, x, y, yerr, xerr) if (associated (plot%first)) then plot%last%next => point else plot%first => point end if plot%last => point if (present (success)) success = .true. end subroutine plot_record_value @ %def plot_record_value @ \subsubsection{Access contents} The number of points. <>= function plot_get_n_entries (plot) result (n) integer :: n type(plot_t), intent(in) :: plot n = plot%count end function plot_get_n_entries @ %def plot_get_n_entries @ Return a pointer to the graph options. <>= function plot_get_graph_options_ptr (p) result (ptr) type(graph_options_t), pointer :: ptr type(plot_t), intent(in), target :: p ptr => p%graph_options end function plot_get_graph_options_ptr @ %def plot_get_graph_options_ptr @ Return a pointer to the drawing options. <>= function plot_get_drawing_options_ptr (p) result (ptr) type(drawing_options_t), pointer :: ptr type(plot_t), intent(in), target :: p ptr => p%drawing_options end function plot_get_drawing_options_ptr @ %def plot_get_drawing_options_ptr @ \subsubsection{Output} This output format is used by the GAMELAN driver below. <>= subroutine plot_write (plot, unit) type(plot_t), intent(in) :: plot integer, intent(in), optional :: unit type(point_t), pointer :: point integer :: u u = given_output_unit (unit); if (u < 0) return call point_write_header (u) point => plot%first do while (associated (point)) call point_write (point, unit) point => point%next end do write (u, *) write (u, "(A,1x,A)") "#", "Summary:" write (u, "(A,1x,I0)") & "n_entries =", plot_get_n_entries (plot) write (u, *) end subroutine plot_write @ %def plot_write @ Write the GAMELAN reader for plot contents. <>= subroutine plot_write_gml_reader (p, filename, unit) type(plot_t), intent(in) :: p type(string_t), intent(in) :: filename integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit); if (u < 0) return write (u, "(2x,A)") 'fromfile "' // char (filename) // '":' write (u, "(4x,A)") 'key "# Plot:";' write (u, "(4x,A)") 'for i withinblock:' write (u, "(6x,A)") 'get x, y, y.err, x.err;' write (u, "(6x,A)") 'plot (' // char (p%drawing_options%dataset) & // ') (x,y);' if (p%drawing_options%err) then write (u, "(6x,A)") 'plot (' // char (p%drawing_options%dataset) & // '.err) (x,y) vbar y.err hbar x.err;' end if write (u, "(4x,A)") 'endfor' write (u, "(2x,A)") 'endfrom' end subroutine plot_write_gml_reader @ %def plot_write_gml_header @ \LaTeX\ and GAMELAN output. Analogous to histogram output. <>= subroutine plot_write_gml_driver (p, filename, unit) type(plot_t), intent(in) :: p type(string_t), intent(in) :: filename integer, intent(in), optional :: unit type(string_t) :: calc_cmd, bg_cmd, draw_cmd, err_cmd, symb_cmd, fg_cmd integer :: u u = given_output_unit (unit); if (u < 0) return call graph_options_write_tex_header (p%graph_options, unit) write (u, "(2x,A)") & char (graph_options_get_gml_setup (p%graph_options)) write (u, "(2x,A)") & char (graph_options_get_gml_graphrange (p%graph_options)) call plot_write_gml_reader (p, filename, unit) calc_cmd = drawing_options_get_calc_command (p%drawing_options) if (calc_cmd /= "") write (u, "(2x,A)") char (calc_cmd) bg_cmd = drawing_options_get_gml_bg_command (p%drawing_options) if (bg_cmd /= "") write (u, "(2x,A)") char (bg_cmd) draw_cmd = drawing_options_get_draw_command (p%drawing_options) if (draw_cmd /= "") write (u, "(2x,A)") char (draw_cmd) err_cmd = drawing_options_get_err_command (p%drawing_options) if (err_cmd /= "") write (u, "(2x,A)") char (err_cmd) symb_cmd = drawing_options_get_symb_command (p%drawing_options) if (symb_cmd /= "") write (u, "(2x,A)") char (symb_cmd) fg_cmd = drawing_options_get_gml_fg_command (p%drawing_options) if (fg_cmd /= "") write (u, "(2x,A)") char (fg_cmd) write (u, "(2x,A)") char (graph_options_get_gml_x_label (p%graph_options)) write (u, "(2x,A)") char (graph_options_get_gml_y_label (p%graph_options)) call graph_options_write_tex_footer (p%graph_options, unit) end subroutine plot_write_gml_driver @ %def plot_write_driver @ Append header for generic data output in ifile format. <>= subroutine plot_get_header (plot, header, comment) type(plot_t), intent(in) :: plot type(ifile_t), intent(inout) :: header type(string_t), intent(in), optional :: comment type(string_t) :: c if (present (comment)) then c = comment else c = "" end if call ifile_append (header, c // "WHIZARD plot data") call graph_options_get_header (plot%graph_options, header, comment) call ifile_append (header, & c // "number of points: " & // int2char (plot_get_n_entries (plot))) end subroutine plot_get_header @ %def plot_get_header @ \subsection{Graphs} A graph is a container for several graph elements. Each graph element is either a plot or a histogram. There is an appropriate base type below (the [[analysis_object_t]]), but to avoid recursion, we define a separate base type here. Note that there is no actual recursion: a graph is an analysis object, but a graph cannot contain graphs. (If we could use type extension, the implementation would be much more transparent.) \subsubsection{Graph elements} Graph elements cannot be filled by the [[record]] command directly. The contents are always copied from elementary histograms or plots. <>= type :: graph_element_t private integer :: type = AN_UNDEFINED type(histogram_t), pointer :: h => null () type(plot_t), pointer :: p => null () end type graph_element_t @ %def graph_element_t <>= subroutine graph_element_final (el) type(graph_element_t), intent(inout) :: el select case (el%type) case (AN_HISTOGRAM) deallocate (el%h) case (AN_PLOT) call plot_final (el%p) deallocate (el%p) end select el%type = AN_UNDEFINED end subroutine graph_element_final @ %def graph_element_final @ Return the number of entries in the graph element: <>= function graph_element_get_n_entries (el) result (n) integer :: n type(graph_element_t), intent(in) :: el select case (el%type) case (AN_HISTOGRAM); n = histogram_get_n_entries (el%h) case (AN_PLOT); n = plot_get_n_entries (el%p) case default; n = 0 end select end function graph_element_get_n_entries @ %def graph_element_get_n_entries @ Return a pointer to the graph / drawing options. <>= function graph_element_get_graph_options_ptr (el) result (ptr) type(graph_options_t), pointer :: ptr type(graph_element_t), intent(in) :: el select case (el%type) case (AN_HISTOGRAM); ptr => histogram_get_graph_options_ptr (el%h) case (AN_PLOT); ptr => plot_get_graph_options_ptr (el%p) case default; ptr => null () end select end function graph_element_get_graph_options_ptr function graph_element_get_drawing_options_ptr (el) result (ptr) type(drawing_options_t), pointer :: ptr type(graph_element_t), intent(in) :: el select case (el%type) case (AN_HISTOGRAM); ptr => histogram_get_drawing_options_ptr (el%h) case (AN_PLOT); ptr => plot_get_drawing_options_ptr (el%p) case default; ptr => null () end select end function graph_element_get_drawing_options_ptr @ %def graph_element_get_graph_options_ptr @ %def graph_element_get_drawing_options_ptr @ Output, simple wrapper for the plot/histogram writer. <>= subroutine graph_element_write (el, unit) type(graph_element_t), intent(in) :: el integer, intent(in), optional :: unit type(graph_options_t), pointer :: gro type(string_t) :: id integer :: u u = given_output_unit (unit); if (u < 0) return gro => graph_element_get_graph_options_ptr (el) id = graph_options_get_id (gro) write (u, "(A,A)") '#', repeat ("-", 78) select case (el%type) case (AN_HISTOGRAM) write (u, "(A)", advance="no") "# Histogram: " write (u, "(1x,A)") char (id) call histogram_write (el%h, unit) case (AN_PLOT) write (u, "(A)", advance="no") "# Plot: " write (u, "(1x,A)") char (id) call plot_write (el%p, unit) end select end subroutine graph_element_write @ %def graph_element_write <>= subroutine graph_element_write_gml_reader (el, filename, unit) type(graph_element_t), intent(in) :: el type(string_t), intent(in) :: filename integer, intent(in), optional :: unit select case (el%type) case (AN_HISTOGRAM); call histogram_write_gml_reader (el%h, filename, unit) case (AN_PLOT); call plot_write_gml_reader (el%p, filename, unit) end select end subroutine graph_element_write_gml_reader @ %def graph_element_write_gml_reader @ \subsubsection{The graph type} The actual graph type contains its own [[graph_options]], which override the individual settings. The [[drawing_options]] are set in the graph elements. This distinction motivates the separation of the two types. <>= type :: graph_t private type(graph_element_t), dimension(:), allocatable :: el type(graph_options_t) :: graph_options end type graph_t @ %def graph_t @ \subsubsection{Initializer/finalizer} The graph is created with a definite number of elements. The elements are filled one by one, optionally with modified drawing options. <>= subroutine graph_init (g, id, n_elements, graph_options) type(graph_t), intent(out) :: g type(string_t), intent(in) :: id integer, intent(in) :: n_elements type(graph_options_t), intent(in), optional :: graph_options allocate (g%el (n_elements)) if (present (graph_options)) then g%graph_options = graph_options else call g%graph_options%init () end if call g%graph_options%set (id = id) end subroutine graph_init @ %def graph_init <>= subroutine graph_insert_histogram (g, i, h, drawing_options) type(graph_t), intent(inout), target :: g integer, intent(in) :: i type(histogram_t), intent(in) :: h type(drawing_options_t), intent(in), optional :: drawing_options type(graph_options_t), pointer :: gro type(drawing_options_t), pointer :: dro type(string_t) :: id g%el(i)%type = AN_HISTOGRAM allocate (g%el(i)%h) call histogram_init_histogram (g%el(i)%h, h, drawing_options) gro => histogram_get_graph_options_ptr (g%el(i)%h) dro => histogram_get_drawing_options_ptr (g%el(i)%h) id = graph_options_get_id (gro) call dro%set (dataset = "dat." // id) end subroutine graph_insert_histogram @ %def graph_insert_histogram <>= subroutine graph_insert_plot (g, i, p, drawing_options) type(graph_t), intent(inout) :: g integer, intent(in) :: i type(plot_t), intent(in) :: p type(drawing_options_t), intent(in), optional :: drawing_options type(graph_options_t), pointer :: gro type(drawing_options_t), pointer :: dro type(string_t) :: id g%el(i)%type = AN_PLOT allocate (g%el(i)%p) call plot_init_plot (g%el(i)%p, p, drawing_options) gro => plot_get_graph_options_ptr (g%el(i)%p) dro => plot_get_drawing_options_ptr (g%el(i)%p) id = graph_options_get_id (gro) call dro%set (dataset = "dat." // id) end subroutine graph_insert_plot @ %def graph_insert_plot @ Finalizer. <>= subroutine graph_final (g) type(graph_t), intent(inout) :: g integer :: i do i = 1, size (g%el) call graph_element_final (g%el(i)) end do deallocate (g%el) end subroutine graph_final @ %def graph_final @ \subsubsection{Access contents} The number of elements. <>= function graph_get_n_elements (graph) result (n) integer :: n type(graph_t), intent(in) :: graph n = size (graph%el) end function graph_get_n_elements @ %def graph_get_n_elements @ Retrieve a pointer to the drawing options of an element, so they can be modified. (The [[target]] attribute is not actually needed because the components are pointers.) <>= function graph_get_drawing_options_ptr (g, i) result (ptr) type(drawing_options_t), pointer :: ptr type(graph_t), intent(in), target :: g integer, intent(in) :: i ptr => graph_element_get_drawing_options_ptr (g%el(i)) end function graph_get_drawing_options_ptr @ %def graph_get_drawing_options_ptr @ \subsubsection{Output} The default output format just writes histogram and plot data. <>= subroutine graph_write (graph, unit) type(graph_t), intent(in) :: graph integer, intent(in), optional :: unit integer :: i do i = 1, size (graph%el) call graph_element_write (graph%el(i), unit) end do end subroutine graph_write @ %def graph_write @ The GAMELAN driver is not a simple wrapper, but it writes the plot/histogram contents embedded the complete graph. First, data are read in, global background commands next, then individual elements, then global foreground commands. <>= subroutine graph_write_gml_driver (g, filename, unit) type(graph_t), intent(in) :: g type(string_t), intent(in) :: filename type(string_t) :: calc_cmd, bg_cmd, draw_cmd, err_cmd, symb_cmd, fg_cmd integer, intent(in), optional :: unit type(drawing_options_t), pointer :: dro integer :: u, i u = given_output_unit (unit); if (u < 0) return call graph_options_write_tex_header (g%graph_options, unit) write (u, "(2x,A)") & char (graph_options_get_gml_setup (g%graph_options)) write (u, "(2x,A)") & char (graph_options_get_gml_graphrange (g%graph_options)) do i = 1, size (g%el) call graph_element_write_gml_reader (g%el(i), filename, unit) calc_cmd = drawing_options_get_calc_command & (graph_element_get_drawing_options_ptr (g%el(i))) if (calc_cmd /= "") write (u, "(2x,A)") char (calc_cmd) end do bg_cmd = graph_options_get_gml_bg_command (g%graph_options) if (bg_cmd /= "") write (u, "(2x,A)") char (bg_cmd) do i = 1, size (g%el) dro => graph_element_get_drawing_options_ptr (g%el(i)) bg_cmd = drawing_options_get_gml_bg_command (dro) if (bg_cmd /= "") write (u, "(2x,A)") char (bg_cmd) draw_cmd = drawing_options_get_draw_command (dro) if (draw_cmd /= "") write (u, "(2x,A)") char (draw_cmd) err_cmd = drawing_options_get_err_command (dro) if (err_cmd /= "") write (u, "(2x,A)") char (err_cmd) symb_cmd = drawing_options_get_symb_command (dro) if (symb_cmd /= "") write (u, "(2x,A)") char (symb_cmd) fg_cmd = drawing_options_get_gml_fg_command (dro) if (fg_cmd /= "") write (u, "(2x,A)") char (fg_cmd) end do fg_cmd = graph_options_get_gml_fg_command (g%graph_options) if (fg_cmd /= "") write (u, "(2x,A)") char (fg_cmd) write (u, "(2x,A)") char (graph_options_get_gml_x_label (g%graph_options)) write (u, "(2x,A)") char (graph_options_get_gml_y_label (g%graph_options)) call graph_options_write_tex_footer (g%graph_options, unit) end subroutine graph_write_gml_driver @ %def graph_write_gml_driver @ Append header for generic data output in ifile format. <>= subroutine graph_get_header (graph, header, comment) type(graph_t), intent(in) :: graph type(ifile_t), intent(inout) :: header type(string_t), intent(in), optional :: comment type(string_t) :: c if (present (comment)) then c = comment else c = "" end if call ifile_append (header, c // "WHIZARD graph data") call graph_options_get_header (graph%graph_options, header, comment) call ifile_append (header, & c // "number of graph elements: " & // int2char (graph_get_n_elements (graph))) end subroutine graph_get_header @ %def graph_get_header @ \subsection{Analysis objects} This data structure holds all observables, histograms and such that are currently active. We have one global store; individual items are identified by their ID strings. (This should rather be coded by type extension.) <>= integer, parameter :: AN_UNDEFINED = 0 integer, parameter :: AN_OBSERVABLE = 1 integer, parameter :: AN_HISTOGRAM = 2 integer, parameter :: AN_PLOT = 3 integer, parameter :: AN_GRAPH = 4 <>= public :: AN_UNDEFINED, AN_HISTOGRAM, AN_OBSERVABLE, AN_PLOT, AN_GRAPH @ %def AN_UNDEFINED @ %def AN_OBSERVABLE AN_HISTOGRAM AN_PLOT AN_GRAPH <>= type :: analysis_object_t private type(string_t) :: id integer :: type = AN_UNDEFINED type(observable_t), pointer :: obs => null () type(histogram_t), pointer :: h => null () type(plot_t), pointer :: p => null () type(graph_t), pointer :: g => null () type(analysis_object_t), pointer :: next => null () end type analysis_object_t @ %def analysis_object_t @ \subsubsection{Initializer/finalizer} Allocate with the correct type but do not fill initial values. <>= subroutine analysis_object_init (obj, id, type) type(analysis_object_t), intent(out) :: obj type(string_t), intent(in) :: id integer, intent(in) :: type obj%id = id obj%type = type select case (obj%type) case (AN_OBSERVABLE); allocate (obj%obs) case (AN_HISTOGRAM); allocate (obj%h) case (AN_PLOT); allocate (obj%p) case (AN_GRAPH); allocate (obj%g) end select end subroutine analysis_object_init @ %def analysis_object_init <>= subroutine analysis_object_final (obj) type(analysis_object_t), intent(inout) :: obj select case (obj%type) case (AN_OBSERVABLE) deallocate (obj%obs) case (AN_HISTOGRAM) deallocate (obj%h) case (AN_PLOT) call plot_final (obj%p) deallocate (obj%p) case (AN_GRAPH) call graph_final (obj%g) deallocate (obj%g) end select obj%type = AN_UNDEFINED end subroutine analysis_object_final @ %def analysis_object_final @ Clear the analysis object, i.e., reset it to its initial state. Not applicable to graphs, which are always combinations of other existing objects. <>= subroutine analysis_object_clear (obj) type(analysis_object_t), intent(inout) :: obj select case (obj%type) case (AN_OBSERVABLE) call observable_clear (obj%obs) case (AN_HISTOGRAM) call histogram_clear (obj%h) case (AN_PLOT) call plot_clear (obj%p) end select end subroutine analysis_object_clear @ %def analysis_object_clear @ \subsubsection{Fill with data} Record data. The effect depends on the type of analysis object. <>= subroutine analysis_object_record_data (obj, & x, y, yerr, xerr, weight, excess, success) type(analysis_object_t), intent(inout) :: obj real(default), intent(in) :: x real(default), intent(in), optional :: y, yerr, xerr, weight, excess logical, intent(out), optional :: success select case (obj%type) case (AN_OBSERVABLE) if (present (weight)) then call observable_record_value_weighted (obj%obs, x, weight, success) else call observable_record_value_unweighted (obj%obs, x, success) end if case (AN_HISTOGRAM) if (present (weight)) then call histogram_record_value_weighted (obj%h, x, weight, success) else call histogram_record_value_unweighted (obj%h, x, excess, success) end if case (AN_PLOT) if (present (y)) then call plot_record_value (obj%p, x, y, yerr, xerr, success) else if (present (success)) success = .false. end if case default if (present (success)) success = .false. end select end subroutine analysis_object_record_data @ %def analysis_object_record_data @ Explicitly set the pointer to the next object in the list. <>= subroutine analysis_object_set_next_ptr (obj, next) type(analysis_object_t), intent(inout) :: obj type(analysis_object_t), pointer :: next obj%next => next end subroutine analysis_object_set_next_ptr @ %def analysis_object_set_next_ptr @ \subsubsection{Access contents} Return a pointer to the next object in the list. <>= function analysis_object_get_next_ptr (obj) result (next) type(analysis_object_t), pointer :: next type(analysis_object_t), intent(in) :: obj next => obj%next end function analysis_object_get_next_ptr @ %def analysis_object_get_next_ptr @ Return data as appropriate for the object type. <>= function analysis_object_get_n_elements (obj) result (n) integer :: n type(analysis_object_t), intent(in) :: obj select case (obj%type) case (AN_HISTOGRAM) n = 1 case (AN_PLOT) n = 1 case (AN_GRAPH) n = graph_get_n_elements (obj%g) case default n = 0 end select end function analysis_object_get_n_elements function analysis_object_get_n_entries (obj, within_bounds) result (n) integer :: n type(analysis_object_t), intent(in) :: obj logical, intent(in), optional :: within_bounds logical :: wb select case (obj%type) case (AN_OBSERVABLE) n = observable_get_n_entries (obj%obs) case (AN_HISTOGRAM) wb = .false.; if (present (within_bounds)) wb = within_bounds if (wb) then n = histogram_get_n_entries_within_bounds (obj%h) else n = histogram_get_n_entries (obj%h) end if case (AN_PLOT) n = plot_get_n_entries (obj%p) case default n = 0 end select end function analysis_object_get_n_entries function analysis_object_get_average (obj, within_bounds) result (avg) real(default) :: avg type(analysis_object_t), intent(in) :: obj logical, intent(in), optional :: within_bounds logical :: wb select case (obj%type) case (AN_OBSERVABLE) avg = observable_get_average (obj%obs) case (AN_HISTOGRAM) wb = .false.; if (present (within_bounds)) wb = within_bounds if (wb) then avg = histogram_get_average_within_bounds (obj%h) else avg = histogram_get_average (obj%h) end if case default avg = 0 end select end function analysis_object_get_average function analysis_object_get_error (obj, within_bounds) result (err) real(default) :: err type(analysis_object_t), intent(in) :: obj logical, intent(in), optional :: within_bounds logical :: wb select case (obj%type) case (AN_OBSERVABLE) err = observable_get_error (obj%obs) case (AN_HISTOGRAM) wb = .false.; if (present (within_bounds)) wb = within_bounds if (wb) then err = histogram_get_error_within_bounds (obj%h) else err = histogram_get_error (obj%h) end if case default err = 0 end select end function analysis_object_get_error @ %def analysis_object_get_n_elements @ %def analysis_object_get_n_entries @ %def analysis_object_get_average @ %def analysis_object_get_error @ Return pointers to the actual contents: <>= function analysis_object_get_observable_ptr (obj) result (obs) type(observable_t), pointer :: obs type(analysis_object_t), intent(in) :: obj select case (obj%type) case (AN_OBSERVABLE); obs => obj%obs case default; obs => null () end select end function analysis_object_get_observable_ptr function analysis_object_get_histogram_ptr (obj) result (h) type(histogram_t), pointer :: h type(analysis_object_t), intent(in) :: obj select case (obj%type) case (AN_HISTOGRAM); h => obj%h case default; h => null () end select end function analysis_object_get_histogram_ptr function analysis_object_get_plot_ptr (obj) result (plot) type(plot_t), pointer :: plot type(analysis_object_t), intent(in) :: obj select case (obj%type) case (AN_PLOT); plot => obj%p case default; plot => null () end select end function analysis_object_get_plot_ptr function analysis_object_get_graph_ptr (obj) result (g) type(graph_t), pointer :: g type(analysis_object_t), intent(in) :: obj select case (obj%type) case (AN_GRAPH); g => obj%g case default; g => null () end select end function analysis_object_get_graph_ptr @ %def analysis_object_get_observable_ptr @ %def analysis_object_get_histogram_ptr @ %def analysis_object_get_plot_ptr @ %def analysis_object_get_graph_ptr @ Return true if the object has a graphical representation: <>= function analysis_object_has_plot (obj) result (flag) logical :: flag type(analysis_object_t), intent(in) :: obj select case (obj%type) case (AN_HISTOGRAM); flag = .true. case (AN_PLOT); flag = .true. case (AN_GRAPH); flag = .true. case default; flag = .false. end select end function analysis_object_has_plot @ %def analysis_object_has_plot @ \subsubsection{Output} <>= subroutine analysis_object_write (obj, unit, verbose) type(analysis_object_t), intent(in) :: obj integer, intent(in), optional :: unit logical, intent(in), optional :: verbose logical :: verb integer :: u u = given_output_unit (unit); if (u < 0) return verb = .false.; if (present (verbose)) verb = verbose write (u, "(A)") repeat ("#", 79) select case (obj%type) case (AN_OBSERVABLE) write (u, "(A)", advance="no") "# Observable:" case (AN_HISTOGRAM) write (u, "(A)", advance="no") "# Histogram: " case (AN_PLOT) write (u, "(A)", advance="no") "# Plot: " case (AN_GRAPH) write (u, "(A)", advance="no") "# Graph: " case default write (u, "(A)") "# [undefined analysis object]" return end select write (u, "(1x,A)") char (obj%id) select case (obj%type) case (AN_OBSERVABLE) call observable_write (obj%obs, unit) case (AN_HISTOGRAM) if (verb) then call obj%h%graph_options%write (unit) write (u, *) call obj%h%drawing_options%write (unit) write (u, *) end if call histogram_write (obj%h, unit) case (AN_PLOT) if (verb) then call obj%p%graph_options%write (unit) write (u, *) call obj%p%drawing_options%write (unit) write (u, *) end if call plot_write (obj%p, unit) case (AN_GRAPH) call graph_write (obj%g, unit) end select end subroutine analysis_object_write @ %def analysis_object_write @ Write the object part of the \LaTeX\ driver file. <>= subroutine analysis_object_write_driver (obj, filename, unit) type(analysis_object_t), intent(in) :: obj type(string_t), intent(in) :: filename integer, intent(in), optional :: unit select case (obj%type) case (AN_OBSERVABLE) call observable_write_driver (obj%obs, unit) case (AN_HISTOGRAM) call histogram_write_gml_driver (obj%h, filename, unit) case (AN_PLOT) call plot_write_gml_driver (obj%p, filename, unit) case (AN_GRAPH) call graph_write_gml_driver (obj%g, filename, unit) end select end subroutine analysis_object_write_driver @ %def analysis_object_write_driver @ Return a data header for external formats, in ifile form. <>= subroutine analysis_object_get_header (obj, header, comment) type(analysis_object_t), intent(in) :: obj type(ifile_t), intent(inout) :: header type(string_t), intent(in), optional :: comment select case (obj%type) case (AN_HISTOGRAM) call histogram_get_header (obj%h, header, comment) case (AN_PLOT) call plot_get_header (obj%p, header, comment) end select end subroutine analysis_object_get_header @ %def analysis_object_get_header @ \subsection{Analysis object iterator} Analysis objects are containers which have iterable data structures: histograms/bins and plots/points. If they are to be treated on a common basis, it is useful to have an iterator which hides the implementation details. The iterator is used only for elementary analysis objects that contain plot data: histograms or plots. It is invalid for meta-objects (graphs) and non-graphical objects (observables). <>= type :: analysis_iterator_t private integer :: type = AN_UNDEFINED type(analysis_object_t), pointer :: object => null () integer :: index = 1 type(point_t), pointer :: point => null () end type @ %def analysis_iterator_t @ The initializer places the iterator at the beginning of the analysis object. <>= subroutine analysis_iterator_init (iterator, object) type(analysis_iterator_t), intent(out) :: iterator type(analysis_object_t), intent(in), target :: object iterator%object => object if (associated (iterator%object)) then iterator%type = iterator%object%type select case (iterator%type) case (AN_PLOT) iterator%point => iterator%object%p%first end select end if end subroutine analysis_iterator_init @ %def analysis_iterator_init @ The iterator is valid as long as it points to an existing entry. An iterator for a data object without array data (observable) is always invalid. <>= function analysis_iterator_is_valid (iterator) result (valid) logical :: valid type(analysis_iterator_t), intent(in) :: iterator if (associated (iterator%object)) then select case (iterator%type) case (AN_HISTOGRAM) valid = iterator%index <= histogram_get_n_bins (iterator%object%h) case (AN_PLOT) valid = associated (iterator%point) case default valid = .false. end select else valid = .false. end if end function analysis_iterator_is_valid @ %def analysis_iterator_is_valid @ Advance the iterator. <>= subroutine analysis_iterator_advance (iterator) type(analysis_iterator_t), intent(inout) :: iterator if (associated (iterator%object)) then select case (iterator%type) case (AN_PLOT) iterator%point => iterator%point%next end select iterator%index = iterator%index + 1 end if end subroutine analysis_iterator_advance @ %def analysis_iterator_advance @ Retrieve the object type: <>= function analysis_iterator_get_type (iterator) result (type) integer :: type type(analysis_iterator_t), intent(in) :: iterator type = iterator%type end function analysis_iterator_get_type @ %def analysis_iterator_get_type @ Use the iterator to retrieve data. We implement a common routine which takes the data descriptors as optional arguments. Data which do not occur in the selected type trigger to an error condition. The iterator must point to a valid entry. <>= subroutine analysis_iterator_get_data (iterator, & x, y, yerr, xerr, width, excess, index, n_total) type(analysis_iterator_t), intent(in) :: iterator real(default), intent(out), optional :: x, y, yerr, xerr, width, excess integer, intent(out), optional :: index, n_total select case (iterator%type) case (AN_HISTOGRAM) if (present (x)) & x = bin_get_midpoint (iterator%object%h%bin(iterator%index)) if (present (y)) & y = bin_get_sum (iterator%object%h%bin(iterator%index)) if (present (yerr)) & yerr = bin_get_error (iterator%object%h%bin(iterator%index)) if (present (xerr)) & call invalid ("histogram", "xerr") if (present (width)) & width = bin_get_width (iterator%object%h%bin(iterator%index)) if (present (excess)) & excess = bin_get_excess (iterator%object%h%bin(iterator%index)) if (present (index)) & index = iterator%index if (present (n_total)) & n_total = histogram_get_n_bins (iterator%object%h) case (AN_PLOT) if (present (x)) & x = point_get_x (iterator%point) if (present (y)) & y = point_get_y (iterator%point) if (present (yerr)) & yerr = point_get_yerr (iterator%point) if (present (xerr)) & xerr = point_get_xerr (iterator%point) if (present (width)) & call invalid ("plot", "width") if (present (excess)) & call invalid ("plot", "excess") if (present (index)) & index = iterator%index if (present (n_total)) & n_total = plot_get_n_entries (iterator%object%p) case default call msg_bug ("analysis_iterator_get_data: called " & // "for unsupported analysis object type") end select contains subroutine invalid (typestr, objstr) character(*), intent(in) :: typestr, objstr call msg_bug ("analysis_iterator_get_data: attempt to get '" & // objstr // "' for type '" // typestr // "'") end subroutine invalid end subroutine analysis_iterator_get_data @ %def analysis_iterator_get_data @ \subsection{Analysis store} This data structure holds all observables, histograms and such that are currently active. We have one global store; individual items are identified by their ID strings and types. <>= type(analysis_store_t), save :: analysis_store @ %def analysis_store <>= type :: analysis_store_t private type(analysis_object_t), pointer :: first => null () type(analysis_object_t), pointer :: last => null () end type analysis_store_t @ %def analysis_store_t @ Delete the analysis store <>= public :: analysis_final <>= module subroutine analysis_final () end subroutine analysis_final <>= module subroutine analysis_final () type(analysis_object_t), pointer :: current do while (associated (analysis_store%first)) current => analysis_store%first analysis_store%first => current%next call analysis_object_final (current) end do analysis_store%last => null () end subroutine analysis_final @ %def analysis_final @ Append a new analysis object <>= subroutine analysis_store_append_object (id, type) type(string_t), intent(in) :: id integer, intent(in) :: type type(analysis_object_t), pointer :: obj allocate (obj) call analysis_object_init (obj, id, type) if (associated (analysis_store%last)) then analysis_store%last%next => obj else analysis_store%first => obj end if analysis_store%last => obj end subroutine analysis_store_append_object @ %def analysis_store_append_object @ Return a pointer to the analysis object with given ID. <>= function analysis_store_get_object_ptr (id) result (obj) type(string_t), intent(in) :: id type(analysis_object_t), pointer :: obj obj => analysis_store%first do while (associated (obj)) if (obj%id == id) return obj => obj%next end do end function analysis_store_get_object_ptr @ %def analysis_store_get_object_ptr @ Initialize an analysis object: either reset it if present, or append a new entry. <>= subroutine analysis_store_init_object (id, type, obj) type(string_t), intent(in) :: id integer, intent(in) :: type type(analysis_object_t), pointer :: obj, next obj => analysis_store_get_object_ptr (id) if (associated (obj)) then next => analysis_object_get_next_ptr (obj) call analysis_object_final (obj) call analysis_object_init (obj, id, type) call analysis_object_set_next_ptr (obj, next) else call analysis_store_append_object (id, type) obj => analysis_store%last end if end subroutine analysis_store_init_object @ %def analysis_store_init_object @ Get the type of a analysis object <>= public :: analysis_store_get_object_type <>= module function analysis_store_get_object_type (id) result (type) type(string_t), intent(in) :: id integer :: type end function analysis_store_get_object_type <>= module function analysis_store_get_object_type (id) result (type) type(string_t), intent(in) :: id integer :: type type(analysis_object_t), pointer :: object object => analysis_store_get_object_ptr (id) if (associated (object)) then type = object%type else type = AN_UNDEFINED end if end function analysis_store_get_object_type @ %def analysis_store_get_object_type @ Return the number of objects in the store. <>= function analysis_store_get_n_objects () result (n) integer :: n type(analysis_object_t), pointer :: current n = 0 current => analysis_store%first do while (associated (current)) n = n + 1 current => current%next end do end function analysis_store_get_n_objects @ %def analysis_store_get_n_objects @ Allocate an array and fill it with all existing IDs. <>= public :: analysis_store_get_ids <>= module subroutine analysis_store_get_ids (id) type(string_t), dimension(:), allocatable, intent(out) :: id end subroutine analysis_store_get_ids <>= module subroutine analysis_store_get_ids (id) type(string_t), dimension(:), allocatable, intent(out) :: id type(analysis_object_t), pointer :: current integer :: i allocate (id (analysis_store_get_n_objects())) i = 0 current => analysis_store%first do while (associated (current)) i = i + 1 id(i) = current%id current => current%next end do end subroutine analysis_store_get_ids @ %def analysis_store_get_ids @ \subsection{\LaTeX\ driver file} Write a driver file for all objects in the store. <>= subroutine analysis_store_write_driver_all (filename_data, unit) type(string_t), intent(in) :: filename_data integer, intent(in), optional :: unit type(analysis_object_t), pointer :: obj call analysis_store_write_driver_header (unit) obj => analysis_store%first do while (associated (obj)) call analysis_object_write_driver (obj, filename_data, unit) obj => obj%next end do call analysis_store_write_driver_footer (unit) end subroutine analysis_store_write_driver_all @ %def analysis_store_write_driver_all @ Write a driver file for an array of objects. <>= subroutine analysis_store_write_driver_obj (filename_data, id, unit) type(string_t), intent(in) :: filename_data type(string_t), dimension(:), intent(in) :: id integer, intent(in), optional :: unit type(analysis_object_t), pointer :: obj integer :: i call analysis_store_write_driver_header (unit) do i = 1, size (id) obj => analysis_store_get_object_ptr (id(i)) if (associated (obj)) & call analysis_object_write_driver (obj, filename_data, unit) end do call analysis_store_write_driver_footer (unit) end subroutine analysis_store_write_driver_obj @ %def analysis_store_write_driver_obj @ The beginning of the driver file. <>= subroutine analysis_store_write_driver_header (unit) integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit); if (u < 0) return write (u, '(A)') "\documentclass[12pt]{article}" write (u, *) write (u, '(A)') "\usepackage{gamelan}" write (u, '(A)') "\usepackage{amsmath}" write (u, '(A)') "\usepackage{ifpdf}" write (u, '(A)') "\ifpdf" write (u, '(A)') " \DeclareGraphicsRule{*}{mps}{*}{}" write (u, '(A)') "\else" write (u, '(A)') " \DeclareGraphicsRule{*}{eps}{*}{}" write (u, '(A)') "\fi" write (u, *) write (u, '(A)') "\begin{document}" write (u, '(A)') "\begin{gmlfile}" write (u, *) write (u, '(A)') "\begin{gmlcode}" write (u, '(A)') " color col.default, col.excess;" write (u, '(A)') " col.default = 0.9white;" write (u, '(A)') " col.excess = red;" write (u, '(A)') " boolean show_excess;" !!! Future excess options for plots ! if (mcs(1)%plot_excess .and. mcs(1)%unweighted) then ! write (u, '(A)') " show_excess = true;" ! else write (u, '(A)') " show_excess = false;" ! end if write (u, '(A)') "\end{gmlcode}" write (u, *) end subroutine analysis_store_write_driver_header @ %def analysis_store_write_driver_header @ The end of the driver file. <>= subroutine analysis_store_write_driver_footer (unit) integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit); if (u < 0) return write(u, *) write(u, '(A)') "\end{gmlfile}" write(u, '(A)') "\end{document}" end subroutine analysis_store_write_driver_footer @ %def analysis_store_write_driver_footer @ \subsection{API} \subsubsection{Creating new objects} The specific versions below: <>= public :: analysis_init_observable <>= module subroutine analysis_init_observable (id, obs_label, obs_unit, graph_options) type(string_t), intent(in) :: id type(string_t), intent(in), optional :: obs_label, obs_unit type(graph_options_t), intent(in), optional :: graph_options end subroutine analysis_init_observable <>= module subroutine analysis_init_observable (id, obs_label, obs_unit, graph_options) type(string_t), intent(in) :: id type(string_t), intent(in), optional :: obs_label, obs_unit type(graph_options_t), intent(in), optional :: graph_options type(analysis_object_t), pointer :: obj type(observable_t), pointer :: obs call analysis_store_init_object (id, AN_OBSERVABLE, obj) obs => analysis_object_get_observable_ptr (obj) call observable_init (obs, obs_label, obs_unit, graph_options) end subroutine analysis_init_observable @ %def analysis_init_observable <>= public :: analysis_init_histogram <>= interface analysis_init_histogram module procedure analysis_init_histogram_n_bins module procedure analysis_init_histogram_bin_width end interface <>= module subroutine analysis_init_histogram_n_bins & (id, lower_bound, upper_bound, n_bins, normalize_bins, & obs_label, obs_unit, graph_options, drawing_options) type(string_t), intent(in) :: id real(default), intent(in) :: lower_bound, upper_bound integer, intent(in) :: n_bins logical, intent(in) :: normalize_bins type(string_t), intent(in), optional :: obs_label, obs_unit type(graph_options_t), intent(in), optional :: graph_options type(drawing_options_t), intent(in), optional :: drawing_options end subroutine analysis_init_histogram_n_bins module subroutine analysis_init_histogram_bin_width & (id, lower_bound, upper_bound, bin_width, normalize_bins, & obs_label, obs_unit, graph_options, drawing_options) type(string_t), intent(in) :: id real(default), intent(in) :: lower_bound, upper_bound, bin_width logical, intent(in) :: normalize_bins type(string_t), intent(in), optional :: obs_label, obs_unit type(graph_options_t), intent(in), optional :: graph_options type(drawing_options_t), intent(in), optional :: drawing_options end subroutine analysis_init_histogram_bin_width <>= module subroutine analysis_init_histogram_n_bins & (id, lower_bound, upper_bound, n_bins, normalize_bins, & obs_label, obs_unit, graph_options, drawing_options) type(string_t), intent(in) :: id real(default), intent(in) :: lower_bound, upper_bound integer, intent(in) :: n_bins logical, intent(in) :: normalize_bins type(string_t), intent(in), optional :: obs_label, obs_unit type(graph_options_t), intent(in), optional :: graph_options type(drawing_options_t), intent(in), optional :: drawing_options type(analysis_object_t), pointer :: obj type(histogram_t), pointer :: h call analysis_store_init_object (id, AN_HISTOGRAM, obj) h => analysis_object_get_histogram_ptr (obj) call histogram_init (h, id, & lower_bound, upper_bound, n_bins, normalize_bins, & obs_label, obs_unit, graph_options, drawing_options) end subroutine analysis_init_histogram_n_bins module subroutine analysis_init_histogram_bin_width & (id, lower_bound, upper_bound, bin_width, normalize_bins, & obs_label, obs_unit, graph_options, drawing_options) type(string_t), intent(in) :: id real(default), intent(in) :: lower_bound, upper_bound, bin_width logical, intent(in) :: normalize_bins type(string_t), intent(in), optional :: obs_label, obs_unit type(graph_options_t), intent(in), optional :: graph_options type(drawing_options_t), intent(in), optional :: drawing_options type(analysis_object_t), pointer :: obj type(histogram_t), pointer :: h call analysis_store_init_object (id, AN_HISTOGRAM, obj) h => analysis_object_get_histogram_ptr (obj) call histogram_init (h, id, & lower_bound, upper_bound, bin_width, normalize_bins, & obs_label, obs_unit, graph_options, drawing_options) end subroutine analysis_init_histogram_bin_width @ %def analysis_init_histogram_n_bins @ %def analysis_init_histogram_bin_width <>= public :: analysis_init_plot <>= module subroutine analysis_init_plot (id, graph_options, drawing_options) type(string_t), intent(in) :: id type(graph_options_t), intent(in), optional :: graph_options type(drawing_options_t), intent(in), optional :: drawing_options end subroutine analysis_init_plot <>= module subroutine analysis_init_plot (id, graph_options, drawing_options) type(string_t), intent(in) :: id type(graph_options_t), intent(in), optional :: graph_options type(drawing_options_t), intent(in), optional :: drawing_options type(analysis_object_t), pointer :: obj type(plot_t), pointer :: plot call analysis_store_init_object (id, AN_PLOT, obj) plot => analysis_object_get_plot_ptr (obj) call plot_init (plot, id, graph_options, drawing_options) end subroutine analysis_init_plot @ %def analysis_init_plot <>= public :: analysis_init_graph <>= module subroutine analysis_init_graph (id, n_elements, graph_options) type(string_t), intent(in) :: id integer, intent(in) :: n_elements type(graph_options_t), intent(in), optional :: graph_options end subroutine analysis_init_graph <>= module subroutine analysis_init_graph (id, n_elements, graph_options) type(string_t), intent(in) :: id integer, intent(in) :: n_elements type(graph_options_t), intent(in), optional :: graph_options type(analysis_object_t), pointer :: obj type(graph_t), pointer :: graph call analysis_store_init_object (id, AN_GRAPH, obj) graph => analysis_object_get_graph_ptr (obj) call graph_init (graph, id, n_elements, graph_options) end subroutine analysis_init_graph @ %def analysis_init_graph @ \subsubsection{Recording data} This procedure resets an object or the whole store to its initial state. <>= public :: analysis_clear <>= interface analysis_clear module procedure analysis_store_clear_obj module procedure analysis_store_clear_all end interface <>= module subroutine analysis_store_clear_obj (id) type(string_t), intent(in) :: id end subroutine analysis_store_clear_obj module subroutine analysis_store_clear_all () end subroutine analysis_store_clear_all <>= module subroutine analysis_store_clear_obj (id) type(string_t), intent(in) :: id type(analysis_object_t), pointer :: obj obj => analysis_store_get_object_ptr (id) if (associated (obj)) then call analysis_object_clear (obj) end if end subroutine analysis_store_clear_obj module subroutine analysis_store_clear_all () type(analysis_object_t), pointer :: obj obj => analysis_store%first do while (associated (obj)) call analysis_object_clear (obj) obj => obj%next end do end subroutine analysis_store_clear_all @ %def analysis_clear @ There is one generic recording function whose behavior depends on the type of analysis object. <>= public :: analysis_record_data <>= module subroutine analysis_record_data (id, x, y, yerr, xerr, & weight, excess, success, exist) type(string_t), intent(in) :: id real(default), intent(in) :: x real(default), intent(in), optional :: y, yerr, xerr, weight, excess logical, intent(out), optional :: success, exist end subroutine analysis_record_data <>= module subroutine analysis_record_data (id, x, y, yerr, xerr, & weight, excess, success, exist) type(string_t), intent(in) :: id real(default), intent(in) :: x real(default), intent(in), optional :: y, yerr, xerr, weight, excess logical, intent(out), optional :: success, exist type(analysis_object_t), pointer :: obj obj => analysis_store_get_object_ptr (id) if (associated (obj)) then call analysis_object_record_data (obj, x, y, yerr, xerr, & weight, excess, success) if (present (exist)) exist = .true. else if (present (success)) success = .false. if (present (exist)) exist = .false. end if end subroutine analysis_record_data @ %def analysis_record_data @ \subsubsection{Build a graph} This routine sets up the array of graph elements by copying the graph elements given as input. The object must exist and already be initialized as a graph. <>= public :: analysis_fill_graph <>= module subroutine analysis_fill_graph (id, i, id_in, drawing_options) type(string_t), intent(in) :: id integer, intent(in) :: i type(string_t), intent(in) :: id_in type(drawing_options_t), intent(in), optional :: drawing_options end subroutine analysis_fill_graph <>= module subroutine analysis_fill_graph (id, i, id_in, drawing_options) type(string_t), intent(in) :: id integer, intent(in) :: i type(string_t), intent(in) :: id_in type(drawing_options_t), intent(in), optional :: drawing_options type(analysis_object_t), pointer :: obj type(graph_t), pointer :: g type(histogram_t), pointer :: h type(plot_t), pointer :: p obj => analysis_store_get_object_ptr (id) g => analysis_object_get_graph_ptr (obj) obj => analysis_store_get_object_ptr (id_in) if (associated (obj)) then select case (obj%type) case (AN_HISTOGRAM) h => analysis_object_get_histogram_ptr (obj) call graph_insert_histogram (g, i, h, drawing_options) case (AN_PLOT) p => analysis_object_get_plot_ptr (obj) call graph_insert_plot (g, i, p, drawing_options) case default call msg_error ("Graph '" // char (id) // "': Element '" & // char (id_in) // "' is neither histogram nor plot.") end select else call msg_error ("Graph '" // char (id) // "': Element '" & // char (id_in) // "' is undefined.") end if end subroutine analysis_fill_graph @ %def analysis_fill_graph @ \subsubsection{Retrieve generic results} Check if a named object exists. <>= public :: analysis_exists <>= module function analysis_exists (id) result (flag) type(string_t), intent(in) :: id logical :: flag end function analysis_exists <>= module function analysis_exists (id) result (flag) type(string_t), intent(in) :: id logical :: flag type(analysis_object_t), pointer :: obj flag = .true. obj => analysis_store%first do while (associated (obj)) if (obj%id == id) return obj => obj%next end do flag = .false. end function analysis_exists @ %def analysis_exists @ The following functions should work for all kinds of analysis object: <>= public :: analysis_get_n_elements public :: analysis_get_n_entries public :: analysis_get_average public :: analysis_get_error <>= module function analysis_get_n_elements (id) result (n) integer :: n type(string_t), intent(in) :: id end function analysis_get_n_elements module function analysis_get_n_entries (id, within_bounds) result (n) integer :: n type(string_t), intent(in) :: id logical, intent(in), optional :: within_bounds end function analysis_get_n_entries module function analysis_get_average (id, within_bounds) result (avg) real(default) :: avg type(string_t), intent(in) :: id logical, intent(in), optional :: within_bounds end function analysis_get_average module function analysis_get_error (id, within_bounds) result (err) real(default) :: err type(string_t), intent(in) :: id logical, intent(in), optional :: within_bounds end function analysis_get_error <>= module function analysis_get_n_elements (id) result (n) integer :: n type(string_t), intent(in) :: id type(analysis_object_t), pointer :: obj obj => analysis_store_get_object_ptr (id) if (associated (obj)) then n = analysis_object_get_n_elements (obj) else n = 0 end if end function analysis_get_n_elements module function analysis_get_n_entries (id, within_bounds) result (n) integer :: n type(string_t), intent(in) :: id logical, intent(in), optional :: within_bounds type(analysis_object_t), pointer :: obj obj => analysis_store_get_object_ptr (id) if (associated (obj)) then n = analysis_object_get_n_entries (obj, within_bounds) else n = 0 end if end function analysis_get_n_entries module function analysis_get_average (id, within_bounds) result (avg) real(default) :: avg type(string_t), intent(in) :: id type(analysis_object_t), pointer :: obj logical, intent(in), optional :: within_bounds obj => analysis_store_get_object_ptr (id) if (associated (obj)) then avg = analysis_object_get_average (obj, within_bounds) else avg = 0 end if end function analysis_get_average module function analysis_get_error (id, within_bounds) result (err) real(default) :: err type(string_t), intent(in) :: id type(analysis_object_t), pointer :: obj logical, intent(in), optional :: within_bounds obj => analysis_store_get_object_ptr (id) if (associated (obj)) then err = analysis_object_get_error (obj, within_bounds) else err = 0 end if end function analysis_get_error @ %def analysis_get_n_elements @ %def analysis_get_n_entries @ %def analysis_get_average @ %def analysis_get_error @ Return true if any analysis object is graphical <>= public :: analysis_has_plots <>= interface analysis_has_plots module procedure analysis_has_plots_any module procedure analysis_has_plots_obj end interface <>= module function analysis_has_plots_any () result (flag) logical :: flag end function analysis_has_plots_any module function analysis_has_plots_obj (id) result (flag) logical :: flag type(string_t), dimension(:), intent(in) :: id end function analysis_has_plots_obj <>= module function analysis_has_plots_any () result (flag) logical :: flag type(analysis_object_t), pointer :: obj flag = .false. obj => analysis_store%first do while (associated (obj)) flag = analysis_object_has_plot (obj) if (flag) return end do end function analysis_has_plots_any module function analysis_has_plots_obj (id) result (flag) logical :: flag type(string_t), dimension(:), intent(in) :: id type(analysis_object_t), pointer :: obj integer :: i flag = .false. do i = 1, size (id) obj => analysis_store_get_object_ptr (id(i)) if (associated (obj)) then flag = analysis_object_has_plot (obj) if (flag) return end if end do end function analysis_has_plots_obj @ %def analysis_has_plots @ \subsubsection{Iterators} Initialize an iterator for the given object. If the object does not exist or has wrong type, the iterator will be invalid. <>= subroutine analysis_init_iterator (id, iterator) type(string_t), intent(in) :: id type(analysis_iterator_t), intent(out) :: iterator type(analysis_object_t), pointer :: obj obj => analysis_store_get_object_ptr (id) if (associated (obj)) call analysis_iterator_init (iterator, obj) end subroutine analysis_init_iterator @ %def analysis_init_iterator @ \subsubsection{Output} <>= public :: analysis_write <>= interface analysis_write module procedure analysis_write_object module procedure analysis_write_all end interface @ %def interface <>= module subroutine analysis_write_object (id, unit, verbose) type(string_t), intent(in) :: id integer, intent(in), optional :: unit logical, intent(in), optional :: verbose end subroutine analysis_write_object module subroutine analysis_write_all (unit, verbose) integer, intent(in), optional :: unit logical, intent(in), optional :: verbose end subroutine analysis_write_all <>= module subroutine analysis_write_object (id, unit, verbose) type(string_t), intent(in) :: id integer, intent(in), optional :: unit logical, intent(in), optional :: verbose type(analysis_object_t), pointer :: obj obj => analysis_store_get_object_ptr (id) if (associated (obj)) then call analysis_object_write (obj, unit, verbose) else call msg_error ("Analysis object '" // char (id) // "' not found") end if end subroutine analysis_write_object module subroutine analysis_write_all (unit, verbose) integer, intent(in), optional :: unit logical, intent(in), optional :: verbose type(analysis_object_t), pointer :: obj integer :: u u = given_output_unit (unit); if (u < 0) return obj => analysis_store%first do while (associated (obj)) call analysis_object_write (obj, unit, verbose) obj => obj%next end do end subroutine analysis_write_all @ %def analysis_write_object @ %def analysis_write_all <>= public :: analysis_write_driver <>= module subroutine analysis_write_driver (filename_data, id, unit) type(string_t), intent(in) :: filename_data type(string_t), dimension(:), intent(in), optional :: id integer, intent(in), optional :: unit end subroutine analysis_write_driver <>= module subroutine analysis_write_driver (filename_data, id, unit) type(string_t), intent(in) :: filename_data type(string_t), dimension(:), intent(in), optional :: id integer, intent(in), optional :: unit if (present (id)) then call analysis_store_write_driver_obj (filename_data, id, unit) else call analysis_store_write_driver_all (filename_data, unit) end if end subroutine analysis_write_driver @ %def analysis_write_driver <>= public :: analysis_compile_tex <>= module subroutine analysis_compile_tex (file, has_gmlcode, os_data) type(string_t), intent(in) :: file logical, intent(in) :: has_gmlcode type(os_data_t), intent(in) :: os_data end subroutine analysis_compile_tex <>= module subroutine analysis_compile_tex (file, has_gmlcode, os_data) type(string_t), intent(in) :: file logical, intent(in) :: has_gmlcode type(os_data_t), intent(in) :: os_data integer :: status if (os_data%event_analysis_ps) then call os_system_call ("make compile " // os_data%makeflags // " -f " // & char (file) // "_ana.makefile", status) if (status /= 0) then call msg_error ("Unable to compile analysis output file") end if else call msg_warning ("Skipping results display because " & // "latex/mpost/dvips is not available") end if end subroutine analysis_compile_tex @ %def analysis_compile_tex @ Write header for generic data output to an ifile. <>= subroutine analysis_get_header (id, header, comment) type(string_t), intent(in) :: id type(ifile_t), intent(inout) :: header type(string_t), intent(in), optional :: comment type(analysis_object_t), pointer :: object object => analysis_store_get_object_ptr (id) if (associated (object)) then call analysis_object_get_header (object, header, comment) end if end subroutine analysis_get_header @ %def analysis_get_header @ Write a makefile in order to do the compile steps. <>= public :: analysis_write_makefile <>= module subroutine analysis_write_makefile (filename, unit, has_gmlcode, os_data) type(string_t), intent(in) :: filename integer, intent(in) :: unit logical, intent(in) :: has_gmlcode type(os_data_t), intent(in) :: os_data end subroutine analysis_write_makefile <>= module subroutine analysis_write_makefile (filename, unit, has_gmlcode, os_data) type(string_t), intent(in) :: filename integer, intent(in) :: unit logical, intent(in) :: has_gmlcode type(os_data_t), intent(in) :: os_data write (unit, "(3A)") "# WHIZARD: Makefile for analysis '", & char (filename), "'" write (unit, "(A)") "# Automatically generated file, do not edit" write (unit, "(A)") "" write (unit, "(A)") "# LaTeX setup" write (unit, "(A)") "LATEX = " // char (os_data%latex) write (unit, "(A)") "MPOST = " // char (os_data%mpost) write (unit, "(A)") "GML = " // char (os_data%gml) write (unit, "(A)") "DVIPS = " // char (os_data%dvips) write (unit, "(A)") "PS2PDF = " // char (os_data%ps2pdf) write (unit, "(A)") 'TEX_FLAGS = "$$TEXINPUTS:' // & char(os_data%whizard_texpath) // '"' write (unit, "(A)") 'MP_FLAGS = "$$MPINPUTS:' // & char(os_data%whizard_texpath) // '"' write (unit, "(A)") "" write (unit, "(5A)") "TEX_SOURCES = ", char (filename), ".tex" if (os_data%event_analysis_pdf) then write (unit, "(5A)") "TEX_OBJECTS = ", char (filename), ".pdf" else write (unit, "(5A)") "TEX_OBJECTS = ", char (filename), ".ps" end if if (os_data%event_analysis_ps) then if (os_data%event_analysis_pdf) then write (unit, "(5A)") char (filename), ".pdf: ", & char (filename), ".tex" else write (unit, "(5A)") char (filename), ".ps: ", & char (filename), ".tex" end if write (unit, "(5A)") TAB, "-TEXINPUTS=$(TEX_FLAGS) $(LATEX) " // & char (filename) // ".tex" if (has_gmlcode) then write (unit, "(5A)") TAB, "$(GML) " // char (filename) write (unit, "(5A)") TAB, "TEXINPUTS=$(TEX_FLAGS) $(LATEX) " // & char (filename) // ".tex" end if write (unit, "(5A)") TAB, "$(DVIPS) -o " // char (filename) // ".ps " // & char (filename) // ".dvi" if (os_data%event_analysis_pdf) then write (unit, "(5A)") TAB, "$(PS2PDF) " // char (filename) // ".ps" end if end if write (unit, "(A)") write (unit, "(A)") "compile: $(TEX_OBJECTS)" write (unit, "(A)") ".PHONY: compile" write (unit, "(A)") write (unit, "(5A)") "CLEAN_OBJECTS = ", char (filename), ".aux" write (unit, "(5A)") "CLEAN_OBJECTS += ", char (filename), ".log" write (unit, "(5A)") "CLEAN_OBJECTS += ", char (filename), ".dvi" write (unit, "(5A)") "CLEAN_OBJECTS += ", char (filename), ".out" write (unit, "(5A)") "CLEAN_OBJECTS += ", char (filename), ".[1-9]" write (unit, "(5A)") "CLEAN_OBJECTS += ", char (filename), ".[1-9][0-9]" write (unit, "(5A)") "CLEAN_OBJECTS += ", char (filename), ".[1-9][0-9][0-9]" write (unit, "(5A)") "CLEAN_OBJECTS += ", char (filename), ".t[1-9]" write (unit, "(5A)") "CLEAN_OBJECTS += ", char (filename), ".t[1-9][0-9]" write (unit, "(5A)") "CLEAN_OBJECTS += ", char (filename), ".t[1-9][0-9][0-9]" write (unit, "(5A)") "CLEAN_OBJECTS += ", char (filename), ".ltp" write (unit, "(5A)") "CLEAN_OBJECTS += ", char (filename), ".mp" write (unit, "(5A)") "CLEAN_OBJECTS += ", char (filename), ".mpx" write (unit, "(5A)") "CLEAN_OBJECTS += ", char (filename), ".dvi" write (unit, "(5A)") "CLEAN_OBJECTS += ", char (filename), ".ps" write (unit, "(5A)") "CLEAN_OBJECTS += ", char (filename), ".pdf" write (unit, "(A)") write (unit, "(A)") "# Generic cleanup targets" write (unit, "(A)") "clean-objects:" write (unit, "(A)") TAB // "rm -f $(CLEAN_OBJECTS)" write (unit, "(A)") "" write (unit, "(A)") "clean: clean-objects" write (unit, "(A)") ".PHONY: clean" end subroutine analysis_write_makefile @ %def analysis_write_makefile @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[analysis_ut.f90]]>>= <> module analysis_ut use unit_tests use analysis_uti <> <> contains <> end module analysis_ut @ %def analysis_ut @ <<[[analysis_uti.f90]]>>= <> module analysis_uti <> <> use format_defs, only: FMT_19 use analysis <> <> contains <> end module analysis_uti @ %def analysis_ut @ API: driver for the unit tests below. <>= public :: analysis_test <>= subroutine analysis_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine analysis_test @ %def analysis_test <>= call test (analysis_1, "analysis_1", & "check elementary analysis building blocks", & u, results) <>= public :: analysis_1 <>= subroutine analysis_1 (u) integer, intent(in) :: u type(string_t) :: id1, id2, id3, id4 integer :: i id1 = "foo" id2 = "bar" id3 = "hist" id4 = "plot" write (u, "(A)") "* Test output: Analysis" write (u, "(A)") "* Purpose: test the analysis routines" write (u, "(A)") call analysis_init_observable (id1) call analysis_init_observable (id2) call analysis_init_histogram & (id3, 0.5_default, 5.5_default, 1._default, normalize_bins=.false.) call analysis_init_plot (id4) do i = 1, 3 write (u, "(A,1x," // FMT_19 // ")") "data = ", real(i,default) call analysis_record_data (id1, real(i,default)) call analysis_record_data (id2, real(i,default), & weight=real(i,default)) call analysis_record_data (id3, real(i,default)) call analysis_record_data (id4, real(i,default), real(i,default)**2) end do write (u, "(A,10(1x,I5))") "n_entries = ", & analysis_get_n_entries (id1), & analysis_get_n_entries (id2), & analysis_get_n_entries (id3), & analysis_get_n_entries (id3, within_bounds = .true.), & analysis_get_n_entries (id4), & analysis_get_n_entries (id4, within_bounds = .true.) write (u, "(A,10(1x," // FMT_19 // "))") "average = ", & analysis_get_average (id1), & analysis_get_average (id2), & analysis_get_average (id3), & analysis_get_average (id3, within_bounds = .true.) write (u, "(A,10(1x," // FMT_19 // "))") "error = ", & analysis_get_error (id1), & analysis_get_error (id2), & analysis_get_error (id3), & analysis_get_error (id3, within_bounds = .true.) write (u, "(A)") write (u, "(A)") "* Clear analysis #2" write (u, "(A)") call analysis_clear (id2) do i = 4, 6 print *, "data = ", real(i,default) call analysis_record_data (id1, real(i,default)) call analysis_record_data (id2, real(i,default), & weight=real(i,default)) call analysis_record_data (id3, real(i,default)) call analysis_record_data (id4, real(i,default), real(i,default)**2) end do write (u, "(A,10(1x,I5))") "n_entries = ", & analysis_get_n_entries (id1), & analysis_get_n_entries (id2), & analysis_get_n_entries (id3), & analysis_get_n_entries (id3, within_bounds = .true.), & analysis_get_n_entries (id4), & analysis_get_n_entries (id4, within_bounds = .true.) write (u, "(A,10(1x," // FMT_19 // "))") "average = ", & analysis_get_average (id1), & analysis_get_average (id2), & analysis_get_average (id3), & analysis_get_average (id3, within_bounds = .true.) write (u, "(A,10(1x," // FMT_19 // "))") "error = ", & analysis_get_error (id1), & analysis_get_error (id2), & analysis_get_error (id3), & analysis_get_error (id3, within_bounds = .true.) write (u, "(A)") call analysis_write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call analysis_clear () call analysis_final () write (u, "(A)") write (u, "(A)") "* Test output end: analysis_1" end subroutine analysis_1 @ %def analysis_1 Index: trunk/tests/ext_tests_nlo/nlo_pptt_ew.sh =================================================================== --- trunk/tests/ext_tests_nlo/nlo_pptt_ew.sh (revision 0) +++ trunk/tests/ext_tests_nlo/nlo_pptt_ew.sh (revision 8818) @@ -0,0 +1,37 @@ +#!/bin/sh +echo "Running script $0" +name=`basename @script@` +if test -f ref-output/$name.ref; then + if test -f OCAML_FLAG -a -f OPENLOOPS_FLAG -a -f FASTJET_FLAG -a -f LHAPDF6_FLAG; then + ./run_whizard.sh @script@ --no-logging + mv $name.log $name.log.tmp + cat $name.log.tmp | sed -e 's/Loading library:.*/Loading library: [...]/' > $name.log + rm $name.log.tmp + diff ref-output/$name.ref $name.log + diffrc=$? + grep --quiet "The desired process has not been found" $name.run.log + greprc=$? + if test $diffrc -gt 0 -a $greprc -eq 0; then + echo "|=============================================================================|" + echo "OpenLoops process library missing" + exit 99 + fi + grep --quiet "'LUXqed_plus_PDF4LHC15_nnlo_100' not found" $name.run.log + greprc=$? + if test $diffrc -gt 0 -a $greprc -eq 0; then + echo "|=============================================================================|" + echo "LHAPDF: Data file 'LUXqed_plus_PDF4LHC15_nnlo_100' missing" + exit 99 + fi + exit $diffrc + else + echo "|=============================================================================|" + echo "No O'Mega/OpenLoops matrix elements / FastJet / LHAPDF6 available" + exit 77 + fi +else + echo "|=============================================================================|" + echo "$name.ref not found" + exit 77 +fi + Index: trunk/tests/ext_tests_nlo/Makefile.am =================================================================== --- trunk/tests/ext_tests_nlo/Makefile.am (revision 8817) +++ trunk/tests/ext_tests_nlo/Makefile.am (revision 8818) @@ -1,326 +1,328 @@ ## Makefile.am -- Makefile for executable WHIZARD test scripts ## ## Process this file with automake to produce Makefile.in ## ######################################################################## # # Copyright (C) 1999-2022 by # Wolfgang Kilian # Thorsten Ohl # Juergen Reuter # with contributions from # cf. main AUTHORS file # # WHIZARD is free software; you can redistribute it and/or modify it # under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2, or (at your option) # any later version. # # WHIZARD is distributed in the hope that it will be useful, but # WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # GNU General Public License for more details. # # You should have received a copy of the GNU General Public License # along with this program; if not, write to the Free Software # Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA. # ######################################################################## WHIZARD_DRIVER = run_whizard.sh TESTS_EXTENDED = \ nlo_ee4b.run \ nlo_ee4j.run \ nlo_ee4t.run \ nlo_ee4tj.run \ nlo_ee5j.run \ nlo_eebb.run \ nlo_eebbj.run \ nlo_eebbjj.run \ nlo_eejj.run \ nlo_eejjj.run \ nlo_eett.run \ nlo_eetta.run \ nlo_eettaa.run \ nlo_eettah.run \ nlo_eettaj.run \ nlo_eettajj.run \ nlo_eettaz.run \ nlo_eettbb.run \ nlo_eetth.run \ nlo_eetthh.run \ nlo_eetthj.run \ nlo_eetthjj.run \ nlo_eetthz.run \ nlo_eettj.run \ nlo_eettjj.run \ nlo_eettjjj.run \ nlo_eettwjj.run \ nlo_eettww.run \ nlo_eettz.run \ nlo_eettzj.run \ nlo_eettzjj.run \ nlo_eettzz.run \ nlo_ppzj_real_partition.run \ nlo_ppz.run \ nlo_ppzj_sim_1.run \ nlo_ppzj_sim_2.run \ nlo_ppzj_sim_3.run \ nlo_ppzj_sim_4.run \ nlo_ppw.run \ nlo_ppzz.run \ nlo_ppzw.run \ nlo_pptttt.run \ nlo_ppee_ew.run \ nlo_pphee_ew.run \ nlo_pphjj_ew.run \ nlo_pphz_ew.run \ nlo_ppllll_ew.run \ nlo_ppllnn_ew.run \ + nlo_pptt_ew.run \ nlo_pptj_ew.run \ nlo_ppwhh_ew.run \ nlo_ppww_ew.run \ nlo_ppwzh_ew.run \ nlo_ppz_ew.run \ nlo_ppzzz_ew.run XFAIL_TESTS_EXTENDED = TESTS_REQ_GAMELAN = TEST_DRIVERS_RUN = \ $(TESTS_EXTENDED) TEST_DRIVERS_SH = $(TEST_DRIVERS_RUN:.run=.sh) ######################################################################## TESTS = $(TESTS_EXTENDED) XFAIL_TESTS = $(XFAIL_TESTS_EXTENDED) EXTRA_DIST = $(TEST_DRIVERS_SH) ######################################################################## VPATH = $(srcdir) SUFFIXES = .sh .run .sh.run: @rm -f $@ @if test -f $(top_builddir)/share/tests/ext_tests_nlo/$*.sin; then \ $(SED) 's|@script@|$(top_builddir)/share/tests/ext_tests_nlo/$*|g' $< > $@; \ elif test -f $(top_srcdir)/share/tests/ext_tests_nlo/$*.sin; then \ $(SED) 's|@script@|$(top_srcdir)/share/tests/ext_tests_nlo/$*|g' $< > $@; \ fi @chmod +x $@ nlo_eejj.run: nlo_settings.sin nlo_eejjj.run: nlo_settings.sin nlo_ee4j.run: nlo_settings.sin nlo_ee5j.run: nlo_settings.sin nlo_eebb.run: nlo_settings.sin nlo_eebbj.run: nlo_settings.sin nlo_eebbjj.run: nlo_settings.sin nlo_ee4b.run: nlo_settings.sin nlo_eett.run: nlo_settings.sin nlo_eettj.run: nlo_settings.sin nlo_eettjj.run: nlo_settings.sin nlo_eettjjj.run: nlo_settings.sin nlo_eettbb.run: nlo_settings.sin nlo_eetta.run: nlo_settings.sin nlo_eettaa.run: nlo_settings.sin nlo_eettaj.run: nlo_settings.sin nlo_eettajj.run: nlo_settings.sin nlo_eettah.run: nlo_settings.sin nlo_eettaz.run: nlo_settings.sin nlo_eettz.run: nlo_settings.sin nlo_eettzj.run: nlo_settings.sin nlo_eettzjj.run: nlo_settings.sin nlo_eettzz.run: nlo_settings.sin nlo_eettwjj.run: nlo_settings.sin nlo_eettww.run: nlo_settings.sin nlo_eetth.run: nlo_settings.sin nlo_eetthj.run: nlo_settings.sin nlo_eetthjj.run: nlo_settings.sin nlo_eetthh.run: nlo_settings.sin nlo_eetthz.run: nlo_settings.sin nlo_ee4t.run: nlo_settings.sin nlo_ee4tj.run: nlo_settings.sin nlo_ppzj_real_partition.run: nlo_settings.sin nlo_ppz.run: nlo_settings.sin nlo_ppw.run: nlo_settings.sin nlo_ppzz.run: nlo_settings.sin nlo_ppzw.run: nlo_settings.sin nlo_pptttt.run: nlo_settings.sin nlo_ppzj_sim_1.run: nlo_settings.sin nlo_ppzj_sim_2.run: nlo_settings.sin nlo_ppzj_sim_3.run: nlo_settings.sin nlo_ppzj_sim_4.run: nlo_settings.sin nlo_ppee_ew.run: nlo_settings_ew.sin nlo_pphee_ew.run: nlo_settings_ew.sin nlo_pphjj_ew.run: nlo_settings_ew.sin nlo_pphz_ew.run: nlo_settings_ew.sin nlo_ppllll_ew.run: nlo_settings_ew.sin nlo_ppllnn_ew.run: nlo_settings_ew.sin +nlo_pptt_ew.run: nlo_settings_ew.sin nlo_pptj_ew.run: nlo_settings_ew.sin nlo_ppwhh_ew.run: nlo_settings_ew.sin nlo_ppww_ew.run: nlo_settings_ew.sin nlo_ppwzh_ew.run: nlo_settings_ew.sin nlo_ppz_ew.run: nlo_settings_ew.sin nlo_ppzzz_ew.run: nlo_settings_ew.sin nlo_settings.sin: $(top_builddir)/share/tests/ext_tests_nlo/nlo_settings.sin cp $< $@ nlo_settings_ew.sin: $(top_builddir)/share/tests/ext_tests_nlo/nlo_settings_ew.sin cp $< $@ if MPOST_AVAILABLE $(TESTS_REQ_GAMELAN): gamelan.sty $(UNIT_TESTS_REQ_GAMELAN): gamelan.sty gamelan.sty: $(top_builddir)/src/gamelan/gamelan.sty cp $< $@ $(top_builddir)/src/gamelan/gamelan.sty: $(MAKE) -C $(top_builddir)/src/gamelan gamelan.sty endif BUILT_SOURCES = \ TESTFLAG \ HEPMC2_FLAG \ HEPMC3_FLAG \ LCIO_FLAG \ FASTJET_FLAG \ LHAPDF5_FLAG \ LHAPDF6_FLAG \ GAMELAN_FLAG \ EVENT_ANALYSIS_FLAG \ OCAML_FLAG \ PYTHON_FLAG \ PYTHIA6_FLAG \ OPENLOOPS_FLAG \ GOSAM_FLAG \ STATIC_FLAG \ ref-output # If this file is found in the working directory, WHIZARD # will use the paths for the uninstalled version (source/build tree), # otherwise it uses the installed version TESTFLAG: touch $@ FASTJET_FLAG: if FASTJET_AVAILABLE touch $@ endif HEPMC2_FLAG: if HEPMC2_AVAILABLE touch $@ endif HEPMC3_FLAG: if HEPMC3_AVAILABLE touch $@ endif LCIO_FLAG: if LCIO_AVAILABLE touch $@ endif LHAPDF5_FLAG: if LHAPDF5_AVAILABLE touch $@ endif LHAPDF6_FLAG: if LHAPDF6_AVAILABLE touch $@ endif GAMELAN_FLAG: if MPOST_AVAILABLE touch $@ endif OCAML_FLAG: if OCAML_AVAILABLE touch $@ endif PYTHON_FLAG: if PYTHON_AVAILABLE touch $@ endif PYTHIA6_FLAG: if PYTHIA6_AVAILABLE touch $@ endif OPENLOOPS_FLAG: if OPENLOOPS_AVAILABLE touch $@ endif GOSAM_FLAG: if GOSAM_AVAILABLE touch $@ endif EVENT_ANALYSIS_FLAG: if EVENT_ANALYSIS_AVAILABLE touch $@ endif STATIC_FLAG: if STATIC_AVAILABLE touch $@ endif # The reference output files are in the source directory. Copy them here. ref-output: $(top_srcdir)/share/tests/ext_tests_nlo/ref-output mkdir -p ref-output for f in $ # Thorsten Ohl # Juergen Reuter # with contributions from # cf. main AUTHORS file # # WHIZARD is free software; you can redistribute it and/or modify it # under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2, or (at your option) # any later version. # # WHIZARD is distributed in the hope that it will be useful, but # WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # GNU General Public License for more details. # # You should have received a copy of the GNU General Public License # along with this program; if not, write to the Free Software # Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA. # ######################################################################## EXTRA_DIST = \ $(TESTSUITE_MACROS) $(TESTSUITES_M4) $(TESTSUITES_SIN) \ $(TESTSUITE_TOOLS) \ $(REF_OUTPUT_FILES) \ cascades2_1.fds \ cascades2_2.fds \ cascades2_lexer_1.fds \ ext_tests_nmssm/nmssm.slha \ functional_tests/structure_2_inc.sin functional_tests/testproc_3.phs \ functional_tests/susyhit.in \ functional_tests/ufo_5_test.slha TESTSUITE_MACROS = testsuite.m4 TESTSUITE_TOOLS = \ check-debug-output.py \ check-debug-output-hadro.py \ check-hepmc-weights.py \ compare-histograms.py \ compare-integrals.py \ compare-integrals-multi.py \ compare-methods.py REF_OUTPUT_FILES = \ extra_integration_results.dat \ $(REF_OUTPUT_FILES_BASE) $(REF_OUTPUT_FILES_DOUBLE) \ $(REF_OUTPUT_FILES_PREC) $(REF_OUTPUT_FILES_EXT) \ $(REF_OUTPUT_FILES_QUAD) REF_OUTPUT_FILES_BASE = \ unit_tests/ref-output/analysis_1.ref \ unit_tests/ref-output/api_1.ref \ unit_tests/ref-output/api_2.ref \ unit_tests/ref-output/api_3.ref \ unit_tests/ref-output/api_4.ref \ unit_tests/ref-output/api_5.ref \ unit_tests/ref-output/api_6.ref \ unit_tests/ref-output/api_7.ref \ unit_tests/ref-output/api_8.ref \ unit_tests/ref-output/api_c_1.ref \ unit_tests/ref-output/api_c_2.ref \ unit_tests/ref-output/api_c_3.ref \ unit_tests/ref-output/api_c_4.ref \ unit_tests/ref-output/api_c_5.ref \ unit_tests/ref-output/api_cc_1.ref \ unit_tests/ref-output/api_cc_2.ref \ unit_tests/ref-output/api_cc_3.ref \ unit_tests/ref-output/api_cc_4.ref \ unit_tests/ref-output/api_cc_5.ref \ unit_tests/ref-output/api_hepmc2_1.ref \ unit_tests/ref-output/api_hepmc2_cc_1.ref \ unit_tests/ref-output/api_hepmc3_1.ref \ unit_tests/ref-output/api_hepmc3_cc_1.ref \ unit_tests/ref-output/api_lcio_1.ref \ unit_tests/ref-output/api_lcio_cc_1.ref \ unit_tests/ref-output/array_list_1.ref \ unit_tests/ref-output/auto_components_1.ref \ unit_tests/ref-output/auto_components_2.ref \ unit_tests/ref-output/auto_components_3.ref \ unit_tests/ref-output/beam_1.ref \ unit_tests/ref-output/beam_2.ref \ unit_tests/ref-output/beam_3.ref \ unit_tests/ref-output/beam_structures_1.ref \ unit_tests/ref-output/beam_structures_2.ref \ unit_tests/ref-output/beam_structures_3.ref \ unit_tests/ref-output/beam_structures_4.ref \ unit_tests/ref-output/beam_structures_5.ref \ unit_tests/ref-output/beam_structures_6.ref \ unit_tests/ref-output/binary_tree_1.ref \ unit_tests/ref-output/blha_1.ref \ unit_tests/ref-output/blha_2.ref \ unit_tests/ref-output/blha_3.ref \ unit_tests/ref-output/bloch_vectors_1.ref \ unit_tests/ref-output/bloch_vectors_2.ref \ unit_tests/ref-output/bloch_vectors_3.ref \ unit_tests/ref-output/bloch_vectors_4.ref \ unit_tests/ref-output/bloch_vectors_5.ref \ unit_tests/ref-output/bloch_vectors_6.ref \ unit_tests/ref-output/bloch_vectors_7.ref \ unit_tests/ref-output/cascades2_1.ref \ unit_tests/ref-output/cascades2_2.ref \ unit_tests/ref-output/cascades2_lexer_1.ref \ unit_tests/ref-output/cascades_1.ref \ unit_tests/ref-output/cascades_2.ref \ unit_tests/ref-output/color_1.ref \ unit_tests/ref-output/color_2.ref \ unit_tests/ref-output/commands_1.ref \ unit_tests/ref-output/commands_2.ref \ unit_tests/ref-output/commands_3.ref \ unit_tests/ref-output/commands_4.ref \ unit_tests/ref-output/commands_5.ref \ unit_tests/ref-output/commands_6.ref \ unit_tests/ref-output/commands_7.ref \ unit_tests/ref-output/commands_8.ref \ unit_tests/ref-output/commands_9.ref \ unit_tests/ref-output/commands_10.ref \ unit_tests/ref-output/commands_11.ref \ unit_tests/ref-output/commands_12.ref \ unit_tests/ref-output/commands_13.ref \ unit_tests/ref-output/commands_14.ref \ unit_tests/ref-output/commands_15.ref \ unit_tests/ref-output/commands_16.ref \ unit_tests/ref-output/commands_17.ref \ unit_tests/ref-output/commands_18.ref \ unit_tests/ref-output/commands_19.ref \ unit_tests/ref-output/commands_20.ref \ unit_tests/ref-output/commands_21.ref \ unit_tests/ref-output/commands_22.ref \ unit_tests/ref-output/commands_23.ref \ unit_tests/ref-output/commands_24.ref \ unit_tests/ref-output/commands_25.ref \ unit_tests/ref-output/commands_26.ref \ unit_tests/ref-output/commands_27.ref \ unit_tests/ref-output/commands_28.ref \ unit_tests/ref-output/commands_29.ref \ unit_tests/ref-output/commands_30.ref \ unit_tests/ref-output/commands_31.ref \ unit_tests/ref-output/commands_32.ref \ unit_tests/ref-output/commands_33.ref \ unit_tests/ref-output/commands_34.ref \ unit_tests/ref-output/compilations_1.ref \ unit_tests/ref-output/compilations_2.ref \ unit_tests/ref-output/compilations_3.ref \ unit_tests/ref-output/compilations_static_1.ref \ unit_tests/ref-output/compilations_static_2.ref \ unit_tests/ref-output/cputime_1.ref \ unit_tests/ref-output/cputime_2.ref \ unit_tests/ref-output/decays_1.ref \ unit_tests/ref-output/decays_2.ref \ unit_tests/ref-output/decays_3.ref \ unit_tests/ref-output/decays_4.ref \ unit_tests/ref-output/decays_5.ref \ unit_tests/ref-output/decays_6.ref \ unit_tests/ref-output/dispatch_1.ref \ unit_tests/ref-output/dispatch_2.ref \ unit_tests/ref-output/dispatch_7.ref \ unit_tests/ref-output/dispatch_8.ref \ unit_tests/ref-output/dispatch_10.ref \ unit_tests/ref-output/dispatch_11.ref \ unit_tests/ref-output/dispatch_mci_1.ref \ unit_tests/ref-output/dispatch_phs_1.ref \ unit_tests/ref-output/dispatch_phs_2.ref \ unit_tests/ref-output/dispatch_rng_1.ref \ unit_tests/ref-output/dispatch_transforms_1.ref \ unit_tests/ref-output/dispatch_transforms_2.ref \ unit_tests/ref-output/eio_ascii_1.ref \ unit_tests/ref-output/eio_ascii_2.ref \ unit_tests/ref-output/eio_ascii_3.ref \ unit_tests/ref-output/eio_ascii_4.ref \ unit_tests/ref-output/eio_ascii_5.ref \ unit_tests/ref-output/eio_ascii_6.ref \ unit_tests/ref-output/eio_ascii_7.ref \ unit_tests/ref-output/eio_ascii_8.ref \ unit_tests/ref-output/eio_ascii_9.ref \ unit_tests/ref-output/eio_ascii_10.ref \ unit_tests/ref-output/eio_ascii_11.ref \ unit_tests/ref-output/eio_base_1.ref \ unit_tests/ref-output/eio_checkpoints_1.ref \ unit_tests/ref-output/eio_data_1.ref \ unit_tests/ref-output/eio_data_2.ref \ unit_tests/ref-output/eio_direct_1.ref \ unit_tests/ref-output/eio_dump_1.ref \ unit_tests/ref-output/eio_hepmc2_1.ref \ unit_tests/ref-output/eio_hepmc2_2.ref \ unit_tests/ref-output/eio_hepmc2_3.ref \ unit_tests/ref-output/eio_hepmc3_1.ref \ unit_tests/ref-output/eio_hepmc3_2.ref \ unit_tests/ref-output/eio_hepmc3_3.ref \ unit_tests/ref-output/eio_lcio_1.ref \ unit_tests/ref-output/eio_lcio_2.ref \ unit_tests/ref-output/eio_lhef_1.ref \ unit_tests/ref-output/eio_lhef_2.ref \ unit_tests/ref-output/eio_lhef_3.ref \ unit_tests/ref-output/eio_lhef_4.ref \ unit_tests/ref-output/eio_lhef_5.ref \ unit_tests/ref-output/eio_lhef_6.ref \ unit_tests/ref-output/eio_raw_1.ref \ unit_tests/ref-output/eio_raw_2.ref \ unit_tests/ref-output/eio_stdhep_1.ref \ unit_tests/ref-output/eio_stdhep_2.ref \ unit_tests/ref-output/eio_stdhep_3.ref \ unit_tests/ref-output/eio_stdhep_4.ref \ unit_tests/ref-output/eio_weights_1.ref \ unit_tests/ref-output/eio_weights_2.ref \ unit_tests/ref-output/eio_weights_3.ref \ unit_tests/ref-output/electron_pdfs_1.ref \ unit_tests/ref-output/electron_pdfs_2.ref \ unit_tests/ref-output/electron_pdfs_3.ref \ unit_tests/ref-output/electron_pdfs_4.ref \ unit_tests/ref-output/electron_pdfs_5.ref \ unit_tests/ref-output/electron_pdfs_6.ref \ unit_tests/ref-output/epa_handler_1.ref \ unit_tests/ref-output/epa_handler_2.ref \ unit_tests/ref-output/epa_handler_3.ref \ unit_tests/ref-output/evaluator_1.ref \ unit_tests/ref-output/evaluator_2.ref \ unit_tests/ref-output/evaluator_3.ref \ unit_tests/ref-output/evaluator_4.ref \ unit_tests/ref-output/event_streams_1.ref \ unit_tests/ref-output/event_streams_2.ref \ unit_tests/ref-output/event_streams_3.ref \ unit_tests/ref-output/event_streams_4.ref \ unit_tests/ref-output/event_transforms_1.ref \ unit_tests/ref-output/events_1.ref \ unit_tests/ref-output/events_2.ref \ unit_tests/ref-output/events_3.ref \ unit_tests/ref-output/events_4.ref \ unit_tests/ref-output/events_5.ref \ unit_tests/ref-output/events_6.ref \ unit_tests/ref-output/events_7.ref \ unit_tests/ref-output/expressions_1.ref \ unit_tests/ref-output/expressions_2.ref \ unit_tests/ref-output/expressions_3.ref \ unit_tests/ref-output/expressions_4.ref \ unit_tests/ref-output/fks_regions_1.ref \ unit_tests/ref-output/fks_regions_2.ref \ unit_tests/ref-output/fks_regions_3.ref \ unit_tests/ref-output/fks_regions_4.ref \ unit_tests/ref-output/fks_regions_5.ref \ unit_tests/ref-output/fks_regions_6.ref \ unit_tests/ref-output/fks_regions_7.ref \ unit_tests/ref-output/fks_regions_8.ref \ unit_tests/ref-output/format_1.ref \ unit_tests/ref-output/grids_1.ref \ unit_tests/ref-output/grids_2.ref \ unit_tests/ref-output/grids_3.ref \ unit_tests/ref-output/grids_4.ref \ unit_tests/ref-output/grids_5.ref \ unit_tests/ref-output/hep_events_1.ref \ unit_tests/ref-output/hepmc2_interface_1.ref \ unit_tests/ref-output/hepmc3_interface_1.ref \ unit_tests/ref-output/integration_results_1.ref \ unit_tests/ref-output/integration_results_2.ref \ unit_tests/ref-output/integration_results_3.ref \ unit_tests/ref-output/integration_results_4.ref \ unit_tests/ref-output/integration_results_5.ref \ unit_tests/ref-output/integrations_1.ref \ unit_tests/ref-output/integrations_2.ref \ unit_tests/ref-output/integrations_3.ref \ unit_tests/ref-output/integrations_4.ref \ unit_tests/ref-output/integrations_5.ref \ unit_tests/ref-output/integrations_6.ref \ unit_tests/ref-output/integrations_7.ref \ unit_tests/ref-output/integrations_8.ref \ unit_tests/ref-output/integrations_9.ref \ unit_tests/ref-output/integrations_history_1.ref \ unit_tests/ref-output/interaction_1.ref \ unit_tests/ref-output/isr_handler_1.ref \ unit_tests/ref-output/isr_handler_2.ref \ unit_tests/ref-output/isr_handler_3.ref \ unit_tests/ref-output/iterations_1.ref \ unit_tests/ref-output/iterations_2.ref \ unit_tests/ref-output/iterator_1.ref \ unit_tests/ref-output/jets_1.ref \ unit_tests/ref-output/lcio_interface_1.ref \ unit_tests/ref-output/lexer_1.ref \ unit_tests/ref-output/mci_base_1.ref \ unit_tests/ref-output/mci_base_2.ref \ unit_tests/ref-output/mci_base_3.ref \ unit_tests/ref-output/mci_base_4.ref \ unit_tests/ref-output/mci_base_5.ref \ unit_tests/ref-output/mci_base_6.ref \ unit_tests/ref-output/mci_base_7.ref \ unit_tests/ref-output/mci_base_8.ref \ unit_tests/ref-output/mci_midpoint_1.ref \ unit_tests/ref-output/mci_midpoint_2.ref \ unit_tests/ref-output/mci_midpoint_3.ref \ unit_tests/ref-output/mci_midpoint_4.ref \ unit_tests/ref-output/mci_midpoint_5.ref \ unit_tests/ref-output/mci_midpoint_6.ref \ unit_tests/ref-output/mci_midpoint_7.ref \ unit_tests/ref-output/mci_none_1.ref \ unit_tests/ref-output/mci_vamp2_1.ref \ unit_tests/ref-output/mci_vamp2_2.ref \ unit_tests/ref-output/mci_vamp2_3.ref \ unit_tests/ref-output/mci_vamp_1.ref \ unit_tests/ref-output/mci_vamp_2.ref \ unit_tests/ref-output/mci_vamp_3.ref \ unit_tests/ref-output/mci_vamp_4.ref \ unit_tests/ref-output/mci_vamp_5.ref \ unit_tests/ref-output/mci_vamp_6.ref \ unit_tests/ref-output/mci_vamp_7.ref \ unit_tests/ref-output/mci_vamp_8.ref \ unit_tests/ref-output/mci_vamp_9.ref \ unit_tests/ref-output/mci_vamp_10.ref \ unit_tests/ref-output/mci_vamp_11.ref \ unit_tests/ref-output/mci_vamp_12.ref \ unit_tests/ref-output/mci_vamp_13.ref \ unit_tests/ref-output/mci_vamp_14.ref \ unit_tests/ref-output/mci_vamp_15.ref \ unit_tests/ref-output/mci_vamp_16.ref \ unit_tests/ref-output/md5_1.ref \ unit_tests/ref-output/models_1.ref \ unit_tests/ref-output/models_2.ref \ unit_tests/ref-output/models_3.ref \ unit_tests/ref-output/models_4.ref \ unit_tests/ref-output/models_5.ref \ unit_tests/ref-output/models_6.ref \ unit_tests/ref-output/models_7.ref \ unit_tests/ref-output/models_8.ref \ unit_tests/ref-output/models_9.ref \ unit_tests/ref-output/models_10.ref \ unit_tests/ref-output/numeric_utils_1.ref \ unit_tests/ref-output/numeric_utils_2.ref \ unit_tests/ref-output/os_interface_1.ref \ unit_tests/ref-output/parse_1.ref \ unit_tests/ref-output/particle_specifiers_1.ref \ unit_tests/ref-output/particle_specifiers_2.ref \ unit_tests/ref-output/particles_1.ref \ unit_tests/ref-output/particles_2.ref \ unit_tests/ref-output/particles_3.ref \ unit_tests/ref-output/particles_4.ref \ unit_tests/ref-output/particles_5.ref \ unit_tests/ref-output/particles_6.ref \ unit_tests/ref-output/particles_7.ref \ unit_tests/ref-output/particles_8.ref \ unit_tests/ref-output/particles_9.ref \ unit_tests/ref-output/parton_states_1.ref \ unit_tests/ref-output/pdg_arrays_1.ref \ unit_tests/ref-output/pdg_arrays_2.ref \ unit_tests/ref-output/pdg_arrays_3.ref \ unit_tests/ref-output/pdg_arrays_4.ref \ unit_tests/ref-output/pdg_arrays_5.ref \ unit_tests/ref-output/phs_base_1.ref \ unit_tests/ref-output/phs_base_2.ref \ unit_tests/ref-output/phs_base_3.ref \ unit_tests/ref-output/phs_base_4.ref \ unit_tests/ref-output/phs_base_5.ref \ unit_tests/ref-output/phs_fks_generator_1.ref \ unit_tests/ref-output/phs_fks_generator_2.ref \ unit_tests/ref-output/phs_fks_generator_3.ref \ unit_tests/ref-output/phs_fks_generator_4.ref \ unit_tests/ref-output/phs_fks_generator_5.ref \ unit_tests/ref-output/phs_fks_generator_6.ref \ unit_tests/ref-output/phs_fks_generator_7.ref \ unit_tests/ref-output/phs_forest_1.ref \ unit_tests/ref-output/phs_forest_2.ref \ unit_tests/ref-output/phs_none_1.ref \ unit_tests/ref-output/phs_points_1.ref \ unit_tests/ref-output/phs_rambo_1.ref \ unit_tests/ref-output/phs_rambo_2.ref \ unit_tests/ref-output/phs_rambo_3.ref \ unit_tests/ref-output/phs_rambo_4.ref \ unit_tests/ref-output/phs_single_1.ref \ unit_tests/ref-output/phs_single_2.ref \ unit_tests/ref-output/phs_single_3.ref \ unit_tests/ref-output/phs_single_4.ref \ unit_tests/ref-output/phs_tree_1.ref \ unit_tests/ref-output/phs_tree_2.ref \ unit_tests/ref-output/phs_wood_1.ref \ unit_tests/ref-output/phs_wood_2.ref \ unit_tests/ref-output/phs_wood_3.ref \ unit_tests/ref-output/phs_wood_4.ref \ unit_tests/ref-output/phs_wood_5.ref \ unit_tests/ref-output/phs_wood_6.ref \ unit_tests/ref-output/phs_wood_vis_1.ref \ unit_tests/ref-output/polarization_1.ref \ unit_tests/ref-output/polarization_2.ref \ unit_tests/ref-output/prc_omega_1.ref \ unit_tests/ref-output/prc_omega_2.ref \ unit_tests/ref-output/prc_omega_3.ref \ unit_tests/ref-output/prc_omega_4.ref \ unit_tests/ref-output/prc_omega_5.ref \ unit_tests/ref-output/prc_omega_6.ref \ unit_tests/ref-output/prc_omega_diags_1.ref \ unit_tests/ref-output/prc_recola_1.ref \ unit_tests/ref-output/prc_recola_2.ref \ unit_tests/ref-output/prc_template_me_1.ref \ unit_tests/ref-output/prc_template_me_2.ref \ unit_tests/ref-output/prc_test_1.ref \ unit_tests/ref-output/prc_test_2.ref \ unit_tests/ref-output/prc_test_3.ref \ unit_tests/ref-output/prc_test_4.ref \ unit_tests/ref-output/prclib_interfaces_1.ref \ unit_tests/ref-output/prclib_interfaces_2.ref \ unit_tests/ref-output/prclib_interfaces_3.ref \ unit_tests/ref-output/prclib_interfaces_4.ref \ unit_tests/ref-output/prclib_interfaces_5.ref \ unit_tests/ref-output/prclib_interfaces_6.ref \ unit_tests/ref-output/prclib_interfaces_7.ref \ unit_tests/ref-output/prclib_stacks_1.ref \ unit_tests/ref-output/prclib_stacks_2.ref \ unit_tests/ref-output/process_configurations_1.ref \ unit_tests/ref-output/process_configurations_2.ref \ unit_tests/ref-output/process_libraries_1.ref \ unit_tests/ref-output/process_libraries_2.ref \ unit_tests/ref-output/process_libraries_3.ref \ unit_tests/ref-output/process_libraries_4.ref \ unit_tests/ref-output/process_libraries_5.ref \ unit_tests/ref-output/process_libraries_6.ref \ unit_tests/ref-output/process_libraries_7.ref \ unit_tests/ref-output/process_libraries_8.ref \ unit_tests/ref-output/process_stacks_1.ref \ unit_tests/ref-output/process_stacks_2.ref \ unit_tests/ref-output/process_stacks_3.ref \ unit_tests/ref-output/process_stacks_4.ref \ unit_tests/ref-output/processes_1.ref \ unit_tests/ref-output/processes_2.ref \ unit_tests/ref-output/processes_3.ref \ unit_tests/ref-output/processes_4.ref \ unit_tests/ref-output/processes_5.ref \ unit_tests/ref-output/processes_6.ref \ unit_tests/ref-output/processes_7.ref \ unit_tests/ref-output/processes_8.ref \ unit_tests/ref-output/processes_9.ref \ unit_tests/ref-output/processes_10.ref \ unit_tests/ref-output/processes_11.ref \ unit_tests/ref-output/processes_12.ref \ unit_tests/ref-output/processes_13.ref \ unit_tests/ref-output/processes_14.ref \ unit_tests/ref-output/processes_15.ref \ unit_tests/ref-output/processes_16.ref \ unit_tests/ref-output/processes_17.ref \ unit_tests/ref-output/processes_18.ref \ unit_tests/ref-output/processes_19.ref \ unit_tests/ref-output/radiation_generator_1.ref \ unit_tests/ref-output/radiation_generator_2.ref \ unit_tests/ref-output/radiation_generator_3.ref \ unit_tests/ref-output/radiation_generator_4.ref \ unit_tests/ref-output/real_subtraction_1.ref \ unit_tests/ref-output/recoil_kinematics_1.ref \ unit_tests/ref-output/recoil_kinematics_2.ref \ unit_tests/ref-output/recoil_kinematics_3.ref \ unit_tests/ref-output/recoil_kinematics_4.ref \ unit_tests/ref-output/recoil_kinematics_5.ref \ unit_tests/ref-output/recoil_kinematics_6.ref \ unit_tests/ref-output/resonance_insertion_1.ref \ unit_tests/ref-output/resonance_insertion_2.ref \ unit_tests/ref-output/resonance_insertion_3.ref \ unit_tests/ref-output/resonance_insertion_4.ref \ unit_tests/ref-output/resonance_insertion_5.ref \ unit_tests/ref-output/resonance_insertion_6.ref \ unit_tests/ref-output/resonances_1.ref \ unit_tests/ref-output/resonances_2.ref \ unit_tests/ref-output/resonances_3.ref \ unit_tests/ref-output/resonances_4.ref \ unit_tests/ref-output/resonances_5.ref \ unit_tests/ref-output/resonances_6.ref \ unit_tests/ref-output/resonances_7.ref \ unit_tests/ref-output/restricted_subprocesses_1.ref \ unit_tests/ref-output/restricted_subprocesses_2.ref \ unit_tests/ref-output/restricted_subprocesses_3.ref \ unit_tests/ref-output/restricted_subprocesses_4.ref \ unit_tests/ref-output/restricted_subprocesses_5.ref \ unit_tests/ref-output/restricted_subprocesses_6.ref \ unit_tests/ref-output/rng_base_1.ref \ unit_tests/ref-output/rng_base_2.ref \ unit_tests/ref-output/rng_stream_1.ref \ unit_tests/ref-output/rng_stream_2.ref \ unit_tests/ref-output/rng_stream_3.ref \ unit_tests/ref-output/rng_tao_1.ref \ unit_tests/ref-output/rng_tao_2.ref \ unit_tests/ref-output/rt_data_1.ref \ unit_tests/ref-output/rt_data_2.ref \ unit_tests/ref-output/rt_data_3.ref \ unit_tests/ref-output/rt_data_4.ref \ unit_tests/ref-output/rt_data_5.ref \ unit_tests/ref-output/rt_data_6.ref \ unit_tests/ref-output/rt_data_7.ref \ unit_tests/ref-output/rt_data_8.ref \ unit_tests/ref-output/rt_data_9.ref \ unit_tests/ref-output/rt_data_10.ref \ unit_tests/ref-output/rt_data_11.ref \ unit_tests/ref-output/selectors_1.ref \ unit_tests/ref-output/selectors_2.ref \ unit_tests/ref-output/sf_aux_1.ref \ unit_tests/ref-output/sf_aux_2.ref \ unit_tests/ref-output/sf_aux_3.ref \ unit_tests/ref-output/sf_aux_4.ref \ unit_tests/ref-output/sf_base_1.ref \ unit_tests/ref-output/sf_base_2.ref \ unit_tests/ref-output/sf_base_3.ref \ unit_tests/ref-output/sf_base_4.ref \ unit_tests/ref-output/sf_base_5.ref \ unit_tests/ref-output/sf_base_6.ref \ unit_tests/ref-output/sf_base_7.ref \ unit_tests/ref-output/sf_base_8.ref \ unit_tests/ref-output/sf_base_9.ref \ unit_tests/ref-output/sf_base_10.ref \ unit_tests/ref-output/sf_base_11.ref \ unit_tests/ref-output/sf_base_12.ref \ unit_tests/ref-output/sf_base_13.ref \ unit_tests/ref-output/sf_base_14.ref \ unit_tests/ref-output/sf_beam_events_1.ref \ unit_tests/ref-output/sf_beam_events_2.ref \ unit_tests/ref-output/sf_beam_events_3.ref \ unit_tests/ref-output/sf_circe1_1.ref \ unit_tests/ref-output/sf_circe1_2.ref \ unit_tests/ref-output/sf_circe1_3.ref \ unit_tests/ref-output/sf_circe2_1.ref \ unit_tests/ref-output/sf_circe2_2.ref \ unit_tests/ref-output/sf_circe2_3.ref \ unit_tests/ref-output/sf_epa_1.ref \ unit_tests/ref-output/sf_epa_2.ref \ unit_tests/ref-output/sf_epa_3.ref \ unit_tests/ref-output/sf_epa_4.ref \ unit_tests/ref-output/sf_epa_5.ref \ unit_tests/ref-output/sf_escan_1.ref \ unit_tests/ref-output/sf_escan_2.ref \ unit_tests/ref-output/sf_ewa_1.ref \ unit_tests/ref-output/sf_ewa_2.ref \ unit_tests/ref-output/sf_ewa_3.ref \ unit_tests/ref-output/sf_ewa_4.ref \ unit_tests/ref-output/sf_ewa_5.ref \ unit_tests/ref-output/sf_gaussian_1.ref \ unit_tests/ref-output/sf_gaussian_2.ref \ unit_tests/ref-output/sf_isr_1.ref \ unit_tests/ref-output/sf_isr_2.ref \ unit_tests/ref-output/sf_isr_3.ref \ unit_tests/ref-output/sf_isr_4.ref \ unit_tests/ref-output/sf_isr_5.ref \ unit_tests/ref-output/sf_lhapdf5_1.ref \ unit_tests/ref-output/sf_lhapdf5_2.ref \ unit_tests/ref-output/sf_lhapdf5_3.ref \ unit_tests/ref-output/sf_lhapdf6_1.ref \ unit_tests/ref-output/sf_lhapdf6_2.ref \ unit_tests/ref-output/sf_lhapdf6_3.ref \ unit_tests/ref-output/sf_mappings_1.ref \ unit_tests/ref-output/sf_mappings_2.ref \ unit_tests/ref-output/sf_mappings_3.ref \ unit_tests/ref-output/sf_mappings_4.ref \ unit_tests/ref-output/sf_mappings_5.ref \ unit_tests/ref-output/sf_mappings_6.ref \ unit_tests/ref-output/sf_mappings_7.ref \ unit_tests/ref-output/sf_mappings_8.ref \ unit_tests/ref-output/sf_mappings_9.ref \ unit_tests/ref-output/sf_mappings_10.ref \ unit_tests/ref-output/sf_mappings_11.ref \ unit_tests/ref-output/sf_mappings_12.ref \ unit_tests/ref-output/sf_mappings_13.ref \ unit_tests/ref-output/sf_mappings_14.ref \ unit_tests/ref-output/sf_mappings_15.ref \ unit_tests/ref-output/sf_mappings_16.ref \ unit_tests/ref-output/sf_pdf_builtin_1.ref \ unit_tests/ref-output/sf_pdf_builtin_2.ref \ unit_tests/ref-output/sf_pdf_builtin_3.ref \ unit_tests/ref-output/shower_1.ref \ unit_tests/ref-output/shower_2.ref \ unit_tests/ref-output/shower_base_1.ref \ unit_tests/ref-output/simulations_1.ref \ unit_tests/ref-output/simulations_2.ref \ unit_tests/ref-output/simulations_3.ref \ unit_tests/ref-output/simulations_4.ref \ unit_tests/ref-output/simulations_5.ref \ unit_tests/ref-output/simulations_6.ref \ unit_tests/ref-output/simulations_7.ref \ unit_tests/ref-output/simulations_8.ref \ unit_tests/ref-output/simulations_9.ref \ unit_tests/ref-output/simulations_10.ref \ unit_tests/ref-output/simulations_11.ref \ unit_tests/ref-output/simulations_12.ref \ unit_tests/ref-output/simulations_13.ref \ unit_tests/ref-output/simulations_14.ref \ unit_tests/ref-output/simulations_15.ref \ unit_tests/ref-output/slha_1.ref \ unit_tests/ref-output/slha_2.ref \ unit_tests/ref-output/sm_physics_1.ref \ unit_tests/ref-output/sm_physics_2.ref \ unit_tests/ref-output/sm_physics_3.ref \ unit_tests/ref-output/sm_qcd_1.ref \ unit_tests/ref-output/sm_qed_1.ref \ unit_tests/ref-output/solver_1.ref \ unit_tests/ref-output/sorting_1.ref \ unit_tests/ref-output/state_matrix_1.ref \ unit_tests/ref-output/state_matrix_2.ref \ unit_tests/ref-output/state_matrix_3.ref \ unit_tests/ref-output/state_matrix_4.ref \ unit_tests/ref-output/state_matrix_5.ref \ unit_tests/ref-output/state_matrix_6.ref \ unit_tests/ref-output/state_matrix_7.ref \ unit_tests/ref-output/su_algebra_1.ref \ unit_tests/ref-output/su_algebra_2.ref \ unit_tests/ref-output/su_algebra_3.ref \ unit_tests/ref-output/su_algebra_4.ref \ unit_tests/ref-output/subevt_expr_1.ref \ unit_tests/ref-output/subevt_expr_2.ref \ unit_tests/ref-output/ttv_formfactors_1.ref \ unit_tests/ref-output/ttv_formfactors_2.ref \ unit_tests/ref-output/vamp2_1.ref \ unit_tests/ref-output/vamp2_2.ref \ unit_tests/ref-output/vamp2_3.ref \ unit_tests/ref-output/vamp2_4.ref \ unit_tests/ref-output/vamp2_5.ref \ unit_tests/ref-output/vegas_1.ref \ unit_tests/ref-output/vegas_2.ref \ unit_tests/ref-output/vegas_3.ref \ unit_tests/ref-output/vegas_4.ref \ unit_tests/ref-output/vegas_5.ref \ unit_tests/ref-output/vegas_6.ref \ unit_tests/ref-output/vegas_7.ref \ unit_tests/ref-output/whizard_lha_1.ref \ unit_tests/ref-output/xml_1.ref \ unit_tests/ref-output/xml_2.ref \ unit_tests/ref-output/xml_3.ref \ unit_tests/ref-output/xml_4.ref \ functional_tests/ref-output/alphas.ref \ functional_tests/ref-output/analyze_1.ref \ functional_tests/ref-output/analyze_2.ref \ functional_tests/ref-output/analyze_3.ref \ functional_tests/ref-output/analyze_4.ref \ functional_tests/ref-output/analyze_5.ref \ functional_tests/ref-output/analyze_6.ref \ functional_tests/ref-output/beam_events_1.ref \ functional_tests/ref-output/beam_events_4.ref \ functional_tests/ref-output/beam_setup_1.ref \ functional_tests/ref-output/beam_setup_2.ref \ functional_tests/ref-output/beam_setup_3.ref \ functional_tests/ref-output/beam_setup_4.ref \ functional_tests/ref-output/bjet_cluster.ref \ functional_tests/ref-output/br_redef_1.ref \ functional_tests/ref-output/cascades2_phs_1.ref \ functional_tests/ref-output/cascades2_phs_2.ref \ functional_tests/ref-output/circe1_1.ref \ functional_tests/ref-output/circe1_2.ref \ functional_tests/ref-output/circe1_3.ref \ functional_tests/ref-output/circe1_6.ref \ functional_tests/ref-output/circe1_10.ref \ functional_tests/ref-output/circe1_errors_1.ref \ functional_tests/ref-output/circe2_1.ref \ functional_tests/ref-output/circe2_2.ref \ functional_tests/ref-output/circe2_3.ref \ functional_tests/ref-output/cmdline_1.ref \ functional_tests/ref-output/colors.ref \ functional_tests/ref-output/colors_hgg.ref \ functional_tests/ref-output/cuts.ref \ functional_tests/ref-output/decay_err_1.ref \ functional_tests/ref-output/decay_err_2.ref \ functional_tests/ref-output/decay_err_3.ref \ functional_tests/ref-output/energy_scan_1.ref \ functional_tests/ref-output/ep_3.ref \ functional_tests/ref-output/epa_1.ref \ functional_tests/ref-output/epa_2.ref \ functional_tests/ref-output/epa_3.ref \ functional_tests/ref-output/epa_4.ref \ functional_tests/ref-output/event_dump_1.ref \ functional_tests/ref-output/event_dump_2.ref \ functional_tests/ref-output/event_eff_1.ref \ functional_tests/ref-output/event_eff_2.ref \ functional_tests/ref-output/event_failed_1.ref \ functional_tests/ref-output/event_weights_1.ref \ functional_tests/ref-output/event_weights_2.ref \ functional_tests/ref-output/ewa_4.ref \ functional_tests/ref-output/extpar.ref \ functional_tests/ref-output/fatal.ref \ functional_tests/ref-output/fatal_beam_decay.ref \ functional_tests/ref-output/fks_res_2.ref \ functional_tests/ref-output/flvsum_1.ref \ functional_tests/ref-output/gaussian_1.ref \ functional_tests/ref-output/gaussian_2.ref \ functional_tests/ref-output/hadronize_1.ref \ functional_tests/ref-output/hepmc_1.ref \ functional_tests/ref-output/hepmc_2.ref \ functional_tests/ref-output/hepmc_3.ref \ functional_tests/ref-output/hepmc_4.ref \ functional_tests/ref-output/hepmc_5.ref \ functional_tests/ref-output/hepmc_6.ref \ functional_tests/ref-output/hepmc_7.ref \ functional_tests/ref-output/hepmc_9.ref \ functional_tests/ref-output/hepmc_10.ref \ functional_tests/ref-output/isr_1.ref \ functional_tests/ref-output/isr_epa_1.ref \ functional_tests/ref-output/jets_xsec.ref \ functional_tests/ref-output/job_id_1.ref \ functional_tests/ref-output/job_id_2.ref \ functional_tests/ref-output/job_id_3.ref \ functional_tests/ref-output/job_id_4.ref \ functional_tests/ref-output/lcio_1.ref \ functional_tests/ref-output/lcio_3.ref \ functional_tests/ref-output/lcio_4.ref \ functional_tests/ref-output/lcio_5.ref \ functional_tests/ref-output/lcio_6.ref \ functional_tests/ref-output/lcio_8.ref \ functional_tests/ref-output/lcio_9.ref \ functional_tests/ref-output/lcio_10.ref \ functional_tests/ref-output/lcio_11.ref \ functional_tests/ref-output/lhef_1.ref \ functional_tests/ref-output/lhef_2.ref \ functional_tests/ref-output/lhef_3.ref \ functional_tests/ref-output/lhef_4.ref \ functional_tests/ref-output/lhef_5.ref \ functional_tests/ref-output/lhef_6.ref \ functional_tests/ref-output/lhef_9.ref \ functional_tests/ref-output/lhef_10.ref \ functional_tests/ref-output/lhef_11.ref \ functional_tests/ref-output/libraries_1.ref \ functional_tests/ref-output/libraries_2.ref \ functional_tests/ref-output/libraries_4.ref \ functional_tests/ref-output/method_ovm_1.ref \ functional_tests/ref-output/mlm_matching_fsr.ref \ functional_tests/ref-output/mlm_pythia6_isr.ref \ functional_tests/ref-output/model_change_1.ref \ functional_tests/ref-output/model_change_2.ref \ functional_tests/ref-output/model_change_3.ref \ functional_tests/ref-output/model_scheme_1.ref \ functional_tests/ref-output/model_test.ref \ functional_tests/ref-output/mssmtest_1.ref \ functional_tests/ref-output/mssmtest_2.ref \ functional_tests/ref-output/mssmtest_3.ref \ functional_tests/ref-output/multi_comp_4.ref \ functional_tests/ref-output/nlo_1.ref \ functional_tests/ref-output/nlo_2.ref \ functional_tests/ref-output/nlo_6.ref \ functional_tests/ref-output/nlo_decay_1.ref \ functional_tests/ref-output/observables_1.ref \ functional_tests/ref-output/openloops_1.ref \ functional_tests/ref-output/openloops_2.ref \ functional_tests/ref-output/openloops_4.ref \ functional_tests/ref-output/openloops_5.ref \ functional_tests/ref-output/openloops_6.ref \ functional_tests/ref-output/openloops_7.ref \ functional_tests/ref-output/openloops_8.ref \ functional_tests/ref-output/openloops_9.ref \ functional_tests/ref-output/openloops_10.ref \ functional_tests/ref-output/openloops_11.ref \ functional_tests/ref-output/pack_1.ref \ functional_tests/ref-output/parton_shower_1.ref \ functional_tests/ref-output/photon_isolation_1.ref \ functional_tests/ref-output/photon_isolation_2.ref \ functional_tests/ref-output/polarized_1.ref \ functional_tests/ref-output/process_log.ref \ functional_tests/ref-output/pythia6_1.ref \ functional_tests/ref-output/pythia6_2.ref \ functional_tests/ref-output/qcdtest_4.ref \ functional_tests/ref-output/qcdtest_5.ref \ functional_tests/ref-output/qcdtest_6.ref \ functional_tests/ref-output/qedtest_1.ref \ functional_tests/ref-output/qedtest_2.ref \ functional_tests/ref-output/qedtest_5.ref \ functional_tests/ref-output/qedtest_6.ref \ functional_tests/ref-output/qedtest_7.ref \ functional_tests/ref-output/qedtest_8.ref \ functional_tests/ref-output/qedtest_9.ref \ functional_tests/ref-output/qedtest_10.ref \ functional_tests/ref-output/rambo_vamp_1.ref \ functional_tests/ref-output/rambo_vamp_2.ref \ functional_tests/ref-output/real_partition_1.ref \ functional_tests/ref-output/rebuild_2.ref \ functional_tests/ref-output/rebuild_3.ref \ functional_tests/ref-output/rebuild_4.ref \ functional_tests/ref-output/recola_1.ref \ functional_tests/ref-output/recola_2.ref \ functional_tests/ref-output/recola_3.ref \ functional_tests/ref-output/recola_4.ref \ functional_tests/ref-output/recola_5.ref \ functional_tests/ref-output/recola_6.ref \ functional_tests/ref-output/recola_7.ref \ functional_tests/ref-output/recola_8.ref \ functional_tests/ref-output/recola_9.ref \ functional_tests/ref-output/resonances_5.ref \ functional_tests/ref-output/resonances_6.ref \ functional_tests/ref-output/resonances_7.ref \ functional_tests/ref-output/resonances_8.ref \ functional_tests/ref-output/resonances_9.ref \ functional_tests/ref-output/resonances_12.ref \ functional_tests/ref-output/restrictions.ref \ functional_tests/ref-output/reweight_1.ref \ functional_tests/ref-output/reweight_2.ref \ functional_tests/ref-output/reweight_3.ref \ functional_tests/ref-output/reweight_4.ref \ functional_tests/ref-output/reweight_5.ref \ functional_tests/ref-output/reweight_6.ref \ functional_tests/ref-output/reweight_7.ref \ functional_tests/ref-output/reweight_8.ref \ functional_tests/ref-output/reweight_9.ref \ functional_tests/ref-output/reweight_10.ref \ functional_tests/ref-output/select_1.ref \ functional_tests/ref-output/select_2.ref \ functional_tests/ref-output/show_1.ref \ functional_tests/ref-output/show_2.ref \ functional_tests/ref-output/show_3.ref \ functional_tests/ref-output/show_4.ref \ functional_tests/ref-output/show_5.ref \ functional_tests/ref-output/shower_err_1.ref \ functional_tests/ref-output/sm_cms_1.ref \ functional_tests/ref-output/smtest_1.ref \ functional_tests/ref-output/smtest_3.ref \ functional_tests/ref-output/smtest_4.ref \ functional_tests/ref-output/smtest_5.ref \ functional_tests/ref-output/smtest_6.ref \ functional_tests/ref-output/smtest_7.ref \ functional_tests/ref-output/smtest_9.ref \ functional_tests/ref-output/smtest_10.ref \ functional_tests/ref-output/smtest_11.ref \ functional_tests/ref-output/smtest_12.ref \ functional_tests/ref-output/smtest_13.ref \ functional_tests/ref-output/smtest_14.ref \ functional_tests/ref-output/smtest_15.ref \ functional_tests/ref-output/smtest_16.ref \ functional_tests/ref-output/smtest_17.ref \ functional_tests/ref-output/spincor_1.ref \ functional_tests/ref-output/static_1.ref \ functional_tests/ref-output/static_2.ref \ functional_tests/ref-output/stdhep_1.ref \ functional_tests/ref-output/stdhep_2.ref \ functional_tests/ref-output/stdhep_3.ref \ functional_tests/ref-output/stdhep_4.ref \ functional_tests/ref-output/stdhep_5.ref \ functional_tests/ref-output/stdhep_6.ref \ functional_tests/ref-output/structure_1.ref \ functional_tests/ref-output/structure_2.ref \ functional_tests/ref-output/structure_3.ref \ functional_tests/ref-output/structure_4.ref \ functional_tests/ref-output/structure_5.ref \ functional_tests/ref-output/structure_6.ref \ functional_tests/ref-output/structure_7.ref \ functional_tests/ref-output/structure_8.ref \ functional_tests/ref-output/susyhit.ref \ functional_tests/ref-output/template_me_1.ref \ functional_tests/ref-output/template_me_2.ref \ functional_tests/ref-output/testproc_1.ref \ functional_tests/ref-output/testproc_2.ref \ functional_tests/ref-output/testproc_3.ref \ functional_tests/ref-output/testproc_4.ref \ functional_tests/ref-output/testproc_5.ref \ functional_tests/ref-output/testproc_6.ref \ functional_tests/ref-output/testproc_7.ref \ functional_tests/ref-output/testproc_8.ref \ functional_tests/ref-output/testproc_9.ref \ functional_tests/ref-output/testproc_10.ref \ functional_tests/ref-output/testproc_11.ref \ functional_tests/ref-output/ufo_1.ref \ functional_tests/ref-output/ufo_2.ref \ functional_tests/ref-output/ufo_3.ref \ functional_tests/ref-output/ufo_4.ref \ functional_tests/ref-output/ufo_5.ref \ functional_tests/ref-output/ufo_6.ref \ functional_tests/ref-output/user_prc_threshold_1.ref \ functional_tests/ref-output/user_prc_threshold_2.ref \ functional_tests/ref-output/vamp2_1.ref \ functional_tests/ref-output/vamp2_2.ref \ functional_tests/ref-output/vamp2_3.ref \ functional_tests/ref-output/vars.ref \ ext_tests_nlo/ref-output/nlo_ee4j.ref \ ext_tests_nlo/ref-output/nlo_ee4t.ref \ ext_tests_nlo/ref-output/nlo_ee5j.ref \ ext_tests_nlo/ref-output/nlo_eejj.ref \ ext_tests_nlo/ref-output/nlo_eejjj.ref \ ext_tests_nlo/ref-output/nlo_eett.ref \ ext_tests_nlo/ref-output/nlo_eetth.ref \ ext_tests_nlo/ref-output/nlo_eetthh.ref \ ext_tests_nlo/ref-output/nlo_eetthj.ref \ ext_tests_nlo/ref-output/nlo_eetthz.ref \ ext_tests_nlo/ref-output/nlo_eettwjj.ref \ ext_tests_nlo/ref-output/nlo_eettww.ref \ ext_tests_nlo/ref-output/nlo_eettz.ref \ ext_tests_nlo/ref-output/nlo_eettzj.ref \ ext_tests_nlo/ref-output/nlo_eettzjj.ref \ ext_tests_nlo/ref-output/nlo_eettzz.ref \ ext_tests_nlo/ref-output/nlo_ppzj_real_partition.ref \ ext_tests_nlo/ref-output/nlo_pptttt.ref \ ext_tests_nlo/ref-output/nlo_ppw.ref \ ext_tests_nlo/ref-output/nlo_ppz.ref \ ext_tests_nlo/ref-output/nlo_ppzj_sim_1.ref \ ext_tests_nlo/ref-output/nlo_ppzj_sim_2.ref \ ext_tests_nlo/ref-output/nlo_ppzj_sim_3.ref \ ext_tests_nlo/ref-output/nlo_ppzj_sim_4.ref \ ext_tests_nlo/ref-output/nlo_ppzw.ref \ ext_tests_nlo/ref-output/nlo_ppzz.ref \ ext_tests_nlo/ref-output/nlo_ppee_ew.ref \ ext_tests_nlo/ref-output/nlo_pphee_ew.ref \ ext_tests_nlo/ref-output/nlo_pphjj_ew.ref \ ext_tests_nlo/ref-output/nlo_pphz_ew.ref \ ext_tests_nlo/ref-output/nlo_ppllll_ew.ref \ ext_tests_nlo/ref-output/nlo_ppllnn_ew.ref \ + ext_tests_nlo/ref-output/nlo_pptt_ew.ref \ ext_tests_nlo/ref-output/nlo_pptj_ew.ref \ ext_tests_nlo/ref-output/nlo_ppwhh_ew.ref \ ext_tests_nlo/ref-output/nlo_ppww_ew.ref \ ext_tests_nlo/ref-output/nlo_ppwzh_ew.ref \ ext_tests_nlo/ref-output/nlo_ppz_ew.ref \ ext_tests_nlo/ref-output/nlo_ppzzz_ew.ref # Reference files that depend on the numerical precision REF_OUTPUT_FILES_DOUBLE = \ functional_tests/ref-output-double/beam_events_2.ref \ functional_tests/ref-output-double/beam_events_3.ref \ functional_tests/ref-output-double/beam_setup_5.ref \ functional_tests/ref-output-double/circe1_4.ref \ functional_tests/ref-output-double/circe1_5.ref \ functional_tests/ref-output-double/circe1_7.ref \ functional_tests/ref-output-double/circe1_8.ref \ functional_tests/ref-output-double/circe1_9.ref \ functional_tests/ref-output-double/circe1_photons_1.ref \ functional_tests/ref-output-double/circe1_photons_2.ref \ functional_tests/ref-output-double/circe1_photons_3.ref \ functional_tests/ref-output-double/circe1_photons_4.ref \ functional_tests/ref-output-double/circe1_photons_5.ref \ functional_tests/ref-output-double/colors_2.ref \ functional_tests/ref-output-double/defaultcuts.ref \ functional_tests/ref-output-double/ep_1.ref \ functional_tests/ref-output-double/ep_2.ref \ functional_tests/ref-output-double/ewa_1.ref \ functional_tests/ref-output-double/ewa_2.ref \ functional_tests/ref-output-double/ewa_3.ref \ functional_tests/ref-output-double/fks_res_1.ref \ functional_tests/ref-output-double/fks_res_3.ref \ functional_tests/ref-output-double/helicity.ref \ functional_tests/ref-output-double/hepmc_8.ref \ functional_tests/ref-output-double/ilc.ref \ functional_tests/ref-output-double/isr_2.ref \ functional_tests/ref-output-double/isr_3.ref \ functional_tests/ref-output-double/isr_4.ref \ functional_tests/ref-output-double/isr_5.ref \ functional_tests/ref-output-double/isr_6.ref \ functional_tests/ref-output-double/lcio_2.ref \ functional_tests/ref-output-double/lcio_7.ref \ functional_tests/ref-output-double/lcio_12.ref \ functional_tests/ref-output-double/lhapdf5.ref \ functional_tests/ref-output-double/lhapdf6.ref \ functional_tests/ref-output-double/lhef_7.ref \ functional_tests/ref-output-double/mlm_matching_isr.ref \ functional_tests/ref-output-double/multi_comp_1.ref \ functional_tests/ref-output-double/multi_comp_2.ref \ functional_tests/ref-output-double/multi_comp_3.ref \ functional_tests/ref-output-double/testproc_12.ref \ functional_tests/ref-output-double/nlo_3.ref \ functional_tests/ref-output-double/nlo_4.ref \ functional_tests/ref-output-double/nlo_5.ref \ functional_tests/ref-output-double/nlo_7.ref \ functional_tests/ref-output-double/nlo_8.ref \ functional_tests/ref-output-double/nlo_9.ref \ functional_tests/ref-output-double/nlo_10.ref \ functional_tests/ref-output-double/observables_2.ref \ functional_tests/ref-output-double/openloops_3.ref \ functional_tests/ref-output-double/openloops_12.ref \ functional_tests/ref-output-double/openloops_13.ref \ functional_tests/ref-output-double/openloops_14.ref \ functional_tests/ref-output-double/parton_shower_2.ref \ functional_tests/ref-output-double/pdf_builtin.ref \ functional_tests/ref-output-double/powheg_1.ref \ functional_tests/ref-output-double/pythia6_3.ref \ functional_tests/ref-output-double/pythia6_4.ref \ functional_tests/ref-output-double/qcdtest_1.ref \ functional_tests/ref-output-double/qcdtest_2.ref \ functional_tests/ref-output-double/qcdtest_3.ref \ functional_tests/ref-output-double/qedtest_3.ref \ functional_tests/ref-output-double/qedtest_4.ref \ functional_tests/ref-output-double/resonances_1.ref \ functional_tests/ref-output-double/resonances_2.ref \ functional_tests/ref-output-double/resonances_3.ref \ functional_tests/ref-output-double/resonances_4.ref \ functional_tests/ref-output-double/resonances_10.ref \ functional_tests/ref-output-double/resonances_11.ref \ functional_tests/ref-output-double/resonances_13.ref \ functional_tests/ref-output-double/resonances_14.ref \ functional_tests/ref-output-double/resonances_15.ref \ functional_tests/ref-output-double/smtest_2.ref \ functional_tests/ref-output-double/smtest_8.ref \ functional_tests/ref-output-double/tauola_1.ref \ functional_tests/ref-output-double/tauola_2.ref \ functional_tests/ref-output-double/tauola_3.ref REF_OUTPUT_FILES_PREC = \ functional_tests/ref-output-prec/beam_setup_5.ref \ functional_tests/ref-output-prec/circe1_9.ref \ functional_tests/ref-output-prec/circe1_photons_1.ref \ functional_tests/ref-output-prec/circe1_photons_2.ref \ functional_tests/ref-output-prec/circe1_photons_3.ref \ functional_tests/ref-output-prec/circe1_photons_4.ref \ functional_tests/ref-output-prec/circe1_photons_5.ref \ functional_tests/ref-output-prec/colors_2.ref \ functional_tests/ref-output-prec/defaultcuts.ref \ functional_tests/ref-output-prec/ep_1.ref \ functional_tests/ref-output-prec/ep_2.ref \ functional_tests/ref-output-prec/ewa_1.ref \ functional_tests/ref-output-prec/fks_res_1.ref \ functional_tests/ref-output-prec/fks_res_3.ref \ functional_tests/ref-output-prec/helicity.ref \ functional_tests/ref-output-prec/ilc.ref \ functional_tests/ref-output-prec/lhapdf5.ref \ functional_tests/ref-output-prec/lhapdf6.ref \ functional_tests/ref-output-prec/lhef_7.ref \ functional_tests/ref-output-prec/multi_comp_1.ref \ functional_tests/ref-output-prec/multi_comp_2.ref \ functional_tests/ref-output-prec/multi_comp_3.ref \ functional_tests/ref-output-prec/testproc_12.ref \ functional_tests/ref-output-prec/nlo_3.ref \ functional_tests/ref-output-prec/nlo_4.ref \ functional_tests/ref-output-prec/parton_shower_2.ref \ functional_tests/ref-output-prec/pdf_builtin.ref \ functional_tests/ref-output-prec/qcdtest_1.ref \ functional_tests/ref-output-prec/qcdtest_2.ref \ functional_tests/ref-output-prec/qcdtest_3.ref \ functional_tests/ref-output-prec/qedtest_3.ref \ functional_tests/ref-output-prec/qedtest_4.ref \ functional_tests/ref-output-prec/smtest_2.ref \ functional_tests/ref-output-prec/smtest_8.ref REF_OUTPUT_FILES_EXT = \ functional_tests/ref-output-ext/beam_events_2.ref \ functional_tests/ref-output-ext/beam_events_3.ref \ functional_tests/ref-output-ext/circe1_4.ref \ functional_tests/ref-output-ext/circe1_5.ref \ functional_tests/ref-output-ext/circe1_7.ref \ functional_tests/ref-output-ext/circe1_8.ref \ functional_tests/ref-output-ext/ewa_2.ref \ functional_tests/ref-output-ext/ewa_3.ref \ functional_tests/ref-output-ext/hepmc_8.ref \ functional_tests/ref-output-ext/isr_2.ref \ functional_tests/ref-output-ext/isr_3.ref \ functional_tests/ref-output-ext/isr_4.ref \ functional_tests/ref-output-ext/isr_5.ref \ functional_tests/ref-output-ext/isr_6.ref \ functional_tests/ref-output-ext/lcio_2.ref \ functional_tests/ref-output-ext/lcio_7.ref \ functional_tests/ref-output-ext/lcio_12.ref \ functional_tests/ref-output-ext/mlm_matching_isr.ref \ functional_tests/ref-output-ext/nlo_5.ref \ functional_tests/ref-output-ext/nlo_7.ref \ functional_tests/ref-output-ext/nlo_8.ref \ functional_tests/ref-output-ext/nlo_9.ref \ functional_tests/ref-output-ext/nlo_10.ref \ functional_tests/ref-output-ext/observables_2.ref \ functional_tests/ref-output-ext/openloops_3.ref \ functional_tests/ref-output-ext/openloops_12.ref \ functional_tests/ref-output-ext/openloops_13.ref \ functional_tests/ref-output-ext/openloops_14.ref \ functional_tests/ref-output-ext/powheg_1.ref \ functional_tests/ref-output-ext/pythia6_3.ref \ functional_tests/ref-output-ext/pythia6_4.ref \ functional_tests/ref-output-ext/resonances_1.ref \ functional_tests/ref-output-ext/resonances_2.ref \ functional_tests/ref-output-ext/resonances_3.ref \ functional_tests/ref-output-ext/resonances_4.ref \ functional_tests/ref-output-ext/resonances_10.ref \ functional_tests/ref-output-ext/resonances_11.ref \ functional_tests/ref-output-ext/resonances_13.ref \ functional_tests/ref-output-ext/resonances_14.ref \ functional_tests/ref-output-ext/resonances_15.ref \ functional_tests/ref-output-ext/tauola_1.ref \ functional_tests/ref-output-ext/tauola_2.ref \ functional_tests/ref-output-ext/tauola_3.ref REF_OUTPUT_FILES_QUAD = \ functional_tests/ref-output-quad/beam_events_2.ref \ functional_tests/ref-output-quad/beam_events_3.ref \ functional_tests/ref-output-quad/circe1_4.ref \ functional_tests/ref-output-quad/circe1_5.ref \ functional_tests/ref-output-quad/circe1_7.ref \ functional_tests/ref-output-quad/circe1_8.ref \ functional_tests/ref-output-quad/ewa_2.ref \ functional_tests/ref-output-quad/ewa_3.ref \ functional_tests/ref-output-quad/hepmc_8.ref \ functional_tests/ref-output-quad/isr_2.ref \ functional_tests/ref-output-quad/isr_3.ref \ functional_tests/ref-output-quad/isr_4.ref \ functional_tests/ref-output-quad/isr_5.ref \ functional_tests/ref-output-quad/isr_6.ref \ functional_tests/ref-output-quad/lcio_2.ref \ functional_tests/ref-output-quad/lcio_7.ref \ functional_tests/ref-output-quad/lcio_12.ref \ functional_tests/ref-output-quad/mlm_matching_isr.ref \ functional_tests/ref-output-quad/nlo_5.ref \ functional_tests/ref-output-quad/nlo_7.ref \ functional_tests/ref-output-quad/nlo_8.ref \ functional_tests/ref-output-quad/nlo_9.ref \ functional_tests/ref-output-quad/nlo_10.ref \ functional_tests/ref-output-quad/observables_2.ref \ functional_tests/ref-output-quad/openloops_3.ref \ functional_tests/ref-output-quad/openloops_12.ref \ functional_tests/ref-output-quad/openloops_13.ref \ functional_tests/ref-output-quad/openloops_14.ref \ functional_tests/ref-output-quad/powheg_1.ref \ functional_tests/ref-output-quad/pythia6_3.ref \ functional_tests/ref-output-quad/pythia6_4.ref \ functional_tests/ref-output-quad/resonances_1.ref \ functional_tests/ref-output-quad/resonances_2.ref \ functional_tests/ref-output-quad/resonances_3.ref \ functional_tests/ref-output-quad/resonances_4.ref \ functional_tests/ref-output-quad/resonances_10.ref \ functional_tests/ref-output-quad/resonances_11.ref \ functional_tests/ref-output-quad/resonances_13.ref \ functional_tests/ref-output-quad/resonances_14.ref \ functional_tests/ref-output-quad/resonances_15.ref \ functional_tests/ref-output-quad/tauola_1.ref \ functional_tests/ref-output-quad/tauola_2.ref \ functional_tests/ref-output-quad/tauola_3.ref TESTSUITES_M4 = \ $(MISC_TESTS_M4) \ $(EXT_MSSM_M4) \ $(EXT_NMSSM_M4) TESTSUITES_SIN = \ $(MISC_TESTS_SIN) \ $(EXT_ILC_SIN) \ $(EXT_MSSM_SIN) \ $(EXT_NMSSM_SIN) \ $(EXT_SHOWER_SIN) \ $(EXT_NLO_SIN) \ $(EXT_NLO_ADD_SIN) MISC_TESTS_M4 = MISC_TESTS_SIN = \ functional_tests/alphas.sin \ functional_tests/analyze_1.sin \ functional_tests/analyze_2.sin \ functional_tests/analyze_3.sin \ functional_tests/analyze_4.sin \ functional_tests/analyze_5.sin \ functional_tests/analyze_6.sin \ functional_tests/beam_events_1.sin \ functional_tests/beam_events_2.sin \ functional_tests/beam_events_3.sin \ functional_tests/beam_events_4.sin \ functional_tests/beam_setup_1.sin \ functional_tests/beam_setup_2.sin \ functional_tests/beam_setup_3.sin \ functional_tests/beam_setup_4.sin \ functional_tests/beam_setup_5.sin \ functional_tests/bjet_cluster.sin \ functional_tests/br_redef_1.sin \ functional_tests/cascades2_phs_1.sin \ functional_tests/cascades2_phs_2.sin \ functional_tests/circe1_1.sin \ functional_tests/circe1_2.sin \ functional_tests/circe1_3.sin \ functional_tests/circe1_4.sin \ functional_tests/circe1_5.sin \ functional_tests/circe1_6.sin \ functional_tests/circe1_7.sin \ functional_tests/circe1_8.sin \ functional_tests/circe1_9.sin \ functional_tests/circe1_10.sin \ functional_tests/circe1_errors_1.sin \ functional_tests/circe1_photons_1.sin \ functional_tests/circe1_photons_2.sin \ functional_tests/circe1_photons_3.sin \ functional_tests/circe1_photons_4.sin \ functional_tests/circe1_photons_5.sin \ functional_tests/circe2_1.sin \ functional_tests/circe2_2.sin \ functional_tests/circe2_3.sin \ functional_tests/cmdline_1.sin \ functional_tests/cmdline_1_a.sin \ functional_tests/cmdline_1_b.sin \ functional_tests/colors.sin \ functional_tests/colors_2.sin \ functional_tests/colors_hgg.sin \ functional_tests/cuts.sin \ functional_tests/decay_err_1.sin \ functional_tests/decay_err_2.sin \ functional_tests/decay_err_3.sin \ functional_tests/defaultcuts.sin \ functional_tests/empty.sin \ functional_tests/energy_scan_1.sin \ functional_tests/ep_1.sin \ functional_tests/ep_2.sin \ functional_tests/ep_3.sin \ functional_tests/epa_1.sin \ functional_tests/epa_2.sin \ functional_tests/epa_3.sin \ functional_tests/epa_4.sin \ functional_tests/event_dump_1.sin \ functional_tests/event_dump_2.sin \ functional_tests/event_eff_1.sin \ functional_tests/event_eff_2.sin \ functional_tests/event_failed_1.sin \ functional_tests/event_weights_1.sin \ functional_tests/event_weights_2.sin \ functional_tests/ewa_1.sin \ functional_tests/ewa_2.sin \ functional_tests/ewa_3.sin \ functional_tests/ewa_4.sin \ functional_tests/extpar.sin \ functional_tests/fatal.sin \ functional_tests/fatal_beam_decay.sin \ functional_tests/fks_res_1.sin \ functional_tests/fks_res_2.sin \ functional_tests/fks_res_3.sin \ functional_tests/flvsum_1.sin \ functional_tests/gaussian_1.sin \ functional_tests/gaussian_2.sin \ functional_tests/hadronize_1.sin \ functional_tests/helicity.sin \ functional_tests/hepmc_1.sin \ functional_tests/hepmc_2.sin \ functional_tests/hepmc_3.sin \ functional_tests/hepmc_4.sin \ functional_tests/hepmc_5.sin \ functional_tests/hepmc_6.sin \ functional_tests/hepmc_7.sin \ functional_tests/hepmc_8.sin \ functional_tests/hepmc_9.sin \ functional_tests/hepmc_10.sin \ functional_tests/ilc.sin \ functional_tests/isr_1.sin \ functional_tests/isr_2.sin \ functional_tests/isr_3.sin \ functional_tests/isr_4.sin \ functional_tests/isr_5.sin \ functional_tests/isr_6.sin \ functional_tests/isr_epa_1.sin \ functional_tests/jets_xsec.sin \ functional_tests/job_id_1.sin \ functional_tests/job_id_2.sin \ functional_tests/job_id_3.sin \ functional_tests/job_id_4.sin \ functional_tests/lcio_1.sin \ functional_tests/lcio_2.sin \ functional_tests/lcio_3.sin \ functional_tests/lcio_4.sin \ functional_tests/lcio_5.sin \ functional_tests/lcio_6.sin \ functional_tests/lcio_7.sin \ functional_tests/lcio_8.sin \ functional_tests/lcio_9.sin \ functional_tests/lcio_10.sin \ functional_tests/lcio_11.sin \ functional_tests/lcio_12.sin \ functional_tests/lhapdf5.sin \ functional_tests/lhapdf6.sin \ functional_tests/lhef_1.sin \ functional_tests/lhef_2.sin \ functional_tests/lhef_3.sin \ functional_tests/lhef_4.sin \ functional_tests/lhef_5.sin \ functional_tests/lhef_6.sin \ functional_tests/lhef_7.sin \ functional_tests/lhef_8.sin \ functional_tests/lhef_9.sin \ functional_tests/lhef_10.sin \ functional_tests/lhef_11.sin \ functional_tests/libraries_1.sin \ functional_tests/libraries_2.sin \ functional_tests/libraries_3.sin \ functional_tests/libraries_4.sin \ functional_tests/method_ovm_1.sin \ functional_tests/mlm_matching_fsr.sin \ functional_tests/mlm_matching_isr.sin \ functional_tests/mlm_pythia6_isr.sin \ functional_tests/model_change_1.sin \ functional_tests/model_change_2.sin \ functional_tests/model_change_3.sin \ functional_tests/model_scheme_1.sin \ functional_tests/model_test.sin \ functional_tests/mssmtest_1.sin \ functional_tests/mssmtest_2.sin \ functional_tests/mssmtest_3.sin \ functional_tests/multi_comp_1.sin \ functional_tests/multi_comp_2.sin \ functional_tests/multi_comp_3.sin \ functional_tests/multi_comp_4.sin \ functional_tests/nlo_1.sin \ functional_tests/nlo_2.sin \ functional_tests/nlo_3.sin \ functional_tests/nlo_4.sin \ functional_tests/nlo_5.sin \ functional_tests/nlo_6.sin \ functional_tests/nlo_7.sin \ functional_tests/nlo_8.sin \ functional_tests/nlo_9.sin \ functional_tests/nlo_10.sin \ functional_tests/nlo_decay_1.sin \ functional_tests/observables_1.sin \ functional_tests/observables_2.sin \ functional_tests/openloops_1.sin \ functional_tests/openloops_2.sin \ functional_tests/openloops_3.sin \ functional_tests/openloops_4.sin \ functional_tests/openloops_5.sin \ functional_tests/openloops_6.sin \ functional_tests/openloops_7.sin \ functional_tests/openloops_8.sin \ functional_tests/openloops_9.sin \ functional_tests/openloops_10.sin \ functional_tests/openloops_11.sin \ functional_tests/openloops_12.sin \ functional_tests/openloops_13.sin \ functional_tests/openloops_14.sin \ functional_tests/pack_1.sin \ functional_tests/parton_shower_1.sin \ functional_tests/parton_shower_2.sin \ functional_tests/pdf_builtin.sin \ functional_tests/photon_isolation_1.sin \ functional_tests/photon_isolation_2.sin \ functional_tests/polarized_1.sin \ functional_tests/powheg_1.sin \ functional_tests/process_log.sin \ functional_tests/pythia6_1.sin \ functional_tests/pythia6_2.sin \ functional_tests/pythia6_3.sin \ functional_tests/pythia6_4.sin \ functional_tests/pythia8_1.sin \ functional_tests/pythia8_2.sin \ functional_tests/qcdtest_1.sin \ functional_tests/qcdtest_2.sin \ functional_tests/qcdtest_3.sin \ functional_tests/qcdtest_4.sin \ functional_tests/qcdtest_5.sin \ functional_tests/qcdtest_6.sin \ functional_tests/qedtest_1.sin \ functional_tests/qedtest_2.sin \ functional_tests/qedtest_3.sin \ functional_tests/qedtest_4.sin \ functional_tests/qedtest_5.sin \ functional_tests/qedtest_6.sin \ functional_tests/qedtest_7.sin \ functional_tests/qedtest_8.sin \ functional_tests/qedtest_9.sin \ functional_tests/qedtest_10.sin \ functional_tests/rambo_vamp_1.sin \ functional_tests/rambo_vamp_2.sin \ functional_tests/real_partition_1.sin \ functional_tests/rebuild_1.sin \ functional_tests/rebuild_2.sin \ functional_tests/rebuild_3.sin \ functional_tests/rebuild_4.sin \ functional_tests/rebuild_5.sin \ functional_tests/recola_1.sin \ functional_tests/recola_2.sin \ functional_tests/recola_3.sin \ functional_tests/recola_4.sin \ functional_tests/recola_5.sin \ functional_tests/recola_6.sin \ functional_tests/recola_7.sin \ functional_tests/recola_8.sin \ functional_tests/recola_9.sin \ functional_tests/resonances_1.sin \ functional_tests/resonances_2.sin \ functional_tests/resonances_3.sin \ functional_tests/resonances_4.sin \ functional_tests/resonances_5.sin \ functional_tests/resonances_6.sin \ functional_tests/resonances_7.sin \ functional_tests/resonances_8.sin \ functional_tests/resonances_9.sin \ functional_tests/resonances_10.sin \ functional_tests/resonances_11.sin \ functional_tests/resonances_12.sin \ functional_tests/resonances_13.sin \ functional_tests/resonances_14.sin \ functional_tests/resonances_15.sin \ functional_tests/restrictions.sin \ functional_tests/reweight_1.sin \ functional_tests/reweight_2.sin \ functional_tests/reweight_3.sin \ functional_tests/reweight_4.sin \ functional_tests/reweight_5.sin \ functional_tests/reweight_6.sin \ functional_tests/reweight_7.sin \ functional_tests/reweight_8.sin \ functional_tests/reweight_9.sin \ functional_tests/reweight_10.sin \ functional_tests/select_1.sin \ functional_tests/select_2.sin \ functional_tests/show_1.sin \ functional_tests/show_2.sin \ functional_tests/show_3.sin \ functional_tests/show_4.sin \ functional_tests/show_5.sin \ functional_tests/shower_err_1.sin \ functional_tests/sm_cms_1.sin \ functional_tests/smtest_1.sin \ functional_tests/smtest_2.sin \ functional_tests/smtest_3.sin \ functional_tests/smtest_4.sin \ functional_tests/smtest_5.sin \ functional_tests/smtest_6.sin \ functional_tests/smtest_7.sin \ functional_tests/smtest_8.sin \ functional_tests/smtest_9.sin \ functional_tests/smtest_10.sin \ functional_tests/smtest_11.sin \ functional_tests/smtest_12.sin \ functional_tests/smtest_13.sin \ functional_tests/smtest_14.sin \ functional_tests/smtest_15.sin \ functional_tests/smtest_16.sin \ functional_tests/smtest_17.sin \ functional_tests/spincor_1.sin \ functional_tests/static_1.exe.sin \ functional_tests/static_1.sin \ functional_tests/static_2.exe.sin \ functional_tests/static_2.sin \ functional_tests/stdhep_1.sin \ functional_tests/stdhep_2.sin \ functional_tests/stdhep_3.sin \ functional_tests/stdhep_4.sin \ functional_tests/stdhep_5.sin \ functional_tests/stdhep_6.sin \ functional_tests/structure_1.sin \ functional_tests/structure_2.sin \ functional_tests/structure_3.sin \ functional_tests/structure_4.sin \ functional_tests/structure_5.sin \ functional_tests/structure_6.sin \ functional_tests/structure_7.sin \ functional_tests/structure_8.sin \ functional_tests/susyhit.sin \ functional_tests/tauola_1.sin \ functional_tests/tauola_2.sin \ functional_tests/tauola_3.sin \ functional_tests/template_me_1.sin \ functional_tests/template_me_2.sin \ functional_tests/testproc_1.sin \ functional_tests/testproc_2.sin \ functional_tests/testproc_3.sin \ functional_tests/testproc_4.sin \ functional_tests/testproc_5.sin \ functional_tests/testproc_6.sin \ functional_tests/testproc_7.sin \ functional_tests/testproc_8.sin \ functional_tests/testproc_9.sin \ functional_tests/testproc_10.sin \ functional_tests/testproc_11.sin \ functional_tests/testproc_12.sin \ functional_tests/ufo_1.sin \ functional_tests/ufo_2.sin \ functional_tests/ufo_3.sin \ functional_tests/ufo_4.sin \ functional_tests/ufo_5.sin \ functional_tests/ufo_6.sin \ functional_tests/user_prc_threshold_1.sin \ functional_tests/user_prc_threshold_2.sin \ functional_tests/vamp2_1.sin \ functional_tests/vamp2_2.sin \ functional_tests/vamp2_3.sin \ functional_tests/vars.sin EXT_MSSM_M4 = \ ext_tests_mssm/mssm_ext-aa.m4 \ ext_tests_mssm/mssm_ext-bb.m4 \ ext_tests_mssm/mssm_ext-bt.m4 \ ext_tests_mssm/mssm_ext-dd.m4 \ ext_tests_mssm/mssm_ext-dd2.m4 \ ext_tests_mssm/mssm_ext-ddckm.m4 \ ext_tests_mssm/mssm_ext-dg.m4 \ ext_tests_mssm/mssm_ext-ee.m4 \ ext_tests_mssm/mssm_ext-ee2.m4 \ ext_tests_mssm/mssm_ext-en.m4 \ ext_tests_mssm/mssm_ext-ga.m4 \ ext_tests_mssm/mssm_ext-gg.m4 \ ext_tests_mssm/mssm_ext-gw.m4 \ ext_tests_mssm/mssm_ext-gz.m4 \ ext_tests_mssm/mssm_ext-tn.m4 \ ext_tests_mssm/mssm_ext-tt.m4 \ ext_tests_mssm/mssm_ext-ug.m4 \ ext_tests_mssm/mssm_ext-uu.m4 \ ext_tests_mssm/mssm_ext-uu2.m4 \ ext_tests_mssm/mssm_ext-uuckm.m4 \ ext_tests_mssm/mssm_ext-wa.m4 \ ext_tests_mssm/mssm_ext-ww.m4 \ ext_tests_mssm/mssm_ext-wz.m4 \ ext_tests_mssm/mssm_ext-za.m4 \ ext_tests_mssm/mssm_ext-zz.m4 EXT_NMSSM_M4 = \ ext_tests_nmssm/nmssm_ext-aa.m4 \ ext_tests_nmssm/nmssm_ext-bb1.m4 \ ext_tests_nmssm/nmssm_ext-bb2.m4 \ ext_tests_nmssm/nmssm_ext-bt.m4 \ ext_tests_nmssm/nmssm_ext-dd1.m4 \ ext_tests_nmssm/nmssm_ext-dd2.m4 \ ext_tests_nmssm/nmssm_ext-ee1.m4 \ ext_tests_nmssm/nmssm_ext-ee2.m4 \ ext_tests_nmssm/nmssm_ext-en.m4 \ ext_tests_nmssm/nmssm_ext-ga.m4 \ ext_tests_nmssm/nmssm_ext-gg.m4 \ ext_tests_nmssm/nmssm_ext-gw.m4 \ ext_tests_nmssm/nmssm_ext-gz.m4 \ ext_tests_nmssm/nmssm_ext-qg.m4 \ ext_tests_nmssm/nmssm_ext-tn.m4 \ ext_tests_nmssm/nmssm_ext-tt1.m4 \ ext_tests_nmssm/nmssm_ext-tt2.m4 \ ext_tests_nmssm/nmssm_ext-uu1.m4 \ ext_tests_nmssm/nmssm_ext-uu2.m4 \ ext_tests_nmssm/nmssm_ext-wa.m4 \ ext_tests_nmssm/nmssm_ext-ww1.m4 \ ext_tests_nmssm/nmssm_ext-ww2.m4 \ ext_tests_nmssm/nmssm_ext-wz.m4 \ ext_tests_nmssm/nmssm_ext-za.m4 \ ext_tests_nmssm/nmssm_ext-zz1.m4 \ ext_tests_nmssm/nmssm_ext-zz2.m4 EXT_MSSM_SIN = $(EXT_MSSM_M4:.m4=.sin) EXT_NMSSM_SIN = $(EXT_NMSSM_M4:.m4=.sin) EXT_ILC_SIN = \ ext_tests_ilc/ilc_settings.sin \ ext_tests_ilc/ilc_top_pair_360.sin \ ext_tests_ilc/ilc_top_pair_500.sin \ ext_tests_ilc/ilc_vbf_higgs_360.sin \ ext_tests_ilc/ilc_vbf_higgs_500.sin \ ext_tests_ilc/ilc_vbf_no_higgs_360.sin \ ext_tests_ilc/ilc_vbf_no_higgs_500.sin \ ext_tests_ilc/ilc_higgs_strahlung_360.sin \ ext_tests_ilc/ilc_higgs_strahlung_500.sin \ ext_tests_ilc/ilc_higgs_strahlung_background_360.sin \ ext_tests_ilc/ilc_higgs_strahlung_background_500.sin \ ext_tests_ilc/ilc_higgs_coupling_360.sin \ ext_tests_ilc/ilc_higgs_coupling_500.sin \ ext_tests_ilc/ilc_higgs_coupling_background_360.sin \ ext_tests_ilc/ilc_higgs_coupling_background_500.sin EXT_SHOWER_SIN = \ ext_tests_shower/shower_1_norad.sin \ ext_tests_shower/shower_2_aall.sin \ ext_tests_shower/shower_3_bb.sin \ ext_tests_shower/shower_3_jj.sin \ ext_tests_shower/shower_3_qqqq.sin \ ext_tests_shower/shower_3_tt.sin \ ext_tests_shower/shower_3_z_nu.sin \ ext_tests_shower/shower_3_z_tau.sin \ ext_tests_shower/shower_4_ee.sin \ ext_tests_shower/shower_5.sin \ ext_tests_shower/shower_6.sin EXT_NLO_SIN = \ ext_tests_nlo/nlo_ee4b.sin \ ext_tests_nlo/nlo_ee4j.sin \ ext_tests_nlo/nlo_ee4t.sin \ ext_tests_nlo/nlo_ee4tj.sin \ ext_tests_nlo/nlo_ee5j.sin \ ext_tests_nlo/nlo_eebb.sin \ ext_tests_nlo/nlo_eebbj.sin \ ext_tests_nlo/nlo_eebbjj.sin \ ext_tests_nlo/nlo_eejj.sin \ ext_tests_nlo/nlo_eejjj.sin \ ext_tests_nlo/nlo_eett.sin \ ext_tests_nlo/nlo_eetta.sin \ ext_tests_nlo/nlo_eettaa.sin \ ext_tests_nlo/nlo_eettah.sin \ ext_tests_nlo/nlo_eettaj.sin \ ext_tests_nlo/nlo_eettajj.sin \ ext_tests_nlo/nlo_eettaz.sin \ ext_tests_nlo/nlo_eettbb.sin \ ext_tests_nlo/nlo_eetth.sin \ ext_tests_nlo/nlo_eetthh.sin \ ext_tests_nlo/nlo_eetthj.sin \ ext_tests_nlo/nlo_eetthjj.sin \ ext_tests_nlo/nlo_eetthz.sin \ ext_tests_nlo/nlo_eettj.sin \ ext_tests_nlo/nlo_eettjj.sin \ ext_tests_nlo/nlo_eettjjj.sin \ ext_tests_nlo/nlo_eettwjj.sin \ ext_tests_nlo/nlo_eettww.sin \ ext_tests_nlo/nlo_eettz.sin \ ext_tests_nlo/nlo_eettzj.sin \ ext_tests_nlo/nlo_eettzjj.sin \ ext_tests_nlo/nlo_eettzz.sin \ ext_tests_nlo/nlo_ppzj_real_partition.sin \ ext_tests_nlo/nlo_pptttt.sin \ ext_tests_nlo/nlo_ppw.sin \ ext_tests_nlo/nlo_ppz.sin \ ext_tests_nlo/nlo_ppzj_sim_1.sin \ ext_tests_nlo/nlo_ppzj_sim_2.sin \ ext_tests_nlo/nlo_ppzj_sim_3.sin \ ext_tests_nlo/nlo_ppzj_sim_4.sin \ ext_tests_nlo/nlo_ppzw.sin \ ext_tests_nlo/nlo_ppzz.sin \ ext_tests_nlo/nlo_ppee_ew.sin \ ext_tests_nlo/nlo_pphee_ew.sin \ ext_tests_nlo/nlo_pphjj_ew.sin \ ext_tests_nlo/nlo_pphz_ew.sin \ ext_tests_nlo/nlo_ppllll_ew.sin \ ext_tests_nlo/nlo_ppllnn_ew.sin \ ext_tests_nlo/nlo_pptj_ew.sin \ ext_tests_nlo/nlo_ppwhh_ew.sin \ ext_tests_nlo/nlo_ppww_ew.sin \ ext_tests_nlo/nlo_ppwzh_ew.sin \ ext_tests_nlo/nlo_ppz_ew.sin \ ext_tests_nlo/nlo_ppzzz_ew.sin \ + ext_tests_nlo/nlo_ppeej_ew.sin \ + ext_tests_nlo/nlo_ppevj_ew.sin \ + ext_tests_nlo/nlo_pptt_ew.sin \ ext_tests_nlo/nlo_settings.sin \ ext_tests_nlo/nlo_settings_ew.sin EXT_NLO_ADD_SIN = \ ext_tests_nlo_add/nlo_decay_tbw.sin \ ext_tests_nlo_add/nlo_fks_delta_i_ppee.sin \ ext_tests_nlo_add/nlo_fks_delta_o_eejj.sin \ ext_tests_nlo_add/nlo_jets.sin \ ext_tests_nlo_add/nlo_methods_gosam.sin \ ext_tests_nlo_add/nlo_qq_powheg.sin \ ext_tests_nlo_add/nlo_threshold_factorized.sin \ ext_tests_nlo_add/nlo_threshold.sin \ ext_tests_nlo_add/nlo_tt_powheg_sudakov.sin \ ext_tests_nlo_add/nlo_tt_powheg.sin \ ext_tests_nlo_add/nlo_tt.sin \ ext_tests_nlo_add/nlo_uu_powheg.sin \ ext_tests_nlo_add/nlo_uu.sin all-local: $(TESTSUITES_SIN) if M4_AVAILABLE SUFFIXES = .m4 .sin .m4.sin: case "$@" in \ */*) \ mkdir -p `sed 's,/.[^/]*$$,,g' <<< "$@"` ;; \ esac $(M4) $(srcdir)/$(TESTSUITE_MACROS) $< > $@ endif M4_AVAILABLE Index: trunk/share/tests/ext_tests_nlo/nlo_ppeej_ew.sin =================================================================== --- trunk/share/tests/ext_tests_nlo/nlo_ppeej_ew.sin (revision 0) +++ trunk/share/tests/ext_tests_nlo/nlo_ppeej_ew.sin (revision 8818) @@ -0,0 +1,201 @@ +include("nlo_settings_ew.sin") +alias jet = u:U:d:D:s:S:c:C:b:B:gl:A:E1:e1 +alias pr=u:U:d:D:s:S:c:C:b:B:A:gl +alias j= u:U:d:D:s:S:c:C:b:B:A:gl +alias quarks = u:U:d:D:s:S:c:C:b:B + + +mZ=91.15348 +mW=80.35797 +wZ=2.494266 +wW=2.084299 + +wtop = 1.36918 + +alpha_power = 2 +alphas_power = 1 + + +cuts= + let subevt @recfermion = photon_recombination [A:e1:E1:quarks] in + let subevt @dressedleptons = select if abs(real(PDG)) == 11. [@recfermion] in + let subevt @firstlep = extract index 1 [@dressedleptons] in + let subevt @secondlep = extract index 2 [@dressedleptons] in + let subevt @dressedquarks = select if abs(real(PDG)) <= 5. [@recfermion] in + let subevt @notreco_photon = select if abs(real(PDG)) == 22. [@recfermion] in + let subevt @clustered_jets = cluster [join[gl, join[@notreco_photon,@dressedquarks]]] in + let subevt @pt_selected = select if Pt > 30 GeV [@clustered_jets] in + let subevt @eta_selected = select if abs(Eta) < 4.5 [@pt_selected] in + count[@eta_selected]>=1 + and all Pt > 10. [@dressedleptons] + and all abs(Eta) < 2.5 [@dressedleptons] + and all Dist >0.4 [@firstlep, @secondlep] + and all M >= 30 [collect[@dressedleptons]] + + + +scale = sum (Pt/2) [jet] + +$nlo_correction_type = "EW" + +seed=1 +process nlo_ppeej_ew = pr, pr => e1,E1, j {nlo_calculation = full} + + +integrate (nlo_ppeej_ew) { iterations = 1:1000:"gw" mult_call_virt = 0.1} + +!!! Note: With the current status of the public_beta branch of OpenLoops (30-03-2022) this Sindarin yields incorrect results. Please check out commit "c56ba08c73696bd8c9ac70adbddc5c2e9da78d0c" in the public_beta git repository for the following results: +!!! +!| Starting integration for process 'drellyNLO' part 'born' +!| Integrate: iterations = 10:30000000:"gw", 3:90000000 +!| Integrator: 10 chains, 39 channels, 7 dimensions +!| Integrator: Using VAMP2 channel equivalences +!| Integrator: Write grid header and grids to 'drellyNLO.m1.vg2' +!| Integrator: Grid checkpoint after each iteration +!| Integrator: 30000000 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. +!| VAMP2: Simple Request Balancing. +! 1 26392286 1.4914477E+05 1.74E+03 1.17 60.03* 0.01 +! 2 25728574 1.5057694E+05 1.58E+02 0.11 5.33* 0.58 +! 3 26552117 1.5065843E+05 6.42E+01 0.04 2.20* 1.09 +! 4 25728574 1.5053324E+05 5.20E+01 0.03 1.75* 0.55 +! 5 25103574 1.5067822E+05 5.03E+01 0.03 1.67* 1.14 +! 6 25064583 1.5065286E+05 4.94E+01 0.03 1.64* 0.95 +! 7 25653894 1.5067880E+05 4.56E+01 0.03 1.53* 1.82 +! 8 25110287 1.5063458E+05 4.39E+01 0.03 1.46* 1.44 +! 9 25162275 1.5057428E+05 4.26E+01 0.03 1.42* 1.94 +! 10 25149278 1.5065034E+05 4.15E+01 0.03 1.38* 2.09 +!|-----------------------------------------------------------------------------| +! 10 255645442 1.5063104E+05 1.67E+01 0.01 1.77 2.09 0.97 10 +!|-----------------------------------------------------------------------------| +!| VAMP2: Simple Request Balancing. +! 11 81422870 1.5057449E+05 2.13E+01 0.01 1.28* 1.75 +! 12 81422870 1.5059629E+05 2.13E+01 0.01 1.28* 1.63 +! 13 81422870 1.5059701E+05 2.13E+01 0.01 1.28 1.62 +!|-----------------------------------------------------------------------------| +! 13 244268610 1.5058927E+05 1.23E+01 0.01 1.28 1.62 0.36 3 +!|=============================================================================| +!| Starting integration for process 'drellyNLO' part 'real' +!| Integrate: iterations = 10:10000000:"gw", 3:30000000 +!| Integrator: 10 chains, 39 channels, 10 dimensions +!| Integrator: Using VAMP2 channel equivalences +!| Integrator: Write grid header and grids to 'drellyNLO.m2.vg2' +!| Integrator: Grid checkpoint after each iteration +!| Integrator: 10000000 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. +!| VAMP2: Simple Request Balancing. +! 1 8266860 -8.0956833E-01 3.05E+02 ******* ******** 0.01 +! 2 8621154 -1.3237095E+02 4.35E+01 32.84 964.16* 0.05 +! 3 8916399 -1.5339777E+02 2.17E+01 14.12 421.62* 0.14 +! 4 8089713 -1.2778050E+02 1.60E+01 12.54 356.64* 0.23 +! 5 8562105 -1.6182601E+02 1.57E+01 9.71 284.07* 0.19 +! 6 9270693 -1.4047393E+02 1.44E+01 10.28 313.05 0.25 +! 7 9211644 -1.4138829E+02 1.32E+01 9.36 284.06* 0.29 +! 8 9624987 -1.5400797E+02 1.35E+01 8.76 271.86* 0.22 +! 9 9388791 -1.3214733E+02 1.28E+01 9.69 296.99 0.23 +! 10 8739252 -1.3451263E+02 1.24E+01 9.20 271.97* 0.32 +!|-----------------------------------------------------------------------------| +! 10 88691598 -1.4171435E+02 5.05E+00 3.56 335.48 0.32 0.52 10 +!|-----------------------------------------------------------------------------| +!| VAMP2: Simple Request Balancing. +! 11 28461618 -1.5191999E+02 7.17E+00 4.72 251.63* 0.18 +! 12 28461618 -1.5380865E+02 7.60E+00 4.94 263.49 0.12 +! 13 28461618 -1.4270325E+02 7.33E+00 5.14 274.07 0.18 +!|-----------------------------------------------------------------------------| +! 13 85384854 -1.4941568E+02 4.25E+00 2.84 262.72 0.18 0.65 3 +!|=============================================================================| +!| Starting integration for process 'drellyNLO' part 'virtual' +!| Integrate: iterations = 10:10000:"gw", 3:30000 +!| Integrator: 10 chains, 39 channels, 7 dimensions +!| Integrator: Using VAMP2 channel equivalences +!| Integrator: Write grid header and grids to 'drellyNLO.m3.vg2' +!| Integrator: Grid checkpoint after each iteration +!| Integrator: 10000 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. +!| VAMP2: Simple Request Balancing. +!######################################################################## +!# # +!# You are using OneLOop # +!# # +!# for the evaluation of 1-loop scalar 1-, 2-, 3- and 4-point functions # +!# # +!# author: Andreas van Hameren # +!# date: 2018-06-13 # +!# # +!# Please cite # +!# A. van Hameren, # +!# Comput.Phys.Commun. 182 (2011) 2427-2438, arXiv:1007.4716 # +!# A. van Hameren, C.G. Papadopoulos and R. Pittau, # +!# JHEP 0909:106,2009, arXiv:0903.4665 # +!# in publications with results obtained with the help of this program. # +!# # +!######################################################################## +! 1 9198 -2.1103786E+03 1.36E+03 64.54 61.89* 0.60 +! 2 9494 -1.2246341E+03 1.67E+02 13.63 13.28* 1.02 +! 3 9233 -1.6442676E+03 8.94E+01 5.43 5.22* 2.52 +! 4 9290 -1.6589427E+03 6.18E+01 3.73 3.59* 5.46 +! 5 9207 -1.6854464E+03 5.64E+01 3.34 3.21* 5.63 +! 6 9144 -1.6063849E+03 5.83E+01 3.63 3.47 6.58 +! 7 9264 -1.7086486E+03 5.83E+01 3.41 3.29* 5.44 +! 8 8939 -1.6474593E+03 5.33E+01 3.24 3.06* 6.86 +! 9 9411 -1.5821779E+03 5.47E+01 3.46 3.35 7.89 +! 10 9204 -1.7027979E+03 5.60E+01 3.29 3.16* 6.83 +!|-----------------------------------------------------------------------------| +! 10 92384 -1.6480367E+03 2.07E+01 1.26 3.82 6.83 1.22 10 +!|-----------------------------------------------------------------------------| +!| VAMP2: Simple Request Balancing. +! 11 28904 -1.6090651E+03 3.20E+01 1.99 3.38 4.70 +! 12 28904 -1.6869201E+03 5.04E+01 2.99 5.08 2.99 +! 13 28904 -1.6309925E+03 2.98E+01 1.83 3.10* 5.20 +!|-----------------------------------------------------------------------------| +! 13 86712 -1.6312545E+03 2.00E+01 1.23 3.61 5.20 0.85 3 +!|=============================================================================| +!| Starting integration for process 'drellyNLO' part 'dglap' +!| Integrate: iterations = 10:1000000:"gw", 3:3000000 +!| Integrator: 10 chains, 39 channels, 8 dimensions +!| Integrator: Using VAMP2 channel equivalences +!| Integrator: Write grid header and grids to 'drellyNLO.m4.vg2' +!| Integrator: Grid checkpoint after each iteration +!| Integrator: 1000000 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. +!| VAMP2: Simple Request Balancing. +! 1 931662 2.5314580E+02 2.20E+01 8.69 83.88* 0.05 +! 2 900947 2.6746813E+02 3.72E+00 1.39 13.20* 0.45 +! 3 942472 2.6911417E+02 1.90E+00 0.71 6.85* 0.98 +! 4 923813 2.6929851E+02 1.48E+00 0.55 5.27* 1.29 +! 5 931662 2.6906123E+02 1.35E+00 0.50 4.85* 1.59 +! 6 925101 2.6989334E+02 1.23E+00 0.46 4.38* 1.81 +! 7 925101 2.7166011E+02 1.15E+00 0.42 4.07* 2.35 +! 8 872613 2.7020142E+02 1.10E+00 0.41 3.81* 2.09 +! 9 925101 2.6844016E+02 1.08E+00 0.40 3.87 2.76 +! 10 885735 2.7113503E+02 1.03E+00 0.38 3.56* 2.62 +!|-----------------------------------------------------------------------------| +! 10 9164207 2.6996244E+02 4.30E-01 0.16 4.82 2.62 0.82 10 +!|-----------------------------------------------------------------------------| +!| VAMP2: Simple Request Balancing. +! 11 2834056 2.6980393E+02 5.72E-01 0.21 3.57 2.18 +! 12 2834056 2.7039402E+02 5.75E-01 0.21 3.58 2.28 +! 13 2834056 2.6941598E+02 5.72E-01 0.21 3.57* 2.13 +!|-----------------------------------------------------------------------------| +! 13 8502168 2.6986934E+02 3.31E-01 0.12 3.57 2.13 0.74 3 +!|=============================================================================| Index: trunk/share/tests/ext_tests_nlo/nlo_ppevj_ew.sin =================================================================== --- trunk/share/tests/ext_tests_nlo/nlo_ppevj_ew.sin (revision 0) +++ trunk/share/tests/ext_tests_nlo/nlo_ppevj_ew.sin (revision 8818) @@ -0,0 +1,192 @@ +include("nlo_settings_ew.sin") + +alias jet = u:U:d:D:s:S:c:C:b:B:gl:A:E1:n1 +alias pr=u:U:d:D:s:S:c:C:b:B:A:gl +alias j= u:U:d:D:s:S:c:C:b:B:A:gl +alias quarks = u:U:d:D:s:S:c:C:b:B + +mZ=91.15348 +mW=80.35797 +wZ=2.494266 +wW=2.084299 + +wtop = 1.36918 + +alpha_power = 2 +alphas_power = 1 + +cuts= + let subevt @recfermion = photon_recombination [A:E1:quarks] in + let subevt @dressedleptons = select if abs(real(PDG)) == 11. [@recfermion] in + let subevt @dressedquarks = select if abs(real(PDG)) <= 5. [@recfermion] in + let subevt @notreco_photon = select if abs(real(PDG)) == 22. [@recfermion] in + let subevt @clustered_jets = cluster [join[gl, join[@notreco_photon,@dressedquarks]]] in + let subevt @pt_selected = select if Pt > 30 GeV [@clustered_jets] in + let subevt @eta_selected = select if abs(Eta) < 4.5 [@pt_selected] in + count[@eta_selected]>=1 + and all Pt > 10. [@dressedleptons] + and all abs(Eta) < 2.5 [@dressedleptons] + + +scale = sum (Pt/2) [jet] + +$nlo_correction_type = "EW" + +seed=1 +process nlo_ppevj_ew = pr, pr => E1,n1, j {nlo_calculation = full} + +integrate (nlo_ppevj_ew) { iterations = 1:1000:"gw" mult_call_virt = 0.1} + +!!! Note: With the current status of the public_beta branch of OpenLoops (30-03-2022) this Sindarin yields incorrect results. Please check out commit "c56ba08c73696bd8c9ac70adbddc5c2e9da78d0c" in the public_beta git repository for the following results: +!!! +!!! ?use_vamp_equivalences = false +!!! +!| Starting integration for process 'drellyNLO' part 'born' +!| Integrate: iterations = 10:30000000:"gw", 3:90000000 +!| Integrator: 10 chains, 17 channels, 7 dimensions +!| Integrator: Write grid header and grids to 'drellyNLO.m1.vg2' +!| Integrator: Grid checkpoint after each iteration +!| Integrator: 30000000 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. +!| VAMP2: Simple Request Balancing. +! 1 27124693 9.1609414E+05 6.32E+03 0.69 35.92* 0.02 +! 2 25741278 9.1414831E+05 8.56E+02 0.09 4.75* 0.44 +! 3 24341598 9.1504515E+05 3.39E+02 0.04 1.83* 0.73 +! 4 24885205 9.1455689E+05 2.63E+02 0.03 1.44* 0.58 +! 5 23781726 9.1479860E+05 2.44E+02 0.03 1.30* 0.99 +! 6 24341598 9.1460105E+05 2.41E+02 0.03 1.30 1.05 +! 7 25181406 9.1451570E+05 2.31E+02 0.03 1.27* 0.98 +! 8 24621534 9.1473165E+05 2.26E+02 0.02 1.22* 1.17 +! 9 25741278 9.1450918E+05 2.22E+02 0.02 1.23 1.12 +! 10 25708748 9.1455930E+05 2.16E+02 0.02 1.20* 1.31 +!|-----------------------------------------------------------------------------| +! 10 251469064 9.1463114E+05 8.50E+01 0.01 1.47 1.31 0.36 10 +!|-----------------------------------------------------------------------------| +!| VAMP2: Simple Request Balancing. +! 11 82783922 9.1473829E+05 1.13E+02 0.01 1.13* 1.24 +! 12 82783922 9.1470782E+05 1.13E+02 0.01 1.13 1.24 +! 13 82783922 9.1478251E+05 1.13E+02 0.01 1.13 1.22 +!|-----------------------------------------------------------------------------| +! 13 248351766 9.1474286E+05 6.54E+01 0.01 1.13 1.22 0.11 3 +!|=============================================================================| +!| Starting integration for process 'drellyNLO' part 'real' +!| Integrate: iterations = 10:50000000:"gw", 3:150000000 +!| Integrator: 10 chains, 17 channels, 10 dimensions +!| Integrator: Write grid header and grids to 'drellyNLO.m2.vg2' +!| Integrator: Grid checkpoint after each iteration +!| Integrator: 50000000 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. +!| VAMP2: Simple Request Balancing. +! 1 44437404 -2.9639406E+02 4.59E+02 155.02 ******** 0.00 +! 2 45217522 3.6848444E+02 5.19E+01 14.08 946.67* 0.03 +! 3 46720534 4.0487202E+02 2.67E+01 6.60 451.32* 0.05 +! 4 47074828 3.3805878E+02 2.14E+01 6.34 434.96* 0.06 +! 5 46205224 3.6896791E+02 1.98E+01 5.37 364.74* 0.09 +! 6 47015779 3.4832998E+02 1.94E+01 5.57 382.04 0.09 +! 7 47192926 3.6935222E+02 1.92E+01 5.21 357.72* 0.07 +! 8 44224345 3.5339274E+02 1.80E+01 5.09 338.33* 0.13 +! 9 46720534 3.3799325E+02 1.84E+01 5.44 372.01 0.11 +! 10 46781408 3.5284701E+02 1.88E+01 5.32 363.66* 0.08 +!|-----------------------------------------------------------------------------| +! 10 461590504 3.5645536E+02 6.94E+00 1.95 418.40 0.08 0.91 10 +!|-----------------------------------------------------------------------------| +!| VAMP2: Simple Request Balancing. +! 11 142606336 3.7685064E+02 1.43E+01 3.80 453.46 0.03 +! 12 142606336 3.6016281E+02 1.05E+01 2.91 347.59* 0.05 +! 13 142606336 3.2957596E+02 1.05E+01 3.18 379.81 0.05 +!|-----------------------------------------------------------------------------| +! 13 427819008 3.5163401E+02 6.58E+00 1.87 387.16 0.05 4.10 3 +!|=============================================================================| +!| Starting integration for process 'drellyNLO' part 'virtual' +!| Integrate: iterations = 10:50000:"gw", 3:100000 +!| Integrator: 10 chains, 17 channels, 7 dimensions +!| Integrator: Write grid header and grids to 'drellyNLO.m3.vg2' +!| Integrator: Grid checkpoint after each iteration +!| Integrator: 50000 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. +!| VAMP2: Simple Request Balancing. +!######################################################################## +!# # +!# You are using OneLOop # +!# # +!# for the evaluation of 1-loop scalar 1-, 2-, 3- and 4-point functions # +!# # +!# author: Andreas van Hameren # +!# date: 2018-06-13 # +!# # +!# Please cite # +!# A. van Hameren, # +!# Comput.Phys.Commun. 182 (2011) 2427-2438, arXiv:1007.4716 # +!# A. van Hameren, C.G. Papadopoulos and R. Pittau, # +!# JHEP 0909:106,2009, arXiv:0903.4665 # +!# in publications with results obtained with the help of this program. # +!# # +!######################################################################## +! 1 47393 -1.3397509E+04 2.04E+03 15.23 33.17* 0.11 +! 2 47437 -1.1676951E+04 3.20E+02 2.74 5.97* 0.65 +! 3 45689 -1.1662400E+04 1.30E+02 1.12 2.39* 2.70 +! 4 44687 -1.1399831E+04 9.73E+01 0.85 1.81* 4.13 +! 5 45305 -1.1475761E+04 9.25E+01 0.81 1.72* 5.04 +! 6 43140 -1.1548673E+04 8.91E+01 0.77 1.60* 5.36 +! 7 42884 -1.1740750E+04 8.91E+01 0.76 1.57* 5.04 +! 8 42884 -1.1693272E+04 8.67E+01 0.74 1.53* 5.77 +! 9 43652 -1.1527727E+04 8.36E+01 0.72 1.51* 7.16 +! 10 44164 -1.1594397E+04 8.17E+01 0.70 1.48* 6.83 +!|-----------------------------------------------------------------------------| +! 10 447235 -1.1581138E+04 3.21E+01 0.28 1.85 6.83 1.28 10 +!|-----------------------------------------------------------------------------| +!| VAMP2: Simple Request Balancing. +! 11 94677 -1.1491718E+04 5.63E+01 0.49 1.51 4.88 +! 12 94677 -1.1568062E+04 6.03E+01 0.52 1.61 5.45 +! 13 94677 -1.1612899E+04 5.68E+01 0.49 1.51* 3.49 +!|-----------------------------------------------------------------------------| +! 13 284031 -1.1556700E+04 3.33E+01 0.29 1.54 3.49 1.17 3 +!|=============================================================================| +!| Starting integration for process 'drellyNLO' part 'dglap' +!| Integrate: iterations = 10:5000000:"gw", 3:10000000 +!| Integrator: 10 chains, 17 channels, 8 dimensions +!| Integrator: Write grid header and grids to 'drellyNLO.m4.vg2' +!| Integrator: Grid checkpoint after each iteration +!| Integrator: 5000000 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. +!| VAMP2: Simple Request Balancing. +! 1 4521984 1.1055191E+03 4.32E+01 3.91 83.10* 0.01 +! 2 4325376 1.0553240E+03 5.27E+00 0.50 10.38* 0.24 +! 3 4325376 1.0571633E+03 2.61E+00 0.25 5.13* 0.60 +! 4 4259840 1.0544896E+03 1.98E+00 0.19 3.88* 1.09 +! 5 4325376 1.0536059E+03 1.78E+00 0.17 3.51* 1.35 +! 6 4325376 1.0538225E+03 1.69E+00 0.16 3.34* 1.57 +! 7 4259840 1.0514160E+03 1.65E+00 0.16 3.24* 1.61 +! 8 4390912 1.0548834E+03 1.65E+00 0.16 3.27 1.53 +! 9 4194304 1.0544613E+03 1.61E+00 0.15 3.13* 1.55 +! 10 4390912 1.0549559E+03 1.63E+00 0.15 3.24 1.58 +!|-----------------------------------------------------------------------------| +! 10 43319296 1.0541500E+03 6.20E-01 0.06 3.87 1.58 0.69 10 +!|-----------------------------------------------------------------------------| +!| VAMP2: Simple Request Balancing. +! 11 8755914 1.0540943E+03 1.11E+00 0.10 3.10* 1.20 +! 12 8755914 1.0557883E+03 1.11E+00 0.10 3.10* 1.19 +! 13 8755914 1.0551535E+03 1.11E+00 0.10 3.10 1.26 +!|-----------------------------------------------------------------------------| +! 13 26267742 1.0550115E+03 6.39E-01 0.06 3.10 1.26 0.60 3 +!|=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_pptt_ew.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_pptt_ew.ref (revision 0) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_pptt_ew.ref (revision 8818) @@ -0,0 +1,535 @@ +?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] pr = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21, 22) +[user variable] j = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21, 22) +alpha_power = 0 +alphas_power = 2 +$nlo_correction_type = "EW" +seed = 1 +| Process library 'nlo_pptt_ew_lib': recorded process 'pptt_as2a0' +mult_call_virt = 1.000000000000E-01 +| Integrate: current process library needs compilation +| Process library 'nlo_pptt_ew_lib': compiling ... +| Process library 'nlo_pptt_ew_lib': writing makefile +| Process library 'nlo_pptt_ew_lib': removing old files +| Process library 'nlo_pptt_ew_lib': writing driver +| Process library 'nlo_pptt_ew_lib': creating source code +| Process library 'nlo_pptt_ew_lib': compiling sources +| Process library 'nlo_pptt_ew_lib': linking +| Process library 'nlo_pptt_ew_lib': loading +| Process library 'nlo_pptt_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 pptt_as2a0: +| 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 'pptt_as2a0.i1.phs' +| Phase space: generating configuration ... +| Phase space: ... success. +| Phase space: writing configuration file 'pptt_as2a0.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]: 'pptt_as2a0' +| Library name = 'nlo_pptt_ew_lib' +| Process index = 1 +| Process components: +| 1: 'pptt_as2a0_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl:A => t, tbar [openloops] +| 2: 'pptt_as2a0_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl:A, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl:A => t, tbar, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl:A [openloops], [real] +| 3: 'pptt_as2a0_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl:A => t, tbar [openloops], [virtual] +| 4: 'pptt_as2a0_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl:A => t, tbar [inactive], [subtraction] +| 5: 'pptt_as2a0_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl:A => t, tbar [openloops], [dglap] +| ------------------------------------------------------------------------ +| Phase space: 5 channels, 2 dimensions +| Phase space: found 5 channels, collected in 2 groves. +| Phase space: Using 9 equivalences between channels. +| Phase space: wood +| Phase space: 5 channels, 5 dimensions +| Phase space: found 5 channels, collected in 2 groves. +| Phase space: Using 9 equivalences between channels. +| Phase space: wood +| Phase space: 5 channels, 2 dimensions +| Phase space: found 5 channels, collected in 2 groves. +| Phase space: Using 9 equivalences between channels. +| Phase space: wood +| Phase space: 5 channels, 3 dimensions +| Phase space: found 5 channels, collected in 2 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 'pptt_as2a0' part 'born' +| Integrate: iterations = 1:1000:"gw" +| Integrator: 2 chains, 5 channels, 4 dimensions +| Integrator: Using VAMP2 channel equivalences +| Integrator: Write grid header and grids to 'pptt_as2a0.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 'pptt_as2a0.m1.vg2'. +| VAMP2: set chain: use chained weights. + 1 810 2.8637550E+05 9.41E+04 32.87 9.35* 1.10 +|-----------------------------------------------------------------------------| + 1 810 2.8637550E+05 9.41E+04 32.87 9.35 1.10 +|=============================================================================| +| Starting integration for process 'pptt_as2a0' part 'real' +| Integrate: iterations = 1:1000:"gw" +| Integrator: 2 chains, 5 channels, 7 dimensions +| Integrator: Using VAMP2 channel equivalences +| Integrator: Write grid header and grids to 'pptt_as2a0.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 'pptt_as2a0.m2.vg2'. +| VAMP2: set chain: use chained weights. + 1 1001 -2.4141809E+03 6.67E+02 27.64 8.75* 1.09 +|-----------------------------------------------------------------------------| + 1 1001 -2.4141809E+03 6.67E+02 27.64 8.75 1.09 +|=============================================================================| +| Starting integration for process 'pptt_as2a0' part 'virtual' +| Integrate: iterations = 1:100:"gw" +| Integrator: 2 chains, 5 channels, 4 dimensions +| Integrator: Using VAMP2 channel equivalences +| Integrator: Write grid header and grids to 'pptt_as2a0.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 'pptt_as2a0.m3.vg2'. +| VAMP2: set chain: use chained weights. + 1 88 -5.3275767E+03 3.28E+03 61.63 5.78* 5.71 +|-----------------------------------------------------------------------------| + 1 88 -5.3275767E+03 3.28E+03 61.63 5.78 5.71 +|=============================================================================| +| Starting integration for process 'pptt_as2a0' part 'dglap' +| Integrate: iterations = 1:1000:"gw" +| Integrator: 2 chains, 5 channels, 5 dimensions +| Integrator: Using VAMP2 channel equivalences +| Integrator: Write grid header and grids to 'pptt_as2a0.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 'pptt_as2a0.m4.vg2'. +| VAMP2: set chain: use chained weights. + 1 992 9.6063155E+02 3.79E+02 39.43 12.42* 0.75 +|-----------------------------------------------------------------------------| + 1 992 9.6063155E+02 3.79E+02 39.43 12.42 0.75 +|=============================================================================| +| Integrate: sum of all components +|=============================================================================| +| It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | +|=============================================================================| + 1 0 2.7959438E+05 9.42E+04 33.69 0.00* 1.07 +| NLO Correction: [O(alpha_s+1)/O(alpha_s)] +| ( -2.37 +- 1.41 ) % +|=============================================================================| +alpha_power = 1 +alphas_power = 1 +seed = 1 +| Process library 'nlo_pptt_ew_lib': unloading +| Process library 'nlo_pptt_ew_lib': open +| Process library 'nlo_pptt_ew_lib': recorded process 'pptt_as1a1' +mult_call_virt = 1.000000000000E-01 +| Integrate: current process library needs compilation +| Process library 'nlo_pptt_ew_lib': compiling ... +| Process library 'nlo_pptt_ew_lib': writing makefile +| Process library 'nlo_pptt_ew_lib': removing old files +| Process library 'nlo_pptt_ew_lib': writing driver +| Process library 'nlo_pptt_ew_lib': creating source code +| Process library 'nlo_pptt_ew_lib': compiling sources +| Process library 'nlo_pptt_ew_lib': linking +| Process library 'nlo_pptt_ew_lib': loading +| Process library 'nlo_pptt_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 pptt_as1a1: +| 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 'pptt_as1a1.i1.phs' +| Phase space: generating configuration ... +| Phase space: ... success. +| Phase space: writing configuration file 'pptt_as1a1.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]: 'pptt_as1a1' +| Library name = 'nlo_pptt_ew_lib' +| Process index = 2 +| Process components: +| 1: 'pptt_as1a1_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl:A => t, tbar [openloops] +| 2: 'pptt_as1a1_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl:A, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl:A => t, tbar, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl:A [openloops], [real] +| 3: 'pptt_as1a1_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl:A => t, tbar [openloops], [virtual] +| 4: 'pptt_as1a1_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl:A => t, tbar [inactive], [subtraction] +| 5: 'pptt_as1a1_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl:A => t, tbar [openloops], [dglap] +| ------------------------------------------------------------------------ +| Phase space: 5 channels, 2 dimensions +| Phase space: found 5 channels, collected in 2 groves. +| Phase space: Using 9 equivalences between channels. +| Phase space: wood +| Phase space: 5 channels, 5 dimensions +| Phase space: found 5 channels, collected in 2 groves. +| Phase space: Using 9 equivalences between channels. +| Phase space: wood +| Phase space: 5 channels, 2 dimensions +| Phase space: found 5 channels, collected in 2 groves. +| Phase space: Using 9 equivalences between channels. +| Phase space: wood +| Phase space: 5 channels, 3 dimensions +| Phase space: found 5 channels, collected in 2 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 'pptt_as1a1' part 'born' +| Integrate: iterations = 1:1000:"gw" +| Integrator: 2 chains, 5 channels, 4 dimensions +| Integrator: Using VAMP2 channel equivalences +| Integrator: Write grid header and grids to 'pptt_as1a1.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 'pptt_as1a1.m1.vg2'. +| VAMP2: set chain: use chained weights. + 1 810 1.4427615E+03 3.35E+02 23.19 6.60* 1.65 +|-----------------------------------------------------------------------------| + 1 810 1.4427615E+03 3.35E+02 23.19 6.60 1.65 +|=============================================================================| +| Starting integration for process 'pptt_as1a1' part 'real' +| Integrate: iterations = 1:1000:"gw" +| Integrator: 2 chains, 5 channels, 7 dimensions +| Integrator: Using VAMP2 channel equivalences +| Integrator: Write grid header and grids to 'pptt_as1a1.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 'pptt_as1a1.m2.vg2'. +| VAMP2: set chain: use chained weights. + 1 1000 2.9705353E+03 1.08E+03 36.33 11.49* 0.87 +|-----------------------------------------------------------------------------| + 1 1000 2.9705353E+03 1.08E+03 36.33 11.49 0.87 +|=============================================================================| +| Starting integration for process 'pptt_as1a1' part 'virtual' +| Integrate: iterations = 1:100:"gw" +| Integrator: 2 chains, 5 channels, 4 dimensions +| Integrator: Using VAMP2 channel equivalences +| Integrator: Write grid header and grids to 'pptt_as1a1.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 'pptt_as1a1.m3.vg2'. +| VAMP2: set chain: use chained weights. + 1 101 -3.8202422E+02 3.48E+02 91.17 9.16* 5.50 +|-----------------------------------------------------------------------------| + 1 101 -3.8202422E+02 3.48E+02 91.17 9.16 5.50 +|=============================================================================| +| Starting integration for process 'pptt_as1a1' part 'dglap' +| Integrate: iterations = 1:1000:"gw" +| Integrator: 2 chains, 5 channels, 5 dimensions +| Integrator: Using VAMP2 channel equivalences +| Integrator: Write grid header and grids to 'pptt_as1a1.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 'pptt_as1a1.m4.vg2'. +| VAMP2: set chain: use chained weights. + 1 928 5.3722743E+01 2.38E+02 443.54 135.12* 1.32 +|-----------------------------------------------------------------------------| + 1 928 5.3722743E+01 2.38E+02 443.54 135.12 1.32 +|=============================================================================| +| Integrate: sum of all components +|=============================================================================| +| It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | +|=============================================================================| + 1 0 4.0849953E+03 1.21E+03 29.53 0.00* 0.94 +| NLO Correction: [O(alpha_s+1)/O(alpha_s)] +| ( 183.14 +- 90.86 ) % +|=============================================================================| +[user variable] pr = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 22) +alpha_power = 2 +alphas_power = 0 +seed = 1 +| Process library 'nlo_pptt_ew_lib': unloading +| Process library 'nlo_pptt_ew_lib': open +| Process library 'nlo_pptt_ew_lib': recorded process 'pptt_as0a2' +mult_call_virt = 1.000000000000E-01 +| Integrate: current process library needs compilation +| Process library 'nlo_pptt_ew_lib': compiling ... +| Process library 'nlo_pptt_ew_lib': writing makefile +| Process library 'nlo_pptt_ew_lib': removing old files +| Process library 'nlo_pptt_ew_lib': writing driver +| Process library 'nlo_pptt_ew_lib': creating source code +| Process library 'nlo_pptt_ew_lib': compiling sources +| Process library 'nlo_pptt_ew_lib': linking +| Process library 'nlo_pptt_ew_lib': loading +| Process library 'nlo_pptt_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 pptt_as0a2: +| 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 'pptt_as0a2.i1.phs' +| Phase space: generating configuration ... +| Phase space: ... success. +| Phase space: writing configuration file 'pptt_as0a2.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]: 'pptt_as0a2' +| Library name = 'nlo_pptt_ew_lib' +| Process index = 3 +| Process components: +| 1: 'pptt_as0a2_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => t, tbar [openloops] +| 2: 'pptt_as0a2_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A => t, tbar, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:A [openloops], [real] +| 3: 'pptt_as0a2_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => t, tbar [openloops], [virtual] +| 4: 'pptt_as0a2_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => t, tbar [inactive], [subtraction] +| 5: 'pptt_as0a2_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => t, tbar [openloops], [dglap] +| ------------------------------------------------------------------------ +| Phase space: 5 channels, 2 dimensions +| Phase space: found 5 channels, collected in 2 groves. +| Phase space: Using 9 equivalences between channels. +| Phase space: wood +| Phase space: 5 channels, 5 dimensions +| Phase space: found 5 channels, collected in 2 groves. +| Phase space: Using 9 equivalences between channels. +| Phase space: wood +| Phase space: 5 channels, 2 dimensions +| Phase space: found 5 channels, collected in 2 groves. +| Phase space: Using 9 equivalences between channels. +| Phase space: wood +| Phase space: 5 channels, 3 dimensions +| Phase space: found 5 channels, collected in 2 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 'pptt_as0a2' part 'born' +| Integrate: iterations = 1:1000:"gw" +| Integrator: 2 chains, 5 channels, 4 dimensions +| Integrator: Using VAMP2 channel equivalences +| Integrator: Write grid header and grids to 'pptt_as0a2.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 'pptt_as0a2.m1.vg2'. +| VAMP2: set chain: use chained weights. + 1 810 1.3139089E+03 4.81E+02 36.65 10.43* 0.96 +|-----------------------------------------------------------------------------| + 1 810 1.3139089E+03 4.81E+02 36.65 10.43 0.96 +|=============================================================================| +| Starting integration for process 'pptt_as0a2' part 'real' +| Integrate: iterations = 1:1000:"gw" +| Integrator: 2 chains, 5 channels, 7 dimensions +| Integrator: Using VAMP2 channel equivalences +| Integrator: Write grid header and grids to 'pptt_as0a2.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 'pptt_as0a2.m2.vg2'. +| VAMP2: set chain: use chained weights. + 1 1002 -1.2574021E+01 8.18E+00 65.07 20.60* 0.81 +|-----------------------------------------------------------------------------| + 1 1002 -1.2574021E+01 8.18E+00 65.07 20.60 0.81 +|=============================================================================| +| Starting integration for process 'pptt_as0a2' part 'virtual' +| Integrate: iterations = 1:100:"gw" +| Integrator: 2 chains, 5 channels, 4 dimensions +| Integrator: Using VAMP2 channel equivalences +| Integrator: Write grid header and grids to 'pptt_as0a2.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 'pptt_as0a2.m3.vg2'. +| VAMP2: set chain: use chained weights. + 1 100 -3.2378830E+01 2.45E+01 75.71 7.57* 6.55 +|-----------------------------------------------------------------------------| + 1 100 -3.2378830E+01 2.45E+01 75.71 7.57 6.55 +|=============================================================================| +| Starting integration for process 'pptt_as0a2' part 'dglap' +| Integrate: iterations = 1:1000:"gw" +| Integrator: 2 chains, 5 channels, 5 dimensions +| Integrator: Using VAMP2 channel equivalences +| Integrator: Write grid header and grids to 'pptt_as0a2.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 'pptt_as0a2.m4.vg2'. +| VAMP2: set chain: use chained weights. + 1 928 2.5348357E+00 9.91E-01 39.09 11.91* 0.91 +|-----------------------------------------------------------------------------| + 1 928 2.5348357E+00 9.91E-01 39.09 11.91 0.91 +|=============================================================================| +| Integrate: sum of all components +|=============================================================================| +| It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | +|=============================================================================| + 1 0 1.2714909E+03 4.82E+02 37.92 0.00* 0.93 +| NLO Correction: [O(alpha_s+1)/O(alpha_s)] +| ( -3.23 +- 2.30 ) % +|=============================================================================| +| There were no errors and 3 warning(s). +| WHIZARD run finished. +|=============================================================================| Index: trunk/share/tests/ext_tests_nlo/nlo_pptt_ew.sin =================================================================== --- trunk/share/tests/ext_tests_nlo/nlo_pptt_ew.sin (revision 0) +++ trunk/share/tests/ext_tests_nlo/nlo_pptt_ew.sin (revision 8818) @@ -0,0 +1,33 @@ +include("nlo_settings_ew.sin") + +alias pr= u:U:d:D:s:S:c:C:b:B:g:A +alias j= u:U:d:D:s:S:c:C:b:B:g:A + +alpha_power = 0 +alphas_power = 2 + + +scale = sum sqrt(Pt^2 + M^2)/2 [t:T] + sum Pt/2 [j] +$nlo_correction_type = "EW" +seed=1 +process pptt_as2a0 = pr, pr => t,T {nlo_calculation = full} + +integrate (pptt_as2a0) { iterations = 1:1000:"gw" mult_call_virt = 0.1} + +alpha_power = 1 +alphas_power = 1 + +seed=1 +process pptt_as1a1 = pr, pr => t,T {nlo_calculation = full} + +integrate (pptt_as1a1) { iterations = 1:1000:"gw" mult_call_virt = 0.1} + +alias pr= u:U:d:D:s:S:c:C:b:B:A + +alpha_power = 2 +alphas_power = 0 + +seed=1 +process pptt_as0a2 = pr, pr => t,T {nlo_calculation = full} + +integrate (pptt_as0a2) { iterations = 1:1000:"gw" mult_call_virt = 0.1} Index: trunk/ChangeLog =================================================================== --- trunk/ChangeLog (revision 8817) +++ trunk/ChangeLog (revision 8818) @@ -1,2303 +1,2308 @@ ChangeLog -- Summary of changes to the WHIZARD package Use svn log to see detailed changes. Version 3.0.2+ +2022-03-31 + NLO EW processes with massless leptons and jets (i.e. + jet clustering and photon recombination) supported + NLO EW for massive initial leptons validated + 2022-03-27 Complete implementation/validation of NLL electron PDFs 2022-02-22 Bug fix: correct normalization for CIRCE2+EPA+polarization 2022-02-21 WHIZARD core now uses Fortran modules and submodules 2022-01-27 Infrastructure for POWHEG matching for hadron collisions 2021-12-16 Event files can be written/read also for decay processes Implementation of running QED coupling alpha 2021-12-10 Independent variations of renormalization/factorization scale ################################################################## 2021-11-23 RELEASE: version 3.0.2 2021-11-19 Support for a wide class of mixed NLO QCD/EW processes 2021-11-18 Add pp processes for NLO EW corrections to testsuite 2021-11-11 Output numerically critical values with LCIO 2.17+ as double 2021-11-05 Minor refactoring on phase space points and kinematics 2021-10-21 NLO (QCD) differential distributions supported for full lepton collider setup: polarization, QED ISR, beamstrahlung 2021-10-15 SINDARIN now has a sum and product function of expressions, SINDARIN supports observables defined on full (sub)events First application: transverse mass Bug fix: 2HDM did not allow H+, H- as external particles 2021-10-14 CT18 PDFs included (NLO, NNLO) 2021-09-30 Bug fix: keep non-recombined photons in the event record 2021-09-13 Modular NLO event generation with real partition 2021-08-20 Bug fix: correctly reading in NLO fixed order events 2021-08-06 Generalize optional partitioning of the NLO real phase space ################################################################## 2021-07-08 RELEASE: version 3.0.1 2021-07-06 MPI parallelization now comes with two incarnations: - standard MPI parallelization ("simple", default) - MPI with load balancer ("load") 2021-07-05 Bug fix for C++17 default compilers w/ HepMC3/ROOT interface 2021-07-02 Improvement for POWHEG matching: - implement massless recoil case - enable reading in existing POWHEG grids - support kinematic cuts at generator level 2021-07-01 Distinguish different cases of photons in NLO EW corrections 2021-06-21 Option to keep negative PDF entries or set them zero 2021-05-31 Full LCIO MC production files can be properly recasted 2021-05-24 Use defaults for UFO models without propagators.py 2021-05-21 Bug fix: prevent invalid code for UFO models containing hyphens 2021-05-20 UFO files with scientific notation float constants allowed UFO files: max. n-arity of vertices bound by process multiplicity ################################################################## 2021-04-27 RELEASE: version 3.0.0 2021-04-20 Minimal required OCaml version is now 4.05.0. Bug fix for tau polarization from stau decays 2021-04-19 NLO EW splitting functions and collinear remnants completed Photon recombination implemented 2021-04-14 Bug fix for vertices/status codes with HepMC2/3 event format 2021-04-08 Correct Lorentz statistics for UFO model with Majorana fermions 2021-04-06 Bug fix for rare script failure in system_dependencies.f90.in Kappa factor for quartic Higgs coupling in SM_ac(_CKM) model 2021-04-04 Support for UFO extensions in SMEFTSim 3.0 2021-02-25 Enable VAMP and VAMP2 channel equivalences for NLO integrations 2021-02-04 Bug fix if user does not set a prefix at configuration 2020-12-10 Generalize NLO calculations to non-CMS lab frames 2020-12-08 Bug fix in expanded p-wave form factor for top threshold 2020-12-06 Patch for macOS Big Sur shared library handling due to libtool; the patch also demands gcc/gfortran 11.0/10.3/9.4/8.5 2020-12-04 O'Mega only inserts non-vanishing couplings from UFO models 2020-11-21 Bug fix for fractional hypercharges in UFO models 2020-11-11 Enable PYTHIA6 settings for eh collisions (enable-pythia6_eh) 2020-11-09 Correct flavor assignment for NLO fixed-order events 2020-11-05 Bug fix for ISR handler not working with unstable particles 2020-10-08 Bug fix in LHAPDF interface for photon PDFs 2020-10-07 Bug fix for structure function setup with asymmetric beams 2020-10-02 Python/Cython layer for WHIZARD API 2020-09-30 Allow mismatches of Python and name attributes in UFO models 2020-09-26 Support for negative PDG particles from certain UFO models 2020-09-24 Allow for QNUMBERS blocks in BSM SLHA files 2020-09-22 Full support for compilation with clang(++) on Darwin/macOS More documentation in the manual Minor clean-ups 2020-09-16 Bug fix enables reading LCIO events with LCIO v2.15+ ################################################################## 2020-09-16 RELEASE: version 2.8.5 2020-09-11 Bug fix for H->tau tau transverse polarization with PYTHIA6 (thanks to Junping Tian / Akiya Miyamoto) 2020-09-09 Fix a long standing bug (since 2.0) in the calculation of color factors when particles of different color were combined in a particle class. NB: O'Mega never produced a wrong number, it only declared all processes as invalid. 2020-09-08 Enable Openloops matrix element equivalences for optimization 2020-09-02 Compatibility fix for PYTHIA v8.301+ interface 2020-09-01 Support exclusive jet clustering in ee for Fastjet interface ################################################################## 2020-08-30 RELEASE: version 3.0.0_beta 2020-08-27 Major revision of NLO distributions and events for processes with structure functions: - Use parton momenta/flavors (instead of beams) for events - Bug fix for Lorentz boosts and Lorentz frames of momenta - Bug fix: apply cuts to virtual NLO component in correct frame - Correctly assign ISR radiation momenta in data structures - Refactoring on quantum numbers for NLO event data structures - Functional tests for hadron collider NLO distributions - many minor bug fixes regarding NLO hadron collider physics 2020-08-11 Bug fix for linking problem with OpenMPI 2020-08-07 New WHIZARD API: WHIZARD can be externally linked as a library, added examples for Fortran, C, C++ programs ################################################################## 2020-07-08 RELEASE: version 2.8.4 2020-07-07 Bug fix: steering of UFO Majorana models from WHIZARD ################################################################## 2020-07-06 Combined integration also for hadron collider processes at NLO 2020-07-05 Bug fix: correctly steer e+e- FastJet clustering algorithms Major revision of NLO differential distributions and events: - Correctly assign quantum numbers to NLO fixed-order events - Correctly assign weights to NLO fixed-order events for combined simulation - Cut all NLO fixed-order subevents in event groups individually - Only allow "sigma" normalization for NLO fixed-order events - Use correct PDF setup for NLO counter events - Several technical fixes and updates of the NLO testsuite ################################################################## 2020-07-03 RELEASE: version 2.8.3 2020-07-02 Feature-complete UFO implementation for Majorana fermions 2020-06-22 Running width scheme supported for O'Mega matrix elements 2020-06-20 Adding H-s-s coupling to SM_Higgs(_CKM) models 2020-06-17 Completion of ILC 2->6 fermion extended test suite 2020-06-15 Bug fix: PYTHIA6/Tauola, correctly assign tau spins for stau decays 2020-06-09 Bug fix: correctly update calls for additional VAMP/2 iterations Bug fix: correct assignment for tau spins from PYTHIA6 interface 2020-06-04 Bug fix: cascades2 tree merge with empty subtree(s) 2020-05-31 Switch $epa_mode for different EPA implementations 2020-05-26 Bug fix: spin information transferred for resonance histories 2020-04-13 HepMC: correct weighted events for non-xsec event normalizations 2020-04-04 Improved HepMC3 interface: HepMC3 Root/RootTree interface 2020-03-24 ISR: Fix on-shell kinematics for events with ?isr_handler=true (set ?isr_handler_keep_mass=false for old behavior) 2020-03-11 Beam masses are correctly passed to hard matrix element for CIRCE2 EPA with polarized beams: double-counting corrected ################################################################## 2020-03-03 RELEASE: version 3.0.0_alpha 2020-02-25 Bug fix: Scale and alphas can be retrieved from internal event format to external formats 2020-02-17 Bug fix: ?keep_failed_events now forces output of actual event data Bug fix: particle-set reconstruction (rescanning events w/o radiation) 2020-01-28 Bug fix for left-over EPA parameter epa_e_max (replaced by epa_q_max) 2020-01-23 Bug fix for real components of NLO QCD 2->1 processes 2020-01-22 Bug fix: correct random number sequencing during parallel MPI event generation with rng_stream 2020-01-21 Consistent distribution of events during parallel MPI event generation 2020-01-20 Bug fix for configure setup for automake v1.16+ 2020-01-18 General SLHA parameter files for UFO models supported 2020-01-08 Bug fix: correctly register RECOLA processes with flavor sums 2019-12-19 Support for UFO customized propagators O'Mega unit tests for fermion-number violating interactions 2019-12-10 For distribution building: check for graphviz/dot version 2.40 or newer 2019-11-21 Bug fix: alternate setups now work correctly Infrastructure for accessing alpha_QED event-by-event Guard against tiny numbers that break ASCII event output Enable inverse hyperbolic functions as SINDARIN observables Remove old compiler bug workarounds 2019-11-20 Allow quoted -e argument, implemented -f option 2019-11-19 Bug fix: resonance histories now work also with UFO models Fix in numerical precision of ASCII VAMP2 grids 2019-11-06 Add squared matrix elements to the LCIO event header 2019-11-05 Do not include RNG state in MD5 sum for CIRCE1/2 2019-11-04 Full CIRCE2 ILC 250 and 500 GeV beam spectra added Minor update on LCIO event header information 2019-10-30 NLO QCD for final states completed When using Openloops, v2.1.1+ mandatory 2019-10-25 Binary grid files for VAMP2 integrator ################################################################## 2019-10-24 RELEASE: version 2.8.2 2019-10-20 Bug fix for HepMC linker flags 2019-10-19 Support for spin-2 particles from UFO files 2019-09-27 LCIO event format allows rescan and alternate weights 2019-09-24 Compatibility fix for OCaml v4.08.0+ ################################################################## 2019-09-21 RELEASE: version 2.8.1 2019-09-19 Carriage return characters in UFO models can be parsed Mathematica symbols in UFO models possible Unused/undefined parameters in UFO models handled 2019-09-13 New extended NLO test suite for ee and pp processes 2019-09-09 Photon isolation (separation of perturbative and fragmentation part a la Frixione) 2019-09-05 Major progress on NLO QCD for hadron collisions: - correctly assign flavor structures for alpha regions - fix crossing of particles for initial state splittings - correct assignment for PDF factors for real subtractions - fix kinematics for collinear splittings - bug fix for integrated virtual subtraction terms 2019-09-03 b and c jet selection in cuts and analysis 2019-08-27 Support for Intel MPI 2019-08-20 Complete (preliminary) HepMC3 support (incl. backwards HepMC2 write/read mode) 2019-08-08 Bug fix: handle carriage returns in UFO files (non-Unix OS) ################################################################## 2019-08-07 RELEASE: version 2.8.0 2019-07-31 Complete WHIZARD UFO interface: - general Lorentz structures - matrix element support for general color factors - missing features: Majorana fermions and SLHA 2019-07-20 Make WHIZARD compatible with OCaml 4.08.0+ 2019-07-19 Fix version testing for LHAPDF 6.2.3 and newer Minimal required OCaml version is now 4.02.3. 2019-04-18 Correctly generate ordered FKS tuples for alpha regions from all possible underlying Born processes 2019-04-08 Extended O'Mega/Recola matrix element test suite 2019-03-29 Correct identical particle symmetry factors for FKS subtraction 2019-03-28 Correct assertion of spin-correlated matrix elements for hadron collisions 2019-03-27 Bug fix for cut-off parameter delta_i for collinear plus/minus regions ################################################################## 2019-03-27 RELEASE: version 2.7.1 2019-02-19 Further infrastructure for HepMC3 interface (v3.01.00) 2019-02-07 Explicit configure option for using debugging options Bug fix for performance by removing unnecessary debug operations 2019-01-29 Bug fix for DGLAP remnants with cut-off parameter delta_i 2019-01-24 Radiative decay neu2 -> neu1 A added to MSSM_Hgg model ################################################################## 2019-01-21 RELEASE: version 2.7.0 2018-12-18 Support RECOLA for integrated und unintegrated subtractions 2018-12-11 FCNC top-up sector in model SM_top_anom 2018-12-05 Use libtirpc instead of SunRPC on Arch Linux etc. 2018-11-30 Display rescaling factor for weighted event samples with cuts 2018-11-29 Reintroduce check against different masses in flavor sums Bug fix for wrong couplings in the Littlest Higgs model(s) 2018-11-22 Bug fix for rescanning events with beam structure 2018-11-09 Major refactoring of internal process data 2018-11-02 PYTHIA8 interface 2018-10-29 Flat phase space parametrization with RAMBO (on diet) implemented 2018-10-17 Revise extended test suite 2018-09-27 Process container for RECOLA processes 2018-09-15 Fixes by M. Berggren for PYTHIA6 interface 2018-09-14 First fixes after HepForge modernization ################################################################## 2018-08-23 RELEASE: version 2.6.4 2018-08-09 Infrastructure to check colored subevents 2018-07-10 Infrastructure for running WHIZARD in batch mode 2018-07-04 MPI available from distribution tarball 2018-06-03 Support Intel Fortran Compiler under MAC OS X 2018-05-07 FKS slicing parameter delta_i (initial state) implementend 2018-05-03 Refactor structure function assignment for NLO 2018-05-02 FKS slicing parameter xi_cut, delta_0 implemented 2018-04-20 Workspace subdirectory for process integration (grid/phs files) Packing/unpacking of files at job end/start Exporting integration results from scan loops 2018-04-13 Extended QCD NLO test suite 2018-04-09 Bug fix for Higgs Singlet Extension model 2018-04-06 Workspace subdirectory for process generation and compilation --job-id option for creating job-specific names 2018-03-20 Bug fix for color flow matching in hadron collisions with identical initial state quarks 2018-03-08 Structure functions quantum numbers correctly assigned for NLO 2018-02-24 Configure setup includes 'pgfortran' and 'flang' 2018-02-21 Include spin-correlated matrix elements in interactions 2018-02-15 Separate module for QED ISR structure functions ################################################################## 2018-02-10 RELEASE: version 2.6.3 2018-02-08 Improvements in memory management for PS generation 2018-01-31 Partial refactoring: quantum number assigment NLO Initial-state QCD splittings for hadron collisions 2018-01-25 Bug fix for weighted events with VAMP2 2018-01-17 Generalized interface for Recola versions 1.3+ and 2.1+ 2018-01-15 Channel equivalences also for VAMP2 integrator 2018-01-12 Fix for OCaml compiler 4.06 (and newer) 2017-12-19 RECOLA matrix elements with flavor sums can be integrated 2017-12-18 Bug fix for segmentation fault in empty resonance histories 2017-12-16 Fixing a bug in PYTHIA6 PYHEPC routine by omitting CMShowers from transferral between PYTHIA and WHIZARD event records 2017-12-15 Event index for multiple processes in event file correct ################################################################## 2017-12-13 RELEASE: version 2.6.2 2017-12-07 User can set offset in event numbers 2017-11-29 Possibility to have more than one RECOLA process in one file 2017-11-23 Transversal/mixed (and unitarized) dim-8 operators 2017-11-16 epa_q_max replaces epa_e_max (trivial factor 2) 2017-11-15 O'Mega matrix element compilation silent now 2017-11-14 Complete expanded P-wave form factor for top threshold 2017-11-10 Incoming particles can be accessed in SINDARIN 2017-11-08 Improved handling of resonance insertion, additional parameters 2017-11-04 Added Higgs-electron coupling (SM_Higgs) ################################################################## 2017-11-03 RELEASE: version 2.6.1 2017-10-20 More than 5 NLO components possible at same time 2017-10-19 Gaussian cutoff for shower resonance matching 2017-10-12 Alternative (more efficient) method to generate phase space file 2017-10-11 Bug fix for shower resonance histories for processes with multiple components 2017-09-25 Bug fix for process libraries in shower resonance histories 2017-09-21 Correctly generate pT distribution for EPA remnants 2017-09-20 Set branching ratios for unstable particles also by hand 2017-09-14 Correctly generate pT distribution for ISR photons ################################################################## 2017-09-08 RELEASE: version 2.6.0 2017-09-05 Bug fix for initial state NLO QCD flavor structures Real and virtual NLO QCD hadron collider processes work with internal interactions 2017-09-04 Fully validated MPI integration and event generation 2017-09-01 Resonance histories for shower: full support Bug fix in O'Mega model constraints O'Mega allows to output a parsable form of the DAG 2017-08-24 Resonance histories in events for transferral to parton shower (e.g. in ee -> jjjj) 2017-08-01 Alpha version of HepMC v3 interface (not yet really functional) 2017-07-31 Beta version for RECOLA OLP support 2017-07-06 Radiation generator fix for LHC processes 2017-06-30 Fix bug for NLO with structure functions and/or polarization 2017-06-23 Collinear limit for QED corrections works 2017-06-17 POWHEG grids generated already during integration 2017-06-12 Soft limit for QED corrections works 2017-05-16 Beta version of full MPI parallelization (VAMP2) Check consistency of POWHEG grid files Logfile config-summary.log for configure summary 2017-05-12 Allow polarization in top threshold 2017-05-09 Minimal demand automake 1.12.2 Silent rules for make procedures 2017-05-07 Major fix for POWHEG damping Correctly initialize FKS ISR phasespace ################################################################## 2017-05-06 RELEASE: version 2.5.0 2017-05-05 Full UFO support (SM-like models) Fixed-beam ISR FKS phase space 2017-04-26 QED splittings in radiation generator 2017-04-10 Retire deprecated O'Mega vertex cache files ################################################################## 2017-03-24 RELEASE: version 2.4.1 2017-03-16 Distinguish resonance charge in phase space channels Keep track of resonance histories in phase space Complex mass scheme default for OpenLoops amplitudes 2017-03-13 Fix helicities for polarized OpenLoops calculations 2017-03-09 Possibility to advance RNG state in rng_stream 2017-03-04 General setup for partitioning real emission phase space 2017-03-06 Bug fix on rescan command for converting event files 2017-02-27 Alternative multi-channel VEGAS implementation VAMP2: serial backbone for MPI setup Smoothstep top threshold matching 2017-02-25 Single-beam structure function with s-channel mapping supported Safeguard against invalid process libraries 2017-02-16 Radiation generator for photon emission 2017-02-10 Fixes for NLO QCD processes (color correlations) 2017-01-16 LCIO variable takes precedence over LCIO_DIR 2017-01-13 Alternative random number generator rng_stream (cf. L'Ecuyer et al.) 2017-01-01 Fix for multi-flavor BLHA tree matrix elements 2016-12-31 Grid path option for VAMP grids 2016-12-28 Alpha version of Recola OLP support 2016-12-27 Dalitz plots for FKS phase space 2016-12-14 NLO multi-flavor events possible 2016-12-09 LCIO event header information added 2016-12-02 Alpha version of RECOLA interface Bug fix for generator status in LCIO ################################################################## 2016-11-28 RELEASE: version 2.4.0 2016-11-24 Bug fix for OpenLoops interface: EW scheme is set by WHIZARD Bug fixes for top threshold implementation 2016-11-11 Refactoring of dispatching 2016-10-18 Bug fix for LCIO output 2016-10-10 First implementation for collinear soft terms 2016-10-06 First full WHIZARD models from UFO files 2016-10-05 WHIZARD does not support legacy gcc 4.7.4 any longer 2016-09-30 Major refactoring of process core and NLO components 2016-09-23 WHIZARD homogeneous entity: discarding subconfigures for CIRCE1/2, O'Mega, VAMP subpackages; these are reconstructable by script projectors 2016-09-06 Introduce main configure summary 2016-08-26 Fix memory leak in event generation ################################################################## 2016-08-25 RELEASE: version 2.3.1 2016-08-19 Bug fix for EW-scheme dependence of gluino propagators 2016-08-01 Beta version of complex mass scheme support 2016-07-26 Fix bug in POWHEG damping for the matching ################################################################## 2016-07-21 RELEASE: version 2.3.0 2016-07-20 UFO file support (alpha version) in O'Mega 2016-07-13 New (more) stable of WHIZARD GUI Support for EW schemes for OpenLoops Factorized NLO top decays for threshold model 2016-06-15 Passing factorization scale to PYTHIA6 Adding charge and neutral observables 2016-06-14 Correcting angular distribution/tweaked kinematics in non-collinear structure functions splittings 2016-05-10 Include (Fortran) TAUOLA/PHOTOS for tau decays via PYTHIA6 (backwards validation of LC CDR/TDR samples) 2016-04-27 Within OpenLoops virtuals: support for Collier library 2016-04-25 O'Mega vertex tables only loaded at first usage 2016-04-21 New CJ15 PDF parameterizations added 2016-04-21 Support for hadron collisions at NLO QCD 2016-04-05 Support for different (parameter) schemes in model files 2016-03-31 Correct transferral of lifetime/vertex from PYTHIA/TAUOLA into the event record 2016-03-21 New internal implementation of polarization via Bloch vectors, remove pointer constructions 2016-03-13 Extension of cascade syntax for processes: exclude propagators/vertices etc. possible 2016-02-24 Full support for OpenLoops QCD NLO matrix elements, inclusion in test suite 2016-02-12 Substantial progress on QCD NLO support 2016-02-02 Automated resonance mapping for FKS subtraction 2015-12-17 New BSM model WZW for diphoton resonances ################################################################## 2015-11-22 RELEASE: version 2.2.8 2015-11-21 Bug fix for fixed-order NLO events 2015-11-20 Anomalous FCNC top-charm vertices 2015-11-19 StdHEP output via HEPEVT/HEPEV4 supported 2015-11-18 Full set of electroweak dim-6 operators included 2015-10-22 Polarized one-loop amplitudes supported 2015-10-21 Fixes for event formats for showered events 2015-10-14 Callback mechanism for event output 2015-09-22 Bypass matrix elements in pure event sample rescans StdHep frozen final version v5.06.01 included internally 2015-09-21 configure option --with-precision to demand 64bit, 80bit, or 128bit Fortran and bind C precision types 2015-09-07 More extensive tests of NLO infrastructure and POWHEG matching 2015-09-01 NLO decay infrastructure User-defined squared matrix elements Inclusive FastJet algorithm plugin Numerical improvement for small boosts ################################################################## 2015-08-11 RELEASE: version 2.2.7 2015-08-10 Infrastructure for damped POWHEG Massive emitters in POWHEG Born matrix elements via BLHA GoSam filters via SINDARIN Minor running coupling bug fixes Fixed-order NLO events 2015-08-06 CT14 PDFs included (LO, NLO, NNLL) 2015-07-07 Revalidation of ILC WHIZARD-PYTHIA event chain Extended test suite for showered events Alpha version of massive FSR for POWHEG 2015-06-09 Fix memory leak in interaction for long cascades Catch mismatch between beam definition and CIRCE2 spectrum 2015-06-08 Automated POWHEG matching: beta version Infrastructure for GKS matching Alpha version of fixed-order NLO events CIRCE2 polarization averaged spectra with explicitly polarized beams 2015-05-12 Abstract matching type: OO structure for matching/merging 2015-05-07 Bug fix in event record WHIZARD-PYTHIA6 transferral Gaussian beam spectra for lepton colliders ################################################################## 2015-05-02 RELEASE: version 2.2.6 2015-05-01 Models for (unitarized) tensor resonances in VBS 2015-04-28 Bug fix in channel weights for event generation. 2015-04-18 Improved event record transfer WHIZARD/PYTHIA6 2015-03-19 POWHEG matching: alpha version ################################################################## 2015-02-27 RELEASE: version 2.2.5 2015-02-26 Abstract types for quantum numbers 2015-02-25 Read-in of StdHEP events, self-tests 2015-02-22 Bug fix for mother-daughter relations in showered/hadronized events 2015-02-20 Projection on polarization in intermediate states 2015-02-13 Correct treatment of beam remnants in event formats (also LC remnants) ################################################################## 2015-02-06 RELEASE: version 2.2.4 2015-02-06 Bug fix in event output 2015-02-05 LCIO event format supported 2015-01-30 Including state matrices in WHIZARD's internal IO Versioning for WHIZARD's internal IO Libtool update from 2.4.3 to 2.4.5 LCIO event output (beta version) 2015-01-27 Progress on NLO integration Fixing a bug for multiple processes in a single event file when using beam event files 2015-01-19 Bug fix for spin correlations evaluated in the rest frame of the mother particle 2015-01-17 Regression fix for statically linked processes from SARAH and FeynRules 2015-01-10 NLO: massive FKS emitters supported (experimental) 2015-01-06 MMHT2014 PDF sets included 2015-01-05 Handling mass degeneracies in auto_decays 2014-12-19 Fixing bug in rescan of event files ################################################################## 2014-11-30 RELEASE: version 2.2.3 2014-11-29 Beta version of LO continuum/NLL-threshold matched top threshold model for e+e- physics 2014-11-28 More internal refactoring: disentanglement of module dependencies 2014-11-21 OVM: O'Mega Virtual Machine, bytecode instructions instead of compiled Fortran code 2014-11-01 Higgs Singlet extension model included 2014-10-18 Internal restructuring of code; half-way WHIZARD main code file disassembled 2014-07-09 Alpha version of NLO infrastructure ################################################################## 2014-07-06 RELEASE: version 2.2.2 2014-07-05 CIRCE2: correlated LC beam spectra and GuineaPig Interface to LC machine parameters 2014-07-01 Reading LHEF for decayed/factorized/showered/ hadronized events 2014-06-25 Configure support for GoSAM/Ninja/Form/QGraf 2014-06-22 LHAPDF6 interface 2014-06-18 Module for automatic generation of radiation and loop infrastructure code 2014-06-11 Improved internal directory structure ################################################################## 2014-06-03 RELEASE: version 2.2.1 2014-05-30 Extensions of internal PDG arrays 2014-05-26 FastJet interface 2014-05-24 CJ12 PDFs included 2014-05-20 Regression fix for external models (via SARAH or FeynRules) ################################################################## 2014-05-18 RELEASE: version 2.2.0 2014-04-11 Multiple components: inclusive process definitions, syntax: process A + B + ... 2014-03-13 Improved PS mappings for e+e- ISR ILC TDR and CLIC spectra included in CIRCE1 2014-02-23 New models: AltH w\ Higgs for exclusion purposes, SM_rx for Dim 6-/Dim-8 operators, SSC for general strong interactions (w/ Higgs), and NoH_rx (w\ Higgs) 2014-02-14 Improved s-channel mapping, new on-shell production mapping (e.g. Drell-Yan) 2014-02-03 PRE-RELEASE: version 2.2.0_beta 2014-01-26 O'Mega: Feynman diagram generation possible (again) 2013-12-16 HOPPET interface for b parton matching 2013-11-15 PRE-RELEASE: version 2.2.0_alpha-4 2013-10-27 LHEF standards 1.0/2.0/3.0 implemented 2013-10-15 PRE-RELEASE: version 2.2.0_alpha-3 2013-10-02 PRE-RELEASE: version 2.2.0_alpha-2 2013-09-25 PRE-RELEASE: version 2.2.0_alpha-1 2013-09-12 PRE-RELEASE: version 2.2.0_alpha 2013-09-03 General 2HDM implemented 2013-08-18 Rescanning/recalculating events 2013-06-07 Reconstruction of complete event from 4-momenta possible 2013-05-06 Process library stacks 2013-05-02 Process stacks 2013-04-29 Single-particle phase space module 2013-04-26 Abstract interface for random number generator 2013-04-24 More object-orientation on modules Midpoint-rule integrator 2013-04-05 Object-oriented integration and event generation 2013-03-12 Processes recasted object-oriented: MEs, scales, structure functions First infrastructure for general Lorentz structures 2013-01-17 Object-orientated reworking of library and process core, more variable internal structure, unit tests 2012-12-14 Update Pythia version to 6.4.27 2012-12-04 Fix the phase in HAZ vertices 2012-11-21 First O'Mega unit tests, some infrastructure 2012-11-13 Bug fix in anom. HVV Lorentz structures ################################################################## 2012-09-18 RELEASE: version 2.1.1 2012-09-11 Model MSSM_Hgg with Hgg and HAA vertices 2012-09-10 First version of implementation of multiple interactions in WHIZARD 2012-09-05 Infrastructure for internal CKKW matching 2012-09-02 C, C++, Python API 2012-07-19 Fixing particle numbering in HepMC format ################################################################## 2012-06-15 RELEASE: version 2.1.0 2012-06-14 Analytical and kT-ordered shower officially released PYTHIA interface officially released 2012-05-09 Intrisince PDFs can be used for showering 2012-05-04 Anomalous Higgs couplings a la hep-ph/9902321 ################################################################## 2012-03-19 RELEASE: version 2.0.7 2012-03-15 Run IDs are available now More event variables in analysis Modified raw event format (compatibility mode exists) 2012-03-12 Bug fix in decay-integration order MLM matching steered completely internally now 2012-03-09 Special phase space mapping for narrow resonances decaying to 4-particle final states with far off-shell intermediate states Running alphas from PDF collaborations with builtin PDFs 2012-02-16 Bug fix in cascades decay infrastructure 2012-02-04 WHIZARD documentation compatible with TeXLive 2011 2012-02-01 Bug fix in FeynRules interface with --prefix flag 2012-01-29 Bug fix with name clash of O'Mega variable names 2012-01-27 Update internal PYTHIA to version 6.4.26 Bug fix in LHEF output 2012-01-21 Catching stricter automake 1.11.2 rules 2011-12-23 Bug fix in decay cascade setup 2011-12-20 Bug fix in helicity selection rules 2011-12-16 Accuracy goal reimplemented 2011-12-14 WHIZARD compatible with TeXLive 2011 2011-12-09 Option --user-target added ################################################################## 2011-12-07 RELEASE: version 2.0.6 2011-12-07 Bug fixes in SM_top_anom Added missing entries to HepMC format 2011-12-06 Allow to pass options to O'Mega Bug fix for HEPEVT block for showered/hadronized events 2011-12-01 Reenabled user plug-in for external code for cuts, structure functions, routines etc. 2011-11-29 Changed model SM_Higgs for Higgs phenomenology 2011-11-25 Supporting a Y, (B-L) Z' model 2011-11-23 Make WHIZARD compatible for MAC OS X Lion/XCode 4 2011-09-25 WHIZARD paper published: Eur.Phys.J. C71 (2011) 1742 2011-08-16 Model SM_QCD: QCD with one EW insertion 2011-07-19 Explicit output channel for dvips avoids printing 2011-07-10 Test suite for WHIZARD unit tests 2011-07-01 Commands for matrix element tests More OpenMP parallelization of kinematics Added unit tests 2011-06-23 Conversion of CIRCE2 from F77 to F90, major clean-up 2011-06-14 Conversion of CIRCE1 from F77 to F90 2011-06-10 OpenMP parallelization of channel kinematics (by Matthias Trudewind) 2011-05-31 RELEASE: version 1.97 2011-05-24 Minor bug fixes: update grids and elsif statement. ################################################################## 2011-05-10 RELEASE: version 2.0.5 2011-05-09 Fixed bug in final state flavor sums Minor improvements on phase-space setup 2011-05-05 Minor bug fixes 2011-04-15 WHIZARD as a precompiled 64-bit binary available 2011-04-06 Wall clock instead of cpu time for time estimates 2011-04-05 Major improvement on the phase space setup 2011-04-02 OpenMP parallelization for helicity loop in O'Mega matrix elements 2011-03-31 Tools for relocating WHIZARD and use in batch environments 2011-03-29 Completely static builds possible, profiling options 2011-03-28 Visualization of integration history 2011-03-27 Fixed broken K-matrix implementation 2011-03-23 Including the GAMELAN manual in the distribution 2011-01-26 WHIZARD analysis can handle hadronized event files 2011-01-17 MSTW2008 and CT10 PDF sets included 2010-12-23 Inclusion of NMSSM with Hgg couplings 2010-12-21 Advanced options for integration passes 2010-11-16 WHIZARD supports CTEQ6 and possibly other PDFs directly; data files included in the distribution ################################################################## 2010-10-26 RELEASE: version 2.0.4 2010-10-06 Bug fix in MSSM implementation 2010-10-01 Update to libtool 2.4 2010-09-29 Support for anomalous top couplings (form factors etc.) Bug fix for running gauge Yukawa SUSY couplings 2010-09-28 RELEASE: version 1.96 2010-09-21 Beam remnants and pT spectra for lepton collider re-enabled Restructuring subevt class 2010-09-16 Shower and matching are disabled by default PYTHIA as a conditional on these two options 2010-09-14 Possibility to read in beam spectra re-enabled (e.g. Guinea Pig) 2010-09-13 Energy scan as (pseudo-) structure functions re-implemented 2010-09-10 CIRCE2 included again in WHIZARD 2 and validated 2010-09-02 Re-implementation of asymmetric beam energies and collision angles, e-p collisions work, inclusion of a HERA DIS test case ################################################################## 2010-10-18 RELEASE: version 2.0.3 2010-08-08 Bug in CP-violating anomalous triple TGCs fixed 2010-08-06 Solving backwards compatibility problem with O'Caml 3.12.0 2010-07-12 Conserved quantum numbers speed up O'Mega code generation 2010-07-07 Attaching full ISR/FSR parton shower and MPI/ISR module Added SM model containing Hgg, HAA, HAZ vertices 2010-07-02 Matching output available as LHEF and STDHEP 2010-06-30 Various bug fixes, missing files, typos 2010-06-26 CIRCE1 completely re-enabled Chaining structure functions supported 2010-06-25 Partial support for conserved quantum numbers in O'Mega 2010-06-21 Major upgrade of the graphics package: error bars, smarter SINDARIN steering, documentation, and all that... 2010-06-17 MLM matching with PYTHIA shower included 2010-06-16 Added full CIRCE1 and CIRCE2 versions including full documentation and miscellanea to the trunk 2010-06-12 User file management supported, improved variable and command structure 2010-05-24 Improved handling of variables in local command lists 2010-05-20 PYTHIA interface re-enabled 2010-05-19 ASCII file formats for interfacing ROOT and gnuplot in data analysis ################################################################## 2010-05-18 RELEASE: version 2.0.2 2010-05-14 Reimplementation of visualization of phase space channels Minor bug fixes 2010-05-12 Improved phase space - elimination of redundancies 2010-05-08 Interface for polarization completed: polarized beams etc. 2010-05-06 Full quantum numbers appear in process log Integration results are usable as user variables Communication with external programs 2010-05-05 Split module commands into commands, integration, simulation modules 2010-05-04 FSR+ISR for the first time connected to the WHIZARD 2 core ################################################################## 2010-04-25 RELEASE: version 2.0.1 2010-04-23 Automatic compile and integrate if simulate is called Minor bug fixes in O'Mega 2010-04-21 Checkpointing for event generation Flush statements to use WHIZARD inside a pipe 2010-04-20 Reimplementation of signal handling in WGIZARD 2.0 2010-04-19 VAMP is now a separately configurable and installable unit of WHIZARD, included VAMP self-checks Support again compilation in quadruple precision 2010-04-06 Allow for logarithmic plots in GAMELAN, reimplement the possibility to set the number of bins 2010-04-15 Improvement on time estimates for event generation ################################################################## 2010-04-12 RELEASE: version 2.0.0 2010-04-09 Per default, the code for the amplitudes is subdivided to allow faster compiler optimization More advanced and unified and straightforward command language syntax Final bug fixes 2010-04-07 Improvement on SINDARIN syntax; printf, sprintf function thorugh a C interface 2010-04-05 Colorizing DAGs instead of model vertices: speed boost in colored code generation 2010-03-31 Generalized options for normalization of weighted and unweighted events Grid and weight histories added again to log files Weights can be used in analyses 2010-03-28 Cascade decays completely implemented including color and spin correlations 2010-03-07 Added new WHIZARD header with logo 2010-03-05 Removed conflict in O'Mega amplitudes between flavour sums and cascades StdHEP interface re-implemented 2010-03-03 RELEASE: version 2.0.0rc3 Several bug fixes for preventing abuse in input files OpenMP support for amplitudes Reimplementation of WHIZARD 1 HEPEVT ASCII event formats FeynRules interface successfully passed MSSM test 2010-02-26 Eliminating ghost gluons from multi-gluon amplitudes 2010-02-25 RELEASE: version 1.95 HEPEVT format from WHIZARD 1 re-implemented in WHIZARD 2 2010-02-23 Running alpha_s implemented in the FeynRules interface 2010-02-19 MSSM (semi-) automatized self-tests finalized 2010-02-17 RELEASE: version 1.94 2010-02-16 Closed memory corruption in WHIZARD 1 Fixed problems of old MadGraph and CompHep drivers with modern compilers Uncolored vertex selection rules for colored amplitudes in O'Mega 2010-02-15 Infrastructure for color correlation computation in O'Mega finished Forbidden processes are warned about, but treated as non-fatal 2010-02-14 Color correlation computation in O'Mega finalized 2010-02-10 Improving phase space mappings for identical particles in initial and final states Introduction of more extended multi-line error message 2010-02-08 First O'Caml code for computation of color correlations in O'Mega 2010-02-07 First MLM matching with e+ e- -> jets ################################################################## 2010-02-06 RELEASE: version 2.0.0rc2 2010-02-05 Reconsidered the Makefile structure and more extended tests Catch a crash between WHIZARD and O'Mega for forbidden processes Tensor products of arbitrary color structures in jet definitions 2010-02-04 Color correlation computation in O'Mega finalized ################################################################## 2010-02-03 RELEASE: version 2.0.0rc1 ################################################################## 2010-01-31 Reimplemented numerical helicity selection rules Phase space functionality of version 1 restored and improved 2009-12-05 NMSSM validated with FeynRules in WHIZARD 1 (Felix Braam) 2009-12-04 RELEASE: version 2.0.0alpha ################################################################## 2009-04-16 RELEASE: version 1.93 2009-04-15 Clean-up of Makefiles and configure scripts Reconfiguration of BSM model implementation extended supersymmetric models 2008-12-23 New model NMSSM (Felix Braam) SLHA2 added Bug in LHAPDF interface fixed 2008-08-16 Bug fixed in K matrix implementation Gravitino option in the MSSM added 2008-03-20 Improved color and flavor sums ################################################################## 2008-03-12 RELEASE: version 1.92 LHEF (Les Houches Event File) format added Fortran 2003 command-line interface (if supported by the compiler) Automated interface to colored models More bug fixes and workarounds for compiler compatibility ################################################################## 2008-03-06 RELEASE: version 1.91 New model K-matrix (resonances and anom. couplings in WW scattering) EWA spectrum Energy-scan pseudo spectrum Preliminary parton shower module (only from final-state quarks) Cleanup and improvements of configure process Improvements for O'Mega parameter files Quadruple precision works again More plotting options: lines, symbols, errors Documentation with PDF bookmarks enabled Various bug fixes 2007-11-29 New model UED ################################################################## 2007-11-23 RELEASE: version 1.90 O'Mega now part of the WHIZARD tree Madgraph/CompHEP disabled by default (but still usable) Support for LHAPDF (preliminary) Added new models: SMZprime, SM_km, Template Improved compiler recognition and compatibility Minor bug fixes ################################################################## 2006-06-15 RELEASE: version 1.51 Support for anomaly-type Higgs couplings (to gluon and photon/Z) Support for spin 3/2 and spin 2 New models: Little Higgs (4 versions), toy models for extra dimensions and gravitinos Fixes to the whizard.nw source documentation to run through LaTeX Intel 9.0 bug workaround (deallocation of some arrays) 2006-05-15 O'Mega RELEASE: version 0.11 merged JRR's O'Mega extensions ################################################################## 2006-02-07 RELEASE: version 1.50 To avoid confusion: Mention outdated manual example in BUGS file O'Mega becomes part of the WHIZARD generator 2006-02-02 [bug fix update] Bug fix: spurious error when writing event files for weighted events Bug fix: 'r' option for omega produced garbage for some particle names Workaround for ifort90 bug (crash when compiling whizard_event) Workaround for ifort90 bug (crash when compiling hepevt_common) 2006-01-27 Added process definition files for MSSM 2->2 processes Included beam recoil for EPA (T.Barklow) Updated STDHEP byte counts (for STDHEP 5.04.02) Fixed STDHEP compatibility (avoid linking of incomplete .so libs) Fixed issue with comphep requiring Xlibs on Opteron Fixed issue with ifort 8.x on Opteron (compiling 'signal' interface) Fixed color-flow code: was broken for omega with option 'c' and 'w' Workaround hacks for g95 compatibility 2005-11-07 O'Mega RELEASE: version 0.10 O'Mega, merged JRR's and WK's color hack for WHiZard O'Mega, EXPERIMENTAL: cache fusion tables (required for colors a la JRR/WK) O'Mega, make JRR's MSSM official ################################################################## 2005-10-25 RELEASE: version 1.43 Minor fixes in MSSM couplings (Higgs/3rd gen squarks). This should be final, since the MSSM results agree now completely with Madgraph and Sherpa User-defined lower and upper limits for split event file count Allow for counters (events, bytes) exceeding $2^{31}$ Revised checksum treatment and implementation (now MD5) Bug fix: missing process energy scale in raw event file ################################################################## 2005-09-30 RELEASE: version 1.42 Graphical display of integration history ('make history') Allow for switching off signals even if supported (configure option) 2005-09-29 Revised phase space generation code, in particular for flavor sums Negative cut and histogram codes use initial beams instead of initial parton momenta. This allows for computing, e.g., E_miss Support constant-width and zero-width options for O'Mega Width options now denoted by w:X (X=f,c,z). f option obsolescent Bug fix: colorized code: flipped indices could screw up result Bug fix: O'Mega with 'c' and 'w:f' option together (still some problem) Bug fix: dvips on systems where dvips defaults to lpr Bug fix: integer overflow if too many events are requested 2005-07-29 Allow for 2 -> 1 processes (if structure functions are on) 2005-07-26 Fixed and expanded the 'test' matrix element: Unit matrix element with option 'u' / default: normalized phase space ################################################################## 2005-07-15 RELEASE: version 1.41 Bug fix: no result for particle decay processes with width=0 Bug fix: line breaks in O'Mega files with color decomposition 2005-06-02 New self-tests (make test-QED / test-QCD / test-SM) check lists of 2->2 processes Bug fix: HELAS calling convention for wwwwxx and jwwwxx (4W-Vertex) 2005-05-25 Revised Makefile structure Eliminated obsolete references to ISAJET/SUSY (superseded by SLHA) 2005-05-19 Support for color in O'Mega (using color flow decomposition) New model QCD Parameter file changes that correspond to replaced SM module in O'Mega Bug fixes in MSSM (O'Mega) parameter file 2005-05-18 New event file formats, useful for LHC applications: ATHENA and Les Houches Accord (external fragmentation) Naive (i.e., leading 1/N) color factor now implemented both for incoming and outgoing partons 2005-01-26 include missing HELAS files for bundle pgf90 compatibility issues [note: still internal error in pgf90] ################################################################## 2004-12-13 RELEASE: version 1.40 compatibility fix: preprocessor marks in helas code now commented out minor bug fix: format string in madgraph source 2004-12-03 support for arbitray beam energies and directions allow for pT kick in structure functions bug fix: rounding error could result in zero cross section (compiler-dependent) 2004-10-07 simulate decay processes list fraction (of total width/cross section) instead of efficiency in process summary new cut/analysis parameters AA, AAD, CTA: absolute polar angle 2004-10-04 Replaced Madgraph I by Madgraph II. Main improvement: model no longer hardcoded introduced parameter reset_seed_each_process (useful for debugging) bug fix: color initialization for some processes was undefined 2004-09-21 don't compile unix_args module if it is not required ################################################################## 2004-09-20 RELEASE: version 1.30 g95 compatibility issues resolved some (irrelevant) memory leaks closed removed obsolete warning in circe1 manual update (essentially) finished 2004-08-03 O'Mega RELEASE: version 0.9 O'Mega, src/trie.mli, src/trie.ml: make interface compatible with the O'Caml 3.08 library (remains compatible with older versions). Implementation of unused functions still incomplete. 2004-07-26 minor fixes and improvements in make process 2004-06-29 workarounds for new Intel compiler bugs ... no rebuild of madgraph/comphep executables after 'make clean' bug fix in phase space routine: wrong energy for massive initial particles bug fix in (new) model interface: name checks for antiparticles pre-run checks for comphep improved ww-strong model file extended Model files particle name fixes, chep SM vertices included 2004-06-22 O'Mega RELEASE: version 0.8 O'Mega MSSM: sign of W+/W-/A and W+/W-/Z couplings 2004-05-05 Fixed bug in PDFLIB interface: p+pbar was initialized as p+p (ThO) NAG compiler: set number of continuation lines to 200 as default Extended format for cross section summary; appears now in whizard.out Fixed 'bundle' feature 2004-04-28 Fixed compatibility with revised O'Mega SM_ac model Fixed problem with x=0 or x=1 when calling PDFLIB (ThO) Fixed bug in comphep module: Vtb was overlooked ################################################################## 2004-04-15 RELEASE: version 1.28 Fixed bug: Color factor was missing for O'Mega processes with four quarks and more Manual partially updated 2004-04-08 Support for grid files in binary format New default value show_histories=F (reduce output file size) Revised phase space switches: removed annihilation_lines, removed s_channel_resonance, changed meaning of extra_off_shell_lines, added show_deleted_channels Bug fixed which lead to omission of some phase space channels Color flow guessed only if requested by guess_color_flow 2004-03-10 New model interface: Only one model name specified in whizard.prc All model-dependent files reside in conf/models (modellib removed) 2004-03-03 Support for input/output in SUSY Les Houches Accord format Split event files if requested Support for overall time limit Support for CIRCE and CIRCE2 generator mode Support for reading beam events from file 2004-02-05 Fixed compiler problems with Intel Fortran 7.1 and 8.0 Support for catching signals ################################################################## 2003-08-06 RELEASE: version 1.27 User-defined PDF libraries as an alternative to the standard PDFLIB 2003-07-23 Revised phase space module: improved mappings for massless particles, equivalences of phase space channels are exploited Improved mapping for PDF (hadron colliders) Madgraph module: increased max number of color flows from 250 to 1000 ################################################################## 2003-06-23 RELEASE: version 1.26 CIRCE2 support Fixed problem with 'TC' integer kind [Intel compiler complained] 2003-05-28 Support for drawing histograms of grids Bug fixes for MSSM definitions ################################################################## 2003-05-22 RELEASE: version 1.25 Experimental MSSM support with ISAJET interface Improved capabilities of generating/analyzing weighted events Optional drawing phase space diagrams using FeynMF ################################################################## 2003-01-31 RELEASE: version 1.24 A few more fixes and workarounds (Intel and Lahey compiler) 2003-01-15 Fixes and workarounds needed for WHIZARD to run with Intel compiler Command-line option interface for the Lahey compiler Bug fix: problem with reading whizard.phs ################################################################## 2002-12-10 RELEASE: version 1.23 Command-line options (on some systems) Allow for initial particles in the event record, ordered: [beams, initials] - [remnants] - outgoing partons Support for PYTHIA 6.2: Les Houches external process interface String pythia_parameters can be up to 1000 characters long Select color flow states in (internal) analysis Bug fix in color flow content of raw event files Support for transversal polarization of fermion beams Cut codes: PHI now for absolute azimuthal angle, DPHI for distance 'Test' matrix elements optionally respect polarization User-defined code can be inserted for spectra, structure functions and fragmentation Time limits can be specified for adaptation and simulation User-defined file names and file directory Initial weights in input file no longer supported Bug fix in MadGraph (wave function counter could overflow) Bug fix: Gamelan (graphical analysis) was not built if noweb absent ################################################################## 2002-03-16 RELEASE: version 1.22 Allow for beam remnants in the event record 2002-03-01 Handling of aliases in whizard.prc fixed (aliases are whole tokens) 2002-02-28 Optimized phase space handling routines (total execution time reduced by 20-60%, depending on process) ################################################################## 2002-02-26 RELEASE: version 1.21 Fixed ISR formula (ISR was underestimated in previous versions). New version includes ISR in leading-log approximation up to third order. Parameter ISR_sqrts renamed to ISR_scale. ################################################################## 2002-02-19 RELEASE: version 1.20 New process-generating method 'test' (dummy matrix element) Compatibility with autoconf 2.50 and current O'Mega version 2002-02-05 Prevent integration channels from being dropped (optionally) New internal mapping for structure functions improves performance Old whizard.phx file deleted after recompiling (could cause trouble) 2002-01-24 Support for user-defined cuts and matrix element reweighting STDHEP output now written by write_events_format=20 (was 3) 2002-01-16 Improved structure function handling; small changes in user interface: new parameter structured_beams in &process_input parameter fixed_energy in &beam_input removed Support for multiple initial states Eta-phi (cone) cut possible (hadron collider applications) Fixed bug: Whizard library was not always recompiled when necessary Fixed bug: Default cuts were insufficient in some cases Fixed bug: Unusable phase space mappings generated in some cases 2001-12-06 Reorganized document source 2001-12-05 Preliminary CIRCE2 support (no functionality yet) 2001-11-27 Intel compiler support (does not yet work because of compiler bugs) New cut and analysis mode cos-theta* and related Fixed circular jetset_interface dependency warning Some broadcast routines removed (parallel support disabled anyway) Minor shifts in cleanup targets (Makefiles) Modified library search, check for pdflib8* 2001-08-06 Fixed bug: I/O unit number could be undefined when reading phase space Fixed bug: Unitialized variable could cause segfault when event generation was disabled Fixed bug: Undefined subroutine in CIRCE replacement module Enabled feature: TGCs in O'Mega (not yet CompHEP!) matrix elements (CompHEP model sm-GF #5, O'Mega model SM_ac) Fixed portability issue: Makefile did rely on PWD environment variable Fixed portability issue: PYTHIA library search ambiguity resolved 2001-08-01 Default whizard.prc and whizard.in depend on activated modules Fixed bug: TEX=latex was not properly enabled when making plots 2001-07-20 Fixed output settings in PERL script calls Cache enabled in various configure checks 2001-07-13 Support for multiple processes in a single WHIZARD run. The integrations are kept separate, but the generated events are mixed The whizard.evx format has changed (incompatible), including now the color flow information for PYTHIA fragmentation Output files are now process-specific, except for the event file Phase space file whizard.phs (if present) is used only as input, program-generated phase space is now in whizard.phx 2001-07-10 Bug fix: Undefined parameters in parameters_SM_ac.f90 removed 2001-07-04 Bug fix: Compiler options for the case OMEGA is disabled Small inconsistencies in whizard.out format fixed 2001-07-01 Workaround for missing PDFLIB dummy routines in PYTHIA library ################################################################## 2001-06-30 RELEASE: version 1.13 Default path /cern/pro/lib in configure script 2001-06-20 New fragmentation option: Interface for PYTHIA with full color flow information, beam remnants etc. 2001-06-18 Severe bug fixed in madgraph interface: 3-gluon coupling was missing Enabled color flow information in madgraph 2001-06-11 VAMP interface module rewritten Revised output format: Multiple VAMP iterations count as one WHIZARD iteration in integration passes 1 and 3 Improved message and error handling Bug fix in VAMP: handle exceptional cases in rebinning_weights 2001-05-31 new parameters for grid adaptation: accuracy_goal and efficiency_goal ################################################################## 2001-05-29 RELEASE: version 1.12 bug fixes (compilation problems): deleted/modified unused functions 2001-05-16 diagram selection improved and documented 2001-05-06 allow for disabling packages during configuration 2001-05-03 slight changes in whizard.out format; manual extended ################################################################## 2001-04-20 RELEASE: version 1.11 fixed some configuration and compilation problems (PDFLIB etc.) 2001-04-18 linked PDFLIB: support for quark/gluon structure functions 2001-04-05 parameter interface written by PERL script SM_ac model file: fixed error in continuation line 2001-03-13 O'Mega, O'Caml 3.01: incompatible changes O'Mega, src/trie.mli: add covariance annotation to T.t This breaks O'Caml 3.00, but is required for O'Caml 3.01. O'Mega, many instances: replace `sig include Module.T end' by `Module.T', since the bug is fixed in O'Caml 3.01 2001-02-28 O'Mega, src/model.mli: new field Model.vertices required for model functors, will retire Model.fuse2, Model.fuse3, Model.fusen soon. ################################################################## 2001-03-27 RELEASE: version 1.10 reorganized the modules as libraries linked PYTHIA: support for parton fragmentation 2000-12-14 fixed some configuration problems (if noweb etc. are absent) ################################################################## 2000-12-01 RELEASE of first public version: version 1.00beta