Index: trunk/src/beams/beams.nw =================================================================== --- trunk/src/beams/beams.nw (revision 8402) +++ trunk/src/beams/beams.nw (revision 8403) @@ -1,25321 +1,25371 @@ %% -*- ess-noweb-default-code-mode: f90-mode; noweb-default-code-mode: f90-mode; -*- % WHIZARD code as NOWEB source: beams and beam structure %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \chapter{Beams} \includemodulegraph{beams} These modules implement beam configuration and beam structure, the latter in abstract terms. \begin{description} \item[beam\_structures] The [[beam_structure_t]] type is a messenger type that communicates the user settings to the \whizard\ core. \item[beams] Beam configuration. \item[sf\_aux] Tools for handling structure functions and splitting \item[sf\_mappings] Mapping functions, useful for structure function implementation \item[sf\_base] The abstract structure-function interaction and structure-function chain types. \end{description} These are the implementation modules, the concrete counterparts of [[sf_base]]: \begin{description} \item[sf\_isr] ISR structure function (photon radiation inclusive and resummed in collinear and IR regions). \item[sf\_epa] Effective Photon Approximation. \item[sf\_ewa] Effective $W$ (and $Z$) approximation. \item[sf\_escan] Energy spectrum that emulates a uniform energy scan. \item[sf\_gaussian] Gaussian beam spread \item[sf\_beam\_events] Beam-event generator that reads its input from an external file. \item[sf\_circe1] CIRCE1 beam spectra for electrons and photons. \item[sf\_circe2] CIRCE2 beam spectra for electrons and photons. \item[hoppet\_interface] Support for $b$-quark matching, addon to PDF modules. \item[sf\_pdf\_builtin] Direct support for selected hadron PDFs. \item[sf\_lhapdf] LHAPDF library support. \end{description} \clearpage %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Beam structure} This module stores the beam structure definition as it is declared in the SINDARIN script. The structure definition is not analyzed, just recorded for later use. We do not capture any numerical parameters, just names of particles and structure functions. <<[[beam_structures.f90]]>>= <> module beam_structures <> <> use io_units use format_defs, only: FMT_19 use diagnostics use lorentz use polarizations <> <> <> <> contains <> end module beam_structures @ %def beam_structures @ \subsection{Beam structure elements} An entry in a beam-structure record consists of a string that denotes a type of structure function. <>= type :: beam_structure_entry_t logical :: is_valid = .false. type(string_t) :: name contains <> end type beam_structure_entry_t @ %def beam_structure_entry_t @ Output. <>= procedure :: to_string => beam_structure_entry_to_string <>= function beam_structure_entry_to_string (object) result (string) class(beam_structure_entry_t), intent(in) :: object type(string_t) :: string if (object%is_valid) then string = object%name else string = "none" end if end function beam_structure_entry_to_string @ %def beam_structure_entry_to_string @ A record in the beam-structure sequence denotes either a structure-function entry, a pair of such entries, or a pair spectrum. <>= type :: beam_structure_record_t type(beam_structure_entry_t), dimension(:), allocatable :: entry end type beam_structure_record_t @ %def beam_structure_record_t @ \subsection{Beam structure type} The beam-structure object contains the beam particle(s) as simple strings. The sequence of records indicates the structure functions by name. No numerical parameters are stored. <>= public :: beam_structure_t <>= type :: beam_structure_t private integer :: n_beam = 0 type(string_t), dimension(:), allocatable :: prt type(beam_structure_record_t), dimension(:), allocatable :: record type(smatrix_t), dimension(:), allocatable :: smatrix real(default), dimension(:), allocatable :: pol_f real(default), dimension(:), allocatable :: p real(default), dimension(:), allocatable :: theta real(default), dimension(:), allocatable :: phi contains <> end type beam_structure_t @ %def beam_structure_t @ The finalizer deletes all contents explicitly, so we can continue with an empty beam record. (It is not needed for deallocation.) We have distinct finalizers for the independent parts of the beam structure. <>= procedure :: final_sf => beam_structure_final_sf <>= subroutine beam_structure_final_sf (object) class(beam_structure_t), intent(inout) :: object if (allocated (object%prt)) deallocate (object%prt) if (allocated (object%record)) deallocate (object%record) object%n_beam = 0 end subroutine beam_structure_final_sf @ %def beam_structure_final_sf @ Output. The actual information fits in a single line, therefore we can provide a [[to_string]] method. The [[show]] method also lists the current values of relevant global variables. <>= procedure :: write => beam_structure_write procedure :: to_string => beam_structure_to_string <>= subroutine beam_structure_write (object, unit) class(beam_structure_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u, i u = given_output_unit (unit) write (u, "(1x,A,A)") "Beam structure: ", char (object%to_string ()) if (allocated (object%smatrix)) then do i = 1, size (object%smatrix) write (u, "(3x,A,I0,A)") "polarization (beam ", i, "):" call object%smatrix(i)%write (u, indent=2) end do end if if (allocated (object%pol_f)) then write (u, "(3x,A,F10.7,:,',',F10.7)") "polarization degree =", & object%pol_f end if if (allocated (object%p)) then write (u, "(3x,A," // FMT_19 // ",:,','," // FMT_19 // & ")") "momentum =", object%p end if if (allocated (object%theta)) then write (u, "(3x,A," // FMT_19 // ",:,','," // FMT_19 // & ")") "angle th =", object%theta end if if (allocated (object%phi)) then write (u, "(3x,A," // FMT_19 // ",:,','," // FMT_19 // & ")") "angle ph =", object%phi end if end subroutine beam_structure_write function beam_structure_to_string (object, sf_only) result (string) class(beam_structure_t), intent(in) :: object logical, intent(in), optional :: sf_only type(string_t) :: string integer :: i, j logical :: with_beams with_beams = .true.; if (present (sf_only)) with_beams = .not. sf_only select case (object%n_beam) case (1) if (with_beams) then string = object%prt(1) else string = "" end if case (2) if (with_beams) then string = object%prt(1) // ", " // object%prt(2) else string = "" end if if (allocated (object%record)) then if (size (object%record) > 0) then if (with_beams) string = string // " => " do i = 1, size (object%record) if (i > 1) string = string // " => " do j = 1, size (object%record(i)%entry) if (j > 1) string = string // ", " string = string // object%record(i)%entry(j)%to_string () end do end do end if end if case default string = "[any particles]" end select end function beam_structure_to_string @ %def beam_structure_write beam_structure_to_string @ Initializer: dimension the beam structure record. Each array element denotes the number of entries for a record within the beam-structure sequence. The number of entries is either one or two, while the number of records is unlimited. <>= procedure :: init_sf => beam_structure_init_sf <>= subroutine beam_structure_init_sf (beam_structure, prt, dim_array) class(beam_structure_t), intent(inout) :: beam_structure type(string_t), dimension(:), intent(in) :: prt integer, dimension(:), intent(in), optional :: dim_array integer :: i call beam_structure%final_sf () beam_structure%n_beam = size (prt) allocate (beam_structure%prt (size (prt))) beam_structure%prt = prt if (present (dim_array)) then allocate (beam_structure%record (size (dim_array))) do i = 1, size (dim_array) allocate (beam_structure%record(i)%entry (dim_array(i))) end do else allocate (beam_structure%record (0)) end if end subroutine beam_structure_init_sf @ %def beam_structure_init_sf @ Set an entry, specified by record number and entry number. <>= procedure :: set_sf => beam_structure_set_sf <>= subroutine beam_structure_set_sf (beam_structure, i, j, name) class(beam_structure_t), intent(inout) :: beam_structure integer, intent(in) :: i, j type(string_t), intent(in) :: name associate (entry => beam_structure%record(i)%entry(j)) entry%name = name entry%is_valid = .true. end associate end subroutine beam_structure_set_sf @ %def beam_structure_set_sf @ Expand the beam-structure object. (i) For a pair spectrum, keep the entry. (ii) For a single-particle structure function written as a single entry, replace this by a record with two entries. (ii) For a record with two nontrivial entries, separate this into two records with one trivial entry each. To achieve this, we need a function that tells us whether an entry is a spectrum or a structure function. It returns 0 for a trivial entry, 1 for a single-particle structure function, and 2 for a two-particle spectrum. <>= abstract interface function strfun_mode_fun (name) result (n) import type(string_t), intent(in) :: name integer :: n end function strfun_mode_fun end interface @ %def is_spectrum_t @ Algorithm: (1) Mark entries as invalid where necessary. (2) Count the number of entries that we will need. (3) Expand and copy entries to a new record array. (4) Replace the old array by the new one. <>= procedure :: expand => beam_structure_expand <>= subroutine beam_structure_expand (beam_structure, strfun_mode) class(beam_structure_t), intent(inout) :: beam_structure procedure(strfun_mode_fun) :: strfun_mode type(beam_structure_record_t), dimension(:), allocatable :: new integer :: n_record, i, j if (.not. allocated (beam_structure%record)) return do i = 1, size (beam_structure%record) associate (entry => beam_structure%record(i)%entry) do j = 1, size (entry) select case (strfun_mode (entry(j)%name)) case (0); entry(j)%is_valid = .false. end select end do end associate end do n_record = 0 do i = 1, size (beam_structure%record) associate (entry => beam_structure%record(i)%entry) select case (size (entry)) case (1) if (entry(1)%is_valid) then select case (strfun_mode (entry(1)%name)) case (1); n_record = n_record + 2 case (2); n_record = n_record + 1 end select end if case (2) do j = 1, 2 if (entry(j)%is_valid) then select case (strfun_mode (entry(j)%name)) case (1); n_record = n_record + 1 case (2) call beam_structure%write () call msg_fatal ("Pair spectrum used as & &single-particle structure function") end select end if end do end select end associate end do allocate (new (n_record)) n_record = 0 do i = 1, size (beam_structure%record) associate (entry => beam_structure%record(i)%entry) select case (size (entry)) case (1) if (entry(1)%is_valid) then select case (strfun_mode (entry(1)%name)) case (1) n_record = n_record + 1 allocate (new(n_record)%entry (2)) new(n_record)%entry(1) = entry(1) n_record = n_record + 1 allocate (new(n_record)%entry (2)) new(n_record)%entry(2) = entry(1) case (2) n_record = n_record + 1 allocate (new(n_record)%entry (1)) new(n_record)%entry(1) = entry(1) end select end if case (2) do j = 1, 2 if (entry(j)%is_valid) then n_record = n_record + 1 allocate (new(n_record)%entry (2)) new(n_record)%entry(j) = entry(j) end if end do end select end associate end do call move_alloc (from = new, to = beam_structure%record) end subroutine beam_structure_expand @ %def beam_structure_expand @ \subsection{Polarization} To record polarization, we provide an allocatable array of [[smatrix]] objects, sparse matrices. The polarization structure is independent of the structure-function setup, they are combined only when an actual beam object is constructed. <>= procedure :: final_pol => beam_structure_final_pol procedure :: init_pol => beam_structure_init_pol <>= subroutine beam_structure_final_pol (beam_structure) class(beam_structure_t), intent(inout) :: beam_structure if (allocated (beam_structure%smatrix)) deallocate (beam_structure%smatrix) if (allocated (beam_structure%pol_f)) deallocate (beam_structure%pol_f) end subroutine beam_structure_final_pol subroutine beam_structure_init_pol (beam_structure, n) class(beam_structure_t), intent(inout) :: beam_structure integer, intent(in) :: n if (allocated (beam_structure%smatrix)) deallocate (beam_structure%smatrix) allocate (beam_structure%smatrix (n)) if (.not. allocated (beam_structure%pol_f)) & allocate (beam_structure%pol_f (n), source = 1._default) end subroutine beam_structure_init_pol @ %def beam_structure_final_pol @ %def beam_structure_init_pol @ Check if polarized beams are used. <>= procedure :: has_polarized_beams => beam_structure_has_polarized_beams <>= elemental function beam_structure_has_polarized_beams (beam_structure) result (pol) logical :: pol class(beam_structure_t), intent(in) :: beam_structure if (allocated (beam_structure%pol_f)) then pol = any (beam_structure%pol_f /= 0) else pol = .false. end if end function beam_structure_has_polarized_beams @ %def beam_structure_has_polarized_beams @ Directly copy the spin density matrices. <>= procedure :: set_smatrix => beam_structure_set_smatrix <>= subroutine beam_structure_set_smatrix (beam_structure, i, smatrix) class(beam_structure_t), intent(inout) :: beam_structure integer, intent(in) :: i type(smatrix_t), intent(in) :: smatrix beam_structure%smatrix(i) = smatrix end subroutine beam_structure_set_smatrix @ %def beam_structure_set_smatrix @ Initialize one of the spin density matrices manually. <>= procedure :: init_smatrix => beam_structure_init_smatrix <>= subroutine beam_structure_init_smatrix (beam_structure, i, n_entry) class(beam_structure_t), intent(inout) :: beam_structure integer, intent(in) :: i integer, intent(in) :: n_entry call beam_structure%smatrix(i)%init (2, n_entry) end subroutine beam_structure_init_smatrix @ %def beam_structure_init_smatrix @ Set a polarization entry. <>= procedure :: set_sentry => beam_structure_set_sentry <>= subroutine beam_structure_set_sentry & (beam_structure, i, i_entry, index, value) class(beam_structure_t), intent(inout) :: beam_structure integer, intent(in) :: i integer, intent(in) :: i_entry integer, dimension(:), intent(in) :: index complex(default), intent(in) :: value call beam_structure%smatrix(i)%set_entry (i_entry, index, value) end subroutine beam_structure_set_sentry @ %def beam_structure_set_sentry @ Set the array of polarization fractions. <>= procedure :: set_pol_f => beam_structure_set_pol_f <>= subroutine beam_structure_set_pol_f (beam_structure, f) class(beam_structure_t), intent(inout) :: beam_structure real(default), dimension(:), intent(in) :: f if (allocated (beam_structure%pol_f)) deallocate (beam_structure%pol_f) allocate (beam_structure%pol_f (size (f)), source = f) end subroutine beam_structure_set_pol_f @ %def beam_structure_set_pol_f @ \subsection{Beam momenta} By default, beam momenta are deduced from the [[sqrts]] value or from the mass of the decaying particle, assuming a c.m.\ setup. Here we set them explicitly. <>= procedure :: final_mom => beam_structure_final_mom <>= subroutine beam_structure_final_mom (beam_structure) class(beam_structure_t), intent(inout) :: beam_structure if (allocated (beam_structure%p)) deallocate (beam_structure%p) if (allocated (beam_structure%theta)) deallocate (beam_structure%theta) if (allocated (beam_structure%phi)) deallocate (beam_structure%phi) end subroutine beam_structure_final_mom @ %def beam_structure_final_mom <>= procedure :: set_momentum => beam_structure_set_momentum procedure :: set_theta => beam_structure_set_theta procedure :: set_phi => beam_structure_set_phi <>= subroutine beam_structure_set_momentum (beam_structure, p) class(beam_structure_t), intent(inout) :: beam_structure real(default), dimension(:), intent(in) :: p if (allocated (beam_structure%p)) deallocate (beam_structure%p) allocate (beam_structure%p (size (p)), source = p) end subroutine beam_structure_set_momentum subroutine beam_structure_set_theta (beam_structure, theta) class(beam_structure_t), intent(inout) :: beam_structure real(default), dimension(:), intent(in) :: theta if (allocated (beam_structure%theta)) deallocate (beam_structure%theta) allocate (beam_structure%theta (size (theta)), source = theta) end subroutine beam_structure_set_theta subroutine beam_structure_set_phi (beam_structure, phi) class(beam_structure_t), intent(inout) :: beam_structure real(default), dimension(:), intent(in) :: phi if (allocated (beam_structure%phi)) deallocate (beam_structure%phi) allocate (beam_structure%phi (size (phi)), source = phi) end subroutine beam_structure_set_phi @ %def beam_structure_set_momentum @ %def beam_structure_set_theta @ %def beam_structure_set_phi @ \subsection{Get contents} Look at the incoming particles. We may also have the case that beam particles are not specified, but polarization. <>= procedure :: is_set => beam_structure_is_set procedure :: get_n_beam => beam_structure_get_n_beam procedure :: get_prt => beam_structure_get_prt <>= function beam_structure_is_set (beam_structure) result (flag) class(beam_structure_t), intent(in) :: beam_structure logical :: flag flag = beam_structure%n_beam > 0 .or. beam_structure%asymmetric () end function beam_structure_is_set function beam_structure_get_n_beam (beam_structure) result (n) class(beam_structure_t), intent(in) :: beam_structure integer :: n n = beam_structure%n_beam end function beam_structure_get_n_beam function beam_structure_get_prt (beam_structure) result (prt) class(beam_structure_t), intent(in) :: beam_structure type(string_t), dimension(:), allocatable :: prt allocate (prt (size (beam_structure%prt))) prt = beam_structure%prt end function beam_structure_get_prt @ %def beam_structure_is_set @ %def beam_structure_get_n_beam @ %def beam_structure_get_prt @ Return the number of records. <>= procedure :: get_n_record => beam_structure_get_n_record <>= function beam_structure_get_n_record (beam_structure) result (n) class(beam_structure_t), intent(in) :: beam_structure integer :: n if (allocated (beam_structure%record)) then n = size (beam_structure%record) else n = 0 end if end function beam_structure_get_n_record @ %def beam_structure_get_n_record @ Return an array consisting of the beam indices affected by the valid entries within a record. After expansion, there should be exactly one valid entry per record. <>= procedure :: get_i_entry => beam_structure_get_i_entry <>= function beam_structure_get_i_entry (beam_structure, i) result (i_entry) class(beam_structure_t), intent(in) :: beam_structure integer, intent(in) :: i integer, dimension(:), allocatable :: i_entry associate (record => beam_structure%record(i)) select case (size (record%entry)) case (1) if (record%entry(1)%is_valid) then allocate (i_entry (2), source = [1, 2]) else allocate (i_entry (0)) end if case (2) if (all (record%entry%is_valid)) then allocate (i_entry (2), source = [1, 2]) else if (record%entry(1)%is_valid) then allocate (i_entry (1), source = [1]) else if (record%entry(2)%is_valid) then allocate (i_entry (1), source = [2]) else allocate (i_entry (0)) end if end select end associate end function beam_structure_get_i_entry @ %def beam_structure_get_i_entry @ Return the name of the first valid entry within a record. After expansion, there should be exactly one valid entry per record. <>= procedure :: get_name => beam_structure_get_name <>= function beam_structure_get_name (beam_structure, i) result (name) type(string_t) :: name class(beam_structure_t), intent(in) :: beam_structure integer, intent(in) :: i associate (record => beam_structure%record(i)) if (record%entry(1)%is_valid) then name = record%entry(1)%name else if (size (record%entry) == 2) then name = record%entry(2)%name end if end associate end function beam_structure_get_name @ %def beam_structure_get_name @ <>= procedure :: has_pdf => beam_structure_has_pdf <>= function beam_structure_has_pdf (beam_structure) result (has_pdf) logical :: has_pdf class(beam_structure_t), intent(in) :: beam_structure integer :: i type(string_t) :: name has_pdf = .false. do i = 1, beam_structure%get_n_record () name = beam_structure%get_name (i) has_pdf = has_pdf .or. name == var_str ("pdf_builtin") .or. name == var_str ("lhapdf") end do end function beam_structure_has_pdf @ %def beam_structure_has_pdf @ Return true if the beam structure contains a particular structure function identifier (such as [[lhapdf]], [[isr]], etc.) <>= procedure :: contains => beam_structure_contains <>= function beam_structure_contains (beam_structure, name) result (flag) class(beam_structure_t), intent(in) :: beam_structure character(*), intent(in) :: name logical :: flag integer :: i, j flag = .false. if (allocated (beam_structure%record)) then do i = 1, size (beam_structure%record) do j = 1, size (beam_structure%record(i)%entry) flag = beam_structure%record(i)%entry(j)%name == name if (flag) return end do end do end if end function beam_structure_contains @ %def beam_structure_contains @ Return polarization data. <>= procedure :: polarized => beam_structure_polarized procedure :: get_smatrix => beam_structure_get_smatrix procedure :: get_pol_f => beam_structure_get_pol_f procedure :: asymmetric => beam_structure_asymmetric <>= function beam_structure_polarized (beam_structure) result (flag) class(beam_structure_t), intent(in) :: beam_structure logical :: flag flag = allocated (beam_structure%smatrix) end function beam_structure_polarized function beam_structure_get_smatrix (beam_structure) result (smatrix) class(beam_structure_t), intent(in) :: beam_structure type(smatrix_t), dimension(:), allocatable :: smatrix allocate (smatrix (size (beam_structure%smatrix)), & source = beam_structure%smatrix) end function beam_structure_get_smatrix function beam_structure_get_pol_f (beam_structure) result (pol_f) class(beam_structure_t), intent(in) :: beam_structure real(default), dimension(:), allocatable :: pol_f allocate (pol_f (size (beam_structure%pol_f)), & source = beam_structure%pol_f) end function beam_structure_get_pol_f function beam_structure_asymmetric (beam_structure) result (flag) class(beam_structure_t), intent(in) :: beam_structure logical :: flag flag = allocated (beam_structure%p) & .or. allocated (beam_structure%theta) & .or. allocated (beam_structure%phi) end function beam_structure_asymmetric @ %def beam_structure_polarized @ %def beam_structure_get_smatrix @ %def beam_structure_get_pol_f @ %def beam_structure_asymmetric @ Return the beam momenta (the space part, i.e., three-momenta). This is meaningful only if momenta and, optionally, angles have been set. <>= procedure :: get_momenta => beam_structure_get_momenta <>= function beam_structure_get_momenta (beam_structure) result (p) class(beam_structure_t), intent(in) :: beam_structure type(vector3_t), dimension(:), allocatable :: p real(default), dimension(:), allocatable :: theta, phi integer :: n, i if (allocated (beam_structure%p)) then n = size (beam_structure%p) if (allocated (beam_structure%theta)) then if (size (beam_structure%theta) == n) then allocate (theta (n), source = beam_structure%theta) else call msg_fatal ("Beam structure: mismatch in momentum vs. & &angle theta specification") end if else allocate (theta (n), source = 0._default) end if if (allocated (beam_structure%phi)) then if (size (beam_structure%phi) == n) then allocate (phi (n), source = beam_structure%phi) else call msg_fatal ("Beam structure: mismatch in momentum vs. & &angle phi specification") end if else allocate (phi (n), source = 0._default) end if allocate (p (n)) do i = 1, n p(i) = beam_structure%p(i) * vector3_moving ([ & sin (theta(i)) * cos (phi(i)), & sin (theta(i)) * sin (phi(i)), & cos (theta(i))]) end do if (n == 2) p(2) = - p(2) else call msg_fatal ("Beam structure: angle theta/phi specified but & &momentum/a p undefined") end if end function beam_structure_get_momenta @ %def beam_structure_get_momenta @ Check for a complete beam structure. The [[applies]] flag tells if the beam structure should actually be used for a process with the given [[n_in]] number of incoming particles. It set if the beam structure matches the process as either decay or scattering. It is unset if beam structure references a scattering setup but the process is a decay. It is also unset if the beam structure itself is empty. If the beam structure cannot be used, terminate with fatal error. <>= procedure :: check_against_n_in => beam_structure_check_against_n_in <>= subroutine beam_structure_check_against_n_in (beam_structure, n_in, applies) class(beam_structure_t), intent(in) :: beam_structure integer, intent(in) :: n_in logical, intent(out) :: applies if (beam_structure%is_set ()) then if (n_in == beam_structure%get_n_beam ()) then applies = .true. else if (beam_structure%get_n_beam () == 0) then call msg_fatal & ("Asymmetric beams: missing beam particle specification") applies = .false. else call msg_fatal & ("Mismatch of process and beam setup (scattering/decay)") applies = .false. end if else applies = .false. end if end subroutine beam_structure_check_against_n_in @ %def beam_structure_check_against_n_in @ \subsection{Unit Tests} Test module, followed by the corresponding implementation module. <<[[beam_structures_ut.f90]]>>= <> module beam_structures_ut use unit_tests use beam_structures_uti <> <> contains <> end module beam_structures_ut @ %def beam_structures_ut @ <<[[beam_structures_uti.f90]]>>= <> module beam_structures_uti <> <> use beam_structures <> <> contains <> <> end module beam_structures_uti @ %def beam_structures_ut @ API: driver for the unit tests below. <>= public :: beam_structures_test <>= subroutine beam_structures_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine beam_structures_test @ %def beam_structures_tests @ \subsubsection{Empty structure} <>= call test (beam_structures_1, "beam_structures_1", & "empty beam structure record", & u, results) <>= public :: beam_structures_1 <>= subroutine beam_structures_1 (u) integer, intent(in) :: u type(beam_structure_t) :: beam_structure write (u, "(A)") "* Test output: beam_structures_1" write (u, "(A)") "* Purpose: display empty beam structure record" write (u, "(A)") call beam_structure%write (u) write (u, "(A)") write (u, "(A)") "* Test output end: beam_structures_1" end subroutine beam_structures_1 @ %def beam_structures_1 @ \subsubsection{Nontrivial configurations} <>= call test (beam_structures_2, "beam_structures_2", & "beam structure records", & u, results) <>= public :: beam_structures_2 <>= subroutine beam_structures_2 (u) integer, intent(in) :: u type(beam_structure_t) :: beam_structure integer, dimension(0) :: empty_array type(string_t) :: s write (u, "(A)") "* Test output: beam_structures_2" write (u, "(A)") "* Purpose: setup beam structure records" write (u, "(A)") s = "s" call beam_structure%init_sf ([s], empty_array) call beam_structure%write (u) write (u, "(A)") call beam_structure%init_sf ([s, s], [1]) call beam_structure%set_sf (1, 1, var_str ("a")) call beam_structure%write (u) write (u, "(A)") call beam_structure%init_sf ([s, s], [2]) call beam_structure%set_sf (1, 1, var_str ("a")) call beam_structure%set_sf (1, 2, var_str ("b")) call beam_structure%write (u) write (u, "(A)") call beam_structure%init_sf ([s, s], [2, 1]) call beam_structure%set_sf (1, 1, var_str ("a")) call beam_structure%set_sf (1, 2, var_str ("b")) call beam_structure%set_sf (2, 1, var_str ("c")) call beam_structure%write (u) write (u, "(A)") write (u, "(A)") "* Test output end: beam_structures_2" end subroutine beam_structures_2 @ %def beam_structures_2 @ \subsubsection{Expansion} Provide a function that tells, for the dummy structure function names used here, whether they are considered a two-particle spectrum or a single-particle structure function: <>= function test_strfun_mode (name) result (n) type(string_t), intent(in) :: name integer :: n select case (char (name)) case ("a"); n = 2 case ("b"); n = 1 case default; n = 0 end select end function test_strfun_mode @ %def test_ist_pair_spectrum @ <>= call test (beam_structures_3, "beam_structures_3", & "beam structure expansion", & u, results) <>= public :: beam_structures_3 <>= subroutine beam_structures_3 (u) integer, intent(in) :: u type(beam_structure_t) :: beam_structure type(string_t) :: s write (u, "(A)") "* Test output: beam_structures_3" write (u, "(A)") "* Purpose: expand beam structure records" write (u, "(A)") s = "s" write (u, "(A)") "* Pair spectrum (keep as-is)" write (u, "(A)") call beam_structure%init_sf ([s, s], [1]) call beam_structure%set_sf (1, 1, var_str ("a")) call beam_structure%write (u) write (u, "(A)") call beam_structure%expand (test_strfun_mode) call beam_structure%write (u) write (u, "(A)") write (u, "(A)") "* Structure function pair (expand)" write (u, "(A)") call beam_structure%init_sf ([s, s], [2]) call beam_structure%set_sf (1, 1, var_str ("b")) call beam_structure%set_sf (1, 2, var_str ("b")) call beam_structure%write (u) write (u, "(A)") call beam_structure%expand (test_strfun_mode) call beam_structure%write (u) write (u, "(A)") write (u, "(A)") "* Structure function (separate and expand)" write (u, "(A)") call beam_structure%init_sf ([s, s], [1]) call beam_structure%set_sf (1, 1, var_str ("b")) call beam_structure%write (u) write (u, "(A)") call beam_structure%expand (test_strfun_mode) call beam_structure%write (u) write (u, "(A)") write (u, "(A)") "* Combination" write (u, "(A)") call beam_structure%init_sf ([s, s], [1, 1]) call beam_structure%set_sf (1, 1, var_str ("a")) call beam_structure%set_sf (2, 1, var_str ("b")) call beam_structure%write (u) write (u, "(A)") call beam_structure%expand (test_strfun_mode) call beam_structure%write (u) write (u, "(A)") write (u, "(A)") "* Test output end: beam_structures_3" end subroutine beam_structures_3 @ %def beam_structures_3 @ \subsubsection{Public methods} Check the methods that can be called to get the beam-structure contents. <>= call test (beam_structures_4, "beam_structures_4", & "beam structure contents", & u, results) <>= public :: beam_structures_4 <>= subroutine beam_structures_4 (u) integer, intent(in) :: u type(beam_structure_t) :: beam_structure type(string_t) :: s type(string_t), dimension(2) :: prt integer :: i write (u, "(A)") "* Test output: beam_structures_4" write (u, "(A)") "* Purpose: check the API" write (u, "(A)") s = "s" write (u, "(A)") "* Structure-function combination" write (u, "(A)") call beam_structure%init_sf ([s, s], [1, 2, 2]) call beam_structure%set_sf (1, 1, var_str ("a")) call beam_structure%set_sf (2, 1, var_str ("b")) call beam_structure%set_sf (3, 2, var_str ("c")) call beam_structure%write (u) write (u, *) write (u, "(1x,A,I0)") "n_beam = ", beam_structure%get_n_beam () prt = beam_structure%get_prt () write (u, "(1x,A,2(1x,A))") "prt =", char (prt(1)), char (prt(2)) write (u, *) write (u, "(1x,A,I0)") "n_record = ", beam_structure%get_n_record () do i = 1, 3 write (u, "(A)") write (u, "(1x,A,I0,A,A)") "name(", i, ") = ", & char (beam_structure%get_name (i)) write (u, "(1x,A,I0,A,2(1x,I0))") "i_entry(", i, ") =", & beam_structure%get_i_entry (i) end do write (u, "(A)") write (u, "(A)") "* Test output end: beam_structures_4" end subroutine beam_structures_4 @ %def beam_structures_4 @ \subsubsection{Polarization} The polarization properties are independent from the structure-function setup. <>= call test (beam_structures_5, "beam_structures_5", & "polarization", & u, results) <>= public :: beam_structures_5 <>= subroutine beam_structures_5 (u) integer, intent(in) :: u type(beam_structure_t) :: beam_structure integer, dimension(0) :: empty_array type(string_t) :: s write (u, "(A)") "* Test output: beam_structures_5" write (u, "(A)") "* Purpose: setup polarization in beam structure records" write (u, "(A)") s = "s" call beam_structure%init_sf ([s], empty_array) call beam_structure%init_pol (1) call beam_structure%init_smatrix (1, 1) call beam_structure%set_sentry (1, 1, [0,0], (1._default, 0._default)) call beam_structure%set_pol_f ([0.5_default]) call beam_structure%write (u) write (u, "(A)") call beam_structure%final_sf () call beam_structure%final_pol () call beam_structure%init_sf ([s, s], [1]) call beam_structure%set_sf (1, 1, var_str ("a")) call beam_structure%init_pol (2) call beam_structure%init_smatrix (1, 2) call beam_structure%set_sentry (1, 1, [-1,1], (0.5_default,-0.5_default)) call beam_structure%set_sentry (1, 2, [ 1,1], (1._default, 0._default)) call beam_structure%init_smatrix (2, 0) call beam_structure%write (u) write (u, "(A)") write (u, "(A)") "* Test output end: beam_structures_5" end subroutine beam_structures_5 @ %def beam_structures_5 @ \subsubsection{Momenta} The momenta are independent from the structure-function setup. <>= call test (beam_structures_6, "beam_structures_6", & "momenta", & u, results) <>= public :: beam_structures_6 <>= subroutine beam_structures_6 (u) integer, intent(in) :: u type(beam_structure_t) :: beam_structure integer, dimension(0) :: empty_array type(string_t) :: s write (u, "(A)") "* Test output: beam_structures_6" write (u, "(A)") "* Purpose: setup momenta in beam structure records" write (u, "(A)") s = "s" call beam_structure%init_sf ([s], empty_array) call beam_structure%set_momentum ([500._default]) call beam_structure%write (u) write (u, "(A)") call beam_structure%final_sf () call beam_structure%final_mom () call beam_structure%init_sf ([s, s], [1]) call beam_structure%set_momentum ([500._default, 700._default]) call beam_structure%set_theta ([0._default, 0.1_default]) call beam_structure%set_phi ([0._default, 1.51_default]) call beam_structure%write (u) write (u, "(A)") write (u, "(A)") "* Test output end: beam_structures_6" end subroutine beam_structures_6 @ %def beam_structures_6 @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Beams for collisions and decays} <<[[beams.f90]]>>= <> module beams <> <> use io_units use format_defs, only: FMT_19 use numeric_utils use diagnostics use md5 use lorentz use model_data use flavors use quantum_numbers use state_matrices use interactions use polarizations use beam_structures <> <> <> <> contains <> end module beams @ %def beams @ \subsection{Beam data} The beam data type contains beam data for one or two beams, depending on whether we are dealing with beam collisions or particle decay. In addition, it holds the c.m.\ energy [[sqrts]], the Lorentz transformation [[L]] that transforms the c.m.\ system into the lab system, and the pair of c.m.\ momenta. <>= public :: beam_data_t <>= type :: beam_data_t logical :: initialized = .false. integer :: n = 0 type(flavor_t), dimension(:), allocatable :: flv real(default), dimension(:), allocatable :: mass type(pmatrix_t), dimension(:), allocatable :: pmatrix logical :: lab_is_cm_frame = .true. type(vector4_t), dimension(:), allocatable :: p_cm type(vector4_t), dimension(:), allocatable :: p type(lorentz_transformation_t), allocatable :: L_cm_to_lab real(default) :: sqrts = 0 character(32) :: md5sum = "" contains <> end type beam_data_t @ %def beam_data_t @ Generic initializer. This is called by the specific initializers below. Initialize either for decay or for collision. <>= subroutine beam_data_init (beam_data, n) type(beam_data_t), intent(out) :: beam_data integer, intent(in) :: n beam_data%n = n allocate (beam_data%flv (n)) allocate (beam_data%mass (n)) allocate (beam_data%pmatrix (n)) allocate (beam_data%p_cm (n)) allocate (beam_data%p (n)) beam_data%initialized = .true. end subroutine beam_data_init @ %def beam_data_init @ Finalizer: needed for the polarization components of the beams. <>= procedure :: final => beam_data_final <>= subroutine beam_data_final (beam_data) class(beam_data_t), intent(inout) :: beam_data beam_data%initialized = .false. end subroutine beam_data_final @ %def beam_data_final @ The verbose (default) version is for debugging. The short version is for screen output in the UI. <>= procedure :: write => beam_data_write <>= subroutine beam_data_write (beam_data, unit, verbose, write_md5sum) class(beam_data_t), intent(in) :: beam_data integer, intent(in), optional :: unit logical, intent(in), optional :: verbose, write_md5sum integer :: prt_name_len logical :: verb, write_md5 integer :: u u = given_output_unit (unit); if (u < 0) return verb = .false.; if (present (verbose)) verb = verbose write_md5 = verb; if (present (write_md5sum)) write_md5 = write_md5sum if (.not. beam_data%initialized) then write (u, "(1x,A)") "Beam data: [undefined]" return end if prt_name_len = maxval (len (beam_data%flv%get_name ())) select case (beam_data%n) case (1) write (u, "(1x,A)") "Beam data (decay):" if (verb) then call write_prt (1) call beam_data%pmatrix(1)%write (u) write (u, *) "R.f. momentum:" call vector4_write (beam_data%p_cm(1), u) write (u, *) "Lab momentum:" call vector4_write (beam_data%p(1), u) else call write_prt (1) end if case (2) write (u, "(1x,A)") "Beam data (collision):" if (verb) then call write_prt (1) call beam_data%pmatrix(1)%write (u) call write_prt (2) call beam_data%pmatrix(2)%write (u) call write_sqrts write (u, *) "C.m. momenta:" call vector4_write (beam_data%p_cm(1), u) call vector4_write (beam_data%p_cm(2), u) write (u, *) "Lab momenta:" call vector4_write (beam_data%p(1), u) call vector4_write (beam_data%p(2), u) else call write_prt (1) call write_prt (2) call write_sqrts end if end select if (allocated (beam_data%L_cm_to_lab)) then if (verb) then call lorentz_transformation_write (beam_data%L_cm_to_lab, u) else write (u, "(1x,A)") "Beam structure: lab and c.m. frame differ" end if end if if (write_md5) then write (u, *) "MD5 sum: ", beam_data%md5sum end if contains subroutine write_sqrts character(80) :: sqrts_str write (sqrts_str, "(" // FMT_19 // ")") beam_data%sqrts write (u, "(3x,A)") "sqrts = " // trim (adjustl (sqrts_str)) // " GeV" end subroutine write_sqrts subroutine write_prt (i) integer, intent(in) :: i character(80) :: name_str, mass_str write (name_str, "(A)") char (beam_data%flv(i)%get_name ()) write (mass_str, "(ES13.7)") beam_data%mass(i) write (u, "(3x,A)", advance="no") & name_str(:prt_name_len) // " (mass = " & // trim (adjustl (mass_str)) // " GeV)" if (beam_data%pmatrix(i)%is_polarized ()) then write (u, "(2x,A)") "polarized" else write (u, *) end if end subroutine write_prt end subroutine beam_data_write @ %def beam_data_write @ Return initialization status: <>= procedure :: are_valid => beam_data_are_valid <>= function beam_data_are_valid (beam_data) result (flag) class(beam_data_t), intent(in) :: beam_data logical :: flag flag = beam_data%initialized end function beam_data_are_valid @ %def beam_data_are_valid @ Check whether beam data agree with the current values of relevant parameters. <>= procedure :: check_scattering => beam_data_check_scattering <>= subroutine beam_data_check_scattering (beam_data, sqrts) class(beam_data_t), intent(in) :: beam_data real(default), intent(in), optional :: sqrts if (beam_data_are_valid (beam_data)) then if (present (sqrts)) then if (.not. nearly_equal (sqrts, beam_data%sqrts)) then call msg_error ("Current setting of sqrts is inconsistent " & // "with beam setup (ignored).") end if end if else call msg_bug ("Beam setup: invalid beam data") end if end subroutine beam_data_check_scattering @ %def beam_data_check_scattering @ Return the number of beams (1 for decays, 2 for collisions). <>= procedure :: get_n_in => beam_data_get_n_in <>= function beam_data_get_n_in (beam_data) result (n_in) class(beam_data_t), intent(in) :: beam_data integer :: n_in n_in = beam_data%n end function beam_data_get_n_in @ %def beam_data_get_n_in @ Return the beam flavor <>= procedure :: get_flavor => beam_data_get_flavor <>= function beam_data_get_flavor (beam_data) result (flv) class(beam_data_t), intent(in) :: beam_data type(flavor_t), dimension(:), allocatable :: flv allocate (flv (beam_data%n)) flv = beam_data%flv end function beam_data_get_flavor @ %def beam_data_get_flavor @ Return the beam energies <>= procedure :: get_energy => beam_data_get_energy <>= function beam_data_get_energy (beam_data) result (e) class(beam_data_t), intent(in) :: beam_data real(default), dimension(:), allocatable :: e integer :: i allocate (e (beam_data%n)) if (beam_data%initialized) then do i = 1, beam_data%n e(i) = energy (beam_data%p(i)) end do else e = 0 end if end function beam_data_get_energy @ %def beam_data_get_energy @ Return the c.m.\ energy. <>= procedure :: get_sqrts => beam_data_get_sqrts <>= function beam_data_get_sqrts (beam_data) result (sqrts) class(beam_data_t), intent(in) :: beam_data real(default) :: sqrts sqrts = beam_data%sqrts end function beam_data_get_sqrts @ %def beam_data_get_sqrts @ Return true if the lab and c.m.\ frame are specified as identical. <>= procedure :: cm_frame => beam_data_cm_frame <>= function beam_data_cm_frame (beam_data) result (flag) class(beam_data_t), intent(in) :: beam_data logical :: flag flag = beam_data%lab_is_cm_frame end function beam_data_cm_frame @ %def beam_data_cm_frame @ Return the polarization in case it is just two degrees <>= procedure :: get_polarization => beam_data_get_polarization <>= function beam_data_get_polarization (beam_data) result (pol) class(beam_data_t), intent(in) :: beam_data real(default), dimension(2) :: pol if (beam_data%n /= 2) & call msg_fatal ("Beam data: can only treat scattering processes.") pol = beam_data%pmatrix%get_simple_pol () end function beam_data_get_polarization @ %def beam_data_get_polarization @ <>= procedure :: get_helicity_state_matrix => beam_data_get_helicity_state_matrix <>= function beam_data_get_helicity_state_matrix (beam_data) result (state_hel) type(state_matrix_t) :: state_hel class(beam_data_t), intent(in) :: beam_data type(polarization_t), dimension(:), allocatable :: pol integer :: i allocate (pol (beam_data%n)) do i = 1, beam_data%n call pol(i)%init_pmatrix (beam_data%pmatrix(i)) end do call combine_polarization_states (pol, state_hel) end function beam_data_get_helicity_state_matrix @ %def beam_data_get_helicity_state_matrix @ <>= procedure :: is_initialized => beam_data_is_initialized <>= function beam_data_is_initialized (beam_data) result (initialized) logical :: initialized class(beam_data_t), intent(in) :: beam_data initialized = any (beam_data%pmatrix%exists ()) end function beam_data_is_initialized @ %def beam_data_is_initialized @ Return a MD5 checksum for beam data. If no checksum is present (because beams have not been initialized), compute the checksum of the sqrts value. <>= procedure :: get_md5sum => beam_data_get_md5sum <>= function beam_data_get_md5sum (beam_data, sqrts) result (md5sum_beams) class(beam_data_t), intent(in) :: beam_data real(default), intent(in) :: sqrts character(32) :: md5sum_beams character(80) :: buffer if (beam_data%md5sum /= "") then md5sum_beams = beam_data%md5sum else write (buffer, *) sqrts md5sum_beams = md5sum (buffer) end if end function beam_data_get_md5sum @ %def beam_data_get_md5sum @ \subsection{Initializers: beam structure} Initialize the beam data object from a beam structure object, given energy and model. <>= procedure :: init_structure => beam_data_init_structure <>= subroutine beam_data_init_structure & (beam_data, structure, sqrts, model, decay_rest_frame) class(beam_data_t), intent(out) :: beam_data type(beam_structure_t), intent(in) :: structure integer :: n_beam real(default), intent(in) :: sqrts class(model_data_t), intent(in), target :: model logical, intent(in), optional :: decay_rest_frame type(flavor_t), dimension(:), allocatable :: flv n_beam = structure%get_n_beam () allocate (flv (n_beam)) call flv%init (structure%get_prt (), model) if (structure%asymmetric ()) then if (structure%polarized ()) then call beam_data%init_momenta (structure%get_momenta (), flv, & structure%get_smatrix (), structure%get_pol_f ()) else call beam_data%init_momenta (structure%get_momenta (), flv) end if else select case (n_beam) case (1) if (structure%polarized ()) then call beam_data%init_decay (flv, & structure%get_smatrix (), structure%get_pol_f (), & rest_frame = decay_rest_frame) else call beam_data%init_decay (flv, & rest_frame = decay_rest_frame) end if case (2) if (structure%polarized ()) then call beam_data%init_sqrts (sqrts, flv, & structure%get_smatrix (), structure%get_pol_f ()) else call beam_data%init_sqrts (sqrts, flv) end if case default call msg_bug ("Beam data: invalid beam structure object") end select end if end subroutine beam_data_init_structure @ %def beam_data_init_structure @ \subsection{Initializers: collisions} This is the simplest one: just the two flavors, c.m.\ energy, polarization. Color is inferred from flavor. Beam momenta and c.m.\ momenta coincide. <>= procedure :: init_sqrts => beam_data_init_sqrts <>= subroutine beam_data_init_sqrts (beam_data, sqrts, flv, smatrix, pol_f) class(beam_data_t), intent(out) :: beam_data real(default), intent(in) :: sqrts type(flavor_t), dimension(:), intent(in) :: flv type(smatrix_t), dimension(:), intent(in), optional :: smatrix real(default), dimension(:), intent(in), optional :: pol_f real(default), dimension(size(flv)) :: E, p call beam_data_init (beam_data, size (flv)) beam_data%sqrts = sqrts beam_data%lab_is_cm_frame = .true. select case (beam_data%n) case (1) E = sqrts; p = 0 beam_data%p_cm = vector4_moving (E, p, 3) beam_data%p = beam_data%p_cm case (2) beam_data%p_cm = colliding_momenta (sqrts, flv%get_mass ()) beam_data%p = colliding_momenta (sqrts, flv%get_mass ()) end select call beam_data_finish_initialization (beam_data, flv, smatrix, pol_f) end subroutine beam_data_init_sqrts @ %def beam_data_init_sqrts @ This version sets beam momenta directly, assuming that they are asymmetric, i.e., lab frame and c.m.\ frame do not coincide. Polarization info is deferred to a common initializer. The Lorentz transformation that we compute here is not actually used in the calculation; instead, it will be recomputed for each event in the subroutine [[phs_set_incoming_momenta]]. We compute it here for the nominal beam setup nevertheless, so we can print it and, in particular, include it in the MD5 sum. <>= procedure :: init_momenta => beam_data_init_momenta <>= subroutine beam_data_init_momenta (beam_data, p3, flv, smatrix, pol_f) class(beam_data_t), intent(out) :: beam_data type(vector3_t), dimension(:), intent(in) :: p3 type(flavor_t), dimension(:), intent(in) :: flv type(smatrix_t), dimension(:), intent(in), optional :: smatrix real(default), dimension(:), intent(in), optional :: pol_f type(vector4_t) :: p0 type(vector4_t), dimension(:), allocatable :: p, p_cm_rot real(default), dimension(size(p3)) :: e real(default), dimension(size(flv)) :: m type(lorentz_transformation_t) :: L_boost, L_rot call beam_data_init (beam_data, size (flv)) m = flv%get_mass () e = sqrt (p3 ** 2 + m ** 2) allocate (p (beam_data%n)) p = vector4_moving (e, p3) p0 = sum (p) beam_data%p = p beam_data%lab_is_cm_frame = .false. beam_data%sqrts = p0 ** 1 L_boost = boost (p0, beam_data%sqrts) allocate (p_cm_rot (beam_data%n)) p_cm_rot = inverse (L_boost) * p allocate (beam_data%L_cm_to_lab) select case (beam_data%n) case (1) beam_data%L_cm_to_lab = L_boost beam_data%p_cm = vector4_at_rest (beam_data%sqrts) case (2) L_rot = rotation_to_2nd (3, space_part (p_cm_rot(1))) beam_data%L_cm_to_lab = L_boost * L_rot beam_data%p_cm = & colliding_momenta (beam_data%sqrts, flv%get_mass ()) end select call beam_data_finish_initialization (beam_data, flv, smatrix, pol_f) end subroutine beam_data_init_momenta @ %def beam_data_init_momenta @ Final steps: If requested, rotate the beams in the lab frame, and set the beam-data components. <>= subroutine beam_data_finish_initialization (beam_data, flv, smatrix, pol_f) type(beam_data_t), intent(inout) :: beam_data type(flavor_t), dimension(:), intent(in) :: flv type(smatrix_t), dimension(:), intent(in), optional :: smatrix real(default), dimension(:), intent(in), optional :: pol_f integer :: i do i = 1, beam_data%n beam_data%flv(i) = flv(i) beam_data%mass(i) = flv(i)%get_mass () if (present (smatrix)) then if (size (smatrix) /= beam_data%n) & call msg_fatal ("Beam data: & &polarization density array has wrong dimension") beam_data%pmatrix(i) = smatrix(i) if (present (pol_f)) then if (size (pol_f) /= size (smatrix)) & call msg_fatal ("Beam data: & &polarization fraction array has wrong dimension") call beam_data%pmatrix(i)%normalize (flv(i), pol_f(i)) else call beam_data%pmatrix(i)%normalize (flv(i), 1._default) end if else call beam_data%pmatrix(i)%init (2, 0) call beam_data%pmatrix(i)%normalize (flv(i), 0._default) end if end do call beam_data%compute_md5sum () end subroutine beam_data_finish_initialization @ %def beam_data_finish_initialization @ The MD5 sum is stored within the beam-data record, so it can be checked for integrity in subsequent runs. <>= procedure :: compute_md5sum => beam_data_compute_md5sum <>= subroutine beam_data_compute_md5sum (beam_data) class(beam_data_t), intent(inout) :: beam_data integer :: unit unit = free_unit () open (unit = unit, status = "scratch", action = "readwrite") call beam_data%write (unit, write_md5sum = .false., & verbose = .true.) rewind (unit) beam_data%md5sum = md5sum (unit) close (unit) end subroutine beam_data_compute_md5sum @ %def beam_data_compute_md5sum @ \subsection{Initializers: decays} This is the simplest one: decay in rest frame. We need just flavor and polarization. Color is inferred from flavor. Beam momentum and c.m.\ momentum coincide. <>= procedure :: init_decay => beam_data_init_decay <>= subroutine beam_data_init_decay (beam_data, flv, smatrix, pol_f, rest_frame) class(beam_data_t), intent(out) :: beam_data type(flavor_t), dimension(1), intent(in) :: flv type(smatrix_t), dimension(1), intent(in), optional :: smatrix real(default), dimension(:), intent(in), optional :: pol_f logical, intent(in), optional :: rest_frame real(default), dimension(1) :: m m = flv%get_mass () if (present (smatrix)) then call beam_data%init_sqrts (m(1), flv, smatrix, pol_f) else call beam_data%init_sqrts (m(1), flv, smatrix, pol_f) end if if (present (rest_frame)) beam_data%lab_is_cm_frame = rest_frame end subroutine beam_data_init_decay @ %def beam_data_init_decay @ \subsection{The beams type} Beam objects are interaction objects that contain the actual beam data including polarization and density matrix. For collisions, the beam object actually contains two beams. <>= public :: beam_t <>= type :: beam_t private type(interaction_t) :: int end type beam_t @ %def beam_t @ The constructor contains code that converts beam data into the (entangled) particle-pair quantum state. First, we set the number of particles and polarization mask. (The polarization mask is handed over to all later interactions, so if helicity is diagonal or absent, this fact is used when constructing the hard-interaction events.) Then, we construct the entangled state that combines helicity, flavor and color of the two particles (where flavor and color are unique, while several helicity states are possible). Then, we transfer this state together with the associated values from the spin density matrix into the [[interaction_t]] object. Calling the [[add_state]] method of the interaction object, we keep the entries of the helicity density matrix without adding them up. This ensures that for unpolarized states, we do not normalize but end up with an $1/N$ entry, where $N$ is the initial-state multiplicity. <>= public :: beam_init <>= subroutine beam_init (beam, beam_data) type(beam_t), intent(out) :: beam type(beam_data_t), intent(in), target :: beam_data logical, dimension(beam_data%n) :: polarized, diagonal type(quantum_numbers_mask_t), dimension(beam_data%n) :: mask, mask_d type(state_matrix_t), target :: state_hel, state_fc, state_tmp type(state_iterator_t) :: it_hel, it_tmp type(quantum_numbers_t), dimension(:), allocatable :: qn complex(default) :: value real(default), parameter :: tolerance = 100 * epsilon (1._default) polarized = beam_data%pmatrix%is_polarized () diagonal = beam_data%pmatrix%is_diagonal () mask = quantum_numbers_mask (.false., .false., & mask_h = .not. polarized, & mask_hd = diagonal) mask_d = quantum_numbers_mask (.false., .false., .false., & mask_hd = polarized .and. diagonal) call beam%int%basic_init & (0, 0, beam_data%n, mask = mask, store_values = .true.) state_hel = beam_data%get_helicity_state_matrix () allocate (qn (beam_data%n)) call qn%init (beam_data%flv, color_from_flavor (beam_data%flv, 1)) call state_fc%init () call state_fc%add_state (qn) call merge_state_matrices (state_hel, state_fc, state_tmp) call it_hel%init (state_hel) call it_tmp%init (state_tmp) do while (it_hel%is_valid ()) qn = it_tmp%get_quantum_numbers () value = it_hel%get_matrix_element () if (any (qn%are_redundant (mask_d))) then ! skip off-diagonal elements for diagonal polarization else if (abs (value) <= tolerance) then ! skip zero entries else call beam%int%add_state (qn, value = value) end if call it_hel%advance () call it_tmp%advance () end do call beam%int%freeze () call beam%int%set_momenta (beam_data%p, outgoing = .true.) call state_hel%final () call state_fc%final () call state_tmp%final () end subroutine beam_init @ %def beam_init @ Finalizer: <>= public :: beam_final <>= subroutine beam_final (beam) type(beam_t), intent(inout) :: beam call beam%int%final () end subroutine beam_final @ %def beam_final @ I/O: <>= public :: beam_write <>= subroutine beam_write (beam, unit, verbose, show_momentum_sum, show_mass, col_verbose) type(beam_t), intent(in) :: beam integer, intent(in), optional :: unit logical, intent(in), optional :: verbose, show_momentum_sum, show_mass logical, intent(in), optional :: col_verbose integer :: u u = given_output_unit (unit); if (u < 0) return select case (beam%int%get_n_out ()) case (1); write (u, *) "Decaying particle:" case (2); write (u, *) "Colliding beams:" end select call beam%int%basic_write & (unit, verbose = verbose, show_momentum_sum = & show_momentum_sum, show_mass = show_mass, & col_verbose = col_verbose) end subroutine beam_write @ %def beam_write @ Defined assignment: deep copy <>= public :: assignment(=) <>= interface assignment(=) module procedure beam_assign end interface <>= subroutine beam_assign (beam_out, beam_in) type(beam_t), intent(out) :: beam_out type(beam_t), intent(in) :: beam_in beam_out%int = beam_in%int end subroutine beam_assign @ %def beam_assign @ \subsection{Inherited procedures} <>= public :: interaction_set_source_link <>= interface interaction_set_source_link module procedure interaction_set_source_link_beam end interface <>= subroutine interaction_set_source_link_beam (int, i, beam1, i1) type(interaction_t), intent(inout) :: int type(beam_t), intent(in), target :: beam1 integer, intent(in) :: i, i1 call int%set_source_link (i, beam1%int, i1) end subroutine interaction_set_source_link_beam @ %def interaction_set_source_link_beam @ \subsection{Accessing contents} Return the interaction component -- as a pointer, to avoid any copying. <>= public :: beam_get_int_ptr <>= function beam_get_int_ptr (beam) result (int) type(interaction_t), pointer :: int type(beam_t), intent(in), target :: beam int => beam%int end function beam_get_int_ptr @ %def beam_get_int_ptr @ Set beam momenta directly. (Used for cascade decays.) <>= public :: beam_set_momenta <>= subroutine beam_set_momenta (beam, p) type(beam_t), intent(inout) :: beam type(vector4_t), dimension(:), intent(in) :: p call beam%int%set_momenta (p) end subroutine beam_set_momenta @ %def beam_set_momenta @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[beams_ut.f90]]>>= <> module beams_ut use unit_tests use beams_uti <> <> contains <> end module beams_ut @ %def beams_ut @ <<[[beams_uti.f90]]>>= <> module beams_uti <> use lorentz use flavors use interactions, only: reset_interaction_counter use polarizations, only: smatrix_t use model_data use beam_structures use beams <> <> contains <> end module beams_uti @ %def beams_ut @ API: driver for the unit tests below. <>= public :: beams_test <>= subroutine beams_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine beams_test @ %def beams_test @ Test the basic beam setup. <>= call test (beam_1, "beam_1", & "check basic beam setup", & u, results) <>= public :: beam_1 <>= subroutine beam_1 (u) integer, intent(in) :: u type(beam_data_t), target :: beam_data type(beam_t) :: beam real(default) :: sqrts type(flavor_t), dimension(2) :: flv type(smatrix_t), dimension(2) :: smatrix real(default), dimension(2) :: pol_f type(model_data_t), target :: model write (u, "(A)") "* Test output: beam_1" write (u, "(A)") "* Purpose: test basic beam setup" write (u, "(A)") write (u, "(A)") "* Reading model file" write (u, "(A)") call reset_interaction_counter () call model%init_sm_test () write (u, "(A)") "* Unpolarized scattering, massless fermions" write (u, "(A)") call reset_interaction_counter () sqrts = 500 call flv%init ([1,-1], model) call beam_data%init_sqrts (sqrts, flv) call beam_data%write (u) write (u, "(A)") call beam_init (beam, beam_data) call beam_write (beam, u) call beam_final (beam) call beam_data%final () write (u, "(A)") write (u, "(A)") "* Unpolarized scattering, massless bosons" write (u, "(A)") call reset_interaction_counter () sqrts = 500 call flv%init ([22,22], model) call beam_data%init_sqrts (sqrts, flv) call beam_data%write (u) write (u, "(A)") call beam_init (beam, beam_data) call beam_write (beam, u) call beam_final (beam) call beam_data%final () write (u, "(A)") write (u, "(A)") "* Unpolarized scattering, massive bosons" write (u, "(A)") call reset_interaction_counter () sqrts = 500 call flv%init ([24,-24], model) call beam_data%init_sqrts (sqrts, flv) call beam_data%write (u) write (u, "(A)") call beam_init (beam, beam_data) call beam_write (beam, u) call beam_final (beam) call beam_data%final () write (u, "(A)") write (u, "(A)") "* Polarized scattering, massless fermions" write (u, "(A)") call reset_interaction_counter () sqrts = 500 call flv%init ([1,-1], model) call smatrix(1)%init (2, 1) call smatrix(1)%set_entry (1, [1,1], (1._default, 0._default)) pol_f(1) = 0.5_default call smatrix(2)%init (2, 3) call smatrix(2)%set_entry (1, [1,1], (1._default, 0._default)) call smatrix(2)%set_entry (2, [-1,-1], (1._default, 0._default)) call smatrix(2)%set_entry (3, [-1,1], (1._default, 0._default)) pol_f(2) = 1._default call beam_data%init_sqrts (sqrts, flv, smatrix, pol_f) call beam_data%write (u) write (u, "(A)") call beam_init (beam, beam_data) call beam_write (beam, u) call beam_final (beam) call beam_data%final () write (u, "(A)") write (u, "(A)") "* Semi-polarized scattering, massless bosons" write (u, "(A)") call reset_interaction_counter () sqrts = 500 call flv%init ([22,22], model) call smatrix(1)%init (2, 0) pol_f(1) = 0._default call smatrix(2)%init (2, 1) call smatrix(2)%set_entry (1, [1,1], (1._default, 0._default)) pol_f(2) = 1._default call beam_data%init_sqrts (sqrts, flv, smatrix, pol_f) call beam_data%write (u) write (u, "(A)") call beam_init (beam, beam_data) call beam_write (beam, u) call beam_final (beam) call beam_data%final () write (u, "(A)") write (u, "(A)") "* Semi-polarized scattering, massive bosons" write (u, "(A)") call reset_interaction_counter () sqrts = 500 call flv%init ([24,-24], model) call smatrix(1)%init (2, 0) pol_f(1) = 0._default call smatrix(2)%init (2, 1) call smatrix(2)%set_entry (1, [0,0], (1._default, 0._default)) pol_f(2) = 1._default call beam_data%init_sqrts (sqrts, flv, smatrix, pol_f) call beam_data%write (u) write (u, "(A)") call beam_init (beam, beam_data) call beam_write (beam, u) call beam_final (beam) call beam_data%final () write (u, "(A)") write (u, "(A)") "* Unpolarized decay, massive boson" write (u, "(A)") call reset_interaction_counter () call flv(1)%init (23, model) call beam_data%init_decay (flv(1:1)) call beam_data%write (u) write (u, "(A)") call beam_init (beam, beam_data) call beam_write (beam, u) write (u, "(A)") write (u, "(A)") "* Polarized decay, massive boson" write (u, "(A)") call reset_interaction_counter () call flv(1)%init (23, model) call smatrix(1)%init (2, 1) call smatrix(1)%set_entry (1, [0,0], (1._default, 0._default)) pol_f(1) = 0.4_default call beam_data%init_decay (flv(1:1), smatrix(1:1), pol_f(1:1)) call beam_data%write (u) write (u, "(A)") call beam_init (beam, beam_data) call beam_write (beam, u) write (u, "(A)") write (u, "(A)") "* Cleanup" call beam_final (beam) call beam_data%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: beam_1" end subroutine beam_1 @ %def beam_1 @ Test advanced beam setup. <>= call test (beam_2, "beam_2", & "beam initialization", & u, results) <>= public :: beam_2 <>= subroutine beam_2 (u) integer, intent(in) :: u type(beam_data_t), target :: beam_data type(beam_t) :: beam real(default) :: sqrts type(flavor_t), dimension(2) :: flv integer, dimension(0) :: no_records type(beam_structure_t) :: beam_structure type(model_data_t), target :: model write (u, "(A)") "* Test output: beam_2" write (u, "(A)") "* Purpose: transfer beam polarization using & &beam structure" write (u, "(A)") write (u, "(A)") "* Reading model file" write (u, "(A)") call model%init_sm_test () write (u, "(A)") "* Unpolarized scattering, massless fermions" write (u, "(A)") call reset_interaction_counter () sqrts = 500 call flv%init ([1,-1], model) call beam_structure%init_sf (flv%get_name (), no_records) call beam_structure%final_pol () call beam_structure%write (u) write (u, *) call beam_data%init_structure (beam_structure, sqrts, model) call beam_data%write (u) write (u, "(A)") call beam_init (beam, beam_data) call beam_write (beam, u) call beam_final (beam) call beam_data%final () write (u, "(A)") write (u, "(A)") "* Unpolarized scattering, massless bosons" write (u, "(A)") call reset_interaction_counter () sqrts = 500 call flv%init ([22,22], model) call beam_structure%init_sf (flv%get_name (), no_records) call beam_structure%final_pol () call beam_structure%write (u) write (u, *) call beam_data%init_structure (beam_structure, sqrts, model) call beam_data%write (u) write (u, "(A)") call beam_init (beam, beam_data) call beam_write (beam, u) call beam_final (beam) call beam_data%final () write (u, "(A)") write (u, "(A)") "* Unpolarized scattering, massive bosons" write (u, "(A)") call reset_interaction_counter () sqrts = 500 call flv%init ([24,-24], model) call beam_structure%init_sf (flv%get_name (), no_records) call beam_structure%final_pol () call beam_structure%write (u) write (u, *) call beam_data%init_structure (beam_structure, sqrts, model) call beam_data%write (u) write (u, "(A)") call beam_init (beam, beam_data) call beam_write (beam, u) call beam_final (beam) call beam_data%final () write (u, "(A)") write (u, "(A)") "* Polarized scattering, massless fermions" write (u, "(A)") call reset_interaction_counter () sqrts = 500 call flv%init ([1,-1], model) call beam_structure%init_sf (flv%get_name (), no_records) call beam_structure%init_pol (2) call beam_structure%init_smatrix (1, 1) call beam_structure%set_sentry (1, 1, [1,1], (1._default, 0._default)) call beam_structure%init_smatrix (2, 3) call beam_structure%set_sentry (2, 1, [1,1], (1._default, 0._default)) call beam_structure%set_sentry (2, 2, [-1,-1], (1._default, 0._default)) call beam_structure%set_sentry (2, 3, [-1,1], (1._default, 0._default)) call beam_structure%set_pol_f ([0.5_default, 1._default]) call beam_structure%write (u) write (u, *) call beam_data%init_structure (beam_structure, sqrts, model) call beam_data%write (u) write (u, *) call beam_init (beam, beam_data) call beam_write (beam, u) call beam_final (beam) call beam_data%final () call beam_structure%final_pol () call beam_structure%final_sf () write (u, "(A)") write (u, "(A)") "* Semi-polarized scattering, massless bosons" write (u, "(A)") call reset_interaction_counter () sqrts = 500 call flv%init ([22,22], model) call beam_structure%init_sf (flv%get_name (), no_records) call beam_structure%init_pol (2) call beam_structure%init_smatrix (1, 0) call beam_structure%init_smatrix (2, 1) call beam_structure%set_sentry (2, 1, [1,1], (1._default, 0._default)) call beam_structure%set_pol_f ([0._default, 1._default]) call beam_structure%write (u) write (u, *) call beam_data%init_structure (beam_structure, sqrts, model) call beam_data%write (u) write (u, "(A)") call beam_init (beam, beam_data) call beam_write (beam, u) call beam_final (beam) call beam_data%final () write (u, "(A)") write (u, "(A)") "* Semi-polarized scattering, massive bosons" write (u, "(A)") call reset_interaction_counter () sqrts = 500 call flv%init ([24,-24], model) call beam_structure%init_sf (flv%get_name (), no_records) call beam_structure%init_pol (2) call beam_structure%init_smatrix (1, 0) call beam_structure%init_smatrix (2, 1) call beam_structure%set_sentry (2, 1, [0,0], (1._default, 0._default)) call beam_structure%write (u) write (u, "(A)") call beam_data%init_structure (beam_structure, sqrts, model) call beam_data%write (u) write (u, "(A)") call beam_init (beam, beam_data) call beam_write (beam, u) call beam_final (beam) call beam_data%final () write (u, "(A)") write (u, "(A)") "* Unpolarized decay, massive boson" write (u, "(A)") call reset_interaction_counter () call flv(1)%init (23, model) call beam_structure%init_sf ([flv(1)%get_name ()], no_records) call beam_structure%final_pol () call beam_structure%write (u) write (u, "(A)") call beam_data%init_structure (beam_structure, sqrts, model) call beam_data%write (u) write (u, "(A)") call beam_init (beam, beam_data) call beam_write (beam, u) write (u, "(A)") write (u, "(A)") "* Polarized decay, massive boson" write (u, "(A)") call reset_interaction_counter () call flv(1)%init (23, model) call beam_structure%init_sf ([flv(1)%get_name ()], no_records) call beam_structure%init_pol (1) call beam_structure%init_smatrix (1, 1) call beam_structure%set_sentry (1, 1, [0,0], (1._default, 0._default)) call beam_structure%set_pol_f ([0.4_default]) call beam_structure%write (u) write (u, *) call beam_data%init_structure (beam_structure, sqrts, model) call beam_data%write (u) write (u, "(A)") call beam_init (beam, beam_data) call beam_write (beam, u) write (u, "(A)") write (u, "(A)") "* Cleanup" call beam_final (beam) call beam_data%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: beam_2" end subroutine beam_2 @ %def beam_2 @ Test advanced beam setup, completely arbitrary momenta. <>= call test (beam_3, "beam_3", & "generic beam momenta", & u, results) <>= public :: beam_3 <>= subroutine beam_3 (u) integer, intent(in) :: u type(beam_data_t), target :: beam_data type(beam_t) :: beam type(flavor_t), dimension(2) :: flv integer, dimension(0) :: no_records type(model_data_t), target :: model type(beam_structure_t) :: beam_structure type(vector3_t), dimension(2) :: p3 type(vector4_t), dimension(2) :: p write (u, "(A)") "* Test output: beam_3" write (u, "(A)") "* Purpose: set up beams with generic momenta" write (u, "(A)") write (u, "(A)") "* Reading model file" write (u, "(A)") call reset_interaction_counter () call model%init_sm_test () write (u, "(A)") "* 1: Scattering process" write (u, "(A)") call flv%init ([2212,2212], model) p3(1) = vector3_moving ([5._default, 0._default, 10._default]) p3(2) = -vector3_moving ([1._default, 1._default, -10._default]) call beam_structure%init_sf (flv%get_name (), no_records) call beam_structure%set_momentum (p3 ** 1) call beam_structure%set_theta (polar_angle (p3)) call beam_structure%set_phi (azimuthal_angle (p3)) call beam_structure%write (u) write (u, *) call beam_data%init_structure (beam_structure, 0._default, model) call pacify (beam_data%l_cm_to_lab, 1e-20_default) call beam_data%compute_md5sum () call beam_data%write (u, verbose = .true.) write (u, *) write (u, "(1x,A)") "Beam momenta reconstructed from LT:" p = beam_data%L_cm_to_lab * beam_data%p_cm call pacify (p, 1e-12_default) call vector4_write (p(1), u) call vector4_write (p(2), u) write (u, "(A)") call beam_init (beam, beam_data) call beam_write (beam, u) call beam_final (beam) call beam_data%final () call beam_structure%final_sf () call beam_structure%final_mom () write (u, "(A)") write (u, "(A)") "* 2: Decay" write (u, "(A)") call flv(1)%init (23, model) p3(1) = vector3_moving ([10._default, 5._default, 50._default]) call beam_structure%init_sf ([flv(1)%get_name ()], no_records) call beam_structure%set_momentum ([p3(1) ** 1]) call beam_structure%set_theta ([polar_angle (p3(1))]) call beam_structure%set_phi ([azimuthal_angle (p3(1))]) call beam_structure%write (u) write (u, *) call beam_data%init_structure (beam_structure, 0._default, model) call beam_data%write (u, verbose = .true.) write (u, "(A)") write (u, "(1x,A)") "Beam momentum reconstructed from LT:" p(1) = beam_data%L_cm_to_lab * beam_data%p_cm(1) call pacify (p(1), 1e-12_default) call vector4_write (p(1), u) write (u, "(A)") call beam_init (beam, beam_data) call beam_write (beam, u) write (u, "(A)") write (u, "(A)") "* Cleanup" call beam_final (beam) call beam_data%final () call beam_structure%final_sf () call beam_structure%final_mom () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: beam_3" end subroutine beam_3 @ %def beam_3 @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Tools} This module contains auxiliary procedures that can be accessed by the structure function code. <<[[sf_aux.f90]]>>= <> module sf_aux <> use io_units use constants, only: twopi use numeric_utils use lorentz <> <> <> <> contains <> end module sf_aux @ %def sf_aux @ \subsection{Momentum splitting} Let us consider first an incoming parton with momentum $k$ and invariant mass squared $s=k^2$ that splits into two partons with momenta $q,p$ and invariant masses $t=q^2$ and $u=p^2$. (This is an abuse of the Mandelstam notation. $t$ is actually the momentum transfer, assuming that $p$ is radiated and $q$ initiates the hard process.) The energy is split among the partons such that if $E=k^0$, we have $q^0 = xE$ and $p^0=\bar x E$, where $\bar x\equiv 1-x$. We define the angle $\theta$ as the polar angle of $p$ w.r.t.\ the momentum axis of the incoming momentum $k$. Ignoring azimuthal angle, we can write the four-momenta in the basis $(E,p_T,p_L)$ as \begin{equation} k = \begin{pmatrix} E \\ 0 \\ p \end{pmatrix}, \qquad p = \begin{pmatrix} \bar x E \\ \bar x\bar p\sin\theta \\ \bar x\bar p\cos\theta \end{pmatrix}, \qquad q = \begin{pmatrix} x E \\ -\bar x\bar p\sin\theta \\ p - \bar x\bar p\cos\theta \end{pmatrix}, \end{equation} where the first two mass-shell conditions are \begin{equation} p^2 = E^2 - s, \qquad \bar p^2 = E^2 - \frac{u}{\bar x^2}. \end{equation} The second condition implies that, for positive $u$, $\bar x^2 > u/E^2$, or equivalently \begin{equation} x < 1 - \sqrt{u} / E. \end{equation} We are interested in the third mass-shell conditions: $s$ and $u$ are fixed, so we need $t$ as a function of $\cos\theta$: \begin{equation} t = -2\bar x \left(E^2 - p\bar p\cos\theta\right) + s + u. \end{equation} Solving for $\cos\theta$, we get \begin{equation} \cos\theta = \frac{2\bar x E^2 + t - s - u}{2\bar x p\bar p}. \end{equation} We can compute $\sin\theta$ numerically as $\sin^2\theta=1-\cos^2\theta$, but it is important to reexpress this in view of numerical stability. To this end, we first determine the bounds for $t$. The cosine must be between $-1$ and $1$, so the bounds are \begin{align} t_0 &= -2\bar x\left(E^2 + p\bar p\right) + s + u, \\ t_1 &= -2\bar x\left(E^2 - p\bar p\right) + s + u. \end{align} Computing $\sin^2\theta$ from $\cos\theta$ above, we observe that the numerator is a quadratic polynomial in $t$ which has the zeros $t_0$ and $t_1$, while the common denominator is given by $(2\bar x p\bar p)^2$. Hence, we can write \begin{equation} \sin^2\theta = -\frac{(t - t_0)(t - t_1)}{(2\bar x p\bar p)^2} \qquad\text{and}\qquad \cos\theta = \frac{(t-t_0) + (t-t_1)}{4\bar x p\bar p}, \end{equation} which is free of large cancellations near $t=t_0$ or $t=t_1$. If all is massless, i.e., $s=u=0$, this simplifies to \begin{align} t_0 &= -4\bar x E^2, & t_1 &= 0, \\ \sin^2\theta &= -\frac{t}{\bar x E^2} \left(1 + \frac{t}{4\bar x E^2}\right), & \cos\theta &= 1 + \frac{t}{2\bar x E^2}. \end{align} Here is the implementation. First, we define a container for the kinematical integration limits and some further data. Note: contents are public only for easy access in unit test. <>= public :: splitting_data_t <>= type :: splitting_data_t ! private logical :: collinear = .false. real(default) :: x0 = 0 real(default) :: x1 real(default) :: t0 real(default) :: t1 real(default) :: phi0 = 0 real(default) :: phi1 = twopi real(default) :: E, p, s, u, m2 real(default) :: x, xb, pb real(default) :: t = 0 real(default) :: phi = 0 contains <> end type splitting_data_t @ %def splitting_data_t @ I/O for debugging: <>= procedure :: write => splitting_data_write <>= subroutine splitting_data_write (d, unit) class(splitting_data_t), intent(in) :: d integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit); if (u < 0) return write (u, "(A)") "Splitting data:" write (u, "(2x,A,L1)") "collinear = ", d%collinear 1 format (2x,A,1x,ES15.8) write (u, 1) "x0 =", d%x0 write (u, 1) "x =", d%x write (u, 1) "xb =", d%xb write (u, 1) "x1 =", d%x1 write (u, 1) "t0 =", d%t0 write (u, 1) "t =", d%t write (u, 1) "t1 =", d%t1 write (u, 1) "phi0 =", d%phi0 write (u, 1) "phi =", d%phi write (u, 1) "phi1 =", d%phi1 write (u, 1) "E =", d%E write (u, 1) "p =", d%p write (u, 1) "pb =", d%pb write (u, 1) "s =", d%s write (u, 1) "u =", d%u write (u, 1) "m2 =", d%m2 end subroutine splitting_data_write @ %def splitting_data_write @ \subsection{Constant data} This is the initializer for the data. The input consists of the incoming momentum, its invariant mass squared, and the invariant mass squared of the radiated particle. $m2$ is the \emph{physical} mass squared of the outgoing particle. The $t$ bounds depend on the chosen $x$ value and cannot be determined yet. <>= procedure :: init => splitting_data_init <>= subroutine splitting_data_init (d, k, mk2, mr2, mo2, collinear) class(splitting_data_t), intent(out) :: d type(vector4_t), intent(in) :: k real(default), intent(in) :: mk2, mr2, mo2 logical, intent(in), optional :: collinear if (present (collinear)) d%collinear = collinear d%E = energy (k) d%x1 = 1 - sqrt (max (mr2, 0._default)) / d%E d%p = sqrt (d%E**2 - mk2) d%s = mk2 d%u = mr2 d%m2 = mo2 end subroutine splitting_data_init @ %def splitting_data_init @ Retrieve the $x$ bounds, if needed for $x$ sampling. Generating an $x$ value is done by the caller, since this is the part that depends on the nature of the structure function. <>= procedure :: get_x_bounds => splitting_get_x_bounds <>= function splitting_get_x_bounds (d) result (x) class(splitting_data_t), intent(in) :: d real(default), dimension(2) :: x x = [ d%x0, d%x1 ] end function splitting_get_x_bounds @ %def splitting_get_x_bounds @ Now set the momentum fraction and compute $t_0$ and $t_1$. [The calculation of $t_1$ is subject to numerical problems. The exact formula is ($s=m_i^2$, $u=m_r^2$) \begin{equation} t_1 = -2\bar x E^2 + m_i^2 + m_r^2 + 2\bar x \sqrt{E^2-m_i^2}\,\sqrt{E^2 - m_r^2/\bar x^2}. \end{equation} The structure-function paradigm is useful only if $E\gg m_i,m_r$. In a Taylor expansion for large $E$, the leading term cancels. The expansion of the square roots (to subleading order) yields \begin{equation} t_1 = xm_i^2 - \frac{x}{\bar x}m_r^2. \end{equation} There are two cases of interest: $m_i=m_o$ and $m_r=0$, \begin{equation} t_1 = xm_o^2 \end{equation} and $m_i=m_r$ and $m_o=0$, \begin{equation} t_1 = -\frac{x^2}{\bar x}m_i^2. \end{equation} In both cases, $t_1\leq m_o^2$.] That said, it turns out that taking the $t_1$ evaluation at face value leads to less problems than the approximation. We express the angles in terms of $t-t_0$ and $t-t_1$. Numerical noise in $t_1$ can then be tolerated. <>= procedure :: set_t_bounds => splitting_set_t_bounds <>= elemental subroutine splitting_set_t_bounds (d, x, xb) class(splitting_data_t), intent(inout) :: d real(default), intent(in), optional :: x, xb real(default) :: tp, tm if (present (x)) d%x = x if (present (xb)) d%xb = xb if (vanishes (d%u)) then d%pb = d%E else if (.not. vanishes (d%xb)) then d%pb = sqrt (max (d%E**2 - d%u / d%xb**2, 0._default)) else d%pb = 0 end if end if tp = -2 * d%xb * d%E**2 + d%s + d%u tm = -2 * d%xb * d%p * d%pb d%t0 = tp + tm d%t1 = tp - tm d%t = d%t1 end subroutine splitting_set_t_bounds @ %def splitting_set_t_bounds @ \subsection{Sampling recoil} Compute a value for the momentum transfer $t$, using a random number $r$. We assume a logarithmic distribution for $t-m^2$, corresponding to the propagator $1/(t-m^2)$ with the physical mass $m$ for the outgoing particle. Optionally, we can narrow the kinematical bounds. If all three masses in the splitting vanish, the upper limit for $t$ is zero. In that case, the $t$ value is set to zero and the splitting will be collinear. <>= procedure :: sample_t => splitting_sample_t <>= subroutine splitting_sample_t (d, r, t0, t1) class(splitting_data_t), intent(inout) :: d real(default), intent(in) :: r real(default), intent(in), optional :: t0, t1 real(default) :: tt0, tt1, tt0m, tt1m if (d%collinear) then d%t = d%t1 else tt0 = d%t0; if (present (t0)) tt0 = max (t0, tt0) tt1 = d%t1; if (present (t1)) tt1 = min (t1, tt1) tt0m = tt0 - d%m2 tt1m = tt1 - d%m2 if (tt0m < 0 .and. tt1m < 0 .and. abs(tt0m) > & epsilon(tt0m) .and. abs(tt1m) > epsilon(tt0m)) then d%t = d%m2 + tt0m * exp (r * log (tt1m / tt0m)) else d%t = tt1 end if end if end subroutine splitting_sample_t @ %def splitting_sample_t @ The inverse operation: Given $t$, we recover the value of $r$ that would have produced this value. <>= procedure :: inverse_t => splitting_inverse_t <>= subroutine splitting_inverse_t (d, r, t0, t1) class(splitting_data_t), intent(in) :: d real(default), intent(out) :: r real(default), intent(in), optional :: t0, t1 real(default) :: tt0, tt1, tt0m, tt1m if (d%collinear) then r = 0 else tt0 = d%t0; if (present (t0)) tt0 = max (t0, tt0) tt1 = d%t1; if (present (t1)) tt1 = min (t1, tt1) tt0m = tt0 - d%m2 tt1m = tt1 - d%m2 if (tt0m < 0 .and. tt1m < 0) then r = log ((d%t - d%m2) / tt0m) / log (tt1m / tt0m) else r = 0 end if end if end subroutine splitting_inverse_t @ %def splitting_inverse_t @ This is trivial, but provided for convenience: <>= procedure :: sample_phi => splitting_sample_phi <>= subroutine splitting_sample_phi (d, r) class(splitting_data_t), intent(inout) :: d real(default), intent(in) :: r if (d%collinear) then d%phi = 0 else d%phi = (1-r) * d%phi0 + r * d%phi1 end if end subroutine splitting_sample_phi @ %def splitting_sample_phi @ Inverse: <>= procedure :: inverse_phi => splitting_inverse_phi <>= subroutine splitting_inverse_phi (d, r) class(splitting_data_t), intent(in) :: d real(default), intent(out) :: r if (d%collinear) then r = 0 else r = (d%phi - d%phi0) / (d%phi1 - d%phi0) end if end subroutine splitting_inverse_phi @ %def splitting_inverse_phi @ \subsection{Splitting} In this function, we actually perform the splitting. The incoming momentum $k$ is split into (if no recoil) $q_1=(1-x)k$ and $q_2=xk$. Apart from the splitting data, we need the incoming momentum $k$, the momentum transfer $t$, and the azimuthal angle $\phi$. The momentum fraction $x$ is already known here. Alternatively, we can split without recoil. The azimuthal angle is irrelevant, and the momentum transfer is always equal to the upper limit $t_1$, so the polar angle is zero. Obviously, if there are nonzero masses it is not possible to keep both energy-momentum conservation and at the same time all particles on shell. We choose for dropping the on-shell condition here. <>= procedure :: split_momentum => splitting_split_momentum <>= function splitting_split_momentum (d, k) result (q) class(splitting_data_t), intent(in) :: d type(vector4_t), dimension(2) :: q type(vector4_t), intent(in) :: k real(default) :: st2, ct2, st, ct, cp, sp type(lorentz_transformation_t) :: rot real(default) :: tt0, tt1, den type(vector3_t) :: kk, q1, q2 if (d%collinear) then if (vanishes (d%s) .and. vanishes(d%u)) then q(1) = d%xb * k q(2) = d%x * k else kk = space_part (k) q1 = d%xb * (d%pb / d%p) * kk q2 = kk - q1 q(1) = vector4_moving (d%xb * d%E, q1) q(2) = vector4_moving (d%x * d%E, q2) end if else den = 2 * d%xb * d%p * d%pb tt0 = max (d%t - d%t0, 0._default) tt1 = min (d%t - d%t1, 0._default) if (den**2 <= epsilon(den)) then st2 = 0 else st2 = - (tt0 * tt1) / den ** 2 end if if (st2 > 1) then st2 = 1 end if ct2 = 1 - st2 st = sqrt (max (st2, 0._default)) ct = sqrt (max (ct2, 0._default)) if ((d%t - d%t0 + d%t - d%t1) < 0) then ct = - ct end if sp = sin (d%phi) cp = cos (d%phi) rot = rotation_to_2nd (3, space_part (k)) q1 = vector3_moving (d%xb * d%pb * [st * cp, st * sp, ct]) q2 = vector3_moving (d%p, 3) - q1 q(1) = rot * vector4_moving (d%xb * d%E, q1) q(2) = rot * vector4_moving (d%x * d%E, q2) end if end function splitting_split_momentum @ %def splitting_split_momentum @ Momenta generated by splitting will in general be off-shell. They are on-shell only if they are collinear and massless. This subroutine puts them on shell by brute force, violating either momentum or energy conservation. The direction of three-momentum is always retained. If the energy is below mass shell, we return a zero momentum. <>= integer, parameter, public :: KEEP_ENERGY = 0, KEEP_MOMENTUM = 1 @ %def KEEP_ENERGY KEEP_MOMENTUM <>= public :: on_shell <>= elemental subroutine on_shell (p, m2, keep) type(vector4_t), intent(inout) :: p real(default), intent(in) :: m2 integer, intent(in) :: keep real(default) :: E, E2, pn select case (keep) case (KEEP_ENERGY) E = energy (p) E2 = E ** 2 if (E2 >= m2) then pn = sqrt (E2 - m2) p = vector4_moving (E, pn * direction (space_part (p))) else p = vector4_null end if case (KEEP_MOMENTUM) E = sqrt (space_part (p) ** 2 + m2) p = vector4_moving (E, space_part (p)) end select end subroutine on_shell @ %def on_shell @ \subsection{Recovering the splitting} This is the inverse problem. We have on-shell momenta and want to deduce the splitting parameters $x$, $t$, and $\phi$. Update 2018-08-22: As a true inverse to [[splitting_split_momentum]], we now use not just a single momentum [[q2]] as before, but the momentum pair [[q1]], [[q2]] for recovering $x$ and $\bar x$ separately. If $x$ happens to be close to $1$, we would completely lose the tiny $\bar x$ value, otherwise, and thus get a meaningless result. <>= procedure :: recover => splitting_recover <>= subroutine splitting_recover (d, k, q, keep) class(splitting_data_t), intent(inout) :: d type(vector4_t), intent(in) :: k type(vector4_t), dimension(2), intent(in) :: q integer, intent(in) :: keep type(lorentz_transformation_t) :: rot type(vector4_t) :: k0 type(vector4_t), dimension(2) :: q0 real(default) :: p1, p2, p3, pt2, pp2, pl real(default) :: aux, den, norm real(default) :: st2, ct2, ct rot = inverse (rotation_to_2nd (3, space_part (k))) q0 = rot * q p1 = vector4_get_component (q0(2), 1) p2 = vector4_get_component (q0(2), 2) p3 = vector4_get_component (q0(2), 3) pt2 = p1 ** 2 + p2 ** 2 pp2 = p1 ** 2 + p2 ** 2 + p3 ** 2 pl = abs (p3) k0 = vector4_moving (d%E, d%p, 3) select case (keep) case (KEEP_ENERGY) d%x = energy (q0(2)) / d%E d%xb = energy (q0(1)) / d%E call d%set_t_bounds () if (.not. d%collinear) then aux = (d%xb * d%pb) ** 2 * pp2 - d%p ** 2 * pt2 den = d%p ** 2 - (d%xb * d%pb) ** 2 if (aux >= 0 .and. den > 0) then norm = (d%p * pl + sqrt (aux)) / den else norm = 1 end if end if case (KEEP_MOMENTUM) d%xb = sqrt (space_part (q0(1)) ** 2 + d%u) / d%E d%x = 1 - d%xb call d%set_t_bounds () norm = 1 end select if (d%collinear) then d%t = d%t1 d%phi = 0 else if ((d%xb * d%pb * norm)**2 < epsilon(d%xb)) then st2 = 1 else st2 = pt2 / (d%xb * d%pb * norm ) ** 2 end if if (st2 > 1) then st2 = 1 end if ct2 = 1 - st2 ct = sqrt (max (ct2, 0._default)) if (.not. vanishes (1 + ct)) then d%t = d%t1 - 2 * d%xb * d%p * d%pb * st2 / (1 + ct) else d%t = d%t0 end if if (.not. vanishes (p1) .or. .not. vanishes (p2)) then d%phi = atan2 (-p2, -p1) else d%phi = 0 end if end if end subroutine splitting_recover @ %def splitting_recover @ \subsection{Extract data} <>= procedure :: get_x => splitting_get_x procedure :: get_xb => splitting_get_xb <>= function splitting_get_x (sd) result (x) class(splitting_data_t), intent(in) :: sd real(default) :: x x = sd%x end function splitting_get_x function splitting_get_xb (sd) result (xb) class(splitting_data_t), intent(in) :: sd real(default) :: xb xb = sd%xb end function splitting_get_xb @ %def splitting_get_x @ %def splitting_get_xb @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[sf_aux_ut.f90]]>>= <> module sf_aux_ut use unit_tests use sf_aux_uti <> <> contains <> end module sf_aux_ut @ %def sf_aux_ut @ <<[[sf_aux_uti.f90]]>>= <> module sf_aux_uti <> use lorentz use sf_aux <> <> contains <> end module sf_aux_uti @ %def sf_aux_ut @ API: driver for the unit tests below. <>= public :: sf_aux_test <>= subroutine sf_aux_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine sf_aux_test @ %def sf_aux_test @ \subsubsection{Momentum splitting: massless radiation} Compute momentum splitting for generic kinematics. It turns out that for $x=0.5$, where $t-m^2$ is the geometric mean between its upper and lower bounds (this can be directly seen from the logarithmic distribution in the function [[sample_t]] for $r \equiv x = 1 - x = 0.5$), we arrive at an exact number $t=-0.15$ for the given input values. <>= call test (sf_aux_1, "sf_aux_1", & "massless radiation", & u, results) <>= public :: sf_aux_1 <>= subroutine sf_aux_1 (u) integer, intent(in) :: u type(splitting_data_t) :: sd type(vector4_t) :: k type(vector4_t), dimension(2) :: q, q0 real(default) :: E, mk, mp, mq real(default) :: x, r1, r2, r1o, r2o real(default) :: k2, q0_2, q1_2, q2_2 write (u, "(A)") "* Test output: sf_aux_1" write (u, "(A)") "* Purpose: compute momentum splitting" write (u, "(A)") " (massless radiated particle)" write (u, "(A)") E = 1 mk = 0.3_default mp = 0 mq = mk k = vector4_moving (E, sqrt (E**2 - mk**2), 3) k2 = k ** 2; call pacify (k2, 1e-10_default) x = 0.6_default r1 = 0.5_default r2 = 0.125_default write (u, "(A)") "* (1) Non-collinear setup" write (u, "(A)") call sd%init (k, mk**2, mp**2, mq**2) call sd%set_t_bounds (x, 1 - x) call sd%sample_t (r1) call sd%sample_phi (r2) call sd%write (u) q = sd%split_momentum (k) q1_2 = q(1) ** 2; call pacify (q1_2, 1e-10_default) q2_2 = q(2) ** 2; call pacify (q2_2, 1e-10_default) write (u, "(A)") write (u, "(A)") "Incoming momentum k =" call vector4_write (k, u) write (u, "(A)") write (u, "(A)") "Outgoing momentum sum p + q =" call vector4_write (sum (q), u) write (u, "(A)") write (u, "(A)") "Radiated momentum p =" call vector4_write (q(1), u) write (u, "(A)") write (u, "(A)") "Outgoing momentum q =" call vector4_write (q(2), u) write (u, "(A)") write (u, "(A)") "Compare: s" write (u, "(2(1x,F11.8))") sd%s, k2 write (u, "(A)") "Compare: t" write (u, "(2(1x,F11.8))") sd%t, q2_2 write (u, "(A)") "Compare: u" write (u, "(2(1x,F11.8))") sd%u, q1_2 write (u, "(A)") "Compare: x" write (u, "(2(1x,F11.8))") sd%x, energy (q(2)) / energy (k) write (u, "(A)") "Compare: 1-x" write (u, "(2(1x,F11.8))") sd%xb, energy (q(1)) / energy (k) write (u, "(A)") write (u, "(A)") "Extract: x, 1-x" write (u, "(2(1x,F11.8))") sd%get_x (), sd%get_xb () write (u, "(A)") write (u, "(A)") "* Project on-shell (keep energy)" q0 = q call on_shell (q0, [mp**2, mq**2], KEEP_ENERGY) write (u, "(A)") write (u, "(A)") "Incoming momentum k =" call vector4_write (k, u) write (u, "(A)") write (u, "(A)") "Outgoing momentum sum p + q =" call vector4_write (sum (q0), u) write (u, "(A)") write (u, "(A)") "Radiated momentum p =" call vector4_write (q0(1), u) write (u, "(A)") write (u, "(A)") "Outgoing momentum q =" call vector4_write (q0(2), u) write (u, "(A)") write (u, "(A)") "Compare: mo^2" q0_2 = q0(2) ** 2; call pacify (q0_2, 1e-10_default) write (u, "(2(1x,F11.8))") sd%m2, q0_2 write (u, "(A)") write (u, "(A)") "* Recover parameters from outgoing momentum" write (u, "(A)") call sd%init (k, mk**2, mp**2, mq**2) call sd%recover (k, q0, KEEP_ENERGY) write (u, "(A)") "Compare: x" write (u, "(2(1x,F11.8))") x, sd%x write (u, "(A)") "Compare: t" write (u, "(2(1x,F11.8))") q2_2, sd%t call sd%inverse_t (r1o) write (u, "(A)") "Compare: r1" write (u, "(2(1x,F11.8))") r1, r1o call sd%inverse_phi (r2o) write (u, "(A)") "Compare: r2" write (u, "(2(1x,F11.8))") r2, r2o write (u, "(A)") call sd%write (u) write (u, "(A)") write (u, "(A)") "* Project on-shell (keep momentum)" q0 = q call on_shell (q0, [mp**2, mq**2], KEEP_MOMENTUM) write (u, "(A)") write (u, "(A)") "Incoming momentum k =" call vector4_write (k, u) write (u, "(A)") write (u, "(A)") "Outgoing momentum sum p + q =" call vector4_write (sum (q0), u) write (u, "(A)") write (u, "(A)") "Radiated momentum p =" call vector4_write (q0(1), u) write (u, "(A)") write (u, "(A)") "Outgoing momentum q =" call vector4_write (q0(2), u) write (u, "(A)") write (u, "(A)") "Compare: mo^2" q0_2 = q0(2) ** 2; call pacify (q0_2, 1e-10_default) write (u, "(2(1x,F11.8))") sd%m2, q0_2 write (u, "(A)") write (u, "(A)") "* Recover parameters from outgoing momentum" write (u, "(A)") call sd%init (k, mk**2, mp**2, mq**2) call sd%recover (k, q0, KEEP_MOMENTUM) write (u, "(A)") "Compare: x" write (u, "(2(1x,F11.8))") x, sd%x write (u, "(A)") "Compare: t" write (u, "(2(1x,F11.8))") q2_2, sd%t call sd%inverse_t (r1o) write (u, "(A)") "Compare: r1" write (u, "(2(1x,F11.8))") r1, r1o call sd%inverse_phi (r2o) write (u, "(A)") "Compare: r2" write (u, "(2(1x,F11.8))") r2, r2o write (u, "(A)") call sd%write (u) write (u, "(A)") write (u, "(A)") "* (2) Collinear setup" write (u, "(A)") call sd%init (k, mk**2, mp**2, mq**2, collinear = .true.) call sd%set_t_bounds (x, 1 - x) call sd%write (u) q = sd%split_momentum (k) q1_2 = q(1) ** 2; call pacify (q1_2, 1e-10_default) q2_2 = q(2) ** 2; call pacify (q2_2, 1e-10_default) write (u, "(A)") write (u, "(A)") "Incoming momentum k =" call vector4_write (k, u) write (u, "(A)") write (u, "(A)") "Outgoing momentum sum p + q =" call vector4_write (sum (q), u) write (u, "(A)") write (u, "(A)") "Radiated momentum p =" call vector4_write (q(1), u) write (u, "(A)") write (u, "(A)") "Outgoing momentum q =" call vector4_write (q(2), u) write (u, "(A)") write (u, "(A)") "Compare: s" write (u, "(2(1x,F11.8))") sd%s, k2 write (u, "(A)") "Compare: t" write (u, "(2(1x,F11.8))") sd%t, q2_2 write (u, "(A)") "Compare: u" write (u, "(2(1x,F11.8))") sd%u, q1_2 write (u, "(A)") "Compare: x" write (u, "(2(1x,F11.8))") sd%x, energy (q(2)) / energy (k) write (u, "(A)") "Compare: 1-x" write (u, "(2(1x,F11.8))") sd%xb, energy (q(1)) / energy (k) write (u, "(A)") write (u, "(A)") "* Project on-shell (keep energy)" q0 = q call on_shell (q0, [mp**2, mq**2], KEEP_ENERGY) write (u, "(A)") write (u, "(A)") "Incoming momentum k =" call vector4_write (k, u) write (u, "(A)") write (u, "(A)") "Outgoing momentum sum p + q =" call vector4_write (sum (q0), u) write (u, "(A)") write (u, "(A)") "Radiated momentum p =" call vector4_write (q0(1), u) write (u, "(A)") write (u, "(A)") "Outgoing momentum q =" call vector4_write (q0(2), u) write (u, "(A)") write (u, "(A)") "Compare: mo^2" q0_2 = q0(2) ** 2; call pacify (q0_2, 1e-10_default) write (u, "(2(1x,F11.8))") sd%m2, q0_2 write (u, "(A)") write (u, "(A)") "* Recover parameters from outgoing momentum" write (u, "(A)") call sd%init (k, mk**2, mp**2, mq**2) call sd%recover (k, q0, KEEP_ENERGY) write (u, "(A)") "Compare: x" write (u, "(2(1x,F11.8))") x, sd%x write (u, "(A)") "Compare: t" write (u, "(2(1x,F11.8))") q2_2, sd%t write (u, "(A)") call sd%write (u) write (u, "(A)") write (u, "(A)") "* Project on-shell (keep momentum)" q0 = q call on_shell (q0, [mp**2, mq**2], KEEP_MOMENTUM) write (u, "(A)") write (u, "(A)") "Incoming momentum k =" call vector4_write (k, u) write (u, "(A)") write (u, "(A)") "Outgoing momentum sum p + q =" call vector4_write (sum (q0), u) write (u, "(A)") write (u, "(A)") "Radiated momentum p =" call vector4_write (q0(1), u) write (u, "(A)") write (u, "(A)") "Outgoing momentum q =" call vector4_write (q0(2), u) write (u, "(A)") write (u, "(A)") "Compare: mo^2" q0_2 = q0(2) ** 2; call pacify (q0_2, 1e-10_default) write (u, "(2(1x,F11.8))") sd%m2, q0_2 write (u, "(A)") write (u, "(A)") "* Recover parameters from outgoing momentum" write (u, "(A)") call sd%init (k, mk**2, mp**2, mq**2) call sd%recover (k, q0, KEEP_MOMENTUM) write (u, "(A)") "Compare: x" write (u, "(2(1x,F11.8))") x, sd%x write (u, "(A)") "Compare: t" write (u, "(2(1x,F11.8))") q2_2, sd%t write (u, "(A)") call sd%write (u) write (u, "(A)") write (u, "(A)") "* Test output end: sf_aux_1" end subroutine sf_aux_1 @ %def sf_aux_1 @ \subsubsection{Momentum splitting: massless parton} Compute momentum splitting for generic kinematics. It turns out that for $x=0.5$, where $t-m^2$ is the geometric mean between its upper and lower bounds, we arrive at an exact number $t=-0.36$ for the given input values. <>= call test (sf_aux_2, "sf_aux_2", & "massless parton", & u, results) <>= public :: sf_aux_2 <>= subroutine sf_aux_2 (u) integer, intent(in) :: u type(splitting_data_t) :: sd type(vector4_t) :: k type(vector4_t), dimension(2) :: q, q0 real(default) :: E, mk, mp, mq real(default) :: x, r1, r2, r1o, r2o real(default) :: k2, q02_2, q1_2, q2_2 write (u, "(A)") "* Test output: sf_aux_2" write (u, "(A)") "* Purpose: compute momentum splitting" write (u, "(A)") " (massless outgoing particle)" write (u, "(A)") E = 1 mk = 0.3_default mp = mk mq = 0 k = vector4_moving (E, sqrt (E**2 - mk**2), 3) k2 = k ** 2; call pacify (k2, 1e-10_default) x = 0.6_default r1 = 0.5_default r2 = 0.125_default write (u, "(A)") "* (1) Non-collinear setup" write (u, "(A)") call sd%init (k, mk**2, mp**2, mq**2) call sd%set_t_bounds (x, 1 - x) call sd%sample_t (r1) call sd%sample_phi (r2) call sd%write (u) q = sd%split_momentum (k) q1_2 = q(1) ** 2; call pacify (q1_2, 1e-10_default) q2_2 = q(2) ** 2; call pacify (q2_2, 1e-10_default) write (u, "(A)") write (u, "(A)") "Incoming momentum k =" call vector4_write (k, u) write (u, "(A)") write (u, "(A)") "Outgoing momentum sum p + q =" call vector4_write (sum (q), u) write (u, "(A)") write (u, "(A)") "Radiated momentum p =" call vector4_write (q(1), u) write (u, "(A)") write (u, "(A)") "Outgoing momentum q =" call vector4_write (q(2), u) write (u, "(A)") write (u, "(A)") "Compare: s" write (u, "(2(1x,F11.8))") sd%s, k2 write (u, "(A)") "Compare: t" write (u, "(2(1x,F11.8))") sd%t, q2_2 write (u, "(A)") "Compare: u" write (u, "(2(1x,F11.8))") sd%u, q1_2 write (u, "(A)") "Compare: x" write (u, "(2(1x,F11.8))") sd%x, energy (q(2)) / energy (k) write (u, "(A)") "Compare: 1-x" write (u, "(2(1x,F11.8))") sd%xb, energy (q(1)) / energy (k) write (u, "(A)") write (u, "(A)") "* Project on-shell (keep energy)" q0 = q call on_shell (q0, [mp**2, mq**2], KEEP_ENERGY) write (u, "(A)") write (u, "(A)") "Incoming momentum k =" call vector4_write (k, u) write (u, "(A)") write (u, "(A)") "Outgoing momentum sum p + q =" call vector4_write (sum (q0), u) write (u, "(A)") write (u, "(A)") "Radiated momentum p =" call vector4_write (q0(1), u) write (u, "(A)") write (u, "(A)") "Outgoing momentum q =" call vector4_write (q0(2), u) write (u, "(A)") write (u, "(A)") "Compare: mo^2" q02_2 = q0(2) ** 2; call pacify (q02_2, 1e-10_default) write (u, "(2(1x,F11.8))") sd%m2, q02_2 write (u, "(A)") write (u, "(A)") "* Recover parameters from outgoing momentum" write (u, "(A)") call sd%init (k, mk**2, mp**2, mq**2) call sd%set_t_bounds (x, 1 - x) call sd%recover (k, q0, KEEP_ENERGY) write (u, "(A)") "Compare: x" write (u, "(2(1x,F11.8))") x, sd%x write (u, "(A)") "Compare: t" write (u, "(2(1x,F11.8))") q2_2, sd%t call sd%inverse_t (r1o) write (u, "(A)") "Compare: r1" write (u, "(2(1x,F11.8))") r1, r1o call sd%inverse_phi (r2o) write (u, "(A)") "Compare: r2" write (u, "(2(1x,F11.8))") r2, r2o write (u, "(A)") call sd%write (u) write (u, "(A)") write (u, "(A)") "* Project on-shell (keep momentum)" q0 = q call on_shell (q0, [mp**2, mq**2], KEEP_MOMENTUM) write (u, "(A)") write (u, "(A)") "Incoming momentum k =" call vector4_write (k, u) write (u, "(A)") write (u, "(A)") "Outgoing momentum sum p + q =" call vector4_write (sum (q0), u) write (u, "(A)") write (u, "(A)") "Radiated momentum p =" call vector4_write (q0(1), u) write (u, "(A)") write (u, "(A)") "Outgoing momentum q =" call vector4_write (q0(2), u) write (u, "(A)") write (u, "(A)") "Compare: mo^2" q02_2 = q0(2) ** 2; call pacify (q02_2, 1e-10_default) write (u, "(2(1x,F11.8))") sd%m2, q02_2 write (u, "(A)") write (u, "(A)") "* Recover parameters from outgoing momentum" write (u, "(A)") call sd%init (k, mk**2, mp**2, mq**2) call sd%set_t_bounds (x, 1 - x) call sd%recover (k, q0, KEEP_MOMENTUM) write (u, "(A)") "Compare: x" write (u, "(2(1x,F11.8))") x, sd%x write (u, "(A)") "Compare: t" write (u, "(2(1x,F11.8))") q2_2, sd%t call sd%inverse_t (r1o) write (u, "(A)") "Compare: r1" write (u, "(2(1x,F11.8))") r1, r1o call sd%inverse_phi (r2o) write (u, "(A)") "Compare: r2" write (u, "(2(1x,F11.8))") r2, r2o write (u, "(A)") call sd%write (u) write (u, "(A)") write (u, "(A)") "* (2) Collinear setup" write (u, "(A)") call sd%init (k, mk**2, mp**2, mq**2, collinear = .true.) call sd%set_t_bounds (x, 1 - x) call sd%write (u) q = sd%split_momentum (k) q1_2 = q(1) ** 2; call pacify (q1_2, 1e-10_default) q2_2 = q(2) ** 2; call pacify (q2_2, 1e-10_default) write (u, "(A)") write (u, "(A)") "Incoming momentum k =" call vector4_write (k, u) write (u, "(A)") write (u, "(A)") "Outgoing momentum sum p + q =" call vector4_write (sum (q), u) write (u, "(A)") write (u, "(A)") "Radiated momentum p =" call vector4_write (q(1), u) write (u, "(A)") write (u, "(A)") "Outgoing momentum q =" call vector4_write (q(2), u) write (u, "(A)") write (u, "(A)") "Compare: s" write (u, "(2(1x,F11.8))") sd%s, k2 write (u, "(A)") "Compare: t" write (u, "(2(1x,F11.8))") sd%t, q2_2 write (u, "(A)") "Compare: u" write (u, "(2(1x,F11.8))") sd%u, q1_2 write (u, "(A)") "Compare: x" write (u, "(2(1x,F11.8))") sd%x, energy (q(2)) / energy (k) write (u, "(A)") "Compare: 1-x" write (u, "(2(1x,F11.8))") sd%xb, energy (q(1)) / energy (k) write (u, "(A)") write (u, "(A)") "* Project on-shell (keep energy)" q0 = q call on_shell (q0, [mp**2, mq**2], KEEP_ENERGY) write (u, "(A)") write (u, "(A)") "Incoming momentum k =" call vector4_write (k, u) write (u, "(A)") write (u, "(A)") "Outgoing momentum sum p + q =" call vector4_write (sum (q0), u) write (u, "(A)") write (u, "(A)") "Radiated momentum p =" call vector4_write (q0(1), u) write (u, "(A)") write (u, "(A)") "Outgoing momentum q =" call vector4_write (q0(2), u) write (u, "(A)") write (u, "(A)") "Compare: mo^2" q02_2 = q0(2) ** 2; call pacify (q02_2, 1e-10_default) write (u, "(2(1x,F11.8))") sd%m2, q02_2 write (u, "(A)") write (u, "(A)") "* Recover parameters from outgoing momentum" write (u, "(A)") call sd%init (k, mk**2, mp**2, mq**2) call sd%set_t_bounds (x, 1 - x) call sd%recover (k, q0, KEEP_ENERGY) write (u, "(A)") "Compare: x" write (u, "(2(1x,F11.8))") x, sd%x write (u, "(A)") "Compare: t" write (u, "(2(1x,F11.8))") q2_2, sd%t write (u, "(A)") call sd%write (u) write (u, "(A)") write (u, "(A)") "* Project on-shell (keep momentum)" q0 = q call on_shell (q0, [mp**2, mq**2], KEEP_MOMENTUM) write (u, "(A)") write (u, "(A)") "Incoming momentum k =" call vector4_write (k, u) write (u, "(A)") write (u, "(A)") "Outgoing momentum sum p + q =" call vector4_write (sum (q0), u) write (u, "(A)") write (u, "(A)") "Radiated momentum p =" call vector4_write (q0(1), u) write (u, "(A)") write (u, "(A)") "Outgoing momentum q =" call vector4_write (q0(2), u) write (u, "(A)") write (u, "(A)") "Compare: mo^2" q02_2 = q0(2) ** 2; call pacify (q02_2, 1e-10_default) write (u, "(2(1x,F11.8))") sd%m2, q02_2 write (u, "(A)") write (u, "(A)") "* Recover parameters from outgoing momentum" write (u, "(A)") call sd%init (k, mk**2, mp**2, mq**2) call sd%set_t_bounds (x, 1 - x) call sd%recover (k, q0, KEEP_MOMENTUM) write (u, "(A)") "Compare: x" write (u, "(2(1x,F11.8))") x, sd%x write (u, "(A)") "Compare: t" write (u, "(2(1x,F11.8))") q2_2, sd%t write (u, "(A)") call sd%write (u) write (u, "(A)") write (u, "(A)") "* Test output end: sf_aux_2" end subroutine sf_aux_2 @ %def sf_aux_2 @ \subsubsection{Momentum splitting: all massless} Compute momentum splitting for massless kinematics. In the non-collinear case, we need a lower cutoff for $|t|$, otherwise a logarithmic distribution is not possible. <>= call test (sf_aux_3, "sf_aux_3", & "massless parton", & u, results) <>= public :: sf_aux_3 <>= subroutine sf_aux_3 (u) integer, intent(in) :: u type(splitting_data_t) :: sd type(vector4_t) :: k type(vector4_t), dimension(2) :: q, q0 real(default) :: E, mk, mp, mq, qmin, qmax real(default) :: x, r1, r2, r1o, r2o real(default) :: k2, q02_2, q1_2, q2_2 write (u, "(A)") "* Test output: sf_aux_3" write (u, "(A)") "* Purpose: compute momentum splitting" write (u, "(A)") " (all massless, q cuts)" write (u, "(A)") E = 1 mk = 0 mp = 0 mq = 0 qmin = 1e-2_default qmax = 1e0_default k = vector4_moving (E, sqrt (E**2 - mk**2), 3) k2 = k ** 2; call pacify (k2, 1e-10_default) x = 0.6_default r1 = 0.5_default r2 = 0.125_default write (u, "(A)") "* (1) Non-collinear setup" write (u, "(A)") call sd%init (k, mk**2, mp**2, mq**2) call sd%set_t_bounds (x, 1 - x) call sd%sample_t (r1, t1 = - qmin ** 2, t0 = - qmax **2) call sd%sample_phi (r2) call sd%write (u) q = sd%split_momentum (k) q1_2 = q(1) ** 2; call pacify (q1_2, 1e-10_default) q2_2 = q(2) ** 2; call pacify (q2_2, 1e-10_default) write (u, "(A)") write (u, "(A)") "Incoming momentum k =" call vector4_write (k, u) write (u, "(A)") write (u, "(A)") "Outgoing momentum sum p + q =" call vector4_write (sum (q), u) write (u, "(A)") write (u, "(A)") "Radiated momentum p =" call vector4_write (q(1), u) write (u, "(A)") write (u, "(A)") "Outgoing momentum q =" call vector4_write (q(2), u) write (u, "(A)") write (u, "(A)") "Compare: s" write (u, "(2(1x,F11.8))") sd%s, k2 write (u, "(A)") "Compare: t" write (u, "(2(1x,F11.8))") sd%t, q2_2 write (u, "(A)") "Compare: u" write (u, "(2(1x,F11.8))") sd%u, q1_2 write (u, "(A)") "Compare: x" write (u, "(2(1x,F11.8))") sd%x, energy (q(2)) / energy (k) write (u, "(A)") "Compare: 1-x" write (u, "(2(1x,F11.8))") sd%xb, energy (q(1)) / energy (k) write (u, "(A)") write (u, "(A)") "* Project on-shell (keep energy)" q0 = q call on_shell (q0, [mp**2, mq**2], KEEP_ENERGY) write (u, "(A)") write (u, "(A)") "Incoming momentum k =" call vector4_write (k, u) write (u, "(A)") write (u, "(A)") "Outgoing momentum sum p + q =" call vector4_write (sum (q0), u) write (u, "(A)") write (u, "(A)") "Radiated momentum p =" call vector4_write (q0(1), u) write (u, "(A)") write (u, "(A)") "Outgoing momentum q =" call vector4_write (q0(2), u) write (u, "(A)") write (u, "(A)") "Compare: mo^2" q02_2 = q0(2) ** 2; call pacify (q02_2, 1e-10_default) write (u, "(2(1x,F11.8))") sd%m2, q02_2 write (u, "(A)") write (u, "(A)") "* Recover parameters from outgoing momentum" write (u, "(A)") call sd%init (k, mk**2, mp**2, mq**2) call sd%set_t_bounds (x, 1 - x) call sd%recover (k, q0, KEEP_ENERGY) write (u, "(A)") "Compare: x" write (u, "(2(1x,F11.8))") x, sd%x write (u, "(A)") "Compare: t" write (u, "(2(1x,F11.8))") q2_2, sd%t call sd%inverse_t (r1o, t1 = - qmin ** 2, t0 = - qmax **2) write (u, "(A)") "Compare: r1" write (u, "(2(1x,F11.8))") r1, r1o call sd%inverse_phi (r2o) write (u, "(A)") "Compare: r2" write (u, "(2(1x,F11.8))") r2, r2o write (u, "(A)") call sd%write (u) write (u, "(A)") write (u, "(A)") "* Project on-shell (keep momentum)" q0 = q call on_shell (q0, [mp**2, mq**2], KEEP_MOMENTUM) write (u, "(A)") write (u, "(A)") "Incoming momentum k =" call vector4_write (k, u) write (u, "(A)") write (u, "(A)") "Outgoing momentum sum p + q =" call vector4_write (sum (q0), u) write (u, "(A)") write (u, "(A)") "Radiated momentum p =" call vector4_write (q0(1), u) write (u, "(A)") write (u, "(A)") "Outgoing momentum q =" call vector4_write (q0(2), u) write (u, "(A)") write (u, "(A)") "Compare: mo^2" q02_2 = q0(2) ** 2; call pacify (q02_2, 1e-10_default) write (u, "(2(1x,F11.8))") sd%m2, q02_2 write (u, "(A)") write (u, "(A)") "* Recover parameters from outgoing momentum" write (u, "(A)") call sd%init (k, mk**2, mp**2, mq**2) call sd%set_t_bounds (x, 1 - x) call sd%recover (k, q0, KEEP_MOMENTUM) write (u, "(A)") "Compare: x" write (u, "(2(1x,F11.8))") x, sd%x write (u, "(A)") "Compare: t" write (u, "(2(1x,F11.8))") q2_2, sd%t call sd%inverse_t (r1o, t1 = - qmin ** 2, t0 = - qmax **2) write (u, "(A)") "Compare: r1" write (u, "(2(1x,F11.8))") r1, r1o call sd%inverse_phi (r2o) write (u, "(A)") "Compare: r2" write (u, "(2(1x,F11.8))") r2, r2o write (u, "(A)") call sd%write (u) write (u, "(A)") write (u, "(A)") "* (2) Collinear setup" write (u, "(A)") call sd%init (k, mk**2, mp**2, mq**2, collinear = .true.) call sd%set_t_bounds (x, 1 - x) call sd%write (u) q = sd%split_momentum (k) q1_2 = q(1) ** 2; call pacify (q1_2, 1e-10_default) q2_2 = q(2) ** 2; call pacify (q2_2, 1e-10_default) write (u, "(A)") write (u, "(A)") "Incoming momentum k =" call vector4_write (k, u) write (u, "(A)") write (u, "(A)") "Outgoing momentum sum p + q =" call vector4_write (sum (q), u) write (u, "(A)") write (u, "(A)") "Radiated momentum p =" call vector4_write (q(1), u) write (u, "(A)") write (u, "(A)") "Outgoing momentum q =" call vector4_write (q(2), u) write (u, "(A)") write (u, "(A)") "Compare: s" write (u, "(2(1x,F11.8))") sd%s, k2 write (u, "(A)") "Compare: t" write (u, "(2(1x,F11.8))") sd%t, q2_2 write (u, "(A)") "Compare: u" write (u, "(2(1x,F11.8))") sd%u, q1_2 write (u, "(A)") "Compare: x" write (u, "(2(1x,F11.8))") sd%x, energy (q(2)) / energy (k) write (u, "(A)") "Compare: 1-x" write (u, "(2(1x,F11.8))") sd%xb, energy (q(1)) / energy (k) write (u, "(A)") write (u, "(A)") "* Project on-shell (keep energy)" q0 = q call on_shell (q0, [mp**2, mq**2], KEEP_ENERGY) write (u, "(A)") write (u, "(A)") "Incoming momentum k =" call vector4_write (k, u) write (u, "(A)") write (u, "(A)") "Outgoing momentum sum p + q =" call vector4_write (sum (q0), u) write (u, "(A)") write (u, "(A)") "Radiated momentum p =" call vector4_write (q0(1), u) write (u, "(A)") write (u, "(A)") "Outgoing momentum q =" call vector4_write (q0(2), u) write (u, "(A)") write (u, "(A)") "Compare: mo^2" q02_2 = q0(2) ** 2; call pacify (q02_2, 1e-10_default) write (u, "(2(1x,F11.8))") sd%m2, q02_2 write (u, "(A)") write (u, "(A)") "* Recover parameters from outgoing momentum" write (u, "(A)") call sd%init (k, mk**2, mp**2, mq**2) call sd%set_t_bounds (x, 1 - x) call sd%recover (k, q0, KEEP_ENERGY) write (u, "(A)") "Compare: x" write (u, "(2(1x,F11.8))") x, sd%x write (u, "(A)") "Compare: t" write (u, "(2(1x,F11.8))") q2_2, sd%t write (u, "(A)") call sd%write (u) write (u, "(A)") write (u, "(A)") "* Project on-shell (keep momentum)" q0 = q call on_shell (q0, [mp**2, mq**2], KEEP_MOMENTUM) write (u, "(A)") write (u, "(A)") "Incoming momentum k =" call vector4_write (k, u) write (u, "(A)") write (u, "(A)") "Outgoing momentum sum p + q =" call vector4_write (sum (q0), u) write (u, "(A)") write (u, "(A)") "Radiated momentum p =" call vector4_write (q0(1), u) write (u, "(A)") write (u, "(A)") "Outgoing momentum q =" call vector4_write (q0(2), u) write (u, "(A)") write (u, "(A)") "Compare: mo^2" q02_2 = q0(2) ** 2; call pacify (q02_2, 1e-10_default) write (u, "(2(1x,F11.8))") sd%m2, q02_2 write (u, "(A)") write (u, "(A)") "* Recover parameters from outgoing momentum" write (u, "(A)") call sd%init (k, mk**2, mp**2, mq**2) call sd%set_t_bounds (x, 1 - x) call sd%recover (k, q0, KEEP_MOMENTUM) write (u, "(A)") "Compare: x" write (u, "(2(1x,F11.8))") x, sd%x write (u, "(A)") "Compare: t" write (u, "(2(1x,F11.8))") q2_2, sd%t write (u, "(A)") call sd%write (u) write (u, "(A)") write (u, "(A)") "* Test output end: sf_aux_3" end subroutine sf_aux_3 @ %def sf_aux_3 @ \subsubsection{Endpoint stability} Compute momentum splitting for collinear kinematics close to both endpoints. In particular, check both directions $x\to$ momenta and momenta $\to x$. For purely massless collinear splitting, the [[KEEP_XXX]] flag is irrelevant. We choose [[KEEP_ENERGY]] here. <>= call test (sf_aux_4, "sf_aux_4", & "endpoint numerics", & u, results) <>= public :: sf_aux_4 <>= subroutine sf_aux_4 (u) integer, intent(in) :: u type(splitting_data_t) :: sd type(vector4_t) :: k type(vector4_t), dimension(2) :: q real(default) :: E, mk, mp, mq, qmin, qmax real(default) :: x, xb write (u, "(A)") "* Test output: sf_aux_4" write (u, "(A)") "* Purpose: compute massless collinear splitting near endpoint" E = 1 mk = 0 mp = 0 mq = 0 qmin = 1e-2_default qmax = 1e0_default k = vector4_moving (E, sqrt (E**2 - mk**2), 3) x = 0.1_default xb = 1 - x write (u, "(A)") write (u, "(A)") "* (1) Collinear setup, moderate kinematics" write (u, "(A)") call sd%init (k, mk**2, mp**2, mq**2, collinear = .true.) call sd%set_t_bounds (x, xb) call sd%write (u) q = sd%split_momentum (k) write (u, "(A)") write (u, "(A)") "Incoming momentum k =" call vector4_write (k, u) write (u, "(A)") write (u, "(A)") "Outgoing momentum sum p + q =" call vector4_write (sum (q), u) write (u, "(A)") write (u, "(A)") "Radiated momentum p =" call vector4_write (q(1), u) write (u, "(A)") write (u, "(A)") "Outgoing momentum q =" call vector4_write (q(2), u) write (u, "(A)") write (u, "(A)") "* Recover parameters from outgoing momenta" write (u, "(A)") call sd%init (k, mk**2, mp**2, mq**2, collinear = .true.) call sd%set_t_bounds (x, xb) call sd%recover (k, q, KEEP_ENERGY) write (u, "(A)") "Compare: x" write (u, "(2(1x,F11.8))") x, sd%x write (u, "(A)") "Compare: 1-x" write (u, "(2(1x,F11.8))") xb, sd%xb write (u, "(A)") call sd%write (u) write (u, "(A)") write (u, "(A)") "* (2) Close to x=0" write (u, "(A)") x = 1e-9_default xb = 1 - x call sd%init (k, mk**2, mp**2, mq**2, collinear = .true.) call sd%set_t_bounds (x, xb) call sd%write (u) q = sd%split_momentum (k) write (u, "(A)") write (u, "(A)") "Incoming momentum k =" call vector4_write (k, u) write (u, "(A)") write (u, "(A)") "Outgoing momentum sum p + q =" call vector4_write (sum (q), u) write (u, "(A)") write (u, "(A)") "Radiated momentum p =" call vector4_write (q(1), u) write (u, "(A)") write (u, "(A)") "Outgoing momentum q =" call vector4_write (q(2), u) write (u, "(A)") write (u, "(A)") "* Recover parameters from outgoing momenta" write (u, "(A)") call sd%init (k, mk**2, mp**2, mq**2, collinear = .true.) call sd%set_t_bounds (x, xb) call sd%recover (k, q, KEEP_ENERGY) write (u, "(A)") "Compare: x" write (u, "(2(1x,F11.8))") x, sd%x write (u, "(A)") "Compare: 1-x" write (u, "(2(1x,F11.8))") xb, sd%xb write (u, "(A)") call sd%write (u) write (u, "(A)") write (u, "(A)") "* (3) Close to x=1" write (u, "(A)") xb = 1e-9_default x = 1 - xb call sd%init (k, mk**2, mp**2, mq**2, collinear = .true.) call sd%set_t_bounds (x, xb) call sd%write (u) q = sd%split_momentum (k) write (u, "(A)") write (u, "(A)") "Incoming momentum k =" call vector4_write (k, u) write (u, "(A)") write (u, "(A)") "Outgoing momentum sum p + q =" call vector4_write (sum (q), u) write (u, "(A)") write (u, "(A)") "Radiated momentum p =" call vector4_write (q(1), u) write (u, "(A)") write (u, "(A)") "Outgoing momentum q =" call vector4_write (q(2), u) write (u, "(A)") write (u, "(A)") "* Recover parameters from outgoing momenta" write (u, "(A)") call sd%init (k, mk**2, mp**2, mq**2, collinear = .true.) call sd%set_t_bounds (x, xb) call sd%recover (k, q, KEEP_ENERGY) write (u, "(A)") "Compare: x" write (u, "(2(1x,F11.8))") x, sd%x write (u, "(A)") "Compare: 1-x" write (u, "(2(1x,F11.8))") xb, sd%xb write (u, "(A)") call sd%write (u) write (u, "(A)") write (u, "(A)") "* Test output end: sf_aux_4" end subroutine sf_aux_4 @ %def sf_aux_4 @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Mappings for structure functions} In this module, we provide a wrapper for useful mappings of the unit (hyper-)square that we can apply to a set of structure functions. In some cases it is useful, or even mandatory, to map the MC input parameters nontrivially onto a set of structure functions for the two beams. In all cases considered here, instead of $x_1,x_2,\ldots$ as parameters for the beams, we generate one parameter that is equal, or related to, the product $x_1x_2\cdots$ (so it directly corresponds to $\sqrt{s}$). The other parameters describe the distribution of energy (loss) between beams and radiations. <<[[sf_mappings.f90]]>>= <> module sf_mappings <> use kinds, only: double use io_units use constants, only: pi, zero, one use numeric_utils use diagnostics <> <> <> <> <> contains <> end module sf_mappings @ %def sf_mappings @ \subsection{Base type} First, we define an abstract base type for the mapping. In all cases we need to store the indices of the parameters on which the mapping applies. Additional parameters can be stored in the extensions of this type. <>= public :: sf_mapping_t <>= type, abstract :: sf_mapping_t integer, dimension(:), allocatable :: i contains <> end type sf_mapping_t @ %def sf_mapping_t @ The output routine is deferred: <>= procedure (sf_mapping_write), deferred :: write <>= abstract interface subroutine sf_mapping_write (object, unit) import class(sf_mapping_t), intent(in) :: object integer, intent(in), optional :: unit end subroutine sf_mapping_write end interface @ %def sf_mapping_write @ Initializer for the base type. The array of parameter indices is allocated but initialized to zero. <>= procedure :: base_init => sf_mapping_base_init <>= subroutine sf_mapping_base_init (mapping, n_par) class(sf_mapping_t), intent(out) :: mapping integer, intent(in) :: n_par allocate (mapping%i (n_par)) mapping%i = 0 end subroutine sf_mapping_base_init @ %def sf_mapping_base_init @ Set an index value. <>= procedure :: set_index => sf_mapping_set_index <>= subroutine sf_mapping_set_index (mapping, j, i) class(sf_mapping_t), intent(inout) :: mapping integer, intent(in) :: j, i mapping%i(j) = i end subroutine sf_mapping_set_index @ %def sf_mapping_set_index @ Retrieve an index value. <>= procedure :: get_index => sf_mapping_get_index <>= function sf_mapping_get_index (mapping, j) result (i) class(sf_mapping_t), intent(inout) :: mapping integer, intent(in) :: j integer :: i i = mapping%i(j) end function sf_mapping_get_index @ %def sf_mapping_get_index @ Return the dimensionality, i.e., the number of parameters. <>= procedure :: get_n_dim => sf_mapping_get_n_dim <>= function sf_mapping_get_n_dim (mapping) result (n) class(sf_mapping_t), intent(in) :: mapping integer :: n n = size (mapping%i) end function sf_mapping_get_n_dim @ %def sf_mapping_get_n_dim @ Computation: the values [[p]] are the input parameters, the values [[r]] are the output parameters. The values [[rb]] are defined as $\bar r = 1 - r$, but provided explicitly. They allow us to avoid numerical problems near $r=1$. The extra parameter [[x_free]] indicates that the total energy has already been renormalized by this factor. We have to take such a factor into account in a resonance or on-shell mapping. The Jacobian is [[f]]. We modify only the two parameters indicated by the indices [[i]]. <>= procedure (sf_mapping_compute), deferred :: compute <>= abstract interface subroutine sf_mapping_compute (mapping, r, rb, f, p, pb, x_free) import class(sf_mapping_t), intent(inout) :: mapping real(default), dimension(:), intent(out) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(in) :: p, pb real(default), intent(inout), optional :: x_free end subroutine sf_mapping_compute end interface @ %def sf_mapping_compute @ The inverse mapping. Use [[r]] and/or [[rb]] to reconstruct [[p]] and also compute [[f]]. <>= procedure (sf_mapping_inverse), deferred :: inverse <>= abstract interface subroutine sf_mapping_inverse (mapping, r, rb, f, p, pb, x_free) import class(sf_mapping_t), intent(inout) :: mapping real(default), dimension(:), intent(in) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: p, pb real(default), intent(inout), optional :: x_free end subroutine sf_mapping_inverse end interface @ %def sf_mapping_inverse @ \subsection{Methods for self-tests} This is a shorthand for: inject parameters, compute the mapping, display results, compute the inverse, display again. We provide an output format for the parameters and, optionally, a different output format for the Jacobians. <>= procedure :: check => sf_mapping_check <>= subroutine sf_mapping_check (mapping, u, p_in, pb_in, fmt_p, fmt_f) class(sf_mapping_t), intent(inout) :: mapping integer, intent(in) :: u real(default), dimension(:), intent(in) :: p_in, pb_in character(*), intent(in) :: fmt_p character(*), intent(in), optional :: fmt_f real(default), dimension(size(p_in)) :: p, pb, r, rb real(default) :: f, tolerance tolerance = 1.5E-17 p = p_in pb= pb_in call mapping%compute (r, rb, f, p, pb) call pacify (p, tolerance) call pacify (pb, tolerance) call pacify (r, tolerance) call pacify (rb, tolerance) write (u, "(3x,A,9(1x," // fmt_p // "))") "p =", p write (u, "(3x,A,9(1x," // fmt_p // "))") "pb=", pb write (u, "(3x,A,9(1x," // fmt_p // "))") "r =", r write (u, "(3x,A,9(1x," // fmt_p // "))") "rb=", rb if (present (fmt_f)) then write (u, "(3x,A,9(1x," // fmt_f // "))") "f =", f else write (u, "(3x,A,9(1x," // fmt_p // "))") "f =", f end if write (u, *) call mapping%inverse (r, rb, f, p, pb) call pacify (p, tolerance) call pacify (pb, tolerance) call pacify (r, tolerance) call pacify (rb, tolerance) write (u, "(3x,A,9(1x," // fmt_p // "))") "p =", p write (u, "(3x,A,9(1x," // fmt_p // "))") "pb=", pb write (u, "(3x,A,9(1x," // fmt_p // "))") "r =", r write (u, "(3x,A,9(1x," // fmt_p // "))") "rb=", rb if (present (fmt_f)) then write (u, "(3x,A,9(1x," // fmt_f // "))") "f =", f else write (u, "(3x,A,9(1x," // fmt_p // "))") "f =", f end if write (u, *) write (u, "(3x,A,9(1x," // fmt_p // "))") "*r=", product (r) end subroutine sf_mapping_check @ %def sf_mapping_check @ This is a consistency check for the self-tests: the integral over the unit square should be unity. We estimate this by a simple binning and adding up the values; this should be sufficient for a self-test. The argument is the requested number of sampling points. We take the square root for binning in both dimensions, so the precise number might be different. <>= procedure :: integral => sf_mapping_integral <>= function sf_mapping_integral (mapping, n_calls) result (integral) class(sf_mapping_t), intent(inout) :: mapping integer, intent(in) :: n_calls real(default) :: integral integer :: n_dim, n_bin, k real(default), dimension(:), allocatable :: p, pb, r, rb integer, dimension(:), allocatable :: ii real(default) :: dx, f, s n_dim = mapping%get_n_dim () allocate (p (n_dim)) allocate (pb(n_dim)) allocate (r (n_dim)) allocate (rb(n_dim)) allocate (ii(n_dim)) n_bin = nint (real (n_calls, default) ** (1._default / n_dim)) dx = 1._default / n_bin s = 0 ii = 1 SAMPLE: do do k = 1, n_dim p(k) = ii(k) * dx - dx/2 pb(k) = (n_bin - ii(k)) * dx + dx/2 end do call mapping%compute (r, rb, f, p, pb) s = s + f INCR: do k = 1, n_dim ii(k) = ii(k) + 1 if (ii(k) <= n_bin) then exit INCR else if (k < n_dim) then ii(k) = 1 else exit SAMPLE end if end do INCR end do SAMPLE integral = s / real (n_bin, default) ** n_dim end function sf_mapping_integral @ %def sf_mapping_integral @ \subsection{Implementation: standard mapping} This maps the unit square ($r_1,r_2$) such that $p_1$ is the product $r_1r_2$, while $p_2$ is related to the ratio. <>= public :: sf_s_mapping_t <>= type, extends (sf_mapping_t) :: sf_s_mapping_t logical :: power_set = .false. real(default) :: power = 1 contains <> end type sf_s_mapping_t @ %def sf_s_mapping_t @ Output. <>= procedure :: write => sf_s_mapping_write <>= subroutine sf_s_mapping_write (object, unit) class(sf_s_mapping_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(1x,A)", advance="no") "map" if (any (object%i /= 0)) then write (u, "('(',I0,',',I0,')')", advance="no") object%i end if write (u, "(A,F7.5,A)") ": standard (", object%power, ")" end subroutine sf_s_mapping_write @ %def sf_s_mapping_write @ Initialize: index pair and power parameter. <>= procedure :: init => sf_s_mapping_init <>= subroutine sf_s_mapping_init (mapping, power) class(sf_s_mapping_t), intent(out) :: mapping real(default), intent(in), optional :: power call mapping%base_init (2) if (present (power)) then mapping%power_set = .true. mapping%power = power end if end subroutine sf_s_mapping_init @ %def sf_s_mapping_init @ Apply mapping. <>= procedure :: compute => sf_s_mapping_compute <>= subroutine sf_s_mapping_compute (mapping, r, rb, f, p, pb, x_free) class(sf_s_mapping_t), intent(inout) :: mapping real(default), dimension(:), intent(out) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(in) :: p, pb real(default), intent(inout), optional :: x_free real(default), dimension(2) :: r2 integer :: j if (mapping%power_set) then call map_unit_square (r2, f, p(mapping%i), mapping%power) else call map_unit_square (r2, f, p(mapping%i)) end if r = p rb= pb do j = 1, 2 r (mapping%i(j)) = r2(j) rb(mapping%i(j)) = 1 - r2(j) end do end subroutine sf_s_mapping_compute @ %def sf_s_mapping_compute @ Apply inverse. <>= procedure :: inverse => sf_s_mapping_inverse <>= subroutine sf_s_mapping_inverse (mapping, r, rb, f, p, pb, x_free) class(sf_s_mapping_t), intent(inout) :: mapping real(default), dimension(:), intent(in) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: p, pb real(default), intent(inout), optional :: x_free real(default), dimension(2) :: p2 integer :: j if (mapping%power_set) then call map_unit_square_inverse (r(mapping%i), f, p2, mapping%power) else call map_unit_square_inverse (r(mapping%i), f, p2) end if p = r pb= rb do j = 1, 2 p (mapping%i(j)) = p2(j) pb(mapping%i(j)) = 1 - p2(j) end do end subroutine sf_s_mapping_inverse @ %def sf_s_mapping_inverse @ \subsection{Implementation: resonance pair mapping} This maps the unit square ($r_1,r_2$) such that $p_1$ is the product $r_1r_2$, while $p_2$ is related to the ratio, then it maps $p_1$ to itself according to a Breit-Wigner shape, i.e., a flat prior distribution in $p_1$ results in a Breit-Wigner distribution. Mass and width of the BW are rescaled by the energy, thus dimensionless fractions. <>= public :: sf_res_mapping_t <>= type, extends (sf_mapping_t) :: sf_res_mapping_t real(default) :: m = 0 real(default) :: w = 0 contains <> end type sf_res_mapping_t @ %def sf_res_mapping_t @ Output. <>= procedure :: write => sf_res_mapping_write <>= subroutine sf_res_mapping_write (object, unit) class(sf_res_mapping_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(1x,A)", advance="no") "map" if (any (object%i /= 0)) then write (u, "('(',I0,',',I0,')')", advance="no") object%i end if write (u, "(A,F7.5,', ',F7.5,A)") ": resonance (", object%m, object%w, ")" end subroutine sf_res_mapping_write @ %def sf_res_mapping_write @ Initialize: index pair and dimensionless mass and width parameters. <>= procedure :: init => sf_res_mapping_init <>= subroutine sf_res_mapping_init (mapping, m, w) class(sf_res_mapping_t), intent(out) :: mapping real(default), intent(in) :: m, w call mapping%base_init (2) mapping%m = m mapping%w = w end subroutine sf_res_mapping_init @ %def sf_res_mapping_init @ Apply mapping. <>= procedure :: compute => sf_res_mapping_compute <>= subroutine sf_res_mapping_compute (mapping, r, rb, f, p, pb, x_free) class(sf_res_mapping_t), intent(inout) :: mapping real(default), dimension(:), intent(out) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(in) :: p, pb real(default), intent(inout), optional :: x_free real(default), dimension(2) :: r2, p2 real(default) :: fbw, f2, p1m integer :: j p2 = p(mapping%i) call map_breit_wigner & (p1m, fbw, p2(1), mapping%m, mapping%w, x_free) call map_unit_square (r2, f2, [p1m, p2(2)]) f = fbw * f2 r = p rb= pb do j = 1, 2 r (mapping%i(j)) = r2(j) rb(mapping%i(j)) = 1 - r2(j) end do end subroutine sf_res_mapping_compute @ %def sf_res_mapping_compute @ Apply inverse. <>= procedure :: inverse => sf_res_mapping_inverse <>= subroutine sf_res_mapping_inverse (mapping, r, rb, f, p, pb, x_free) class(sf_res_mapping_t), intent(inout) :: mapping real(default), dimension(:), intent(in) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: p, pb real(default), intent(inout), optional :: x_free real(default), dimension(2) :: p2 real(default) :: fbw, f2, p1m call map_unit_square_inverse (r(mapping%i), f2, p2) call map_breit_wigner_inverse & (p2(1), fbw, p1m, mapping%m, mapping%w, x_free) p = r pb= rb p (mapping%i(1)) = p1m pb(mapping%i(1)) = 1 - p1m p (mapping%i(2)) = p2(2) pb(mapping%i(2)) = 1 - p2(2) f = fbw * f2 end subroutine sf_res_mapping_inverse @ %def sf_res_mapping_inverse @ \subsection{Implementation: resonance single mapping} While simpler, this is needed for structure-function setups only in exceptional cases. This maps the unit interval ($r_1$) to itself according to a Breit-Wigner shape, i.e., a flat prior distribution in $r_1$ results in a Breit-Wigner distribution. Mass and width of the BW are rescaled by the energy, thus dimensionless fractions. <>= public :: sf_res_mapping_single_t <>= type, extends (sf_mapping_t) :: sf_res_mapping_single_t real(default) :: m = 0 real(default) :: w = 0 contains <> end type sf_res_mapping_single_t @ %def sf_res_mapping_single_t @ Output. <>= procedure :: write => sf_res_mapping_single_write <>= subroutine sf_res_mapping_single_write (object, unit) class(sf_res_mapping_single_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(1x,A)", advance="no") "map" if (any (object%i /= 0)) then write (u, "('(',I0,')')", advance="no") object%i end if write (u, "(A,F7.5,', ',F7.5,A)") ": resonance (", object%m, object%w, ")" end subroutine sf_res_mapping_single_write @ %def sf_res_mapping_single_write @ Initialize: single index (!) and dimensionless mass and width parameters. <>= procedure :: init => sf_res_mapping_single_init <>= subroutine sf_res_mapping_single_init (mapping, m, w) class(sf_res_mapping_single_t), intent(out) :: mapping real(default), intent(in) :: m, w call mapping%base_init (1) mapping%m = m mapping%w = w end subroutine sf_res_mapping_single_init @ %def sf_res_mapping_single_init @ Apply mapping. <>= procedure :: compute => sf_res_mapping_single_compute <>= subroutine sf_res_mapping_single_compute (mapping, r, rb, f, p, pb, x_free) class(sf_res_mapping_single_t), intent(inout) :: mapping real(default), dimension(:), intent(out) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(in) :: p, pb real(default), intent(inout), optional :: x_free real(default), dimension(1) :: r2, p2 real(default) :: fbw integer :: j p2 = p(mapping%i) call map_breit_wigner & (r2(1), fbw, p2(1), mapping%m, mapping%w, x_free) f = fbw r = p rb= pb r (mapping%i(1)) = r2(1) rb(mapping%i(1)) = 1 - r2(1) end subroutine sf_res_mapping_single_compute @ %def sf_res_mapping_single_compute @ Apply inverse. <>= procedure :: inverse => sf_res_mapping_single_inverse <>= subroutine sf_res_mapping_single_inverse (mapping, r, rb, f, p, pb, x_free) class(sf_res_mapping_single_t), intent(inout) :: mapping real(default), dimension(:), intent(in) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: p, pb real(default), intent(inout), optional :: x_free real(default), dimension(1) :: p2 real(default) :: fbw call map_breit_wigner_inverse & (r(mapping%i(1)), fbw, p2(1), mapping%m, mapping%w, x_free) p = r pb= rb p (mapping%i(1)) = p2(1) pb(mapping%i(1)) = 1 - p2(1) f = fbw end subroutine sf_res_mapping_single_inverse @ %def sf_res_mapping_single_inverse @ \subsection{Implementation: on-shell mapping} This is a degenerate version of the unit-square mapping where the product $r_1r_2$ is constant. This product is given by the rescaled squared mass. We introduce an artificial first parameter $p_1$ to keep the counting, but nothing depends on it. The second parameter is the same $p_2$ as for the standard unit-square mapping for $\alpha=1$, it parameterizes the ratio of $r_1$ and $r_2$. <>= public :: sf_os_mapping_t <>= type, extends (sf_mapping_t) :: sf_os_mapping_t real(default) :: m = 0 real(default) :: lm2 = 0 contains <> end type sf_os_mapping_t @ %def sf_os_mapping_t @ Output. <>= procedure :: write => sf_os_mapping_write <>= subroutine sf_os_mapping_write (object, unit) class(sf_os_mapping_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(1x,A)", advance="no") "map" if (any (object%i /= 0)) then write (u, "('(',I0,',',I0,')')", advance="no") object%i end if write (u, "(A,F7.5,A)") ": on-shell (", object%m, ")" end subroutine sf_os_mapping_write @ %def sf_os_mapping_write @ Initialize: index pair and dimensionless mass parameter. <>= procedure :: init => sf_os_mapping_init <>= subroutine sf_os_mapping_init (mapping, m) class(sf_os_mapping_t), intent(out) :: mapping real(default), intent(in) :: m call mapping%base_init (2) mapping%m = m mapping%lm2 = abs (2 * log (mapping%m)) end subroutine sf_os_mapping_init @ %def sf_os_mapping_init @ Apply mapping. The [[x_free]] parameter rescales the total energy, which must be accounted for in the enclosed mapping. <>= procedure :: compute => sf_os_mapping_compute <>= subroutine sf_os_mapping_compute (mapping, r, rb, f, p, pb, x_free) class(sf_os_mapping_t), intent(inout) :: mapping real(default), dimension(:), intent(out) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(in) :: p, pb real(default), intent(inout), optional :: x_free real(default), dimension(2) :: r2, p2 integer :: j p2 = p(mapping%i) call map_on_shell (r2, f, p2, mapping%lm2, x_free) r = p rb= pb do j = 1, 2 r (mapping%i(j)) = r2(j) rb(mapping%i(j)) = 1 - r2(j) end do end subroutine sf_os_mapping_compute @ %def sf_os_mapping_compute @ Apply inverse. The irrelevant parameter $p_1$ is always set zero. <>= procedure :: inverse => sf_os_mapping_inverse <>= subroutine sf_os_mapping_inverse (mapping, r, rb, f, p, pb, x_free) class(sf_os_mapping_t), intent(inout) :: mapping real(default), dimension(:), intent(in) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: p, pb real(default), intent(inout), optional :: x_free real(default), dimension(2) :: p2, r2 r2 = r(mapping%i) call map_on_shell_inverse (r2, f, p2, mapping%lm2, x_free) p = r pb= rb p (mapping%i(1)) = p2(1) pb(mapping%i(1)) = 1 - p2(1) p (mapping%i(2)) = p2(2) pb(mapping%i(2)) = 1 - p2(2) end subroutine sf_os_mapping_inverse @ %def sf_os_mapping_inverse @ \subsection{Implementation: on-shell single mapping} This is a degenerate version of the unit-interval mapping where the result $r$ is constant. The value is given by the rescaled squared mass. The input parameter $p_1$ is actually ignored, nothing depends on it. <>= public :: sf_os_mapping_single_t <>= type, extends (sf_mapping_t) :: sf_os_mapping_single_t real(default) :: m = 0 real(default) :: lm2 = 0 contains <> end type sf_os_mapping_single_t @ %def sf_os_mapping_single_t @ Output. <>= procedure :: write => sf_os_mapping_single_write <>= subroutine sf_os_mapping_single_write (object, unit) class(sf_os_mapping_single_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(1x,A)", advance="no") "map" if (any (object%i /= 0)) then write (u, "('(',I0,')')", advance="no") object%i end if write (u, "(A,F7.5,A)") ": on-shell (", object%m, ")" end subroutine sf_os_mapping_single_write @ %def sf_os_mapping_single_write @ Initialize: index pair and dimensionless mass parameter. <>= procedure :: init => sf_os_mapping_single_init <>= subroutine sf_os_mapping_single_init (mapping, m) class(sf_os_mapping_single_t), intent(out) :: mapping real(default), intent(in) :: m call mapping%base_init (1) mapping%m = m mapping%lm2 = abs (2 * log (mapping%m)) end subroutine sf_os_mapping_single_init @ %def sf_os_mapping_single_init @ Apply mapping. The [[x_free]] parameter rescales the total energy, which must be accounted for in the enclosed mapping. <>= procedure :: compute => sf_os_mapping_single_compute <>= subroutine sf_os_mapping_single_compute (mapping, r, rb, f, p, pb, x_free) class(sf_os_mapping_single_t), intent(inout) :: mapping real(default), dimension(:), intent(out) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(in) :: p, pb real(default), intent(inout), optional :: x_free real(default), dimension(1) :: r2, p2 integer :: j p2 = p(mapping%i) call map_on_shell_single (r2, f, p2, mapping%lm2, x_free) r = p rb= pb r (mapping%i(1)) = r2(1) rb(mapping%i(1)) = 1 - r2(1) end subroutine sf_os_mapping_single_compute @ %def sf_os_mapping_single_compute @ Apply inverse. The irrelevant parameter $p_1$ is always set zero. <>= procedure :: inverse => sf_os_mapping_single_inverse <>= subroutine sf_os_mapping_single_inverse (mapping, r, rb, f, p, pb, x_free) class(sf_os_mapping_single_t), intent(inout) :: mapping real(default), dimension(:), intent(in) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: p, pb real(default), intent(inout), optional :: x_free real(default), dimension(1) :: p2, r2 r2 = r(mapping%i) call map_on_shell_single_inverse (r2, f, p2, mapping%lm2, x_free) p = r pb= rb p (mapping%i(1)) = p2(1) pb(mapping%i(1)) = 1 - p2(1) end subroutine sf_os_mapping_single_inverse @ %def sf_os_mapping_single_inverse @ \subsection{Implementation: endpoint mapping} This maps the unit square ($r_1,r_2$) such that $p_1$ is the product $r_1r_2$, while $p_2$ is related to the ratio. Furthermore, we enhance the region at $r_1=1$ and $r_2=1$, which translates into $p_1=1$ and $p_2=0,1$. The enhancement is such that any power-like singularity is caught. This is useful for beamstrahlung spectra. In addition, we allow for a delta-function singularity in $r_1$ and/or $r_2$. The singularity is smeared to an interval of width $\epsilon$. If nonzero, we distinguish the kinematical momentum fractions $r_i$ from effective values $x_i$, which should go into the structure-function evaluation. A bin of width $\epsilon$ in $r$ is mapped to $x=1$ exactly, while the interval $(0,1-\epsilon)$ is mapped to $(0,1)$ in $x$. The Jacobian reflects this distinction, and the logical [[in_peak]] allows for an unambiguous distinction. The delta-peak fraction is used only for the integration self-test. <>= public :: sf_ep_mapping_t <>= type, extends (sf_mapping_t) :: sf_ep_mapping_t real(default) :: a = 1 contains <> end type sf_ep_mapping_t @ %def sf_ep_mapping_t @ Output. <>= procedure :: write => sf_ep_mapping_write <>= subroutine sf_ep_mapping_write (object, unit) class(sf_ep_mapping_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(1x,A)", advance="no") "map" if (any (object%i /= 0)) then write (u, "('(',I0,',',I0,')')", advance="no") object%i end if write (u, "(A,ES12.5,A)") ": endpoint (a =", object%a, ")" end subroutine sf_ep_mapping_write @ %def sf_ep_mapping_write @ Initialize: no extra parameters. <>= procedure :: init => sf_ep_mapping_init <>= subroutine sf_ep_mapping_init (mapping, a) class(sf_ep_mapping_t), intent(out) :: mapping real(default), intent(in), optional :: a call mapping%base_init (2) if (present (a)) mapping%a = a end subroutine sf_ep_mapping_init @ %def sf_ep_mapping_init @ Apply mapping. <>= procedure :: compute => sf_ep_mapping_compute <>= subroutine sf_ep_mapping_compute (mapping, r, rb, f, p, pb, x_free) class(sf_ep_mapping_t), intent(inout) :: mapping real(default), dimension(:), intent(out) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(in) :: p, pb real(default), intent(inout), optional :: x_free real(default), dimension(2) :: px, r2 real(default) :: f1, f2 integer :: j call map_endpoint_1 (px(1), f1, p(mapping%i(1)), mapping%a) call map_endpoint_01 (px(2), f2, p(mapping%i(2)), mapping%a) call map_unit_square (r2, f, px) f = f * f1 * f2 r = p rb= pb do j = 1, 2 r (mapping%i(j)) = r2(j) rb(mapping%i(j)) = 1 - r2(j) end do end subroutine sf_ep_mapping_compute @ %def sf_ep_mapping_compute @ Apply inverse. <>= procedure :: inverse => sf_ep_mapping_inverse <>= subroutine sf_ep_mapping_inverse (mapping, r, rb, f, p, pb, x_free) class(sf_ep_mapping_t), intent(inout) :: mapping real(default), dimension(:), intent(in) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: p, pb real(default), intent(inout), optional :: x_free real(default), dimension(2) :: r2, px, p2 real(default) :: f1, f2 integer :: j do j = 1, 2 r2(j) = r(mapping%i(j)) end do call map_unit_square_inverse (r2, f, px) call map_endpoint_inverse_1 (px(1), f1, p2(1), mapping%a) call map_endpoint_inverse_01 (px(2), f2, p2(2), mapping%a) f = f * f1 * f2 p = r pb= rb do j = 1, 2 p (mapping%i(j)) = p2(j) pb(mapping%i(j)) = 1 - p2(j) end do end subroutine sf_ep_mapping_inverse @ %def sf_ep_mapping_inverse @ \subsection{Implementation: endpoint mapping with resonance} Like the endpoint mapping for $p_2$, but replace the endpoint mapping by a Breit-Wigner mapping for $p_1$. This covers resonance production in the presence of beamstrahlung. If the flag [[resonance]] is unset, we skip the resonance mapping, so the parameter $p_1$ remains equal to $r_1r_2$, as in the standard s-channel mapping. <>= public :: sf_epr_mapping_t <>= type, extends (sf_mapping_t) :: sf_epr_mapping_t real(default) :: a = 1 real(default) :: m = 0 real(default) :: w = 0 logical :: resonance = .true. contains <> end type sf_epr_mapping_t @ %def sf_epr_mapping_t @ Output. <>= procedure :: write => sf_epr_mapping_write <>= subroutine sf_epr_mapping_write (object, unit) class(sf_epr_mapping_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(1x,A)", advance="no") "map" if (any (object%i /= 0)) then write (u, "('(',I0,',',I0,')')", advance="no") object%i end if if (object%resonance) then write (u, "(A,F7.5,A,F7.5,', ',F7.5,A)") ": ep/res (a = ", object%a, & " | ", object%m, object%w, ")" else write (u, "(A,F7.5,A)") ": ep/nores (a = ", object%a, ")" end if end subroutine sf_epr_mapping_write @ %def sf_epr_mapping_write @ Initialize: if mass and width are not given, we initialize a non-resonant version of the mapping. <>= procedure :: init => sf_epr_mapping_init <>= subroutine sf_epr_mapping_init (mapping, a, m, w) class(sf_epr_mapping_t), intent(out) :: mapping real(default), intent(in) :: a real(default), intent(in), optional :: m, w call mapping%base_init (2) mapping%a = a if (present (m) .and. present (w)) then mapping%m = m mapping%w = w else mapping%resonance = .false. end if end subroutine sf_epr_mapping_init @ %def sf_epr_mapping_init @ Apply mapping. <>= procedure :: compute => sf_epr_mapping_compute <>= subroutine sf_epr_mapping_compute (mapping, r, rb, f, p, pb, x_free) class(sf_epr_mapping_t), intent(inout) :: mapping real(default), dimension(:), intent(out) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(in) :: p, pb real(default), intent(inout), optional :: x_free real(default), dimension(2) :: px, r2 real(default) :: f1, f2 integer :: j if (mapping%resonance) then call map_breit_wigner & (px(1), f1, p(mapping%i(1)), mapping%m, mapping%w, x_free) else px(1) = p(mapping%i(1)) f1 = 1 end if call map_endpoint_01 (px(2), f2, p(mapping%i(2)), mapping%a) call map_unit_square (r2, f, px) f = f * f1 * f2 r = p rb= pb do j = 1, 2 r (mapping%i(j)) = r2(j) rb(mapping%i(j)) = 1 - r2(j) end do end subroutine sf_epr_mapping_compute @ %def sf_epr_mapping_compute @ Apply inverse. <>= procedure :: inverse => sf_epr_mapping_inverse <>= subroutine sf_epr_mapping_inverse (mapping, r, rb, f, p, pb, x_free) class(sf_epr_mapping_t), intent(inout) :: mapping real(default), dimension(:), intent(in) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: p, pb real(default), intent(inout), optional :: x_free real(default), dimension(2) :: px, p2 real(default) :: f1, f2 integer :: j call map_unit_square_inverse (r(mapping%i), f, px) if (mapping%resonance) then call map_breit_wigner_inverse & (px(1), f1, p2(1), mapping%m, mapping%w, x_free) else p2(1) = px(1) f1 = 1 end if call map_endpoint_inverse_01 (px(2), f2, p2(2), mapping%a) f = f * f1 * f2 p = r pb= rb do j = 1, 2 p (mapping%i(j)) = p2(j) pb(mapping%i(j)) = 1 - p2(j) end do end subroutine sf_epr_mapping_inverse @ %def sf_epr_mapping_inverse @ \subsection{Implementation: endpoint mapping for on-shell particle} Analogous to the resonance mapping, but the $p_1$ input is ignored altogether. This covers on-shell particle production in the presence of beamstrahlung. <>= public :: sf_epo_mapping_t <>= type, extends (sf_mapping_t) :: sf_epo_mapping_t real(default) :: a = 1 real(default) :: m = 0 real(default) :: lm2 = 0 contains <> end type sf_epo_mapping_t @ %def sf_epo_mapping_t @ Output. <>= procedure :: write => sf_epo_mapping_write <>= subroutine sf_epo_mapping_write (object, unit) class(sf_epo_mapping_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(1x,A)", advance="no") "map" if (any (object%i /= 0)) then write (u, "('(',I0,',',I0,')')", advance="no") object%i end if write (u, "(A,F7.5,A,F7.5,A)") ": ep/on-shell (a = ", object%a, & " | ", object%m, ")" end subroutine sf_epo_mapping_write @ %def sf_epo_mapping_write @ Initialize: no extra parameters. <>= procedure :: init => sf_epo_mapping_init <>= subroutine sf_epo_mapping_init (mapping, a, m) class(sf_epo_mapping_t), intent(out) :: mapping real(default), intent(in) :: a, m call mapping%base_init (2) mapping%a = a mapping%m = m mapping%lm2 = abs (2 * log (mapping%m)) end subroutine sf_epo_mapping_init @ %def sf_epo_mapping_init @ Apply mapping. <>= procedure :: compute => sf_epo_mapping_compute <>= subroutine sf_epo_mapping_compute (mapping, r, rb, f, p, pb, x_free) class(sf_epo_mapping_t), intent(inout) :: mapping real(default), dimension(:), intent(out) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(in) :: p, pb real(default), intent(inout), optional :: x_free real(default), dimension(2) :: px, r2 real(default) :: f2 integer :: j px(1) = 0 call map_endpoint_01 (px(2), f2, p(mapping%i(2)), mapping%a) call map_on_shell (r2, f, px, mapping%lm2) f = f * f2 r = p rb= pb do j = 1, 2 r (mapping%i(j)) = r2(j) rb(mapping%i(j)) = 1 - r2(j) end do end subroutine sf_epo_mapping_compute @ %def sf_epo_mapping_compute @ Apply inverse. <>= procedure :: inverse => sf_epo_mapping_inverse <>= subroutine sf_epo_mapping_inverse (mapping, r, rb, f, p, pb, x_free) class(sf_epo_mapping_t), intent(inout) :: mapping real(default), dimension(:), intent(in) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: p, pb real(default), intent(inout), optional :: x_free real(default), dimension(2) :: px, p2 real(default) :: f2 integer :: j call map_on_shell_inverse (r(mapping%i), f, px, mapping%lm2) p2(1) = 0 call map_endpoint_inverse_01 (px(2), f2, p2(2), mapping%a) f = f * f2 p = r pb= rb do j = 1, 2 p (mapping%i(j)) = p2(j) pb(mapping%i(j)) = 1 - p2(j) end do end subroutine sf_epo_mapping_inverse @ %def sf_epo_mapping_inverse @ \subsection{Implementation: ISR endpoint mapping} Similar to the endpoint mapping above: This maps the unit square ($r_1,r_2$) such that $p_1$ is the product $r_1r_2$, while $p_2$ is related to the ratio. Furthermore, we enhance the region at $r_1=1$ and $r_2=1$, which translates into $p_1=1$ and $p_2=0,1$. The enhancement is such that ISR singularity $(1-x)^{-1+\epsilon}$ is flattened. This would be easy in one dimension, but becomes nontrivial in two dimensions. <>= public :: sf_ip_mapping_t <>= type, extends (sf_mapping_t) :: sf_ip_mapping_t real(default) :: eps = 0 contains <> end type sf_ip_mapping_t @ %def sf_ip_mapping_t @ Output. <>= procedure :: write => sf_ip_mapping_write <>= subroutine sf_ip_mapping_write (object, unit) class(sf_ip_mapping_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(1x,A)", advance="no") "map" if (any (object%i /= 0)) then write (u, "('(',I0,',',I0,')')", advance="no") object%i end if write (u, "(A,ES12.5,A)") ": isr (eps =", object%eps, ")" end subroutine sf_ip_mapping_write @ %def sf_ip_mapping_write @ Initialize: no extra parameters. <>= procedure :: init => sf_ip_mapping_init <>= subroutine sf_ip_mapping_init (mapping, eps) class(sf_ip_mapping_t), intent(out) :: mapping real(default), intent(in), optional :: eps call mapping%base_init (2) if (present (eps)) mapping%eps = eps if (mapping%eps <= 0) & call msg_fatal ("ISR mapping: regulator epsilon must not be zero") end subroutine sf_ip_mapping_init @ %def sf_ip_mapping_init @ Apply mapping. <>= procedure :: compute => sf_ip_mapping_compute <>= subroutine sf_ip_mapping_compute (mapping, r, rb, f, p, pb, x_free) class(sf_ip_mapping_t), intent(inout) :: mapping real(default), dimension(:), intent(out) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(in) :: p, pb real(default), intent(inout), optional :: x_free real(default), dimension(2) :: px, pxb, r2, r2b real(default) :: f1, f2, xb, y, yb integer :: j call map_power_1 (xb, f1, pb(mapping%i(1)), 2 * mapping%eps) call map_power_01 (y, yb, f2, pb(mapping%i(2)), mapping%eps) px(1) = 1 - xb pxb(1) = xb px(2) = y pxb(2) = yb call map_unit_square_prec (r2, r2b, f, px, pxb) f = f * f1 * f2 r = p rb= pb do j = 1, 2 r (mapping%i(j)) = r2 (j) rb(mapping%i(j)) = r2b(j) end do end subroutine sf_ip_mapping_compute @ %def sf_ip_mapping_compute @ Apply inverse. <>= procedure :: inverse => sf_ip_mapping_inverse <>= subroutine sf_ip_mapping_inverse (mapping, r, rb, f, p, pb, x_free) class(sf_ip_mapping_t), intent(inout) :: mapping real(default), dimension(:), intent(in) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: p, pb real(default), intent(inout), optional :: x_free real(default), dimension(2) :: r2, r2b, px, pxb, p2, p2b real(default) :: f1, f2, xb, y, yb integer :: j do j = 1, 2 r2 (j) = r (mapping%i(j)) r2b(j) = rb(mapping%i(j)) end do call map_unit_square_inverse_prec (r2, r2b, f, px, pxb) xb = pxb(1) if (px(1) > 0) then y = px(2) yb = pxb(2) else y = 0.5_default yb = 0.5_default end if call map_power_inverse_1 (xb, f1, p2b(1), 2 * mapping%eps) call map_power_inverse_01 (y, yb, f2, p2b(2), mapping%eps) p2 = 1 - p2b f = f * f1 * f2 p = r pb= rb do j = 1, 2 p (mapping%i(j)) = p2(j) pb(mapping%i(j)) = p2b(j) end do end subroutine sf_ip_mapping_inverse @ %def sf_ip_mapping_inverse @ \subsection{Implementation: ISR endpoint mapping, resonant} Similar to the endpoint mapping above: This maps the unit square ($r_1,r_2$) such that $p_1$ is the product $r_1r_2$, while $p_2$ is related to the ratio. Furthermore, we enhance the region at $r_1=1$ and $r_2=1$, which translates into $p_1=1$ and $p_2=0,1$. The enhancement is such that ISR singularity $(1-x)^{-1+\epsilon}$ is flattened. This would be easy in one dimension, but becomes nontrivial in two dimensions. The resonance can be turned off by the flag [[resonance]]. <>= public :: sf_ipr_mapping_t <>= type, extends (sf_mapping_t) :: sf_ipr_mapping_t real(default) :: eps = 0 real(default) :: m = 0 real(default) :: w = 0 logical :: resonance = .true. contains <> end type sf_ipr_mapping_t @ %def sf_ipr_mapping_t @ Output. <>= procedure :: write => sf_ipr_mapping_write <>= subroutine sf_ipr_mapping_write (object, unit) class(sf_ipr_mapping_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(1x,A)", advance="no") "map" if (any (object%i /= 0)) then write (u, "('(',I0,',',I0,')')", advance="no") object%i end if if (object%resonance) then write (u, "(A,F7.5,A,F7.5,', ',F7.5,A)") ": isr/res (eps = ", & object%eps, " | ", object%m, object%w, ")" else write (u, "(A,F7.5,A)") ": isr/res (eps = ", object%eps, ")" end if end subroutine sf_ipr_mapping_write @ %def sf_ipr_mapping_write @ Initialize: <>= procedure :: init => sf_ipr_mapping_init <>= subroutine sf_ipr_mapping_init (mapping, eps, m, w) class(sf_ipr_mapping_t), intent(out) :: mapping real(default), intent(in), optional :: eps, m, w call mapping%base_init (2) if (present (eps)) mapping%eps = eps if (mapping%eps <= 0) & call msg_fatal ("ISR mapping: regulator epsilon must not be zero") if (present (m) .and. present (w)) then mapping%m = m mapping%w = w else mapping%resonance = .false. end if end subroutine sf_ipr_mapping_init @ %def sf_ipr_mapping_init @ Apply mapping. <>= procedure :: compute => sf_ipr_mapping_compute <>= subroutine sf_ipr_mapping_compute (mapping, r, rb, f, p, pb, x_free) class(sf_ipr_mapping_t), intent(inout) :: mapping real(default), dimension(:), intent(out) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(in) :: p, pb real(default), intent(inout), optional :: x_free real(default), dimension(2) :: px, pxb, r2, r2b real(default) :: f1, f2, y, yb integer :: j if (mapping%resonance) then call map_breit_wigner & (px(1), f1, p(mapping%i(1)), mapping%m, mapping%w, x_free) else px(1) = p(mapping%i(1)) f1 = 1 end if call map_power_01 (y, yb, f2, pb(mapping%i(2)), mapping%eps) pxb(1) = 1 - px(1) px(2) = y pxb(2) = yb call map_unit_square_prec (r2, r2b, f, px, pxb) f = f * f1 * f2 r = p rb= pb do j = 1, 2 r (mapping%i(j)) = r2 (j) rb(mapping%i(j)) = r2b(j) end do end subroutine sf_ipr_mapping_compute @ %def sf_ipr_mapping_compute @ Apply inverse. <>= procedure :: inverse => sf_ipr_mapping_inverse <>= subroutine sf_ipr_mapping_inverse (mapping, r, rb, f, p, pb, x_free) class(sf_ipr_mapping_t), intent(inout) :: mapping real(default), dimension(:), intent(in) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: p, pb real(default), intent(inout), optional :: x_free real(default), dimension(2) :: r2, r2b, px, pxb, p2, p2b real(default) :: f1, f2, y, yb integer :: j do j = 1, 2 r2 (j) = r (mapping%i(j)) r2b(j) = rb(mapping%i(j)) end do call map_unit_square_inverse_prec (r2, r2b, f, px, pxb) if (px(1) > 0) then y = px(2) yb = pxb(2) else y = 0.5_default yb = 0.5_default end if if (mapping%resonance) then call map_breit_wigner_inverse & (px(1), f1, p2(1), mapping%m, mapping%w, x_free) else p2(1) = px(1) f1 = 1 end if call map_power_inverse_01 (y, yb, f2, p2b(2), mapping%eps) p2b(1) = 1 - p2(1) p2 (2) = 1 - p2b(2) f = f * f1 * f2 p = r pb= rb do j = 1, 2 p (mapping%i(j)) = p2(j) pb(mapping%i(j)) = p2b(j) end do end subroutine sf_ipr_mapping_inverse @ %def sf_ipr_mapping_inverse @ \subsection{Implementation: ISR on-shell mapping} Similar to the endpoint mapping above: This maps the unit square ($r_1,r_2$) such that $p_1$ is ignored while the product $r_1r_2$ is constant. $p_2$ is related to the ratio. Furthermore, we enhance the region at $r_1=1$ and $r_2=1$, which translates into $p_1=1$ and $p_2=0,1$. The enhancement is such that ISR singularity $(1-x)^{-1+\epsilon}$ is flattened. This would be easy in one dimension, but becomes nontrivial in two dimensions. <>= public :: sf_ipo_mapping_t <>= type, extends (sf_mapping_t) :: sf_ipo_mapping_t real(default) :: eps = 0 real(default) :: m = 0 contains <> end type sf_ipo_mapping_t @ %def sf_ipo_mapping_t @ Output. <>= procedure :: write => sf_ipo_mapping_write <>= subroutine sf_ipo_mapping_write (object, unit) class(sf_ipo_mapping_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(1x,A)", advance="no") "map" if (any (object%i /= 0)) then write (u, "('(',I0,',',I0,')')", advance="no") object%i end if write (u, "(A,F7.5,A,F7.5,A)") ": isr/os (eps = ", object%eps, & " | ", object%m, ")" end subroutine sf_ipo_mapping_write @ %def sf_ipo_mapping_write @ Initialize: no extra parameters. <>= procedure :: init => sf_ipo_mapping_init <>= subroutine sf_ipo_mapping_init (mapping, eps, m) class(sf_ipo_mapping_t), intent(out) :: mapping real(default), intent(in), optional :: eps, m call mapping%base_init (2) if (present (eps)) mapping%eps = eps if (mapping%eps <= 0) & call msg_fatal ("ISR mapping: regulator epsilon must not be zero") mapping%m = m end subroutine sf_ipo_mapping_init @ %def sf_ipo_mapping_init @ Apply mapping. <>= procedure :: compute => sf_ipo_mapping_compute <>= subroutine sf_ipo_mapping_compute (mapping, r, rb, f, p, pb, x_free) class(sf_ipo_mapping_t), intent(inout) :: mapping real(default), dimension(:), intent(out) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(in) :: p, pb real(default), intent(inout), optional :: x_free real(default), dimension(2) :: px, pxb, r2, r2b real(default) :: f1, f2, y, yb integer :: j call map_power_01 (y, yb, f2, pb(mapping%i(2)), mapping%eps) px(1) = mapping%m ** 2 if (present (x_free)) px(1) = px(1) / x_free pxb(1) = 1 - px(1) px(2) = y pxb(2) = yb call map_unit_square_prec (r2, r2b, f1, px, pxb) f = f1 * f2 r = p rb= pb do j = 1, 2 r (mapping%i(j)) = r2 (j) rb(mapping%i(j)) = r2b(j) end do end subroutine sf_ipo_mapping_compute @ %def sf_ipo_mapping_compute @ Apply inverse. <>= procedure :: inverse => sf_ipo_mapping_inverse <>= subroutine sf_ipo_mapping_inverse (mapping, r, rb, f, p, pb, x_free) class(sf_ipo_mapping_t), intent(inout) :: mapping real(default), dimension(:), intent(in) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: p, pb real(default), intent(inout), optional :: x_free real(default), dimension(2) :: r2, r2b, px, pxb, p2, p2b real(default) :: f1, f2, y, yb integer :: j do j = 1, 2 r2 (j) = r (mapping%i(j)) r2b(j) = rb(mapping%i(j)) end do call map_unit_square_inverse_prec (r2, r2b, f1, px, pxb) y = px(2) yb = pxb(2) call map_power_inverse_01 (y, yb, f2, p2b(2), mapping%eps) p2(1) = 0 p2b(1)= 1 p2(2) = 1 - p2b(2) f = f1 * f2 p = r pb= rb do j = 1, 2 p (mapping%i(j)) = p2(j) pb(mapping%i(j)) = p2b(j) end do end subroutine sf_ipo_mapping_inverse @ %def sf_ipo_mapping_inverse @ \subsection{Implementation: Endpoint + ISR power mapping} This is a combination of endpoint (i.e., beamstrahlung) and ISR power mapping. The first two parameters apply to the beamstrahlung spectrum, the last two to the ISR function for the first and second beam, respectively. <>= public :: sf_ei_mapping_t <>= type, extends (sf_mapping_t) :: sf_ei_mapping_t type(sf_ep_mapping_t) :: ep type(sf_ip_mapping_t) :: ip contains <> end type sf_ei_mapping_t @ %def sf_ei_mapping_t @ Output. <>= procedure :: write => sf_ei_mapping_write <>= subroutine sf_ei_mapping_write (object, unit) class(sf_ei_mapping_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(1x,A)", advance="no") "map" if (any (object%i /= 0)) then write (u, "('(',I0,3(',',I0),')')", advance="no") object%i end if write (u, "(A,ES12.5,A,ES12.5,A)") ": ep/isr (a =", object%ep%a, & ", eps =", object%ip%eps, ")" end subroutine sf_ei_mapping_write @ %def sf_ei_mapping_write @ Initialize: no extra parameters. <>= procedure :: init => sf_ei_mapping_init <>= subroutine sf_ei_mapping_init (mapping, a, eps) class(sf_ei_mapping_t), intent(out) :: mapping real(default), intent(in), optional :: a, eps call mapping%base_init (4) call mapping%ep%init (a) call mapping%ip%init (eps) end subroutine sf_ei_mapping_init @ %def sf_ei_mapping_init @ Set an index value. We should communicate the appropriate indices to the enclosed sub-mappings, therefore override the method. <>= procedure :: set_index => sf_ei_mapping_set_index <>= subroutine sf_ei_mapping_set_index (mapping, j, i) class(sf_ei_mapping_t), intent(inout) :: mapping integer, intent(in) :: j, i mapping%i(j) = i select case (j) case (1:2); call mapping%ep%set_index (j, i) case (3:4); call mapping%ip%set_index (j-2, i) end select end subroutine sf_ei_mapping_set_index @ %def sf_mapping_set_index @ Apply mapping. Now, the beamstrahlung and ISR mappings are independent of each other. The parameter subsets that are actually used should not overlap. The Jacobians are multiplied. <>= procedure :: compute => sf_ei_mapping_compute <>= subroutine sf_ei_mapping_compute (mapping, r, rb, f, p, pb, x_free) class(sf_ei_mapping_t), intent(inout) :: mapping real(default), dimension(:), intent(out) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(in) :: p, pb real(default), intent(inout), optional :: x_free real(default), dimension(size(p)) :: q, qb real(default) :: f1, f2 call mapping%ep%compute (q, qb, f1, p, pb, x_free) call mapping%ip%compute (r, rb, f2, q, qb, x_free) f = f1 * f2 end subroutine sf_ei_mapping_compute @ %def sf_ei_mapping_compute @ Apply inverse. <>= procedure :: inverse => sf_ei_mapping_inverse <>= subroutine sf_ei_mapping_inverse (mapping, r, rb, f, p, pb, x_free) class(sf_ei_mapping_t), intent(inout) :: mapping real(default), dimension(:), intent(in) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: p, pb real(default), intent(inout), optional :: x_free real(default), dimension(size(p)) :: q, qb real(default) :: f1, f2 call mapping%ip%inverse (r, rb, f2, q, qb, x_free) call mapping%ep%inverse (q, qb, f1, p, pb, x_free) f = f1 * f2 end subroutine sf_ei_mapping_inverse @ %def sf_ei_mapping_inverse @ \subsection{Implementation: Endpoint + ISR + resonance} This is a combination of endpoint (i.e., beamstrahlung) and ISR power mapping, adapted for an s-channel resonance. The first two internal parameters apply to the beamstrahlung spectrum, the last two to the ISR function for the first and second beam, respectively. The first and third parameters are the result of an overall resonance mapping, so on the outside, the first parameter is the total momentum fraction, the third one describes the distribution between beamstrahlung and ISR. <>= public :: sf_eir_mapping_t <>= type, extends (sf_mapping_t) :: sf_eir_mapping_t type(sf_res_mapping_t) :: res type(sf_epr_mapping_t) :: ep type(sf_ipr_mapping_t) :: ip contains <> end type sf_eir_mapping_t @ %def sf_eir_mapping_t @ Output. <>= procedure :: write => sf_eir_mapping_write <>= subroutine sf_eir_mapping_write (object, unit) class(sf_eir_mapping_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(1x,A)", advance="no") "map" if (any (object%i /= 0)) then write (u, "('(',I0,3(',',I0),')')", advance="no") object%i end if write (u, "(A,F7.5,A,F7.5,A,F7.5,', ',F7.5,A)") & ": ep/isr/res (a =", object%ep%a, & ", eps =", object%ip%eps, " | ", object%res%m, object%res%w, ")" end subroutine sf_eir_mapping_write @ %def sf_eir_mapping_write @ Initialize: no extra parameters. <>= procedure :: init => sf_eir_mapping_init <>= subroutine sf_eir_mapping_init (mapping, a, eps, m, w) class(sf_eir_mapping_t), intent(out) :: mapping real(default), intent(in) :: a, eps, m, w call mapping%base_init (4) call mapping%res%init (m, w) call mapping%ep%init (a) call mapping%ip%init (eps) end subroutine sf_eir_mapping_init @ %def sf_eir_mapping_init @ Set an index value. We should communicate the appropriate indices to the enclosed sub-mappings, therefore override the method. <>= procedure :: set_index => sf_eir_mapping_set_index <>= subroutine sf_eir_mapping_set_index (mapping, j, i) class(sf_eir_mapping_t), intent(inout) :: mapping integer, intent(in) :: j, i mapping%i(j) = i select case (j) case (1); call mapping%res%set_index (1, i) case (3); call mapping%res%set_index (2, i) end select select case (j) case (1:2); call mapping%ep%set_index (j, i) case (3:4); call mapping%ip%set_index (j-2, i) end select end subroutine sf_eir_mapping_set_index @ %def sf_mapping_set_index @ Apply mapping. Now, the beamstrahlung and ISR mappings are independent of each other. The parameter subsets that are actually used should not overlap. The Jacobians are multiplied. <>= procedure :: compute => sf_eir_mapping_compute <>= subroutine sf_eir_mapping_compute (mapping, r, rb, f, p, pb, x_free) class(sf_eir_mapping_t), intent(inout) :: mapping real(default), dimension(:), intent(out) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(in) :: p, pb real(default), intent(inout), optional :: x_free real(default), dimension(size(p)) :: px, pxb, q, qb real(default) :: f0, f1, f2 call mapping%res%compute (px, pxb, f0, p, pb, x_free) call mapping%ep%compute (q, qb, f1, px, pxb, x_free) call mapping%ip%compute (r, rb, f2, q, qb, x_free) f = f0 * f1 * f2 end subroutine sf_eir_mapping_compute @ %def sf_eir_mapping_compute @ Apply inverse. <>= procedure :: inverse => sf_eir_mapping_inverse <>= subroutine sf_eir_mapping_inverse (mapping, r, rb, f, p, pb, x_free) class(sf_eir_mapping_t), intent(inout) :: mapping real(default), dimension(:), intent(in) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: p, pb real(default), intent(inout), optional :: x_free real(default), dimension(size(p)) :: px, pxb, q, qb real(default) :: f0, f1, f2 call mapping%ip%inverse (r, rb, f2, q, qb, x_free) call mapping%ep%inverse (q, qb, f1, px, pxb, x_free) call mapping%res%inverse (px, pxb, f0, p, pb, x_free) f = f0 * f1 * f2 end subroutine sf_eir_mapping_inverse @ %def sf_eir_mapping_inverse @ \subsection{Implementation: Endpoint + ISR power mapping, on-shell} This is a combination of endpoint (i.e., beamstrahlung) and ISR power mapping. The first two parameters apply to the beamstrahlung spectrum, the last two to the ISR function for the first and second beam, respectively. On top of that, we map the first and third parameter such that the product is constant. From the outside, the first parameter is irrelevant while the third parameter describes the distribution of energy (loss) among beamstrahlung and ISR. <>= public :: sf_eio_mapping_t <>= type, extends (sf_mapping_t) :: sf_eio_mapping_t type(sf_os_mapping_t) :: os type(sf_epr_mapping_t) :: ep type(sf_ipr_mapping_t) :: ip contains <> end type sf_eio_mapping_t @ %def sf_eio_mapping_t @ Output. <>= procedure :: write => sf_eio_mapping_write <>= subroutine sf_eio_mapping_write (object, unit) class(sf_eio_mapping_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(1x,A)", advance="no") "map" if (any (object%i /= 0)) then write (u, "('(',I0,3(',',I0),')')", advance="no") object%i end if write (u, "(A,F7.5,A,F7.5,A,F7.5,A)") ": ep/isr/os (a =", object%ep%a, & ", eps =", object%ip%eps, " | ", object%os%m, ")" end subroutine sf_eio_mapping_write @ %def sf_eio_mapping_write @ Initialize: no extra parameters. <>= procedure :: init => sf_eio_mapping_init <>= subroutine sf_eio_mapping_init (mapping, a, eps, m) class(sf_eio_mapping_t), intent(out) :: mapping real(default), intent(in), optional :: a, eps, m call mapping%base_init (4) call mapping%os%init (m) call mapping%ep%init (a) call mapping%ip%init (eps) end subroutine sf_eio_mapping_init @ %def sf_eio_mapping_init @ Set an index value. We should communicate the appropriate indices to the enclosed sub-mappings, therefore override the method. <>= procedure :: set_index => sf_eio_mapping_set_index <>= subroutine sf_eio_mapping_set_index (mapping, j, i) class(sf_eio_mapping_t), intent(inout) :: mapping integer, intent(in) :: j, i mapping%i(j) = i select case (j) case (1); call mapping%os%set_index (1, i) case (3); call mapping%os%set_index (2, i) end select select case (j) case (1:2); call mapping%ep%set_index (j, i) case (3:4); call mapping%ip%set_index (j-2, i) end select end subroutine sf_eio_mapping_set_index @ %def sf_mapping_set_index @ Apply mapping. Now, the beamstrahlung and ISR mappings are independent of each other. The parameter subsets that are actually used should not overlap. The Jacobians are multiplied. <>= procedure :: compute => sf_eio_mapping_compute <>= subroutine sf_eio_mapping_compute (mapping, r, rb, f, p, pb, x_free) class(sf_eio_mapping_t), intent(inout) :: mapping real(default), dimension(:), intent(out) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(in) :: p, pb real(default), intent(inout), optional :: x_free real(default), dimension(size(p)) :: px, pxb, q, qb real(default) :: f0, f1, f2 call mapping%os%compute (px, pxb, f0, p, pb, x_free) call mapping%ep%compute (q, qb, f1, px, pxb, x_free) call mapping%ip%compute (r, rb, f2, q, qb, x_free) f = f0 * f1 * f2 end subroutine sf_eio_mapping_compute @ %def sf_eio_mapping_compute @ Apply inverse. <>= procedure :: inverse => sf_eio_mapping_inverse <>= subroutine sf_eio_mapping_inverse (mapping, r, rb, f, p, pb, x_free) class(sf_eio_mapping_t), intent(inout) :: mapping real(default), dimension(:), intent(in) :: r, rb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: p, pb real(default), intent(inout), optional :: x_free real(default), dimension(size(p)) :: px, pxb, q, qb real(default) :: f0, f1, f2 call mapping%ip%inverse (r, rb, f2, q, qb, x_free) call mapping%ep%inverse (q, qb, f1, px, pxb, x_free) call mapping%os%inverse (px, pxb, f0, p, pb, x_free) f = f0 * f1 * f2 end subroutine sf_eio_mapping_inverse @ %def sf_eio_mapping_inverse @ \subsection{Basic formulas} \subsubsection{Standard mapping of the unit square} This mapping of the unit square is appropriate in particular for structure functions which are concentrated at the lower end. Instead of a rectangular grid, one set of grid lines corresponds to constant parton c.m. energy. The other set is chosen such that the jacobian is only mildly singular ($\ln x$ which is zero at $x=1$), corresponding to an initial concentration of sampling points at the maximum energy. If [[power]] is greater than one (the default), points are also concentrated at the lower end. The formula is ([[power]]=$\alpha$): \begin{align} r_1 &= (p_1 ^ {p_2})^\alpha \\ r_2 &= (p_1 ^ {1 - p_2})^\alpha\\ f &= \alpha^2 p_1 ^ {\alpha - 1} |\log p_1| \end{align} and for the default case $\alpha=1$: \begin{align} r_1 &= p_1 ^ {p_2} \\ r_2 &= p_1 ^ {1 - p_2} \\ f &= |\log p_1| \end{align} <>= subroutine map_unit_square (r, factor, p, power) real(default), dimension(2), intent(out) :: r real(default), intent(out) :: factor real(default), dimension(2), intent(in) :: p real(default), intent(in), optional :: power real(default) :: xx, yy factor = 1 xx = p(1) yy = p(2) if (present(power)) then if (p(1) > 0 .and. power > 1) then xx = p(1)**power factor = factor * power * xx / p(1) end if end if if (.not. vanishes (xx)) then r(1) = xx ** yy r(2) = xx / r(1) factor = factor * abs (log (xx)) else r = 0 end if end subroutine map_unit_square @ %def map_unit_square @ This is the inverse mapping. <>= subroutine map_unit_square_inverse (r, factor, p, power) real(kind=default), dimension(2), intent(in) :: r real(kind=default), intent(out) :: factor real(kind=default), dimension(2), intent(out) :: p real(kind=default), intent(in), optional :: power real(kind=default) :: lg, xx, yy factor = 1 xx = r(1) * r(2) if (.not. vanishes (xx)) then lg = log (xx) if (.not. vanishes (lg)) then yy = log (r(1)) / lg else yy = 0 end if p(2) = yy factor = factor * abs (lg) if (present(power)) then p(1) = xx**(1._default/power) factor = factor * power * xx / p(1) else p(1) = xx end if else p = 0 end if end subroutine map_unit_square_inverse @ %def map_unit_square_inverse @ \subsubsection{Precise mapping of the unit square} A more precise version (with unit power parameter). This version should be numerically stable near $x=1$ and $y=0,1$. The formulas are again \begin{equation} r_1 = p_1^{p_2}, \qquad r_2 = p_1^{\bar p_2}, \qquad f = - \log p_1 \end{equation} but we compute both $r_i$ and $\bar r_i$ simultaneously and make direct use of both $p_i$ and $\bar p_i$ as appropriate. <>= subroutine map_unit_square_prec (r, rb, factor, p, pb) real(default), dimension(2), intent(out) :: r real(default), dimension(2), intent(out) :: rb real(default), intent(out) :: factor real(default), dimension(2), intent(in) :: p real(default), dimension(2), intent(in) :: pb if (p(1) > 0.5_default) then call compute_prec_xy_1 (r(1), rb(1), p(1), pb(1), p (2)) call compute_prec_xy_1 (r(2), rb(2), p(1), pb(1), pb(2)) factor = - log_prec (p(1), pb(1)) else if (.not. vanishes (p(1))) then call compute_prec_xy_0 (r(1), rb(1), p(1), pb(1), p (2)) call compute_prec_xy_0 (r(2), rb(2), p(1), pb(1), pb(2)) factor = - log_prec (p(1), pb(1)) else r = 0 rb = 1 factor = 0 end if end subroutine map_unit_square_prec @ %def map_unit_square_prec @ This is the inverse mapping. <>= subroutine map_unit_square_inverse_prec (r, rb, factor, p, pb) real(default), dimension(2), intent(in) :: r real(default), dimension(2), intent(in) :: rb real(default), intent(out) :: factor real(default), dimension(2), intent(out) :: p real(default), dimension(2), intent(out) :: pb call inverse_prec_x (r, rb, p(1), pb(1)) if (all (r > 0)) then if (rb(1) < rb(2)) then call inverse_prec_y (r, rb, p(2), pb(2)) else call inverse_prec_y ([r(2),r(1)], [rb(2),rb(1)], pb(2), p(2)) end if factor = - log_prec (p(1), pb(1)) else p(1) = 0 pb(1) = 1 p(2) = 0.5_default pb(2) = 0.5_default factor = 0 end if end subroutine map_unit_square_inverse_prec @ %def map_unit_square_prec_inverse @ This is an auxiliary function: evaluate the expression $\bar z = 1 - x^y$ in a numerically stable way. Instabilities occur for $y=0$ and $x=1$. The idea is to replace the bracket by the first terms of its Taylor expansion around $x=1$ (read $\bar x\equiv 1 -x$) \begin{equation} 1 - x^y = y\bar x\left(1 + \frac12(1-y)\bar x + \frac16(2-y)(1-y)\bar x^2\right) \end{equation} whenever this is the better approximation. Actually, the relative numerical error of the exact formula is about $\eta/(y\bar x)$ where $\eta$ is given by [[epsilon(KIND)]] in Fortran. The relative error of the approximation is better than the last included term divided by $(y\bar x)$. The first subroutine computes $z$ and $\bar z$ near $x=1$ where $\log x$ should be expanded, the second one near $x=0$ where $\log x$ can be kept. <>= subroutine compute_prec_xy_1 (z, zb, x, xb, y) real(default), intent(out) :: z, zb real(default), intent(in) :: x, xb, y real(default) :: a1, a2, a3 a1 = y * xb a2 = a1 * (1 - y) * xb / 2 a3 = a2 * (2 - y) * xb / 3 if (abs (a3) < epsilon (a3)) then zb = a1 + a2 + a3 z = 1 - zb else z = x ** y zb = 1 - z end if end subroutine compute_prec_xy_1 subroutine compute_prec_xy_0 (z, zb, x, xb, y) real(default), intent(out) :: z, zb real(default), intent(in) :: x, xb, y real(default) :: a1, a2, a3, lx lx = -log (x) a1 = y * lx a2 = a1 * y * lx / 2 a3 = a2 * y * lx / 3 if (abs (a3) < epsilon (a3)) then zb = a1 + a2 + a3 z = 1 - zb else z = x ** y zb = 1 - z end if end subroutine compute_prec_xy_0 @ %def compute_prec_xy_1 @ %def compute_prec_xy_0 @ For the inverse calculation, we evaluate $x=r_1r_2$ in a stable way. Since it is just a polynomial, the expansion near $x=1$ is analytically exact, and we don't need to choose based on precision. <>= subroutine inverse_prec_x (r, rb, x, xb) real(default), dimension(2), intent(in) :: r, rb real(default), intent(out) :: x, xb real(default) :: a0, a1 a0 = rb(1) + rb(2) a1 = rb(1) * rb(2) if (a0 > 0.5_default) then xb = a0 - a1 x = 1 - xb else x = r(1) * r(2) xb = 1 - x end if end subroutine inverse_prec_x @ %def inverse_prec_x @ The inverse calculation for the relative momentum fraction \begin{equation} y = \frac{1}{1 + \frac{\log{r_2}}{\log{r_1}}} \end{equation} is slightly more complicated. We should take the precise form of the logarithm, so we are safe near $r_i=1$. A series expansion is required if $r_1\ll r_2$, since then $y$ becomes small. (We assume $r_1>= subroutine inverse_prec_y (r, rb, y, yb) real(default), dimension(2), intent(in) :: r, rb real(default), intent(out) :: y, yb real(default) :: log1, log2, a1, a2, a3 log1 = log_prec (r(1), rb(1)) log2 = log_prec (r(2), rb(2)) if (abs (log2**3) < epsilon (one)) then if (abs(log1) < epsilon (one)) then y = zero else y = one / (one + log2 / log1) end if if (abs(log2) < epsilon (one)) then yb = zero else yb = one / (one + log1 / log2) end if return end if a1 = - rb(1) / log2 a2 = - rb(1) ** 2 * (one / log2**2 + one / (2 * log2)) a3 = - rb(1) ** 3 * (one / log2**3 + one / log2**2 + one/(3 * log2)) if (abs (a3) < epsilon (a3)) then y = a1 + a2 + a3 yb = one - y else y = one / (one + log2 / log1) yb = one / (one + log1 / log2) end if end subroutine inverse_prec_y @ %def inverse_prec_y @ \subsubsection{Mapping for on-shell s-channel} The limiting case, if the product $r_1r_2$ is fixed for on-shell production. The parameter $p_1$ is ignored. In the inverse mapping, it is returned zero. The parameter [[x_free]], if present, rescales the total energy. If it is less than one, the rescaled mass parameter $m^2$ should be increased accordingly. Public for access in unit test. <>= public :: map_on_shell public :: map_on_shell_inverse <>= subroutine map_on_shell (r, factor, p, lm2, x_free) real(default), dimension(2), intent(out) :: r real(default), intent(out) :: factor real(default), dimension(2), intent(in) :: p real(default), intent(in) :: lm2 real(default), intent(in), optional :: x_free real(default) :: lx lx = lm2; if (present (x_free)) lx = lx + log (x_free) r(1) = exp (- p(2) * lx) r(2) = exp (- (1 - p(2)) * lx) factor = lx end subroutine map_on_shell subroutine map_on_shell_inverse (r, factor, p, lm2, x_free) real(default), dimension(2), intent(in) :: r real(default), intent(out) :: factor real(default), dimension(2), intent(out) :: p real(default), intent(in) :: lm2 real(default), intent(in), optional :: x_free real(default) :: lx lx = lm2; if (present (x_free)) lx = lx + log (x_free) p(1) = 0 p(2) = abs (log (r(1))) / lx factor = lx end subroutine map_on_shell_inverse @ %def map_on_shell @ %def map_on_shell_inverse @ \subsubsection{Mapping for on-shell s-channel, single parameter} This is a pseudo-mapping which applies if there is actually just one parameter [[p]]. The output parameter [[r]] is fixed for on-shell production. The lone parameter $p_1$ is ignored. In the inverse mapping, it is returned zero. The parameter [[x_free]], if present, rescales the total energy. If it is less than one, the rescaled mass parameter $m^2$ should be increased accordingly. Public for access in unit test. <>= public :: map_on_shell_single public :: map_on_shell_single_inverse <>= subroutine map_on_shell_single (r, factor, p, lm2, x_free) real(default), dimension(1), intent(out) :: r real(default), intent(out) :: factor real(default), dimension(1), intent(in) :: p real(default), intent(in) :: lm2 real(default), intent(in), optional :: x_free real(default) :: lx lx = lm2; if (present (x_free)) lx = lx + log (x_free) r(1) = exp (- lx) factor = 1 end subroutine map_on_shell_single subroutine map_on_shell_single_inverse (r, factor, p, lm2, x_free) real(default), dimension(1), intent(in) :: r real(default), intent(out) :: factor real(default), dimension(1), intent(out) :: p real(default), intent(in) :: lm2 real(default), intent(in), optional :: x_free real(default) :: lx lx = lm2; if (present (x_free)) lx = lx + log (x_free) p(1) = 0 factor = 1 end subroutine map_on_shell_single_inverse @ %def map_on_shell_single @ %def map_on_shell_single_inverse @ \subsubsection{Mapping for a Breit-Wigner resonance} This is the standard Breit-Wigner mapping. We apply it to a single variable, independently of or in addition to a unit-square mapping. We assume here that the limits for the variable are 0 and 1, and that the mass $m$ and width $w$ are rescaled appropriately, so they are dimensionless and usually between 0 and 1. If [[x_free]] is set, it rescales the total energy and thus mass and width, since these are defined with respect to the total energy. <>= subroutine map_breit_wigner (r, factor, p, m, w, x_free) real(default), intent(out) :: r real(default), intent(out) :: factor real(default), intent(in) :: p real(default), intent(in) :: m real(default), intent(in) :: w real(default), intent(in), optional :: x_free real(default) :: m2, mw, a1, a2, a3, z, tmp m2 = m ** 2 mw = m * w if (present (x_free)) then m2 = m2 / x_free mw = mw / x_free end if a1 = atan (- m2 / mw) a2 = atan ((1 - m2) / mw) a3 = (a2 - a1) * mw z = (1-p) * a1 + p * a2 if (-pi/2 < z .and. z < pi/2) then tmp = tan (z) r = max (m2 + mw * tmp, 0._default) factor = a3 * (1 + tmp ** 2) else r = 0 factor = 0 end if end subroutine map_breit_wigner subroutine map_breit_wigner_inverse (r, factor, p, m, w, x_free) real(default), intent(in) :: r real(default), intent(out) :: factor real(default), intent(out) :: p real(default), intent(in) :: m real(default), intent(in) :: w real(default) :: m2, mw, a1, a2, a3, tmp real(default), intent(in), optional :: x_free m2 = m ** 2 mw = m * w if (present (x_free)) then m2 = m2 / x_free mw = mw / x_free end if a1 = atan (- m2 / mw) a2 = atan ((1 - m2) / mw) a3 = (a2 - a1) * mw tmp = (r - m2) / mw p = (atan (tmp) - a1) / (a2 - a1) factor = a3 * (1 + tmp ** 2) end subroutine map_breit_wigner_inverse @ %def map_breit_wigner @ %def map_breit_wigner_inverse @ \subsubsection{Mapping with endpoint enhancement} This is a mapping which is close to the unit mapping, except that at the endpoint(s), the output values are exponentially enhanced. \begin{equation} y = \tanh (a \tan (\frac{\pi}{2}x)) \end{equation} We have two variants: one covers endpoints at $0$ and $1$ symmetrically, while the other one (which essentially maps one-half of the range), covers only the endpoint at $1$. <>= subroutine map_endpoint_1 (x3, factor, x1, a) real(default), intent(out) :: x3, factor real(default), intent(in) :: x1 real(default), intent(in) :: a real(default) :: x2 if (abs (x1) < 1) then x2 = tan (x1 * pi / 2) x3 = tanh (a * x2) factor = a * pi/2 * (1 + x2 ** 2) * (1 - x3 ** 2) else x3 = x1 factor = 0 end if end subroutine map_endpoint_1 subroutine map_endpoint_inverse_1 (x3, factor, x1, a) real(default), intent(in) :: x3 real(default), intent(out) :: x1, factor real(default), intent(in) :: a real(default) :: x2 if (abs (x3) < 1) then x2 = atanh (x3) / a x1 = 2 / pi * atan (x2) factor = a * pi/2 * (1 + x2 ** 2) * (1 - x3 ** 2) else x1 = x3 factor = 0 end if end subroutine map_endpoint_inverse_1 subroutine map_endpoint_01 (x4, factor, x0, a) real(default), intent(out) :: x4, factor real(default), intent(in) :: x0 real(default), intent(in) :: a real(default) :: x1, x3 x1 = 2 * x0 - 1 call map_endpoint_1 (x3, factor, x1, a) x4 = (x3 + 1) / 2 end subroutine map_endpoint_01 subroutine map_endpoint_inverse_01 (x4, factor, x0, a) real(default), intent(in) :: x4 real(default), intent(out) :: x0, factor real(default), intent(in) :: a real(default) :: x1, x3 x3 = 2 * x4 - 1 call map_endpoint_inverse_1 (x3, factor, x1, a) x0 = (x1 + 1) / 2 end subroutine map_endpoint_inverse_01 @ %def map_endpoint_1 @ %def map_endpoint_inverse_1 @ %def map_endpoint_01 @ %def map_endpoint_inverse_01 @ \subsubsection{Mapping with endpoint enhancement (ISR)} This is another endpoint mapping. It is designed to flatten the ISR singularity which is of power type at $x=1$, i.e., if \begin{equation} \sigma = \int_0^1 dx\,f(x)\,G(x) = \int_0^1 dx\,\epsilon(1-x)^{-1+\epsilon} G(x), \end{equation} we replace this by \begin{equation} r = x^\epsilon \quad\Longrightarrow\quad \sigma = \int_0^1 dr\,G(1- (1-r)^{1/\epsilon}). \end{equation} We expect that $\epsilon$ is small. The actual mapping is $r\to x$ (so $x$ emerges closer to $1$). The Jacobian that we return is thus $1/f(x)$. We compute the mapping in terms of $\bar x\equiv 1 - x$, so we can achieve the required precision. Because some compilers show quite wild numeric fluctuations, we internally convert numeric types to explicit [[double]] precision. <>= public :: map_power_1 public :: map_power_inverse_1 <>= subroutine map_power_1 (xb, factor, rb, eps) real(default), intent(out) :: xb, factor real(default), intent(in) :: rb real(double) :: rb_db, factor_db, eps_db, xb_db real(default), intent(in) :: eps rb_db = real (rb, kind=double) eps_db = real (eps, kind=double) xb_db = rb_db ** (1 / eps_db) if (rb_db > 0) then factor_db = xb_db / rb_db / eps_db factor = real (factor_db, kind=default) else factor = 0 end if xb = real (xb_db, kind=default) end subroutine map_power_1 subroutine map_power_inverse_1 (xb, factor, rb, eps) real(default), intent(in) :: xb real(default), intent(out) :: rb, factor real(double) :: xb_db, factor_db, eps_db, rb_db real(default), intent(in) :: eps xb_db = real (xb, kind=double) eps_db = real (eps, kind=double) rb_db = xb_db ** eps_db if (xb_db > 0) then factor_db = xb_db / rb_db / eps_db factor = real (factor_db, kind=default) else factor = 0 end if rb = real (rb_db, kind=default) end subroutine map_power_inverse_1 @ %def map_power_1 @ %def map_power_inverse_1 @ Here we apply a power mapping to both endpoints. We divide the interval in two equal halves and apply the power mapping for the nearest endpoint, either $0$ or $1$. <>= subroutine map_power_01 (y, yb, factor, r, eps) real(default), intent(out) :: y, yb, factor real(default), intent(in) :: r real(default), intent(in) :: eps real(default) :: u, ub, zp, zm u = 2 * r - 1 if (u > 0) then ub = 2 * (1 - r) call map_power_1 (zm, factor, ub, eps) zp = 2 - zm else if (u < 0) then ub = 2 * r call map_power_1 (zp, factor, ub, eps) zm = 2 - zp else factor = 1 / eps zp = 1 zm = 1 end if y = zp / 2 yb = zm / 2 end subroutine map_power_01 subroutine map_power_inverse_01 (y, yb, factor, r, eps) real(default), intent(in) :: y, yb real(default), intent(out) :: r, factor real(default), intent(in) :: eps real(default) :: ub, zp, zm zp = 2 * y zm = 2 * yb if (zm < zp) then call map_power_inverse_1 (zm, factor, ub, eps) r = 1 - ub / 2 else if (zp < zm) then call map_power_inverse_1 (zp, factor, ub, eps) r = ub / 2 else factor = 1 / eps ub = 1 r = ub / 2 end if end subroutine map_power_inverse_01 @ %def map_power_01 @ %def map_power_inverse_01 @ \subsubsection{Structure-function channels} A structure-function chain parameterization (channel) may contain a mapping that applies to multiple structure functions. This is described by an extension of the [[sf_mapping_t]] type. In addition, it may contain mappings that apply to (other) individual structure functions. The details of these mappings are implementation-specific. The [[sf_channel_t]] type combines this information. It contains an array of map codes, one for each structure-function entry. The code values are: \begin{description} \item[none] MC input parameters $r$ directly become energy fractions $x$ \item[single] default mapping for a single structure-function entry \item[multi/s] map $r\to x$ such that one MC input parameter is $\hat s/s$ \item[multi/resonance] as before, adapted to s-channel resonance \item[multi/on-shell] as before, adapted to an on-shell particle in the s channel \item[multi/endpoint] like multi/s, but enhance the region near $r_i=1$ \item[multi/endpoint/res] endpoint mapping with resonance \item[multi/endpoint/os] endpoint mapping for on-shell \item[multi/power/os] like multi/endpoint, regulating a power singularity \end{description} <>= integer, parameter :: SFMAP_NONE = 0 integer, parameter :: SFMAP_SINGLE = 1 integer, parameter :: SFMAP_MULTI_S = 2 integer, parameter :: SFMAP_MULTI_RES = 3 integer, parameter :: SFMAP_MULTI_ONS = 4 integer, parameter :: SFMAP_MULTI_EP = 5 integer, parameter :: SFMAP_MULTI_EPR = 6 integer, parameter :: SFMAP_MULTI_EPO = 7 integer, parameter :: SFMAP_MULTI_IP = 8 integer, parameter :: SFMAP_MULTI_IPR = 9 integer, parameter :: SFMAP_MULTI_IPO = 10 integer, parameter :: SFMAP_MULTI_EI = 11 integer, parameter :: SFMAP_MULTI_SRS = 13 integer, parameter :: SFMAP_MULTI_SON = 14 @ %def SFMAP_NONE SFMAP_SINGLE @ %def SFMAP_MULTI_S SFMAP_MULTI_RES SFMAP_MULTI_ONS @ %def SFMAP_MULTI_EP SFMAP_MULTI_EPR SFMAP_MULTI_EPO @ %def SFMAP_MULTI_IP SFMAP_MULTI_IPR SFMAP_MULTI_IPO @ %def SFMAP_MULTI_EI @ %def SFMAP_MULTI_SRS SFMAP_MULTI_SON @ Then, it contains an allocatable entry for the multi mapping. This entry holds the MC-parameter indices on which the mapping applies (there may be more than one MC parameter per structure-function entry) and any parameters associated with the mapping. There can be only one multi-mapping per channel. <>= public :: sf_channel_t <>= type :: sf_channel_t integer, dimension(:), allocatable :: map_code class(sf_mapping_t), allocatable :: multi_mapping contains <> end type sf_channel_t @ %def sf_channel_t @ The output format prints a single character for each structure-function entry and, if applicable, an account of the mapping parameters. <>= procedure :: write => sf_channel_write <>= subroutine sf_channel_write (object, unit) class(sf_channel_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u, i u = given_output_unit (unit) if (allocated (object%map_code)) then do i = 1, size (object%map_code) select case (object%map_code (i)) case (SFMAP_NONE) write (u, "(1x,A)", advance="no") "-" case (SFMAP_SINGLE) write (u, "(1x,A)", advance="no") "+" case (SFMAP_MULTI_S) write (u, "(1x,A)", advance="no") "s" case (SFMAP_MULTI_RES, SFMAP_MULTI_SRS) write (u, "(1x,A)", advance="no") "r" case (SFMAP_MULTI_ONS, SFMAP_MULTI_SON) write (u, "(1x,A)", advance="no") "o" case (SFMAP_MULTI_EP) write (u, "(1x,A)", advance="no") "e" case (SFMAP_MULTI_EPR) write (u, "(1x,A)", advance="no") "p" case (SFMAP_MULTI_EPO) write (u, "(1x,A)", advance="no") "q" case (SFMAP_MULTI_IP) write (u, "(1x,A)", advance="no") "i" case (SFMAP_MULTI_IPR) write (u, "(1x,A)", advance="no") "i" case (SFMAP_MULTI_IPO) write (u, "(1x,A)", advance="no") "i" case (SFMAP_MULTI_EI) write (u, "(1x,A)", advance="no") "i" case default write (u, "(1x,A)", advance="no") "?" end select end do else write (u, "(1x,A)", advance="no") "-" end if if (allocated (object%multi_mapping)) then write (u, "(1x,'/')", advance="no") call object%multi_mapping%write (u) else write (u, *) end if end subroutine sf_channel_write @ %def sf_channel_write @ Initializer for a single [[sf_channel]] object. <>= procedure :: init => sf_channel_init <>= subroutine sf_channel_init (channel, n_strfun) class(sf_channel_t), intent(out) :: channel integer, intent(in) :: n_strfun allocate (channel%map_code (n_strfun)) channel%map_code = SFMAP_NONE end subroutine sf_channel_init @ %def sf_channel_init @ Assignment. This merely copies intrinsic assignment. <>= generic :: assignment (=) => sf_channel_assign procedure :: sf_channel_assign <>= subroutine sf_channel_assign (copy, original) class(sf_channel_t), intent(out) :: copy type(sf_channel_t), intent(in) :: original allocate (copy%map_code (size (original%map_code))) copy%map_code = original%map_code if (allocated (original%multi_mapping)) then allocate (copy%multi_mapping, source = original%multi_mapping) end if end subroutine sf_channel_assign @ %def sf_channel_assign @ This initializer allocates an array of channels with common number of structure-function entries, therefore it is not a type-bound procedure. <>= public :: allocate_sf_channels <>= subroutine allocate_sf_channels (channel, n_channel, n_strfun) type(sf_channel_t), dimension(:), intent(out), allocatable :: channel integer, intent(in) :: n_channel integer, intent(in) :: n_strfun integer :: c allocate (channel (n_channel)) do c = 1, n_channel call channel(c)%init (n_strfun) end do end subroutine allocate_sf_channels @ %def allocate_sf_channels @ This marks a given subset of indices as single-mapping. <>= procedure :: activate_mapping => sf_channel_activate_mapping <>= subroutine sf_channel_activate_mapping (channel, i_sf) class(sf_channel_t), intent(inout) :: channel integer, dimension(:), intent(in) :: i_sf channel%map_code(i_sf) = SFMAP_SINGLE end subroutine sf_channel_activate_mapping @ %def sf_channel_activate_mapping @ This sets an s-channel multichannel mapping. The parameter indices are not yet set. <>= procedure :: set_s_mapping => sf_channel_set_s_mapping <>= subroutine sf_channel_set_s_mapping (channel, i_sf, power) class(sf_channel_t), intent(inout) :: channel integer, dimension(:), intent(in) :: i_sf real(default), intent(in), optional :: power channel%map_code(i_sf) = SFMAP_MULTI_S allocate (sf_s_mapping_t :: channel%multi_mapping) select type (mapping => channel%multi_mapping) type is (sf_s_mapping_t) call mapping%init (power) end select end subroutine sf_channel_set_s_mapping @ %def sf_channel_set_s_mapping @ This sets an s-channel resonance multichannel mapping. <>= procedure :: set_res_mapping => sf_channel_set_res_mapping <>= subroutine sf_channel_set_res_mapping (channel, i_sf, m, w, single) class(sf_channel_t), intent(inout) :: channel integer, dimension(:), intent(in) :: i_sf real(default), intent(in) :: m, w logical, intent(in) :: single if (single) then channel%map_code(i_sf) = SFMAP_MULTI_SRS allocate (sf_res_mapping_single_t :: channel%multi_mapping) select type (mapping => channel%multi_mapping) type is (sf_res_mapping_single_t) call mapping%init (m, w) end select else channel%map_code(i_sf) = SFMAP_MULTI_RES allocate (sf_res_mapping_t :: channel%multi_mapping) select type (mapping => channel%multi_mapping) type is (sf_res_mapping_t) call mapping%init (m, w) end select end if end subroutine sf_channel_set_res_mapping @ %def sf_channel_set_res_mapping @ This sets an s-channel on-shell multichannel mapping. The length of the [[i_sf]] array must be 2. (The first parameter actually becomes an irrelevant dummy.) <>= procedure :: set_os_mapping => sf_channel_set_os_mapping <>= subroutine sf_channel_set_os_mapping (channel, i_sf, m, single) class(sf_channel_t), intent(inout) :: channel integer, dimension(:), intent(in) :: i_sf real(default), intent(in) :: m logical, intent(in) :: single if (single) then channel%map_code(i_sf) = SFMAP_MULTI_SON allocate (sf_os_mapping_single_t :: channel%multi_mapping) select type (mapping => channel%multi_mapping) type is (sf_os_mapping_single_t) call mapping%init (m) end select else channel%map_code(i_sf) = SFMAP_MULTI_ONS allocate (sf_os_mapping_t :: channel%multi_mapping) select type (mapping => channel%multi_mapping) type is (sf_os_mapping_t) call mapping%init (m) end select end if end subroutine sf_channel_set_os_mapping @ %def sf_channel_set_os_mapping @ This sets an s-channel endpoint mapping. The parameter $a$ is the slope parameter (default 1); increasing it moves the endpoint region (at $x=1$ to lower values in the input parameter. region even more. <>= procedure :: set_ep_mapping => sf_channel_set_ep_mapping <>= subroutine sf_channel_set_ep_mapping (channel, i_sf, a) class(sf_channel_t), intent(inout) :: channel integer, dimension(:), intent(in) :: i_sf real(default), intent(in), optional :: a channel%map_code(i_sf) = SFMAP_MULTI_EP allocate (sf_ep_mapping_t :: channel%multi_mapping) select type (mapping => channel%multi_mapping) type is (sf_ep_mapping_t) call mapping%init (a = a) end select end subroutine sf_channel_set_ep_mapping @ %def sf_channel_set_ep_mapping @ This sets a resonant endpoint mapping. <>= procedure :: set_epr_mapping => sf_channel_set_epr_mapping <>= subroutine sf_channel_set_epr_mapping (channel, i_sf, a, m, w) class(sf_channel_t), intent(inout) :: channel integer, dimension(:), intent(in) :: i_sf real(default), intent(in) :: a, m, w channel%map_code(i_sf) = SFMAP_MULTI_EPR allocate (sf_epr_mapping_t :: channel%multi_mapping) select type (mapping => channel%multi_mapping) type is (sf_epr_mapping_t) call mapping%init (a, m, w) end select end subroutine sf_channel_set_epr_mapping @ %def sf_channel_set_epr_mapping @ This sets an on-shell endpoint mapping. <>= procedure :: set_epo_mapping => sf_channel_set_epo_mapping <>= subroutine sf_channel_set_epo_mapping (channel, i_sf, a, m) class(sf_channel_t), intent(inout) :: channel integer, dimension(:), intent(in) :: i_sf real(default), intent(in) :: a, m channel%map_code(i_sf) = SFMAP_MULTI_EPO allocate (sf_epo_mapping_t :: channel%multi_mapping) select type (mapping => channel%multi_mapping) type is (sf_epo_mapping_t) call mapping%init (a, m) end select end subroutine sf_channel_set_epo_mapping @ %def sf_channel_set_epo_mapping @ This sets an s-channel power mapping, regulating a singularity of type $(1-x)^{-1+\epsilon}$. The parameter $\epsilon$ depends on the structure function. <>= procedure :: set_ip_mapping => sf_channel_set_ip_mapping <>= subroutine sf_channel_set_ip_mapping (channel, i_sf, eps) class(sf_channel_t), intent(inout) :: channel integer, dimension(:), intent(in) :: i_sf real(default), intent(in), optional :: eps channel%map_code(i_sf) = SFMAP_MULTI_IP allocate (sf_ip_mapping_t :: channel%multi_mapping) select type (mapping => channel%multi_mapping) type is (sf_ip_mapping_t) call mapping%init (eps) end select end subroutine sf_channel_set_ip_mapping @ %def sf_channel_set_ip_mapping @ This sets an s-channel resonant power mapping, regulating a singularity of type $(1-x)^{-1+\epsilon}$ in the presence of an s-channel resonance. The parameter $\epsilon$ depends on the structure function. <>= procedure :: set_ipr_mapping => sf_channel_set_ipr_mapping <>= subroutine sf_channel_set_ipr_mapping (channel, i_sf, eps, m, w) class(sf_channel_t), intent(inout) :: channel integer, dimension(:), intent(in) :: i_sf real(default), intent(in), optional :: eps, m, w channel%map_code(i_sf) = SFMAP_MULTI_IPR allocate (sf_ipr_mapping_t :: channel%multi_mapping) select type (mapping => channel%multi_mapping) type is (sf_ipr_mapping_t) call mapping%init (eps, m, w) end select end subroutine sf_channel_set_ipr_mapping @ %def sf_channel_set_ipr_mapping @ This sets an on-shell power mapping, regulating a singularity of type $(1-x)^{-1+\epsilon}$ for the production of a single on-shell particle.. The parameter $\epsilon$ depends on the structure function. <>= procedure :: set_ipo_mapping => sf_channel_set_ipo_mapping <>= subroutine sf_channel_set_ipo_mapping (channel, i_sf, eps, m) class(sf_channel_t), intent(inout) :: channel integer, dimension(:), intent(in) :: i_sf real(default), intent(in), optional :: eps, m channel%map_code(i_sf) = SFMAP_MULTI_IPO allocate (sf_ipo_mapping_t :: channel%multi_mapping) select type (mapping => channel%multi_mapping) type is (sf_ipo_mapping_t) call mapping%init (eps, m) end select end subroutine sf_channel_set_ipo_mapping @ %def sf_channel_set_ipo_mapping @ This sets a combined endpoint/ISR mapping. <>= procedure :: set_ei_mapping => sf_channel_set_ei_mapping <>= subroutine sf_channel_set_ei_mapping (channel, i_sf, a, eps) class(sf_channel_t), intent(inout) :: channel integer, dimension(:), intent(in) :: i_sf real(default), intent(in), optional :: a, eps channel%map_code(i_sf) = SFMAP_MULTI_EI allocate (sf_ei_mapping_t :: channel%multi_mapping) select type (mapping => channel%multi_mapping) type is (sf_ei_mapping_t) call mapping%init (a, eps) end select end subroutine sf_channel_set_ei_mapping @ %def sf_channel_set_ei_mapping @ This sets a combined endpoint/ISR mapping with resonance. <>= procedure :: set_eir_mapping => sf_channel_set_eir_mapping <>= subroutine sf_channel_set_eir_mapping (channel, i_sf, a, eps, m, w) class(sf_channel_t), intent(inout) :: channel integer, dimension(:), intent(in) :: i_sf real(default), intent(in), optional :: a, eps, m, w channel%map_code(i_sf) = SFMAP_MULTI_EI allocate (sf_eir_mapping_t :: channel%multi_mapping) select type (mapping => channel%multi_mapping) type is (sf_eir_mapping_t) call mapping%init (a, eps, m, w) end select end subroutine sf_channel_set_eir_mapping @ %def sf_channel_set_eir_mapping @ This sets a combined endpoint/ISR mapping, on-shell. <>= procedure :: set_eio_mapping => sf_channel_set_eio_mapping <>= subroutine sf_channel_set_eio_mapping (channel, i_sf, a, eps, m) class(sf_channel_t), intent(inout) :: channel integer, dimension(:), intent(in) :: i_sf real(default), intent(in), optional :: a, eps, m channel%map_code(i_sf) = SFMAP_MULTI_EI allocate (sf_eio_mapping_t :: channel%multi_mapping) select type (mapping => channel%multi_mapping) type is (sf_eio_mapping_t) call mapping%init (a, eps, m) end select end subroutine sf_channel_set_eio_mapping @ %def sf_channel_set_eio_mapping @ Return true if the mapping code at position [[i_sf]] is [[SFMAP_SINGLE]]. <>= procedure :: is_single_mapping => sf_channel_is_single_mapping <>= function sf_channel_is_single_mapping (channel, i_sf) result (flag) class(sf_channel_t), intent(in) :: channel integer, intent(in) :: i_sf logical :: flag flag = channel%map_code(i_sf) == SFMAP_SINGLE end function sf_channel_is_single_mapping @ %def sf_channel_is_single_mapping @ Return true if the mapping code at position [[i_sf]] is any of the [[SFMAP_MULTI]] mappings. <>= procedure :: is_multi_mapping => sf_channel_is_multi_mapping <>= function sf_channel_is_multi_mapping (channel, i_sf) result (flag) class(sf_channel_t), intent(in) :: channel integer, intent(in) :: i_sf logical :: flag select case (channel%map_code(i_sf)) case (SFMAP_NONE, SFMAP_SINGLE) flag = .false. case default flag = .true. end select end function sf_channel_is_multi_mapping @ %def sf_channel_is_multi_mapping @ Return the number of parameters that the multi-mapping requires. The mapping object must be allocated. <>= procedure :: get_multi_mapping_n_par => sf_channel_get_multi_mapping_n_par <>= function sf_channel_get_multi_mapping_n_par (channel) result (n_par) class(sf_channel_t), intent(in) :: channel integer :: n_par if (allocated (channel%multi_mapping)) then n_par = channel%multi_mapping%get_n_dim () else n_par = 0 end if end function sf_channel_get_multi_mapping_n_par @ %def sf_channel_is_multi_mapping @ Return true if there is any nontrivial mapping in any of the channels. <>= public :: any_sf_channel_has_mapping <>= function any_sf_channel_has_mapping (channel) result (flag) type(sf_channel_t), dimension(:), intent(in) :: channel logical :: flag integer :: c flag = .false. do c = 1, size (channel) flag = flag .or. any (channel(c)%map_code /= SFMAP_NONE) end do end function any_sf_channel_has_mapping @ %def any_sf_channel_has_mapping @ Set a parameter index for an active multi mapping. We assume that the index array is allocated properly. <>= procedure :: set_par_index => sf_channel_set_par_index <>= subroutine sf_channel_set_par_index (channel, j, i_par) class(sf_channel_t), intent(inout) :: channel integer, intent(in) :: j integer, intent(in) :: i_par associate (mapping => channel%multi_mapping) if (j >= 1 .and. j <= mapping%get_n_dim ()) then if (mapping%get_index (j) == 0) then call channel%multi_mapping%set_index (j, i_par) else call msg_bug ("Structure-function setup: mapping index set twice") end if else call msg_bug ("Structure-function setup: mapping index out of range") end if end associate end subroutine sf_channel_set_par_index @ %def sf_channel_set_par_index @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[sf_mappings_ut.f90]]>>= <> module sf_mappings_ut use unit_tests use sf_mappings_uti <> <> contains <> end module sf_mappings_ut @ %def sf_mappings_ut @ <<[[sf_mappings_uti.f90]]>>= <> module sf_mappings_uti <> use format_defs, only: FMT_11, FMT_12, FMT_13, FMT_14, FMT_15, FMT_16 use sf_mappings <> <> contains <> end module sf_mappings_uti @ %def sf_mappings_ut @ API: driver for the unit tests below. <>= public :: sf_mappings_test <>= subroutine sf_mappings_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine sf_mappings_test @ %def sf_mappings_test @ \subsubsection{Check standard mapping} Probe the standard mapping of the unit square for different parameter values. Also calculates integrals. For a finite number of bins, they differ slightly from $1$, but the result is well-defined because we are not using random points. <>= call test (sf_mappings_1, "sf_mappings_1", & "standard pair mapping", & u, results) <>= public :: sf_mappings_1 <>= subroutine sf_mappings_1 (u) integer, intent(in) :: u class(sf_mapping_t), allocatable :: mapping real(default), dimension(2) :: p write (u, "(A)") "* Test output: sf_mappings_1" write (u, "(A)") "* Purpose: probe standard mapping" write (u, "(A)") allocate (sf_s_mapping_t :: mapping) select type (mapping) type is (sf_s_mapping_t) call mapping%init () call mapping%set_index (1, 1) call mapping%set_index (2, 2) end select call mapping%write (u) write (u, *) write (u, "(A)") "Probe at (0,0):" p = [0._default, 0._default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Probe at (0.5,0.5):" p = [0.5_default, 0.5_default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Probe at (0.1,0.5):" p = [0.1_default, 0.5_default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Probe at (0.1,0.1):" p = [0.1_default, 0.1_default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Compute integral:" write (u, "(3x,A,1x,F7.5)") "I =", mapping%integral (100000) deallocate (mapping) allocate (sf_s_mapping_t :: mapping) select type (mapping) type is (sf_s_mapping_t) call mapping%init (power=2._default) call mapping%set_index (1, 1) call mapping%set_index (2, 2) end select write (u, *) call mapping%write (u) write (u, *) write (u, "(A)") "Probe at (0,0):" p = [0._default, 0._default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Probe at (0.5,0.5):" p = [0.5_default, 0.5_default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Probe at (0.1,0.5):" p = [0.1_default, 0.5_default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Probe at (0.1,0.1):" p = [0.1_default, 0.1_default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Compute integral:" write (u, "(3x,A,1x,F7.5)") "I =", mapping%integral (100000) write (u, "(A)") write (u, "(A)") "* Test output end: sf_mappings_1" end subroutine sf_mappings_1 @ %def sf_mappings_1 @ \subsubsection{Channel entries} Construct channel entries and print them. <>= call test (sf_mappings_2, "sf_mappings_2", & "structure-function mapping channels", & u, results) <>= public :: sf_mappings_2 <>= subroutine sf_mappings_2 (u) integer, intent(in) :: u type(sf_channel_t), dimension(:), allocatable :: channel integer :: c write (u, "(A)") "* Test output: sf_mappings_2" write (u, "(A)") "* Purpose: construct and display & &mapping-channel objects" write (u, "(A)") call allocate_sf_channels (channel, n_channel = 8, n_strfun = 2) call channel(2)%activate_mapping ([1]) call channel(3)%set_s_mapping ([1,2]) call channel(4)%set_s_mapping ([1,2], power=2._default) call channel(5)%set_res_mapping ([1,2], m = 0.5_default, w = 0.1_default, single = .false.) call channel(6)%set_os_mapping ([1,2], m = 0.5_default, single = .false.) call channel(7)%set_res_mapping ([1], m = 0.5_default, w = 0.1_default, single = .true.) call channel(8)%set_os_mapping ([1], m = 0.5_default, single = .true.) call channel(3)%set_par_index (1, 1) call channel(3)%set_par_index (2, 4) call channel(4)%set_par_index (1, 1) call channel(4)%set_par_index (2, 4) call channel(5)%set_par_index (1, 1) call channel(5)%set_par_index (2, 3) call channel(6)%set_par_index (1, 1) call channel(6)%set_par_index (2, 2) call channel(7)%set_par_index (1, 1) call channel(8)%set_par_index (1, 1) do c = 1, size (channel) write (u, "(I0,':')", advance="no") c call channel(c)%write (u) end do write (u, "(A)") write (u, "(A)") "* Test output end: sf_mappings_2" end subroutine sf_mappings_2 @ %def sf_mappings_2 @ \subsubsection{Check resonance mapping} Probe the resonance mapping of the unit square for different parameter values. Also calculates integrals. For a finite number of bins, they differ slightly from $1$, but the result is well-defined because we are not using random points. The resonance mass is at $1/2$ the energy, the width is $1/10$. <>= call test (sf_mappings_3, "sf_mappings_3", & "resonant pair mapping", & u, results) <>= public :: sf_mappings_3 <>= subroutine sf_mappings_3 (u) integer, intent(in) :: u class(sf_mapping_t), allocatable :: mapping real(default), dimension(2) :: p write (u, "(A)") "* Test output: sf_mappings_3" write (u, "(A)") "* Purpose: probe resonance pair mapping" write (u, "(A)") allocate (sf_res_mapping_t :: mapping) select type (mapping) type is (sf_res_mapping_t) call mapping%init (0.5_default, 0.1_default) call mapping%set_index (1, 1) call mapping%set_index (2, 2) end select call mapping%write (u) write (u, *) write (u, "(A)") "Probe at (0,0):" p = [0._default, 0._default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Probe at (0.5,0.5):" p = [0.5_default, 0.5_default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Probe at (0.1,0.5):" p = [0.1_default, 0.5_default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Probe at (0.1,0.1):" p = [0.1_default, 0.1_default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Compute integral:" write (u, "(3x,A,1x,F7.5)") "I =", mapping%integral (100000) deallocate (mapping) write (u, "(A)") write (u, "(A)") "* Test output end: sf_mappings_3" end subroutine sf_mappings_3 @ %def sf_mappings_3 @ \subsubsection{Check on-shell mapping} Probe the on-shell mapping of the unit square for different parameter values. Also calculates integrals. In this case, the Jacobian is constant and given by $|\log m^2|$, so this is also the value of the integral. The factor results from the variable change in the $\delta$ function $\delta (m^2 - x_1x_2)$ which multiplies the cross section for the case at hand. For the test, the (rescaled) resonance mass is set at $1/2$ the energy. <>= call test (sf_mappings_4, "sf_mappings_4", & "on-shell pair mapping", & u, results) <>= public :: sf_mappings_4 <>= subroutine sf_mappings_4 (u) integer, intent(in) :: u class(sf_mapping_t), allocatable :: mapping real(default), dimension(2) :: p write (u, "(A)") "* Test output: sf_mappings_4" write (u, "(A)") "* Purpose: probe on-shell pair mapping" write (u, "(A)") allocate (sf_os_mapping_t :: mapping) select type (mapping) type is (sf_os_mapping_t) call mapping%init (0.5_default) call mapping%set_index (1, 1) call mapping%set_index (2, 2) end select call mapping%write (u) write (u, *) write (u, "(A)") "Probe at (0,0):" p = [0._default, 0._default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Probe at (0.5,0.5):" p = [0.5_default, 0.5_default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Probe at (0,0.1):" p = [0._default, 0.1_default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Probe at (0,1.0):" p = [0._default, 1.0_default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Compute integral:" write (u, "(3x,A,1x,F7.5)") "I =", mapping%integral (100000) deallocate (mapping) write (u, "(A)") write (u, "(A)") "* Test output end: sf_mappings_4" end subroutine sf_mappings_4 @ %def sf_mappings_4 @ \subsubsection{Check endpoint mapping} Probe the endpoint mapping of the unit square for different parameter values. Also calculates integrals. For a finite number of bins, they differ slightly from $1$, but the result is well-defined because we are not using random points. <>= call test (sf_mappings_5, "sf_mappings_5", & "endpoint pair mapping", & u, results) <>= public :: sf_mappings_5 <>= subroutine sf_mappings_5 (u) integer, intent(in) :: u class(sf_mapping_t), allocatable :: mapping real(default), dimension(2) :: p write (u, "(A)") "* Test output: sf_mappings_5" write (u, "(A)") "* Purpose: probe endpoint pair mapping" write (u, "(A)") allocate (sf_ep_mapping_t :: mapping) select type (mapping) type is (sf_ep_mapping_t) call mapping%init () call mapping%set_index (1, 1) call mapping%set_index (2, 2) end select call mapping%write (u) write (u, *) write (u, "(A)") "Probe at (0,0):" p = [0._default, 0._default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Probe at (0.5,0.5):" p = [0.5_default, 0.5_default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Probe at (0.1,0.5):" p = [0.1_default, 0.5_default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Probe at (0.7,0.2):" p = [0.7_default, 0.2_default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Compute integral:" write (u, "(3x,A,1x,F7.5)") "I =", mapping%integral (100000) deallocate (mapping) write (u, "(A)") write (u, "(A)") "* Test output end: sf_mappings_5" end subroutine sf_mappings_5 @ %def sf_mappings_5 @ \subsubsection{Check endpoint resonant mapping} Probe the endpoint mapping with resonance. Also calculates integrals. <>= call test (sf_mappings_6, "sf_mappings_6", & "endpoint resonant mapping", & u, results) <>= public :: sf_mappings_6 <>= subroutine sf_mappings_6 (u) integer, intent(in) :: u class(sf_mapping_t), allocatable :: mapping real(default), dimension(2) :: p write (u, "(A)") "* Test output: sf_mappings_6" write (u, "(A)") "* Purpose: probe endpoint resonant mapping" write (u, "(A)") allocate (sf_epr_mapping_t :: mapping) select type (mapping) type is (sf_epr_mapping_t) call mapping%init (a = 1._default, m = 0.5_default, w = 0.1_default) call mapping%set_index (1, 1) call mapping%set_index (2, 2) end select call mapping%write (u) write (u, *) write (u, "(A)") "Probe at (0,0):" p = [0._default, 0._default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Probe at (0.5,0.5):" p = [0.5_default, 0.5_default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Probe at (0.1,0.5):" p = [0.1_default, 0.5_default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Probe at (0.7,0.2):" p = [0.7_default, 0.2_default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Compute integral:" write (u, "(3x,A,1x,F7.5)") "I =", mapping%integral (100000) deallocate (mapping) write (u, "(A)") write (u, "(A)") "* Same mapping without resonance:" write (u, "(A)") allocate (sf_epr_mapping_t :: mapping) select type (mapping) type is (sf_epr_mapping_t) call mapping%init (a = 1._default) call mapping%set_index (1, 1) call mapping%set_index (2, 2) end select call mapping%write (u) write (u, *) write (u, "(A)") "Probe at (0,0):" p = [0._default, 0._default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Probe at (0.5,0.5):" p = [0.5_default, 0.5_default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Probe at (0.1,0.5):" p = [0.1_default, 0.5_default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Probe at (0.7,0.2):" p = [0.7_default, 0.2_default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Compute integral:" write (u, "(3x,A,1x,F7.5)") "I =", mapping%integral (100000) deallocate (mapping) write (u, "(A)") write (u, "(A)") "* Test output end: sf_mappings_6" end subroutine sf_mappings_6 @ %def sf_mappings_6 @ \subsubsection{Check endpoint on-shell mapping} Probe the endpoint mapping with an on-shell particle. Also calculates integrals. <>= call test (sf_mappings_7, "sf_mappings_7", & "endpoint on-shell mapping", & u, results) <>= public :: sf_mappings_7 <>= subroutine sf_mappings_7 (u) integer, intent(in) :: u class(sf_mapping_t), allocatable :: mapping real(default), dimension(2) :: p write (u, "(A)") "* Test output: sf_mappings_7" write (u, "(A)") "* Purpose: probe endpoint on-shell mapping" write (u, "(A)") allocate (sf_epo_mapping_t :: mapping) select type (mapping) type is (sf_epo_mapping_t) call mapping%init (a = 1._default, m = 0.5_default) call mapping%set_index (1, 1) call mapping%set_index (2, 2) end select call mapping%write (u) write (u, *) write (u, "(A)") "Probe at (0,0):" p = [0._default, 0._default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Probe at (0.5,0.5):" p = [0.5_default, 0.5_default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Probe at (0.1,0.5):" p = [0.1_default, 0.5_default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Probe at (0.7,0.2):" p = [0.7_default, 0.2_default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Compute integral:" write (u, "(3x,A,1x,F7.5)") "I =", mapping%integral (100000) deallocate (mapping) write (u, "(A)") write (u, "(A)") "* Test output end: sf_mappings_7" end subroutine sf_mappings_7 @ %def sf_mappings_7 @ \subsubsection{Check power mapping} Probe the power mapping of the unit square for different parameter values. Also calculates integrals. For a finite number of bins, they differ slightly from $1$, but the result is well-defined because we are not using random points. <>= call test (sf_mappings_8, "sf_mappings_8", & "power pair mapping", & u, results) <>= public :: sf_mappings_8 <>= subroutine sf_mappings_8 (u) integer, intent(in) :: u class(sf_mapping_t), allocatable :: mapping real(default), dimension(2) :: p, pb write (u, "(A)") "* Test output: sf_mappings_8" write (u, "(A)") "* Purpose: probe power pair mapping" write (u, "(A)") allocate (sf_ip_mapping_t :: mapping) select type (mapping) type is (sf_ip_mapping_t) call mapping%init (eps = 0.1_default) call mapping%set_index (1, 1) call mapping%set_index (2, 2) end select call mapping%write (u) write (u, *) write (u, "(A)") "Probe at (0,0.5):" p = [0._default, 0.5_default] pb= [1._default, 0.5_default] call mapping%check (u, p, pb, FMT_16) write (u, *) write (u, "(A)") "Probe at (0.5,0.5):" p = [0.5_default, 0.5_default] pb= [0.5_default, 0.5_default] call mapping%check (u, p, pb, FMT_16) write (u, *) write (u, "(A)") "Probe at (0.9,0.5):" p = [0.9_default, 0.5_default] pb= [0.1_default, 0.5_default] call mapping%check (u, p, pb, FMT_16) write (u, *) write (u, "(A)") "Probe at (0.7,0.2):" p = [0.7_default, 0.2_default] pb= [0.3_default, 0.8_default] call mapping%check (u, p, pb, FMT_16) write (u, *) write (u, "(A)") "Probe at (0.7,0.8):" p = [0.7_default, 0.8_default] pb= [0.3_default, 0.2_default] call mapping%check (u, p, pb, FMT_16) write (u, *) write (u, "(A)") "Probe at (0.99,0.02):" p = [0.99_default, 0.02_default] pb= [0.01_default, 0.98_default] call mapping%check (u, p, pb, FMT_14, FMT_12) write (u, *) write (u, "(A)") "Probe at (0.99,0.98):" p = [0.99_default, 0.98_default] pb= [0.01_default, 0.02_default] call mapping%check (u, p, pb, FMT_14, FMT_12) write (u, *) write (u, "(A)") "Compute integral:" write (u, "(3x,A,1x,F7.5)") "I =", mapping%integral (100000) deallocate (mapping) write (u, "(A)") write (u, "(A)") "* Test output end: sf_mappings_8" end subroutine sf_mappings_8 @ %def sf_mappings_8 @ \subsubsection{Check resonant power mapping} Probe the power mapping of the unit square, adapted for an s-channel resonance, for different parameter values. Also calculates integrals. For a finite number of bins, they differ slightly from $1$, but the result is well-defined because we are not using random points. <>= call test (sf_mappings_9, "sf_mappings_9", & "power resonance mapping", & u, results) <>= public :: sf_mappings_9 <>= subroutine sf_mappings_9 (u) integer, intent(in) :: u class(sf_mapping_t), allocatable :: mapping real(default), dimension(2) :: p, pb write (u, "(A)") "* Test output: sf_mappings_9" write (u, "(A)") "* Purpose: probe power resonant pair mapping" write (u, "(A)") allocate (sf_ipr_mapping_t :: mapping) select type (mapping) type is (sf_ipr_mapping_t) call mapping%init (eps = 0.1_default, m = 0.5_default, w = 0.1_default) call mapping%set_index (1, 1) call mapping%set_index (2, 2) end select call mapping%write (u) write (u, *) write (u, "(A)") "Probe at (0,0.5):" p = [0._default, 0.5_default] pb= [1._default, 0.5_default] call mapping%check (u, p, pb, FMT_16) write (u, *) write (u, "(A)") "Probe at (0.5,0.5):" p = [0.5_default, 0.5_default] pb= [0.5_default, 0.5_default] call mapping%check (u, p, pb, FMT_16) write (u, *) write (u, "(A)") "Probe at (0.9,0.5):" p = [0.9_default, 0.5_default] pb= [0.1_default, 0.5_default] call mapping%check (u, p, pb, FMT_16) write (u, *) write (u, "(A)") "Probe at (0.7,0.2):" p = [0.7_default, 0.2_default] pb= [0.3_default, 0.8_default] call mapping%check (u, p, pb, FMT_16) write (u, *) write (u, "(A)") "Probe at (0.7,0.8):" p = [0.7_default, 0.8_default] pb= [0.3_default, 0.2_default] call mapping%check (u, p, pb, FMT_16) write (u, *) write (u, "(A)") "Probe at (0.9999,0.02):" p = [0.9999_default, 0.02_default] pb= [0.0001_default, 0.98_default] call mapping%check (u, p, pb, FMT_11, FMT_12) write (u, *) write (u, "(A)") "Probe at (0.9999,0.98):" p = [0.9999_default, 0.98_default] pb= [0.0001_default, 0.02_default] call mapping%check (u, p, pb, FMT_11, FMT_12) write (u, *) write (u, "(A)") "Compute integral:" write (u, "(3x,A,1x,F7.5)") "I =", mapping%integral (100000) deallocate (mapping) write (u, "(A)") write (u, "(A)") "* Same mapping without resonance:" write (u, "(A)") allocate (sf_ipr_mapping_t :: mapping) select type (mapping) type is (sf_ipr_mapping_t) call mapping%init (eps = 0.1_default) call mapping%set_index (1, 1) call mapping%set_index (2, 2) end select call mapping%write (u) write (u, *) write (u, "(A)") "Probe at (0,0.5):" p = [0._default, 0.5_default] pb= [1._default, 0.5_default] call mapping%check (u, p, pb, FMT_16) write (u, *) write (u, "(A)") "Probe at (0.5,0.5):" p = [0.5_default, 0.5_default] pb= [0.5_default, 0.5_default] call mapping%check (u, p, pb, FMT_16) write (u, *) write (u, "(A)") "Probe at (0.9,0.5):" p = [0.9_default, 0.5_default] pb= [0.1_default, 0.5_default] call mapping%check (u, p, pb, FMT_16) write (u, *) write (u, "(A)") "Probe at (0.7,0.2):" p = [0.7_default, 0.2_default] pb= [0.3_default, 0.8_default] call mapping%check (u, p, pb, FMT_16) write (u, *) write (u, "(A)") "Probe at (0.7,0.8):" p = [0.7_default, 0.8_default] pb= [0.3_default, 0.2_default] call mapping%check (u, p, pb, FMT_16) write (u, *) write (u, "(A)") "Compute integral:" write (u, "(3x,A,1x,F7.5)") "I =", mapping%integral (100000) deallocate (mapping) write (u, "(A)") write (u, "(A)") "* Test output end: sf_mappings_9" end subroutine sf_mappings_9 @ %def sf_mappings_9 @ \subsubsection{Check on-shell power mapping} Probe the power mapping of the unit square, adapted for single-particle production, for different parameter values. Also calculates integrals. For a finite number of bins, they differ slightly from $1$, but the result is well-defined because we are not using random points. <>= call test (sf_mappings_10, "sf_mappings_10", & "power on-shell mapping", & u, results) <>= public :: sf_mappings_10 <>= subroutine sf_mappings_10 (u) integer, intent(in) :: u class(sf_mapping_t), allocatable :: mapping real(default), dimension(2) :: p, pb write (u, "(A)") "* Test output: sf_mappings_10" write (u, "(A)") "* Purpose: probe power on-shell mapping" write (u, "(A)") allocate (sf_ipo_mapping_t :: mapping) select type (mapping) type is (sf_ipo_mapping_t) call mapping%init (eps = 0.1_default, m = 0.5_default) call mapping%set_index (1, 1) call mapping%set_index (2, 2) end select call mapping%write (u) write (u, *) write (u, "(A)") "Probe at (0,0.5):" p = [0._default, 0.5_default] pb= [1._default, 0.5_default] call mapping%check (u, p, pb, FMT_16) write (u, *) write (u, "(A)") "Probe at (0,0.02):" p = [0._default, 0.02_default] pb= [1._default, 0.98_default] call mapping%check (u, p, pb, FMT_15, FMT_12) write (u, *) write (u, "(A)") "Probe at (0,0.98):" p = [0._default, 0.98_default] pb= [1._default, 0.02_default] call mapping%check (u, p, pb, FMT_15, FMT_12) write (u, *) write (u, "(A)") "Compute integral:" write (u, "(3x,A,1x,F7.5)") "I =", mapping%integral (100000) deallocate (mapping) write (u, "(A)") write (u, "(A)") "* Test output end: sf_mappings_10" end subroutine sf_mappings_10 @ %def sf_mappings_10 @ \subsubsection{Check combined endpoint-power mapping} Probe the mapping for the beamstrahlung/ISR combination. <>= call test (sf_mappings_11, "sf_mappings_11", & "endpoint/power combined mapping", & u, results) <>= public :: sf_mappings_11 <>= subroutine sf_mappings_11 (u) integer, intent(in) :: u class(sf_mapping_t), allocatable :: mapping real(default), dimension(4) :: p, pb write (u, "(A)") "* Test output: sf_mappings_11" write (u, "(A)") "* Purpose: probe power pair mapping" write (u, "(A)") allocate (sf_ei_mapping_t :: mapping) select type (mapping) type is (sf_ei_mapping_t) call mapping%init (eps = 0.1_default) call mapping%set_index (1, 1) call mapping%set_index (2, 2) call mapping%set_index (3, 3) call mapping%set_index (4, 4) end select call mapping%write (u) write (u, *) write (u, "(A)") "Probe at (0.5, 0.5, 0.5, 0.5):" p = [0.5_default, 0.5_default, 0.5_default, 0.5_default] pb= [0.5_default, 0.5_default, 0.5_default, 0.5_default] call mapping%check (u, p, pb, FMT_16) write (u, *) write (u, "(A)") "Probe at (0.7, 0.2, 0.4, 0.8):" p = [0.7_default, 0.2_default, 0.4_default, 0.8_default] pb= [0.3_default, 0.8_default, 0.6_default, 0.2_default] call mapping%check (u, p, pb, FMT_16) write (u, *) write (u, "(A)") "Probe at (0.9, 0.06, 0.95, 0.1):" p = [0.9_default, 0.06_default, 0.95_default, 0.1_default] pb= [0.1_default, 0.94_default, 0.05_default, 0.9_default] call mapping%check (u, p, pb, FMT_13, FMT_12) write (u, *) write (u, "(A)") "Compute integral:" write (u, "(3x,A,1x,F7.5)") "I =", mapping%integral (100000) deallocate (mapping) write (u, "(A)") write (u, "(A)") "* Test output end: sf_mappings_11" end subroutine sf_mappings_11 @ %def sf_mappings_11 @ \subsubsection{Check resonant endpoint-power mapping} Probe the mapping for the beamstrahlung/ISR combination. <>= call test (sf_mappings_12, "sf_mappings_12", & "endpoint/power resonant combined mapping", & u, results) <>= public :: sf_mappings_12 <>= subroutine sf_mappings_12 (u) integer, intent(in) :: u class(sf_mapping_t), allocatable :: mapping real(default), dimension(4) :: p, pb write (u, "(A)") "* Test output: sf_mappings_12" write (u, "(A)") "* Purpose: probe resonant combined mapping" write (u, "(A)") allocate (sf_eir_mapping_t :: mapping) select type (mapping) type is (sf_eir_mapping_t) call mapping%init (a = 1._default, & eps = 0.1_default, m = 0.5_default, w = 0.1_default) call mapping%set_index (1, 1) call mapping%set_index (2, 2) call mapping%set_index (3, 3) call mapping%set_index (4, 4) end select call mapping%write (u) write (u, *) write (u, "(A)") "Probe at (0.5, 0.5, 0.5, 0.5):" p = [0.5_default, 0.5_default, 0.5_default, 0.5_default] pb= [0.5_default, 0.5_default, 0.5_default, 0.5_default] call mapping%check (u, p, pb, FMT_16) write (u, *) write (u, "(A)") "Probe at (0.7, 0.2, 0.4, 0.8):" p = [0.7_default, 0.2_default, 0.4_default, 0.8_default] pb= [0.3_default, 0.8_default, 0.6_default, 0.2_default] call mapping%check (u, p, pb, FMT_16) write (u, *) write (u, "(A)") "Probe at (0.9, 0.06, 0.95, 0.1):" p = [0.9_default, 0.06_default, 0.95_default, 0.1_default] pb= [0.1_default, 0.94_default, 0.05_default, 0.9_default] call mapping%check (u, p, pb, FMT_15, FMT_12) write (u, *) write (u, "(A)") "Compute integral:" write (u, "(3x,A,1x,F7.5)") "I =", mapping%integral (100000) deallocate (mapping) write (u, "(A)") write (u, "(A)") "* Test output end: sf_mappings_12" end subroutine sf_mappings_12 @ %def sf_mappings_12 @ \subsubsection{Check on-shell endpoint-power mapping} Probe the mapping for the beamstrahlung/ISR combination. <>= call test (sf_mappings_13, "sf_mappings_13", & "endpoint/power on-shell combined mapping", & u, results) <>= public :: sf_mappings_13 <>= subroutine sf_mappings_13 (u) integer, intent(in) :: u class(sf_mapping_t), allocatable :: mapping real(default), dimension(4) :: p, pb write (u, "(A)") "* Test output: sf_mappings_13" write (u, "(A)") "* Purpose: probe on-shell combined mapping" write (u, "(A)") allocate (sf_eio_mapping_t :: mapping) select type (mapping) type is (sf_eio_mapping_t) call mapping%init (a = 1._default, eps = 0.1_default, m = 0.5_default) call mapping%set_index (1, 1) call mapping%set_index (2, 2) call mapping%set_index (3, 3) call mapping%set_index (4, 4) end select call mapping%write (u) write (u, *) write (u, "(A)") "Probe at (0.5, 0.5, 0.5, 0.5):" p = [0.5_default, 0.5_default, 0.5_default, 0.5_default] pb= [0.5_default, 0.5_default, 0.5_default, 0.5_default] call mapping%check (u, p, pb, FMT_16) write (u, *) write (u, "(A)") "Probe at (0.7, 0.2, 0.4, 0.8):" p = [0.7_default, 0.2_default, 0.4_default, 0.8_default] pb= [0.3_default, 0.8_default, 0.6_default, 0.2_default] call mapping%check (u, p, pb, FMT_16) write (u, *) write (u, "(A)") "Probe at (0.9, 0.06, 0.95, 0.1):" p = [0.9_default, 0.06_default, 0.95_default, 0.1_default] pb= [0.1_default, 0.94_default, 0.05_default, 0.9_default] call mapping%check (u, p, pb, FMT_14, FMT_12) write (u, *) write (u, "(A)") "Compute integral:" write (u, "(3x,A,1x,F7.5)") "I =", mapping%integral (100000) deallocate (mapping) write (u, "(A)") write (u, "(A)") "* Test output end: sf_mappings_13" end subroutine sf_mappings_13 @ %def sf_mappings_13 @ \subsubsection{Check rescaling} Check the rescaling factor in on-shell basic mapping. <>= call test (sf_mappings_14, "sf_mappings_14", & "rescaled on-shell mapping", & u, results) <>= public :: sf_mappings_14 <>= subroutine sf_mappings_14 (u) integer, intent(in) :: u real(default), dimension(2) :: p2, r2 real(default), dimension(1) :: p1, r1 real(default) :: f, x_free, m2 write (u, "(A)") "* Test output: sf_mappings_14" write (u, "(A)") "* Purpose: probe rescaling in os mapping" write (u, "(A)") x_free = 0.9_default m2 = 0.5_default write (u, "(A)") "* Two parameters" write (u, "(A)") p2 = [0.1_default, 0.2_default] call map_on_shell (r2, f, p2, -log (m2), x_free) write (u, "(A,9(1x," // FMT_14 // "))") "p =", p2 write (u, "(A,9(1x," // FMT_14 // "))") "r =", r2 write (u, "(A,9(1x," // FMT_14 // "))") "f =", f write (u, "(A,9(1x," // FMT_14 // "))") "*r=", x_free * product (r2) write (u, *) call map_on_shell_inverse (r2, f, p2, -log (m2), x_free) write (u, "(A,9(1x," // FMT_14 // "))") "p =", p2 write (u, "(A,9(1x," // FMT_14 // "))") "r =", r2 write (u, "(A,9(1x," // FMT_14 // "))") "f =", f write (u, "(A,9(1x," // FMT_14 // "))") "*r=", x_free * product (r2) write (u, "(A)") write (u, "(A)") "* One parameter" write (u, "(A)") p1 = [0.1_default] call map_on_shell_single (r1, f, p1, -log (m2), x_free) write (u, "(A,9(1x," // FMT_14 // "))") "p =", p1 write (u, "(A,9(1x," // FMT_14 // "))") "r =", r1 write (u, "(A,9(1x," // FMT_14 // "))") "f =", f write (u, "(A,9(1x," // FMT_14 // "))") "*r=", x_free * product (r1) write (u, *) call map_on_shell_single_inverse (r1, f, p1, -log (m2), x_free) write (u, "(A,9(1x," // FMT_14 // "))") "p =", p1 write (u, "(A,9(1x," // FMT_14 // "))") "r =", r1 write (u, "(A,9(1x," // FMT_14 // "))") "f =", f write (u, "(A,9(1x," // FMT_14 // "))") "*r=", x_free * product (r1) write (u, "(A)") write (u, "(A)") "* Test output end: sf_mappings_14" end subroutine sf_mappings_14 @ %def sf_mappings_14 @ \subsubsection{Check single parameter resonance mapping} Probe the resonance mapping of the unit interval for different parameter values. Also calculates integrals. The resonance mass is at $1/2$ the energy, the width is $1/10$. <>= call test (sf_mappings_15, "sf_mappings_15", & "resonant single mapping", & u, results) <>= public :: sf_mappings_15 <>= subroutine sf_mappings_15 (u) integer, intent(in) :: u class(sf_mapping_t), allocatable :: mapping real(default), dimension(1) :: p write (u, "(A)") "* Test output: sf_mappings_15" write (u, "(A)") "* Purpose: probe resonance single mapping" write (u, "(A)") allocate (sf_res_mapping_single_t :: mapping) select type (mapping) type is (sf_res_mapping_single_t) call mapping%init (0.5_default, 0.1_default) call mapping%set_index (1, 1) end select call mapping%write (u) write (u, *) write (u, "(A)") "Probe at (0):" p = [0._default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Probe at (0.5):" p = [0.5_default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Probe at (0.1):" p = [0.1_default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Compute integral:" write (u, "(3x,A,1x,F7.5)") "I =", mapping%integral (100000) deallocate (mapping) write (u, "(A)") write (u, "(A)") "* Test output end: sf_mappings_15" end subroutine sf_mappings_15 @ %def sf_mappings_15 @ \subsubsection{Check single parameter on-shell mapping} Probe the on-shell (pseudo) mapping of the unit interval for different parameter values. Also calculates integrals. The resonance mass is at $1/2$ the energy. <>= call test (sf_mappings_16, "sf_mappings_16", & "on-shell single mapping", & u, results) <>= public :: sf_mappings_16 <>= subroutine sf_mappings_16 (u) integer, intent(in) :: u class(sf_mapping_t), allocatable :: mapping real(default), dimension(1) :: p write (u, "(A)") "* Test output: sf_mappings_16" write (u, "(A)") "* Purpose: probe on-shell single mapping" write (u, "(A)") allocate (sf_os_mapping_single_t :: mapping) select type (mapping) type is (sf_os_mapping_single_t) call mapping%init (0.5_default) call mapping%set_index (1, 1) end select call mapping%write (u) write (u, *) write (u, "(A)") "Probe at (0):" p = [0._default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Probe at (0.5):" p = [0.5_default] call mapping%check (u, p, 1-p, "F7.5") write (u, *) write (u, "(A)") "Compute integral:" write (u, "(3x,A,1x,F7.5)") "I =", mapping%integral (100000) deallocate (mapping) write (u, "(A)") write (u, "(A)") "* Test output end: sf_mappings_16" end subroutine sf_mappings_16 @ %def sf_mappings_16 @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Structure function base} <<[[sf_base.f90]]>>= <> module sf_base <> <> use io_units use format_utils, only: write_separator use format_defs, only: FMT_17, FMT_19 use diagnostics use lorentz use quantum_numbers use interactions use evaluators use pdg_arrays use beams use sf_aux use sf_mappings use constants, only: one, two use physics_defs, only: n_beams_rescaled <> <> <> <> <> contains <> end module sf_base @ %def sf_base @ \subsection{Abstract rescale data-type} NLO calculations require the treatment of initial state parton radiation. The radiation of a parton rescales the energy fraction which enters the hard process. We allow for different rescale settings by extending the abstract. [[sf_rescale_t]] data type. <>= public :: sf_rescale_t <>= type, abstract :: sf_rescale_t integer :: i_beam = 0 contains <> end type sf_rescale_t @ %def sf_rescale_t @ <>= procedure (sf_rescale_apply), deferred :: apply <>= abstract interface subroutine sf_rescale_apply (func, x) import class(sf_rescale_t), intent(in) :: func real(default), intent(inout) :: x end subroutine sf_rescale_apply end interface @ %def rescale_apply @ <>= procedure :: set_i_beam => sf_rescale_set_i_beam <>= subroutine sf_rescale_set_i_beam (func, i_beam) class(sf_rescale_t), intent(inout) :: func integer, intent(in) :: i_beam func%i_beam = i_beam end subroutine sf_rescale_set_i_beam @ %def rescale_set_i_beam @ <>= public :: sf_rescale_collinear_t <>= type, extends (sf_rescale_t) :: sf_rescale_collinear_t real(default) :: xi_tilde contains <> end type sf_rescale_collinear_t @ %def sf_rescale_collinear_t @ For the subtraction terms we need to rescale the Born $x$ of both beams in the collinear limit. This leaves one beam unaffected and rescales the other according to \begin{equation} x = \frac{\overline{x}}{1-\xi} \end{equation} which is the collinear limit of [[sf_rescale_real_apply]]. <>= procedure :: apply => sf_rescale_collinear_apply <>= subroutine sf_rescale_collinear_apply (func, x) class(sf_rescale_collinear_t), intent(in) :: func real(default), intent(inout) :: x real(default) :: xi if (debug2_active (D_BEAMS)) then print *, 'Rescaling function - Collinear: ' print *, 'Input, unscaled x: ', x print *, 'xi_tilde: ', func%xi_tilde end if xi = func%xi_tilde * (one - x) x = x / (one - xi) if (debug2_active (D_BEAMS)) print *, 'rescaled x: ', x end subroutine sf_rescale_collinear_apply @ %def sf_rescale_collinear_apply @ <>= procedure :: set => sf_rescale_collinear_set <>= subroutine sf_rescale_collinear_set (func, xi_tilde) class(sf_rescale_collinear_t), intent(inout) :: func real(default), intent(in) :: xi_tilde func%xi_tilde = xi_tilde end subroutine sf_rescale_collinear_set @ %def sf_rescale_collinear_set @ <>= public :: sf_rescale_real_t <>= type, extends (sf_rescale_t) :: sf_rescale_real_t real(default) :: xi, y contains <> end type sf_rescale_real_t @ %def sf_rescale_real_t @ In case of IS Splittings, the beam $x$ changes from Born to real and thus needs to be rescaled 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} Refs: \begin{itemize} \item[\textbullet] [0709.2092] Eq. (5.7). \item[\textbullet] [0907.4076] Eq. (2.21). \item Christian Weiss' PhD Thesis (DESY-THESIS-2017-025), Eq. (A.2.3). \end{itemize} <>= procedure :: apply => sf_rescale_real_apply <>= subroutine sf_rescale_real_apply (func, x) class(sf_rescale_real_t), intent(in) :: func real(default), intent(inout) :: x real(default) :: onepy, onemy if (debug2_active (D_BEAMS)) then print *, 'Rescaling function - Real: ' print *, 'Input, unscaled: ', x print *, 'Beam index: ', func%i_beam print *, 'xi: ', func%xi, 'y: ', func%y end if x = x / sqrt (one - func%xi) onepy = one + func%y; onemy = one - func%y if (func%i_beam == 1) then x = x * sqrt ((two - func%xi * onemy) / (two - func%xi * onepy)) else if (func%i_beam == 2) then x = x * sqrt ((two - func%xi * onepy) / (two - func%xi * onemy)) else call msg_fatal ("sf_rescale_real_apply - invalid beam index") end if if (debug2_active (D_BEAMS)) print *, 'rescaled x: ', x end subroutine sf_rescale_real_apply @ %def sf_rescale_real_apply @ <>= procedure :: set => sf_rescale_real_set <>= subroutine sf_rescale_real_set (func, xi, y) class(sf_rescale_real_t), intent(inout) :: func real(default), intent(in) :: xi, y func%xi = xi; func%y = y end subroutine sf_rescale_real_set @ %def sf_rescale_real_set <>= public :: sf_rescale_dglap_t <>= type, extends(sf_rescale_t) :: sf_rescale_dglap_t real(default), dimension(:), allocatable :: z contains <> end type sf_rescale_dglap_t @ %def sf_rescale_dglap_t @ <>= procedure :: apply => sf_rescale_dglap_apply <>= subroutine sf_rescale_dglap_apply (func, x) class(sf_rescale_dglap_t), intent(in) :: func real(default), intent(inout) :: x if (debug2_active (D_BEAMS)) then print *, "Rescaling function - DGLAP:" print *, "Input: ", x print *, "Beam index: ", func%i_beam print *, "z: ", func%z end if x = x / func%z(func%i_beam) if (debug2_active (D_BEAMS)) print *, "scaled x: ", x end subroutine sf_rescale_dglap_apply @ %def sf_rescale_dglap_apply @ <>= procedure :: set => sf_rescale_dglap_set <>= subroutine sf_rescale_dglap_set (func, z) class(sf_rescale_dglap_t), intent(inout) :: func real(default), dimension(:), intent(in) :: z ! allocate-on-assginment func%z = z end subroutine sf_rescale_dglap_set @ %def sf_rescale_dglap_set @ \subsection{Abstract structure-function data type} This type should hold all configuration data for a specific type of structure function. The base object is empty; the implementations will fill it. <>= public :: sf_data_t <>= type, abstract :: sf_data_t contains <> end type sf_data_t @ %def sf_data_t @ Output. <>= procedure (sf_data_write), deferred :: write <>= abstract interface subroutine sf_data_write (data, unit, verbose) import class(sf_data_t), intent(in) :: data integer, intent(in), optional :: unit logical, intent(in), optional :: verbose end subroutine sf_data_write end interface @ %def sf_data_write @ Return true if this structure function is in generator mode. In that case, all parameters are free, otherwise bound. (We do not support mixed cases.) Default is: no generator. <>= procedure :: is_generator => sf_data_is_generator <>= function sf_data_is_generator (data) result (flag) class(sf_data_t), intent(in) :: data logical :: flag flag = .false. end function sf_data_is_generator @ %def sf_data_is_generator @ Return the number of input parameters that determine the structure function. <>= procedure (sf_data_get_int), deferred :: get_n_par <>= abstract interface function sf_data_get_int (data) result (n) import class(sf_data_t), intent(in) :: data integer :: n end function sf_data_get_int end interface @ %def sf_data_get_int @ Return the outgoing particle PDG codes for the current setup. The codes can be an array of particles, for each beam. <>= procedure (sf_data_get_pdg_out), deferred :: get_pdg_out <>= abstract interface subroutine sf_data_get_pdg_out (data, pdg_out) import class(sf_data_t), intent(in) :: data type(pdg_array_t), dimension(:), intent(inout) :: pdg_out end subroutine sf_data_get_pdg_out end interface @ %def sf_data_get_pdg_out @ Allocate a matching structure function interaction object and properly initialize it. <>= procedure (sf_data_allocate_sf_int), deferred :: allocate_sf_int <>= abstract interface subroutine sf_data_allocate_sf_int (data, sf_int) import class(sf_data_t), intent(in) :: data class(sf_int_t), intent(inout), allocatable :: sf_int end subroutine sf_data_allocate_sf_int end interface @ %def sf_data_allocate_sf_int @ Return the PDF set index, if applicable. We implement a default method which returns zero. The PDF (builtin and LHA) implementations will override this. <>= procedure :: get_pdf_set => sf_data_get_pdf_set <>= elemental function sf_data_get_pdf_set (data) result (pdf_set) class(sf_data_t), intent(in) :: data integer :: pdf_set pdf_set = 0 end function sf_data_get_pdf_set @ %def sf_data_get_pdf_set @ Return the spectrum file, if applicable. We implement a default method which returns zero. CIRCE1, CIRCE2 and the beam spectrum will override this. <>= procedure :: get_beam_file => sf_data_get_beam_file <>= function sf_data_get_beam_file (data) result (file) class(sf_data_t), intent(in) :: data type(string_t) :: file file = "" end function sf_data_get_beam_file @ %def sf_data_get_beam_file @ \subsection{Structure-function chain configuration} This is the data type that the [[process]] module uses for setting up its structure-function chain. For each structure function described by the beam data, there is an entry. The [[i]] array indicates the beam(s) to which this structure function applies, and the [[data]] object contains the actual configuration data. <>= public :: sf_config_t <>= type :: sf_config_t integer, dimension(:), allocatable :: i class(sf_data_t), allocatable :: data contains <> end type sf_config_t @ %def sf_config_t @ Output: <>= procedure :: write => sf_config_write <>= subroutine sf_config_write (object, unit, verbose) class(sf_config_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: verbose integer :: u u = given_output_unit (unit) if (allocated (object%i)) then write (u, "(1x,A,2(1x,I0))") "Structure-function configuration: & &beam(s)", object%i if (allocated (object%data)) & call object%data%write (u, verbose = verbose) else write (u, "(1x,A)") "Structure-function configuration: [undefined]" end if end subroutine sf_config_write @ %def sf_config_write @ Initialize. <>= procedure :: init => sf_config_init <>= subroutine sf_config_init (sf_config, i_beam, sf_data) class(sf_config_t), intent(out) :: sf_config integer, dimension(:), intent(in) :: i_beam class(sf_data_t), intent(in) :: sf_data allocate (sf_config%i (size (i_beam)), source = i_beam) allocate (sf_config%data, source = sf_data) end subroutine sf_config_init @ %def sf_config_init @ Return the PDF set, if any. <>= procedure :: get_pdf_set => sf_config_get_pdf_set <>= elemental function sf_config_get_pdf_set (sf_config) result (pdf_set) class(sf_config_t), intent(in) :: sf_config integer :: pdf_set pdf_set = sf_config%data%get_pdf_set () end function sf_config_get_pdf_set @ %def sf_config_get_pdf_set @ Return the beam spectrum file, if any. <>= procedure :: get_beam_file => sf_config_get_beam_file <>= function sf_config_get_beam_file (sf_config) result (file) class(sf_config_t), intent(in) :: sf_config type(string_t) :: file file = sf_config%data%get_beam_file () end function sf_config_get_beam_file @ %def sf_config_get_beam_file @ \subsection{Structure-function instance} The [[sf_int_t]] data type contains an [[interaction_t]] object (it is an extension of this type) and a pointer to the [[sf_data_t]] configuration data. This interaction, or copies of it, is used to implement structure-function kinematics and dynamics in the context of process evaluation. The status code [[status]] tells whether the interaction is undefined, has defined kinematics (but matrix elements invalid), or is completely defined. There is also a status code for failure. The implementation is responsible for updating the status. The entries [[mi2]], [[mr2]], and [[mo2]] hold the squared invariant masses of the incoming, radiated, and outgoing particle, respectively. They are supposed to be set upon initialization, but could also be varied event by event. If the radiated or outgoing mass is nonzero, we may need to apply an on-shell projection. The projection mode is stored as [[on_shell_mode]]. The array [[beam_index]] is the list of beams on which this structure function applies ($1$, $2$, or both). The arrays [[incoming]], [[radiated]], and [[outgoing]] contain the indices of the respective particle sets within the interaction, for convenient lookup. The array [[par_index]] indicates the MC input parameters that this entry will use up in the structure-function chain. The first parameter (or the first two, for a spectrum) in this array determines the momentum fraction and is thus subject to global mappings. In the abstract base type, we do not implement the data pointer. This allows us to restrict its type in the implementations. <>= public :: sf_int_t <>= type, abstract, extends (interaction_t) :: sf_int_t integer :: status = SF_UNDEFINED real(default), dimension(:), allocatable :: mi2 real(default), dimension(:), allocatable :: mr2 real(default), dimension(:), allocatable :: mo2 integer :: on_shell_mode = KEEP_ENERGY logical :: qmin_defined = .false. logical :: qmax_defined = .false. real(default), dimension(:), allocatable :: qmin real(default), dimension(:), allocatable :: qmax integer, dimension(:), allocatable :: beam_index integer, dimension(:), allocatable :: incoming integer, dimension(:), allocatable :: radiated integer, dimension(:), allocatable :: outgoing integer, dimension(:), allocatable :: par_index integer, dimension(:), allocatable :: par_primary contains <> end type sf_int_t @ %def sf_int_t @ Status codes. The codes that refer to links, masks, and connections, apply to structure-function chains only. The status codes are public. <>= integer, parameter, public :: SF_UNDEFINED = 0 integer, parameter, public :: SF_INITIAL = 1 integer, parameter, public :: SF_DONE_LINKS = 2 integer, parameter, public :: SF_FAILED_MASK = 3 integer, parameter, public :: SF_DONE_MASK = 4 integer, parameter, public :: SF_FAILED_CONNECTIONS = 5 integer, parameter, public :: SF_DONE_CONNECTIONS = 6 integer, parameter, public :: SF_SEED_KINEMATICS = 10 integer, parameter, public :: SF_FAILED_KINEMATICS = 11 integer, parameter, public :: SF_DONE_KINEMATICS = 12 integer, parameter, public :: SF_FAILED_EVALUATION = 13 integer, parameter, public :: SF_EVALUATED = 20 @ %def SF_UNDEFINED SF_INITIAL @ %def SF_DONE_LINKS SF_DONE_MASK SF_DONE_CONNECTIONS @ %def SF_DONE_KINEMATICS SF_EVALUATED @ %def SF_FAILED_MASK SF_FAILED_CONNECTIONS @ %def SF_FAILED_KINEMATICS SF_FAILED_EVALUATION @ Write a string version of the status code: <>= subroutine write_sf_status (status, u) integer, intent(in) :: status integer, intent(in) :: u select case (status) case (SF_UNDEFINED) write (u, "(1x,'[',A,']')") "undefined" case (SF_INITIAL) write (u, "(1x,'[',A,']')") "initialized" case (SF_DONE_LINKS) write (u, "(1x,'[',A,']')") "links set" case (SF_FAILED_MASK) write (u, "(1x,'[',A,']')") "mask mismatch" case (SF_DONE_MASK) write (u, "(1x,'[',A,']')") "mask set" case (SF_FAILED_CONNECTIONS) write (u, "(1x,'[',A,']')") "connections failed" case (SF_DONE_CONNECTIONS) write (u, "(1x,'[',A,']')") "connections set" case (SF_SEED_KINEMATICS) write (u, "(1x,'[',A,']')") "incoming momenta set" case (SF_FAILED_KINEMATICS) write (u, "(1x,'[',A,']')") "kinematics failed" case (SF_DONE_KINEMATICS) write (u, "(1x,'[',A,']')") "kinematics set" case (SF_FAILED_EVALUATION) write (u, "(1x,'[',A,']')") "evaluation failed" case (SF_EVALUATED) write (u, "(1x,'[',A,']')") "evaluated" end select end subroutine write_sf_status @ %def write_sf_status @ This is the basic output routine. Display status and interaction. <>= procedure :: base_write => sf_int_base_write <>= subroutine sf_int_base_write (object, unit, testflag) class(sf_int_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u u = given_output_unit (unit) write (u, "(1x,A)", advance="no") "SF instance:" call write_sf_status (object%status, u) if (allocated (object%beam_index)) & write (u, "(3x,A,2(1x,I0))") "beam =", object%beam_index if (allocated (object%incoming)) & write (u, "(3x,A,2(1x,I0))") "incoming =", object%incoming if (allocated (object%radiated)) & write (u, "(3x,A,2(1x,I0))") "radiated =", object%radiated if (allocated (object%outgoing)) & write (u, "(3x,A,2(1x,I0))") "outgoing =", object%outgoing if (allocated (object%par_index)) & write (u, "(3x,A,2(1x,I0))") "parameter =", object%par_index if (object%qmin_defined) & write (u, "(3x,A,1x," // FMT_19 // ")") "q_min =", object%qmin if (object%qmax_defined) & write (u, "(3x,A,1x," // FMT_19 // ")") "q_max =", object%qmax call object%interaction_t%basic_write (u, testflag = testflag) end subroutine sf_int_base_write @ %def sf_int_base_write @ The type string identifies the structure function class, and possibly more details about the structure function. <>= procedure (sf_int_type_string), deferred :: type_string <>= abstract interface function sf_int_type_string (object) result (string) import class(sf_int_t), intent(in) :: object type(string_t) :: string end function sf_int_type_string end interface @ %def sf_int_type_string @ Output of the concrete object. We should not forget to call the output routine for the base type. <>= procedure (sf_int_write), deferred :: write <>= abstract interface subroutine sf_int_write (object, unit, testflag) import class(sf_int_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag end subroutine sf_int_write end interface @ %def sf_int_write @ Basic initialization: set the invariant masses for the particles and initialize the interaction. The caller should then add states to the interaction and freeze it. The dimension of the mask should be equal to the sum of the dimensions of the mass-squared arrays, which determine incoming, radiated, and outgoing particles, respectively. Optionally, we can define minimum and maximum values for the momentum transfer to the outgoing particle(s). If all masses are zero, this is actually required for non-collinear splitting. <>= procedure :: base_init => sf_int_base_init <>= subroutine sf_int_base_init & (sf_int, mask, mi2, mr2, mo2, qmin, qmax, hel_lock) class(sf_int_t), intent(out) :: sf_int type (quantum_numbers_mask_t), dimension(:), intent(in) :: mask real(default), dimension(:), intent(in) :: mi2, mr2, mo2 real(default), dimension(:), intent(in), optional :: qmin, qmax integer, dimension(:), intent(in), optional :: hel_lock allocate (sf_int%mi2 (size (mi2))) sf_int%mi2 = mi2 allocate (sf_int%mr2 (size (mr2))) sf_int%mr2 = mr2 allocate (sf_int%mo2 (size (mo2))) sf_int%mo2 = mo2 if (present (qmin)) then sf_int%qmin_defined = .true. allocate (sf_int%qmin (size (qmin))) sf_int%qmin = qmin end if if (present (qmax)) then sf_int%qmax_defined = .true. allocate (sf_int%qmax (size (qmax))) sf_int%qmax = qmax end if call sf_int%interaction_t%basic_init & (size (mi2), 0, size (mr2) + size (mo2), & mask = mask, hel_lock = hel_lock, set_relations = .true.) end subroutine sf_int_base_init @ %def sf_int_base_init @ Set the indices of the incoming, radiated, and outgoing particles, respectively. <>= procedure :: set_incoming => sf_int_set_incoming procedure :: set_radiated => sf_int_set_radiated procedure :: set_outgoing => sf_int_set_outgoing <>= subroutine sf_int_set_incoming (sf_int, incoming) class(sf_int_t), intent(inout) :: sf_int integer, dimension(:), intent(in) :: incoming allocate (sf_int%incoming (size (incoming))) sf_int%incoming = incoming end subroutine sf_int_set_incoming subroutine sf_int_set_radiated (sf_int, radiated) class(sf_int_t), intent(inout) :: sf_int integer, dimension(:), intent(in) :: radiated allocate (sf_int%radiated (size (radiated))) sf_int%radiated = radiated end subroutine sf_int_set_radiated subroutine sf_int_set_outgoing (sf_int, outgoing) class(sf_int_t), intent(inout) :: sf_int integer, dimension(:), intent(in) :: outgoing allocate (sf_int%outgoing (size (outgoing))) sf_int%outgoing = outgoing end subroutine sf_int_set_outgoing @ %def sf_int_set_incoming @ %def sf_int_set_radiated @ %def sf_int_set_outgoing @ Initialization. This proceeds via an abstract data object, which for the actual implementation should have the matching concrete type. Since all implementations have the same signature, we can prepare a deferred procedure. The data object will become the target of a corresponding pointer within the [[sf_int_t]] implementation. This should call the previous procedure. <>= procedure (sf_int_init), deferred :: init <>= abstract interface subroutine sf_int_init (sf_int, data) import class(sf_int_t), intent(out) :: sf_int class(sf_data_t), intent(in), target :: data end subroutine sf_int_init end interface @ %def sf_int_init @ Complete initialization. This routine contains initializations that can only be performed after the interaction object got its final shape, i.e., redundant helicities have been eliminated by matching with beams and process. The default implementation does nothing. The [[target]] attribute is formally required since some overriding implementations use a temporary pointer (iterator) to the state-matrix component. It doesn't appear to make a real difference, though. <>= procedure :: setup_constants => sf_int_setup_constants <>= subroutine sf_int_setup_constants (sf_int) class(sf_int_t), intent(inout), target :: sf_int end subroutine sf_int_setup_constants @ %def sf_int_setup_constants @ Set beam indices, i.e., the beam(s) on which this structure function applies. <>= procedure :: set_beam_index => sf_int_set_beam_index <>= subroutine sf_int_set_beam_index (sf_int, beam_index) class(sf_int_t), intent(inout) :: sf_int integer, dimension(:), intent(in) :: beam_index allocate (sf_int%beam_index (size (beam_index))) sf_int%beam_index = beam_index end subroutine sf_int_set_beam_index @ %def sf_int_set_beam_index @ Set parameter indices, indicating which MC input parameters are to be used for evaluating this structure function. <>= procedure :: set_par_index => sf_int_set_par_index <>= subroutine sf_int_set_par_index (sf_int, par_index) class(sf_int_t), intent(inout) :: sf_int integer, dimension(:), intent(in) :: par_index allocate (sf_int%par_index (size (par_index))) sf_int%par_index = par_index end subroutine sf_int_set_par_index @ %def sf_int_set_par_index @ Initialize the structure-function kinematics, setting incoming momenta. We assume that array shapes match. Three versions. The first version relies on the momenta being linked to another interaction. The second version sets the momenta explicitly. In the third version, we first compute momenta for the specified energies and store those. <>= generic :: seed_kinematics => sf_int_receive_momenta generic :: seed_kinematics => sf_int_seed_momenta generic :: seed_kinematics => sf_int_seed_energies procedure :: sf_int_receive_momenta procedure :: sf_int_seed_momenta procedure :: sf_int_seed_energies <>= subroutine sf_int_receive_momenta (sf_int) class(sf_int_t), intent(inout) :: sf_int if (sf_int%status >= SF_INITIAL) then call sf_int%receive_momenta () sf_int%status = SF_SEED_KINEMATICS end if end subroutine sf_int_receive_momenta subroutine sf_int_seed_momenta (sf_int, k) class(sf_int_t), intent(inout) :: sf_int type(vector4_t), dimension(:), intent(in) :: k if (sf_int%status >= SF_INITIAL) then call sf_int%set_momenta (k, outgoing=.false.) sf_int%status = SF_SEED_KINEMATICS end if end subroutine sf_int_seed_momenta subroutine sf_int_seed_energies (sf_int, E) class(sf_int_t), intent(inout) :: sf_int real(default), dimension(:), intent(in) :: E type(vector4_t), dimension(:), allocatable :: k integer :: j if (sf_int%status >= SF_INITIAL) then allocate (k (size (E))) if (all (E**2 >= sf_int%mi2)) then do j = 1, size (E) k(j) = vector4_moving (E(j), & (3-2*j) * sqrt (E(j)**2 - sf_int%mi2(j)), 3) end do call sf_int%seed_kinematics (k) end if end if end subroutine sf_int_seed_energies @ %def sf_int_seed_momenta @ %def sf_int_seed_energies @ Tell if in generator mode. By default, this is false. To be overridden where appropriate; we may refer to the [[is_generator]] method of the [[data]] component in the concrete type. <>= procedure :: is_generator => sf_int_is_generator <>= function sf_int_is_generator (sf_int) result (flag) class(sf_int_t), intent(in) :: sf_int logical :: flag flag = .false. end function sf_int_is_generator @ %def sf_int_is_generator @ Generate free parameters [[r]]. Parameters are free if they do not correspond to integration parameters (i.e., are bound), but are generated by the structure function object itself. By default, all parameters are bound, and the output values of this procedure will be discarded. With free parameters, we have to override this procedure. The value [[x_free]] is the renormalization factor of the total energy that corresponds to the free parameters. If there are no free parameters, the procedure will not change its value, which starts as unity. Otherwise, the fraction is typically decreased, but may also be increased in some cases. <>= procedure :: generate_free => sf_int_generate_free <>= subroutine sf_int_generate_free (sf_int, r, rb, x_free) class(sf_int_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: r, rb real(default), intent(inout) :: x_free r = 0 rb= 1 end subroutine sf_int_generate_free @ %def sf_int_generate_free @ Complete the structure-function kinematics, derived from an input parameter (array) $r$ between 0 and 1. The interaction momenta are calculated, and we return $x$ (the momentum fraction), and $f$ (the Jacobian factor for the map $r\to x$), if [[map]] is set. If the [[map]] flag is unset, $r$ and $x$ values will coincide, and $f$ will become unity. If it is set, the structure-function implementation chooses a convenient mapping from $r$ to $x$ with Jacobian $f$. In the [[inverse_kinematics]] variant, we exchange the intent of [[x]] and [[r]]. The momenta are calculated only if the optional flag [[set_momenta]] is present and set. Internal parameters of [[sf_int]] are calculated only if the optional flag [[set_x]] is present and set. Update 2018-08-22: Throughout this algorithm, we now carry [[xb]]=$1-x$ together with [[x]] values, as we did for [[r]] before. This allows us to handle unstable endpoint numerics wherever necessary. The only place where the changes actually did matter was for inverse kinematics in the ISR setup, with a very soft photon, but it might be most sensible to apply the extension with [[xb]] everywhere. <>= procedure (sf_int_complete_kinematics), deferred :: complete_kinematics procedure (sf_int_inverse_kinematics), deferred :: inverse_kinematics <>= abstract interface subroutine sf_int_complete_kinematics (sf_int, x, xb, f, r, rb, map) import class(sf_int_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: x real(default), dimension(:), intent(out) :: xb real(default), intent(out) :: f real(default), dimension(:), intent(in) :: r real(default), dimension(:), intent(in) :: rb logical, intent(in) :: map end subroutine sf_int_complete_kinematics end interface abstract interface subroutine sf_int_inverse_kinematics (sf_int, x, xb, f, r, rb, map, set_momenta) import class(sf_int_t), intent(inout) :: sf_int real(default), dimension(:), intent(in) :: x real(default), dimension(:), intent(in) :: xb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: r real(default), dimension(:), intent(out) :: rb logical, intent(in) :: map logical, intent(in), optional :: set_momenta end subroutine sf_int_inverse_kinematics end interface @ %def sf_int_complete_kinematics @ %def sf_int_inverse_kinematics @ Single splitting: compute momenta, given $x$ input parameters. We assume that the incoming momentum is set. The status code is set to [[SF_FAILED_KINEMATICS]] if the $x$ array does not correspond to a valid momentum configuration. Otherwise, it is updated to [[SF_DONE_KINEMATICS]]. We force the outgoing particle on-shell. The on-shell projection is determined by the [[on_shell_mode]]. The radiated particle should already be on shell. <>= procedure :: split_momentum => sf_int_split_momentum <>= subroutine sf_int_split_momentum (sf_int, x, xb) class(sf_int_t), intent(inout) :: sf_int real(default), dimension(:), intent(in) :: x real(default), dimension(:), intent(in) :: xb type(vector4_t) :: k type(vector4_t), dimension(2) :: q type(splitting_data_t) :: sd real(default) :: E1, E2 logical :: fail if (sf_int%status >= SF_SEED_KINEMATICS) then k = sf_int%get_momentum (1) call sd%init (k, & sf_int%mi2(1), sf_int%mr2(1), sf_int%mo2(1), & collinear = size (x) == 1) call sd%set_t_bounds (x(1), xb(1)) select case (size (x)) case (1) case (3) if (sf_int%qmax_defined) then if (sf_int%qmin_defined) then call sd%sample_t (x(2), & t0 = - sf_int%qmax(1) ** 2, t1 = - sf_int%qmin(1) ** 2) else call sd%sample_t (x(2), & t0 = - sf_int%qmax(1) ** 2) end if else if (sf_int%qmin_defined) then call sd%sample_t (x(2), t1 = - sf_int%qmin(1) ** 2) else call sd%sample_t (x(2)) end if end if call sd%sample_phi (x(3)) case default call msg_bug ("Structure function: impossible number of parameters") end select q = sd%split_momentum (k) call on_shell (q, [sf_int%mr2, sf_int%mo2], & sf_int%on_shell_mode) call sf_int%set_momenta (q, outgoing=.true.) E1 = energy (q(1)) E2 = energy (q(2)) fail = E1 < 0 .or. E2 < 0 & .or. E1 ** 2 < sf_int%mr2(1) & .or. E2 ** 2 < sf_int%mo2(1) if (fail) then sf_int%status = SF_FAILED_KINEMATICS else sf_int%status = SF_DONE_KINEMATICS end if end if end subroutine sf_int_split_momentum @ %def sf_test_split_momentum @ Pair splitting: two incoming momenta, two radiated, two outgoing. This is simple because we insist on all momenta being collinear. <>= procedure :: split_momenta => sf_int_split_momenta <>= subroutine sf_int_split_momenta (sf_int, x, xb) class(sf_int_t), intent(inout) :: sf_int real(default), dimension(:), intent(in) :: x real(default), dimension(:), intent(in) :: xb type(vector4_t), dimension(2) :: k type(vector4_t), dimension(4) :: q real(default), dimension(4) :: E logical :: fail if (sf_int%status >= SF_SEED_KINEMATICS) then select case (size (x)) case (2) case default call msg_bug ("Pair structure function: recoil requested & &but not implemented yet") end select k(1) = sf_int%get_momentum (1) k(2) = sf_int%get_momentum (2) q(1:2) = xb * k q(3:4) = x * k select case (size (sf_int%mr2)) case (2) call on_shell (q, & [sf_int%mr2(1), sf_int%mr2(2), & sf_int%mo2(1), sf_int%mo2(2)], & sf_int%on_shell_mode) call sf_int%set_momenta (q, outgoing=.true.) E = energy (q) fail = any (E < 0) & .or. any (E(1:2) ** 2 < sf_int%mr2) & .or. any (E(3:4) ** 2 < sf_int%mo2) case default; call msg_bug ("split momenta: incorrect use") end select if (fail) then sf_int%status = SF_FAILED_KINEMATICS else sf_int%status = SF_DONE_KINEMATICS end if end if end subroutine sf_int_split_momenta @ %def sf_int_split_momenta @ Pair spectrum: the reduced version of the previous splitting, without radiated momenta. <>= procedure :: reduce_momenta => sf_int_reduce_momenta <>= subroutine sf_int_reduce_momenta (sf_int, x) class(sf_int_t), intent(inout) :: sf_int real(default), dimension(:), intent(in) :: x type(vector4_t), dimension(2) :: k type(vector4_t), dimension(2) :: q real(default), dimension(2) :: E logical :: fail if (sf_int%status >= SF_SEED_KINEMATICS) then select case (size (x)) case (2) case default call msg_bug ("Pair spectrum: recoil requested & &but not implemented yet") end select k(1) = sf_int%get_momentum (1) k(2) = sf_int%get_momentum (2) q = x * k call on_shell (q, & [sf_int%mo2(1), sf_int%mo2(2)], & sf_int%on_shell_mode) call sf_int%set_momenta (q, outgoing=.true.) E = energy (q) fail = any (E < 0) & .or. any (E ** 2 < sf_int%mo2) if (fail) then sf_int%status = SF_FAILED_KINEMATICS else sf_int%status = SF_DONE_KINEMATICS end if end if end subroutine sf_int_reduce_momenta @ %def sf_int_reduce_momenta @ The inverse procedure: we compute the [[x]] array from the momentum configuration. In an overriding TBP, we may also set internal data that depend on this, for convenience. NOTE: Here and above, the single-particle case is treated in detail, allowing for non-collinearity and non-vanishing masses and nontrivial momentum-transfer bounds. For the pair case, we currently implement only collinear splitting and assume massless particles. This should be improved. Update 2017-08-22: recover also [[xb]], using the updated [[recover]] method of the splitting-data object. Th <>= procedure :: recover_x => sf_int_recover_x procedure :: base_recover_x => sf_int_recover_x <>= subroutine sf_int_recover_x (sf_int, x, xb, x_free) class(sf_int_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: x real(default), dimension(:), intent(out) :: xb real(default), intent(inout), optional :: x_free type(vector4_t), dimension(:), allocatable :: k type(vector4_t), dimension(:), allocatable :: q type(splitting_data_t) :: sd if (sf_int%status >= SF_SEED_KINEMATICS) then allocate (k (sf_int%interaction_t%get_n_in ())) allocate (q (sf_int%interaction_t%get_n_out ())) k = sf_int%get_momenta (outgoing=.false.) q = sf_int%get_momenta (outgoing=.true.) select case (size (k)) case (1) call sd%init (k(1), & sf_int%mi2(1), sf_int%mr2(1), sf_int%mo2(1), & collinear = size (x) == 1) call sd%recover (k(1), q, sf_int%on_shell_mode) x(1) = sd%get_x () xb(1) = sd%get_xb () select case (size (x)) case (1) case (3) if (sf_int%qmax_defined) then if (sf_int%qmin_defined) then call sd%inverse_t (x(2), & t0 = - sf_int%qmax(1) ** 2, t1 = - sf_int%qmin(1) ** 2) else call sd%inverse_t (x(2), & t0 = - sf_int%qmax(1) ** 2) end if else if (sf_int%qmin_defined) then call sd%inverse_t (x(2), t1 = - sf_int%qmin(1) ** 2) else call sd%inverse_t (x(2)) end if end if call sd%inverse_phi (x(3)) xb(2:3) = 1 - x(2:3) case default call msg_bug ("Structure function: impossible number & &of parameters") end select case (2) select case (size (x)) case (2) case default call msg_bug ("Pair structure function: recoil requested & &but not implemented yet") end select select case (sf_int%on_shell_mode) case (KEEP_ENERGY) select case (size (q)) case (4) x = energy (q(3:4)) / energy (k) xb= energy (q(1:2)) / energy (k) case (2) x = energy (q) / energy (k) xb= 1 - x end select case (KEEP_MOMENTUM) select case (size (q)) case (4) x = longitudinal_part (q(3:4)) / longitudinal_part (k) xb= longitudinal_part (q(1:2)) / longitudinal_part (k) case (2) x = longitudinal_part (q) / longitudinal_part (k) xb= 1 - x end select end select end select end if end subroutine sf_int_recover_x @ %def sf_int_recover_x @ Apply the structure function, i.e., evaluate the interaction. For the calculation, we may use the stored momenta, any further information stored inside the [[sf_int]] implementation during kinematics setup, and the given energy scale. It may happen that for the given kinematics the value is not defined. This should be indicated by the status code. <>= procedure (sf_int_apply), deferred :: apply <>= abstract interface subroutine sf_int_apply (sf_int, scale, rescale, i_sub) import class(sf_int_t), intent(inout) :: sf_int real(default), intent(in) :: scale class(sf_rescale_t), intent(in), optional :: rescale integer, intent(in), optional :: i_sub end subroutine sf_int_apply end interface @ %def sf_int_apply @ \subsection{Accessing the structure function} Return metadata. Once [[interaction_t]] is rewritten in OO, some of this will be inherited. The number of outgoing particles is equal to the number of incoming particles. The radiated particles are the difference. <>= procedure :: get_n_in => sf_int_get_n_in procedure :: get_n_rad => sf_int_get_n_rad procedure :: get_n_out => sf_int_get_n_out <>= pure function sf_int_get_n_in (object) result (n_in) class(sf_int_t), intent(in) :: object integer :: n_in n_in = object%interaction_t%get_n_in () end function sf_int_get_n_in pure function sf_int_get_n_rad (object) result (n_rad) class(sf_int_t), intent(in) :: object integer :: n_rad n_rad = object%interaction_t%get_n_out () & - object%interaction_t%get_n_in () end function sf_int_get_n_rad pure function sf_int_get_n_out (object) result (n_out) class(sf_int_t), intent(in) :: object integer :: n_out n_out = object%interaction_t%get_n_in () end function sf_int_get_n_out @ %def sf_int_get_n_in @ %def sf_int_get_n_rad @ %def sf_int_get_n_out @ Number of matrix element entries in the interaction: <>= procedure :: get_n_states => sf_int_get_n_states <>= function sf_int_get_n_states (sf_int) result (n_states) class(sf_int_t), intent(in) :: sf_int integer :: n_states n_states = sf_int%get_n_matrix_elements () end function sf_int_get_n_states @ %def sf_int_get_n_states @ Return a specific state as a quantum-number array. <>= procedure :: get_state => sf_int_get_state <>= function sf_int_get_state (sf_int, i) result (qn) class(sf_int_t), intent(in) :: sf_int type(quantum_numbers_t), dimension(:), allocatable :: qn integer, intent(in) :: i allocate (qn (sf_int%get_n_tot ())) qn = sf_int%get_quantum_numbers (i) end function sf_int_get_state @ %def sf_int_get_state @ Return the matrix-element values for all states. We can assume that the matrix elements are real, so we take the real part. <>= procedure :: get_values => sf_int_get_values <>= subroutine sf_int_get_values (sf_int, value) class(sf_int_t), intent(in) :: sf_int real(default), dimension(:), intent(out) :: value integer :: i if (sf_int%status >= SF_EVALUATED) then do i = 1, size (value) value(i) = real (sf_int%get_matrix_element (i)) end do else value = 0 end if end subroutine sf_int_get_values @ %def sf_int_get_values @ \subsection{Direct calculations} Compute a structure function value (array) directly, given an array of $x$ values and a scale. If the energy is also given, we initialize the kinematics for that energy, otherwise take it from a previous run. We assume that the [[E]] array has dimension [[n_in]], and the [[x]] array has [[n_par]]. Note: the output x values ([[xx]] and [[xxb]]) are unused in this use case. <>= procedure :: compute_values => sf_int_compute_values <>= subroutine sf_int_compute_values (sf_int, value, x, xb, scale, E) class(sf_int_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: value real(default), dimension(:), intent(in) :: x real(default), dimension(:), intent(in) :: xb real(default), intent(in) :: scale real(default), dimension(:), intent(in), optional :: E real(default), dimension(size (x)) :: xx, xxb real(default) :: f if (present (E)) call sf_int%seed_kinematics (E) if (sf_int%status >= SF_SEED_KINEMATICS) then call sf_int%complete_kinematics (xx, xxb, f, x, xb, map=.false.) call sf_int%apply (scale) call sf_int%get_values (value) value = value * f else value = 0 end if end subroutine sf_int_compute_values @ %def sf_int_compute_values @ Compute just a single value for one of the states, i.e., throw the others away. <>= procedure :: compute_value => sf_int_compute_value <>= subroutine sf_int_compute_value & (sf_int, i_state, value, x, xb, scale, E) class(sf_int_t), intent(inout) :: sf_int integer, intent(in) :: i_state real(default), intent(out) :: value real(default), dimension(:), intent(in) :: x real(default), dimension(:), intent(in) :: xb real(default), intent(in) :: scale real(default), dimension(:), intent(in), optional :: E real(default), dimension(:), allocatable :: value_array if (sf_int%status >= SF_INITIAL) then allocate (value_array (sf_int%get_n_states ())) call sf_int%compute_values (value_array, x, xb, scale, E) value = value_array(i_state) else value = 0 end if end subroutine sf_int_compute_value @ %def sf_int_compute_value @ \subsection{Structure-function instance} This is a wrapper for [[sf_int_t]] objects, such that we can build an array with different structure-function types. The structure-function contains an array (a sequence) of [[sf_int_t]] objects. The object, it holds the evaluator that connects the preceding part of the structure-function chain to the current interaction. It also stores the input and output parameter values for the contained structure function. The [[r]] array has a second dimension, corresponding to the mapping channels in a multi-channel configuration. There is a Jacobian entry [[f]] for each channel. The corresponding logical array [[mapping]] tells whether we apply the mapping appropriate for the current structure function in this channel. The [[x]] parameter values (energy fractions) are common to all channels. <>= type :: sf_instance_t class(sf_int_t), allocatable :: int type(evaluator_t) :: eval real(default), dimension(:,:), allocatable :: r real(default), dimension(:,:), allocatable :: rb real(default), dimension(:), allocatable :: f logical, dimension(:), allocatable :: m real(default), dimension(:), allocatable :: x real(default), dimension(:), allocatable :: xb end type sf_instance_t @ %def sf_instance_t @ \subsection{Structure-function chain} A chain is an array of structure functions [[sf]], initiated by a beam setup. We do not use this directly for evaluation, but create instances with copies of the contained interactions. [[n_par]] is the total number of parameters that is necessary for completely determining the structure-function chain. [[n_bound]] is the number of MC input parameters that are requested from the integrator. The difference of [[n_par]] and [[n_bound]] is the number of free parameters, which are generated by a structure-function object in generator mode. <>= public :: sf_chain_t <>= type, extends (beam_t) :: sf_chain_t type(beam_data_t), pointer :: beam_data => null () integer :: n_in = 0 integer :: n_strfun = 0 integer :: n_par = 0 integer :: n_bound = 0 type(sf_instance_t), dimension(:), allocatable :: sf logical :: trace_enable = .false. integer :: trace_unit = 0 contains <> end type sf_chain_t @ %def sf_chain_t @ Finalizer. <>= procedure :: final => sf_chain_final <>= subroutine sf_chain_final (object) class(sf_chain_t), intent(inout) :: object integer :: i call object%final_tracing () if (allocated (object%sf)) then do i = 1, size (object%sf, 1) associate (sf => object%sf(i)) if (allocated (sf%int)) then call sf%int%final () end if end associate end do end if call beam_final (object%beam_t) end subroutine sf_chain_final @ %def sf_chain_final @ Output. <>= procedure :: write => sf_chain_write <>= subroutine sf_chain_write (object, unit) class(sf_chain_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u, i u = given_output_unit (unit) write (u, "(1x,A)") "Incoming particles / structure-function chain:" if (associated (object%beam_data)) then write (u, "(3x,A,I0)") "n_in = ", object%n_in write (u, "(3x,A,I0)") "n_strfun = ", object%n_strfun write (u, "(3x,A,I0)") "n_par = ", object%n_par if (object%n_par /= object%n_bound) then write (u, "(3x,A,I0)") "n_bound = ", object%n_bound end if call object%beam_data%write (u) call write_separator (u) call beam_write (object%beam_t, u) if (allocated (object%sf)) then do i = 1, object%n_strfun associate (sf => object%sf(i)) call write_separator (u) if (allocated (sf%int)) then call sf%int%write (u) else write (u, "(1x,A)") "SF instance: [undefined]" end if end associate end do end if else write (u, "(3x,A)") "[undefined]" end if end subroutine sf_chain_write @ %def sf_chain_write @ Initialize: setup beams. The [[beam_data]] target must remain valid for the lifetime of the chain, since we just establish a pointer. The structure-function configuration array is used to initialize the individual structure-function entries. The target attribute is needed because the [[sf_int]] entries establish pointers to the configuration data. <>= procedure :: init => sf_chain_init <>= subroutine sf_chain_init (sf_chain, beam_data, sf_config) class(sf_chain_t), intent(out) :: sf_chain type(beam_data_t), intent(in), target :: beam_data type(sf_config_t), dimension(:), intent(in), optional, target :: sf_config integer :: i sf_chain%beam_data => beam_data sf_chain%n_in = beam_data%get_n_in () call beam_init (sf_chain%beam_t, beam_data) if (present (sf_config)) then sf_chain%n_strfun = size (sf_config) allocate (sf_chain%sf (sf_chain%n_strfun)) do i = 1, sf_chain%n_strfun call sf_chain%set_strfun (i, sf_config(i)%i, sf_config(i)%data) end do end if end subroutine sf_chain_init @ %def sf_chain_init @ Receive the beam momenta from a source to which the beam interaction is linked. <>= procedure :: receive_beam_momenta => sf_chain_receive_beam_momenta <>= subroutine sf_chain_receive_beam_momenta (sf_chain) class(sf_chain_t), intent(inout), target :: sf_chain type(interaction_t), pointer :: beam_int beam_int => sf_chain%get_beam_int_ptr () call beam_int%receive_momenta () end subroutine sf_chain_receive_beam_momenta @ %def sf_chain_receive_beam_momenta @ Explicitly set the beam momenta. <>= procedure :: set_beam_momenta => sf_chain_set_beam_momenta <>= subroutine sf_chain_set_beam_momenta (sf_chain, p) class(sf_chain_t), intent(inout) :: sf_chain type(vector4_t), dimension(:), intent(in) :: p call beam_set_momenta (sf_chain%beam_t, p) end subroutine sf_chain_set_beam_momenta @ %def sf_chain_set_beam_momenta @ Set a structure-function entry. We use the [[data]] input to allocate the [[int]] structure-function instance with appropriate type, then initialize the entry. The entry establishes a pointer to [[data]]. The index [[i]] is the structure-function index in the chain. <>= procedure :: set_strfun => sf_chain_set_strfun <>= subroutine sf_chain_set_strfun (sf_chain, i, beam_index, data) class(sf_chain_t), intent(inout) :: sf_chain integer, intent(in) :: i integer, dimension(:), intent(in) :: beam_index class(sf_data_t), intent(in), target :: data integer :: n_par, j n_par = data%get_n_par () call data%allocate_sf_int (sf_chain%sf(i)%int) associate (sf_int => sf_chain%sf(i)%int) call sf_int%init (data) call sf_int%set_beam_index (beam_index) call sf_int%set_par_index & ([(j, j = sf_chain%n_par + 1, sf_chain%n_par + n_par)]) sf_chain%n_par = sf_chain%n_par + n_par if (.not. data%is_generator ()) then sf_chain%n_bound = sf_chain%n_bound + n_par end if end associate end subroutine sf_chain_set_strfun @ %def sf_chain_set_strfun @ Return the number of structure-function parameters. <>= procedure :: get_n_par => sf_chain_get_n_par procedure :: get_n_bound => sf_chain_get_n_bound <>= function sf_chain_get_n_par (sf_chain) result (n) class(sf_chain_t), intent(in) :: sf_chain integer :: n n = sf_chain%n_par end function sf_chain_get_n_par function sf_chain_get_n_bound (sf_chain) result (n) class(sf_chain_t), intent(in) :: sf_chain integer :: n n = sf_chain%n_bound end function sf_chain_get_n_bound @ %def sf_chain_get_n_par @ %def sf_chain_get_n_bound @ Return a pointer to the beam interaction. <>= procedure :: get_beam_int_ptr => sf_chain_get_beam_int_ptr <>= function sf_chain_get_beam_int_ptr (sf_chain) result (int) type(interaction_t), pointer :: int class(sf_chain_t), intent(in), target :: sf_chain int => beam_get_int_ptr (sf_chain%beam_t) end function sf_chain_get_beam_int_ptr @ %def sf_chain_get_beam_int_ptr @ Enable the trace feature: record structure function data (input parameters, $x$ values, evaluation result) to an external file. <>= procedure :: setup_tracing => sf_chain_setup_tracing procedure :: final_tracing => sf_chain_final_tracing <>= subroutine sf_chain_setup_tracing (sf_chain, file) class(sf_chain_t), intent(inout) :: sf_chain type(string_t), intent(in) :: file if (sf_chain%n_strfun > 0) then sf_chain%trace_enable = .true. sf_chain%trace_unit = free_unit () open (sf_chain%trace_unit, file = char (file), action = "write", & status = "replace") call sf_chain%write_trace_header () else call msg_error ("Beam structure: no structure functions, tracing & &disabled") end if end subroutine sf_chain_setup_tracing subroutine sf_chain_final_tracing (sf_chain) class(sf_chain_t), intent(inout) :: sf_chain if (sf_chain%trace_enable) then close (sf_chain%trace_unit) sf_chain%trace_enable = .false. end if end subroutine sf_chain_final_tracing @ %def sf_chain_setup_tracing @ %def sf_chain_final_tracing @ Write the header for the tracing file. <>= procedure :: write_trace_header => sf_chain_write_trace_header <>= subroutine sf_chain_write_trace_header (sf_chain) class(sf_chain_t), intent(in) :: sf_chain integer :: u if (sf_chain%trace_enable) then u = sf_chain%trace_unit write (u, "('# ',A)") "WHIZARD output: & &structure-function sampling data" write (u, "('# ',A,1x,I0)") "Number of sf records:", sf_chain%n_strfun write (u, "('# ',A,1x,I0)") "Number of parameters:", sf_chain%n_par write (u, "('# ',A)") "Columns: channel, p(n_par), x(n_par), f, Jac * f" end if end subroutine sf_chain_write_trace_header @ %def sf_chain_write_trace_header @ Write a record which collects the structure function data for the current data point. For the selected channel, we print first the input integration parameters, then the $x$ values, then the structure-function value summed over all quantum numbers, then the structure function value times the mapping Jacobian. <>= procedure :: trace => sf_chain_trace <>= subroutine sf_chain_trace (sf_chain, c_sel, p, x, f, sf_sum) class(sf_chain_t), intent(in) :: sf_chain integer, intent(in) :: c_sel real(default), dimension(:,:), intent(in) :: p real(default), dimension(:), intent(in) :: x real(default), dimension(:), intent(in) :: f real(default), intent(in) :: sf_sum real(default) :: sf_sum_pac, f_sf_sum_pac integer :: u, i if (sf_chain%trace_enable) then u = sf_chain%trace_unit write (u, "(1x,I0)", advance="no") c_sel write (u, "(2x)", advance="no") do i = 1, sf_chain%n_par write (u, "(1x," // FMT_17 // ")", advance="no") p(i,c_sel) end do write (u, "(2x)", advance="no") do i = 1, sf_chain%n_par write (u, "(1x," // FMT_17 // ")", advance="no") x(i) end do write (u, "(2x)", advance="no") sf_sum_pac = sf_sum f_sf_sum_pac = f(c_sel) * sf_sum call pacify (sf_sum_pac, 1.E-28_default) call pacify (f_sf_sum_pac, 1.E-28_default) write (u, "(2(1x," // FMT_17 // "))") sf_sum_pac, f_sf_sum_pac end if end subroutine sf_chain_trace @ %def sf_chain_trace @ \subsection{Chain instances} A structure-function chain instance contains copies of the interactions in the configuration chain, suitably linked to each other and connected by evaluators. After initialization, [[out_sf]] should point, for each beam, to the last structure function that affects this beam. [[out_sf_i]] should indicate the index of the corresponding outgoing particle within that structure-function interaction. Analogously, [[out_eval]] is the last evaluator in the structure-function chain, which contains the complete set of outgoing particles. [[out_eval_i]] should indicate the index of the outgoing particles, within that evaluator, which will initiate the collision. When calculating actual kinematics, we fill the [[p]], [[r]], and [[x]] arrays and the [[f]] factor. The [[p]] array denotes the MC input parameters as they come from the random-number generator. The [[r]] array results from applying global mappings. The [[x]] array results from applying structure-function local mappings. The $x$ values can be interpreted directly as momentum fractions (or angle fractions, where recoil is involved). The [[f]] factor is the Jacobian that results from applying all mappings. Update 2017-08-22: carry and output all complements ([[pb]], [[rb]], [[xb]]). Previously, [[xb]] was not included in the record, and the output did not contain either. It does become more verbose, however. The [[mapping]] entry may store a global mapping that is applied to a combination of $x$ values and structure functions, as opposed to mappings that affect only a single structure function. It is applied before the latter mappings, in the transformation from the [[p]] array to the [[r]] array. For parameters affected by this mapping, we should ensure that they are not involved in a local mapping. <>= public :: sf_chain_instance_t <>= type, extends (beam_t) :: sf_chain_instance_t type(sf_chain_t), pointer :: config => null () integer :: status = SF_UNDEFINED type(sf_instance_t), dimension(:), allocatable :: sf integer, dimension(:), allocatable :: out_sf integer, dimension(:), allocatable :: out_sf_i integer :: out_eval = 0 integer, dimension(:), allocatable :: out_eval_i integer :: selected_channel = 0 real(default), dimension(:,:), allocatable :: p, pb real(default), dimension(:,:), allocatable :: r, rb real(default), dimension(:), allocatable :: f real(default), dimension(:), allocatable :: x, xb logical, dimension(:), allocatable :: bound real(default) :: x_free = 1 type(sf_channel_t), dimension(:), allocatable :: channel contains <> end type sf_chain_instance_t @ %def sf_chain_instance_t @ Finalizer. <>= procedure :: final => sf_chain_instance_final <>= subroutine sf_chain_instance_final (object) class(sf_chain_instance_t), intent(inout) :: object integer :: i if (allocated (object%sf)) then do i = 1, size (object%sf, 1) associate (sf => object%sf(i)) if (allocated (sf%int)) then call sf%eval%final () call sf%int%final () end if end associate end do end if call beam_final (object%beam_t) end subroutine sf_chain_instance_final @ %def sf_chain_instance_final @ Output. <>= procedure :: write => sf_chain_instance_write <>= subroutine sf_chain_instance_write (object, unit, col_verbose) class(sf_chain_instance_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: col_verbose integer :: u, i, c u = given_output_unit (unit) write (u, "(1x,A)", advance="no") "Structure-function chain instance:" call write_sf_status (object%status, u) if (allocated (object%out_sf)) then write (u, "(3x,A)", advance="no") "outgoing (interactions) =" do i = 1, size (object%out_sf) write (u, "(1x,I0,':',I0)", advance="no") & object%out_sf(i), object%out_sf_i(i) end do write (u, *) end if if (object%out_eval /= 0) then write (u, "(3x,A)", advance="no") "outgoing (evaluators) =" do i = 1, size (object%out_sf) write (u, "(1x,I0,':',I0)", advance="no") & object%out_eval, object%out_eval_i(i) end do write (u, *) end if if (allocated (object%sf)) then if (size (object%sf) /= 0) then write (u, "(1x,A)") "Structure-function parameters:" do c = 1, size (object%f) write (u, "(1x,A,I0,A)", advance="no") "Channel #", c, ":" if (c == object%selected_channel) then write (u, "(1x,A)") "[selected]" else write (u, *) end if write (u, "(3x,A,9(1x,F9.7))") "p =", object%p(:,c) write (u, "(3x,A,9(1x,F9.7))") "pb=", object%pb(:,c) write (u, "(3x,A,9(1x,F9.7))") "r =", object%r(:,c) write (u, "(3x,A,9(1x,F9.7))") "rb=", object%rb(:,c) write (u, "(3x,A,9(1x,ES13.7))") "f =", object%f(c) write (u, "(3x,A)", advance="no") "m =" call object%channel(c)%write (u) end do write (u, "(3x,A,9(1x,F9.7))") "x =", object%x write (u, "(3x,A,9(1x,F9.7))") "xb=", object%xb if (.not. all (object%bound)) then write (u, "(3x,A,9(1x,L1))") "bound =", object%bound end if end if end if call write_separator (u) call beam_write (object%beam_t, u, col_verbose = col_verbose) if (allocated (object%sf)) then do i = 1, size (object%sf) associate (sf => object%sf(i)) call write_separator (u) if (allocated (sf%int)) then if (allocated (sf%r)) then write (u, "(1x,A)") "Structure-function parameters:" do c = 1, size (sf%f) write (u, "(1x,A,I0,A)", advance="no") "Channel #", c, ":" if (c == object%selected_channel) then write (u, "(1x,A)") "[selected]" else write (u, *) end if write (u, "(3x,A,9(1x,F9.7))") "r =", sf%r(:,c) write (u, "(3x,A,9(1x,F9.7))") "rb=", sf%rb(:,c) write (u, "(3x,A,9(1x,ES13.7))") "f =", sf%f(c) write (u, "(3x,A,9(1x,L1,7x))") "m =", sf%m(c) end do write (u, "(3x,A,9(1x,F9.7))") "x =", sf%x write (u, "(3x,A,9(1x,F9.7))") "xb=", sf%xb end if call sf%int%write(u) if (.not. sf%eval%is_empty ()) then call sf%eval%write (u, col_verbose = col_verbose) end if end if end associate end do end if end subroutine sf_chain_instance_write @ %def sf_chain_instance_write @ Initialize. This creates a copy of the interactions in the configuration chain, assumed to be properly initialized. In the copy, we allocate the [[p]] etc.\ arrays. The brute-force assignment of the [[sf]] component would be straightforward, but we provide a more fine-grained copy. In any case, the copy is deep as far as allocatables are concerned, but for the contained [[interaction_t]] objects the copy is shallow, as long as we do not bind defined assignment to the type. Therefore, we have to re-assign the [[interaction_t]] components explicitly, this time calling the proper defined assignment. Furthermore, we allocate the parameter arrays for each structure function. <>= procedure :: init => sf_chain_instance_init <>= subroutine sf_chain_instance_init (chain, config, n_channel) class(sf_chain_instance_t), intent(out), target :: chain type(sf_chain_t), intent(in), target :: config integer, intent(in) :: n_channel integer :: i, j integer :: n_par_tot, n_par, n_strfun chain%config => config n_strfun = config%n_strfun chain%beam_t = config%beam_t allocate (chain%out_sf (config%n_in), chain%out_sf_i (config%n_in)) allocate (chain%out_eval_i (config%n_in)) chain%out_sf = 0 chain%out_sf_i = [(i, i = 1, config%n_in)] chain%out_eval_i = chain%out_sf_i n_par_tot = 0 if (n_strfun /= 0) then allocate (chain%sf (n_strfun)) do i = 1, n_strfun associate (sf => chain%sf(i)) allocate (sf%int, source=config%sf(i)%int) sf%int%interaction_t = config%sf(i)%int%interaction_t n_par = size (sf%int%par_index) allocate (sf%r (n_par, n_channel)); sf%r = 0 allocate (sf%rb(n_par, n_channel)); sf%rb= 0 allocate (sf%f (n_channel)); sf%f = 0 allocate (sf%m (n_channel)); sf%m = .false. allocate (sf%x (n_par)); sf%x = 0 allocate (sf%xb(n_par)); sf%xb= 0 n_par_tot = n_par_tot + n_par end associate end do allocate (chain%p (n_par_tot, n_channel)); chain%p = 0 allocate (chain%pb(n_par_tot, n_channel)); chain%pb= 0 allocate (chain%r (n_par_tot, n_channel)); chain%r = 0 allocate (chain%rb(n_par_tot, n_channel)); chain%rb= 0 allocate (chain%f (n_channel)); chain%f = 0 allocate (chain%x (n_par_tot)); chain%x = 0 allocate (chain%xb(n_par_tot)); chain%xb= 0 call allocate_sf_channels & (chain%channel, n_channel=n_channel, n_strfun=n_strfun) end if allocate (chain%bound (n_par_tot), source = .true.) do i = 1, n_strfun associate (sf => chain%sf(i)) if (sf%int%is_generator ()) then do j = 1, size (sf%int%par_index) chain%bound(sf%int%par_index(j)) = .false. end do end if end associate end do chain%status = SF_INITIAL end subroutine sf_chain_instance_init @ %def sf_chain_instance_init @ Manually select a channel. <>= procedure :: select_channel => sf_chain_instance_select_channel <>= subroutine sf_chain_instance_select_channel (chain, channel) class(sf_chain_instance_t), intent(inout) :: chain integer, intent(in), optional :: channel if (present (channel)) then chain%selected_channel = channel else chain%selected_channel = 0 end if end subroutine sf_chain_instance_select_channel @ %def sf_chain_instance_select_channel @ Copy a channel-mapping object to the structure-function chain instance. We assume that assignment is sufficient, i.e., any non-static components of the [[channel]] object are allocatable und thus recursively copied. After the copy, we extract the single-entry mappings and activate them for the individual structure functions. If there is a multi-entry mapping, we obtain the corresponding MC parameter indices and set them in the copy of the channel object. <>= procedure :: set_channel => sf_chain_instance_set_channel <>= subroutine sf_chain_instance_set_channel (chain, c, channel) class(sf_chain_instance_t), intent(inout) :: chain integer, intent(in) :: c type(sf_channel_t), intent(in) :: channel integer :: i, j, k if (chain%status >= SF_INITIAL) then chain%channel(c) = channel j = 0 do i = 1, chain%config%n_strfun associate (sf => chain%sf(i)) sf%m(c) = channel%is_single_mapping (i) if (channel%is_multi_mapping (i)) then do k = 1, size (sf%int%beam_index) j = j + 1 call chain%channel(c)%set_par_index & (j, sf%int%par_index(k)) end do end if end associate end do if (j /= chain%channel(c)%get_multi_mapping_n_par ()) then print *, "index last filled = ", j print *, "number of parameters = ", & chain%channel(c)%get_multi_mapping_n_par () call msg_bug ("Structure-function setup: mapping index mismatch") end if chain%status = SF_INITIAL end if end subroutine sf_chain_instance_set_channel @ %def sf_chain_instance_set_channel @ Link the interactions in the chain. First, link the beam instance to its template in the configuration chain, which should have the appropriate momenta fixed. Then, we follow the chain via the arrays [[out_sf]] and [[out_sf_i]]. The arrays are (up to) two-dimensional, the entries correspond to the beam particle(s). For each beam, the entry [[out_sf]] points to the last interaction that affected this beam, and [[out_sf_i]] is the out-particle index within that interaction. For the initial beam, [[out_sf]] is zero by definition. For each entry in the chain, we scan the affected beams (one or two). We look for [[out_sf]] and link the out-particle there to the corresponding in-particle in the current interaction. Then, we update the entry in [[out_sf]] and [[out_sf_i]] to point to the current interaction. <>= procedure :: link_interactions => sf_chain_instance_link_interactions <>= subroutine sf_chain_instance_link_interactions (chain) class(sf_chain_instance_t), intent(inout), target :: chain type(interaction_t), pointer :: int integer :: i, j, b if (chain%status >= SF_INITIAL) then do b = 1, chain%config%n_in int => beam_get_int_ptr (chain%beam_t) call interaction_set_source_link (int, b, & chain%config%beam_t, b) end do if (allocated (chain%sf)) then do i = 1, size (chain%sf) associate (sf_int => chain%sf(i)%int) do j = 1, size (sf_int%beam_index) b = sf_int%beam_index(j) call link (sf_int%interaction_t, b, sf_int%incoming(j)) chain%out_sf(b) = i chain%out_sf_i(b) = sf_int%outgoing(j) end do end associate end do end if chain%status = SF_DONE_LINKS end if contains subroutine link (int, b, in_index) type(interaction_t), intent(inout) :: int integer, intent(in) :: b, in_index integer :: i i = chain%out_sf(b) select case (i) case (0) call interaction_set_source_link (int, in_index, & chain%beam_t, chain%out_sf_i(b)) case default call int%set_source_link (in_index, & chain%sf(i)%int, chain%out_sf_i(b)) end select end subroutine link end subroutine sf_chain_instance_link_interactions @ %def sf_chain_instance_link_interactions @ Exchange the quantum-number masks between the interactions in the chain, so we can combine redundant entries and detect any obvious mismatch. We proceed first in the forward direction and then backwards again. After this is finished, we finalize initialization by calling the [[setup_constants]] method, which prepares constant data that depend on the matrix element structure. <>= procedure :: exchange_mask => sf_chain_exchange_mask <>= subroutine sf_chain_exchange_mask (chain) class(sf_chain_instance_t), intent(inout), target :: chain type(interaction_t), pointer :: int type(quantum_numbers_mask_t), dimension(:), allocatable :: mask integer :: i if (chain%status >= SF_DONE_LINKS) then if (allocated (chain%sf)) then int => beam_get_int_ptr (chain%beam_t) allocate (mask (int%get_n_out ())) mask = int%get_mask () if (size (chain%sf) /= 0) then do i = 1, size (chain%sf) - 1 call interaction_exchange_mask (chain%sf(i)%int%interaction_t) end do do i = size (chain%sf), 1, -1 call interaction_exchange_mask (chain%sf(i)%int%interaction_t) end do if (any (mask .neqv. int%get_mask ())) then chain%status = SF_FAILED_MASK return end if do i = 1, size (chain%sf) call chain%sf(i)%int%setup_constants () end do end if end if chain%status = SF_DONE_MASK end if end subroutine sf_chain_exchange_mask @ %def sf_chain_exchange_mask @ Initialize the evaluators that connect the interactions in the chain. <>= procedure :: init_evaluators => sf_chain_instance_init_evaluators <>= subroutine sf_chain_instance_init_evaluators (chain, extended_sf) class(sf_chain_instance_t), intent(inout), target :: chain logical, intent(in), optional :: extended_sf type(interaction_t), pointer :: int type(quantum_numbers_mask_t) :: mask integer :: i logical :: yorn yorn = .false.; if (present (extended_sf)) yorn = extended_sf if (chain%status >= SF_DONE_MASK) then if (allocated (chain%sf)) then if (size (chain%sf) /= 0) then mask = quantum_numbers_mask (.false., .false., .true.) int => beam_get_int_ptr (chain%beam_t) do i = 1, size (chain%sf) associate (sf => chain%sf(i)) if (yorn) then if (int%get_n_sub () == 0) then call int%declare_subtraction (n_beams_rescaled) end if if (sf%int%interaction_t%get_n_sub () == 0) then call sf%int%interaction_t%declare_subtraction (n_beams_rescaled) end if end if call sf%eval%init_product (int, sf%int%interaction_t, mask,& & ignore_sub_for_qn = .true.) if (sf%eval%is_empty ()) then chain%status = SF_FAILED_CONNECTIONS return end if int => sf%eval%interaction_t end associate end do call find_outgoing_particles () end if else if (chain%out_eval == 0) then int => beam_get_int_ptr (chain%beam_t) call int%tag_hard_process () end if chain%status = SF_DONE_CONNECTIONS end if contains <> end subroutine sf_chain_instance_init_evaluators @ %def sf_chain_instance_init_evaluators @ For debug purposes <>= procedure :: write_interaction => sf_chain_instance_write_interaction <>= subroutine sf_chain_instance_write_interaction (chain, i_sf, i_int, unit) class(sf_chain_instance_t), intent(in) :: chain integer, intent(in) :: i_sf, i_int integer, intent(in) :: unit class(interaction_t), pointer :: int_in1 => null () class(interaction_t), pointer :: int_in2 => null () integer :: u u = given_output_unit (unit); if (u < 0) return if (chain%status >= SF_DONE_MASK) then if (allocated (chain%sf)) then int_in1 => evaluator_get_int_in_ptr (chain%sf(i_sf)%eval, 1) int_in2 => evaluator_get_int_in_ptr (chain%sf(i_sf)%eval, 2) if (int_in1%get_tag () == i_int) then call int_in1%basic_write (u) else if (int_in2%get_tag () == i_int) then call int_in2%basic_write (u) else write (u, "(A,1x,I0,1x,A,1x,I0)") 'No tag of sf', i_sf, 'matches' , i_int end if else write (u, "(A)") 'No sf_chain allocated!' end if else write (u, "(A)") 'sf_chain not ready!' end if end subroutine sf_chain_instance_write_interaction @ %def sf_chain_instance_write_interaction @ This is an internal subroutine of the previous one: After evaluators are set, trace the outgoing particles to the last evaluator. We only need the first channel, all channels are equivalent for this purpose. For each beam, the outgoing particle is located by [[out_sf]] (the structure-function object where it originates) and [[out_sf_i]] (the index within that object). This particle is referenced by the corresponding evaluator, which in turn is referenced by the next evaluator, until we are at the end of the chain. We can trace back references by [[interaction_find_link]]. Knowing that [[out_eval]] is the index of the last evaluator, we thus determine [[out_eval_i]], the index of the outgoing particle within that evaluator. <>= subroutine find_outgoing_particles () type(interaction_t), pointer :: int, int_next integer :: i, j, out_sf, out_i chain%out_eval = size (chain%sf) do j = 1, size (chain%out_eval_i) out_sf = chain%out_sf(j) out_i = chain%out_sf_i(j) if (out_sf == 0) then int => beam_get_int_ptr (chain%beam_t) out_sf = 1 else int => chain%sf(out_sf)%int%interaction_t end if do i = out_sf, chain%out_eval int_next => chain%sf(i)%eval%interaction_t out_i = interaction_find_link (int_next, int, out_i) int => int_next end do chain%out_eval_i(j) = out_i end do call int%tag_hard_process (chain%out_eval_i) end subroutine find_outgoing_particles @ %def find_outgoing_particles @ Compute the kinematics in the chain instance. We can assume that the seed momenta are set in the configuration beams. Scanning the chain, we first transfer the incoming momenta. Then, the use up the MC input parameter array [[p]] to compute the radiated and outgoing momenta. In the multi-channel case, [[c_sel]] is the channel which we use for computing the kinematics and the [[x]] values. In the other channels, we invert the kinematics in order to recover the corresponding rows in the [[r]] array, and the Jacobian [[f]]. We first apply any global mapping to transform the input [[p]] into the array [[r]]. This is then given to the structure functions which compute the final array [[x]] and Jacobian factors [[f]], which we multiply to obtain the overall Jacobian. <>= procedure :: compute_kinematics => sf_chain_instance_compute_kinematics <>= subroutine sf_chain_instance_compute_kinematics (chain, c_sel, p_in) class(sf_chain_instance_t), intent(inout), target :: chain integer, intent(in) :: c_sel real(default), dimension(:), intent(in) :: p_in type(interaction_t), pointer :: int real(default) :: f_mapping integer :: i, j, c if (chain%status >= SF_DONE_CONNECTIONS) then call chain%select_channel (c_sel) int => beam_get_int_ptr (chain%beam_t) call int%receive_momenta () if (allocated (chain%sf)) then if (size (chain%sf) /= 0) then forall (i = 1:size (chain%sf)) chain%sf(i)%int%status = SF_INITIAL chain%p (:,c_sel) = unpack (p_in, chain%bound, 0._default) chain%pb(:,c_sel) = 1 - chain%p(:,c_sel) chain%f = 1 chain%x_free = 1 do i = 1, size (chain%sf) associate (sf => chain%sf(i)) call sf%int%generate_free (sf%r(:,c_sel), sf%rb(:,c_sel), & chain%x_free) do j = 1, size (sf%x) if (.not. chain%bound(sf%int%par_index(j))) then chain%p (sf%int%par_index(j),c_sel) = sf%r (j,c_sel) chain%pb(sf%int%par_index(j),c_sel) = sf%rb(j,c_sel) end if end do end associate end do if (allocated (chain%channel(c_sel)%multi_mapping)) then call chain%channel(c_sel)%multi_mapping%compute & (chain%r(:,c_sel), chain%rb(:,c_sel), & f_mapping, & chain%p(:,c_sel), chain%pb(:,c_sel), & chain%x_free) chain%f(c_sel) = f_mapping else chain%r (:,c_sel) = chain%p (:,c_sel) chain%rb(:,c_sel) = chain%pb(:,c_sel) chain%f(c_sel) = 1 end if do i = 1, size (chain%sf) associate (sf => chain%sf(i)) call sf%int%seed_kinematics () do j = 1, size (sf%x) sf%r (j,c_sel) = chain%r (sf%int%par_index(j),c_sel) sf%rb(j,c_sel) = chain%rb(sf%int%par_index(j),c_sel) end do call sf%int%complete_kinematics & (sf%x, sf%xb, sf%f(c_sel), sf%r(:,c_sel), sf%rb(:,c_sel), & sf%m(c_sel)) do j = 1, size (sf%x) chain%x(sf%int%par_index(j)) = sf%x(j) chain%xb(sf%int%par_index(j)) = sf%xb(j) end do if (sf%int%status <= SF_FAILED_KINEMATICS) then chain%status = SF_FAILED_KINEMATICS return end if do c = 1, size (sf%f) if (c /= c_sel) then call sf%int%inverse_kinematics & (sf%x, sf%xb, sf%f(c), sf%r(:,c), sf%rb(:,c), sf%m(c)) do j = 1, size (sf%x) chain%r (sf%int%par_index(j),c) = sf%r (j,c) chain%rb(sf%int%par_index(j),c) = sf%rb(j,c) end do end if chain%f(c) = chain%f(c) * sf%f(c) end do if (.not. sf%eval%is_empty ()) then call sf%eval%receive_momenta () end if end associate end do do c = 1, size (chain%f) if (c /= c_sel) then if (allocated (chain%channel(c)%multi_mapping)) then call chain%channel(c)%multi_mapping%inverse & (chain%r(:,c), chain%rb(:,c), & f_mapping, & chain%p(:,c), chain%pb(:,c), & chain%x_free) chain%f(c) = chain%f(c) * f_mapping else chain%p (:,c) = chain%r (:,c) chain%pb(:,c) = chain%rb(:,c) end if end if end do end if end if chain%status = SF_DONE_KINEMATICS end if end subroutine sf_chain_instance_compute_kinematics @ %def sf_chain_instance_compute_kinematics @ This is a variant of the previous procedure. We know the $x$ parameters and reconstruct the momenta and the MC input parameters [[p]]. We do not need to select a channel. Note: this is probably redundant, since the method we actually want starts from the momenta, recovers all $x$ parameters, and then inverts mappings. See below [[recover_kinematics]]. <>= procedure :: inverse_kinematics => sf_chain_instance_inverse_kinematics <>= subroutine sf_chain_instance_inverse_kinematics (chain, x, xb) class(sf_chain_instance_t), intent(inout), target :: chain real(default), dimension(:), intent(in) :: x real(default), dimension(:), intent(in) :: xb type(interaction_t), pointer :: int real(default) :: f_mapping integer :: i, j, c if (chain%status >= SF_DONE_CONNECTIONS) then call chain%select_channel () int => beam_get_int_ptr (chain%beam_t) call int%receive_momenta () if (allocated (chain%sf)) then chain%f = 1 if (size (chain%sf) /= 0) then forall (i = 1:size (chain%sf)) chain%sf(i)%int%status = SF_INITIAL chain%x = x chain%xb= xb do i = 1, size (chain%sf) associate (sf => chain%sf(i)) call sf%int%seed_kinematics () do j = 1, size (sf%x) sf%x(j) = chain%x(sf%int%par_index(j)) sf%xb(j) = chain%xb(sf%int%par_index(j)) end do do c = 1, size (sf%f) call sf%int%inverse_kinematics & (sf%x, sf%xb, sf%f(c), sf%r(:,c), sf%rb(:,c), sf%m(c), & set_momenta = c==1) chain%f(c) = chain%f(c) * sf%f(c) do j = 1, size (sf%x) chain%r (sf%int%par_index(j),c) = sf%r (j,c) chain%rb(sf%int%par_index(j),c) = sf%rb(j,c) end do end do if (.not. sf%eval%is_empty ()) then call sf%eval%receive_momenta () end if end associate end do do c = 1, size (chain%f) if (allocated (chain%channel(c)%multi_mapping)) then call chain%channel(c)%multi_mapping%inverse & (chain%r(:,c), chain%rb(:,c), & f_mapping, & chain%p(:,c), chain%pb(:,c), & chain%x_free) chain%f(c) = chain%f(c) * f_mapping else chain%p (:,c) = chain%r (:,c) chain%pb(:,c) = chain%rb(:,c) end if end do end if end if chain%status = SF_DONE_KINEMATICS end if end subroutine sf_chain_instance_inverse_kinematics @ %def sf_chain_instance_inverse_kinematics @ Recover the kinematics: assuming that the last evaluator has been filled with a valid set of momenta, we travel the momentum links backwards and fill the preceding evaluators and, as a side effect, interactions. We stop at the beam interaction. After all momenta are set, apply the [[inverse_kinematics]] procedure above, suitably modified, to recover the $x$ and $p$ parameters and the Jacobian factors. The [[c_sel]] (channel) argument is just used to mark a selected channel for the records, otherwise the recovery procedure is independent of this. <>= procedure :: recover_kinematics => sf_chain_instance_recover_kinematics <>= subroutine sf_chain_instance_recover_kinematics (chain, c_sel) class(sf_chain_instance_t), intent(inout), target :: chain integer, intent(in) :: c_sel real(default) :: f_mapping integer :: i, j, c if (chain%status >= SF_DONE_CONNECTIONS) then call chain%select_channel (c_sel) if (allocated (chain%sf)) then do i = size (chain%sf), 1, -1 associate (sf => chain%sf(i)) if (.not. sf%eval%is_empty ()) then call interaction_send_momenta (sf%eval%interaction_t) end if end associate end do chain%f = 1 if (size (chain%sf) /= 0) then forall (i = 1:size (chain%sf)) chain%sf(i)%int%status = SF_INITIAL chain%x_free = 1 do i = 1, size (chain%sf) associate (sf => chain%sf(i)) call sf%int%seed_kinematics () call sf%int%recover_x (sf%x, sf%xb, chain%x_free) do j = 1, size (sf%x) chain%x(sf%int%par_index(j)) = sf%x(j) chain%xb(sf%int%par_index(j)) = sf%xb(j) end do do c = 1, size (sf%f) call sf%int%inverse_kinematics & (sf%x, sf%xb, sf%f(c), sf%r(:,c), sf%rb(:,c), sf%m(c), & set_momenta = .false.) chain%f(c) = chain%f(c) * sf%f(c) do j = 1, size (sf%x) chain%r (sf%int%par_index(j),c) = sf%r (j,c) chain%rb(sf%int%par_index(j),c) = sf%rb(j,c) end do end do end associate end do do c = 1, size (chain%f) if (allocated (chain%channel(c)%multi_mapping)) then call chain%channel(c)%multi_mapping%inverse & (chain%r(:,c), chain%rb(:,c), & f_mapping, & chain%p(:,c), chain%pb(:,c), & chain%x_free) chain%f(c) = chain%f(c) * f_mapping else chain%p (:,c) = chain%r (:,c) chain%pb(:,c) = chain%rb(:,c) end if end do end if end if chain%status = SF_DONE_KINEMATICS end if end subroutine sf_chain_instance_recover_kinematics @ %def sf_chain_instance_recover_kinematics @ Return the initial beam momenta to their source, thus completing kinematics recovery. Obviously, this works as a side effect. <>= procedure :: return_beam_momenta => sf_chain_instance_return_beam_momenta <>= subroutine sf_chain_instance_return_beam_momenta (chain) class(sf_chain_instance_t), intent(in), target :: chain type(interaction_t), pointer :: int if (chain%status >= SF_DONE_KINEMATICS) then int => beam_get_int_ptr (chain%beam_t) call interaction_send_momenta (int) end if end subroutine sf_chain_instance_return_beam_momenta @ %def sf_chain_instance_return_beam_momenta @ Evaluate all interactions in the chain and the product evaluators. We provide a [[scale]] argument that is given to all structure functions in the chain. Hadronic NLO calculations involve rescaled fractions of the original beam momentum. In particular, we have to handle the following cases: \begin{itemize} \item normal evaluation (where [[i_sub = 0]]) for all terms except the real non-subtracted, \item rescaled momentum fraction for both beams in the case of the real non-subtracted term ([[i_sub = 0]]), \item and rescaled momentum fraction for one of both beams in the case of the subtraction and DGLAP component ([[i_sub = 1,2]]). \end{itemize} For the collinear final or intial state counter terms, we apply a rescaling to one beam, and keep the other beam as is. We redo it then vice versa having now two subtractions. <>= procedure :: evaluate => sf_chain_instance_evaluate <>= subroutine sf_chain_instance_evaluate (chain, scale, sf_rescale) class(sf_chain_instance_t), intent(inout), target :: chain real(default), intent(in) :: scale class(sf_rescale_t), intent(inout), optional :: sf_rescale type(interaction_t), pointer :: out_int real(default) :: sf_sum integer :: i_beam, i_sub, n_sub logical :: rescale n_sub = 0 rescale = .false.; if (present (sf_rescale)) rescale = .true. if (rescale) then n_sub = chain%get_n_sub () end if if (chain%status >= SF_DONE_KINEMATICS) then if (allocated (chain%sf)) then if (size (chain%sf) /= 0) then do i_beam = 1, size (chain%sf) associate (sf => chain%sf(i_beam)) if (rescale) then call sf_rescale%set_i_beam (i_beam) do i_sub = 0, n_sub select case (i_sub) case (0) if (n_sub == 0) then call sf%int%apply (scale, sf_rescale, i_sub = i_sub) else call sf%int%apply (scale, i_sub = i_sub) end if case default if (i_beam == i_sub) then call sf%int%apply (scale, sf_rescale, i_sub = i_sub) else call sf%int%apply (scale, i_sub = i_sub) end if end select end do else call sf%int%apply (scale, i_sub = n_sub) end if if (sf%int%status <= SF_FAILED_EVALUATION) then chain%status = SF_FAILED_EVALUATION return end if if (.not. sf%eval%is_empty ()) call sf%eval%evaluate () end associate end do out_int => chain%get_out_int_ptr () sf_sum = real (out_int%sum ()) call chain%config%trace & (chain%selected_channel, chain%p, chain%x, chain%f, sf_sum) end if end if chain%status = SF_EVALUATED end if end subroutine sf_chain_instance_evaluate @ %def sf_chain_instance_evaluate @ \subsection{Access to the chain instance} Transfer the outgoing momenta to the array [[p]]. We assume that array sizes match. <>= procedure :: get_out_momenta => sf_chain_instance_get_out_momenta <>= subroutine sf_chain_instance_get_out_momenta (chain, p) class(sf_chain_instance_t), intent(in), target :: chain type(vector4_t), dimension(:), intent(out) :: p type(interaction_t), pointer :: int integer :: i, j if (chain%status >= SF_DONE_KINEMATICS) then do j = 1, size (chain%out_sf) i = chain%out_sf(j) select case (i) case (0) int => beam_get_int_ptr (chain%beam_t) case default int => chain%sf(i)%int%interaction_t end select p(j) = int%get_momentum (chain%out_sf_i(j)) end do end if end subroutine sf_chain_instance_get_out_momenta @ %def sf_chain_instance_get_out_momenta @ Return a pointer to the last evaluator in the chain (to the interaction). <>= procedure :: get_out_int_ptr => sf_chain_instance_get_out_int_ptr <>= function sf_chain_instance_get_out_int_ptr (chain) result (int) class(sf_chain_instance_t), intent(in), target :: chain type(interaction_t), pointer :: int if (chain%out_eval == 0) then int => beam_get_int_ptr (chain%beam_t) else int => chain%sf(chain%out_eval)%eval%interaction_t end if end function sf_chain_instance_get_out_int_ptr @ %def sf_chain_instance_get_out_int_ptr @ Return the index of the [[j]]-th outgoing particle, within the last evaluator. <>= procedure :: get_out_i => sf_chain_instance_get_out_i <>= function sf_chain_instance_get_out_i (chain, j) result (i) class(sf_chain_instance_t), intent(in) :: chain integer, intent(in) :: j integer :: i i = chain%out_eval_i(j) end function sf_chain_instance_get_out_i @ %def sf_chain_instance_get_out_i @ Return the mask for the outgoing particle(s), within the last evaluator. <>= procedure :: get_out_mask => sf_chain_instance_get_out_mask <>= function sf_chain_instance_get_out_mask (chain) result (mask) class(sf_chain_instance_t), intent(in), target :: chain type(quantum_numbers_mask_t), dimension(:), allocatable :: mask type(interaction_t), pointer :: int allocate (mask (chain%config%n_in)) int => chain%get_out_int_ptr () mask = int%get_mask (chain%out_eval_i) end function sf_chain_instance_get_out_mask @ %def sf_chain_instance_get_out_mask @ Return the array of MC input parameters that corresponds to channel [[c]]. This is the [[p]] array, the parameters before all mappings. The [[p]] array may be deallocated. This should correspond to a zero-size [[r]] argument, so nothing to do then. <>= procedure :: get_mcpar => sf_chain_instance_get_mcpar <>= subroutine sf_chain_instance_get_mcpar (chain, c, r) class(sf_chain_instance_t), intent(in) :: chain integer, intent(in) :: c real(default), dimension(:), intent(out) :: r if (allocated (chain%p)) r = pack (chain%p(:,c), chain%bound) end subroutine sf_chain_instance_get_mcpar @ %def sf_chain_instance_get_mcpar @ Return the Jacobian factor that corresponds to channel [[c]]. <>= procedure :: get_f => sf_chain_instance_get_f <>= function sf_chain_instance_get_f (chain, c) result (f) class(sf_chain_instance_t), intent(in) :: chain integer, intent(in) :: c real(default) :: f if (allocated (chain%f)) then f = chain%f(c) else f = 1 end if end function sf_chain_instance_get_f @ %def sf_chain_instance_get_f @ Return the evaluation status. <>= procedure :: get_status => sf_chain_instance_get_status <>= function sf_chain_instance_get_status (chain) result (status) class(sf_chain_instance_t), intent(in) :: chain integer :: status status = chain%status end function sf_chain_instance_get_status @ %def sf_chain_instance_get_status @ <>= procedure :: get_matrix_elements => sf_chain_instance_get_matrix_elements <>= subroutine sf_chain_instance_get_matrix_elements (chain, i, ff) class(sf_chain_instance_t), intent(in) :: chain integer, intent(in) :: i real(default), intent(out), dimension(:), allocatable :: ff associate (sf => chain%sf(i)) ff = real (sf%int%get_matrix_element ()) end associate end subroutine sf_chain_instance_get_matrix_elements @ %def sf_chain_instance_get_matrix_elements @ <>= procedure :: get_beam_int_ptr => sf_chain_instance_get_beam_int_ptr <>= function sf_chain_instance_get_beam_int_ptr (chain) result (int) type(interaction_t), pointer :: int class(sf_chain_instance_t), intent(in), target :: chain int => beam_get_int_ptr (chain%beam_t) end function sf_chain_instance_get_beam_int_ptr @ %def sf_chain_instance_get_beam_ptr @ <>= procedure :: get_n_sub => sf_chain_instance_get_n_sub <>= integer function sf_chain_instance_get_n_sub (chain) result (n_sub) type(interaction_t), pointer :: int class(sf_chain_instance_t), intent(in), target :: chain int => beam_get_int_ptr (chain%beam_t) n_sub = int%get_n_sub () end function sf_chain_instance_get_n_sub @ %def sf_chain_instance_get_n_sub @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[sf_base_ut.f90]]>>= <> module sf_base_ut use unit_tests use sf_base_uti <> <> <> contains <> end module sf_base_ut @ %def sf_base_ut @ <<[[sf_base_uti.f90]]>>= <> module sf_base_uti <> <> use io_units use format_defs, only: FMT_19 use format_utils, only: write_separator use diagnostics use lorentz use pdg_arrays use flavors use colors use helicities use quantum_numbers use state_matrices, only: FM_IGNORE_HELICITY use interactions use particles use model_data use beams use sf_aux use sf_mappings use sf_base <> <> <> <> contains <> <> end module sf_base_uti @ %def sf_base_ut @ API: driver for the unit tests below. <>= public :: sf_base_test <>= subroutine sf_base_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine sf_base_test @ %def sf_base_test @ \subsection{Test implementation: structure function} This is a template for the actual structure-function implementation which will be defined in separate modules. \subsubsection{Configuration data} The test structure function uses the [[Test]] model. It describes a scalar within an arbitrary initial particle, which is given in the initialization. The radiated particle is also a scalar, the same one, but we set its mass artificially to zero. <>= public :: sf_test_data_t <>= type, extends (sf_data_t) :: sf_test_data_t class(model_data_t), pointer :: model => null () integer :: mode = 0 type(flavor_t) :: flv_in type(flavor_t) :: flv_out type(flavor_t) :: flv_rad real(default) :: m = 0 logical :: collinear = .true. real(default), dimension(:), allocatable :: qbounds contains <> end type sf_test_data_t @ %def sf_test_data_t @ Output. <>= procedure :: write => sf_test_data_write <>= subroutine sf_test_data_write (data, unit, verbose) class(sf_test_data_t), intent(in) :: data integer, intent(in), optional :: unit logical, intent(in), optional :: verbose integer :: u u = given_output_unit (unit) write (u, "(1x,A)") "SF test data:" write (u, "(3x,A,A)") "model = ", char (data%model%get_name ()) write (u, "(3x,A)", advance="no") "incoming = " call data%flv_in%write (u); write (u, *) write (u, "(3x,A)", advance="no") "outgoing = " call data%flv_out%write (u); write (u, *) write (u, "(3x,A)", advance="no") "radiated = " call data%flv_rad%write (u); write (u, *) write (u, "(3x,A," // FMT_19 // ")") "mass = ", data%m write (u, "(3x,A,L1)") "collinear = ", data%collinear if (.not. data%collinear .and. allocated (data%qbounds)) then write (u, "(3x,A," // FMT_19 // ")") "qmin = ", data%qbounds(1) write (u, "(3x,A," // FMT_19 // ")") "qmax = ", data%qbounds(2) end if end subroutine sf_test_data_write @ %def sf_test_data_write @ Initialization. <>= procedure :: init => sf_test_data_init <>= subroutine sf_test_data_init (data, model, pdg_in, collinear, qbounds, mode) class(sf_test_data_t), intent(out) :: data class(model_data_t), intent(in), target :: model type(pdg_array_t), intent(in) :: pdg_in logical, intent(in), optional :: collinear real(default), dimension(2), intent(in), optional :: qbounds integer, intent(in), optional :: mode data%model => model if (present (mode)) data%mode = mode if (pdg_array_get (pdg_in, 1) /= 25) then call msg_fatal ("Test spectrum function: input flavor must be 's'") end if call data%flv_in%init (25, model) data%m = data%flv_in%get_mass () if (present (collinear)) data%collinear = collinear call data%flv_out%init (25, model) call data%flv_rad%init (25, model) if (present (qbounds)) then allocate (data%qbounds (2)) data%qbounds = qbounds end if end subroutine sf_test_data_init @ %def sf_test_data_init @ Return the number of parameters: 1 if only consider collinear splitting, 3 otherwise. <>= procedure :: get_n_par => sf_test_data_get_n_par <>= function sf_test_data_get_n_par (data) result (n) class(sf_test_data_t), intent(in) :: data integer :: n if (data%collinear) then n = 1 else n = 3 end if end function sf_test_data_get_n_par @ %def sf_test_data_get_n_par @ Return the outgoing particle PDG code: 25 <>= procedure :: get_pdg_out => sf_test_data_get_pdg_out <>= subroutine sf_test_data_get_pdg_out (data, pdg_out) class(sf_test_data_t), intent(in) :: data type(pdg_array_t), dimension(:), intent(inout) :: pdg_out pdg_out(1) = 25 end subroutine sf_test_data_get_pdg_out @ %def sf_test_data_get_pdg_out @ Allocate the matching interaction. <>= procedure :: allocate_sf_int => sf_test_data_allocate_sf_int <>= subroutine sf_test_data_allocate_sf_int (data, sf_int) class(sf_test_data_t), intent(in) :: data class(sf_int_t), intent(inout), allocatable :: sf_int if (allocated (sf_int)) deallocate (sf_int) allocate (sf_test_t :: sf_int) end subroutine sf_test_data_allocate_sf_int @ %def sf_test_data_allocate_sf_int @ \subsubsection{Interaction} <>= type, extends (sf_int_t) :: sf_test_t type(sf_test_data_t), pointer :: data => null () real(default) :: x = 0 contains <> end type sf_test_t @ %def sf_test_t @ Type string: constant <>= procedure :: type_string => sf_test_type_string <>= function sf_test_type_string (object) result (string) class(sf_test_t), intent(in) :: object type(string_t) :: string string = "Test" end function sf_test_type_string @ %def sf_test_type_string @ Output. Call the interaction routine after displaying the configuration. <>= procedure :: write => sf_test_write <>= subroutine sf_test_write (object, unit, testflag) class(sf_test_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u u = given_output_unit (unit) if (associated (object%data)) then call object%data%write (u) call object%base_write (u, testflag) else write (u, "(1x,A)") "SF test data: [undefined]" end if end subroutine sf_test_write @ %def sf_test_write @ Initialize. We know that [[data]] will be of concrete type [[sf_test_data_t]], but we have to cast this explicitly. For this implementation, we set the incoming and outgoing masses equal to the physical particle mass, but keep the radiated mass zero. Optionally, we can provide minimum and maximum values for the momentum transfer. <>= procedure :: init => sf_test_init <>= subroutine sf_test_init (sf_int, data) class(sf_test_t), intent(out) :: sf_int class(sf_data_t), intent(in), target :: data type(quantum_numbers_mask_t), dimension(3) :: mask type(helicity_t) :: hel0 type(color_t) :: col0 type(quantum_numbers_t), dimension(3) :: qn mask = quantum_numbers_mask (.false., .false., .false.) select type (data) type is (sf_test_data_t) if (allocated (data%qbounds)) then call sf_int%base_init (mask, & [data%m**2], [0._default], [data%m**2], & [data%qbounds(1)], [data%qbounds(2)]) else call sf_int%base_init (mask, & [data%m**2], [0._default], [data%m**2]) end if sf_int%data => data call hel0%init (0) call col0%init () call qn(1)%init (data%flv_in, col0, hel0) call qn(2)%init (data%flv_rad, col0, hel0) call qn(3)%init (data%flv_out, col0, hel0) call sf_int%add_state (qn) call sf_int%freeze () call sf_int%set_incoming ([1]) call sf_int%set_radiated ([2]) call sf_int%set_outgoing ([3]) end select sf_int%status = SF_INITIAL end subroutine sf_test_init @ %def sf_test_init @ Set kinematics. If [[map]] is unset, the $r$ and $x$ values coincide, and the Jacobian $f(r)$ is trivial. If [[map]] is set, we are asked to provide an efficient mapping. For the test case, we set $x=r^2$ and consequently $f(r)=2r$. <>= procedure :: complete_kinematics => sf_test_complete_kinematics <>= subroutine sf_test_complete_kinematics (sf_int, x, xb, f, r, rb, map) class(sf_test_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: x real(default), dimension(:), intent(out) :: xb real(default), intent(out) :: f real(default), dimension(:), intent(in) :: r real(default), dimension(:), intent(in) :: rb logical, intent(in) :: map if (map) then x(1) = r(1)**2 f = 2 * r(1) else x(1) = r(1) f = 1 end if xb(1) = 1 - x(1) if (size (x) == 3) then x(2:3) = r(2:3) xb(2:3) = rb(2:3) end if call sf_int%split_momentum (x, xb) sf_int%x = x(1) select case (sf_int%status) case (SF_FAILED_KINEMATICS); f = 0 end select end subroutine sf_test_complete_kinematics @ %def sf_test_complete_kinematics @ Compute inverse kinematics. Here, we start with the $x$ array and compute the ``input'' $r$ values and the Jacobian $f$. After this, we can set momenta by the same formula as for normal kinematics. <>= procedure :: inverse_kinematics => sf_test_inverse_kinematics <>= subroutine sf_test_inverse_kinematics (sf_int, x, xb, f, r, rb, map, set_momenta) class(sf_test_t), intent(inout) :: sf_int real(default), dimension(:), intent(in) :: x real(default), dimension(:), intent(in) :: xb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: r real(default), dimension(:), intent(out) :: rb logical, intent(in) :: map logical, intent(in), optional :: set_momenta logical :: set_mom set_mom = .false.; if (present (set_momenta)) set_mom = set_momenta if (map) then r(1) = sqrt (x(1)) f = 2 * r(1) else r(1) = x(1) f = 1 end if if (size (x) == 3) r(2:3) = x(2:3) rb = 1 - r sf_int%x = x(1) if (set_mom) then call sf_int%split_momentum (x, xb) select case (sf_int%status) case (SF_FAILED_KINEMATICS); f = 0 end select end if end subroutine sf_test_inverse_kinematics @ %def sf_test_inverse_kinematics @ Apply the structure function. The matrix element becomes unity and the application always succeeds. If the [[mode]] indicator is one, the matrix element is equal to the parameter~$x$. <>= procedure :: apply => sf_test_apply <>= subroutine sf_test_apply (sf_int, scale, rescale, i_sub) class(sf_test_t), intent(inout) :: sf_int real(default), intent(in) :: scale class(sf_rescale_t), intent(in), optional :: rescale integer, intent(in), optional :: i_sub select case (sf_int%data%mode) case (0) call sf_int%set_matrix_element & (cmplx (1._default, kind=default)) case (1) call sf_int%set_matrix_element & (cmplx (sf_int%x, kind=default)) end select sf_int%status = SF_EVALUATED end subroutine sf_test_apply @ %def sf_test_apply @ \subsection{Test implementation: pair spectrum} Another template, this time for a incoming particle pair, splitting into two radiated and two outgoing particles. \subsubsection{Configuration data} For simplicity, the spectrum contains two mirror images of the previous structure-function configuration: the incoming and all outgoing particles are test scalars. We have two versions, one with radiated particles, one without. <>= type, extends (sf_data_t) :: sf_test_spectrum_data_t class(model_data_t), pointer :: model => null () type(flavor_t) :: flv_in type(flavor_t) :: flv_out type(flavor_t) :: flv_rad logical :: with_radiation = .true. real(default) :: m = 0 contains <> end type sf_test_spectrum_data_t @ %def sf_test_spectrum_data_t @ Output. <>= procedure :: write => sf_test_spectrum_data_write <>= subroutine sf_test_spectrum_data_write (data, unit, verbose) class(sf_test_spectrum_data_t), intent(in) :: data integer, intent(in), optional :: unit logical, intent(in), optional :: verbose integer :: u u = given_output_unit (unit) write (u, "(1x,A)") "SF test spectrum data:" write (u, "(3x,A,A)") "model = ", char (data%model%get_name ()) write (u, "(3x,A)", advance="no") "incoming = " call data%flv_in%write (u); write (u, *) write (u, "(3x,A)", advance="no") "outgoing = " call data%flv_out%write (u); write (u, *) write (u, "(3x,A)", advance="no") "radiated = " call data%flv_rad%write (u); write (u, *) write (u, "(3x,A," // FMT_19 // ")") "mass = ", data%m end subroutine sf_test_spectrum_data_write @ %def sf_test_spectrum_data_write @ Initialization. <>= procedure :: init => sf_test_spectrum_data_init <>= subroutine sf_test_spectrum_data_init (data, model, pdg_in, with_radiation) class(sf_test_spectrum_data_t), intent(out) :: data class(model_data_t), intent(in), target :: model type(pdg_array_t), intent(in) :: pdg_in logical, intent(in) :: with_radiation data%model => model data%with_radiation = with_radiation if (pdg_array_get (pdg_in, 1) /= 25) then call msg_fatal ("Test structure function: input flavor must be 's'") end if call data%flv_in%init (25, model) data%m = data%flv_in%get_mass () call data%flv_out%init (25, model) if (with_radiation) then call data%flv_rad%init (25, model) end if end subroutine sf_test_spectrum_data_init @ %def sf_test_spectrum_data_init @ Return the number of parameters: 2, since we have only collinear splitting here. <>= procedure :: get_n_par => sf_test_spectrum_data_get_n_par <>= function sf_test_spectrum_data_get_n_par (data) result (n) class(sf_test_spectrum_data_t), intent(in) :: data integer :: n n = 2 end function sf_test_spectrum_data_get_n_par @ %def sf_test_spectrum_data_get_n_par @ Return the outgoing particle PDG codes: 25 <>= procedure :: get_pdg_out => sf_test_spectrum_data_get_pdg_out <>= subroutine sf_test_spectrum_data_get_pdg_out (data, pdg_out) class(sf_test_spectrum_data_t), intent(in) :: data type(pdg_array_t), dimension(:), intent(inout) :: pdg_out pdg_out(1) = 25 pdg_out(2) = 25 end subroutine sf_test_spectrum_data_get_pdg_out @ %def sf_test_spectrum_data_get_pdg_out @ Allocate the matching interaction. <>= procedure :: allocate_sf_int => & sf_test_spectrum_data_allocate_sf_int <>= subroutine sf_test_spectrum_data_allocate_sf_int (data, sf_int) class(sf_test_spectrum_data_t), intent(in) :: data class(sf_int_t), intent(inout), allocatable :: sf_int allocate (sf_test_spectrum_t :: sf_int) end subroutine sf_test_spectrum_data_allocate_sf_int @ %def sf_test_spectrum_data_allocate_sf_int @ \subsubsection{Interaction} <>= type, extends (sf_int_t) :: sf_test_spectrum_t type(sf_test_spectrum_data_t), pointer :: data => null () contains <> end type sf_test_spectrum_t @ %def sf_test_spectrum_t <>= procedure :: type_string => sf_test_spectrum_type_string <>= function sf_test_spectrum_type_string (object) result (string) class(sf_test_spectrum_t), intent(in) :: object type(string_t) :: string string = "Test Spectrum" end function sf_test_spectrum_type_string @ %def sf_test_spectrum_type_string @ Output. Call the interaction routine after displaying the configuration. <>= procedure :: write => sf_test_spectrum_write <>= subroutine sf_test_spectrum_write (object, unit, testflag) class(sf_test_spectrum_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u u = given_output_unit (unit) if (associated (object%data)) then call object%data%write (u) call object%base_write (u, testflag) else write (u, "(1x,A)") "SF test spectrum data: [undefined]" end if end subroutine sf_test_spectrum_write @ %def sf_test_spectrum_write @ Initialize. We know that [[data]] will be of concrete type [[sf_test_spectrum_data_t]], but we have to cast this explicitly. For this implementation, we set the incoming and outgoing masses equal to the physical particle mass, but keep the radiated mass zero. Optionally, we can provide minimum and maximum values for the momentum transfer. <>= procedure :: init => sf_test_spectrum_init <>= subroutine sf_test_spectrum_init (sf_int, data) class(sf_test_spectrum_t), intent(out) :: sf_int class(sf_data_t), intent(in), target :: data type(quantum_numbers_mask_t), dimension(6) :: mask type(helicity_t) :: hel0 type(color_t) :: col0 type(quantum_numbers_t), dimension(6) :: qn mask = quantum_numbers_mask (.false., .false., .false.) select type (data) type is (sf_test_spectrum_data_t) if (data%with_radiation) then call sf_int%base_init (mask(1:6), & [data%m**2, data%m**2], & [0._default, 0._default], & [data%m**2, data%m**2]) sf_int%data => data call hel0%init (0) call col0%init () call qn(1)%init (data%flv_in, col0, hel0) call qn(2)%init (data%flv_in, col0, hel0) call qn(3)%init (data%flv_rad, col0, hel0) call qn(4)%init (data%flv_rad, col0, hel0) call qn(5)%init (data%flv_out, col0, hel0) call qn(6)%init (data%flv_out, col0, hel0) call sf_int%add_state (qn(1:6)) call sf_int%set_incoming ([1,2]) call sf_int%set_radiated ([3,4]) call sf_int%set_outgoing ([5,6]) else call sf_int%base_init (mask(1:4), & [data%m**2, data%m**2], & [real(default) :: ], & [data%m**2, data%m**2]) sf_int%data => data call hel0%init (0) call col0%init () call qn(1)%init (data%flv_in, col0, hel0) call qn(2)%init (data%flv_in, col0, hel0) call qn(3)%init (data%flv_out, col0, hel0) call qn(4)%init (data%flv_out, col0, hel0) call sf_int%add_state (qn(1:4)) call sf_int%set_incoming ([1,2]) call sf_int%set_outgoing ([3,4]) end if call sf_int%freeze () end select sf_int%status = SF_INITIAL end subroutine sf_test_spectrum_init @ %def sf_test_spectrum_init @ Set kinematics. If [[map]] is unset, the $r$ and $x$ values coincide, and the Jacobian $f(r)$ is trivial. If [[map]] is set, we are asked to provide an efficient mapping. For the test case, we set $x=r^2$ (as above) for both $x$ parameters and consequently $f(r)=4r_1r_2$. <>= procedure :: complete_kinematics => sf_test_spectrum_complete_kinematics <>= subroutine sf_test_spectrum_complete_kinematics (sf_int, x, xb, f, r, rb, map) class(sf_test_spectrum_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: x real(default), dimension(:), intent(out) :: xb real(default), intent(out) :: f real(default), dimension(:), intent(in) :: r real(default), dimension(:), intent(in) :: rb logical, intent(in) :: map real(default), dimension(2) :: xb1 if (map) then x = r**2 f = 4 * r(1) * r(2) else x = r f = 1 end if xb = 1 - x if (sf_int%data%with_radiation) then call sf_int%split_momenta (x, xb) else call sf_int%reduce_momenta (x) end if select case (sf_int%status) case (SF_FAILED_KINEMATICS); f = 0 end select end subroutine sf_test_spectrum_complete_kinematics @ %def sf_test_spectrum_complete_kinematics @ Compute inverse kinematics. Here, we start with the $x$ array and compute the ``input'' $r$ values and the Jacobian $f$. After this, we can set momenta by the same formula as for normal kinematics. <>= procedure :: inverse_kinematics => sf_test_spectrum_inverse_kinematics <>= subroutine sf_test_spectrum_inverse_kinematics & (sf_int, x, xb, f, r, rb, map, set_momenta) class(sf_test_spectrum_t), intent(inout) :: sf_int real(default), dimension(:), intent(in) :: x real(default), dimension(:), intent(in) :: xb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: r real(default), dimension(:), intent(out) :: rb logical, intent(in) :: map logical, intent(in), optional :: set_momenta real(default), dimension(2) :: xb1 logical :: set_mom set_mom = .false.; if (present (set_momenta)) set_mom = set_momenta if (map) then r = sqrt (x) f = 4 * r(1) * r(2) else r = x f = 1 end if rb = 1 - r if (set_mom) then if (sf_int%data%with_radiation) then call sf_int%split_momenta (x, xb) else call sf_int%reduce_momenta (x) end if select case (sf_int%status) case (SF_FAILED_KINEMATICS); f = 0 end select end if end subroutine sf_test_spectrum_inverse_kinematics @ %def sf_test_spectrum_inverse_kinematics @ Apply the structure function. The matrix element becomes unity and the application always succeeds. <>= procedure :: apply => sf_test_spectrum_apply <>= subroutine sf_test_spectrum_apply (sf_int, scale, rescale, i_sub) class(sf_test_spectrum_t), intent(inout) :: sf_int real(default), intent(in) :: scale class(sf_rescale_t), intent(in), optional :: rescale integer, intent(in), optional :: i_sub call sf_int%set_matrix_element & (cmplx (1._default, kind=default)) sf_int%status = SF_EVALUATED end subroutine sf_test_spectrum_apply @ %def sf_test_spectrum_apply @ \subsection{Test implementation: generator spectrum} A generator for two beams, no radiation (for simplicity). \subsubsection{Configuration data} For simplicity, the spectrum contains two mirror images of the previous structure-function configuration: the incoming and all outgoing particles are test scalars. We have two versions, one with radiated particles, one without. <>= type, extends (sf_data_t) :: sf_test_generator_data_t class(model_data_t), pointer :: model => null () type(flavor_t) :: flv_in type(flavor_t) :: flv_out type(flavor_t) :: flv_rad real(default) :: m = 0 contains <> end type sf_test_generator_data_t @ %def sf_test_generator_data_t @ Output. <>= procedure :: write => sf_test_generator_data_write <>= subroutine sf_test_generator_data_write (data, unit, verbose) class(sf_test_generator_data_t), intent(in) :: data integer, intent(in), optional :: unit logical, intent(in), optional :: verbose integer :: u u = given_output_unit (unit) write (u, "(1x,A)") "SF test generator data:" write (u, "(3x,A,A)") "model = ", char (data%model%get_name ()) write (u, "(3x,A)", advance="no") "incoming = " call data%flv_in%write (u); write (u, *) write (u, "(3x,A)", advance="no") "outgoing = " call data%flv_out%write (u); write (u, *) write (u, "(3x,A," // FMT_19 // ")") "mass = ", data%m end subroutine sf_test_generator_data_write @ %def sf_test_generator_data_write @ Initialization. <>= procedure :: init => sf_test_generator_data_init <>= subroutine sf_test_generator_data_init (data, model, pdg_in) class(sf_test_generator_data_t), intent(out) :: data class(model_data_t), intent(in), target :: model type(pdg_array_t), intent(in) :: pdg_in data%model => model if (pdg_array_get (pdg_in, 1) /= 25) then call msg_fatal ("Test generator: input flavor must be 's'") end if call data%flv_in%init (25, model) data%m = data%flv_in%get_mass () call data%flv_out%init (25, model) end subroutine sf_test_generator_data_init @ %def sf_test_generator_data_init @ This structure function is a generator. <>= procedure :: is_generator => sf_test_generator_data_is_generator <>= function sf_test_generator_data_is_generator (data) result (flag) class(sf_test_generator_data_t), intent(in) :: data logical :: flag flag = .true. end function sf_test_generator_data_is_generator @ %def sf_test_generator_data_is_generator @ Return the number of parameters: 2, since we have only collinear splitting here. <>= procedure :: get_n_par => sf_test_generator_data_get_n_par <>= function sf_test_generator_data_get_n_par (data) result (n) class(sf_test_generator_data_t), intent(in) :: data integer :: n n = 2 end function sf_test_generator_data_get_n_par @ %def sf_test_generator_data_get_n_par @ Return the outgoing particle PDG codes: 25 <>= procedure :: get_pdg_out => sf_test_generator_data_get_pdg_out <>= subroutine sf_test_generator_data_get_pdg_out (data, pdg_out) class(sf_test_generator_data_t), intent(in) :: data type(pdg_array_t), dimension(:), intent(inout) :: pdg_out pdg_out(1) = 25 pdg_out(2) = 25 end subroutine sf_test_generator_data_get_pdg_out @ %def sf_test_generator_data_get_pdg_out @ Allocate the matching interaction. <>= procedure :: allocate_sf_int => & sf_test_generator_data_allocate_sf_int <>= subroutine sf_test_generator_data_allocate_sf_int (data, sf_int) class(sf_test_generator_data_t), intent(in) :: data class(sf_int_t), intent(inout), allocatable :: sf_int allocate (sf_test_generator_t :: sf_int) end subroutine sf_test_generator_data_allocate_sf_int @ %def sf_test_generator_data_allocate_sf_int @ \subsubsection{Interaction} <>= type, extends (sf_int_t) :: sf_test_generator_t type(sf_test_generator_data_t), pointer :: data => null () contains <> end type sf_test_generator_t @ %def sf_test_generator_t <>= procedure :: type_string => sf_test_generator_type_string <>= function sf_test_generator_type_string (object) result (string) class(sf_test_generator_t), intent(in) :: object type(string_t) :: string string = "Test Generator" end function sf_test_generator_type_string @ %def sf_test_generator_type_string @ Output. Call the interaction routine after displaying the configuration. <>= procedure :: write => sf_test_generator_write <>= subroutine sf_test_generator_write (object, unit, testflag) class(sf_test_generator_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u u = given_output_unit (unit) if (associated (object%data)) then call object%data%write (u) call object%base_write (u, testflag) else write (u, "(1x,A)") "SF test generator data: [undefined]" end if end subroutine sf_test_generator_write @ %def sf_test_generator_write @ Initialize. We know that [[data]] will be of concrete type [[sf_test_generator_data_t]], but we have to cast this explicitly. For this implementation, we set the incoming and outgoing masses equal to the physical particle mass. No radiation. <>= procedure :: init => sf_test_generator_init <>= subroutine sf_test_generator_init (sf_int, data) class(sf_test_generator_t), intent(out) :: sf_int class(sf_data_t), intent(in), target :: data type(quantum_numbers_mask_t), dimension(4) :: mask type(helicity_t) :: hel0 type(color_t) :: col0 type(quantum_numbers_t), dimension(4) :: qn mask = quantum_numbers_mask (.false., .false., .false.) select type (data) type is (sf_test_generator_data_t) call sf_int%base_init (mask(1:4), & [data%m**2, data%m**2], & [real(default) :: ], & [data%m**2, data%m**2]) sf_int%data => data call hel0%init (0) call col0%init () call qn(1)%init (data%flv_in, col0, hel0) call qn(2)%init (data%flv_in, col0, hel0) call qn(3)%init (data%flv_out, col0, hel0) call qn(4)%init (data%flv_out, col0, hel0) call sf_int%add_state (qn(1:4)) call sf_int%set_incoming ([1,2]) call sf_int%set_outgoing ([3,4]) call sf_int%freeze () end select sf_int%status = SF_INITIAL end subroutine sf_test_generator_init @ %def sf_test_generator_init @ This structure function is a generator. <>= procedure :: is_generator => sf_test_generator_is_generator <>= function sf_test_generator_is_generator (sf_int) result (flag) class(sf_test_generator_t), intent(in) :: sf_int logical :: flag flag = sf_int%data%is_generator () end function sf_test_generator_is_generator @ %def sf_test_generator_is_generator @ Generate free parameters. This mock generator always produces the nubmers 0.8 and 0.5. <>= procedure :: generate_free => sf_test_generator_generate_free <>= subroutine sf_test_generator_generate_free (sf_int, r, rb, x_free) class(sf_test_generator_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: r, rb real(default), intent(inout) :: x_free r = [0.8, 0.5] rb= 1 - r x_free = x_free * product (r) end subroutine sf_test_generator_generate_free @ %def sf_test_generator_generate_free @ Recover momentum fractions. Since the x values are free, we also set the [[x_free]] parameter. <>= procedure :: recover_x => sf_test_generator_recover_x <>= subroutine sf_test_generator_recover_x (sf_int, x, xb, x_free) class(sf_test_generator_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: x real(default), dimension(:), intent(out) :: xb real(default), intent(inout), optional :: x_free call sf_int%base_recover_x (x, xb) if (present (x_free)) x_free = x_free * product (x) end subroutine sf_test_generator_recover_x @ %def sf_test_generator_recover_x @ Set kinematics. Since this is a generator, just transfer input to output. <>= procedure :: complete_kinematics => sf_test_generator_complete_kinematics <>= subroutine sf_test_generator_complete_kinematics (sf_int, x, xb, f, r, rb, map) class(sf_test_generator_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: x real(default), dimension(:), intent(out) :: xb real(default), intent(out) :: f real(default), dimension(:), intent(in) :: r real(default), dimension(:), intent(in) :: rb logical, intent(in) :: map x = r xb= rb f = 1 call sf_int%reduce_momenta (x) end subroutine sf_test_generator_complete_kinematics @ %def sf_test_generator_complete_kinematics @ Compute inverse kinematics. Here, we start with the $x$ array and compute the ``input'' $r$ values and the Jacobian $f$. After this, we can set momenta by the same formula as for normal kinematics. <>= procedure :: inverse_kinematics => sf_test_generator_inverse_kinematics <>= subroutine sf_test_generator_inverse_kinematics & (sf_int, x, xb, f, r, rb, map, set_momenta) class(sf_test_generator_t), intent(inout) :: sf_int real(default), dimension(:), intent(in) :: x real(default), dimension(:), intent(in) :: xb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: r real(default), dimension(:), intent(out) :: rb logical, intent(in) :: map logical, intent(in), optional :: set_momenta logical :: set_mom set_mom = .false.; if (present (set_momenta)) set_mom = set_momenta r = x rb= xb f = 1 if (set_mom) call sf_int%reduce_momenta (x) end subroutine sf_test_generator_inverse_kinematics @ %def sf_test_generator_inverse_kinematics @ Apply the structure function. The matrix element becomes unity and the application always succeeds. <>= procedure :: apply => sf_test_generator_apply <>= subroutine sf_test_generator_apply (sf_int, scale, rescale, i_sub) class(sf_test_generator_t), intent(inout) :: sf_int real(default), intent(in) :: scale class(sf_rescale_t), intent(in), optional :: rescale integer, intent(in), optional :: i_sub call sf_int%set_matrix_element & (cmplx (1._default, kind=default)) sf_int%status = SF_EVALUATED end subroutine sf_test_generator_apply @ %def sf_test_generator_apply @ \subsubsection{Test structure function data} Construct and display a test structure function data object. <>= call test (sf_base_1, "sf_base_1", & "structure function configuration", & u, results) <>= public :: sf_base_1 <>= subroutine sf_base_1 (u) integer, intent(in) :: u type(model_data_t), target :: model type(pdg_array_t) :: pdg_in type(pdg_array_t), dimension(1) :: pdg_out integer, dimension(:), allocatable :: pdg1 class(sf_data_t), allocatable :: data write (u, "(A)") "* Test output: sf_base_1" write (u, "(A)") "* Purpose: initialize and display & &test structure function data" write (u, "(A)") call model%init_test () pdg_in = 25 allocate (sf_test_data_t :: data) select type (data) type is (sf_test_data_t) call data%init (model, pdg_in) end select call data%write (u) write (u, "(A)") write (u, "(1x,A)") "Outgoing particle code:" call data%get_pdg_out (pdg_out) pdg1 = pdg_out(1) write (u, "(2x,99(1x,I0))") pdg1 call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_base_1" end subroutine sf_base_1 @ %def sf_base_1 @ \subsubsection{Test and probe structure function} Construct and display a structure function object based on the test structure function. <>= call test (sf_base_2, "sf_base_2", & "structure function instance", & u, results) <>= public :: sf_base_2 <>= subroutine sf_base_2 (u) integer, intent(in) :: u type(model_data_t), target :: model type(flavor_t) :: flv type(pdg_array_t) :: pdg_in class(sf_data_t), allocatable, target :: data class(sf_int_t), allocatable :: sf_int type(vector4_t) :: k type(vector4_t), dimension(2) :: q real(default) :: E real(default), dimension(:), allocatable :: r, rb, x, xb real(default) :: f write (u, "(A)") "* Test output: sf_base_2" write (u, "(A)") "* Purpose: initialize and fill & &test structure function object" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call model%init_test () pdg_in = 25 call flv%init (25, model) call reset_interaction_counter () allocate (sf_test_data_t :: data) select type (data) type is (sf_test_data_t) call data%init (model, pdg_in) end select write (u, "(A)") "* Initialize structure-function object" write (u, "(A)") call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1]) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Initialize incoming momentum with E=500" write (u, "(A)") E = 500 k = vector4_moving (E, sqrt (E**2 - flv%get_mass ()**2), 3) call vector4_write (k, u) call sf_int%seed_kinematics ([k]) write (u, "(A)") write (u, "(A)") "* Set kinematics for x=0" write (u, "(A)") allocate (r (data%get_n_par ())) allocate (rb(size (r))) allocate (x (size (r))) allocate (xb(size (r))) r = 0 rb = 1 - r call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%write (u) write (u, "(A)") write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Set kinematics for x=1" write (u, "(A)") r = 1 rb = 1 - r call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%write (u) write (u, "(A)") write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Set kinematics for x=0.5" write (u, "(A)") r = 0.5_default rb = 1 - r call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%write (u) write (u, "(A)") write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Set kinematics with mapping for r=0.8" write (u, "(A)") r = 0.8_default rb = 1 - r call sf_int%complete_kinematics (x, xb, f, r, rb, map=.true.) call sf_int%write (u) write (u, "(A)") write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Recover x from momenta" write (u, "(A)") q = sf_int%get_momenta (outgoing=.true.) call sf_int%final () deallocate (sf_int) call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1]) call sf_int%seed_kinematics ([k]) call sf_int%set_momenta (q, outgoing=.true.) call sf_int%recover_x (x, xb) write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A)") write (u, "(A)") "* Compute inverse kinematics for x=0.64 and evaluate" write (u, "(A)") x = 0.64_default call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.true.) call sf_int%apply (scale=0._default) call sf_int%write (u) write (u, "(A)") write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Cleanup" call sf_int%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_base_2" end subroutine sf_base_2 @ %def sf_base_2 @ \subsubsection{Collinear kinematics} Scan over the possibilities for mass assignment and on-shell projections, collinear case. <>= call test (sf_base_3, "sf_base_3", & "alternatives for collinear kinematics", & u, results) <>= public :: sf_base_3 <>= subroutine sf_base_3 (u) integer, intent(in) :: u type(model_data_t), target :: model type(pdg_array_t) :: pdg_in type(flavor_t) :: flv class(sf_data_t), allocatable, target :: data class(sf_int_t), allocatable :: sf_int type(vector4_t) :: k real(default) :: E real(default), dimension(:), allocatable :: r, rb, x, xb real(default) :: f write (u, "(A)") "* Test output: sf_base_3" write (u, "(A)") "* Purpose: check various kinematical setups" write (u, "(A)") "* for collinear structure-function splitting." write (u, "(A)") " (two masses equal, one zero)" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call model%init_test () pdg_in = 25 call flv%init (25, model) call reset_interaction_counter () allocate (sf_test_data_t :: data) select type (data) type is (sf_test_data_t) call data%init (model, pdg_in) end select write (u, "(A)") "* Initialize structure-function object" write (u, "(A)") call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%write (u) allocate (r (data%get_n_par ())) allocate (rb(size (r))) allocate (x (size (r))) allocate (xb(size (r))) write (u, "(A)") write (u, "(A)") "* Initialize incoming momentum with E=500" E = 500 k = vector4_moving (E, sqrt (E**2 - flv%get_mass ()**2), 3) call sf_int%seed_kinematics ([k]) write (u, "(A)") write (u, "(A)") "* Set radiated mass to zero" sf_int%mr2 = 0 sf_int%mo2 = sf_int%mi2 write (u, "(A)") write (u, "(A)") "* Set kinematics for x=0.5, keeping energy" write (u, "(A)") r = 0.5_default rb = 1 - r sf_int%on_shell_mode = KEEP_ENERGY call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Recover x and r" write (u, "(A)") call sf_int%recover_x (x, xb) call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.false.) write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A)") write (u, "(A)") "* Set kinematics for x=0.5, keeping momentum" write (u, "(A)") r = 0.5_default rb = 1 - r sf_int%on_shell_mode = KEEP_MOMENTUM call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Recover x and r" write (u, "(A)") call sf_int%recover_x (x, xb) call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.false.) write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A)") write (u, "(A)") "* Set outgoing mass to zero" sf_int%mr2 = sf_int%mi2 sf_int%mo2 = 0 write (u, "(A)") write (u, "(A)") "* Set kinematics for x=0.5, keeping energy" write (u, "(A)") r = 0.5_default rb = 1 - r sf_int%on_shell_mode = KEEP_ENERGY call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Recover x and r" write (u, "(A)") call sf_int%recover_x (x, xb) call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.false.) write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A)") write (u, "(A)") "* Set kinematics for x=0.5, keeping momentum" write (u, "(A)") r = 0.5_default rb = 1 - r sf_int%on_shell_mode = KEEP_MOMENTUM call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Recover x and r" write (u, "(A)") call sf_int%recover_x (x, xb) call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.false.) write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A)") write (u, "(A)") "* Set incoming mass to zero" k = vector4_moving (E, E, 3) call sf_int%seed_kinematics ([k]) sf_int%mr2 = sf_int%mi2 sf_int%mo2 = sf_int%mi2 sf_int%mi2 = 0 write (u, "(A)") write (u, "(A)") "* Set kinematics for x=0.5, keeping energy" write (u, "(A)") r = 0.5_default rb = 1 - r sf_int%on_shell_mode = KEEP_ENERGY call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Recover x and r" write (u, "(A)") call sf_int%recover_x (x, xb) call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.false.) write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A)") write (u, "(A)") "* Set kinematics for x=0.5, keeping momentum" write (u, "(A)") r = 0.5_default rb = 1 - r sf_int%on_shell_mode = KEEP_MOMENTUM call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Recover x and r" write (u, "(A)") call sf_int%recover_x (x, xb) call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.false.) write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A)") write (u, "(A)") "* Set all masses to zero" sf_int%mr2 = 0 sf_int%mo2 = 0 sf_int%mi2 = 0 write (u, "(A)") write (u, "(A)") "* Set kinematics for x=0.5, keeping energy" write (u, "(A)") r = 0.5_default rb = 1 - r sf_int%on_shell_mode = KEEP_ENERGY call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Recover x and r" write (u, "(A)") call sf_int%recover_x (x, xb) call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.false.) write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A)") write (u, "(A)") "* Set kinematics for x=0.5, keeping momentum" write (u, "(A)") r = 0.5_default rb = 1 - r sf_int%on_shell_mode = KEEP_MOMENTUM call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Recover x and r" write (u, "(A)") call sf_int%recover_x (x, xb) call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.false.) write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A)") write (u, "(A)") "* Cleanup" call sf_int%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_base_3" end subroutine sf_base_3 @ %def sf_base_3 @ \subsubsection{Non-collinear kinematics} Scan over the possibilities for mass assignment and on-shell projections, non-collinear case. <>= call test (sf_base_4, "sf_base_4", & "alternatives for non-collinear kinematics", & u, results) <>= public :: sf_base_4 <>= subroutine sf_base_4 (u) integer, intent(in) :: u type(model_data_t), target :: model type(pdg_array_t) :: pdg_in type(flavor_t) :: flv class(sf_data_t), allocatable, target :: data class(sf_int_t), allocatable :: sf_int type(vector4_t) :: k real(default) :: E real(default), dimension(:), allocatable :: r, rb, x, xb real(default) :: f write (u, "(A)") "* Test output: sf_base_4" write (u, "(A)") "* Purpose: check various kinematical setups" write (u, "(A)") "* for free structure-function splitting." write (u, "(A)") " (two masses equal, one zero)" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call model%init_test () pdg_in = 25 call flv%init (25, model) call reset_interaction_counter () allocate (sf_test_data_t :: data) select type (data) type is (sf_test_data_t) call data%init (model, pdg_in, collinear=.false.) end select write (u, "(A)") "* Initialize structure-function object" write (u, "(A)") call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%write (u) allocate (r (data%get_n_par ())) allocate (rb(size (r))) allocate (x (size (r))) allocate (xb(size (r))) write (u, "(A)") write (u, "(A)") "* Initialize incoming momentum with E=500" E = 500 k = vector4_moving (E, sqrt (E**2 - flv%get_mass ()**2), 3) call sf_int%seed_kinematics ([k]) write (u, "(A)") write (u, "(A)") "* Set radiated mass to zero" sf_int%mr2 = 0 sf_int%mo2 = sf_int%mi2 write (u, "(A)") write (u, "(A)") "* Set kinematics for x=0.5/0.5/0.125, keeping energy" write (u, "(A)") r = [0.5_default, 0.5_default, 0.125_default] rb = 1 - r sf_int%on_shell_mode = KEEP_ENERGY call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Recover x and r" write (u, "(A)") call sf_int%recover_x (x, xb) call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.false.) write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A)") write (u, "(A)") "* Set kinematics for x=0.5/0.5/0.125, keeping momentum" write (u, "(A)") r = [0.5_default, 0.5_default, 0.125_default] rb = 1 - r sf_int%on_shell_mode = KEEP_MOMENTUM call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Recover x and r" write (u, "(A)") call sf_int%recover_x (x, xb) call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.false.) write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A)") write (u, "(A)") "* Set outgoing mass to zero" sf_int%mr2 = sf_int%mi2 sf_int%mo2 = 0 write (u, "(A)") write (u, "(A)") "* Set kinematics for x=0.5/0.5/0.125, keeping energy" write (u, "(A)") r = [0.5_default, 0.5_default, 0.125_default] rb = 1 - r sf_int%on_shell_mode = KEEP_ENERGY call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Recover x and r" write (u, "(A)") call sf_int%recover_x (x, xb) call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.false.) write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A)") write (u, "(A)") "* Set kinematics for x=0.5/0.5/0.125, keeping momentum" write (u, "(A)") r = [0.5_default, 0.5_default, 0.125_default] rb = 1 - r sf_int%on_shell_mode = KEEP_MOMENTUM call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Recover x and r" write (u, "(A)") call sf_int%recover_x (x, xb) call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.false.) write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A)") write (u, "(A)") "* Set incoming mass to zero" k = vector4_moving (E, E, 3) call sf_int%seed_kinematics ([k]) sf_int%mr2 = sf_int%mi2 sf_int%mo2 = sf_int%mi2 sf_int%mi2 = 0 write (u, "(A)") write (u, "(A)") "* Set kinematics for x=0.5/0.5/0.125, keeping energy" write (u, "(A)") r = [0.5_default, 0.5_default, 0.125_default] rb = 1 - r sf_int%on_shell_mode = KEEP_ENERGY call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Recover x and r" write (u, "(A)") call sf_int%recover_x (x, xb) call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.false.) write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A)") write (u, "(A)") "* Set kinematics for x=0.5/0.5/0.125, keeping momentum" write (u, "(A)") r = [0.5_default, 0.5_default, 0.125_default] rb = 1 - r sf_int%on_shell_mode = KEEP_MOMENTUM call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Recover x and r" write (u, "(A)") call sf_int%recover_x (x, xb) call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.false.) write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A)") write (u, "(A)") "* Set all masses to zero" sf_int%mr2 = 0 sf_int%mo2 = 0 sf_int%mi2 = 0 write (u, "(A)") write (u, "(A)") "* Re-Initialize structure-function object with Q bounds" call reset_interaction_counter () select type (data) type is (sf_test_data_t) call data%init (model, pdg_in, collinear=.false., & qbounds = [1._default, 100._default]) end select call sf_int%init (data) call sf_int%seed_kinematics ([k]) write (u, "(A)") write (u, "(A)") "* Set kinematics for x=0.5/0.5/0.125, keeping energy" write (u, "(A)") r = [0.5_default, 0.5_default, 0.125_default] rb = 1 - r sf_int%on_shell_mode = KEEP_ENERGY call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Recover x and r" write (u, "(A)") call sf_int%recover_x (x, xb) call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.false.) write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A)") write (u, "(A)") "* Set kinematics for x=0.5/0.5/0.125, keeping momentum" write (u, "(A)") r = [0.5_default, 0.5_default, 0.125_default] rb = 1 - r sf_int%on_shell_mode = KEEP_MOMENTUM call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Recover x and r" write (u, "(A)") call sf_int%recover_x (x, xb) call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.false.) write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A)") write (u, "(A)") "* Cleanup" call sf_int%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_base_4" end subroutine sf_base_4 @ %def sf_base_4 @ \subsubsection{Pair spectrum} Construct and display a structure function object for a pair spectrum (a structure function involving two particles simultaneously). <>= call test (sf_base_5, "sf_base_5", & "pair spectrum with radiation", & u, results) <>= public :: sf_base_5 <>= subroutine sf_base_5 (u) integer, intent(in) :: u type(model_data_t), target :: model type(pdg_array_t) :: pdg_in type(pdg_array_t), dimension(2) :: pdg_out integer, dimension(:), allocatable :: pdg1, pdg2 type(flavor_t) :: flv class(sf_data_t), allocatable, target :: data class(sf_int_t), allocatable :: sf_int type(vector4_t), dimension(2) :: k type(vector4_t), dimension(4) :: q real(default) :: E real(default), dimension(:), allocatable :: r, rb, x, xb real(default) :: f write (u, "(A)") "* Test output: sf_base_5" write (u, "(A)") "* Purpose: initialize and fill & &a pair spectrum object" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call model%init_test () call flv%init (25, model) pdg_in = 25 call reset_interaction_counter () allocate (sf_test_spectrum_data_t :: data) select type (data) type is (sf_test_spectrum_data_t) call data%init (model, pdg_in, with_radiation=.true.) end select write (u, "(1x,A)") "Outgoing particle codes:" call data%get_pdg_out (pdg_out) pdg1 = pdg_out(1) pdg2 = pdg_out(2) write (u, "(2x,99(1x,I0))") pdg1, pdg2 write (u, "(A)") write (u, "(A)") "* Initialize spectrum object" write (u, "(A)") call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Initialize incoming momenta with sqrts=1000" E = 500 k(1) = vector4_moving (E, sqrt (E**2 - flv%get_mass ()**2), 3) k(2) = vector4_moving (E, sqrt (E**2 - flv%get_mass ()**2), 3) call sf_int%seed_kinematics (k) write (u, "(A)") write (u, "(A)") "* Set kinematics for x=0.4,0.8" write (u, "(A)") allocate (r (data%get_n_par ())) allocate (rb(size (r))) allocate (x (size (r))) allocate (xb(size (r))) r = [0.4_default, 0.8_default] rb = 1 - r call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%write (u) write (u, "(A)") write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Set kinematics with mapping for r=0.6,0.8" write (u, "(A)") r = [0.6_default, 0.8_default] rb = 1 - r call sf_int%complete_kinematics (x, xb, f, r, rb, map=.true.) call sf_int%write (u) write (u, "(A)") write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Recover x from momenta" write (u, "(A)") q = sf_int%get_momenta (outgoing=.true.) call sf_int%final () deallocate (sf_int) call reset_interaction_counter () call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%seed_kinematics (k) call sf_int%set_momenta (q, outgoing=.true.) call sf_int%recover_x (x, xb) write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A)") write (u, "(A)") "* Compute inverse kinematics for x=0.36,0.64 & &and evaluate" write (u, "(A)") x = [0.36_default, 0.64_default] xb = 1 - x call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.true.) call sf_int%apply (scale=0._default) call sf_int%write (u) write (u, "(A)") write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Cleanup" call sf_int%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_base_5" end subroutine sf_base_5 @ %def sf_base_5 @ \subsubsection{Pair spectrum without radiation} Construct and display a structure function object for a pair spectrum (a structure function involving two particles simultaneously). <>= call test (sf_base_6, "sf_base_6", & "pair spectrum without radiation", & u, results) <>= public :: sf_base_6 <>= subroutine sf_base_6 (u) integer, intent(in) :: u type(model_data_t), target :: model type(pdg_array_t) :: pdg_in type(flavor_t) :: flv class(sf_data_t), allocatable, target :: data class(sf_int_t), allocatable :: sf_int type(vector4_t), dimension(2) :: k type(vector4_t), dimension(2) :: q real(default) :: E real(default), dimension(:), allocatable :: r, rb, x, xb real(default) :: f write (u, "(A)") "* Test output: sf_base_6" write (u, "(A)") "* Purpose: initialize and fill & &a pair spectrum object" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call model%init_test () call flv%init (25, model) pdg_in = 25 call reset_interaction_counter () allocate (sf_test_spectrum_data_t :: data) select type (data) type is (sf_test_spectrum_data_t) call data%init (model, pdg_in, with_radiation=.false.) end select write (u, "(A)") "* Initialize spectrum object" write (u, "(A)") call data%allocate_sf_int (sf_int) call sf_int%init (data) write (u, "(A)") "* Initialize incoming momenta with sqrts=1000" E = 500 k(1) = vector4_moving (E, sqrt (E**2 - flv%get_mass ()**2), 3) k(2) = vector4_moving (E, sqrt (E**2 - flv%get_mass ()**2), 3) call sf_int%seed_kinematics (k) write (u, "(A)") write (u, "(A)") "* Set kinematics for x=0.4,0.8" write (u, "(A)") allocate (r (data%get_n_par ())) allocate (rb(size (r))) allocate (x (size (r))) allocate (xb(size (r))) r = [0.4_default, 0.8_default] rb = 1 - r call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%write (u) write (u, "(A)") write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Recover x from momenta" write (u, "(A)") q = sf_int%get_momenta (outgoing=.true.) call sf_int%final () deallocate (sf_int) call reset_interaction_counter () call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%seed_kinematics (k) call sf_int%set_momenta (q, outgoing=.true.) call sf_int%recover_x (x, xb) write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A)") write (u, "(A)") "* Compute inverse kinematics for x=0.4,0.8 & &and evaluate" write (u, "(A)") x = [0.4_default, 0.8_default] xb = 1 - x call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%apply (scale=0._default) call sf_int%write (u) write (u, "(A)") write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Cleanup" call sf_int%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_base_6" end subroutine sf_base_6 @ %def sf_base_6 @ \subsubsection{Direct access to structure function} Probe a structure function directly. <>= call test (sf_base_7, "sf_base_7", & "direct access", & u, results) <>= public :: sf_base_7 <>= subroutine sf_base_7 (u) integer, intent(in) :: u type(model_data_t), target :: model type(pdg_array_t) :: pdg_in type(flavor_t) :: flv class(sf_data_t), allocatable, target :: data class(sf_int_t), allocatable :: sf_int real(default), dimension(:), allocatable :: value write (u, "(A)") "* Test output: sf_base_7" write (u, "(A)") "* Purpose: check direct access method" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call model%init_test () call flv%init (25, model) pdg_in = 25 call reset_interaction_counter () write (u, "(A)") "* Initialize structure-function object" write (u, "(A)") allocate (sf_test_data_t :: data) select type (data) type is (sf_test_data_t) call data%init (model, pdg_in) end select call data%allocate_sf_int (sf_int) call sf_int%init (data) write (u, "(A)") "* Probe structure function: states" write (u, "(A)") write (u, "(A,I0)") "n_states = ", sf_int%get_n_states () write (u, "(A,I0)") "n_in = ", sf_int%get_n_in () write (u, "(A,I0)") "n_rad = ", sf_int%get_n_rad () write (u, "(A,I0)") "n_out = ", sf_int%get_n_out () write (u, "(A)") write (u, "(A)", advance="no") "state(1) = " call quantum_numbers_write (sf_int%get_state (1), u) write (u, *) allocate (value (sf_int%get_n_states ())) call sf_int%compute_values (value, & E=[500._default], x=[0.5_default], xb=[0.5_default], scale=0._default) write (u, "(A)") write (u, "(A)", advance="no") "value (E=500, x=0.5) =" write (u, "(9(1x," // FMT_19 // "))") value call sf_int%compute_values (value, & x=[0.1_default], xb=[0.9_default], scale=0._default) write (u, "(A)") write (u, "(A)", advance="no") "value (E=500, x=0.1) =" write (u, "(9(1x," // FMT_19 // "))") value write (u, "(A)") write (u, "(A)") "* Initialize spectrum object" write (u, "(A)") deallocate (value) call sf_int%final () deallocate (sf_int) deallocate (data) allocate (sf_test_spectrum_data_t :: data) select type (data) type is (sf_test_spectrum_data_t) call data%init (model, pdg_in, with_radiation=.false.) end select call data%allocate_sf_int (sf_int) call sf_int%init (data) write (u, "(A)") "* Probe spectrum: states" write (u, "(A)") write (u, "(A,I0)") "n_states = ", sf_int%get_n_states () write (u, "(A,I0)") "n_in = ", sf_int%get_n_in () write (u, "(A,I0)") "n_rad = ", sf_int%get_n_rad () write (u, "(A,I0)") "n_out = ", sf_int%get_n_out () write (u, "(A)") write (u, "(A)", advance="no") "state(1) = " call quantum_numbers_write (sf_int%get_state (1), u) write (u, *) allocate (value (sf_int%get_n_states ())) call sf_int%compute_value (1, value(1), & E = [500._default, 500._default], & x = [0.5_default, 0.6_default], & xb= [0.5_default, 0.4_default], & scale = 0._default) write (u, "(A)") write (u, "(A)", advance="no") "value (E=500,500, x=0.5,0.6) =" write (u, "(9(1x," // FMT_19 // "))") value write (u, "(A)") write (u, "(A)") "* Cleanup" call sf_int%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_base_7" end subroutine sf_base_7 @ %def sf_base_7 @ \subsubsection{Structure function chain configuration} <>= call test (sf_base_8, "sf_base_8", & "structure function chain configuration", & u, results) <>= public :: sf_base_8 <>= subroutine sf_base_8 (u) integer, intent(in) :: u type(model_data_t), target :: model type(flavor_t) :: flv type(pdg_array_t) :: pdg_in type(beam_data_t), target :: beam_data class(sf_data_t), allocatable, target :: data_strfun class(sf_data_t), allocatable, target :: data_spectrum type(sf_config_t), dimension(:), allocatable :: sf_config type(sf_chain_t) :: sf_chain write (u, "(A)") "* Test output: sf_base_8" write (u, "(A)") "* Purpose: set up a structure-function chain" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call model%init_test () call flv%init (25, model) pdg_in = 25 call reset_interaction_counter () call beam_data%init_sqrts (1000._default, [flv, flv]) allocate (sf_test_data_t :: data_strfun) select type (data_strfun) type is (sf_test_data_t) call data_strfun%init (model, pdg_in) end select allocate (sf_test_spectrum_data_t :: data_spectrum) select type (data_spectrum) type is (sf_test_spectrum_data_t) call data_spectrum%init (model, pdg_in, with_radiation=.true.) end select write (u, "(A)") "* Set up chain with beams only" write (u, "(A)") call sf_chain%init (beam_data) call write_separator (u, 2) call sf_chain%write (u) call write_separator (u, 2) call sf_chain%final () write (u, "(A)") write (u, "(A)") "* Set up chain with structure function" write (u, "(A)") allocate (sf_config (1)) call sf_config(1)%init ([1], data_strfun) call sf_chain%init (beam_data, sf_config) call write_separator (u, 2) call sf_chain%write (u) call write_separator (u, 2) call sf_chain%final () write (u, "(A)") write (u, "(A)") "* Set up chain with spectrum and structure function" write (u, "(A)") deallocate (sf_config) allocate (sf_config (2)) call sf_config(1)%init ([1,2], data_spectrum) call sf_config(2)%init ([2], data_strfun) call sf_chain%init (beam_data, sf_config) call write_separator (u, 2) call sf_chain%write (u) call write_separator (u, 2) call sf_chain%final () write (u, "(A)") write (u, "(A)") "* Cleanup" call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_base_8" end subroutine sf_base_8 @ %def sf_base_8 @ \subsubsection{Structure function instance configuration} We create a structure-function chain instance which implements a configured structure-function chain. We link the momentum entries in the interactions and compute kinematics. We do not actually connect the interactions and create evaluators. We skip this step and manually advance the status of the chain instead. <>= call test (sf_base_9, "sf_base_9", & "structure function chain instance", & u, results) <>= public :: sf_base_9 <>= subroutine sf_base_9 (u) integer, intent(in) :: u type(model_data_t), target :: model type(flavor_t) :: flv type(pdg_array_t) :: pdg_in type(beam_data_t), target :: beam_data class(sf_data_t), allocatable, target :: data_strfun class(sf_data_t), allocatable, target :: data_spectrum type(sf_config_t), dimension(:), allocatable, target :: sf_config type(sf_chain_t), target :: sf_chain type(sf_chain_instance_t), target :: sf_chain_instance type(sf_channel_t), dimension(2) :: sf_channel type(vector4_t), dimension(2) :: p integer :: j write (u, "(A)") "* Test output: sf_base_9" write (u, "(A)") "* Purpose: set up a structure-function chain & &and create an instance" write (u, "(A)") "* compute kinematics" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call model%init_test () call flv%init (25, model) pdg_in = 25 call reset_interaction_counter () call beam_data%init_sqrts (1000._default, [flv, flv]) allocate (sf_test_data_t :: data_strfun) select type (data_strfun) type is (sf_test_data_t) call data_strfun%init (model, pdg_in) end select allocate (sf_test_spectrum_data_t :: data_spectrum) select type (data_spectrum) type is (sf_test_spectrum_data_t) call data_spectrum%init (model, pdg_in, with_radiation=.true.) end select write (u, "(A)") "* Set up chain with beams only" write (u, "(A)") call sf_chain%init (beam_data) call sf_chain_instance%init (sf_chain, n_channel = 1) call sf_chain_instance%link_interactions () sf_chain_instance%status = SF_DONE_CONNECTIONS call sf_chain_instance%compute_kinematics (1, [real(default) ::]) call write_separator (u, 2) call sf_chain%write (u) call write_separator (u, 2) call sf_chain_instance%write (u) call write_separator (u, 2) call sf_chain_instance%get_out_momenta (p) write (u, "(A)") write (u, "(A)") "* Outgoing momenta:" do j = 1, 2 write (u, "(A)") call vector4_write (p(j), u) end do call sf_chain_instance%final () call sf_chain%final () write (u, "(A)") write (u, "(A)") "* Set up chain with structure function" write (u, "(A)") allocate (sf_config (1)) call sf_config(1)%init ([1], data_strfun) call sf_chain%init (beam_data, sf_config) call sf_chain_instance%init (sf_chain, n_channel = 1) call sf_channel(1)%init (1) call sf_channel(1)%activate_mapping ([1]) call sf_chain_instance%set_channel (1, sf_channel(1)) call sf_chain_instance%link_interactions () sf_chain_instance%status = SF_DONE_CONNECTIONS call sf_chain_instance%compute_kinematics (1, [0.8_default]) call write_separator (u, 2) call sf_chain%write (u) call write_separator (u, 2) call sf_chain_instance%write (u) call write_separator (u, 2) call sf_chain_instance%get_out_momenta (p) write (u, "(A)") write (u, "(A)") "* Outgoing momenta:" do j = 1, 2 write (u, "(A)") call vector4_write (p(j), u) end do call sf_chain_instance%final () call sf_chain%final () write (u, "(A)") write (u, "(A)") "* Set up chain with spectrum and structure function" write (u, "(A)") deallocate (sf_config) allocate (sf_config (2)) call sf_config(1)%init ([1,2], data_spectrum) call sf_config(2)%init ([2], data_strfun) call sf_chain%init (beam_data, sf_config) call sf_chain_instance%init (sf_chain, n_channel = 1) call sf_channel(2)%init (2) call sf_channel(2)%activate_mapping ([2]) call sf_chain_instance%set_channel (1, sf_channel(2)) call sf_chain_instance%link_interactions () sf_chain_instance%status = SF_DONE_CONNECTIONS call sf_chain_instance%compute_kinematics & (1, [0.5_default, 0.6_default, 0.8_default]) call write_separator (u, 2) call sf_chain%write (u) call write_separator (u, 2) call sf_chain_instance%write (u) call write_separator (u, 2) call sf_chain_instance%get_out_momenta (p) write (u, "(A)") write (u, "(A)") "* Outgoing momenta:" do j = 1, 2 write (u, "(A)") call vector4_write (p(j), u) end do call sf_chain_instance%final () call sf_chain%final () write (u, "(A)") write (u, "(A)") "* Cleanup" call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_base_9" end subroutine sf_base_9 @ %def sf_base_9 @ \subsubsection{Structure function chain mappings} Set up a structure function chain instance with a pair of single-particle structure functions. We test different global mappings for this setup. Again, we skip evaluators. <>= call test (sf_base_10, "sf_base_10", & "structure function chain mapping", & u, results) <>= public :: sf_base_10 <>= subroutine sf_base_10 (u) integer, intent(in) :: u type(model_data_t), target :: model type(flavor_t) :: flv type(pdg_array_t) :: pdg_in type(beam_data_t), target :: beam_data class(sf_data_t), allocatable, target :: data_strfun type(sf_config_t), dimension(:), allocatable, target :: sf_config type(sf_chain_t), target :: sf_chain type(sf_chain_instance_t), target :: sf_chain_instance type(sf_channel_t), dimension(2) :: sf_channel real(default), dimension(2) :: x_saved write (u, "(A)") "* Test output: sf_base_10" write (u, "(A)") "* Purpose: set up a structure-function chain" write (u, "(A)") "* and check mappings" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call model%init_test () call flv%init (25, model) pdg_in = 25 call reset_interaction_counter () call beam_data%init_sqrts (1000._default, [flv, flv]) allocate (sf_test_data_t :: data_strfun) select type (data_strfun) type is (sf_test_data_t) call data_strfun%init (model, pdg_in) end select write (u, "(A)") "* Set up chain with structure function pair & &and standard mapping" write (u, "(A)") allocate (sf_config (2)) call sf_config(1)%init ([1], data_strfun) call sf_config(2)%init ([2], data_strfun) call sf_chain%init (beam_data, sf_config) call sf_chain_instance%init (sf_chain, n_channel = 1) call sf_channel(1)%init (2) call sf_channel(1)%set_s_mapping ([1,2]) call sf_chain_instance%set_channel (1, sf_channel(1)) call sf_chain_instance%link_interactions () sf_chain_instance%status = SF_DONE_CONNECTIONS call sf_chain_instance%compute_kinematics (1, [0.8_default, 0.6_default]) call write_separator (u, 2) call sf_chain_instance%write (u) call write_separator (u, 2) write (u, "(A)") write (u, "(A)") "* Invert the kinematics calculation" write (u, "(A)") x_saved = sf_chain_instance%x call sf_chain_instance%init (sf_chain, n_channel = 1) call sf_channel(2)%init (2) call sf_channel(2)%set_s_mapping ([1, 2]) call sf_chain_instance%set_channel (1, sf_channel(2)) call sf_chain_instance%link_interactions () sf_chain_instance%status = SF_DONE_CONNECTIONS call sf_chain_instance%inverse_kinematics (x_saved, 1 - x_saved) call write_separator (u, 2) call sf_chain_instance%write (u) call write_separator (u, 2) call sf_chain_instance%final () call sf_chain%final () write (u, "(A)") write (u, "(A)") "* Cleanup" call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_base_10" end subroutine sf_base_10 @ %def sf_base_10 @ \subsubsection{Structure function chain evaluation} Here, we test the complete workflow for structure-function chains. First, we create the template chain, then initialize an instance. We set up links, mask, and evaluators. Finally, we set kinematics and evaluate the matrix elements and their products. <>= call test (sf_base_11, "sf_base_11", & "structure function chain evaluation", & u, results) <>= public :: sf_base_11 <>= subroutine sf_base_11 (u) integer, intent(in) :: u type(model_data_t), target :: model type(flavor_t) :: flv type(pdg_array_t) :: pdg_in type(beam_data_t), target :: beam_data class(sf_data_t), allocatable, target :: data_strfun class(sf_data_t), allocatable, target :: data_spectrum type(sf_config_t), dimension(:), allocatable, target :: sf_config type(sf_chain_t), target :: sf_chain type(sf_chain_instance_t), target :: sf_chain_instance type(sf_channel_t), dimension(2) :: sf_channel type(particle_set_t) :: pset type(interaction_t), pointer :: int logical :: ok write (u, "(A)") "* Test output: sf_base_11" write (u, "(A)") "* Purpose: set up a structure-function chain" write (u, "(A)") "* create an instance and evaluate" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call model%init_test () call flv%init (25, model) pdg_in = 25 call reset_interaction_counter () call beam_data%init_sqrts (1000._default, [flv, flv]) allocate (sf_test_data_t :: data_strfun) select type (data_strfun) type is (sf_test_data_t) call data_strfun%init (model, pdg_in) end select allocate (sf_test_spectrum_data_t :: data_spectrum) select type (data_spectrum) type is (sf_test_spectrum_data_t) call data_spectrum%init (model, pdg_in, with_radiation=.true.) end select write (u, "(A)") "* Set up chain with beams only" write (u, "(A)") call sf_chain%init (beam_data) call sf_chain_instance%init (sf_chain, n_channel = 1) call sf_chain_instance%link_interactions () call sf_chain_instance%exchange_mask () call sf_chain_instance%init_evaluators () call sf_chain_instance%compute_kinematics (1, [real(default) ::]) call sf_chain_instance%evaluate (scale=0._default) call write_separator (u, 2) call sf_chain_instance%write (u) call write_separator (u, 2) int => sf_chain_instance%get_out_int_ptr () call pset%init (ok, int, int, FM_IGNORE_HELICITY, & [0._default, 0._default], .false., .true.) call sf_chain_instance%final () 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 chain:" write (u, "(A)") call sf_chain_instance%init (sf_chain, n_channel = 1) call sf_chain_instance%link_interactions () call sf_chain_instance%exchange_mask () call sf_chain_instance%init_evaluators () int => sf_chain_instance%get_out_int_ptr () call pset%fill_interaction (int, 2, check_match=.false.) call sf_chain_instance%recover_kinematics (1) call sf_chain_instance%evaluate (scale=0._default) call write_separator (u, 2) call sf_chain_instance%write (u) call write_separator (u, 2) call pset%final () call sf_chain_instance%final () call sf_chain%final () write (u, "(A)") write (u, "(A)") write (u, "(A)") write (u, "(A)") "* Set up chain with structure function" write (u, "(A)") allocate (sf_config (1)) call sf_config(1)%init ([1], data_strfun) call sf_chain%init (beam_data, sf_config) call sf_chain_instance%init (sf_chain, n_channel = 1) call sf_channel(1)%init (1) call sf_channel(1)%activate_mapping ([1]) call sf_chain_instance%set_channel (1, sf_channel(1)) call sf_chain_instance%link_interactions () call sf_chain_instance%exchange_mask () call sf_chain_instance%init_evaluators () call sf_chain_instance%compute_kinematics (1, [0.8_default]) call sf_chain_instance%evaluate (scale=0._default) call write_separator (u, 2) call sf_chain_instance%write (u) call write_separator (u, 2) int => sf_chain_instance%get_out_int_ptr () call pset%init (ok, int, int, FM_IGNORE_HELICITY, & [0._default, 0._default], .false., .true.) call sf_chain_instance%final () 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 chain:" write (u, "(A)") call sf_chain_instance%init (sf_chain, n_channel = 1) call sf_channel(1)%init (1) call sf_channel(1)%activate_mapping ([1]) call sf_chain_instance%set_channel (1, sf_channel(1)) call sf_chain_instance%link_interactions () call sf_chain_instance%exchange_mask () call sf_chain_instance%init_evaluators () int => sf_chain_instance%get_out_int_ptr () call pset%fill_interaction (int, 2, check_match=.false.) call sf_chain_instance%recover_kinematics (1) call sf_chain_instance%evaluate (scale=0._default) call write_separator (u, 2) call sf_chain_instance%write (u) call write_separator (u, 2) call pset%final () call sf_chain_instance%final () call sf_chain%final () write (u, "(A)") write (u, "(A)") write (u, "(A)") write (u, "(A)") "* Set up chain with spectrum and structure function" write (u, "(A)") deallocate (sf_config) allocate (sf_config (2)) call sf_config(1)%init ([1,2], data_spectrum) call sf_config(2)%init ([2], data_strfun) call sf_chain%init (beam_data, sf_config) call sf_chain_instance%init (sf_chain, n_channel = 1) call sf_channel(2)%init (2) call sf_channel(2)%activate_mapping ([2]) call sf_chain_instance%set_channel (1, sf_channel(2)) call sf_chain_instance%link_interactions () call sf_chain_instance%exchange_mask () call sf_chain_instance%init_evaluators () call sf_chain_instance%compute_kinematics & (1, [0.5_default, 0.6_default, 0.8_default]) call sf_chain_instance%evaluate (scale=0._default) call write_separator (u, 2) call sf_chain_instance%write (u) call write_separator (u, 2) int => sf_chain_instance%get_out_int_ptr () call pset%init (ok, int, int, FM_IGNORE_HELICITY, & [0._default, 0._default], .false., .true.) call sf_chain_instance%final () 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 chain:" write (u, "(A)") call sf_chain_instance%init (sf_chain, n_channel = 1) call sf_channel(2)%init (2) call sf_channel(2)%activate_mapping ([2]) call sf_chain_instance%set_channel (1, sf_channel(2)) call sf_chain_instance%link_interactions () call sf_chain_instance%exchange_mask () call sf_chain_instance%init_evaluators () int => sf_chain_instance%get_out_int_ptr () call pset%fill_interaction (int, 2, check_match=.false.) call sf_chain_instance%recover_kinematics (1) call sf_chain_instance%evaluate (scale=0._default) call write_separator (u, 2) call sf_chain_instance%write (u) call write_separator (u, 2) call pset%final () call sf_chain_instance%final () call sf_chain%final () write (u, "(A)") write (u, "(A)") "* Cleanup" call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_base_11" end subroutine sf_base_11 @ %def sf_base_11 @ \subsubsection{Multichannel case} We set up a structure-function chain as before, but with three different parameterizations. The first instance is without mappings, the second one with single-particle mappings, and the third one with two-particle mappings. <>= call test (sf_base_12, "sf_base_12", & "multi-channel structure function chain", & u, results) <>= public :: sf_base_12 <>= subroutine sf_base_12 (u) integer, intent(in) :: u type(model_data_t), target :: model type(flavor_t) :: flv type(pdg_array_t) :: pdg_in type(beam_data_t), target :: beam_data class(sf_data_t), allocatable, target :: data type(sf_config_t), dimension(:), allocatable, target :: sf_config type(sf_chain_t), target :: sf_chain type(sf_chain_instance_t), target :: sf_chain_instance real(default), dimension(2) :: x_saved real(default), dimension(2,3) :: p_saved type(sf_channel_t), dimension(:), allocatable :: sf_channel write (u, "(A)") "* Test output: sf_base_12" write (u, "(A)") "* Purpose: set up and evaluate a multi-channel & &structure-function chain" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call model%init_test () call flv%init (25, model) pdg_in = 25 call reset_interaction_counter () call beam_data%init_sqrts (1000._default, [flv, flv]) allocate (sf_test_data_t :: data) select type (data) type is (sf_test_data_t) call data%init (model, pdg_in) end select write (u, "(A)") "* Set up chain with structure function pair & &and three different mappings" write (u, "(A)") allocate (sf_config (2)) call sf_config(1)%init ([1], data) call sf_config(2)%init ([2], data) call sf_chain%init (beam_data, sf_config) call sf_chain_instance%init (sf_chain, n_channel = 3) call allocate_sf_channels (sf_channel, n_channel = 3, n_strfun = 2) ! channel 1: no mapping call sf_chain_instance%set_channel (1, sf_channel(1)) ! channel 2: single-particle mappings call sf_channel(2)%activate_mapping ([1,2]) ! call sf_chain_instance%activate_mapping (2, [1,2]) call sf_chain_instance%set_channel (2, sf_channel(2)) ! channel 3: two-particle mapping call sf_channel(3)%set_s_mapping ([1,2]) ! call sf_chain_instance%set_s_mapping (3, [1, 2]) call sf_chain_instance%set_channel (3, sf_channel(3)) call sf_chain_instance%link_interactions () call sf_chain_instance%exchange_mask () call sf_chain_instance%init_evaluators () write (u, "(A)") "* Compute kinematics in channel 1 and evaluate" write (u, "(A)") call sf_chain_instance%compute_kinematics (1, [0.8_default, 0.6_default]) call sf_chain_instance%evaluate (scale=0._default) call write_separator (u, 2) call sf_chain_instance%write (u) call write_separator (u, 2) write (u, "(A)") write (u, "(A)") "* Invert the kinematics calculation" write (u, "(A)") x_saved = sf_chain_instance%x call sf_chain_instance%inverse_kinematics (x_saved, 1 - x_saved) call sf_chain_instance%evaluate (scale=0._default) call write_separator (u, 2) call sf_chain_instance%write (u) call write_separator (u, 2) write (u, "(A)") write (u, "(A)") "* Compute kinematics in channel 2 and evaluate" write (u, "(A)") p_saved = sf_chain_instance%p call sf_chain_instance%compute_kinematics (2, p_saved(:,2)) call sf_chain_instance%evaluate (scale=0._default) call write_separator (u, 2) call sf_chain_instance%write (u) call write_separator (u, 2) write (u, "(A)") write (u, "(A)") "* Compute kinematics in channel 3 and evaluate" write (u, "(A)") call sf_chain_instance%compute_kinematics (3, p_saved(:,3)) call sf_chain_instance%evaluate (scale=0._default) call write_separator (u, 2) call sf_chain_instance%write (u) call write_separator (u, 2) write (u, "(A)") write (u, "(A)") "* Cleanup" call sf_chain_instance%final () call sf_chain%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_base_12" end subroutine sf_base_12 @ %def sf_base_12 @ \subsubsection{Generated spectrum} Construct and evaluate a structure function object for a pair spectrum which is evaluated as a beam-event generator. <>= call test (sf_base_13, "sf_base_13", & "pair spectrum generator", & u, results) <>= public :: sf_base_13 <>= subroutine sf_base_13 (u) integer, intent(in) :: u type(model_data_t), target :: model type(flavor_t) :: flv type(pdg_array_t) :: pdg_in class(sf_data_t), allocatable, target :: data class(sf_int_t), allocatable :: sf_int type(vector4_t), dimension(2) :: k type(vector4_t), dimension(2) :: q real(default) :: E real(default), dimension(:), allocatable :: r, rb, x, xb real(default) :: f, x_free write (u, "(A)") "* Test output: sf_base_13" write (u, "(A)") "* Purpose: initialize and fill & &a pair generator object" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call model%init_test () call flv%init (25, model) pdg_in = 25 call reset_interaction_counter () allocate (sf_test_generator_data_t :: data) select type (data) type is (sf_test_generator_data_t) call data%init (model, pdg_in) end select write (u, "(A)") "* Initialize generator object" write (u, "(A)") call data%allocate_sf_int (sf_int) call sf_int%init (data) allocate (r (data%get_n_par ())) allocate (rb(size (r))) allocate (x (size (r))) allocate (xb(size (r))) write (u, "(A)") "* Generate free r values" write (u, "(A)") x_free = 1 call sf_int%generate_free (r, rb, x_free) write (u, "(A)") "* Initialize incoming momenta with sqrts=1000" E = 500 k(1) = vector4_moving (E, sqrt (E**2 - flv%get_mass ()**2), 3) k(2) = vector4_moving (E, sqrt (E**2 - flv%get_mass ()**2), 3) call sf_int%seed_kinematics (k) write (u, "(A)") write (u, "(A)") "* Complete kinematics" write (u, "(A)") call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%write (u) write (u, "(A)") write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A,9(1x,F10.7))") "xf=", x_free write (u, "(A)") write (u, "(A)") "* Recover x from momenta" write (u, "(A)") q = sf_int%get_momenta (outgoing=.true.) call sf_int%final () deallocate (sf_int) call reset_interaction_counter () call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%seed_kinematics (k) call sf_int%set_momenta (q, outgoing=.true.) x_free = 1 call sf_int%recover_x (x, xb, x_free) write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "xf=", x_free write (u, "(A)") write (u, "(A)") "* Compute inverse kinematics & &and evaluate" write (u, "(A)") call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%apply (scale=0._default) call sf_int%write (u) write (u, "(A)") write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Cleanup" call sf_int%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_base_13" end subroutine sf_base_13 @ %def sf_base_13 @ \subsubsection{Structure function chain evaluation} Here, we test the complete workflow for a structure-function chain with generator. First, we create the template chain, then initialize an instance. We set up links, mask, and evaluators. Finally, we set kinematics and evaluate the matrix elements and their products. <>= call test (sf_base_14, "sf_base_14", & "structure function generator evaluation", & u, results) <>= public :: sf_base_14 <>= subroutine sf_base_14 (u) integer, intent(in) :: u type(model_data_t), target :: model type(flavor_t) :: flv type(pdg_array_t) :: pdg_in type(beam_data_t), target :: beam_data class(sf_data_t), allocatable, target :: data_strfun class(sf_data_t), allocatable, target :: data_generator type(sf_config_t), dimension(:), allocatable, target :: sf_config real(default), dimension(:), allocatable :: p_in type(sf_chain_t), target :: sf_chain type(sf_chain_instance_t), target :: sf_chain_instance write (u, "(A)") "* Test output: sf_base_14" write (u, "(A)") "* Purpose: set up a structure-function chain" write (u, "(A)") "* create an instance and evaluate" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call model%init_test () call flv%init (25, model) pdg_in = 25 call reset_interaction_counter () call beam_data%init_sqrts (1000._default, [flv, flv]) allocate (sf_test_data_t :: data_strfun) select type (data_strfun) type is (sf_test_data_t) call data_strfun%init (model, pdg_in) end select allocate (sf_test_generator_data_t :: data_generator) select type (data_generator) type is (sf_test_generator_data_t) call data_generator%init (model, pdg_in) end select write (u, "(A)") "* Set up chain with generator and structure function" write (u, "(A)") allocate (sf_config (2)) call sf_config(1)%init ([1,2], data_generator) call sf_config(2)%init ([2], data_strfun) call sf_chain%init (beam_data, sf_config) call sf_chain_instance%init (sf_chain, n_channel = 1) call sf_chain_instance%link_interactions () call sf_chain_instance%exchange_mask () call sf_chain_instance%init_evaluators () write (u, "(A)") "* Inject integration parameter" write (u, "(A)") allocate (p_in (sf_chain%get_n_bound ()), source = 0.9_default) write (u, "(A,9(1x,F10.7))") "p_in =", p_in write (u, "(A)") write (u, "(A)") "* Evaluate" write (u, "(A)") call sf_chain_instance%compute_kinematics (1, p_in) call sf_chain_instance%evaluate (scale=0._default) call sf_chain_instance%write (u) write (u, "(A)") write (u, "(A)") "* Extract integration parameter" write (u, "(A)") call sf_chain_instance%get_mcpar (1, p_in) write (u, "(A,9(1x,F10.7))") "p_in =", p_in call sf_chain_instance%final () call sf_chain%final () write (u, "(A)") write (u, "(A)") "* Cleanup" call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_base_14" end subroutine sf_base_14 @ %def sf_base_14 @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Photon radiation: ISR} <<[[sf_isr.f90]]>>= <> module sf_isr <> <> use io_units use constants, only: pi use format_defs, only: FMT_15, FMT_19 use numeric_utils use diagnostics use physics_defs, only: PHOTON use lorentz use sm_physics, only: Li2 use pdg_arrays use model_data use flavors use colors use quantum_numbers use polarizations use sf_aux use sf_mappings use sf_base use electron_pdfs <> <> <> <> contains <> end module sf_isr @ %def sf_isr @ \subsection{Physics} The ISR structure function is in the most crude approximation (LLA without $\alpha$ corrections, i.e. $\epsilon^0$) \begin{equation} f_0(x) = \epsilon (1-x)^{-1+\epsilon} \qquad\text{with}\qquad \epsilon = \frac{\alpha}{\pi}q_e^2\ln\frac{s}{m^2}, \end{equation} where $m$ is the mass of the incoming (and outgoing) particle, which is initially assumed on-shell. In $f_0(x)$, there is an integrable singularity at $x=1$ which does not spoil the integration, but would lead to an unbounded $f_{\rm max}$. Therefore, we map this singularity like \begin{equation}\label{ISR-mapping} x = 1 - (1-x')^{1/\epsilon} \end{equation} such that \begin{equation} \int dx\,f_0(x) = \int dx' \end{equation} For the detailed form of the QED ISR structure function cf. Chap.~\ref{chap:qed_pdf}. \subsection{Implementation} In the concrete implementation, the zeroth order mapping (\ref{ISR-mapping}) is implemented, and the Jacobian is equal to $f_i(x)/f_0(x)$. This can be written as \begin{align} \frac{f_0(x)}{f_0(x)} &= 1 \\ \frac{f_1(x)}{f_0(x)} &= 1 + \frac34\epsilon - \frac{1-x^2}{2(1-x')} \\ \begin{split}\label{ISR-f2} \frac{f_2(x)}{f_0(x)} &= 1 + \frac34\epsilon + \frac{27 - 8\pi^2}{96}\epsilon^2 - \frac{1-x^2}{2(1-x')} \\ &\quad - \frac{(1+3x^2)\ln x + (1-x)\left(4(1+x)\ln(1-x) + 5 + x\right)}{8(1-x')}\epsilon \end{split} \end{align} %' For $x=1$ (i.e., numerically indistinguishable from $1$), this reduces to \begin{align} \frac{f_0(x)}{f_0(x)} &= 1 \\ \frac{f_1(x)}{f_0(x)} &= 1 + \frac34\epsilon \\ \frac{f_2(x)}{f_0(x)} &= 1 + \frac34\epsilon + \frac{27 - 8\pi^2}{96}\epsilon^2 \end{align} The last line in (\ref{ISR-f2}) is zero for \begin{equation} x_{\rm min} = 0.00714053329734592839549879772019 \end{equation} (Mathematica result), independent of $\epsilon$. For $x$ values less than this we ignore this correction because of the logarithmic singularity which should in principle be resummed. \subsection{The ISR data block} <>= public :: isr_data_t <>= type, extends (sf_data_t) :: isr_data_t private class(model_data_t), pointer :: model => null () type(flavor_t), dimension(:), allocatable :: flv_in type(qed_pdf_t) :: pdf real(default) :: alpha = 0 real(default) :: q_max = 0 real(default) :: real_mass = 0 real(default) :: mass = 0 real(default) :: eps = 0 real(default) :: log = 0 logical :: recoil = .false. logical :: keep_energy = .true. integer :: order = 3 integer :: error = NONE contains <> end type isr_data_t @ %def isr_data_t @ Error codes <>= integer, parameter :: NONE = 0 integer, parameter :: ZERO_MASS = 1 integer, parameter :: Q_MAX_TOO_SMALL = 2 integer, parameter :: EPS_TOO_LARGE = 3 integer, parameter :: INVALID_ORDER = 4 integer, parameter :: CHARGE_MIX = 5 integer, parameter :: CHARGE_ZERO = 6 integer, parameter :: MASS_MIX = 7 @ Generate flavor-dependent ISR data: <>= procedure :: init => isr_data_init <>= subroutine isr_data_init (data, model, pdg_in, alpha, q_max, & mass, order, recoil, keep_energy) class(isr_data_t), intent(out) :: data class(model_data_t), intent(in), target :: model type(pdg_array_t), intent(in) :: pdg_in real(default), intent(in) :: alpha real(default), intent(in) :: q_max real(default), intent(in), optional :: mass integer, intent(in), optional :: order logical, intent(in), optional :: recoil logical, intent(in), optional :: keep_energy integer :: i, n_flv real(default) :: charge data%model => model n_flv = pdg_array_get_length (pdg_in) allocate (data%flv_in (n_flv)) do i = 1, n_flv call data%flv_in(i)%init (pdg_array_get (pdg_in, i), model) end do data%alpha = alpha data%q_max = q_max if (present (order)) then call data%set_order (order) end if if (present (recoil)) then data%recoil = recoil end if if (present (keep_energy)) then data%keep_energy = keep_energy end if data%real_mass = data%flv_in(1)%get_mass () if (present (mass)) then if (mass > 0) then data%mass = mass else data%mass = data%real_mass if (any (data%flv_in%get_mass () /= data%mass)) then data%error = MASS_MIX; return end if end if else data%mass = data%real_mass if (any (data%flv_in%get_mass () /= data%mass)) then data%error = MASS_MIX; return end if end if if (vanishes (data%mass)) then data%error = ZERO_MASS; return else if (data%mass >= data%q_max) then data%error = Q_MAX_TOO_SMALL; return end if data%log = log (1 + (data%q_max / data%mass)**2) charge = data%flv_in(1)%get_charge () if (any (abs (data%flv_in%get_charge ()) /= abs (charge))) then data%error = CHARGE_MIX; return else if (charge == 0) then data%error = CHARGE_ZERO; return end if data%eps = data%alpha / pi * charge ** 2 & * (2 * log (data%q_max / data%mass) - 1) if (data%eps > 1) then data%error = EPS_TOO_LARGE; return end if call data%pdf%init & (data%mass, data%alpha, charge, data%q_max, data%order) end subroutine isr_data_init @ %def isr_data_init @ Explicitly set ISR order <>= procedure :: set_order => isr_data_set_order <>= elemental subroutine isr_data_set_order (data, order) class(isr_data_t), intent(inout) :: data integer, intent(in) :: order if (order < 0 .or. order > 3) then data%error = INVALID_ORDER else data%order = order end if end subroutine isr_data_set_order @ %def isr_data_set_order @ Handle error conditions. Should always be done after initialization, unless we are sure everything is ok. <>= procedure :: check => isr_data_check <>= subroutine isr_data_check (data) class(isr_data_t), intent(in) :: data select case (data%error) case (ZERO_MASS) call msg_fatal ("ISR: Particle mass is zero") case (Q_MAX_TOO_SMALL) call msg_fatal ("ISR: Particle mass exceeds Qmax") case (EPS_TOO_LARGE) call msg_fatal ("ISR: Expansion parameter too large, " // & "perturbative expansion breaks down") case (INVALID_ORDER) call msg_error ("ISR: LLA order invalid (valid values are 0,1,2,3)") case (MASS_MIX) call msg_fatal ("ISR: Incoming particle masses must be uniform") case (CHARGE_MIX) call msg_fatal ("ISR: Incoming particle charges must be uniform") case (CHARGE_ZERO) call msg_fatal ("ISR: Incoming particle must be charged") end select end subroutine isr_data_check @ %def isr_data_check @ Output <>= procedure :: write => isr_data_write <>= subroutine isr_data_write (data, unit, verbose) class(isr_data_t), intent(in) :: data integer, intent(in), optional :: unit logical, intent(in), optional :: verbose integer :: u, i u = given_output_unit (unit); if (u < 0) return write (u, "(1x,A)") "ISR data:" if (allocated (data%flv_in)) then write (u, "(3x,A)", advance="no") " flavor = " do i = 1, size (data%flv_in) if (i > 1) write (u, "(',',1x)", advance="no") call data%flv_in(i)%write (u) end do write (u, *) write (u, "(3x,A," // FMT_19 // ")") " alpha = ", data%alpha write (u, "(3x,A," // FMT_19 // ")") " q_max = ", data%q_max write (u, "(3x,A," // FMT_19 // ")") " mass = ", data%mass write (u, "(3x,A," // FMT_19 // ")") " eps = ", data%eps write (u, "(3x,A," // FMT_19 // ")") " log = ", data%log write (u, "(3x,A,I2)") " order = ", data%order write (u, "(3x,A,L2)") " recoil = ", data%recoil write (u, "(3x,A,L2)") " keep en. = ", data%keep_energy else write (u, "(3x,A)") "[undefined]" end if end subroutine isr_data_write @ %def isr_data_write @ For ISR, there is the option to generate transverse momentum is generated. Hence, there can be up to three parameters, $x$, and two angles. <>= procedure :: get_n_par => isr_data_get_n_par <>= function isr_data_get_n_par (data) result (n) class(isr_data_t), intent(in) :: data integer :: n if (data%recoil) then n = 3 else n = 1 end if end function isr_data_get_n_par @ %def isr_data_get_n_par @ Return the outgoing particles PDG codes. For ISR, these are identical to the incoming particles. <>= procedure :: get_pdg_out => isr_data_get_pdg_out <>= subroutine isr_data_get_pdg_out (data, pdg_out) class(isr_data_t), intent(in) :: data type(pdg_array_t), dimension(:), intent(inout) :: pdg_out pdg_out(1) = data%flv_in%get_pdg () end subroutine isr_data_get_pdg_out @ %def isr_data_get_pdg_out @ Return the [[eps]] value. We need it for an appropriate mapping of structure-function parameters. <>= procedure :: get_eps => isr_data_get_eps <>= function isr_data_get_eps (data) result (eps) class(isr_data_t), intent(in) :: data real(default) :: eps eps = data%eps end function isr_data_get_eps @ %def isr_data_get_eps @ Allocate the interaction record. <>= procedure :: allocate_sf_int => isr_data_allocate_sf_int <>= subroutine isr_data_allocate_sf_int (data, sf_int) class(isr_data_t), intent(in) :: data class(sf_int_t), intent(inout), allocatable :: sf_int allocate (isr_t :: sf_int) end subroutine isr_data_allocate_sf_int @ %def isr_data_allocate_sf_int @ \subsection{The ISR object} The [[isr_t]] data type is a $1\to 2$ interaction, i.e., we allow for single-photon emission only (but use the multi-photon resummed radiator function). The particles are ordered as (incoming, photon, outgoing). There is no need to handle several flavors (and data blocks) in parallel, since ISR is always applied immediately after beam collision. (ISR for partons is accounted for by the PDFs themselves.) Polarization is carried through, i.e., we retain the polarization of the incoming particle and treat the emitted photon as unpolarized. Color is trivially carried through. This implies that particles 1 and 3 should be locked together. For ISR we don't need the q variable. <>= public :: isr_t <>= type, extends (sf_int_t) :: isr_t private type(isr_data_t), pointer :: data => null () real(default) :: x = 0 real(default) :: xb= 0 contains <> end type isr_t @ %def isr_t @ Type string: has to be here, but there is no string variable on which ISR depends. Hence, a dummy routine. <>= procedure :: type_string => isr_type_string <>= function isr_type_string (object) result (string) class(isr_t), intent(in) :: object type(string_t) :: string if (associated (object%data)) then string = "ISR: e+ e- ISR spectrum" else string = "ISR: [undefined]" end if end function isr_type_string @ %def isr_type_string @ Output. Call the interaction routine after displaying the configuration. <>= procedure :: write => isr_write <>= subroutine isr_write (object, unit, testflag) class(isr_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u u = given_output_unit (unit) if (associated (object%data)) then call object%data%write (u) if (object%status >= SF_DONE_KINEMATICS) then write (u, "(1x,A)") "SF parameters:" write (u, "(3x,A," // FMT_15 // ")") "x =", object%x write (u, "(3x,A," // FMT_15 // ")") "xb=", object%xb end if call object%base_write (u, testflag) else write (u, "(1x,A)") "ISR data: [undefined]" end if end subroutine isr_write @ %def isr_write @ Explicitly set ISR order (for unit test). <>= procedure :: set_order => isr_set_order <>= subroutine isr_set_order (object, order) class(isr_t), intent(inout) :: object integer, intent(in) :: order call object%data%set_order (order) call object%data%pdf%set_order (order) end subroutine isr_set_order @ %def isr_set_order @ \subsection{Kinematics} Set kinematics. If [[map]] is unset, the $r$ and $x$ values coincide, and the Jacobian $f(r)$ were trivial. The ISR structure function allows for a straightforward mapping of the unit interval. So, to leading order, the structure function value is unity, but the $x$ value is transformed. Higher orders affect the function value. The structure function implementation applies the above mapping to the input (random) number [[r]] to generate the momentum fraction [[x]] and the function value [[f]]. For numerical stability reasons, we also output [[xb]], which is $\bar x=1-x$. For the ISR structure function, the mapping Jacobian cancels the structure function (to order zero). We apply the cancellation explicitly, therefore both the Jacobian [[f]] and the zeroth-order value (see the [[apply]] method) are unity if mapping is turned on. If mapping is turned off, the Jacobian [[f]] includes the value of the (zeroth-order) structure function, and strongly peaked. <>= procedure :: complete_kinematics => isr_complete_kinematics <>= subroutine isr_complete_kinematics (sf_int, x, xb, f, r, rb, map) class(isr_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: x real(default), dimension(:), intent(out) :: xb real(default), intent(out) :: f real(default), dimension(:), intent(in) :: r real(default), dimension(:), intent(in) :: rb logical, intent(in) :: map real(default) :: eps eps = sf_int%data%eps if (map) then call map_power_1 (sf_int%xb, f, rb(1), eps) else sf_int%xb = rb(1) if (rb(1) > 0) then f = 1 else f = 0 end if end if sf_int%x = 1 - sf_int%xb x(1) = sf_int%x xb(1) = sf_int%xb if (size (x) == 3) then x(2:3) = r(2:3) xb(2:3) = rb(2:3) end if call sf_int%split_momentum (x, xb) select case (sf_int%status) case (SF_FAILED_KINEMATICS) sf_int%x = 0 sf_int%xb= 0 f = 0 end select end subroutine isr_complete_kinematics @ %def isr_complete_kinematics @ Overriding the default method: we compute the [[x]] array from the momentum configuration. In the specific case of ISR, we also set the internally stored $x$ and $\bar x$ values, so they can be used in the following routine. <>= procedure :: recover_x => sf_isr_recover_x <>= subroutine sf_isr_recover_x (sf_int, x, xb, x_free) class(isr_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: x real(default), dimension(:), intent(out) :: xb real(default), intent(inout), optional :: x_free call sf_int%base_recover_x (x, xb, x_free) sf_int%x = x(1) sf_int%xb = xb(1) end subroutine sf_isr_recover_x @ %def sf_isr_recover_x @ Compute inverse kinematics. Here, we start with the $x$ array and compute the ``input'' $r$ values and the Jacobian $f$. After this, we can set momenta by the same formula as for normal kinematics. For extracting $x$, we rely on the stored $\bar x$ value, since the $x$ value in the argument is likely imprecise. This means that either [[complete_kinematics]] or [[recover_x]] must be called first, for the current sampling point (but maybe another channel). <>= procedure :: inverse_kinematics => isr_inverse_kinematics <>= subroutine isr_inverse_kinematics (sf_int, x, xb, f, r, rb, map, set_momenta) class(isr_t), intent(inout) :: sf_int real(default), dimension(:), intent(in) :: x real(default), dimension(:), intent(in) :: xb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: r real(default), dimension(:), intent(out) :: rb logical, intent(in) :: map logical, intent(in), optional :: set_momenta real(default) :: eps logical :: set_mom set_mom = .false.; if (present (set_momenta)) set_mom = set_momenta eps = sf_int%data%eps if (map) then call map_power_inverse_1 (xb(1), f, rb(1), eps) else rb(1) = xb(1) if (rb(1) > 0) then f = 1 else f = 0 end if end if r(1) = 1 - rb(1) if (size(r) == 3) then r(2:3) = x(2:3) rb(2:3)= xb(2:3) end if if (set_mom) then call sf_int%split_momentum (x, xb) select case (sf_int%status) case (SF_FAILED_KINEMATICS) r = 0 rb= 0 f = 0 end select end if end subroutine isr_inverse_kinematics @ %def isr_inverse_kinematics @ <>= procedure :: init => isr_init <>= subroutine isr_init (sf_int, data) class(isr_t), intent(out) :: sf_int class(sf_data_t), intent(in), target :: data type(quantum_numbers_mask_t), dimension(3) :: mask integer, dimension(3) :: hel_lock type(polarization_t), target :: pol type(quantum_numbers_t), dimension(1) :: qn_fc type(flavor_t) :: flv_photon type(color_t) :: col_photon type(quantum_numbers_t) :: qn_hel, qn_photon, qn type(polarization_iterator_t) :: it_hel real(default) :: m2 integer :: i mask = quantum_numbers_mask (.false., .false., & mask_h = [.false., .true., .false.]) hel_lock = [3, 0, 1] select type (data) type is (isr_data_t) m2 = data%mass**2 call sf_int%base_init (mask, [m2], [0._default], [m2], & hel_lock = hel_lock) sf_int%data => data call flv_photon%init (PHOTON, data%model) call col_photon%init () call qn_photon%init (flv_photon, col_photon) call qn_photon%tag_radiated () do i = 1, size (data%flv_in) call pol%init_generic (data%flv_in(i)) call qn_fc(1)%init (& flv = data%flv_in(i), & col = color_from_flavor (data%flv_in(i), 1)) call it_hel%init (pol) do while (it_hel%is_valid ()) qn_hel = it_hel%get_quantum_numbers () qn = qn_hel .merge. qn_fc(1) call sf_int%add_state ([qn, qn_photon, qn]) call it_hel%advance () end do ! call pol%final () !!! Obsolete end do call sf_int%freeze () if (data%keep_energy) then sf_int%on_shell_mode = KEEP_ENERGY else sf_int%on_shell_mode = KEEP_MOMENTUM end if call sf_int%set_incoming ([1]) call sf_int%set_radiated ([2]) call sf_int%set_outgoing ([3]) sf_int%status = SF_INITIAL end select end subroutine isr_init @ %def isr_init @ \subsection{ISR application} For ISR, we could in principle compute kinematics and function value in a single step. In order to be able to reweight matrix elements including structure functions we split kinematics and structure function calculation. The structure function works on a single beam, assuming that the input momentum has been set. For the structure-function evaluation, we rely on the fact that the power mapping, which we apply in the kinematics method (if the [[map]] flag is set), has a Jacobian which is just the inverse lowest-order structure function. With mapping active, the two should cancel exactly. After splitting momenta, we set the outgoing momenta on-shell. We choose to conserve momentum, so energy conservation may be violated. <>= procedure :: apply => isr_apply <>= subroutine isr_apply (sf_int, scale, rescale, i_sub) class(isr_t), intent(inout) :: sf_int real(default), intent(in) :: scale class(sf_rescale_t), intent(in), optional :: rescale integer, intent(in), optional :: i_sub real(default) :: f, finv, x, xb, eps, rb real(default) :: log_x, log_xb, x_2 associate (data => sf_int%data) eps = sf_int%data%eps x = sf_int%x xb = sf_int%xb call map_power_inverse_1 (xb, finv, rb, eps) if (finv > 0) then f = 1 / finv else f = 0 end if call data%pdf%evolve_qed_pdf (x, xb, rb, f) end associate call sf_int%set_matrix_element (cmplx (f, kind=default)) sf_int%status = SF_EVALUATED end subroutine isr_apply @ %def isr_apply @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[sf_isr_ut.f90]]>>= <> module sf_isr_ut use unit_tests use sf_isr_uti <> <> contains <> end module sf_isr_ut @ %def sf_isr_ut @ <<[[sf_isr_uti.f90]]>>= <> module sf_isr_uti <> <> use io_units use format_defs, only: FMT_12 use physics_defs, only: ELECTRON use lorentz use pdg_arrays use flavors use interactions, only: reset_interaction_counter use interactions, only: interaction_pacify_momenta use model_data use sf_aux, only: KEEP_ENERGY use sf_mappings use sf_base use sf_isr <> <> contains <> end module sf_isr_uti @ %def sf_isr_ut @ API: driver for the unit tests below. <>= public :: sf_isr_test <>= subroutine sf_isr_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine sf_isr_test @ %def sf_isr_test @ \subsubsection{Test structure function data} Construct and display a test structure function data object. <>= call test (sf_isr_1, "sf_isr_1", & "structure function configuration", & u, results) <>= public :: sf_isr_1 <>= subroutine sf_isr_1 (u) integer, intent(in) :: u type(model_data_t), target :: model type(pdg_array_t) :: pdg_in type(pdg_array_t), dimension(1) :: pdg_out integer, dimension(:), allocatable :: pdg1 class(sf_data_t), allocatable :: data write (u, "(A)") "* Test output: sf_isr_1" write (u, "(A)") "* Purpose: initialize and display & &test structure function data" write (u, "(A)") write (u, "(A)") "* Create empty data object" write (u, "(A)") call model%init_qed_test () pdg_in = ELECTRON allocate (isr_data_t :: data) call data%write (u) write (u, "(A)") write (u, "(A)") "* Initialize" write (u, "(A)") select type (data) type is (isr_data_t) call data%init (model, pdg_in, 1./137._default, 10._default, & 0.000511_default, order = 3, recoil = .false.) end select call data%write (u) write (u, "(A)") write (u, "(1x,A)") "Outgoing particle codes:" call data%get_pdg_out (pdg_out) pdg1 = pdg_out(1) write (u, "(2x,99(1x,I0))") pdg1 call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_isr_1" end subroutine sf_isr_1 @ %def sf_isr_1 @ \subsubsection{Structure function without mapping} Direct ISR evaluation. This is the use case for a double-beam structure function. The parameter pair is mapped in the calling program. <>= call test (sf_isr_2, "sf_isr_2", & "no ISR mapping", & u, results) <>= public :: sf_isr_2 <>= subroutine sf_isr_2 (u) integer, intent(in) :: u type(model_data_t), target :: model type(pdg_array_t) :: pdg_in type(flavor_t) :: flv class(sf_data_t), allocatable, target :: data class(sf_int_t), allocatable :: sf_int type(vector4_t) :: k real(default) :: E real(default), dimension(:), allocatable :: r, rb, x, xb real(default) :: f, f_isr write (u, "(A)") "* Test output: sf_isr_2" write (u, "(A)") "* Purpose: initialize and fill & &test structure function object" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call model%init_qed_test () pdg_in = ELECTRON call flv%init (ELECTRON, model) call reset_interaction_counter () allocate (isr_data_t :: data) select type (data) type is (isr_data_t) call data%init (model, pdg_in, 1./137._default, 500._default, & 0.000511_default, order = 3, recoil = .false.) end select write (u, "(A)") "* Initialize structure-function object" write (u, "(A)") call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1]) write (u, "(A)") "* Initialize incoming momentum with E=500" write (u, "(A)") E = 500 k = vector4_moving (E, sqrt (E**2 - flv%get_mass ()**2), 3) call pacify (k, 1e-10_default) call vector4_write (k, u) call sf_int%seed_kinematics ([k]) write (u, "(A)") write (u, "(A)") "* Set kinematics for r=0.9, no ISR mapping, & &collinear" write (u, "(A)") allocate (r (data%get_n_par ())) allocate (rb(size (r))) allocate (x (size (r))) allocate (xb(size (r))) r = 0.9_default rb = 1 - r write (u, "(A,9(1x," // FMT_12 // "))") "r =", r write (u, "(A,9(1x," // FMT_12 // "))") "rb=", rb call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) write (u, "(A)") write (u, "(A,9(1x," // FMT_12 // "))") "x =", x write (u, "(A,9(1x," // FMT_12 // "))") "xb=", xb write (u, "(A,9(1x," // FMT_12 // "))") "f =", f write (u, "(A)") write (u, "(A)") "* Invert kinematics" write (u, "(A)") call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.false.) write (u, "(A,9(1x," // FMT_12 // "))") "r =", r write (u, "(A,9(1x," // FMT_12 // "))") "rb=", rb write (u, "(A,9(1x," // FMT_12 // "))") "f =", f write (u, "(A)") write (u, "(A)") "* Evaluate ISR structure function" write (u, "(A)") call sf_int%apply (scale = 100._default) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Structure-function value, default order" write (u, "(A)") f_isr = sf_int%get_matrix_element (1) write (u, "(A,9(1x," // FMT_12 // "))") "f_isr =", f_isr write (u, "(A,9(1x," // FMT_12 // "))") "f_isr * f_map =", f_isr * f write (u, "(A)") write (u, "(A)") "* Re-evaluate structure function, leading order" write (u, "(A)") select type (sf_int) type is (isr_t) call sf_int%set_order (0) end select call sf_int%apply (scale = 100._default) f_isr = sf_int%get_matrix_element (1) write (u, "(A,9(1x," // FMT_12 // "))") "f_isr =", f_isr write (u, "(A,9(1x," // FMT_12 // "))") "f_isr * f_map =", f_isr * f write (u, "(A)") write (u, "(A)") "* Cleanup" call sf_int%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_isr_2" end subroutine sf_isr_2 @ %def sf_isr_2 @ \subsubsection{Structure function with mapping} Apply the optimal ISR mapping. This is the use case for a single-beam structure function. <>= call test (sf_isr_3, "sf_isr_3", & "ISR mapping", & u, results) <>= public :: sf_isr_3 <>= subroutine sf_isr_3 (u) integer, intent(in) :: u type(model_data_t), target :: model type(flavor_t) :: flv type(pdg_array_t) :: pdg_in class(sf_data_t), allocatable, target :: data class(sf_int_t), allocatable :: sf_int type(vector4_t) :: k real(default) :: E real(default), dimension(:), allocatable :: r, rb, x, xb real(default) :: f, f_isr write (u, "(A)") "* Test output: sf_isr_3" write (u, "(A)") "* Purpose: initialize and fill & &test structure function object" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call model%init_qed_test () call flv%init (ELECTRON, model) pdg_in = ELECTRON call reset_interaction_counter () allocate (isr_data_t :: data) select type (data) type is (isr_data_t) call data%init (model, pdg_in, 1./137._default, 500._default, & 0.000511_default, order = 3, recoil = .false.) end select write (u, "(A)") "* Initialize structure-function object" write (u, "(A)") call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1]) write (u, "(A)") "* Initialize incoming momentum with E=500" write (u, "(A)") E = 500 k = vector4_moving (E, sqrt (E**2 - flv%get_mass ()**2), 3) call pacify (k, 1e-10_default) call vector4_write (k, u) call sf_int%seed_kinematics ([k]) write (u, "(A)") write (u, "(A)") "* Set kinematics for r=0.7, with ISR mapping, & &collinear" write (u, "(A)") allocate (r (data%get_n_par ())) allocate (rb(size (r))) allocate (x (size (r))) allocate (xb(size (r))) r = 0.7_default rb = 1 - r write (u, "(A,9(1x," // FMT_12 // "))") "r =", r write (u, "(A,9(1x," // FMT_12 // "))") "rb=", rb call sf_int%complete_kinematics (x, xb, f, r, rb, map=.true.) write (u, "(A)") write (u, "(A,9(1x," // FMT_12 // "))") "x =", x write (u, "(A,9(1x," // FMT_12 // "))") "xb=", xb write (u, "(A,9(1x," // FMT_12 // "))") "f =", f write (u, "(A)") write (u, "(A)") "* Invert kinematics" write (u, "(A)") call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.true.) write (u, "(A,9(1x," // FMT_12 // "))") "r =", r write (u, "(A,9(1x," // FMT_12 // "))") "rb=", rb write (u, "(A,9(1x," // FMT_12 // "))") "f =", f write (u, "(A)") write (u, "(A)") "* Evaluate ISR structure function" write (u, "(A)") call sf_int%apply (scale = 100._default) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Structure-function value, default order" write (u, "(A)") f_isr = sf_int%get_matrix_element (1) write (u, "(A,9(1x," // FMT_12 // "))") "f_isr =", f_isr write (u, "(A,9(1x," // FMT_12 // "))") "f_isr * f_map =", f_isr * f write (u, "(A)") write (u, "(A)") "* Re-evaluate structure function, leading order" write (u, "(A)") select type (sf_int) type is (isr_t) call sf_int%set_order (0) end select call sf_int%apply (scale = 100._default) f_isr = sf_int%get_matrix_element (1) write (u, "(A,9(1x," // FMT_12 // "))") "f_isr =", f_isr write (u, "(A,9(1x," // FMT_12 // "))") "f_isr * f_map =", f_isr * f write (u, "(A)") write (u, "(A)") "* Cleanup" call sf_int%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_isr_3" end subroutine sf_isr_3 @ %def sf_isr_3 @ \subsubsection{Non-collinear ISR splitting} Construct and display a structure function object based on the ISR structure function. We blank out numerical fluctuations for 32bit. <>= call test (sf_isr_4, "sf_isr_4", & "ISR non-collinear", & u, results) <>= public :: sf_isr_4 <>= subroutine sf_isr_4 (u) integer, intent(in) :: u type(model_data_t), target :: model type(flavor_t) :: flv type(pdg_array_t) :: pdg_in class(sf_data_t), allocatable, target :: data class(sf_int_t), allocatable :: sf_int type(vector4_t) :: k type(vector4_t), dimension(2) :: q real(default) :: E real(default), dimension(:), allocatable :: r, rb, x, xb real(default) :: f, f_isr character(len=80) :: buffer integer :: u_scratch, iostat write (u, "(A)") "* Test output: sf_isr_4" write (u, "(A)") "* Purpose: initialize and fill & &test structure function object" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call model%init_qed_test () call flv%init (ELECTRON, model) pdg_in = ELECTRON call reset_interaction_counter () write (u, "(A)") write (u, "(A)") "* Initialize structure-function object" write (u, "(A)") allocate (isr_data_t :: data) select type (data) type is (isr_data_t) call data%init (model, pdg_in, 1./137._default, 500._default, & 0.000511_default, order = 3, recoil = .true.) end select call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1]) write (u, "(A)") write (u, "(A)") "* Initialize incoming momentum with E=500" write (u, "(A)") E = 500 k = vector4_moving (E, sqrt (E**2 - flv%get_mass ()**2), 3) call pacify (k, 1e-10_default) call vector4_write (k, u) call sf_int%seed_kinematics ([k]) write (u, "(A)") write (u, "(A)") "* Set kinematics for x=0.5/0.5/0.25, with ISR mapping, " write (u, "(A)") " non-coll., keeping energy" write (u, "(A)") allocate (r (data%get_n_par ())) allocate (rb(size (r))) allocate (x (size (r))) allocate (xb(size (r))) r = [0.5_default, 0.5_default, 0.25_default] rb = 1 - r sf_int%on_shell_mode = KEEP_ENERGY call sf_int%complete_kinematics (x, xb, f, r, rb, map=.true.) call interaction_pacify_momenta (sf_int%interaction_t, 1e-10_default) write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Recover x and r from momenta" write (u, "(A)") q = sf_int%get_momenta (outgoing=.true.) call sf_int%final () deallocate (sf_int) call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1]) call sf_int%seed_kinematics ([k]) call sf_int%set_momenta (q, outgoing=.true.) call sf_int%recover_x (x, xb) call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.true.) write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A)") write (u, "(A)") "* Evaluate ISR structure function" write (u, "(A)") call sf_int%complete_kinematics (x, xb, f, r, rb, map=.true.) call interaction_pacify_momenta (sf_int%interaction_t, 1e-10_default) call sf_int%apply (scale = 10._default) u_scratch = free_unit () open (u_scratch, status="scratch", action = "readwrite") call sf_int%write (u_scratch, testflag = .true.) rewind (u_scratch) do read (u_scratch, "(A)", iostat=iostat) buffer if (iostat /= 0) exit if (buffer(1:25) == " P = 0.000000E+00 9.57") then buffer = replace (buffer, 26, "XXXX") end if if (buffer(1:25) == " P = 0.000000E+00 -9.57") then buffer = replace (buffer, 26, "XXXX") end if write (u, "(A)") buffer end do close (u_scratch) write (u, "(A)") write (u, "(A)") "* Structure-function value" write (u, "(A)") f_isr = sf_int%get_matrix_element (1) write (u, "(A,9(1x," // FMT_12 // "))") "f_isr =", f_isr write (u, "(A,9(1x," // FMT_12 // "))") "f_isr * f_map =", f_isr * f write (u, "(A)") write (u, "(A)") "* Cleanup" call sf_int%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_isr_4" end subroutine sf_isr_4 @ %def sf_isr_4 @ \subsubsection{Structure function pair with mapping} Apply the ISR mapping for a ISR pair. structure function. <>= call test (sf_isr_5, "sf_isr_5", & "ISR pair mapping", & u, results) <>= public :: sf_isr_5 <>= subroutine sf_isr_5 (u) integer, intent(in) :: u type(model_data_t), target :: model type(flavor_t) :: flv type(pdg_array_t) :: pdg_in class(sf_data_t), allocatable, target :: data class(sf_mapping_t), allocatable :: mapping class(sf_int_t), dimension(:), allocatable :: sf_int type(vector4_t), dimension(2) :: k real(default) :: E, f_map real(default), dimension(:), allocatable :: p, pb, r, rb, x, xb real(default), dimension(2) :: f, f_isr integer :: i write (u, "(A)") "* Test output: sf_isr_5" write (u, "(A)") "* Purpose: initialize and fill & &test structure function object" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call model%init_qed_test () call flv%init (ELECTRON, model) pdg_in = ELECTRON call reset_interaction_counter () allocate (isr_data_t :: data) select type (data) type is (isr_data_t) call data%init (model, pdg_in, 1./137._default, 500._default, & 0.000511_default, order = 3, recoil = .false.) end select allocate (sf_ip_mapping_t :: mapping) select type (mapping) type is (sf_ip_mapping_t) select type (data) type is (isr_data_t) call mapping%init (eps = data%get_eps ()) end select call mapping%set_index (1, 1) call mapping%set_index (2, 2) end select call mapping%write (u) write (u, "(A)") write (u, "(A)") "* Initialize structure-function object" write (u, "(A)") allocate (isr_t :: sf_int (2)) do i = 1, 2 call sf_int(i)%init (data) call sf_int(i)%set_beam_index ([i]) end do write (u, "(A)") "* Initialize incoming momenta with E=500" write (u, "(A)") E = 500 k(1) = vector4_moving (E, sqrt (E**2 - flv%get_mass ()**2), 3) k(2) = vector4_moving (E, - sqrt (E**2 - flv%get_mass ()**2), 3) call pacify (k, 1e-10_default) do i = 1, 2 call vector4_write (k(i), u) call sf_int(i)%seed_kinematics (k(i:i)) end do write (u, "(A)") write (u, "(A)") "* Set kinematics for p=[0.7,0.4], collinear" write (u, "(A)") allocate (p (2 * data%get_n_par ())) allocate (pb(size (p))) allocate (r (size (p))) allocate (rb(size (p))) allocate (x (size (p))) allocate (xb(size (p))) p = [0.7_default, 0.4_default] pb= 1 - p call mapping%compute (r, rb, f_map, p, pb) write (u, "(A,9(1x," // FMT_12 // "))") "p =", p write (u, "(A,9(1x," // FMT_12 // "))") "pb=", pb write (u, "(A,9(1x," // FMT_12 // "))") "r =", r write (u, "(A,9(1x," // FMT_12 // "))") "rb=", rb write (u, "(A,9(1x," // FMT_12 // "))") "fm=", f_map do i = 1, 2 call sf_int(i)%complete_kinematics (x(i:i), xb(i:i), f(i), r(i:i), rb(i:i), & map=.false.) end do write (u, "(A)") write (u, "(A,9(1x," // FMT_12 // "))") "x =", x write (u, "(A,9(1x," // FMT_12 // "))") "xb=", xb write (u, "(A,9(1x," // FMT_12 // "))") "f =", f write (u, "(A)") write (u, "(A)") "* Invert kinematics" write (u, "(A)") do i = 1, 2 call sf_int(i)%inverse_kinematics (x(i:i), xb(i:i), f(i), r(i:i), rb(i:i), & map=.false.) end do call mapping%inverse (r, rb, f_map, p, pb) write (u, "(A,9(1x," // FMT_12 // "))") "p =", p write (u, "(A,9(1x," // FMT_12 // "))") "pb=", pb write (u, "(A,9(1x," // FMT_12 // "))") "r =", r write (u, "(A,9(1x," // FMT_12 // "))") "rb=", rb write (u, "(A,9(1x," // FMT_12 // "))") "fm=", f_map write (u, "(A)") write (u, "(A)") "* Evaluate ISR structure function" call sf_int(1)%apply (scale = 100._default) call sf_int(2)%apply (scale = 100._default) write (u, "(A)") write (u, "(A)") "* Structure function #1" write (u, "(A)") call sf_int(1)%write (u, testflag = .true.) write (u, "(A)") write (u, "(A)") "* Structure function #2" write (u, "(A)") call sf_int(2)%write (u, testflag = .true.) write (u, "(A)") write (u, "(A)") "* Structure-function value, default order" write (u, "(A)") do i = 1, 2 f_isr(i) = sf_int(i)%get_matrix_element (1) end do write (u, "(A,9(1x," // FMT_12 // "))") "f_isr =", & product (f_isr) write (u, "(A,9(1x," // FMT_12 // "))") "f_isr * f_map =", & product (f_isr * f) * f_map write (u, "(A)") write (u, "(A)") "* Cleanup" do i = 1, 2 call sf_int(i)%final () end do call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_isr_5" end subroutine sf_isr_5 @ %def sf_isr_5 @ \clearpage %------------------------------------------------------------------------ \section{EPA} <<[[sf_epa.f90]]>>= <> module sf_epa <> <> use io_units use constants, only: pi use format_defs, only: FMT_17, FMT_19 use numeric_utils use diagnostics use physics_defs, only: PHOTON use lorentz use pdg_arrays use model_data use flavors use colors use quantum_numbers use state_matrices use polarizations use interactions use sf_aux use sf_base <> <> <> <> contains <> end module sf_epa @ %def sf_epa @ \subsection{Physics} The EPA structure function for a photon inside an (elementary) particle $p$ with energy $E$, mass $m$ and charge $q_p$ (e.g., electron) is given by ($\bar x \equiv 1-x$) There are several variants of the EPA, which are steered by the [[\$epa\_mode]] switch. The formula (6.17b) from the report by Budnev et al. is given by %% %\cite{Budnev:1974de} %% \bibitem{Budnev:1974de} %% V.~M.~Budnev, I.~F.~Ginzburg, G.~V.~Meledin and V.~G.~Serbo, %% %``The Two photon particle production mechanism. Physical problems. %% %Applications. Equivalent photon approximation,'' %% Phys.\ Rept.\ {\bf 15} (1974) 181. %% %%CITATION = PRPLC,15,181;%% \begin{multline} \label{EPA_617} f(x) = \frac{\alpha}{\pi}\,q_p^2\, \frac{1}{x}\, \biggl[\left(\bar x + \frac{x^2}{2}\right) \ln\frac{Q^2_{\rm max}}{Q^2_{\rm min}} \\ - \left(1 - \frac{x}{2}\right)^2 \ln\frac{x^2+\frac{Q^2_{\rm max}}{E^2}} {x^2+\frac{Q^2_{\rm min}}{E^2}} - x^2\frac{m^2}{Q^2_{\rm min}} \left(1 - \frac{Q^2_{\rm min}}{Q^2_{\rm max}}\right) \biggr]. \end{multline} If no explicit $Q$ bounds are provided, the kinematical bounds are \begin{align} -Q^2_{\rm max} &= t_0 = -2\bar x(E^2+p\bar p) + 2m^2 \approx -4\bar x E^2, \\ -Q^2_{\rm min} &= t_1 = -2\bar x(E^2-p\bar p) + 2m^2 \approx -\frac{x^2}{\bar x}m^2. \end{align} The second and third terms in (\ref{EPA_617}) are negative definite (and subleading). Noting that $\bar x + x^2/2$ is bounded between $1/2$ and $1$, we derive that $f(x)$ is always smaller than \begin{equation} \bar f(x) = \frac{\alpha}{\pi}\,q_p^2\,\frac{L - 2\ln x}{x} \qquad\text{where}\qquad L = \ln\frac{\min(4E_{\rm max}^2,Q^2_{\rm max})}{\max(m^2,Q_{\rm min}^2)}, \end{equation} where we allow for explicit $Q$ bounds that narrow the kinematical range. Therefore, we generate this distribution: \begin{equation}\label{EPA-subst} \int_{x_0}^{x_1} dx\,\bar f(x) = C(x_0,x_1)\int_0^1 dx' \end{equation} We set \begin{equation}\label{EPA-x(x')} \ln x = \frac12\left\{ L - \sqrt{L^2 - 4\left[ x'\ln x_1(L-\ln x_1) + \bar x'\ln x_0(L-\ln x_0) \right]} \right\} \end{equation} such that $x(0)=x_0$ and $x(1)=x_1$ and \begin{equation} \frac{dx}{dx'} = \left(\frac{\alpha}{\pi} q_p^2 \right)^{-1} x\frac{C(x_0,x_1)}{L - 2\ln x} \end{equation} with \begin{equation} C(x_0,x_1) = \frac{\alpha}{\pi} q_p^2\,\left[\ln x_1(L-\ln x_1) - \ln x_0(L-\ln x_0)\right] \end{equation} such that (\ref{EPA-subst}) is satisfied. Finally, we have \begin{equation} \int_{x_0}^{x_1} dx\,f(x) = C(x_0,x_1)\int_0^1 dx'\, \frac{f(x(x'))}{\bar f(x(x'))} \end{equation} where $x'$ is calculated from $x$ via (\ref{EPA-x(x')}). The structure of the mapping is most obvious from: \begin{equation} x'(x) = \frac{\log x ( L - \log x) - \log x_0 (L - \log x_0)} {\log x_1 ( L - \log x_1) - \log x_0 (L - \log x_0)} \; . \end{equation} Taking the Eq. (6.16e) from the Budnev et al. report, and integrating it over $q^2$ yields the modified result \begin{equation} \label{EPA_616e} f(x) = \frac{\alpha}{\pi}\,q_p^2\, \frac{1}{x}\, \biggl[\left(\bar x + \frac{x^2}{2}\right) \ln\frac{Q^2_{\rm max}}{Q^2_{\rm min}} - x^2\frac{m^2}{Q^2_{\rm min}} \left(1 - \frac{Q^2_{\rm min}}{Q^2_{\rm max}}\right) \biggr]. \end{equation} This is closer to many standard papers from LEP times, and to textbook formulae like e.g. in Peskin/Schroeder. For historical reasons, we keep Eq.~(\ref{EPA_617}) as the default in \whizard. \subsection{The EPA data block} The EPA parameters are: $\alpha$, $E_{\rm max}$, $m$, $Q_{\rm min}$, and $x_{\rm min}$. Instead of $m$ we can use the incoming particle PDG code as input; from this we can deduce the mass and charge. Internally we store in addition $C_{0/1} = \frac{\alpha}{\pi}q_e^2\ln x_{0/1} (L - \ln x_{0/1})$, the c.m. energy squared and the incoming particle mass. <>= public :: EPA_MODE_DEFAULT public :: EPA_MODE_BUDNEV_617 public :: EPA_MODE_BUDNEV_616E + public :: EPA_MODE_LOG_POWER + public :: EPA_MODE_LOG_SIMPLE + public :: EPA_MODE_LOG <>= integer, parameter :: EPA_MODE_DEFAULT = 0 integer, parameter :: EPA_MODE_BUDNEV_617 = 0 integer, parameter :: EPA_MODE_BUDNEV_616E = 1 + integer, parameter :: EPA_MODE_LOG_POWER = 2 + integer, parameter :: EPA_MODE_LOG_SIMPLE = 3 + integer, parameter :: EPA_MODE_LOG = 4 @ %def EPA_MODE_DEFAULT EPA_MODE_BUDNEV_617 EPA_MODE_BUDNEV_616E +@ %def EPA_MODE_LOG_POWER EPA_MODE_LOG_SIMPLE EPA_MODE_LOG +@ <>= public :: epa_data_t <>= type, extends(sf_data_t) :: epa_data_t private class(model_data_t), pointer :: model => null () type(flavor_t), dimension(:), allocatable :: flv_in real(default) :: alpha real(default) :: x_min real(default) :: x_max real(default) :: q_min real(default) :: q_max real(default) :: E_max real(default) :: mass real(default) :: log real(default) :: a real(default) :: c0 real(default) :: c1 real(default) :: dc integer :: mode = EPA_MODE_DEFAULT integer :: error = NONE logical :: recoil = .false. logical :: keep_energy = .true. contains <> end type epa_data_t @ %def epa_data_t @ Error codes <>= integer, parameter :: NONE = 0 integer, parameter :: ZERO_QMIN = 1 integer, parameter :: Q_MAX_TOO_SMALL = 2 integer, parameter :: ZERO_XMIN = 3 integer, parameter :: MASS_MIX = 4 integer, parameter :: NO_EPA = 5 <>= procedure :: init => epa_data_init <>= subroutine epa_data_init (data, model, mode, pdg_in, alpha, & x_min, q_min, q_max, mass, recoil, keep_energy) class(epa_data_t), intent(inout) :: data class(model_data_t), intent(in), target :: model type(pdg_array_t), intent(in) :: pdg_in integer, intent(in) :: mode real(default), intent(in) :: alpha, x_min, q_min, q_max real(default), intent(in), optional :: mass logical, intent(in), optional :: recoil logical, intent(in), optional :: keep_energy integer :: n_flv, i data%model => model data%mode = mode n_flv = pdg_array_get_length (pdg_in) allocate (data%flv_in (n_flv)) do i = 1, n_flv call data%flv_in(i)%init (pdg_array_get (pdg_in, i), model) end do data%alpha = alpha data%E_max = q_max / 2 data%x_min = x_min data%x_max = 1 if (vanishes (data%x_min)) then data%error = ZERO_XMIN; return end if data%q_min = q_min data%q_max = q_max select case (char (data%model%get_name ())) case ("QCD","Test") data%error = NO_EPA; return end select if (present (recoil)) then data%recoil = recoil end if if (present (keep_energy)) then data%keep_energy = keep_energy end if if (present (mass)) then data%mass = mass else data%mass = data%flv_in(1)%get_mass () if (any (data%flv_in%get_mass () /= data%mass)) then data%error = MASS_MIX; return end if end if if (max (data%mass, data%q_min) == 0) then data%error = ZERO_QMIN; return else if (max (data%mass, data%q_min) >= data%E_max) then data%error = Q_MAX_TOO_SMALL; return end if data%log = log ((data%q_max / max (data%mass, data%q_min)) ** 2 ) data%a = data%alpha / pi data%c0 = log (data%x_min) * (data%log - log (data%x_min)) data%c1 = log (data%x_max) * (data%log - log (data%x_max)) data%dc = data%c1 - data%c0 end subroutine epa_data_init @ %def epa_data_init @ Handle error conditions. Should always be done after initialization, unless we are sure everything is ok. <>= procedure :: check => epa_data_check <>= subroutine epa_data_check (data) class(epa_data_t), intent(in) :: data select case (data%error) case (NO_EPA) call msg_fatal ("EPA structure function not available for model " & // char (data%model%get_name ()) // ".") case (ZERO_QMIN) call msg_fatal ("EPA: Particle mass is zero") case (Q_MAX_TOO_SMALL) call msg_fatal ("EPA: Particle mass exceeds Qmax") case (ZERO_XMIN) call msg_fatal ("EPA: x_min must be larger than zero") case (MASS_MIX) call msg_fatal ("EPA: incoming particle masses must be uniform") end select end subroutine epa_data_check @ %def epa_data_check @ Output <>= procedure :: write => epa_data_write <>= subroutine epa_data_write (data, unit, verbose) class(epa_data_t), intent(in) :: data integer, intent(in), optional :: unit logical, intent(in), optional :: verbose integer :: u, i u = given_output_unit (unit); if (u < 0) return write (u, "(1x,A)") "EPA data:" if (allocated (data%flv_in)) then write (u, "(3x,A)", advance="no") " flavor = " do i = 1, size (data%flv_in) if (i > 1) write (u, "(',',1x)", advance="no") call data%flv_in(i)%write (u) end do write (u, *) write (u, "(3x,A," // FMT_19 // ")") " alpha = ", data%alpha write (u, "(3x,A," // FMT_19 // ")") " x_min = ", data%x_min write (u, "(3x,A," // FMT_19 // ")") " x_max = ", data%x_max write (u, "(3x,A," // FMT_19 // ")") " q_min = ", data%q_min write (u, "(3x,A," // FMT_19 // ")") " q_max = ", data%q_max write (u, "(3x,A," // FMT_19 // ")") " E_max = ", data%e_max write (u, "(3x,A," // FMT_19 // ")") " mass = ", data%mass write (u, "(3x,A," // FMT_19 // ")") " a = ", data%a write (u, "(3x,A," // FMT_19 // ")") " c0 = ", data%c0 write (u, "(3x,A," // FMT_19 // ")") " c1 = ", data%c1 write (u, "(3x,A," // FMT_19 // ")") " log = ", data%log write (u, "(3x,A,L2)") " recoil = ", data%recoil write (u, "(3x,A,L2)") " keep en. = ", data%keep_energy else write (u, "(3x,A)") "[undefined]" end if end subroutine epa_data_write @ %def epa_data_write @ The number of kinematic parameters. <>= procedure :: get_n_par => epa_data_get_n_par <>= function epa_data_get_n_par (data) result (n) class(epa_data_t), intent(in) :: data integer :: n if (data%recoil) then n = 3 else n = 1 end if end function epa_data_get_n_par @ %def epa_data_get_n_par @ Return the outgoing particles PDG codes. The outgoing particle is always the photon while the radiated particle is identical to the incoming one. <>= procedure :: get_pdg_out => epa_data_get_pdg_out <>= subroutine epa_data_get_pdg_out (data, pdg_out) class(epa_data_t), intent(in) :: data type(pdg_array_t), dimension(:), intent(inout) :: pdg_out pdg_out(1) = PHOTON end subroutine epa_data_get_pdg_out @ %def epa_data_get_pdg_out @ Allocate the interaction record. <>= procedure :: allocate_sf_int => epa_data_allocate_sf_int <>= subroutine epa_data_allocate_sf_int (data, sf_int) class(epa_data_t), intent(in) :: data class(sf_int_t), intent(inout), allocatable :: sf_int allocate (epa_t :: sf_int) end subroutine epa_data_allocate_sf_int @ %def epa_data_allocate_sf_int @ \subsection{The EPA object} The [[epa_t]] data type is a $1\to 2$ interaction. We should be able to handle several flavors in parallel, since EPA is not necessarily applied immediately after beam collision: Photons may be radiated from quarks. In that case, the partons are massless and $q_{\rm min}$ applies instead, so we do not need to generate several kinematical configurations in parallel. The squared charge values multiply the matrix elements, depending on the flavour. We scan the interaction after building it, so we have the correct assignments. The particles are ordered as (incoming, radiated, photon), where the photon initiates the hard interaction. We generate an unpolarized photon and transfer initial polarization to the radiated parton. Color is transferred in the same way. <>= type, extends (sf_int_t) :: epa_t type(epa_data_t), pointer :: data => null () real(default) :: x = 0 real(default) :: xb = 0 real(default) :: E = 0 real(default), dimension(:), allocatable :: charge2 contains <> end type epa_t @ %def epa_t @ Type string: has to be here, but there is no string variable on which EPA depends. Hence, a dummy routine. <>= procedure :: type_string => epa_type_string <>= function epa_type_string (object) result (string) class(epa_t), intent(in) :: object type(string_t) :: string if (associated (object%data)) then string = "EPA: equivalent photon approx." else string = "EPA: [undefined]" end if end function epa_type_string @ %def epa_type_string @ Output. Call the interaction routine after displaying the configuration. <>= procedure :: write => epa_write <>= subroutine epa_write (object, unit, testflag) class(epa_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u u = given_output_unit (unit) if (associated (object%data)) then call object%data%write (u) if (object%status >= SF_DONE_KINEMATICS) then write (u, "(1x,A)") "SF parameters:" write (u, "(3x,A," // FMT_17 // ")") "x =", object%x if (object%status >= SF_FAILED_EVALUATION) then write (u, "(3x,A," // FMT_17 // ")") "E =", object%E end if end if call object%base_write (u, testflag) else write (u, "(1x,A)") "EPA data: [undefined]" end if end subroutine epa_write @ %def epa_write @ Prepare the interaction object. We have to construct transition matrix elements for all flavor and helicity combinations. <>= procedure :: init => epa_init <>= subroutine epa_init (sf_int, data) class(epa_t), intent(out) :: sf_int class(sf_data_t), intent(in), target :: data type(quantum_numbers_mask_t), dimension(3) :: mask integer, dimension(3) :: hel_lock type(polarization_t), target :: pol type(quantum_numbers_t), dimension(1) :: qn_fc type(flavor_t) :: flv_photon type(color_t) :: col_photon type(quantum_numbers_t) :: qn_hel, qn_photon, qn, qn_rad type(polarization_iterator_t) :: it_hel integer :: i mask = quantum_numbers_mask (.false., .false., & mask_h = [.false., .false., .true.]) hel_lock = [2, 1, 0] select type (data) type is (epa_data_t) call sf_int%base_init (mask, [data%mass**2], & [data%mass**2], [0._default], hel_lock = hel_lock) sf_int%data => data call flv_photon%init (PHOTON, data%model) call col_photon%init () call qn_photon%init (flv_photon, col_photon) do i = 1, size (data%flv_in) call pol%init_generic (data%flv_in(i)) call qn_fc(1)%init ( & flv = data%flv_in(i), & col = color_from_flavor (data%flv_in(i), 1)) call it_hel%init (pol) do while (it_hel%is_valid ()) qn_hel = it_hel%get_quantum_numbers () qn = qn_hel .merge. qn_fc(1) qn_rad = qn call qn_rad%tag_radiated () call sf_int%add_state ([qn, qn_rad, qn_photon]) call it_hel%advance () end do ! call pol%final () end do call sf_int%freeze () if (data%keep_energy) then sf_int%on_shell_mode = KEEP_ENERGY else sf_int%on_shell_mode = KEEP_MOMENTUM end if call sf_int%set_incoming ([1]) call sf_int%set_radiated ([2]) call sf_int%set_outgoing ([3]) end select end subroutine epa_init @ %def epa_init @ Prepare the charge array. This is separate from the previous routine since the state matrix may be helicity-contracted. <>= procedure :: setup_constants => epa_setup_constants <>= subroutine epa_setup_constants (sf_int) class(epa_t), intent(inout), target :: sf_int type(state_iterator_t) :: it type(flavor_t) :: flv integer :: i, n_me n_me = sf_int%get_n_matrix_elements () allocate (sf_int%charge2 (n_me)) call it%init (sf_int%interaction_t%get_state_matrix_ptr ()) do while (it%is_valid ()) i = it%get_me_index () flv = it%get_flavor (1) sf_int%charge2(i) = flv%get_charge () ** 2 call it%advance () end do sf_int%status = SF_INITIAL end subroutine epa_setup_constants @ %def epa_setup_constants @ \subsection{Kinematics} Set kinematics. If [[map]] is unset, the $r$ and $x$ values coincide, and the Jacobian $f(r)$ is trivial. The EPA structure function allows for a straightforward mapping of the unit interval. The $x$ value is transformed, and the mapped structure function becomes unity at its upper boundary. The structure function implementation applies the above mapping to the input (random) number [[r]] to generate the momentum fraction [[x]] and the function value [[f]]. For numerical stability reasons, we also output [[xb]], which is $\bar x=1-x$. <>= procedure :: complete_kinematics => epa_complete_kinematics <>= subroutine epa_complete_kinematics (sf_int, x, xb, f, r, rb, map) class(epa_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: x real(default), dimension(:), intent(out) :: xb real(default), intent(out) :: f real(default), dimension(:), intent(in) :: r real(default), dimension(:), intent(in) :: rb logical, intent(in) :: map real(default) :: delta, sqrt_delta, lx if (map) then associate (data => sf_int%data) delta = data%log ** 2 - 4 * (r(1) * data%c1 + rb(1) * data%c0) if (delta > 0) then sqrt_delta = sqrt (delta) lx = (data%log - sqrt_delta) / 2 else sf_int%status = SF_FAILED_KINEMATICS f = 0 return end if x(1) = exp (lx) f = x(1) * data%dc / sqrt_delta end associate else x(1) = r(1) if (sf_int%data%x_min < x(1) .and. x(1) < sf_int%data%x_max) then f = 1 else sf_int%status = SF_FAILED_KINEMATICS f = 0 return end if end if xb(1) = 1 - x(1) if (size(x) == 3) then x(2:3) = r(2:3) xb(2:3) = rb(2:3) end if call sf_int%split_momentum (x, xb) select case (sf_int%status) case (SF_DONE_KINEMATICS) sf_int%x = x(1) sf_int%xb= xb(1) sf_int%E = energy (sf_int%get_momentum (1)) case (SF_FAILED_KINEMATICS) sf_int%x = 0 sf_int%xb= 0 f = 0 end select end subroutine epa_complete_kinematics @ %def epa_complete_kinematics @ Overriding the default method: we compute the [[x]] array from the momentum configuration. In the specific case of EPA, we also set the internally stored $x$ and $\bar x$ values, so they can be used in the following routine. Note: the extraction of $\bar x$ is not numerically safe, but it cannot be as long as the base [[recover_x]] is not. <>= procedure :: recover_x => sf_epa_recover_x <>= subroutine sf_epa_recover_x (sf_int, x, xb, x_free) class(epa_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: x real(default), dimension(:), intent(out) :: xb real(default), intent(inout), optional :: x_free call sf_int%base_recover_x (x, xb, x_free) sf_int%x = x(1) sf_int%xb = xb(1) end subroutine sf_epa_recover_x @ %def sf_epa_recover_x @ Compute inverse kinematics. Here, we start with the $x$ array and compute the ``input'' $r$ values and the Jacobian $f$. After this, we can set momenta by the same formula as for normal kinematics. <>= procedure :: inverse_kinematics => epa_inverse_kinematics <>= subroutine epa_inverse_kinematics (sf_int, x, xb, f, r, rb, map, set_momenta) class(epa_t), intent(inout) :: sf_int real(default), dimension(:), intent(in) :: x real(default), dimension(:), intent(in) :: xb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: r real(default), dimension(:), intent(out) :: rb logical, intent(in) :: map logical, intent(in), optional :: set_momenta real(default) :: lx, delta, sqrt_delta, c logical :: set_mom set_mom = .false.; if (present (set_momenta)) set_mom = set_momenta if (map) then associate (data => sf_int%data) lx = log (x(1)) sqrt_delta = data%log - 2 * lx delta = sqrt_delta ** 2 c = (data%log ** 2 - delta) / 4 r (1) = (c - data%c0) / data%dc rb(1) = (data%c1 - c) / data%dc f = x(1) * data%dc / sqrt_delta end associate else r (1) = x(1) rb(1) = xb(1) if (sf_int%data%x_min < x(1) .and. x(1) < sf_int%data%x_max) then f = 1 else f = 0 end if end if if (size(r) == 3) then r (2:3) = x(2:3) rb(2:3) = xb(2:3) end if if (set_mom) then call sf_int%split_momentum (x, xb) select case (sf_int%status) case (SF_FAILED_KINEMATICS); f = 0 end select end if sf_int%E = energy (sf_int%get_momentum (1)) end subroutine epa_inverse_kinematics @ %def epa_inverse_kinematics @ \subsection{EPA application} For EPA, we can in principle compute kinematics and function value in a single step. In order to be able to reweight events, kinematics and structure function application are separated. This function works on a single beam, assuming that the input momentum has been set. We need three random numbers as input: one for $x$, and two for the polar and azimuthal angles. Alternatively, for the no-recoil case, we can skip $p_T$ generation; in this case, we only need one. For obtaining splitting kinematics, we rely on the assumption that all in-particles are mass-degenerate (or there is only one), so the generated $x$ values are identical. Fix 2020-03-10: Divide by two if there is polarization. In the polarized case, the outgoing electron/positron retains the incoming polarization. The latter is summed over when convoluting with the beam, but there are still two states with different outgoing polarization but identical structure-function value. This leads to double-counting for the overall cross section. <>= procedure :: apply => epa_apply <>= subroutine epa_apply (sf_int, scale, rescale, i_sub) class(epa_t), intent(inout) :: sf_int real(default), intent(in) :: scale class(sf_rescale_t), intent(in), optional :: rescale integer, intent(in), optional :: i_sub - real(default) :: x, xb, qminsq, qmaxsq, f, E + real(default) :: x, xb, qminsq, qmaxsq, f, E, m2 associate (data => sf_int%data) x = sf_int%x xb= sf_int%xb E = sf_int%E + m2 = data%mass ** 2 qminsq = max (x ** 2 / xb * data%mass ** 2, data%q_min ** 2) - qmaxsq = min (4 * xb * E ** 2, data%q_max ** 2) - if (qminsq < qmaxsq) then - select case (data%mode) - case (0) + select case (data%mode) + case (0) + qmaxsq = min (4 * xb * E ** 2, data%q_max ** 2) + if (qminsq < qmaxsq) then f = data%a / x & * ((xb + x ** 2 / 2) * log (qmaxsq / qminsq) & - (1 - x / 2) ** 2 & * log ((x**2 + qmaxsq / E ** 2) / (x**2 + qminsq / E ** 2)) & - x ** 2 * data%mass ** 2 / qminsq * (1 - qminsq / qmaxsq)) - case (1) + else + f = 0 + end if + case (1) + qmaxsq = min (4 * xb * E ** 2, data%q_max ** 2) + if (qminsq < qmaxsq) then f = data%a / x & * ((xb + x ** 2 / 2) * log (qmaxsq / qminsq) & - x ** 2 * data%mass ** 2 / qminsq * (1 - qminsq / qmaxsq)) - end select - else - f = 0 - end if + else + f = 0 + end if + case (2) + qmaxsq = data%q_max ** 2 + if (data%mass ** 2 < qmaxsq) then + f = data%a / x & + * ((xb + x ** 2 / 2) * log (qmaxsq / m2) & + - x ** 2 * data%mass ** 2 / qminsq * (1 - qminsq / qmaxsq)) + else + f = 0 + end if + case (3) + qmaxsq = data%q_max ** 2 + if (data%mass ** 2 < qmaxsq) then + f = data%a / x & + * ((xb + x ** 2 / 2) * log (qmaxsq / m2) & + - x ** 2 * (1 - m2 / qmaxsq)) + else + f = 0 + end if + case (4) + qmaxsq = data%q_max ** 2 + if (data%mass ** 2 < qmaxsq) then + f = data%a / x & + * ((xb + x ** 2 / 2) * log (qmaxsq / m2)) + else + f = 0 + end if + end select f = f / sf_int%get_n_matrix_elements () call sf_int%set_matrix_element & (cmplx (f, kind=default) * sf_int%charge2) end associate sf_int%status = SF_EVALUATED end subroutine epa_apply @ %def epa_apply @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[sf_epa_ut.f90]]>>= <> module sf_epa_ut use unit_tests use sf_epa_uti <> <> contains <> end module sf_epa_ut @ %def sf_epa_ut @ <<[[sf_epa_uti.f90]]>>= <> module sf_epa_uti <> use physics_defs, only: ELECTRON use lorentz use pdg_arrays use flavors use interactions, only: reset_interaction_counter use interactions, only: interaction_pacify_momenta use model_data use sf_aux use sf_base use sf_epa <> <> contains <> end module sf_epa_uti @ %def sf_epa_ut @ API: driver for the unit tests below. <>= public :: sf_epa_test <>= subroutine sf_epa_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine sf_epa_test @ %def sf_epa_test @ \subsubsection{Test structure function data} Construct and display a test structure function data object. <>= call test (sf_epa_1, "sf_epa_1", & "structure function configuration", & u, results) <>= public :: sf_epa_1 <>= subroutine sf_epa_1 (u) integer, intent(in) :: u type(model_data_t), target :: model type(pdg_array_t) :: pdg_in type(pdg_array_t), dimension(1) :: pdg_out integer, dimension(:), allocatable :: pdg1 class(sf_data_t), allocatable :: data write (u, "(A)") "* Test output: sf_epa_1" write (u, "(A)") "* Purpose: initialize and display & &test structure function data" write (u, "(A)") write (u, "(A)") "* Create empty data object" write (u, "(A)") call model%init_qed_test () pdg_in = ELECTRON allocate (epa_data_t :: data) call data%write (u) write (u, "(A)") write (u, "(A)") "* Initialize" write (u, "(A)") select type (data) type is (epa_data_t) call data%init (model, 0, pdg_in, 1./137._default, 0.01_default, & 10._default, 100._default, 0.000511_default, recoil = .false.) end select call data%write (u) write (u, "(A)") write (u, "(1x,A)") "Outgoing particle codes:" call data%get_pdg_out (pdg_out) pdg1 = pdg_out(1) write (u, "(2x,99(1x,I0))") pdg1 call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_epa_1" end subroutine sf_epa_1 @ %def sf_epa_1 @ \subsubsection{Test and probe structure function} Construct and display a structure function object based on the EPA structure function. <>= call test (sf_epa_2, "sf_epa_2", & "structure function instance", & u, results) <>= public :: sf_epa_2 <>= subroutine sf_epa_2 (u) integer, intent(in) :: u type(model_data_t), target :: model type(flavor_t) :: flv type(pdg_array_t) :: pdg_in class(sf_data_t), allocatable, target :: data class(sf_int_t), allocatable :: sf_int type(vector4_t) :: k type(vector4_t), dimension(2) :: q real(default) :: E real(default), dimension(:), allocatable :: r, rb, x, xb real(default) :: f write (u, "(A)") "* Test output: sf_epa_2" write (u, "(A)") "* Purpose: initialize and fill & &test structure function object" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call model%init_qed_test () call flv%init (ELECTRON, model) pdg_in = ELECTRON call reset_interaction_counter () allocate (epa_data_t :: data) select type (data) type is (epa_data_t) call data%init (model, 0, pdg_in, 1./137._default, 0.01_default, & 10._default, 100._default, 0.000511_default, recoil = .false.) end select write (u, "(A)") "* Initialize structure-function object" write (u, "(A)") call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1]) call sf_int%setup_constants () write (u, "(A)") "* Initialize incoming momentum with E=500" write (u, "(A)") E = 500 k = vector4_moving (E, sqrt (E**2 - flv%get_mass ()**2), 3) call pacify (k, 1e-10_default) call vector4_write (k, u) call sf_int%seed_kinematics ([k]) write (u, "(A)") write (u, "(A)") "* Set kinematics for r=0.4, no EPA mapping, collinear" write (u, "(A)") allocate (r (data%get_n_par ())) allocate (rb(size (r))) allocate (x (size (r))) allocate (xb(size (r))) r = 0.4_default rb = 1 - r call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Recover x from momenta" write (u, "(A)") q = sf_int%get_momenta (outgoing=.true.) call sf_int%final () deallocate (sf_int) call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1]) call sf_int%setup_constants () call sf_int%seed_kinematics ([k]) call sf_int%set_momenta (q, outgoing=.true.) call sf_int%recover_x (x, xb) call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.false., & set_momenta=.true.) write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Evaluate EPA structure function" write (u, "(A)") call sf_int%apply (scale = 100._default) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call sf_int%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_epa_2" end subroutine sf_epa_2 @ %def sf_epa_2 @ \subsubsection{Standard mapping} Construct and display a structure function object based on the EPA structure function, applying the standard single-particle mapping. <>= call test (sf_epa_3, "sf_epa_3", & "apply mapping", & u, results) <>= public :: sf_epa_3 <>= subroutine sf_epa_3 (u) integer, intent(in) :: u type(model_data_t), target :: model type(flavor_t) :: flv type(pdg_array_t) :: pdg_in class(sf_data_t), allocatable, target :: data class(sf_int_t), allocatable :: sf_int type(vector4_t) :: k type(vector4_t), dimension(2) :: q real(default) :: E real(default), dimension(:), allocatable :: r, rb, x, xb real(default) :: f write (u, "(A)") "* Test output: sf_epa_3" write (u, "(A)") "* Purpose: initialize and fill & &test structure function object" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call model%init_qed_test () call flv%init (ELECTRON, model) pdg_in = ELECTRON call reset_interaction_counter () allocate (epa_data_t :: data) select type (data) type is (epa_data_t) call data%init (model, 0, pdg_in, 1./137._default, 0.01_default, & 10._default, 100._default, 0.000511_default, recoil = .false.) end select write (u, "(A)") "* Initialize structure-function object" write (u, "(A)") call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1]) call sf_int%setup_constants () write (u, "(A)") "* Initialize incoming momentum with E=500" write (u, "(A)") E = 500 k = vector4_moving (E, sqrt (E**2 - flv%get_mass ()**2), 3) call pacify (k, 1e-10_default) call vector4_write (k, u) call sf_int%seed_kinematics ([k]) write (u, "(A)") write (u, "(A)") "* Set kinematics for r=0.4, with EPA mapping, collinear" write (u, "(A)") allocate (r (data%get_n_par ())) allocate (rb(size (r))) allocate (x (size (r))) allocate (xb(size (r))) r = 0.4_default rb = 1 - r call sf_int%complete_kinematics (x, xb, f, r, rb, map=.true.) write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Recover x from momenta" write (u, "(A)") q = sf_int%get_momenta (outgoing=.true.) call sf_int%final () deallocate (sf_int) call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1]) call sf_int%setup_constants () call sf_int%seed_kinematics ([k]) call sf_int%set_momenta (q, outgoing=.true.) call sf_int%recover_x (x, xb) call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.true., & set_momenta=.true.) write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Evaluate EPA structure function" write (u, "(A)") call sf_int%apply (scale = 100._default) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call sf_int%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_epa_3" end subroutine sf_epa_3 @ %def sf_epa_3 @ \subsubsection{Non-collinear case} Construct and display a structure function object based on the EPA structure function. <>= call test (sf_epa_4, "sf_epa_4", & "non-collinear", & u, results) <>= public :: sf_epa_4 <>= subroutine sf_epa_4 (u) integer, intent(in) :: u type(model_data_t), target :: model type(flavor_t) :: flv type(pdg_array_t) :: pdg_in class(sf_data_t), allocatable, target :: data class(sf_int_t), allocatable :: sf_int type(vector4_t) :: k type(vector4_t), dimension(2) :: q real(default) :: E, m real(default), dimension(:), allocatable :: r, rb, x, xb real(default) :: f write (u, "(A)") "* Test output: sf_epa_4" write (u, "(A)") "* Purpose: initialize and fill & &test structure function object" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call model%init_qed_test () call flv%init (ELECTRON, model) pdg_in = ELECTRON call reset_interaction_counter () allocate (epa_data_t :: data) select type (data) type is (epa_data_t) call data%init (model, 0, pdg_in, 1./137._default, 0.01_default, & 10._default, 100._default, 5.0_default, recoil = .true.) end select write (u, "(A)") "* Initialize structure-function object" write (u, "(A)") call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1]) call sf_int%setup_constants () write (u, "(A)") "* Initialize incoming momentum with E=500, me = 5 GeV" write (u, "(A)") E = 500 m = 5 k = vector4_moving (E, sqrt (E**2 - m**2), 3) call pacify (k, 1e-10_default) call vector4_write (k, u) call sf_int%seed_kinematics ([k]) write (u, "(A)") write (u, "(A)") "* Set kinematics for r=0.5/0.5/0.25, with EPA mapping, " write (u, "(A)") " non-coll., keeping energy, me = 5 GeV" write (u, "(A)") allocate (r (data%get_n_par ())) allocate (rb(size (r))) allocate (x (size (r))) allocate (xb(size (r))) r = [0.5_default, 0.5_default, 0.25_default] rb = 1 - r sf_int%on_shell_mode = KEEP_ENERGY call sf_int%complete_kinematics (x, xb, f, r, rb, map=.true.) call interaction_pacify_momenta (sf_int%interaction_t, 1e-10_default) write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Recover x and r from momenta" write (u, "(A)") q = sf_int%get_momenta (outgoing=.true.) call sf_int%final () deallocate (sf_int) call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1]) call sf_int%setup_constants () call sf_int%seed_kinematics ([k]) call sf_int%set_momenta (q, outgoing=.true.) call sf_int%recover_x (x, xb) call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.true., & set_momenta=.true.) call interaction_pacify_momenta (sf_int%interaction_t, 1e-10_default) write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Evaluate EPA structure function" write (u, "(A)") call sf_int%apply (scale = 100._default) call sf_int%write (u, testflag = .true.) write (u, "(A)") write (u, "(A)") "* Cleanup" call sf_int%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_epa_4" end subroutine sf_epa_4 @ %def sf_epa_4 @ \subsubsection{Structure function for multiple flavors} Construct and display a structure function object based on the EPA structure function. The incoming state has multiple particles with non-uniform charge. <>= call test (sf_epa_5, "sf_epa_5", & "multiple flavors", & u, results) <>= public :: sf_epa_5 <>= subroutine sf_epa_5 (u) integer, intent(in) :: u type(model_data_t), target :: model type(flavor_t) :: flv type(pdg_array_t) :: pdg_in class(sf_data_t), allocatable, target :: data class(sf_int_t), allocatable :: sf_int type(vector4_t) :: k real(default) :: E real(default), dimension(:), allocatable :: r, rb, x, xb real(default) :: f write (u, "(A)") "* Test output: sf_epa_5" write (u, "(A)") "* Purpose: initialize and fill & &test structure function object" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call model%init_sm_test () call flv%init (1, model) pdg_in = [1, 2, -1, -2] call reset_interaction_counter () allocate (epa_data_t :: data) select type (data) type is (epa_data_t) call data%init (model, 0, pdg_in, 1./137._default, 0.01_default, & 10._default, 100._default, 0.000511_default, recoil = .false.) call data%check () end select write (u, "(A)") "* Initialize structure-function object" write (u, "(A)") call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1]) call sf_int%setup_constants () write (u, "(A)") "* Initialize incoming momentum with E=500" write (u, "(A)") E = 500 k = vector4_moving (E, sqrt (E**2 - flv%get_mass ()**2), 3) call pacify (k, 1e-10_default) call vector4_write (k, u) call sf_int%seed_kinematics ([k]) write (u, "(A)") write (u, "(A)") "* Set kinematics for r=0.4, no EPA mapping, collinear" write (u, "(A)") allocate (r (data%get_n_par ())) allocate (rb(size (r))) allocate (x (size (r))) allocate (xb(size (r))) r = 0.4_default rb = 1 - r call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Evaluate EPA structure function" write (u, "(A)") call sf_int%apply (scale = 100._default) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call sf_int%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_epa_5" end subroutine sf_epa_5 @ %def sf_epa_5 @ \clearpage %------------------------------------------------------------------------ \section{EWA} <<[[sf_ewa.f90]]>>= <> module sf_ewa <> <> use io_units use constants, only: pi use format_defs, only: FMT_17, FMT_19 use numeric_utils use diagnostics use physics_defs, only: W_BOSON, Z_BOSON use lorentz use pdg_arrays use model_data use flavors use colors use quantum_numbers use state_matrices use polarizations use interactions use sf_aux use sf_base <> <> <> <> contains <> end module sf_ewa @ %def sf_ewa @ \subsection{Physics} The EWA structure function for a $Z$ or $W$ inside a fermion (lepton or quark) depends on the vector-boson polarization. We distinguish transversal ($\pm$) and longitudinal ($0$) polarization. \begin{align} F_{+}(x) &= \frac{1}{16\pi^2}\,\frac{(v-a)^2 + (v+a)^2\bar x^2}{x} \left[ \ln\left(\frac{p_{\perp,\textrm{max}}^2 + \bar x M^2}{\bar x M^2}\right) - \frac{p_{\perp,\textrm{max}}^2}{p_{\perp,\textrm{max}}^2 + \bar x M^2} \right] \\ F_{-}(x) &= \frac{1}{16\pi^2}\,\frac{(v+a)^2 + (v-a)^2\bar x^2}{x} \left[ \ln\left(\frac{p_{\perp,\textrm{max}}^2 + \bar x M^2}{\bar x M^2}\right) - \frac{p_{\perp,\textrm{max}}^2}{p_{\perp,\textrm{max}}^2 + \bar x M^2} \right] \\ F_0(x) &= \frac{v^2+a^2}{8\pi^2}\,\frac{2\bar x}{x}\, \frac{p_{\perp,\textrm{max}}^2}{p_{\perp,\textrm{max}}^2 + \bar x M^2} \end{align} where $p_{\perp,\textrm{max}}$ is the cutoff in transversal momentum, $M$ is the vector-boson mass, $v$ and $a$ are the vector and axial-vector couplings, and $\bar x\equiv 1-x$. Note that the longitudinal structure function is finite for large cutoff, while the transversal structure function is logarithmically divergent. The maximal transverse momentum is given by the kinematical limit, it is \begin{equation} p_{\perp,\textrm{max}} = \bar x \sqrt{s}/2. \end{equation} The vector and axial couplings for a fermion branching into a $W$ are \begin{align} v_W &= \frac{g}{2\sqrt 2}, & a_W &= \frac{g}{2\sqrt 2}. \end{align} For $Z$ emission, this is replaced by \begin{align} v_Z &= \frac{g}{2\cos\theta_w}\left(t_3 - 2q\sin^2\theta_w\right), & a_Z &= \frac{g}{2\cos\theta_w}t_3, \end{align} where $t_3=\pm\frac12$ is the fermion isospin, and $q$ its charge. For an initial antifermion, the signs of the axial couplings are inverted. Note that a common sign change of $v$ and $a$ is irrelevant. %% Differentiating with respect to the cutoff, we get structure functions %% \begin{align} %% f_{W,\pm}(x,p_T) &= \frac{g^2}{16\pi^2}\, %% \frac{1+\bar x^2}{x} %% \frac{p_\perp}{p_\perp^2 + \bar x M^2} %% \\ %% f_{W,0}(x,p_T) &= \frac{g^2}{16\pi^2}\, %% \frac{2\bar x}{x}\, %% \frac{p_\perp \bar xM^2}{(p_\perp^2 + \bar x M^2)^2} %% \\ %% F_{Z,\pm}(x,p_T) &= \frac{g^2}{16\pi^2\cos\theta_w^2} %% \left[(t_3^f-2q^2\sin\theta_w^2)^2 + (t_3^f)^2\right]\, %% \frac{1+\bar x^2}{x} %% \frac{p_\perp}{p_\perp^2 + \bar x M^2} %% \\ %% F_{Z,0}(x,p_T) &= \frac{g^2}{16\pi^2\cos\theta_w^2}\, %% \left[(t_3^f-2q^2\sin\theta_w^2)^2 + (t_3^f)^2\right]\, %% \frac{2\bar x}{x}\, %% \frac{p_\perp \bar xM^2}{(p_\perp^2 + \bar x M^2)^2} %% \end{align} %% Here, $t_3^f$ is the $SU(2)_L$ quantum number of the fermion %% $(\pm\frac12)$, and $q^f$ is the fermion charge in units of the %% positron charge. The EWA depends on the parameters $g$, $\sin^2\theta_w$, $M_W$, and $M_Z$. These can all be taken from the SM input, and the prefactors are calculated from those and the incoming particle type. Since these structure functions have a $1/x$ singularity (which is not really relevant in practice, however, since the vector boson mass is finite), we map this singularity allowing for nontrivial $x$ bounds: \begin{equation} x = \exp(\bar r\ln x_0 + r\ln x_1) \end{equation} such that \begin{equation} \int_{x_0}^{x_1}\frac{dx}{x} = (\ln x_1 - \ln x_0)\int_0^1 dr. \end{equation} As a user parameter, we have the cutoff $p_{\perp,\textrm{max}}$. The divergence $1/x$ also requires a $x_0$ cutoff; and for completeness we introduce a corresponding $x_1$. Physically, the minimal sensible value of $x$ is $M^2/s$, although the approximation loses its value already at higher $x$ values. \subsection{The EWA data block} The EWA parameters are: $p_{T,\rm max}$, $c_V$, $c_A$, and $m$. Instead of $m$ we can use the incoming particle PDG code as input; from this we can deduce the mass and charges. In the initialization phase it is not yet determined whether a $W$ or a $Z$ is radiated, hence we set the vector and axial-vector couplings equal to the common prefactors $g/2 = e/2/\sin\theta_W$. In principle, for EWA it would make sense to allow the user to also set the upper bound for $x$, $x_{\rm max}$, but we fix it to one here. <>= public :: ewa_data_t <>= type, extends(sf_data_t) :: ewa_data_t private class(model_data_t), pointer :: model => null () type(flavor_t), dimension(:), allocatable :: flv_in type(flavor_t), dimension(:), allocatable :: flv_out real(default) :: pt_max real(default) :: sqrts real(default) :: x_min real(default) :: x_max real(default) :: mass real(default) :: m_out real(default) :: q_min real(default) :: cv real(default) :: ca real(default) :: costhw real(default) :: sinthw real(default) :: mW real(default) :: mZ real(default) :: coeff logical :: mass_set = .false. logical :: recoil = .false. logical :: keep_energy = .false. integer :: id = 0 integer :: error = NONE contains <> end type ewa_data_t @ %def ewa_data_t @ Error codes <>= integer, parameter :: NONE = 0 integer, parameter :: ZERO_QMIN = 1 integer, parameter :: Q_MAX_TOO_SMALL = 2 integer, parameter :: ZERO_XMIN = 3 integer, parameter :: MASS_MIX = 4 integer, parameter :: ZERO_SW = 5 integer, parameter :: ISOSPIN_MIX = 6 integer, parameter :: WRONG_PRT = 7 integer, parameter :: MASS_MIX_OUT = 8 integer, parameter :: NO_EWA = 9 <>= procedure :: init => ewa_data_init <>= subroutine ewa_data_init (data, model, pdg_in, x_min, pt_max, & sqrts, recoil, keep_energy, mass) class(ewa_data_t), intent(inout) :: data class(model_data_t), intent(in), target :: model type(pdg_array_t), intent(in) :: pdg_in real(default), intent(in) :: x_min, pt_max, sqrts logical, intent(in) :: recoil, keep_energy real(default), intent(in), optional :: mass real(default) :: g, ee integer :: n_flv, i data%model => model if (.not. any (pdg_in .match. & [1,2,3,4,5,6,11,13,15,-1,-2,-3,-4,-5,-6,-11,-13,-15])) then data%error = WRONG_PRT; return end if n_flv = pdg_array_get_length (pdg_in) allocate (data%flv_in (n_flv)) allocate (data%flv_out(n_flv)) do i = 1, n_flv call data%flv_in(i)%init (pdg_array_get (pdg_in, i), model) end do data%pt_max = pt_max data%sqrts = sqrts data%x_min = x_min data%x_max = 1 if (vanishes (data%x_min)) then data%error = ZERO_XMIN; return end if select case (char (data%model%get_name ())) case ("QCD","QED","Test") data%error = NO_EWA; return end select ee = data%model%get_real (var_str ("ee")) data%sinthw = data%model%get_real (var_str ("sw")) data%costhw = data%model%get_real (var_str ("cw")) data%mZ = data%model%get_real (var_str ("mZ")) data%mW = data%model%get_real (var_str ("mW")) if (data%sinthw /= 0) then g = ee / data%sinthw else data%error = ZERO_SW; return end if data%cv = g / 2._default data%ca = g / 2._default data%coeff = 1._default / (8._default * PI**2) data%recoil = recoil data%keep_energy = keep_energy if (present (mass)) then data%mass = mass data%m_out = mass data%mass_set = .true. else data%mass = data%flv_in(1)%get_mass () if (any (data%flv_in%get_mass () /= data%mass)) then data%error = MASS_MIX; return end if end if end subroutine ewa_data_init @ %def ewa_data_init @ Set the vector boson ID for distinguishing $W$ and $Z$ bosons. <>= procedure :: set_id => ewa_set_id <>= subroutine ewa_set_id (data, id) class(ewa_data_t), intent(inout) :: data integer, intent(in) :: id integer :: i, isospin, pdg if (.not. allocated (data%flv_in)) & call msg_bug ("EWA: incoming particles not set") data%id = id select case (data%id) case (23) data%m_out = data%mass data%flv_out = data%flv_in case (24) do i = 1, size (data%flv_in) pdg = data%flv_in(i)%get_pdg () isospin = data%flv_in(i)%get_isospin_type () if (isospin > 0) then !!! up-type quark or neutrinos if (data%flv_in(i)%is_antiparticle ()) then call data%flv_out(i)%init (pdg + 1, data%model) else call data%flv_out(i)%init (pdg - 1, data%model) end if else !!! down-type quark or lepton if (data%flv_in(i)%is_antiparticle ()) then call data%flv_out(i)%init (pdg - 1, data%model) else call data%flv_out(i)%init (pdg + 1, data%model) end if end if end do if (.not. data%mass_set) then data%m_out = data%flv_out(1)%get_mass () if (any (data%flv_out%get_mass () /= data%m_out)) then data%error = MASS_MIX_OUT; return end if end if end select end subroutine ewa_set_id @ %def ewa_set_id @ Handle error conditions. Should always be done after initialization, unless we are sure everything is ok. <>= procedure :: check => ewa_data_check <>= subroutine ewa_data_check (data) class(ewa_data_t), intent(in) :: data select case (data%error) case (WRONG_PRT) call msg_fatal ("EWA structure function only accessible for " & // "SM quarks and leptons.") case (NO_EWA) call msg_fatal ("EWA structure function not available for model " & // char (data%model%get_name ())) case (ZERO_SW) call msg_fatal ("EWA: Vanishing value of sin(theta_w)") case (ZERO_QMIN) call msg_fatal ("EWA: Particle mass is zero") case (Q_MAX_TOO_SMALL) call msg_fatal ("EWA: Particle mass exceeds Qmax") case (ZERO_XMIN) call msg_fatal ("EWA: x_min must be larger than zero") case (MASS_MIX) call msg_fatal ("EWA: incoming particle masses must be uniform") case (MASS_MIX_OUT) call msg_fatal ("EWA: outgoing particle masses must be uniform") case (ISOSPIN_MIX) call msg_fatal ("EWA: incoming particle isospins must be uniform") end select end subroutine ewa_data_check @ %def ewa_data_check @ Output <>= procedure :: write => ewa_data_write <>= subroutine ewa_data_write (data, unit, verbose) class(ewa_data_t), intent(in) :: data integer, intent(in), optional :: unit logical, intent(in), optional :: verbose integer :: u, i u = given_output_unit (unit); if (u < 0) return write (u, "(1x,A)") "EWA data:" if (allocated (data%flv_in) .and. allocated (data%flv_out)) then write (u, "(3x,A)", advance="no") " flavor(in) = " do i = 1, size (data%flv_in) if (i > 1) write (u, "(',',1x)", advance="no") call data%flv_in(i)%write (u) end do write (u, *) write (u, "(3x,A)", advance="no") " flavor(out) = " do i = 1, size (data%flv_out) if (i > 1) write (u, "(',',1x)", advance="no") call data%flv_out(i)%write (u) end do write (u, *) write (u, "(3x,A," // FMT_19 // ")") " x_min = ", data%x_min write (u, "(3x,A," // FMT_19 // ")") " x_max = ", data%x_max write (u, "(3x,A," // FMT_19 // ")") " pt_max = ", data%pt_max write (u, "(3x,A," // FMT_19 // ")") " sqrts = ", data%sqrts write (u, "(3x,A," // FMT_19 // ")") " mass = ", data%mass write (u, "(3x,A," // FMT_19 // ")") " cv = ", data%cv write (u, "(3x,A," // FMT_19 // ")") " ca = ", data%ca write (u, "(3x,A," // FMT_19 // ")") " coeff = ", data%coeff write (u, "(3x,A," // FMT_19 // ")") " costhw = ", data%costhw write (u, "(3x,A," // FMT_19 // ")") " sinthw = ", data%sinthw write (u, "(3x,A," // FMT_19 // ")") " mZ = ", data%mZ write (u, "(3x,A," // FMT_19 // ")") " mW = ", data%mW write (u, "(3x,A,L2)") " recoil = ", data%recoil write (u, "(3x,A,L2)") " keep en. = ", data%keep_energy write (u, "(3x,A,I2)") " PDG (VB) = ", data%id else write (u, "(3x,A)") "[undefined]" end if end subroutine ewa_data_write @ %def ewa_data_write @ The number of parameters is one for collinear splitting, in case the [[recoil]] option is set, we take the recoil into account. <>= procedure :: get_n_par => ewa_data_get_n_par <>= function ewa_data_get_n_par (data) result (n) class(ewa_data_t), intent(in) :: data integer :: n if (data%recoil) then n = 3 else n = 1 end if end function ewa_data_get_n_par @ %def ewa_data_get_n_par @ Return the outgoing particles PDG codes. This depends, whether this is a charged-current or neutral-current interaction. <>= procedure :: get_pdg_out => ewa_data_get_pdg_out <>= subroutine ewa_data_get_pdg_out (data, pdg_out) class(ewa_data_t), intent(in) :: data type(pdg_array_t), dimension(:), intent(inout) :: pdg_out integer, dimension(:), allocatable :: pdg1 integer :: i, n_flv if (allocated (data%flv_out)) then n_flv = size (data%flv_out) else n_flv = 0 end if allocate (pdg1 (n_flv)) do i = 1, n_flv pdg1(i) = data%flv_out(i)%get_pdg () end do pdg_out(1) = pdg1 end subroutine ewa_data_get_pdg_out @ %def ewa_data_get_pdg_out @ Allocate the interaction record. <>= procedure :: allocate_sf_int => ewa_data_allocate_sf_int <>= subroutine ewa_data_allocate_sf_int (data, sf_int) class(ewa_data_t), intent(in) :: data class(sf_int_t), intent(inout), allocatable :: sf_int allocate (ewa_t :: sf_int) end subroutine ewa_data_allocate_sf_int @ %def ewa_data_allocate_sf_int @ \subsection{The EWA object} The [[ewa_t]] data type is a $1\to 2$ interaction. We should be able to handle several flavors in parallel, since EWA is not necessarily applied immediately after beam collision: $W/Z$ bosons may be radiated from quarks. In that case, the partons are massless and $q_{\rm min}$ applies instead, so we do not need to generate several kinematical configurations in parallel. The particles are ordered as (incoming, radiated, W/Z), where the W/Z initiates the hard interaction. In the case of EPA, we generated an unpolarized photon and transferred initial polarization to the radiated parton. Color is transferred in the same way. I do not know whether the same can/should be done for EWA, as the structure functions depend on the W/Z polarization. If we are having $Z$ bosons, both up- and down-type fermions can participate. Otherwise, with a $W^+$ an up-type fermion is transferred to a down-type fermion, and the other way round. <>= type, extends (sf_int_t) :: ewa_t type(ewa_data_t), pointer :: data => null () real(default) :: x = 0 real(default) :: xb = 0 integer :: n_me = 0 real(default), dimension(:), allocatable :: cv real(default), dimension(:), allocatable :: ca contains <> end type ewa_t @ %def ewa_t @ Type string: has to be here, but there is no string variable on which EWA depends. Hence, a dummy routine. <>= procedure :: type_string => ewa_type_string <>= function ewa_type_string (object) result (string) class(ewa_t), intent(in) :: object type(string_t) :: string if (associated (object%data)) then string = "EWA: equivalent W/Z approx." else string = "EWA: [undefined]" end if end function ewa_type_string @ %def ewa_type_string @ Output. Call the interaction routine after displaying the configuration. <>= procedure :: write => ewa_write <>= subroutine ewa_write (object, unit, testflag) class(ewa_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u u = given_output_unit (unit) if (associated (object%data)) then call object%data%write (u) if (object%status >= SF_DONE_KINEMATICS) then write (u, "(1x,A)") "SF parameters:" write (u, "(3x,A," // FMT_17 // ")") "x =", object%x write (u, "(3x,A," // FMT_17 // ")") "xb=", object%xb end if call object%base_write (u, testflag) else write (u, "(1x,A)") "EWA data: [undefined]" end if end subroutine ewa_write @ %def ewa_write @ The current implementation requires uniform isospin for all incoming particles, therefore we need to probe only the first one. <>= procedure :: init => ewa_init <>= subroutine ewa_init (sf_int, data) class(ewa_t), intent(out) :: sf_int class(sf_data_t), intent(in), target :: data type(quantum_numbers_mask_t), dimension(3) :: mask integer, dimension(3) :: hel_lock type(polarization_t), target :: pol type(quantum_numbers_t), dimension(1) :: qn_fc, qn_fc_fin type(flavor_t) :: flv_z, flv_wp, flv_wm type(color_t) :: col0 type(quantum_numbers_t) :: qn_hel, qn_z, qn_wp, qn_wm, qn, qn_rad, qn_w type(polarization_iterator_t) :: it_hel integer :: i, isospin select type (data) type is (ewa_data_t) mask = quantum_numbers_mask (.false., .false., & mask_h = [.false., .false., .true.]) hel_lock = [2, 1, 0] call col0%init () select case (data%id) case (23) !!! Z boson, flavor is not changing call sf_int%base_init (mask, [data%mass**2], [data%mass**2], & [data%mZ**2], hel_lock = hel_lock) sf_int%data => data call flv_z%init (Z_BOSON, data%model) call qn_z%init (flv_z, col0) do i = 1, size (data%flv_in) call pol%init_generic (data%flv_in(i)) call qn_fc(1)%init ( & flv = data%flv_in(i), & col = color_from_flavor (data%flv_in(i), 1)) call it_hel%init (pol) do while (it_hel%is_valid ()) qn_hel = it_hel%get_quantum_numbers () qn = qn_hel .merge. qn_fc(1) qn_rad = qn call qn_rad%tag_radiated () call sf_int%add_state ([qn, qn_rad, qn_z]) call it_hel%advance () end do ! call pol%final () end do case (24) call sf_int%base_init (mask, [data%mass**2], [data%m_out**2], & [data%mW**2], hel_lock = hel_lock) sf_int%data => data call flv_wp%init (W_BOSON, data%model) call flv_wm%init (- W_BOSON, data%model) call qn_wp%init (flv_wp, col0) call qn_wm%init (flv_wm, col0) do i = 1, size (data%flv_in) isospin = data%flv_in(i)%get_isospin_type () if (isospin > 0) then !!! up-type quark or neutrinos if (data%flv_in(i)%is_antiparticle ()) then qn_w = qn_wm else qn_w = qn_wp end if else !!! down-type quark or lepton if (data%flv_in(i)%is_antiparticle ()) then qn_w = qn_wp else qn_w = qn_wm end if end if call pol%init_generic (data%flv_in(i)) call qn_fc(1)%init ( & flv = data%flv_in(i), & col = color_from_flavor (data%flv_in(i), 1)) call qn_fc_fin(1)%init ( & flv = data%flv_out(i), & col = color_from_flavor (data%flv_out(i), 1)) call it_hel%init (pol) do while (it_hel%is_valid ()) qn_hel = it_hel%get_quantum_numbers () qn = qn_hel .merge. qn_fc(1) qn_rad = qn_hel .merge. qn_fc_fin(1) call qn_rad%tag_radiated () call sf_int%add_state ([qn, qn_rad, qn_w]) call it_hel%advance () end do ! call pol%final () end do case default call msg_fatal ("EWA initialization failed: wrong particle type.") end select call sf_int%freeze () if (data%keep_energy) then sf_int%on_shell_mode = KEEP_ENERGY else sf_int%on_shell_mode = KEEP_MOMENTUM end if call sf_int%set_incoming ([1]) call sf_int%set_radiated ([2]) call sf_int%set_outgoing ([3]) end select end subroutine ewa_init @ %def ewa_init @ Prepare the coupling arrays. This is separate from the previous routine since the state matrix may be helicity-contracted. <>= procedure :: setup_constants => ewa_setup_constants <>= subroutine ewa_setup_constants (sf_int) class(ewa_t), intent(inout), target :: sf_int type(state_iterator_t) :: it type(flavor_t) :: flv real(default) :: q, t3 integer :: i sf_int%n_me = sf_int%get_n_matrix_elements () allocate (sf_int%cv (sf_int%n_me)) allocate (sf_int%ca (sf_int%n_me)) associate (data => sf_int%data) select case (data%id) case (23) call it%init (sf_int%interaction_t%get_state_matrix_ptr ()) do while (it%is_valid ()) i = it%get_me_index () flv = it%get_flavor (1) q = flv%get_charge () t3 = flv%get_isospin () if (flv%is_antiparticle ()) then sf_int%cv(i) = - data%cv & * (t3 - 2._default * q * data%sinthw**2) / data%costhw sf_int%ca(i) = data%ca * t3 / data%costhw else sf_int%cv(i) = data%cv & * (t3 - 2._default * q * data%sinthw**2) / data%costhw sf_int%ca(i) = data%ca * t3 / data%costhw end if call it%advance () end do case (24) call it%init (sf_int%interaction_t%get_state_matrix_ptr ()) do while (it%is_valid ()) i = it%get_me_index () flv = it%get_flavor (1) if (flv%is_antiparticle ()) then sf_int%cv(i) = data%cv / sqrt(2._default) sf_int%ca(i) = - data%ca / sqrt(2._default) else sf_int%cv(i) = data%cv / sqrt(2._default) sf_int%ca(i) = data%ca / sqrt(2._default) end if call it%advance () end do end select end associate sf_int%status = SF_INITIAL end subroutine ewa_setup_constants @ %def ewa_setup_constants @ \subsection{Kinematics} Set kinematics. The EWA structure function allows for a straightforward mapping of the unit interval. So, to leading order, the structure function value is unity, but the $x$ value is transformed. Higher orders affect the function value. If [[map]] is unset, the $r$ and $x$ values coincide, and the Jacobian $f(r)$ is trivial. If [[map]] is set, the exponential mapping for the $1/x$ singularity discussed above is applied. <>= procedure :: complete_kinematics => ewa_complete_kinematics <>= subroutine ewa_complete_kinematics (sf_int, x, xb, f, r, rb, map) class(ewa_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: x real(default), dimension(:), intent(out) :: xb real(default), intent(out) :: f real(default), dimension(:), intent(in) :: r real(default), dimension(:), intent(in) :: rb logical, intent(in) :: map real(default) :: e_1 real(default) :: x0, x1, lx0, lx1, lx e_1 = energy (sf_int%get_momentum (1)) if (sf_int%data%recoil) then select case (sf_int%data%id) case (23) x0 = max (sf_int%data%x_min, sf_int%data%mz / e_1) case (24) x0 = max (sf_int%data%x_min, sf_int%data%mw / e_1) end select else x0 = sf_int%data%x_min end if x1 = sf_int%data%x_max if ( x0 >= x1) then f = 0 sf_int%status = SF_FAILED_KINEMATICS return end if if (map) then lx0 = log (x0) lx1 = log (x1) lx = lx1 * r(1) + lx0 * rb(1) x(1) = exp(lx) f = x(1) * (lx1 - lx0) else x(1) = r(1) if (x0 < x(1) .and. x(1) < x1) then f = 1 else sf_int%status = SF_FAILED_KINEMATICS f = 0 return end if end if xb(1) = 1 - x(1) if (size(x) == 3) then x(2:3) = r(2:3) xb(2:3) = rb(2:3) end if call sf_int%split_momentum (x, xb) select case (sf_int%status) case (SF_DONE_KINEMATICS) sf_int%x = x(1) sf_int%xb = xb(1) case (SF_FAILED_KINEMATICS) sf_int%x = 0 sf_int%xb = 0 f = 0 end select end subroutine ewa_complete_kinematics @ %def ewa_complete_kinematics @ Overriding the default method: we compute the [[x]] array from the momentum configuration. In the specific case of EWA, we also set the internally stored $x$ and $\bar x$ values, so they can be used in the following routine. <>= procedure :: recover_x => sf_ewa_recover_x <>= subroutine sf_ewa_recover_x (sf_int, x, xb, x_free) class(ewa_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: x real(default), dimension(:), intent(out) :: xb real(default), intent(inout), optional :: x_free call sf_int%base_recover_x (x, xb, x_free) sf_int%x = x(1) sf_int%xb = xb(1) end subroutine sf_ewa_recover_x @ %def sf_ewa_recover_x @ Compute inverse kinematics. Here, we start with the $x$ array and compute the ``input'' $r$ values and the Jacobian $f$. After this, we can set momenta by the same formula as for normal kinematics. <>= procedure :: inverse_kinematics => ewa_inverse_kinematics <>= subroutine ewa_inverse_kinematics (sf_int, x, xb, f, r, rb, map, set_momenta) class(ewa_t), intent(inout) :: sf_int real(default), dimension(:), intent(in) :: x real(default), dimension(:), intent(in) :: xb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: r real(default), dimension(:), intent(out) :: rb logical, intent(in) :: map logical, intent(in), optional :: set_momenta real(default) :: x0, x1, lx0, lx1, lx, e_1 logical :: set_mom set_mom = .false.; if (present (set_momenta)) set_mom = set_momenta e_1 = energy (sf_int%get_momentum (1)) if (sf_int%data%recoil) then select case (sf_int%data%id) case (23) x0 = max (sf_int%data%x_min, sf_int%data%mz / e_1) case (24) x0 = max (sf_int%data%x_min, sf_int%data%mw / e_1) end select else x0 = sf_int%data%x_min end if x1 = sf_int%data%x_max if (map) then lx0 = log (x0) lx1 = log (x1) lx = log (x(1)) r(1) = (lx - lx0) / (lx1 - lx0) rb(1) = (lx1 - lx) / (lx1 - lx0) f = x(1) * (lx1 - lx0) else r (1) = x(1) rb(1) = 1 - x(1) if (x0 < x(1) .and. x(1) < x1) then f = 1 else f = 0 end if end if if (size(r) == 3) then r (2:3) = x(2:3) rb(2:3) = xb(2:3) end if if (set_mom) then call sf_int%split_momentum (x, xb) select case (sf_int%status) case (SF_FAILED_KINEMATICS); f = 0 end select end if end subroutine ewa_inverse_kinematics @ %def ewa_inverse_kinematics @ \subsection{EWA application} For EWA, we can compute kinematics and function value in a single step. This function works on a single beam, assuming that the input momentum has been set. We need four random numbers as input: one for $x$, one for $Q^2$, and two for the polar and azimuthal angles. Alternatively, we can skip $p_T$ generation; in this case, we only need one. For obtaining splitting kinematics, we rely on the assumption that all in-particles are mass-degenerate (or there is only one), so the generated $x$ values are identical. <>= procedure :: apply => ewa_apply <>= subroutine ewa_apply (sf_int, scale, rescale, i_sub) class(ewa_t), intent(inout) :: sf_int real(default), intent(in) :: scale class(sf_rescale_t), intent(in), optional :: rescale integer, intent(in), optional :: i_sub real(default) :: x, xb, pt2, c1, c2 real(default) :: cv, ca real(default) :: f, fm, fp, fL integer :: i associate (data => sf_int%data) x = sf_int%x xb = sf_int%xb pt2 = min ((data%pt_max)**2, (xb * data%sqrts / 2)**2) select case (data%id) case (23) !!! Z boson structure function c1 = log (1 + pt2 / (xb * (data%mZ)**2)) c2 = 1 / (1 + (xb * (data%mZ)**2) / pt2) case (24) !!! W boson structure function c1 = log (1 + pt2 / (xb * (data%mW)**2)) c2 = 1 / (1 + (xb * (data%mW)**2) / pt2) end select do i = 1, sf_int%n_me cv = sf_int%cv(i) ca = sf_int%ca(i) fm = data%coeff * & ((cv + ca)**2 + ((cv - ca) * xb)**2) * (c1 - c2) / (2 * x) fp = data%coeff * & ((cv - ca)**2 + ((cv + ca) * xb)**2) * (c1 - c2) / (2 * x) fL = data%coeff * & (cv**2 + ca**2) * (2 * xb / x) * c2 f = fp + fm + fL if (.not. vanishes (f)) then fp = fp / f fm = fm / f fL = fL / f end if call sf_int%set_matrix_element (i, cmplx (f, kind=default)) end do end associate sf_int%status = SF_EVALUATED end subroutine ewa_apply @ %def ewa_apply @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[sf_ewa_ut.f90]]>>= <> module sf_ewa_ut use unit_tests use sf_ewa_uti <> <> contains <> end module sf_ewa_ut @ %def sf_ewa_ut @ <<[[sf_ewa_uti.f90]]>>= <> module sf_ewa_uti <> use lorentz use pdg_arrays use flavors use interactions, only: reset_interaction_counter use interactions, only: interaction_pacify_momenta use model_data use sf_aux use sf_base use sf_ewa <> <> contains <> end module sf_ewa_uti @ %def sf_ewa_ut @ API: driver for the unit tests below. <>= public :: sf_ewa_test <>= subroutine sf_ewa_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine sf_ewa_test @ %def sf_ewa_test @ \subsubsection{Test structure function data} Construct and display a test structure function data object. <>= call test (sf_ewa_1, "sf_ewa_1", & "structure function configuration", & u, results) <>= public :: sf_ewa_1 <>= subroutine sf_ewa_1 (u) integer, intent(in) :: u type(model_data_t), target :: model type(pdg_array_t) :: pdg_in type(pdg_array_t), dimension(1) :: pdg_out integer, dimension(:), allocatable :: pdg1 class(sf_data_t), allocatable :: data write (u, "(A)") "* Test output: sf_ewa_1" write (u, "(A)") "* Purpose: initialize and display & &test structure function data" write (u, "(A)") write (u, "(A)") "* Create empty data object" write (u, "(A)") call model%init_sm_test () pdg_in = 2 allocate (ewa_data_t :: data) call data%write (u) write (u, "(A)") write (u, "(A)") "* Initialize for Z boson" write (u, "(A)") select type (data) type is (ewa_data_t) call data%init (model, pdg_in, 0.01_default, & 500._default, 5000._default, .false., .false.) call data%set_id (23) end select call data%write (u) write (u, "(A)") write (u, "(1x,A)") "Outgoing particle codes:" call data%get_pdg_out (pdg_out) pdg1 = pdg_out(1) write (u, "(2x,99(1x,I0))") pdg1 write (u, "(A)") write (u, "(A)") "* Initialize for W boson" write (u, "(A)") deallocate (data) allocate (ewa_data_t :: data) select type (data) type is (ewa_data_t) call data%init (model, pdg_in, 0.01_default, & 500._default, 5000._default, .false., .false.) call data%set_id (24) end select call data%write (u) write (u, "(A)") write (u, "(1x,A)") "Outgoing particle codes:" call data%get_pdg_out (pdg_out) pdg1 = pdg_out(1) write (u, "(2x,99(1x,I0))") pdg1 call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_ewa_1" end subroutine sf_ewa_1 @ %def sf_ewa_1 @ \subsubsection{Test and probe structure function} Construct and display a structure function object based on the EWA structure function. <>= call test (sf_ewa_2, "sf_ewa_2", & "structure function instance", & u, results) <>= public :: sf_ewa_2 <>= subroutine sf_ewa_2 (u) integer, intent(in) :: u type(model_data_t), target :: model type(flavor_t) :: flv type(pdg_array_t) :: pdg_in class(sf_data_t), allocatable, target :: data class(sf_int_t), allocatable :: sf_int type(vector4_t) :: k type(vector4_t), dimension(2) :: q real(default) :: E real(default), dimension(:), allocatable :: r, rb, x, xb real(default) :: f write (u, "(A)") "* Test output: sf_ewa_2" write (u, "(A)") "* Purpose: initialize and fill & &test structure function object" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call model%init_sm_test () call flv%init (2, model) pdg_in = 2 call reset_interaction_counter () allocate (ewa_data_t :: data) select type (data) type is (ewa_data_t) call data%init (model, pdg_in, 0.01_default, & 500._default, 3000._default, .false., .true.) call data%set_id (24) end select write (u, "(A)") "* Initialize structure-function object" write (u, "(A)") call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1]) call sf_int%setup_constants () call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Initialize incoming momentum with E=1500" write (u, "(A)") E = 1500 k = vector4_moving (E, sqrt (E**2 - flv%get_mass ()**2), 3) call pacify (k, 1e-10_default) call vector4_write (k, u) call sf_int%seed_kinematics ([k]) write (u, "(A)") write (u, "(A)") "* Set kinematics for r=0.4, no EWA mapping, collinear" write (u, "(A)") allocate (r (data%get_n_par ())) allocate (rb(size (r))) allocate (x (size (r))) allocate (xb(size (r))) r = 0.4_default rb = 1 - r call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Recover x from momenta" write (u, "(A)") q = sf_int%get_momenta (outgoing=.true.) call sf_int%final () deallocate (sf_int) call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1]) call sf_int%setup_constants () call sf_int%seed_kinematics ([k]) call sf_int%set_momenta (q, outgoing=.true.) call sf_int%recover_x (x, xb) call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.false., & set_momenta=.true.) write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Evaluate EWA structure function" write (u, "(A)") call sf_int%apply (scale = 100._default) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call sf_int%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_ewa_2" end subroutine sf_ewa_2 @ %def sf_ewa_2 @ \subsubsection{Standard mapping} Construct and display a structure function object based on the EWA structure function, applying the standard single-particle mapping. <>= call test (sf_ewa_3, "sf_ewa_3", & "apply mapping", & u, results) <>= public :: sf_ewa_3 <>= subroutine sf_ewa_3 (u) integer, intent(in) :: u type(model_data_t), target :: model type(flavor_t) :: flv type(pdg_array_t) :: pdg_in class(sf_data_t), allocatable, target :: data class(sf_int_t), allocatable :: sf_int type(vector4_t) :: k type(vector4_t), dimension(2) :: q real(default) :: E real(default), dimension(:), allocatable :: r, rb, x, xb real(default) :: f write (u, "(A)") "* Test output: sf_ewa_3" write (u, "(A)") "* Purpose: initialize and fill & &test structure function object" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call model%init_sm_test () call flv%init (2, model) pdg_in = 2 call reset_interaction_counter () allocate (ewa_data_t :: data) select type (data) type is (ewa_data_t) call data%init (model, pdg_in, 0.01_default, & 500._default, 3000._default, .false., .true.) call data%set_id (24) end select write (u, "(A)") "* Initialize structure-function object" write (u, "(A)") call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1]) call sf_int%setup_constants () call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Initialize incoming momentum with E=1500" write (u, "(A)") E = 1500 k = vector4_moving (E, sqrt (E**2 - flv%get_mass ()**2), 3) call pacify (k, 1e-10_default) call vector4_write (k, u) call sf_int%seed_kinematics ([k]) write (u, "(A)") write (u, "(A)") "* Set kinematics for r=0.4, with EWA mapping, collinear" write (u, "(A)") allocate (r (data%get_n_par ())) allocate (rb(size (r))) allocate (x (size (r))) allocate (xb(size (r))) r = 0.4_default rb = 1 - r call sf_int%complete_kinematics (x, xb, f, r, rb, map=.true.) write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Recover x from momenta" write (u, "(A)") q = sf_int%get_momenta (outgoing=.true.) call sf_int%final () deallocate (sf_int) call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1]) call sf_int%setup_constants () call sf_int%seed_kinematics ([k]) call sf_int%set_momenta (q, outgoing=.true.) call sf_int%recover_x (x, xb) call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.true., & set_momenta=.true.) write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Evaluate EWA structure function" write (u, "(A)") call sf_int%apply (scale = 100._default) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call sf_int%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_ewa_3" end subroutine sf_ewa_3 @ %def sf_ewa_3 @ \subsubsection{Non-collinear case} Construct and display a structure function object based on the EPA structure function. <>= call test (sf_ewa_4, "sf_ewa_4", & "non-collinear", & u, results) <>= public :: sf_ewa_4 <>= subroutine sf_ewa_4 (u) integer, intent(in) :: u type(model_data_t), target :: model type(flavor_t) :: flv type(pdg_array_t) :: pdg_in class(sf_data_t), allocatable, target :: data class(sf_int_t), allocatable :: sf_int type(vector4_t) :: k type(vector4_t), dimension(2) :: q real(default) :: E real(default), dimension(:), allocatable :: r, rb, x, xb real(default) :: f write (u, "(A)") "* Test output: sf_ewa_4" write (u, "(A)") "* Purpose: initialize and fill & &test structure function object" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call modeL%init_sm_test () call flv%init (2, model) pdg_in = 2 call reset_interaction_counter () allocate (ewa_data_t :: data) select type (data) type is (ewa_data_t) call data%init (model, pdg_in, 0.01_default, & 500._default, 3000.0_default, .true., .true.) call data%set_id (24) end select write (u, "(A)") "* Initialize structure-function object" write (u, "(A)") call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1]) call sf_int%setup_constants () write (u, "(A)") "* Initialize incoming momentum with E=1500" write (u, "(A)") E = 1500 k = vector4_moving (E, sqrt (E**2 - flv%get_mass ()**2), 3) call pacify (k, 1e-10_default) call vector4_write (k, u) call sf_int%seed_kinematics ([k]) write (u, "(A)") write (u, "(A)") "* Set kinematics for r=0.5/0.5/0.25, with EWA mapping, " write (u, "(A)") " non-coll., keeping energy" write (u, "(A)") allocate (r (data%get_n_par ())) allocate (rb(size (r))) allocate (x (size (r))) allocate (xb(size (r))) r = [0.5_default, 0.5_default, 0.25_default] rb = 1 - r sf_int%on_shell_mode = KEEP_ENERGY call sf_int%complete_kinematics (x, xb, f, r, rb, map=.true.) call interaction_pacify_momenta (sf_int%interaction_t, 1e-10_default) write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Recover x and r from momenta" write (u, "(A)") q = sf_int%get_momenta (outgoing=.true.) call sf_int%final () deallocate (sf_int) call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1]) call sf_int%setup_constants () call sf_int%seed_kinematics ([k]) call sf_int%set_momenta (q, outgoing=.true.) call sf_int%recover_x (x, xb) call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.true., & set_momenta=.true.) call interaction_pacify_momenta (sf_int%interaction_t, 1e-10_default) write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Evaluate EWA structure function" write (u, "(A)") call sf_int%apply (scale = 1500._default) call sf_int%write (u, testflag = .true.) write (u, "(A)") write (u, "(A)") "* Cleanup" call sf_int%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_ewa_4" end subroutine sf_ewa_4 @ %def sf_ewa_4 @ \subsubsection{Structure function for multiple flavors} Construct and display a structure function object based on the EWA structure function. The incoming state has multiple particles with non-uniform quantum numbers. <>= call test (sf_ewa_5, "sf_ewa_5", & "structure function instance", & u, results) <>= public :: sf_ewa_5 <>= subroutine sf_ewa_5 (u) integer, intent(in) :: u type(model_data_t), target :: model type(flavor_t) :: flv type(pdg_array_t) :: pdg_in class(sf_data_t), allocatable, target :: data class(sf_int_t), allocatable :: sf_int type(vector4_t) :: k real(default) :: E real(default), dimension(:), allocatable :: r, rb, x, xb real(default) :: f write (u, "(A)") "* Test output: sf_ewa_5" write (u, "(A)") "* Purpose: initialize and fill & &test structure function object" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call model%init_sm_test () call flv%init (2, model) pdg_in = [1, 2, -1, -2] call reset_interaction_counter () allocate (ewa_data_t :: data) select type (data) type is (ewa_data_t) call data%init (model, pdg_in, 0.01_default, & 500._default, 3000._default, .false., .true.) call data%set_id (24) end select write (u, "(A)") "* Initialize structure-function object" write (u, "(A)") call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1]) call sf_int%setup_constants () call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Initialize incoming momentum with E=1500" write (u, "(A)") E = 1500 k = vector4_moving (E, sqrt (E**2 - flv%get_mass ()**2), 3) call pacify (k, 1e-10_default) call vector4_write (k, u) call sf_int%seed_kinematics ([k]) write (u, "(A)") write (u, "(A)") "* Set kinematics for r=0.4, no EWA mapping, collinear" write (u, "(A)") allocate (r (data%get_n_par ())) allocate (rb(size (r))) allocate (x (size (r))) allocate (xb(size (r))) r = 0.4_default rb = 1 - r call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Evaluate EWA structure function" write (u, "(A)") call sf_int%apply (scale = 100._default) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call sf_int%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_ewa_5" end subroutine sf_ewa_5 @ %def sf_ewa_5 @ \clearpage %------------------------------------------------------------------------ \section{Energy-scan spectrum} This spectrum is actually a trick that allows us to plot the c.m.\ energy dependence of a cross section without scanning the input energy. We start with the observation that a spectrum $f(x)$, applied to one of the incoming beams only, results in a cross section \begin{equation} \sigma = \int dx\,f(x)\,\hat\sigma(xs). \end{equation} We want to compute the distribution of $E=\sqrt{\hat s}=\sqrt{xs}$, i.e., \begin{equation} \frac{d\sigma}{dE} = \frac{2\sqrt{x}}{\sqrt{s}}\,\frac{d\sigma}{dx} = \frac{2\sqrt{x}}{\sqrt{s}}\,f(x)\,\hat\sigma(xs), \end{equation} so if we set \begin{equation} f(x) = \frac{\sqrt{s}}{2\sqrt{x}}, \end{equation} we get the distribution \begin{equation} \frac{d\sigma}{dE} = \hat\sigma(\hat s=E^2). \end{equation} We implement this as a spectrum with a single parameter $x$. The parameters for the individual beams are computed as $x_i=\sqrt{x}$, so they are equal and the kinematics is always symmetric. <<[[sf_escan.f90]]>>= <> module sf_escan <> <> use io_units use format_defs, only: FMT_12 use numeric_utils use diagnostics use lorentz use pdg_arrays use model_data use flavors use quantum_numbers use state_matrices use polarizations use sf_base <> <> <> contains <> end module sf_escan @ %def sf_escan @ \subsection{Data type} The [[norm]] is unity if the total cross section should be normalized to one, and $\sqrt{s}$ if it should be normalized to the total energy. In the latter case, the differential distribution $d\sigma/d\sqrt{\hat s}$ coincides with the partonic cross section $\hat\sigma$ as a function of $\sqrt{\hat s}$. <>= public :: escan_data_t <>= type, extends(sf_data_t) :: escan_data_t private type(flavor_t), dimension(:,:), allocatable :: flv_in integer, dimension(2) :: n_flv = 0 real(default) :: norm = 1 contains <> end type escan_data_t @ %def escan_data_t <>= procedure :: init => escan_data_init <>= subroutine escan_data_init (data, model, pdg_in, norm) class(escan_data_t), intent(out) :: data class(model_data_t), intent(in), target :: model type(pdg_array_t), dimension(2), intent(in) :: pdg_in real(default), intent(in), optional :: norm real(default), dimension(2) :: m2 integer :: i, j data%n_flv = pdg_array_get_length (pdg_in) allocate (data%flv_in (maxval (data%n_flv), 2)) do i = 1, 2 do j = 1, data%n_flv(i) call data%flv_in(j, i)%init (pdg_array_get (pdg_in(i), j), model) end do end do m2 = data%flv_in(1,:)%get_mass () do i = 1, 2 if (.not. any (nearly_equal (data%flv_in(1:data%n_flv(i),i)%get_mass (), m2(i)))) then call msg_fatal ("Energy scan: incoming particle mass must be uniform") end if end do if (present (norm)) data%norm = norm end subroutine escan_data_init @ %def escan_data_init @ Output <>= procedure :: write => escan_data_write <>= subroutine escan_data_write (data, unit, verbose) class(escan_data_t), intent(in) :: data integer, intent(in), optional :: unit logical, intent(in), optional :: verbose integer :: u, i, j u = given_output_unit (unit); if (u < 0) return write (u, "(1x,A)") "Energy-scan data:" write (u, "(3x,A)", advance="no") "prt_in = " do i = 1, 2 if (i > 1) write (u, "(',',1x)", advance="no") do j = 1, data%n_flv(i) if (j > 1) write (u, "(':')", advance="no") write (u, "(A)", advance="no") char (data%flv_in(j,i)%get_name ()) end do end do write (u, *) write (u, "(3x,A," // FMT_12 // ")") "norm =", data%norm end subroutine escan_data_write @ %def escan_data_write @ Kinematics is completely collinear, hence there is only one parameter for a pair spectrum. <>= procedure :: get_n_par => escan_data_get_n_par <>= function escan_data_get_n_par (data) result (n) class(escan_data_t), intent(in) :: data integer :: n n = 1 end function escan_data_get_n_par @ %def escan_data_get_n_par @ Return the outgoing particles PDG codes. This is always the same as the incoming particle, where we use two indices for the two beams. <>= procedure :: get_pdg_out => escan_data_get_pdg_out <>= subroutine escan_data_get_pdg_out (data, pdg_out) class(escan_data_t), intent(in) :: data type(pdg_array_t), dimension(:), intent(inout) :: pdg_out integer :: i, n n = 2 do i = 1, n pdg_out(i) = data%flv_in(1:data%n_flv(i),i)%get_pdg () end do end subroutine escan_data_get_pdg_out @ %def escan_data_get_pdg_out @ Allocate the interaction record. <>= procedure :: allocate_sf_int => escan_data_allocate_sf_int <>= subroutine escan_data_allocate_sf_int (data, sf_int) class(escan_data_t), intent(in) :: data class(sf_int_t), intent(inout), allocatable :: sf_int allocate (escan_t :: sf_int) end subroutine escan_data_allocate_sf_int @ %def escan_data_allocate_sf_int @ \subsection{The Energy-scan object} This is a spectrum, not a radiation. We create an interaction with two incoming and two outgoing particles, flavor, color, and helicity being carried through. $x$ nevertheless is only one-dimensional, as we are always using only one beam parameter. <>= type, extends (sf_int_t) :: escan_t type(escan_data_t), pointer :: data => null () contains <> end type escan_t @ %def escan_t @ Type string: for the energy scan this is just a dummy function. <>= procedure :: type_string => escan_type_string <>= function escan_type_string (object) result (string) class(escan_t), intent(in) :: object type(string_t) :: string if (associated (object%data)) then string = "Escan: energy scan" else string = "Escan: [undefined]" end if end function escan_type_string @ %def escan_type_string @ Output. Call the interaction routine after displaying the configuration. <>= procedure :: write => escan_write <>= subroutine escan_write (object, unit, testflag) class(escan_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u u = given_output_unit (unit) if (associated (object%data)) then call object%data%write (u) call object%base_write (u, testflag) else write (u, "(1x,A)") "Energy scan data: [undefined]" end if end subroutine escan_write @ %def escan_write @ <>= procedure :: init => escan_init <>= subroutine escan_init (sf_int, data) class(escan_t), intent(out) :: sf_int class(sf_data_t), intent(in), target :: data type(quantum_numbers_mask_t), dimension(4) :: mask integer, dimension(4) :: hel_lock real(default), dimension(2) :: m2 real(default), dimension(0) :: mr2 type(quantum_numbers_t), dimension(4) :: qn_fc, qn_hel, qn type(polarization_t), target :: pol1, pol2 type(polarization_iterator_t) :: it_hel1, it_hel2 integer :: j1, j2 select type (data) type is (escan_data_t) hel_lock = [3, 4, 1, 2] m2 = data%flv_in(1,:)%get_mass () call sf_int%base_init (mask, m2, mr2, m2, hel_lock = hel_lock) sf_int%data => data do j1 = 1, data%n_flv(1) call qn_fc(1)%init ( & flv = data%flv_in(j1,1), & col = color_from_flavor (data%flv_in(j1,1))) call qn_fc(3)%init ( & flv = data%flv_in(j1,1), & col = color_from_flavor (data%flv_in(j1,1))) call pol1%init_generic (data%flv_in(j1,1)) do j2 = 1, data%n_flv(2) call qn_fc(2)%init ( & flv = data%flv_in(j2,2), & col = color_from_flavor (data%flv_in(j2,2))) call qn_fc(4)%init ( & flv = data%flv_in(j2,2), & col = color_from_flavor (data%flv_in(j2,2))) call pol2%init_generic (data%flv_in(j2,2)) call it_hel1%init (pol1) do while (it_hel1%is_valid ()) qn_hel(1) = it_hel1%get_quantum_numbers () qn_hel(3) = it_hel1%get_quantum_numbers () call it_hel2%init (pol2) do while (it_hel2%is_valid ()) qn_hel(2) = it_hel2%get_quantum_numbers () qn_hel(4) = it_hel2%get_quantum_numbers () qn = qn_hel .merge. qn_fc call sf_int%add_state (qn) call it_hel2%advance () end do call it_hel1%advance () end do ! call pol2%final () end do ! call pol1%final () end do call sf_int%set_incoming ([1,2]) call sf_int%set_outgoing ([3,4]) call sf_int%freeze () sf_int%status = SF_INITIAL end select end subroutine escan_init @ %def escan_init @ \subsection{Kinematics} Set kinematics. We have a single parameter, but reduce both beams. The [[map]] flag is ignored. <>= procedure :: complete_kinematics => escan_complete_kinematics <>= subroutine escan_complete_kinematics (sf_int, x, xb, f, r, rb, map) class(escan_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: x real(default), dimension(:), intent(out) :: xb real(default), intent(out) :: f real(default) :: sqrt_x real(default), dimension(:), intent(in) :: r real(default), dimension(:), intent(in) :: rb logical, intent(in) :: map x = r xb= rb sqrt_x = sqrt (x(1)) if (sqrt_x > 0) then f = 1 / (2 * sqrt_x) else f = 0 sf_int%status = SF_FAILED_KINEMATICS return end if call sf_int%reduce_momenta ([sqrt_x, sqrt_x]) end subroutine escan_complete_kinematics @ %def escan_complete_kinematics @ Recover $x$. The base procedure should return two momentum fractions for the two beams, while we have only one parameter. This is the product of the extracted momentum fractions. <>= procedure :: recover_x => escan_recover_x <>= subroutine escan_recover_x (sf_int, x, xb, x_free) class(escan_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: x real(default), dimension(:), intent(out) :: xb real(default), intent(inout), optional :: x_free real(default), dimension(2) :: xi, xib call sf_int%base_recover_x (xi, xib, x_free) x = product (xi) xb= 1 - x end subroutine escan_recover_x @ %def escan_recover_x @ Compute inverse kinematics. <>= procedure :: inverse_kinematics => escan_inverse_kinematics <>= subroutine escan_inverse_kinematics (sf_int, x, xb, f, r, rb, map, set_momenta) class(escan_t), intent(inout) :: sf_int real(default), dimension(:), intent(in) :: x real(default), dimension(:), intent(in) :: xb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: r real(default), dimension(:), intent(out) :: rb logical, intent(in) :: map logical, intent(in), optional :: set_momenta real(default) :: sqrt_x logical :: set_mom set_mom = .false.; if (present (set_momenta)) set_mom = set_momenta sqrt_x = sqrt (x(1)) if (sqrt_x > 0) then f = 1 / (2 * sqrt_x) else f = 0 sf_int%status = SF_FAILED_KINEMATICS return end if r = x rb = xb if (set_mom) then call sf_int%reduce_momenta ([sqrt_x, sqrt_x]) end if end subroutine escan_inverse_kinematics @ %def escan_inverse_kinematics @ \subsection{Energy scan application} Here, we insert the predefined norm. <>= procedure :: apply => escan_apply <>= subroutine escan_apply (sf_int, scale, rescale, i_sub) class(escan_t), intent(inout) :: sf_int real(default), intent(in) :: scale class(sf_rescale_t), intent(in), optional :: rescale integer, intent(in), optional :: i_sub real(default) :: f associate (data => sf_int%data) f = data%norm end associate call sf_int%set_matrix_element (cmplx (f, kind=default)) sf_int%status = SF_EVALUATED end subroutine escan_apply @ %def escan_apply @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[sf_escan_ut.f90]]>>= <> module sf_escan_ut use unit_tests use sf_escan_uti <> <> contains <> end module sf_escan_ut @ %def sf_escan_ut @ <<[[sf_escan_uti.f90]]>>= <> module sf_escan_uti <> use physics_defs, only: ELECTRON use lorentz use pdg_arrays use flavors use interactions, only: reset_interaction_counter use model_data use sf_aux use sf_base use sf_escan <> <> contains <> end module sf_escan_uti @ %def sf_escan_ut @ API: driver for the unit tests below. <>= public :: sf_escan_test <>= subroutine sf_escan_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine sf_escan_test @ %def sf_escan_test @ \subsubsection{Test structure function data} Construct and display a test structure function data object. <>= call test (sf_escan_1, "sf_escan_1", & "structure function configuration", & u, results) <>= public :: sf_escan_1 <>= subroutine sf_escan_1 (u) integer, intent(in) :: u type(model_data_t), target :: model type(pdg_array_t), dimension(2) :: pdg_in type(pdg_array_t), dimension(2) :: pdg_out integer, dimension(:), allocatable :: pdg1, pdg2 class(sf_data_t), allocatable :: data write (u, "(A)") "* Test output: sf_escan_1" write (u, "(A)") "* Purpose: initialize and display & &energy-scan structure function data" write (u, "(A)") call model%init_qed_test () pdg_in(1) = ELECTRON pdg_in(2) = -ELECTRON allocate (escan_data_t :: data) select type (data) type is (escan_data_t) call data%init (model, pdg_in, norm = 2._default) end select call data%write (u) write (u, "(A)") write (u, "(1x,A)") "Outgoing particle codes:" call data%get_pdg_out (pdg_out) pdg1 = pdg_out(1) pdg2 = pdg_out(2) write (u, "(2x,99(1x,I0))") pdg1, pdg2 call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_escan_1" end subroutine sf_escan_1 @ %def sf_escan_1 g@ \subsubsection{Probe the structure-function object} Active the beam event reader, generate an event. <>= call test (sf_escan_2, "sf_escan_2", & "generate event", & u, results) <>= public :: sf_escan_2 <>= subroutine sf_escan_2 (u) integer, intent(in) :: u type(model_data_t), target :: model type(flavor_t), dimension(2) :: flv type(pdg_array_t), dimension(2) :: pdg_in class(sf_data_t), allocatable, target :: data class(sf_int_t), allocatable :: sf_int type(vector4_t) :: k1, k2 real(default) :: E real(default), dimension(:), allocatable :: r, rb, x, xb real(default) :: x_free, f write (u, "(A)") "* Test output: sf_escan_2" write (u, "(A)") "* Purpose: initialize and display & &beam-events structure function data" write (u, "(A)") call model%init_qed_test () call flv(1)%init (ELECTRON, model) call flv(2)%init (-ELECTRON, model) pdg_in(1) = ELECTRON pdg_in(2) = -ELECTRON call reset_interaction_counter () allocate (escan_data_t :: data) select type (data) type is (escan_data_t) call data%init (model, pdg_in) end select write (u, "(A)") "* Initialize structure-function object" write (u, "(A)") call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1,2]) write (u, "(A)") "* Initialize incoming momentum with E=500" write (u, "(A)") E = 250 k1 = vector4_moving (E, sqrt (E**2 - flv(1)%get_mass ()**2), 3) k2 = vector4_moving (E,-sqrt (E**2 - flv(2)%get_mass ()**2), 3) call vector4_write (k1, u) call vector4_write (k2, u) call sf_int%seed_kinematics ([k1, k2]) write (u, "(A)") write (u, "(A)") "* Set dummy parameters and generate x" write (u, "(A)") allocate (r (data%get_n_par ())) allocate (rb(size (r))) allocate (x (size (r))) allocate (xb(size (r))) r = 0.8 rb = 1 - r x_free = 1 call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A,9(1x,F10.7))") "xf=", x_free write (u, "(A)") write (u, "(A)") "* Inverse kinematics" write (u, "(A)") call sf_int%recover_x (x, xb, x_free) call sf_int%inverse_kinematics (x, xb, f, r, rb, map=.false.) write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A,9(1x,F10.7))") "xf=", x_free write (u, "(A)") write (u, "(A)") "* Evaluate" write (u, "(A)") call sf_int%apply (scale = 0._default) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call sf_int%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_escan_2" end subroutine sf_escan_2 @ %def sf_escan_2 @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Gaussian beam spread} Instead of an analytic beam description, beam data may be provided in form of an event file. In its most simple form, the event file contains pairs of $x$ values, relative to nominal beam energies. More advanced formats may include polarization, etc. The current implementation carries beam polarization through, if specified. The code is very similar to the energy scan described above. However, we must include a file-handle manager for the beam-event files. Two different processes may access a given beam-event file at the same time (i.e., serially but alternating). Accessing an open file from two different units is non-standard and not supported by all compilers. Therefore, we keep a global registry of open files, associated units, and reference counts. The [[gaussian_t]] objects act as proxies to this registry. <<[[sf_gaussian.f90]]>>= <> module sf_gaussian <> <> use io_units use format_defs, only: FMT_12 use file_registries use diagnostics use lorentz use rng_base use pdg_arrays use model_data use flavors use quantum_numbers use state_matrices use polarizations use sf_base <> <> <> contains <> end module sf_gaussian @ %def sf_gaussian @ \subsection{The beam-data file registry} We manage data files via the [[file_registries]] module. To this end, we keep the registry as a private module variable here. <>= type(file_registry_t), save :: beam_file_registry @ %def beam_file_registry @ \subsection{Data type} We store the spread for each beam, as a relative number related to the beam energy. For the actual generation, we include an (abstract) random-number generator factory. <>= public :: gaussian_data_t <>= type, extends(sf_data_t) :: gaussian_data_t private type(flavor_t), dimension(2) :: flv_in real(default), dimension(2) :: spread class(rng_factory_t), allocatable :: rng_factory contains <> end type gaussian_data_t @ %def gaussian_data_t <>= procedure :: init => gaussian_data_init <>= subroutine gaussian_data_init (data, model, pdg_in, spread, rng_factory) class(gaussian_data_t), intent(out) :: data class(model_data_t), intent(in), target :: model type(pdg_array_t), dimension(2), intent(in) :: pdg_in real(default), dimension(2), intent(in) :: spread class(rng_factory_t), intent(inout), allocatable :: rng_factory if (any (spread < 0)) then call msg_fatal ("Gaussian beam spread: must not be negative") end if call data%flv_in(1)%init (pdg_array_get (pdg_in(1), 1), model) call data%flv_in(2)%init (pdg_array_get (pdg_in(2), 1), model) data%spread = spread call move_alloc (from = rng_factory, to = data%rng_factory) end subroutine gaussian_data_init @ %def gaussian_data_init @ Return true since this spectrum is always in generator mode. <>= procedure :: is_generator => gaussian_data_is_generator <>= function gaussian_data_is_generator (data) result (flag) class(gaussian_data_t), intent(in) :: data logical :: flag flag = .true. end function gaussian_data_is_generator @ %def gaussian_data_is_generator @ The number of parameters is two. They are free parameters. <>= procedure :: get_n_par => gaussian_data_get_n_par <>= function gaussian_data_get_n_par (data) result (n) class(gaussian_data_t), intent(in) :: data integer :: n n = 2 end function gaussian_data_get_n_par @ %def gaussian_data_get_n_par <>= procedure :: get_pdg_out => gaussian_data_get_pdg_out <>= subroutine gaussian_data_get_pdg_out (data, pdg_out) class(gaussian_data_t), intent(in) :: data type(pdg_array_t), dimension(:), intent(inout) :: pdg_out integer :: i, n n = 2 do i = 1, n pdg_out(i) = data%flv_in(i)%get_pdg () end do end subroutine gaussian_data_get_pdg_out @ %def gaussian_data_get_pdg_out @ Allocate the interaction record. <>= procedure :: allocate_sf_int => gaussian_data_allocate_sf_int <>= subroutine gaussian_data_allocate_sf_int (data, sf_int) class(gaussian_data_t), intent(in) :: data class(sf_int_t), intent(inout), allocatable :: sf_int allocate (gaussian_t :: sf_int) end subroutine gaussian_data_allocate_sf_int @ %def gaussian_data_allocate_sf_int @ Output <>= procedure :: write => gaussian_data_write <>= subroutine gaussian_data_write (data, unit, verbose) class(gaussian_data_t), intent(in) :: data integer, intent(in), optional :: unit logical, intent(in), optional :: verbose integer :: u u = given_output_unit (unit); if (u < 0) return write (u, "(1x,A)") "Gaussian beam spread data:" write (u, "(3x,A,A,A,A)") "prt_in = ", & char (data%flv_in(1)%get_name ()), & ", ", char (data%flv_in(2)%get_name ()) write (u, "(3x,A,2(1x," // FMT_12 // "))") "spread =", data%spread call data%rng_factory%write (u) end subroutine gaussian_data_write @ %def gaussian_data_write @ \subsection{The gaussian object} Flavor and polarization carried through, no radiated particles. The generator needs a random-number generator, obviously. <>= public :: gaussian_t <>= type, extends (sf_int_t) :: gaussian_t type(gaussian_data_t), pointer :: data => null () class(rng_t), allocatable :: rng contains <> end type gaussian_t @ %def gaussian_t @ Type string: show gaussian file. <>= procedure :: type_string => gaussian_type_string <>= function gaussian_type_string (object) result (string) class(gaussian_t), intent(in) :: object type(string_t) :: string if (associated (object%data)) then string = "Gaussian: gaussian beam-energy spread" else string = "Gaussian: [undefined]" end if end function gaussian_type_string @ %def gaussian_type_string @ Output. Call the interaction routine after displaying the configuration. <>= procedure :: write => gaussian_write <>= subroutine gaussian_write (object, unit, testflag) class(gaussian_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u u = given_output_unit (unit) if (associated (object%data)) then call object%data%write (u) call object%rng%write (u) call object%base_write (u, testflag) else write (u, "(1x,A)") "gaussian data: [undefined]" end if end subroutine gaussian_write @ %def gaussian_write @ <>= procedure :: init => gaussian_init <>= subroutine gaussian_init (sf_int, data) class(gaussian_t), intent(out) :: sf_int class(sf_data_t), intent(in), target :: data real(default), dimension(2) :: m2 real(default), dimension(0) :: mr2 type(quantum_numbers_mask_t), dimension(4) :: mask integer, dimension(4) :: hel_lock type(quantum_numbers_t), dimension(4) :: qn_fc, qn_hel, qn type(polarization_t), target :: pol1, pol2 type(polarization_iterator_t) :: it_hel1, it_hel2 integer :: i select type (data) type is (gaussian_data_t) m2 = data%flv_in%get_mass () ** 2 hel_lock = [3, 4, 1, 2] mask = quantum_numbers_mask (.false., .false., .false.) call sf_int%base_init (mask, m2, mr2, m2, hel_lock = hel_lock) sf_int%data => data do i = 1, 2 call qn_fc(i)%init ( & flv = data%flv_in(i), & col = color_from_flavor (data%flv_in(i))) call qn_fc(i+2)%init ( & flv = data%flv_in(i), & col = color_from_flavor (data%flv_in(i))) end do call pol1%init_generic (data%flv_in(1)) call it_hel1%init (pol1) do while (it_hel1%is_valid ()) qn_hel(1) = it_hel1%get_quantum_numbers () qn_hel(3) = it_hel1%get_quantum_numbers () call pol2%init_generic (data%flv_in(2)) call it_hel2%init (pol2) do while (it_hel2%is_valid ()) qn_hel(2) = it_hel2%get_quantum_numbers () qn_hel(4) = it_hel2%get_quantum_numbers () qn = qn_hel .merge. qn_fc call sf_int%add_state (qn) call it_hel2%advance () end do ! call pol2%final () call it_hel1%advance () end do ! call pol1%final () call sf_int%freeze () call sf_int%set_incoming ([1,2]) call sf_int%set_outgoing ([3,4]) sf_int%status = SF_INITIAL end select call sf_int%data%rng_factory%make (sf_int%rng) end subroutine gaussian_init @ %def gaussian_init @ This spectrum type needs a finalizer, which closes the data file. <>= procedure :: final => sf_gaussian_final <>= subroutine sf_gaussian_final (object) class(gaussian_t), intent(inout) :: object call object%interaction_t%final () end subroutine sf_gaussian_final @ %def sf_gaussian_final @ \subsection{Kinematics} Refer to the [[data]] component. <>= procedure :: is_generator => gaussian_is_generator <>= function gaussian_is_generator (sf_int) result (flag) class(gaussian_t), intent(in) :: sf_int logical :: flag flag = sf_int%data%is_generator () end function gaussian_is_generator @ %def gaussian_is_generator @ Generate free parameters. The $x$ value should be distributed with mean $1$ and $\sigma$ given by the spread. We reject negative $x$ values. (This cut slightly biases the distribution, but for reasonable (small) spreads negative $r$ should not occur. <>= procedure :: generate_free => gaussian_generate_free <>= subroutine gaussian_generate_free (sf_int, r, rb, x_free) class(gaussian_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: r, rb real(default), intent(inout) :: x_free real(default), dimension(size(r)) :: z associate (data => sf_int%data) do call sf_int%rng%generate_gaussian (z) rb = z * data%spread r = 1 - rb x_free = x_free * product (r) if (all (r > 0)) exit end do end associate end subroutine gaussian_generate_free @ %def gaussian_generate_free @ Set kinematics. Trivial transfer since this is a pure generator. The [[map]] flag doesn't apply. <>= procedure :: complete_kinematics => gaussian_complete_kinematics <>= subroutine gaussian_complete_kinematics (sf_int, x, xb, f, r, rb, map) class(gaussian_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: x real(default), dimension(:), intent(out) :: xb real(default), intent(out) :: f real(default), dimension(:), intent(in) :: r real(default), dimension(:), intent(in) :: rb logical, intent(in) :: map if (map) then call msg_fatal ("gaussian: map flag not supported") else x = r xb= rb f = 1 end if call sf_int%reduce_momenta (x) end subroutine gaussian_complete_kinematics @ %def gaussian_complete_kinematics @ Compute inverse kinematics. Trivial in this case. <>= procedure :: inverse_kinematics => gaussian_inverse_kinematics <>= subroutine gaussian_inverse_kinematics & (sf_int, x, xb, f, r, rb, map, set_momenta) class(gaussian_t), intent(inout) :: sf_int real(default), dimension(:), intent(in) :: x real(default), dimension(:), intent(in) :: xb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: r real(default), dimension(:), intent(out) :: rb logical, intent(in) :: map logical, intent(in), optional :: set_momenta logical :: set_mom set_mom = .false.; if (present (set_momenta)) set_mom = set_momenta if (map) then call msg_fatal ("gaussian: map flag not supported") else r = x rb= xb f = 1 end if if (set_mom) then call sf_int%reduce_momenta (x) end if end subroutine gaussian_inverse_kinematics @ %def gaussian_inverse_kinematics @ \subsection{gaussian application} Trivial, just set the unit weight. <>= procedure :: apply => gaussian_apply <>= subroutine gaussian_apply (sf_int, scale, rescale, i_sub) class(gaussian_t), intent(inout) :: sf_int real(default), intent(in) :: scale class(sf_rescale_t), intent(in), optional :: rescale integer, intent(in), optional :: i_sub real(default) :: f f = 1 call sf_int%set_matrix_element (cmplx (f, kind=default)) sf_int%status = SF_EVALUATED end subroutine gaussian_apply @ %def gaussian_apply @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[sf_gaussian_ut.f90]]>>= <> module sf_gaussian_ut use unit_tests use sf_gaussian_uti <> <> contains <> end module sf_gaussian_ut @ %def sf_gaussian_ut @ <<[[sf_gaussian_uti.f90]]>>= <> module sf_gaussian_uti <> use physics_defs, only: ELECTRON use lorentz use pdg_arrays use flavors use interactions, only: reset_interaction_counter use model_data use rng_base use sf_aux use sf_base use sf_gaussian use rng_base_ut, only: rng_test_factory_t <> <> contains <> end module sf_gaussian_uti @ %def sf_gaussian_ut @ API: driver for the unit tests below. <>= public :: sf_gaussian_test <>= subroutine sf_gaussian_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine sf_gaussian_test @ %def sf_gaussian_test @ \subsubsection{Test structure function data} Construct and display a test structure function data object. <>= call test (sf_gaussian_1, "sf_gaussian_1", & "structure function configuration", & u, results) <>= public :: sf_gaussian_1 <>= subroutine sf_gaussian_1 (u) integer, intent(in) :: u type(model_data_t), target :: model type(pdg_array_t), dimension(2) :: pdg_in type(pdg_array_t), dimension(2) :: pdg_out integer, dimension(:), allocatable :: pdg1, pdg2 class(sf_data_t), allocatable :: data class(rng_factory_t), allocatable :: rng_factory write (u, "(A)") "* Test output: sf_gaussian_1" write (u, "(A)") "* Purpose: initialize and display & &gaussian-spread structure function data" write (u, "(A)") call model%init_qed_test () pdg_in(1) = ELECTRON pdg_in(2) = -ELECTRON allocate (gaussian_data_t :: data) allocate (rng_test_factory_t :: rng_factory) select type (data) type is (gaussian_data_t) call data%init (model, pdg_in, [1e-2_default, 2e-2_default], rng_factory) end select call data%write (u) write (u, "(A)") write (u, "(1x,A)") "Outgoing particle codes:" call data%get_pdg_out (pdg_out) pdg1 = pdg_out(1) pdg2 = pdg_out(2) write (u, "(2x,99(1x,I0))") pdg1, pdg2 call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_gaussian_1" end subroutine sf_gaussian_1 @ %def sf_gaussian_1 @ \subsubsection{Probe the structure-function object} Active the beam event reader, generate an event. <>= call test (sf_gaussian_2, "sf_gaussian_2", & "generate event", & u, results) <>= public :: sf_gaussian_2 <>= subroutine sf_gaussian_2 (u) integer, intent(in) :: u type(model_data_t), target :: model type(flavor_t), dimension(2) :: flv type(pdg_array_t), dimension(2) :: pdg_in class(sf_data_t), allocatable, target :: data class(rng_factory_t), allocatable :: rng_factory class(sf_int_t), allocatable :: sf_int type(vector4_t) :: k1, k2 real(default) :: E real(default), dimension(:), allocatable :: r, rb, x, xb real(default) :: x_free, f integer :: i write (u, "(A)") "* Test output: sf_gaussian_2" write (u, "(A)") "* Purpose: initialize and display & &gaussian-spread structure function data" write (u, "(A)") call model%init_qed_test () call flv(1)%init (ELECTRON, model) call flv(2)%init (-ELECTRON, model) pdg_in(1) = ELECTRON pdg_in(2) = -ELECTRON call reset_interaction_counter () allocate (gaussian_data_t :: data) allocate (rng_test_factory_t :: rng_factory) select type (data) type is (gaussian_data_t) call data%init (model, pdg_in, [1e-2_default, 2e-2_default], rng_factory) end select write (u, "(A)") "* Initialize structure-function object" write (u, "(A)") call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1,2]) write (u, "(A)") "* Initialize incoming momentum with E=500" write (u, "(A)") E = 250 k1 = vector4_moving (E, sqrt (E**2 - flv(1)%get_mass ()**2), 3) k2 = vector4_moving (E,-sqrt (E**2 - flv(2)%get_mass ()**2), 3) call vector4_write (k1, u) call vector4_write (k2, u) call sf_int%seed_kinematics ([k1, k2]) write (u, "(A)") write (u, "(A)") "* Set dummy parameters and generate x." write (u, "(A)") allocate (r (data%get_n_par ())) allocate (rb(size (r))) allocate (x (size (r))) allocate (xb(size (r))) r = 0 rb = 0 x_free = 1 call sf_int%generate_free (r, rb, x_free) call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call pacify (rb, 1.e-8_default) call pacify (xb, 1.e-8_default) write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A,9(1x,F10.7))") "xf=", x_free write (u, "(A)") write (u, "(A)") "* Evaluate" write (u, "(A)") call sf_int%apply (scale = 0._default) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Generate more events" write (u, "(A)") select type (sf_int) type is (gaussian_t) do i = 1, 3 call sf_int%generate_free (r, rb, x_free) write (u, "(A,9(1x,F10.7))") "r =", r end do end select write (u, "(A)") write (u, "(A)") "* Cleanup" call sf_int%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_gaussian_2" end subroutine sf_gaussian_2 @ %def sf_gaussian_2 @ \clearpage @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Using beam event data} Instead of an analytic beam description, beam data may be provided in form of an event file. In its most simple form, the event file contains pairs of $x$ values, relative to nominal beam energies. More advanced formats may include polarization, etc. The current implementation carries beam polarization through, if specified. The code is very similar to the energy scan described above. However, we must include a file-handle manager for the beam-event files. Two different processes may access a given beam-event file at the same time (i.e., serially but alternating). Accessing an open file from two different units is non-standard and not supported by all compilers. Therefore, we keep a global registry of open files, associated units, and reference counts. The [[beam_events_t]] objects act as proxies to this registry. <<[[sf_beam_events.f90]]>>= <> module sf_beam_events <> <> use io_units use file_registries use diagnostics use lorentz use pdg_arrays use model_data use flavors use quantum_numbers use state_matrices use polarizations use sf_base <> <> <> <> contains <> end module sf_beam_events @ %def sf_beam_events @ \subsection{The beam-data file registry} We manage data files via the [[file_registries]] module. To this end, we keep the registry as a private module variable here. This is public only for the unit tests. <>= public :: beam_file_registry <>= type(file_registry_t), save :: beam_file_registry @ %def beam_file_registry @ \subsection{Data type} <>= public :: beam_events_data_t <>= type, extends(sf_data_t) :: beam_events_data_t private type(flavor_t), dimension(2) :: flv_in type(string_t) :: dir type(string_t) :: file type(string_t) :: fqn integer :: unit = 0 logical :: warn_eof = .true. contains <> end type beam_events_data_t @ %def beam_events_data_t <>= procedure :: init => beam_events_data_init <>= subroutine beam_events_data_init (data, model, pdg_in, dir, file, warn_eof) class(beam_events_data_t), intent(out) :: data class(model_data_t), intent(in), target :: model type(pdg_array_t), dimension(2), intent(in) :: pdg_in type(string_t), intent(in) :: dir type(string_t), intent(in) :: file logical, intent(in), optional :: warn_eof if (any (pdg_array_get_length (pdg_in) /= 1)) then call msg_fatal ("Beam events: incoming beam particles must be unique") end if call data%flv_in(1)%init (pdg_array_get (pdg_in(1), 1), model) call data%flv_in(2)%init (pdg_array_get (pdg_in(2), 1), model) data%dir = dir data%file = file if (present (warn_eof)) data%warn_eof = warn_eof end subroutine beam_events_data_init @ %def beam_events_data_init @ Return true since this spectrum is always in generator mode. <>= procedure :: is_generator => beam_events_data_is_generator <>= function beam_events_data_is_generator (data) result (flag) class(beam_events_data_t), intent(in) :: data logical :: flag flag = .true. end function beam_events_data_is_generator @ %def beam_events_data_is_generator @ The number of parameters is two. They are free parameters. <>= procedure :: get_n_par => beam_events_data_get_n_par <>= function beam_events_data_get_n_par (data) result (n) class(beam_events_data_t), intent(in) :: data integer :: n n = 2 end function beam_events_data_get_n_par @ %def beam_events_data_get_n_par <>= procedure :: get_pdg_out => beam_events_data_get_pdg_out <>= subroutine beam_events_data_get_pdg_out (data, pdg_out) class(beam_events_data_t), intent(in) :: data type(pdg_array_t), dimension(:), intent(inout) :: pdg_out integer :: i, n n = 2 do i = 1, n pdg_out(i) = data%flv_in(i)%get_pdg () end do end subroutine beam_events_data_get_pdg_out @ %def beam_events_data_get_pdg_out @ Allocate the interaction record. <>= procedure :: allocate_sf_int => beam_events_data_allocate_sf_int <>= subroutine beam_events_data_allocate_sf_int (data, sf_int) class(beam_events_data_t), intent(in) :: data class(sf_int_t), intent(inout), allocatable :: sf_int allocate (beam_events_t :: sf_int) end subroutine beam_events_data_allocate_sf_int @ %def beam_events_data_allocate_sf_int @ Output <>= procedure :: write => beam_events_data_write <>= subroutine beam_events_data_write (data, unit, verbose) class(beam_events_data_t), intent(in) :: data integer, intent(in), optional :: unit logical, intent(in), optional :: verbose integer :: u u = given_output_unit (unit); if (u < 0) return write (u, "(1x,A)") "Beam-event file data:" write (u, "(3x,A,A,A,A)") "prt_in = ", & char (data%flv_in(1)%get_name ()), & ", ", char (data%flv_in(2)%get_name ()) write (u, "(3x,A,A,A)") "file = '", char (data%file), "'" write (u, "(3x,A,I0)") "unit = ", data%unit write (u, "(3x,A,L1)") "warn = ", data%warn_eof end subroutine beam_events_data_write @ %def beam_events_data_write @ The data file needs to be opened and closed explicitly. The open/close message is communicated to the file handle registry, which does the actual work. We determine first whether to look in the local directory or in the given system directory. <>= procedure :: open => beam_events_data_open procedure :: close => beam_events_data_close <>= subroutine beam_events_data_open (data) class(beam_events_data_t), intent(inout) :: data logical :: exist if (data%unit == 0) then data%fqn = data%file if (data%fqn == "") & call msg_fatal ("Beam events: $beam_events_file is not set") inquire (file = char (data%fqn), exist = exist) if (.not. exist) then data%fqn = data%dir // "/" // data%file inquire (file = char (data%fqn), exist = exist) if (.not. exist) then data%fqn = "" call msg_fatal ("Beam events: file '" & // char (data%file) // "' not found") return end if end if call msg_message ("Beam events: reading from file '" & // char (data%file) // "'") call beam_file_registry%open (data%fqn, data%unit) else call msg_bug ("Beam events: file '" & // char (data%file) // "' is already open") end if end subroutine beam_events_data_open subroutine beam_events_data_close (data) class(beam_events_data_t), intent(inout) :: data if (data%unit /= 0) then call beam_file_registry%close (data%fqn) call msg_message ("Beam events: closed file '" & // char (data%file) // "'") data%unit = 0 end if end subroutine beam_events_data_close @ %def beam_events_data_close @ Return the beam event file. <>= procedure :: get_beam_file => beam_events_data_get_beam_file <>= function beam_events_data_get_beam_file (data) result (file) class(beam_events_data_t), intent(in) :: data type(string_t) :: file file = "Beam events: " // data%file end function beam_events_data_get_beam_file @ %def beam_events_data_get_beam_file @ \subsection{The beam events object} Flavor and polarization carried through, no radiated particles. <>= public :: beam_events_t <>= type, extends (sf_int_t) :: beam_events_t type(beam_events_data_t), pointer :: data => null () integer :: count = 0 contains <> end type beam_events_t @ %def beam_events_t @ Type string: show beam events file. <>= procedure :: type_string => beam_events_type_string <>= function beam_events_type_string (object) result (string) class(beam_events_t), intent(in) :: object type(string_t) :: string if (associated (object%data)) then string = "Beam events: " // object%data%file else string = "Beam events: [undefined]" end if end function beam_events_type_string @ %def beam_events_type_string @ Output. Call the interaction routine after displaying the configuration. <>= procedure :: write => beam_events_write <>= subroutine beam_events_write (object, unit, testflag) class(beam_events_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u u = given_output_unit (unit) if (associated (object%data)) then call object%data%write (u) call object%base_write (u, testflag) else write (u, "(1x,A)") "Beam events data: [undefined]" end if end subroutine beam_events_write @ %def beam_events_write @ <>= procedure :: init => beam_events_init <>= subroutine beam_events_init (sf_int, data) class(beam_events_t), intent(out) :: sf_int class(sf_data_t), intent(in), target :: data real(default), dimension(2) :: m2 real(default), dimension(0) :: mr2 type(quantum_numbers_mask_t), dimension(4) :: mask integer, dimension(4) :: hel_lock type(quantum_numbers_t), dimension(4) :: qn_fc, qn_hel, qn type(polarization_t), target :: pol1, pol2 type(polarization_iterator_t) :: it_hel1, it_hel2 integer :: i select type (data) type is (beam_events_data_t) m2 = data%flv_in%get_mass () ** 2 hel_lock = [3, 4, 1, 2] mask = quantum_numbers_mask (.false., .false., .false.) call sf_int%base_init (mask, m2, mr2, m2, hel_lock = hel_lock) sf_int%data => data do i = 1, 2 call qn_fc(i)%init ( & flv = data%flv_in(i), & col = color_from_flavor (data%flv_in(i))) call qn_fc(i+2)%init ( & flv = data%flv_in(i), & col = color_from_flavor (data%flv_in(i))) end do call pol1%init_generic (data%flv_in(1)) call it_hel1%init (pol1) do while (it_hel1%is_valid ()) qn_hel(1) = it_hel1%get_quantum_numbers () qn_hel(3) = it_hel1%get_quantum_numbers () call pol2%init_generic (data%flv_in(2)) call it_hel2%init (pol2) do while (it_hel2%is_valid ()) qn_hel(2) = it_hel2%get_quantum_numbers () qn_hel(4) = it_hel2%get_quantum_numbers () qn = qn_hel .merge. qn_fc call sf_int%add_state (qn) call it_hel2%advance () end do ! call pol2%final () call it_hel1%advance () end do ! call pol1%final () call sf_int%freeze () call sf_int%set_incoming ([1,2]) call sf_int%set_outgoing ([3,4]) call sf_int%data%open () sf_int%status = SF_INITIAL end select end subroutine beam_events_init @ %def beam_events_init @ This spectrum type needs a finalizer, which closes the data file. <>= procedure :: final => sf_beam_events_final <>= subroutine sf_beam_events_final (object) class(beam_events_t), intent(inout) :: object call object%data%close () call object%interaction_t%final () end subroutine sf_beam_events_final @ %def sf_beam_events_final @ \subsection{Kinematics} Refer to the [[data]] component. <>= procedure :: is_generator => beam_events_is_generator <>= function beam_events_is_generator (sf_int) result (flag) class(beam_events_t), intent(in) :: sf_int logical :: flag flag = sf_int%data%is_generator () end function beam_events_is_generator @ %def beam_events_is_generator @ Generate free parameters. We read them from file. <>= procedure :: generate_free => beam_events_generate_free <>= recursive subroutine beam_events_generate_free (sf_int, r, rb, x_free) class(beam_events_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: r, rb real(default), intent(inout) :: x_free integer :: iostat associate (data => sf_int%data) if (data%unit /= 0) then read (data%unit, fmt=*, iostat=iostat) r if (iostat > 0) then write (msg_buffer, "(A,I0,A)") & "Beam events: I/O error after reading ", sf_int%count, & " events" call msg_fatal () else if (iostat < 0) then if (sf_int%count == 0) then call msg_fatal ("Beam events: file is empty") else if (sf_int%data%warn_eof) then write (msg_buffer, "(A,I0,A)") & "Beam events: End of file after reading ", sf_int%count, & " events, rewinding" call msg_warning () end if rewind (data%unit) sf_int%count = 0 call sf_int%generate_free (r, rb, x_free) else sf_int%count = sf_int%count + 1 rb = 1 - r x_free = x_free * product (r) end if else call msg_bug ("Beam events: file is not open for reading") end if end associate end subroutine beam_events_generate_free @ %def beam_events_generate_free @ Set kinematics. Trivial transfer since this is a pure generator. The [[map]] flag doesn't apply. <>= procedure :: complete_kinematics => beam_events_complete_kinematics <>= subroutine beam_events_complete_kinematics (sf_int, x, xb, f, r, rb, map) class(beam_events_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: x real(default), dimension(:), intent(out) :: xb real(default), intent(out) :: f real(default), dimension(:), intent(in) :: r real(default), dimension(:), intent(in) :: rb logical, intent(in) :: map if (map) then call msg_fatal ("Beam events: map flag not supported") else x = r xb= rb f = 1 end if call sf_int%reduce_momenta (x) end subroutine beam_events_complete_kinematics @ %def beam_events_complete_kinematics @ Compute inverse kinematics. Trivial in this case. <>= procedure :: inverse_kinematics => beam_events_inverse_kinematics <>= subroutine beam_events_inverse_kinematics & (sf_int, x, xb, f, r, rb, map, set_momenta) class(beam_events_t), intent(inout) :: sf_int real(default), dimension(:), intent(in) :: x real(default), dimension(:), intent(in) :: xb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: r real(default), dimension(:), intent(out) :: rb logical, intent(in) :: map logical, intent(in), optional :: set_momenta logical :: set_mom set_mom = .false.; if (present (set_momenta)) set_mom = set_momenta if (map) then call msg_fatal ("Beam events: map flag not supported") else r = x rb= xb f = 1 end if if (set_mom) then call sf_int%reduce_momenta (x) end if end subroutine beam_events_inverse_kinematics @ %def beam_events_inverse_kinematics @ \subsection{Beam events application} Trivial, just set the unit weight. <>= procedure :: apply => beam_events_apply <>= subroutine beam_events_apply (sf_int, scale, rescale, i_sub) class(beam_events_t), intent(inout) :: sf_int real(default), intent(in) :: scale class(sf_rescale_t), intent(in), optional :: rescale integer, intent(in), optional :: i_sub real(default) :: f f = 1 call sf_int%set_matrix_element (cmplx (f, kind=default)) sf_int%status = SF_EVALUATED end subroutine beam_events_apply @ %def beam_events_apply @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[sf_beam_events_ut.f90]]>>= <> module sf_beam_events_ut use unit_tests use sf_beam_events_uti <> <> contains <> end module sf_beam_events_ut @ %def sf_beam_events_ut @ <<[[sf_beam_events_uti.f90]]>>= <> module sf_beam_events_uti <> <> use io_units use physics_defs, only: ELECTRON use lorentz use pdg_arrays use flavors use interactions, only: reset_interaction_counter use model_data use sf_aux use sf_base use sf_beam_events <> <> contains <> end module sf_beam_events_uti @ %def sf_beam_events_ut @ API: driver for the unit tests below. <>= public :: sf_beam_events_test <>= subroutine sf_beam_events_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine sf_beam_events_test @ %def sf_beam_events_test @ \subsubsection{Test structure function data} Construct and display a test structure function data object. <>= call test (sf_beam_events_1, "sf_beam_events_1", & "structure function configuration", & u, results) <>= public :: sf_beam_events_1 <>= subroutine sf_beam_events_1 (u) integer, intent(in) :: u type(model_data_t), target :: model type(pdg_array_t), dimension(2) :: pdg_in type(pdg_array_t), dimension(2) :: pdg_out integer, dimension(:), allocatable :: pdg1, pdg2 class(sf_data_t), allocatable :: data write (u, "(A)") "* Test output: sf_beam_events_1" write (u, "(A)") "* Purpose: initialize and display & &beam-events structure function data" write (u, "(A)") call model%init_qed_test () pdg_in(1) = ELECTRON pdg_in(2) = -ELECTRON allocate (beam_events_data_t :: data) select type (data) type is (beam_events_data_t) call data%init (model, pdg_in, var_str (""), var_str ("beam_events.dat")) end select call data%write (u) write (u, "(A)") write (u, "(1x,A)") "Outgoing particle codes:" call data%get_pdg_out (pdg_out) pdg1 = pdg_out(1) pdg2 = pdg_out(2) write (u, "(2x,99(1x,I0))") pdg1, pdg2 call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_beam_events_1" end subroutine sf_beam_events_1 @ %def sf_beam_events_1 @ \subsubsection{Probe the structure-function object} Active the beam event reader, generate an event. <>= call test (sf_beam_events_2, "sf_beam_events_2", & "generate event", & u, results) <>= public :: sf_beam_events_2 <>= subroutine sf_beam_events_2 (u) integer, intent(in) :: u type(model_data_t), target :: model type(flavor_t), dimension(2) :: flv type(pdg_array_t), dimension(2) :: pdg_in class(sf_data_t), allocatable, target :: data class(sf_int_t), allocatable :: sf_int type(vector4_t) :: k1, k2 real(default) :: E real(default), dimension(:), allocatable :: r, rb, x, xb real(default) :: x_free, f integer :: i write (u, "(A)") "* Test output: sf_beam_events_2" write (u, "(A)") "* Purpose: initialize and display & &beam-events structure function data" write (u, "(A)") call model%init_qed_test () call flv(1)%init (ELECTRON, model) call flv(2)%init (-ELECTRON, model) pdg_in(1) = ELECTRON pdg_in(2) = -ELECTRON call reset_interaction_counter () allocate (beam_events_data_t :: data) select type (data) type is (beam_events_data_t) call data%init (model, pdg_in, & var_str (""), var_str ("test_beam_events.dat")) end select write (u, "(A)") "* Initialize structure-function object" write (u, "(A)") call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1,2]) write (u, "(A)") "* Initialize incoming momentum with E=500" write (u, "(A)") E = 250 k1 = vector4_moving (E, sqrt (E**2 - flv(1)%get_mass ()**2), 3) k2 = vector4_moving (E,-sqrt (E**2 - flv(2)%get_mass ()**2), 3) call vector4_write (k1, u) call vector4_write (k2, u) call sf_int%seed_kinematics ([k1, k2]) write (u, "(A)") write (u, "(A)") "* Set dummy parameters and generate x." write (u, "(A)") allocate (r (data%get_n_par ())) allocate (rb(size (r))) allocate (x (size (r))) allocate (xb(size (r))) r = 0 rb = 0 x_free = 1 call sf_int%generate_free (r, rb, x_free) call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,9(1x,F10.7))") "rb=", rb write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A,9(1x,F10.7))") "xf=", x_free select type (sf_int) type is (beam_events_t) write (u, "(A,1x,I0)") "count =", sf_int%count end select write (u, "(A)") write (u, "(A)") "* Evaluate" write (u, "(A)") call sf_int%apply (scale = 0._default) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Generate more events, rewind" write (u, "(A)") select type (sf_int) type is (beam_events_t) do i = 1, 3 call sf_int%generate_free (r, rb, x_free) write (u, "(A,9(1x,F10.7))") "r =", r write (u, "(A,1x,I0)") "count =", sf_int%count end do end select write (u, "(A)") write (u, "(A)") "* Cleanup" call sf_int%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_beam_events_2" end subroutine sf_beam_events_2 @ %def sf_beam_events_2 @ \subsubsection{Check the file handle registry} Open and close some files, checking the registry contents. <>= call test (sf_beam_events_3, "sf_beam_events_3", & "check registry", & u, results) <>= public :: sf_beam_events_3 <>= subroutine sf_beam_events_3 (u) integer, intent(in) :: u integer :: u1 write (u, "(A)") "* Test output: sf_beam_events_2" write (u, "(A)") "* Purpose: check file handle registry" write (u, "(A)") write (u, "(A)") "* Create some empty files" write (u, "(A)") u1 = free_unit () open (u1, file = "sf_beam_events_f1.tmp", action="write", status="new") close (u1) open (u1, file = "sf_beam_events_f2.tmp", action="write", status="new") close (u1) open (u1, file = "sf_beam_events_f3.tmp", action="write", status="new") close (u1) write (u, "(A)") "* Empty registry" write (u, "(A)") call beam_file_registry%write (u) write (u, "(A)") write (u, "(A)") "* Insert three entries" write (u, "(A)") call beam_file_registry%open (var_str ("sf_beam_events_f3.tmp")) call beam_file_registry%open (var_str ("sf_beam_events_f2.tmp")) call beam_file_registry%open (var_str ("sf_beam_events_f1.tmp")) call beam_file_registry%write (u) write (u, "(A)") write (u, "(A)") "* Open a second channel" write (u, "(A)") call beam_file_registry%open (var_str ("sf_beam_events_f2.tmp")) call beam_file_registry%write (u) write (u, "(A)") write (u, "(A)") "* Close second entry twice" write (u, "(A)") call beam_file_registry%close (var_str ("sf_beam_events_f2.tmp")) call beam_file_registry%close (var_str ("sf_beam_events_f2.tmp")) call beam_file_registry%write (u) write (u, "(A)") write (u, "(A)") "* Close last entry" write (u, "(A)") call beam_file_registry%close (var_str ("sf_beam_events_f3.tmp")) call beam_file_registry%write (u) write (u, "(A)") write (u, "(A)") "* Close remaining entry" write (u, "(A)") call beam_file_registry%close (var_str ("sf_beam_events_f1.tmp")) call beam_file_registry%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" open (u1, file = "sf_beam_events_f1.tmp", action="write") close (u1, status = "delete") open (u1, file = "sf_beam_events_f2.tmp", action="write") close (u1, status = "delete") open (u1, file = "sf_beam_events_f3.tmp", action="write") close (u1, status = "delete") write (u, "(A)") write (u, "(A)") "* Test output end: sf_beam_events_3" end subroutine sf_beam_events_3 @ %def sf_beam_events_3 @ \clearpage %------------------------------------------------------------------------ \section{Lepton collider beamstrahlung: CIRCE1} <<[[sf_circe1.f90]]>>= <> module sf_circe1 <> use kinds, only: double <> use io_units use format_defs, only: FMT_17, FMT_19 use diagnostics use physics_defs, only: ELECTRON, PHOTON use lorentz use rng_base use pdg_arrays use model_data use flavors use colors use quantum_numbers use state_matrices use polarizations use sf_mappings use sf_base use circe1, circe1_rng_t => rng_type !NODEP! <> <> <> contains <> end module sf_circe1 @ %def sf_circe1 @ \subsection{Physics} Beamstrahlung is applied before ISR. The [[CIRCE1]] implementation has a single structure function for both beams (which makes sense since it has to be switched on or off for both beams simultaneously). Nevertheless it is factorized: The functional form in the [[CIRCE1]] parameterization is defined for electrons or photons \begin{equation} f(x) = \alpha\,x^\beta\,(1-x)^\gamma \end{equation} for $x<1-\epsilon$ (resp.\ $x>\epsilon$ in the photon case). In the remaining interval, the standard form is zero, with a delta singularity at $x=1$ (resp.\ $x=0$). Equivalently, the delta part may be distributed uniformly among this interval. This latter form is implemented in the [[kirke]] version of the [[CIRCE1]] subroutines, and is used here. The parameter [[circe1\_eps]] sets the peak mapping of the [[CIRCE1]] structure function. Its default value is $10^{-5}$. The other parameters are the parameterization version and revision number, the accelerator type, and the $\sqrt{s}$ value used by [[CIRCE1]]. The chattiness can also be set. Since the energy is distributed in a narrow region around unity (for electrons) or zero (for photons), it is advantageous to map the interval first. The mapping is controlled by the parameter [[circe1\_epsilon]] which is taken from the [[CIRCE1]] internal data structure. The $\sqrt{s}$ value, if not explicitly set, is taken from the process data. Note that interpolating $\sqrt{s}$ is not recommended; one should rather choose one of the distinct values known to [[CIRCE1]]. \subsection{The CIRCE1 data block} The CIRCE1 parameters are: The incoming flavors, the flags whether the photon or the lepton is the parton in the hard interaction, the flags for the generation mode (generator/mapping/no mapping), the mapping parameter $\epsilon$, $\sqrt{s}$ and several steering parameters: [[ver]], [[rev]], [[acc]], [[chat]]. In generator mode, the $x$ values are actually discarded and a random number generator is used instead. <>= public :: circe1_data_t <>= type, extends (sf_data_t) :: circe1_data_t private class(model_data_t), pointer :: model => null () type(flavor_t), dimension(2) :: flv_in integer, dimension(2) :: pdg_in real(default), dimension(2) :: m_in = 0 logical, dimension(2) :: photon = .false. logical :: generate = .false. class(rng_factory_t), allocatable :: rng_factory real(default) :: sqrts = 0 real(default) :: eps = 0 integer :: ver = 0 integer :: rev = 0 character(6) :: acc = "?" integer :: chat = 0 logical :: with_radiation = .false. contains <> end type circe1_data_t @ %def circe1_data_t @ <>= procedure :: init => circe1_data_init <>= subroutine circe1_data_init & (data, model, pdg_in, sqrts, eps, out_photon, & ver, rev, acc, chat, with_radiation) class(circe1_data_t), intent(out) :: data class(model_data_t), intent(in), target :: model type(pdg_array_t), dimension(2), intent(in) :: pdg_in real(default), intent(in) :: sqrts real(default), intent(in) :: eps logical, dimension(2), intent(in) :: out_photon character(*), intent(in) :: acc integer, intent(in) :: ver, rev, chat logical, intent(in) :: with_radiation data%model => model if (any (pdg_array_get_length (pdg_in) /= 1)) then call msg_fatal ("CIRCE1: incoming beam particles must be unique") end if call data%flv_in(1)%init (pdg_array_get (pdg_in(1), 1), model) call data%flv_in(2)%init (pdg_array_get (pdg_in(2), 1), model) data%pdg_in = data%flv_in%get_pdg () data%m_in = data%flv_in%get_mass () data%sqrts = sqrts data%eps = eps data%photon = out_photon data%ver = ver data%rev = rev data%acc = acc data%chat = chat data%with_radiation = with_radiation call data%check () call circex (0.d0, 0.d0, dble (data%sqrts), & data%acc, data%ver, data%rev, data%chat) end subroutine circe1_data_init @ %def circe1_data_init @ Activate the generator mode. We import a RNG factory into the data type, which can then spawn RNG generator objects. <>= procedure :: set_generator_mode => circe1_data_set_generator_mode <>= subroutine circe1_data_set_generator_mode (data, rng_factory) class(circe1_data_t), intent(inout) :: data class(rng_factory_t), intent(inout), allocatable :: rng_factory data%generate = .true. call move_alloc (from = rng_factory, to = data%rng_factory) end subroutine circe1_data_set_generator_mode @ %def circe1_data_set_generator_mode @ Handle error conditions. <>= procedure :: check => circe1_data_check <>= subroutine circe1_data_check (data) class(circe1_data_t), intent(in) :: data type(flavor_t) :: flv_electron, flv_photon call flv_electron%init (ELECTRON, data%model) call flv_photon%init (PHOTON, data%model) if (.not. flv_electron%is_defined () & .or. .not. flv_photon%is_defined ()) then call msg_fatal ("CIRCE1: model must contain photon and electron") end if if (any (abs (data%pdg_in) /= ELECTRON) & .or. (data%pdg_in(1) /= - data%pdg_in(2))) then call msg_fatal ("CIRCE1: applicable only for e+e- or e-e+ collisions") end if if (data%eps <= 0) then call msg_error ("CIRCE1: circe1_eps = 0: integration will & &miss x=1 peak") end if end subroutine circe1_data_check @ %def circe1_data_check @ Output <>= procedure :: write => circe1_data_write <>= subroutine circe1_data_write (data, unit, verbose) class(circe1_data_t), intent(in) :: data integer, intent(in), optional :: unit logical, intent(in), optional :: verbose integer :: u logical :: verb verb = .false.; if (present (verbose)) verb = verbose u = given_output_unit (unit); if (u < 0) return write (u, "(1x,A)") "CIRCE1 data:" write (u, "(3x,A,2(1x,A))") "prt_in =", & char (data%flv_in(1)%get_name ()), & char (data%flv_in(2)%get_name ()) write (u, "(3x,A,2(1x,L1))") "photon =", data%photon write (u, "(3x,A,L1)") "generate = ", data%generate write (u, "(3x,A,2(1x," // FMT_19 // "))") "m_in =", data%m_in write (u, "(3x,A," // FMT_19 // ")") "sqrts = ", data%sqrts write (u, "(3x,A," // FMT_19 // ")") "eps = ", data%eps write (u, "(3x,A,I0)") "ver = ", data%ver write (u, "(3x,A,I0)") "rev = ", data%rev write (u, "(3x,A,A)") "acc = ", data%acc write (u, "(3x,A,I0)") "chat = ", data%chat write (u, "(3x,A,L1)") "with rad.= ", data%with_radiation if (data%generate) then if (verb) then call data%rng_factory%write (u) end if end if end subroutine circe1_data_write @ %def circe1_data_write @ Return true if this structure function is in generator mode. In that case, all parameters are free, otherwise bound. (We do not support mixed cases.) Default is: no generator. <>= procedure :: is_generator => circe1_data_is_generator <>= function circe1_data_is_generator (data) result (flag) class(circe1_data_t), intent(in) :: data logical :: flag flag = data%generate end function circe1_data_is_generator @ %def circe1_data_is_generator @ The number of parameters is two, collinear splitting for the two beams. <>= procedure :: get_n_par => circe1_data_get_n_par <>= function circe1_data_get_n_par (data) result (n) class(circe1_data_t), intent(in) :: data integer :: n n = 2 end function circe1_data_get_n_par @ %def circe1_data_get_n_par @ Return the outgoing particles PDG codes. This is either the incoming particle (if a photon is radiated), or the photon if that is the particle of the hard interaction. The latter is determined via the [[photon]] flag. There are two entries for the two beams. <>= procedure :: get_pdg_out => circe1_data_get_pdg_out <>= subroutine circe1_data_get_pdg_out (data, pdg_out) class(circe1_data_t), intent(in) :: data type(pdg_array_t), dimension(:), intent(inout) :: pdg_out integer :: i, n n = 2 do i = 1, n if (data%photon(i)) then pdg_out(i) = PHOTON else pdg_out(i) = data%pdg_in(i) end if end do end subroutine circe1_data_get_pdg_out @ %def circe1_data_get_pdg_out @ This variant is not inherited, it returns integers. <>= procedure :: get_pdg_int => circe1_data_get_pdg_int <>= function circe1_data_get_pdg_int (data) result (pdg) class(circe1_data_t), intent(in) :: data integer, dimension(2) :: pdg integer :: i do i = 1, 2 if (data%photon(i)) then pdg(i) = PHOTON else pdg(i) = data%pdg_in(i) end if end do end function circe1_data_get_pdg_int @ %def circe1_data_get_pdg_int @ Allocate the interaction record. <>= procedure :: allocate_sf_int => circe1_data_allocate_sf_int <>= subroutine circe1_data_allocate_sf_int (data, sf_int) class(circe1_data_t), intent(in) :: data class(sf_int_t), intent(inout), allocatable :: sf_int allocate (circe1_t :: sf_int) end subroutine circe1_data_allocate_sf_int @ %def circe1_data_allocate_sf_int @ Return the accelerator type. <>= procedure :: get_beam_file => circe1_data_get_beam_file <>= function circe1_data_get_beam_file (data) result (file) class(circe1_data_t), intent(in) :: data type(string_t) :: file file = "CIRCE1: " // data%acc end function circe1_data_get_beam_file @ %def circe1_data_get_beam_file @ \subsection{Random Number Generator for CIRCE} The CIRCE implementation now supports a generic random-number generator object that allows for a local state as a component. To support this, we must extend the abstract type provided by CIRCE and delegate the generator call to the (also abstract) RNG used by WHIZARD. <>= type, extends (circe1_rng_t) :: rng_obj_t class(rng_t), allocatable :: rng contains procedure :: generate => rng_obj_generate end type rng_obj_t @ %def rng_obj_t <>= subroutine rng_obj_generate (rng_obj, u) class(rng_obj_t), intent(inout) :: rng_obj real(double), intent(out) :: u real(default) :: x call rng_obj%rng%generate (x) u = x end subroutine rng_obj_generate @ %def rng_obj_generate @ \subsection{The CIRCE1 object} This is a $2\to 4$ interaction, where, depending on the parameters, any two of the four outgoing particles are connected to the hard interactions, the others are radiated. Knowing that all particles are colorless, we do not have to deal with color. The flavors are sorted such that the first two particles are the incoming leptons, the next two are the radiated particles, and the last two are the partons initiating the hard interaction. CIRCE1 does not support polarized beams explicitly. For simplicity, we nevertheless carry beam polarization through to the outgoing electrons and make the photons unpolarized. In the case that no radiated particle is kept (which actually is the default), polarization is always transferred to the electrons, too. If there is a recoil photon in the event, the radiated particles are 3 and 4, respectively, and 5 and 6 are the outgoing ones (triggering the hard scattering process), while in the case of no radiation, the outgoing particles are 3 and 4, respectively. In the case of the electron being the radiated particle, helicity is not kept. <>= public :: circe1_t <>= type, extends (sf_int_t) :: circe1_t type(circe1_data_t), pointer :: data => null () real(default), dimension(2) :: x = 0 real(default), dimension(2) :: xb= 0 real(default) :: f = 0 logical, dimension(2) :: continuum = .true. logical, dimension(2) :: peak = .true. type(rng_obj_t) :: rng_obj contains <> end type circe1_t @ %def circe1_t @ Type string: has to be here, but there is no string variable on which CIRCE1 depends. Hence, a dummy routine. <>= procedure :: type_string => circe1_type_string <>= function circe1_type_string (object) result (string) class(circe1_t), intent(in) :: object type(string_t) :: string if (associated (object%data)) then string = "CIRCE1: beamstrahlung" else string = "CIRCE1: [undefined]" end if end function circe1_type_string @ %def circe1_type_string @ Output. Call the interaction routine after displaying the configuration. <>= procedure :: write => circe1_write <>= subroutine circe1_write (object, unit, testflag) class(circe1_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u u = given_output_unit (unit) if (associated (object%data)) then call object%data%write (u) if (object%data%generate) call object%rng_obj%rng%write (u) if (object%status >= SF_DONE_KINEMATICS) then write (u, "(3x,A,2(1x," // FMT_17 // "))") "x =", object%x write (u, "(3x,A,2(1x," // FMT_17 // "))") "xb=", object%xb if (object%status >= SF_FAILED_EVALUATION) then write (u, "(3x,A,1x," // FMT_17 // ")") "f =", object%f end if end if call object%base_write (u, testflag) else write (u, "(1x,A)") "CIRCE1 data: [undefined]" end if end subroutine circe1_write @ %def circe1_write @ <>= procedure :: init => circe1_init <>= subroutine circe1_init (sf_int, data) class(circe1_t), intent(out) :: sf_int class(sf_data_t), intent(in), target :: data logical, dimension(6) :: mask_h type(quantum_numbers_mask_t), dimension(6) :: mask integer, dimension(6) :: hel_lock type(polarization_t), target :: pol1, pol2 type(quantum_numbers_t), dimension(1) :: qn_fc1, qn_fc2 type(flavor_t) :: flv_photon type(color_t) :: col0 real(default), dimension(2) :: mi2, mr2, mo2 type(quantum_numbers_t) :: qn_hel1, qn_hel2, qn_photon, qn1, qn2 type(quantum_numbers_t), dimension(6) :: qn type(polarization_iterator_t) :: it_hel1, it_hel2 hel_lock = 0 mask_h = .false. select type (data) type is (circe1_data_t) mi2 = data%m_in**2 if (data%with_radiation) then if (data%photon(1)) then hel_lock(1) = 3; hel_lock(3) = 1; mask_h(5) = .true. mr2(1) = mi2(1) mo2(1) = 0._default else hel_lock(1) = 5; hel_lock(5) = 1; mask_h(3) = .true. mr2(1) = 0._default mo2(1) = mi2(1) end if if (data%photon(2)) then hel_lock(2) = 4; hel_lock(4) = 2; mask_h(6) = .true. mr2(2) = mi2(2) mo2(2) = 0._default else hel_lock(2) = 6; hel_lock(6) = 2; mask_h(4) = .true. mr2(2) = 0._default mo2(2) = mi2(2) end if mask = quantum_numbers_mask (.false., .false., mask_h) call sf_int%base_init (mask, mi2, mr2, mo2, & hel_lock = hel_lock) sf_int%data => data call flv_photon%init (PHOTON, data%model) call col0%init () call qn_photon%init (flv_photon, col0) call pol1%init_generic (data%flv_in(1)) call qn_fc1(1)%init (flv = data%flv_in(1), col = col0) call pol2%init_generic (data%flv_in(2)) call qn_fc2(1)%init (flv = data%flv_in(2), col = col0) call it_hel1%init (pol1) do while (it_hel1%is_valid ()) qn_hel1 = it_hel1%get_quantum_numbers () qn1 = qn_hel1 .merge. qn_fc1(1) qn(1) = qn1 if (data%photon(1)) then qn(3) = qn1; qn(5) = qn_photon else qn(3) = qn_photon; qn(5) = qn1 end if call it_hel2%init (pol2) do while (it_hel2%is_valid ()) qn_hel2 = it_hel2%get_quantum_numbers () qn2 = qn_hel2 .merge. qn_fc2(1) qn(2) = qn2 if (data%photon(2)) then qn(4) = qn2; qn(6) = qn_photon else qn(4) = qn_photon; qn(6) = qn2 end if call qn(3:4)%tag_radiated () call sf_int%add_state (qn) call it_hel2%advance () end do call it_hel1%advance () end do ! call pol1%final () ! call pol2%final () call sf_int%freeze () call sf_int%set_incoming ([1,2]) call sf_int%set_radiated ([3,4]) call sf_int%set_outgoing ([5,6]) else if (data%photon(1)) then mask_h(3) = .true. mo2(1) = 0._default else hel_lock(1) = 3; hel_lock(3) = 1 mo2(1) = mi2(1) end if if (data%photon(2)) then mask_h(4) = .true. mo2(2) = 0._default else hel_lock(2) = 4; hel_lock(4) = 2 mo2(2) = mi2(2) end if mask = quantum_numbers_mask (.false., .false., mask_h) call sf_int%base_init (mask(1:4), mi2, [real(default) :: ], mo2, & hel_lock = hel_lock(1:4)) sf_int%data => data call flv_photon%init (PHOTON, data%model) call col0%init () call qn_photon%init (flv_photon, col0) call pol1%init_generic (data%flv_in(1)) call qn_fc1(1)%init (flv = data%flv_in(1), col = col0) call pol2%init_generic (data%flv_in(2)) call qn_fc2(1)%init (flv = data%flv_in(2), col = col0) call it_hel1%init (pol1) do while (it_hel1%is_valid ()) qn_hel1 = it_hel1%get_quantum_numbers () qn1 = qn_hel1 .merge. qn_fc1(1) qn(1) = qn1 if (data%photon(1)) then qn(3) = qn_photon else qn(3) = qn1 end if call it_hel2%init (pol2) do while (it_hel2%is_valid ()) qn_hel2 = it_hel2%get_quantum_numbers () qn2 = qn_hel2 .merge. qn_fc2(1) qn(2) = qn2 if (data%photon(2)) then qn(4) = qn_photon else qn(4) = qn2 end if call sf_int%add_state (qn(1:4)) call it_hel2%advance () end do call it_hel1%advance () end do ! call pol1%final () ! call pol2%final () call sf_int%freeze () call sf_int%set_incoming ([1,2]) call sf_int%set_outgoing ([3,4]) end if sf_int%status = SF_INITIAL end select if (sf_int%data%generate) then call sf_int%data%rng_factory%make (sf_int%rng_obj%rng) end if end subroutine circe1_init @ %def circe1_init @ \subsection{Kinematics} Refer to the [[data]] component. <>= procedure :: is_generator => circe1_is_generator <>= function circe1_is_generator (sf_int) result (flag) class(circe1_t), intent(in) :: sf_int logical :: flag flag = sf_int%data%is_generator () end function circe1_is_generator @ %def circe1_is_generator @ Generate free parameters, if generator mode is on. Otherwise, the parameters will be discarded. <>= procedure :: generate_free => circe1_generate_free <>= subroutine circe1_generate_free (sf_int, r, rb, x_free) class(circe1_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: r, rb real(default), intent(inout) :: x_free if (sf_int%data%generate) then call circe_generate (r, sf_int%data%get_pdg_int (), sf_int%rng_obj) rb = 1 - r x_free = x_free * product (r) else r = 0 rb= 1 end if end subroutine circe1_generate_free @ %def circe1_generate_free @ Generator mode: depending on the particle codes, call one of the available [[girce]] generators. Illegal particle code combinations should have been caught during data initialization. <>= subroutine circe_generate (x, pdg, rng_obj) real(default), dimension(2), intent(out) :: x integer, dimension(2), intent(in) :: pdg class(rng_obj_t), intent(inout) :: rng_obj real(double) :: xc1, xc2 select case (abs (pdg(1))) case (ELECTRON) select case (abs (pdg(2))) case (ELECTRON) call gircee (xc1, xc2, rng_obj = rng_obj) case (PHOTON) call girceg (xc1, xc2, rng_obj = rng_obj) end select case (PHOTON) select case (abs (pdg(2))) case (ELECTRON) call girceg (xc2, xc1, rng_obj = rng_obj) case (PHOTON) call gircgg (xc1, xc2, rng_obj = rng_obj) end select end select x = [xc1, xc2] end subroutine circe_generate @ %def circe_generate @ Set kinematics. The $r$ values (either from integration or from the generator call above) are copied to $x$ unchanged, and $f$ is unity. We store the $x$ values, so we can use them for the evaluation later. <>= procedure :: complete_kinematics => circe1_complete_kinematics <>= subroutine circe1_complete_kinematics (sf_int, x, xb, f, r, rb, map) class(circe1_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: x real(default), dimension(:), intent(out) :: xb real(default), intent(out) :: f real(default), dimension(:), intent(in) :: r real(default), dimension(:), intent(in) :: rb logical, intent(in) :: map x = r xb = rb sf_int%x = x sf_int%xb= xb f = 1 if (sf_int%data%with_radiation) then call sf_int%split_momenta (x, xb) else call sf_int%reduce_momenta (x) end if select case (sf_int%status) case (SF_FAILED_KINEMATICS); f = 0 end select end subroutine circe1_complete_kinematics @ %def circe1_complete_kinematics @ Compute inverse kinematics. In generator mode, the $r$ values are meaningless, but we copy them anyway. <>= procedure :: inverse_kinematics => circe1_inverse_kinematics <>= subroutine circe1_inverse_kinematics (sf_int, x, xb, f, r, rb, map, set_momenta) class(circe1_t), intent(inout) :: sf_int real(default), dimension(:), intent(in) :: x real(default), dimension(:), intent(in) :: xb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: r real(default), dimension(:), intent(out) :: rb logical, intent(in) :: map logical, intent(in), optional :: set_momenta logical :: set_mom set_mom = .false.; if (present (set_momenta)) set_mom = set_momenta r = x rb = xb sf_int%x = x sf_int%xb= xb f = 1 if (set_mom) then call sf_int%split_momenta (x, xb) select case (sf_int%status) case (SF_FAILED_KINEMATICS); f = 0 end select end if end subroutine circe1_inverse_kinematics @ %def circe1_inverse_kinematics @ \subsection{CIRCE1 application} CIRCE is applied for the two beams at once. We can safely assume that no structure functions are applied before this, so the incoming particles are on-shell electrons/positrons. The scale is ignored. <>= procedure :: apply => circe1_apply <>= subroutine circe1_apply (sf_int, scale, rescale, i_sub) class(circe1_t), intent(inout) :: sf_int real(default), intent(in) :: scale class(sf_rescale_t), intent(in), optional :: rescale integer, intent(in), optional :: i_sub real(default), dimension(2) :: xb real(double), dimension(2) :: xc real(double), parameter :: one = 1 associate (data => sf_int%data) xc = sf_int%x xb = sf_int%xb if (data%generate) then sf_int%f = 1 else sf_int%f = 0 if (all (sf_int%continuum)) then sf_int%f = circe (xc(1), xc(2), data%pdg_in(1), data%pdg_in(2)) end if if (sf_int%continuum(2) .and. sf_int%peak(1)) then sf_int%f = sf_int%f & + circe (one, xc(2), data%pdg_in(1), data%pdg_in(2)) & * peak (xb(1), data%eps) end if if (sf_int%continuum(1) .and. sf_int%peak(2)) then sf_int%f = sf_int%f & + circe (xc(1), one, data%pdg_in(1), data%pdg_in(2)) & * peak (xb(2), data%eps) end if if (all (sf_int%peak)) then sf_int%f = sf_int%f & + circe (one, one, data%pdg_in(1), data%pdg_in(2)) & * peak (xb(1), data%eps) * peak (xb(2), data%eps) end if end if end associate call sf_int%set_matrix_element (cmplx (sf_int%f, kind=default)) sf_int%status = SF_EVALUATED end subroutine circe1_apply @ %def circe1_apply @ This is a smeared delta peak at zero, as an endpoint singularity. We choose an exponentially decreasing function, starting at zero, with integral (from $0$ to $1$) $1-e^{-1/\epsilon}$. For small $\epsilon$, this reduces to one. <>= function peak (x, eps) result (f) real(default), intent(in) :: x, eps real(default) :: f f = exp (-x / eps) / eps end function peak @ %def peak @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[sf_circe1_ut.f90]]>>= <> module sf_circe1_ut use unit_tests use sf_circe1_uti <> <> contains <> end module sf_circe1_ut @ %def sf_circe1_ut @ <<[[sf_circe1_uti.f90]]>>= <> module sf_circe1_uti <> use physics_defs, only: ELECTRON use lorentz use pdg_arrays use flavors use interactions, only: reset_interaction_counter use model_data use rng_base use sf_aux use sf_base use sf_circe1 use rng_base_ut, only: rng_test_factory_t <> <> contains <> end module sf_circe1_uti @ %def sf_circe1_ut @ API: driver for the unit tests below. <>= public :: sf_circe1_test <>= subroutine sf_circe1_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine sf_circe1_test @ %def sf_circe1_test @ \subsubsection{Test structure function data} Construct and display a test structure function data object. <>= call test (sf_circe1_1, "sf_circe1_1", & "structure function configuration", & u, results) <>= public :: sf_circe1_1 <>= subroutine sf_circe1_1 (u) integer, intent(in) :: u type(model_data_t), target :: model type(pdg_array_t), dimension(2) :: pdg_in type(pdg_array_t), dimension(2) :: pdg_out integer, dimension(:), allocatable :: pdg1, pdg2 class(sf_data_t), allocatable :: data write (u, "(A)") "* Test output: sf_circe1_1" write (u, "(A)") "* Purpose: initialize and display & &CIRCE structure function data" write (u, "(A)") write (u, "(A)") "* Create empty data object" write (u, "(A)") call model%init_qed_test () pdg_in(1) = ELECTRON pdg_in(2) = -ELECTRON allocate (circe1_data_t :: data) call data%write (u) write (u, "(A)") write (u, "(A)") "* Initialize" write (u, "(A)") select type (data) type is (circe1_data_t) call data%init (model, pdg_in, & sqrts = 500._default, & eps = 1e-6_default, & out_photon = [.false., .false.], & ver = 0, & rev = 0, & acc = "SBAND", & chat = 0, & with_radiation = .true.) end select call data%write (u) write (u, "(A)") write (u, "(1x,A)") "Outgoing particle codes:" call data%get_pdg_out (pdg_out) pdg1 = pdg_out(1) pdg2 = pdg_out(2) write (u, "(2x,99(1x,I0))") pdg1, pdg2 call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_circe1_1" end subroutine sf_circe1_1 @ %def sf_circe1_1 @ \subsubsection{Test and probe structure function} Construct and display a structure function object based on the PDF builtin structure function. <>= call test (sf_circe1_2, "sf_circe1_2", & "structure function instance", & u, results) <>= public :: sf_circe1_2 <>= subroutine sf_circe1_2 (u) integer, intent(in) :: u type(model_data_t), target :: model type(flavor_t), dimension(2) :: flv type(pdg_array_t), dimension(2) :: pdg_in class(sf_data_t), allocatable, target :: data class(sf_int_t), allocatable :: sf_int type(vector4_t) :: k1, k2 type(vector4_t), dimension(4) :: q real(default) :: E real(default), dimension(:), allocatable :: r, rb, x, xb real(default) :: f write (u, "(A)") "* Test output: sf_circe1_2" write (u, "(A)") "* Purpose: initialize and fill & &circe1 structure function object" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call model%init_qed_test () call flv(1)%init (ELECTRON, model) call flv(2)%init (-ELECTRON, model) pdg_in(1) = ELECTRON pdg_in(2) = -ELECTRON call reset_interaction_counter () allocate (circe1_data_t :: data) select type (data) type is (circe1_data_t) call data%init (model, pdg_in, & sqrts = 500._default, & eps = 1e-6_default, & out_photon = [.false., .false.], & ver = 0, & rev = 0, & acc = "SBAND", & chat = 0, & with_radiation = .true.) end select write (u, "(A)") "* Initialize structure-function object" write (u, "(A)") call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1,2]) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Initialize incoming momentum with E=500" write (u, "(A)") E = 250 k1 = vector4_moving (E, sqrt (E**2 - flv(1)%get_mass ()**2), 3) k2 = vector4_moving (E,-sqrt (E**2 - flv(2)%get_mass ()**2), 3) call vector4_write (k1, u) call vector4_write (k2, u) call sf_int%seed_kinematics ([k1, k2]) write (u, "(A)") write (u, "(A)") "* Set kinematics for x=0.95,0.85." write (u, "(A)") allocate (r (data%get_n_par ())) allocate (rb(size (r))) allocate (x (size (r))) allocate (xb(size (r))) r = [0.9_default, 0.8_default] rb = 1 - r call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%write (u) write (u, "(A)") write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Recover x from momenta" write (u, "(A)") q = sf_int%get_momenta (outgoing=.true.) call sf_int%final () deallocate (sf_int) call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1, 2]) call sf_int%seed_kinematics ([k1, k2]) call sf_int%set_momenta (q, outgoing=.true.) call sf_int%recover_x (x, xb) write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A)") write (u, "(A)") "* Evaluate" write (u, "(A)") call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%apply (scale = 0._default) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call sf_int%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_circe1_2" end subroutine sf_circe1_2 @ %def sf_circe1_2 @ \subsubsection{Generator mode} Construct and evaluate a structure function object in generator mode. <>= call test (sf_circe1_3, "sf_circe1_3", & "generator mode", & u, results) <>= public :: sf_circe1_3 <>= subroutine sf_circe1_3 (u) integer, intent(in) :: u type(model_data_t), target :: model type(flavor_t), dimension(2) :: flv type(pdg_array_t), dimension(2) :: pdg_in class(sf_data_t), allocatable, target :: data class(rng_factory_t), allocatable :: rng_factory class(sf_int_t), allocatable :: sf_int type(vector4_t) :: k1, k2 real(default) :: E real(default), dimension(:), allocatable :: r, rb, x, xb real(default) :: f, x_free write (u, "(A)") "* Test output: sf_circe1_3" write (u, "(A)") "* Purpose: initialize and fill & &circe1 structure function object" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call model%init_qed_test () call flv(1)%init (ELECTRON, model) call flv(2)%init (-ELECTRON, model) pdg_in(1) = ELECTRON pdg_in(2) = -ELECTRON call reset_interaction_counter () allocate (circe1_data_t :: data) allocate (rng_test_factory_t :: rng_factory) select type (data) type is (circe1_data_t) call data%init (model, pdg_in, & sqrts = 500._default, & eps = 1e-6_default, & out_photon = [.false., .false.], & ver = 0, & rev = 0, & acc = "SBAND", & chat = 0, & with_radiation = .true.) call data%set_generator_mode (rng_factory) end select write (u, "(A)") "* Initialize structure-function object" write (u, "(A)") call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1,2]) select type (sf_int) type is (circe1_t) call sf_int%rng_obj%rng%init (3) end select write (u, "(A)") "* Initialize incoming momentum with E=500" write (u, "(A)") E = 250 k1 = vector4_moving (E, sqrt (E**2 - flv(1)%get_mass ()**2), 3) k2 = vector4_moving (E,-sqrt (E**2 - flv(2)%get_mass ()**2), 3) call vector4_write (k1, u) call vector4_write (k2, u) call sf_int%seed_kinematics ([k1, k2]) write (u, "(A)") write (u, "(A)") "* Generate x" write (u, "(A)") allocate (r (data%get_n_par ())) allocate (rb(size (r))) allocate (x (size (r))) allocate (xb(size (r))) r = 0 rb = 0 x_free = 1 call sf_int%generate_free (r, rb, x_free) call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A,9(1x,F10.7))") "xf=", x_free write (u, "(A)") write (u, "(A)") "* Evaluate" write (u, "(A)") call sf_int%apply (scale = 0._default) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call sf_int%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_circe1_3" end subroutine sf_circe1_3 @ %def sf_circe1_3 @ \clearpage %------------------------------------------------------------------------ \section{Lepton Collider Beamstrahlung and Photon collider: CIRCE2} <<[[sf_circe2.f90]]>>= <> module sf_circe2 <> <> use io_units use format_defs, only: FMT_19 use numeric_utils use diagnostics use os_interface use physics_defs, only: PHOTON, ELECTRON use lorentz use rng_base use selectors use pdg_arrays use model_data use flavors use colors use helicities use quantum_numbers use state_matrices use polarizations use sf_base use circe2, circe2_rng_t => rng_type !NODEP! <> <> <> contains <> end module sf_circe2 @ %def sf_circe2 @ \subsection{Physics} [[CIRCE2]] describes photon spectra Beamstrahlung is applied before ISR. The [[CIRCE2]] implementation has a single structure function for both beams (which makes sense since it has to be switched on or off for both beams simultaneously). \subsection{The CIRCE2 data block} The CIRCE2 parameters are: file and collider specification, incoming (= outgoing) particles. The luminosity is returned by [[circe2_luminosity]]. <>= public :: circe2_data_t <>= type, extends (sf_data_t) :: circe2_data_t private class(model_data_t), pointer :: model => null () type(flavor_t), dimension(2) :: flv_in integer, dimension(2) :: pdg_in real(default) :: sqrts = 0 logical :: polarized = .false. logical :: beams_polarized = .false. class(rng_factory_t), allocatable :: rng_factory type(string_t) :: filename type(string_t) :: file type(string_t) :: design real(default) :: lumi = 0 real(default), dimension(4) :: lumi_hel_frac = 0 integer, dimension(0:4) :: h1 = [0, -1, -1, 1, 1] integer, dimension(0:4) :: h2 = [0, -1, 1,-1, 1] integer :: error = 1 contains <> end type circe2_data_t @ %def circe2_data_t <>= type(circe2_state) :: circe2_global_state @ <>= procedure :: init => circe2_data_init <>= subroutine circe2_data_init (data, os_data, model, pdg_in, & sqrts, polarized, beam_pol, file, design) class(circe2_data_t), intent(out) :: data type(os_data_t), intent(in) :: os_data class(model_data_t), intent(in), target :: model type(pdg_array_t), dimension(2), intent(in) :: pdg_in real(default), intent(in) :: sqrts logical, intent(in) :: polarized, beam_pol type(string_t), intent(in) :: file, design integer :: h data%model => model if (any (pdg_array_get_length (pdg_in) /= 1)) then call msg_fatal ("CIRCE2: incoming beam particles must be unique") end if call data%flv_in(1)%init (pdg_array_get (pdg_in(1), 1), model) call data%flv_in(2)%init (pdg_array_get (pdg_in(2), 1), model) data%pdg_in = data%flv_in%get_pdg () data%sqrts = sqrts data%polarized = polarized data%beams_polarized = beam_pol data%filename = file data%design = design call data%check_file (os_data) call circe2_load (circe2_global_state, trim (char(data%file)), & trim (char(data%design)), data%sqrts, data%error) call data%check () data%lumi = circe2_luminosity (circe2_global_state, data%pdg_in, [0, 0]) if (vanishes (data%lumi)) then call msg_fatal ("CIRCE2: luminosity vanishes for specified beams.") end if if (data%polarized) then do h = 1, 4 data%lumi_hel_frac(h) = & circe2_luminosity (circe2_global_state, data%pdg_in, & [data%h1(h), data%h2(h)]) & / data%lumi end do end if end subroutine circe2_data_init @ %def circe2_data_init @ Activate the generator mode. We import a RNG factory into the data type, which can then spawn RNG generator objects. <>= procedure :: set_generator_mode => circe2_data_set_generator_mode <>= subroutine circe2_data_set_generator_mode (data, rng_factory) class(circe2_data_t), intent(inout) :: data class(rng_factory_t), intent(inout), allocatable :: rng_factory call move_alloc (from = rng_factory, to = data%rng_factory) end subroutine circe2_data_set_generator_mode @ %def circe2_data_set_generator_mode @ Check whether the requested data file is in the system directory or in the current directory. <>= procedure :: check_file => circe2_check_file <>= subroutine circe2_check_file (data, os_data) class(circe2_data_t), intent(inout) :: data type(os_data_t), intent(in) :: os_data logical :: exist type(string_t) :: file file = data%filename if (file == "") & call msg_fatal ("CIRCE2: $circe2_file is not set") inquire (file = char (file), exist = exist) if (exist) then data%file = file else file = os_data%whizard_circe2path // "/" // data%filename inquire (file = char (file), exist = exist) if (exist) then data%file = file else call msg_fatal ("CIRCE2: data file '" // char (data%filename) & // "' not found") end if end if end subroutine circe2_check_file @ %def circe2_check_file @ Handle error conditions. <>= procedure :: check => circe2_data_check <>= subroutine circe2_data_check (data) class(circe2_data_t), intent(in) :: data type(flavor_t) :: flv_photon, flv_electron call flv_photon%init (PHOTON, data%model) if (.not. flv_photon%is_defined ()) then call msg_fatal ("CIRCE2: model must contain photon") end if call flv_electron%init (ELECTRON, data%model) if (.not. flv_electron%is_defined ()) then call msg_fatal ("CIRCE2: model must contain electron") end if if (any (abs (data%pdg_in) /= PHOTON .and. abs (data%pdg_in) /= ELECTRON)) & then call msg_fatal ("CIRCE2: applicable only for e+e- or photon collisions") end if select case (data%error) case (-1) call msg_fatal ("CIRCE2: data file not found.") case (-2) call msg_fatal ("CIRCE2: beam setup does not match data file.") case (-3) call msg_fatal ("CIRCE2: invalid format of data file.") case (-4) call msg_fatal ("CIRCE2: data file too large.") end select end subroutine circe2_data_check @ %def circe2_data_check @ Output <>= procedure :: write => circe2_data_write <>= subroutine circe2_data_write (data, unit, verbose) class(circe2_data_t), intent(in) :: data integer, intent(in), optional :: unit logical, intent(in), optional :: verbose integer :: u, h logical :: verb verb = .false.; if (present (verbose)) verb = verbose u = given_output_unit (unit) write (u, "(1x,A)") "CIRCE2 data:" write (u, "(3x,A,A)") "file = ", char(data%filename) write (u, "(3x,A,A)") "design = ", char(data%design) write (u, "(3x,A," // FMT_19 // ")") "sqrts = ", data%sqrts write (u, "(3x,A,A,A,A)") "prt_in = ", & char (data%flv_in(1)%get_name ()), & ", ", char (data%flv_in(2)%get_name ()) write (u, "(3x,A,L1)") "polarized = ", data%polarized write (u, "(3x,A,L1)") "beams pol. = ", data%beams_polarized write (u, "(3x,A," // FMT_19 // ")") "luminosity = ", data%lumi if (data%polarized) then do h = 1, 4 write (u, "(6x,'(',I2,1x,I2,')',1x,'=',1x)", advance="no") & data%h1(h), data%h2(h) write (u, "(6x, " // FMT_19 // ")") data%lumi_hel_frac(h) end do end if if (verb) then call data%rng_factory%write (u) end if end subroutine circe2_data_write @ %def circe2_data_write @ This is always in generator mode. <>= procedure :: is_generator => circe2_data_is_generator <>= function circe2_data_is_generator (data) result (flag) class(circe2_data_t), intent(in) :: data logical :: flag flag = .true. end function circe2_data_is_generator @ %def circe2_data_is_generator @ The number of parameters is two, collinear splitting for the two beams. <>= procedure :: get_n_par => circe2_data_get_n_par <>= function circe2_data_get_n_par (data) result (n) class(circe2_data_t), intent(in) :: data integer :: n n = 2 end function circe2_data_get_n_par @ %def circe2_data_get_n_par @ Return the outgoing particles PDG codes. They are equal to the incoming ones. <>= procedure :: get_pdg_out => circe2_data_get_pdg_out <>= subroutine circe2_data_get_pdg_out (data, pdg_out) class(circe2_data_t), intent(in) :: data type(pdg_array_t), dimension(:), intent(inout) :: pdg_out integer :: i, n n = 2 do i = 1, n pdg_out(i) = data%pdg_in(i) end do end subroutine circe2_data_get_pdg_out @ %def circe2_data_get_pdg_out @ Allocate the interaction record. <>= procedure :: allocate_sf_int => circe2_data_allocate_sf_int <>= subroutine circe2_data_allocate_sf_int (data, sf_int) class(circe2_data_t), intent(in) :: data class(sf_int_t), intent(inout), allocatable :: sf_int allocate (circe2_t :: sf_int) end subroutine circe2_data_allocate_sf_int @ %def circe2_data_allocate_sf_int @ Return the beam file. <>= procedure :: get_beam_file => circe2_data_get_beam_file <>= function circe2_data_get_beam_file (data) result (file) class(circe2_data_t), intent(in) :: data type(string_t) :: file file = "CIRCE2: " // data%filename end function circe2_data_get_beam_file @ %def circe2_data_get_beam_file @ \subsection{Random Number Generator for CIRCE} The CIRCE implementation now supports a generic random-number generator object that allows for a local state as a component. To support this, we must extend the abstract type provided by CIRCE and delegate the generator call to the (also abstract) RNG used by WHIZARD. <>= type, extends (circe2_rng_t) :: rng_obj_t class(rng_t), allocatable :: rng contains procedure :: generate => rng_obj_generate end type rng_obj_t @ %def rng_obj_t <>= subroutine rng_obj_generate (rng_obj, u) class(rng_obj_t), intent(inout) :: rng_obj real(default), intent(out) :: u real(default) :: x call rng_obj%rng%generate (x) u = x end subroutine rng_obj_generate @ %def rng_obj_generate @ \subsection{The CIRCE2 object} For CIRCE2 spectra it does not make sense to describe the state matrix as a radiation interaction, even if photons originate from laser backscattering. Instead, it is a $2\to 2$ interaction where the incoming particles are identical to the outgoing ones. The current implementation of CIRCE2 does support polarization and classical correlations, but no entanglement, so the density matrix of the outgoing particles is diagonal. The incoming particles are unpolarized (user-defined polarization for beams is meaningless, since polarization is described by the data file). The outgoing particles are polarized or polarization-averaged, depending on user request. When assigning matrix elements, we scan the previously initialized state matrix. For each entry, we extract helicity and call the structure function. In the unpolarized case, the helicity is undefined and replaced by value zero. In the polarized case, there are four entries. If the generator is used, only one entry is nonzero in each call. Which one, is determined by comparing with a previously (randomly, distributed by relative luminosity) selected pair of helicities. <>= public :: circe2_t <>= type, extends (sf_int_t) :: circe2_t type(circe2_data_t), pointer :: data => null () type(rng_obj_t) :: rng_obj type(selector_t) :: selector integer :: h_sel = 0 contains <> end type circe2_t @ %def circe2_t @ Type string: show file and design of [[CIRCE2]] structure function. <>= procedure :: type_string => circe2_type_string <>= function circe2_type_string (object) result (string) class(circe2_t), intent(in) :: object type(string_t) :: string if (associated (object%data)) then string = "CIRCE2: " // object%data%design else string = "CIRCE2: [undefined]" end if end function circe2_type_string @ %def circe2_type_string @ @ Output. Call the interaction routine after displaying the configuration. <>= procedure :: write => circe2_write <>= subroutine circe2_write (object, unit, testflag) class(circe2_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u u = given_output_unit (unit) if (associated (object%data)) then call object%data%write (u) call object%base_write (u, testflag) else write (u, "(1x,A)") "CIRCE2 data: [undefined]" end if end subroutine circe2_write @ %def circe2_write @ <>= procedure :: init => circe2_init <>= subroutine circe2_init (sf_int, data) class(circe2_t), intent(out) :: sf_int class(sf_data_t), intent(in), target :: data logical, dimension(4) :: mask_h real(default), dimension(2) :: m2_array real(default), dimension(0) :: null_array type(quantum_numbers_mask_t), dimension(4) :: mask type(quantum_numbers_t), dimension(4) :: qn type(helicity_t) :: hel type(color_t) :: col0 integer :: h select type (data) type is (circe2_data_t) if (data%polarized .and. data%beams_polarized) then call msg_fatal ("CIRCE2: Beam polarization can't be set & &for polarized data file") else if (data%beams_polarized) then call msg_warning ("CIRCE2: User-defined beam polarization set & &for unpolarized CIRCE2 data file") end if mask_h(1:2) = .not. data%beams_polarized mask_h(3:4) = .not. (data%polarized .or. data%beams_polarized) mask = quantum_numbers_mask (.false., .false., mask_h) m2_array(:) = (data%flv_in(:)%get_mass ())**2 call sf_int%base_init (mask, m2_array, null_array, m2_array) sf_int%data => data if (data%polarized) then if (vanishes (sum (data%lumi_hel_frac)) .or. & any (data%lumi_hel_frac < 0)) then call msg_fatal ("CIRCE2: Helicity-dependent lumi " & // "fractions all vanish or", & [var_str ("are negative: Please inspect the " & // "CIRCE2 file or "), & var_str ("switch off the polarized" // & " option for CIRCE2.")]) else call sf_int%selector%init (data%lumi_hel_frac) end if end if call col0%init () if (data%beams_polarized) then do h = 1, 4 call hel%init (data%h1(h)) call qn(1)%init & (flv = data%flv_in(1), col = col0, hel = hel) call qn(3)%init & (flv = data%flv_in(1), col = col0, hel = hel) call hel%init (data%h2(h)) call qn(2)%init & (flv = data%flv_in(2), col = col0, hel = hel) call qn(4)%init & (flv = data%flv_in(2), col = col0, hel = hel) call sf_int%add_state (qn) end do else if (data%polarized) then call qn(1)%init (flv = data%flv_in(1), col = col0) call qn(2)%init (flv = data%flv_in(2), col = col0) do h = 1, 4 call hel%init (data%h1(h)) call qn(3)%init & (flv = data%flv_in(1), col = col0, hel = hel) call hel%init (data%h2(h)) call qn(4)%init & (flv = data%flv_in(2), col = col0, hel = hel) call sf_int%add_state (qn) end do else call qn(1)%init (flv = data%flv_in(1), col = col0) call qn(2)%init (flv = data%flv_in(2), col = col0) call qn(3)%init (flv = data%flv_in(1), col = col0) call qn(4)%init (flv = data%flv_in(2), col = col0) call sf_int%add_state (qn) end if call sf_int%freeze () call sf_int%set_incoming ([1,2]) call sf_int%set_outgoing ([3,4]) call sf_int%data%rng_factory%make (sf_int%rng_obj%rng) sf_int%status = SF_INITIAL end select end subroutine circe2_init @ %def circe2_init @ \subsection{Kinematics} Refer to the [[data]] component. <>= procedure :: is_generator => circe2_is_generator <>= function circe2_is_generator (sf_int) result (flag) class(circe2_t), intent(in) :: sf_int logical :: flag flag = sf_int%data%is_generator () end function circe2_is_generator @ %def circe2_is_generator @ Generate free parameters. We first select a helicity, which we have to store, then generate $x$ values for that helicity. <>= procedure :: generate_free => circe2_generate_whizard_free <>= subroutine circe2_generate_whizard_free (sf_int, r, rb, x_free) class(circe2_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: r, rb real(default), intent(inout) :: x_free integer :: h_sel if (sf_int%data%polarized) then call sf_int%selector%generate (sf_int%rng_obj%rng, h_sel) else h_sel = 0 end if sf_int%h_sel = h_sel call circe2_generate_whizard (r, sf_int%data%pdg_in, & [sf_int%data%h1(h_sel), sf_int%data%h2(h_sel)], & sf_int%rng_obj) rb = 1 - r x_free = x_free * product (r) end subroutine circe2_generate_whizard_free @ %def circe2_generate_whizard_free @ Generator mode: call the CIRCE2 generator for the given particles and helicities. (For unpolarized generation, helicities are zero.) <>= subroutine circe2_generate_whizard (x, pdg, hel, rng_obj) real(default), dimension(2), intent(out) :: x integer, dimension(2), intent(in) :: pdg integer, dimension(2), intent(in) :: hel class(rng_obj_t), intent(inout) :: rng_obj call circe2_generate (circe2_global_state, rng_obj, x, pdg, hel) end subroutine circe2_generate_whizard @ %def circe2_generate_whizard @ Set kinematics. Trivial here. <>= procedure :: complete_kinematics => circe2_complete_kinematics <>= subroutine circe2_complete_kinematics (sf_int, x, xb, f, r, rb, map) class(circe2_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: x real(default), dimension(:), intent(out) :: xb real(default), intent(out) :: f real(default), dimension(:), intent(in) :: r real(default), dimension(:), intent(in) :: rb logical, intent(in) :: map if (map) then call msg_fatal ("CIRCE2: map flag not supported") else x = r xb= rb f = 1 end if call sf_int%reduce_momenta (x) end subroutine circe2_complete_kinematics @ %def circe2_complete_kinematics @ Compute inverse kinematics. <>= procedure :: inverse_kinematics => circe2_inverse_kinematics <>= subroutine circe2_inverse_kinematics (sf_int, x, xb, f, r, rb, map, set_momenta) class(circe2_t), intent(inout) :: sf_int real(default), dimension(:), intent(in) :: x real(default), dimension(:), intent(in) :: xb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: r real(default), dimension(:), intent(out) :: rb logical, intent(in) :: map logical, intent(in), optional :: set_momenta logical :: set_mom set_mom = .false.; if (present (set_momenta)) set_mom = set_momenta if (map) then call msg_fatal ("CIRCE2: map flag not supported") else r = x rb= xb f = 1 end if if (set_mom) then call sf_int%reduce_momenta (x) end if end subroutine circe2_inverse_kinematics @ %def circe2_inverse_kinematics @ \subsection{CIRCE2 application} This function works on both beams. In polarized mode, we set only the selected helicity. In unpolarized mode, the interaction has only one entry, and the factor is unity. <>= procedure :: apply => circe2_apply <>= subroutine circe2_apply (sf_int, scale, rescale, i_sub) class(circe2_t), intent(inout) :: sf_int real(default), intent(in) :: scale class(sf_rescale_t), intent(in), optional :: rescale integer, intent(in), optional :: i_sub complex(default) :: f associate (data => sf_int%data) f = 1 if (data%beams_polarized) then call sf_int%set_matrix_element (f) else if (data%polarized) then call sf_int%set_matrix_element (sf_int%h_sel, f) else call sf_int%set_matrix_element (1, f) end if end associate sf_int%status = SF_EVALUATED end subroutine circe2_apply @ %def circe2_apply @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[sf_circe2_ut.f90]]>>= <> module sf_circe2_ut use unit_tests use sf_circe2_uti <> <> contains <> end module sf_circe2_ut @ %def sf_circe2_ut @ <<[[sf_circe2_uti.f90]]>>= <> module sf_circe2_uti <> <> use os_interface use physics_defs, only: PHOTON use lorentz use pdg_arrays use flavors use interactions, only: reset_interaction_counter use model_data use rng_base use sf_aux use sf_base use sf_circe2 use rng_base_ut, only: rng_test_factory_t <> <> contains <> end module sf_circe2_uti @ %def sf_circe2_ut @ API: driver for the unit tests below. <>= public :: sf_circe2_test <>= subroutine sf_circe2_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine sf_circe2_test @ %def sf_circe2_test @ \subsubsection{Test structure function data} Construct and display a test structure function data object. <>= call test (sf_circe2_1, "sf_circe2_1", & "structure function configuration", & u, results) <>= public :: sf_circe2_1 <>= subroutine sf_circe2_1 (u) integer, intent(in) :: u type(os_data_t) :: os_data type(model_data_t), target :: model type(pdg_array_t), dimension(2) :: pdg_in type(pdg_array_t), dimension(2) :: pdg_out integer, dimension(:), allocatable :: pdg1, pdg2 class(sf_data_t), allocatable :: data class(rng_factory_t), allocatable :: rng_factory write (u, "(A)") "* Test output: sf_circe2_1" write (u, "(A)") "* Purpose: initialize and display & &CIRCE structure function data" write (u, "(A)") write (u, "(A)") "* Create empty data object" write (u, "(A)") call os_data%init () call model%init_qed_test () pdg_in(1) = PHOTON pdg_in(2) = PHOTON allocate (circe2_data_t :: data) allocate (rng_test_factory_t :: rng_factory) write (u, "(A)") write (u, "(A)") "* Initialize (unpolarized)" write (u, "(A)") select type (data) type is (circe2_data_t) call data%init (os_data, model, pdg_in, & sqrts = 500._default, & polarized = .false., & beam_pol = .false., & file = var_str ("teslagg_500_polavg.circe"), & design = var_str ("TESLA/GG")) call data%set_generator_mode (rng_factory) end select call data%write (u, verbose = .true.) write (u, "(A)") write (u, "(1x,A)") "Outgoing particle codes:" call data%get_pdg_out (pdg_out) pdg1 = pdg_out(1) pdg2 = pdg_out(2) write (u, "(2x,99(1x,I0))") pdg1, pdg2 write (u, "(A)") write (u, "(A)") "* Initialize (polarized)" write (u, "(A)") allocate (rng_test_factory_t :: rng_factory) select type (data) type is (circe2_data_t) call data%init (os_data, model, pdg_in, & sqrts = 500._default, & polarized = .true., & beam_pol = .false., & file = var_str ("teslagg_500.circe"), & design = var_str ("TESLA/GG")) call data%set_generator_mode (rng_factory) end select call data%write (u, verbose = .true.) call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_circe2_1" end subroutine sf_circe2_1 @ %def sf_circe2_1 @ \subsubsection{Generator mode, unpolarized} Construct and evaluate a structure function object in generator mode. <>= call test (sf_circe2_2, "sf_circe2_2", & "generator, unpolarized", & u, results) <>= public :: sf_circe2_2 <>= subroutine sf_circe2_2 (u) integer, intent(in) :: u type(os_data_t) :: os_data type(model_data_t), target :: model type(flavor_t), dimension(2) :: flv type(pdg_array_t), dimension(2) :: pdg_in class(sf_data_t), allocatable, target :: data class(rng_factory_t), allocatable :: rng_factory class(sf_int_t), allocatable :: sf_int type(vector4_t) :: k1, k2 real(default) :: E real(default), dimension(:), allocatable :: r, rb, x, xb real(default) :: f, x_free write (u, "(A)") "* Test output: sf_circe2_2" write (u, "(A)") "* Purpose: initialize and fill & &circe2 structure function object" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call os_data%init () call model%init_qed_test () call flv(1)%init (PHOTON, model) call flv(2)%init (PHOTON, model) pdg_in(1) = PHOTON pdg_in(2) = PHOTON call reset_interaction_counter () allocate (circe2_data_t :: data) allocate (rng_test_factory_t :: rng_factory) select type (data) type is (circe2_data_t) call data%init (os_data, model, pdg_in, & sqrts = 500._default, & polarized = .false., & beam_pol = .false., & file = var_str ("teslagg_500_polavg.circe"), & design = var_str ("TESLA/GG")) call data%set_generator_mode (rng_factory) end select write (u, "(A)") "* Initialize structure-function object" write (u, "(A)") call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1,2]) select type (sf_int) type is (circe2_t) call sf_int%rng_obj%rng%init (3) end select write (u, "(A)") "* Initialize incoming momentum with E=500" write (u, "(A)") E = 250 k1 = vector4_moving (E, sqrt (E**2 - flv(1)%get_mass ()**2), 3) k2 = vector4_moving (E,-sqrt (E**2 - flv(2)%get_mass ()**2), 3) call vector4_write (k1, u) call vector4_write (k2, u) call sf_int%seed_kinematics ([k1, k2]) write (u, "(A)") write (u, "(A)") "* Generate x" write (u, "(A)") allocate (r (data%get_n_par ())) allocate (rb(size (r))) allocate (x (size (r))) allocate (xb(size (r))) r = 0 rb = 0 x_free = 1 call sf_int%generate_free (r, rb, x_free) call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A,9(1x,F10.7))") "xf=", x_free write (u, "(A)") write (u, "(A)") "* Evaluate" write (u, "(A)") call sf_int%apply (scale = 0._default) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call sf_int%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_circe2_2" end subroutine sf_circe2_2 @ %def sf_circe2_2 @ \subsubsection{Generator mode, polarized} Construct and evaluate a structure function object in generator mode. <>= call test (sf_circe2_3, "sf_circe2_3", & "generator, polarized", & u, results) <>= public :: sf_circe2_3 <>= subroutine sf_circe2_3 (u) integer, intent(in) :: u type(os_data_t) :: os_data type(model_data_t), target :: model type(flavor_t), dimension(2) :: flv type(pdg_array_t), dimension(2) :: pdg_in class(sf_data_t), allocatable, target :: data class(rng_factory_t), allocatable :: rng_factory class(sf_int_t), allocatable :: sf_int type(vector4_t) :: k1, k2 real(default) :: E real(default), dimension(:), allocatable :: r, rb, x, xb real(default) :: f, x_free write (u, "(A)") "* Test output: sf_circe2_3" write (u, "(A)") "* Purpose: initialize and fill & &circe2 structure function object" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call os_data%init () call model%init_qed_test () call flv(1)%init (PHOTON, model) call flv(2)%init (PHOTON, model) pdg_in(1) = PHOTON pdg_in(2) = PHOTON call reset_interaction_counter () allocate (circe2_data_t :: data) allocate (rng_test_factory_t :: rng_factory) select type (data) type is (circe2_data_t) call data%init (os_data, model, pdg_in, & sqrts = 500._default, & polarized = .true., & beam_pol = .false., & file = var_str ("teslagg_500.circe"), & design = var_str ("TESLA/GG")) call data%set_generator_mode (rng_factory) end select write (u, "(A)") "* Initialize structure-function object" write (u, "(A)") call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1,2]) select type (sf_int) type is (circe2_t) call sf_int%rng_obj%rng%init (3) end select write (u, "(A)") "* Initialize incoming momentum with E=500" write (u, "(A)") E = 250 k1 = vector4_moving (E, sqrt (E**2 - flv(1)%get_mass ()**2), 3) k2 = vector4_moving (E,-sqrt (E**2 - flv(2)%get_mass ()**2), 3) call vector4_write (k1, u) call vector4_write (k2, u) call sf_int%seed_kinematics ([k1, k2]) write (u, "(A)") write (u, "(A)") "* Generate x" write (u, "(A)") allocate (r (data%get_n_par ())) allocate (rb(size (r))) allocate (x (size (r))) allocate (xb(size (r))) r = 0 rb = 0 x_free = 1 call sf_int%generate_free (r, rb, x_free) call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A,9(1x,F10.7))") "xf=", x_free write (u, "(A)") write (u, "(A)") "* Evaluate" write (u, "(A)") call sf_int%apply (scale = 0._default) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call sf_int%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_circe2_3" end subroutine sf_circe2_3 @ %def sf_circe2_3 @ \clearpage %------------------------------------------------------------------------ \section{HOPPET interface} Interface to the HOPPET wrapper necessary to perform the LO vs. NLO matching of processes containing an initial b quark. <<[[hoppet_interface.f90]]>>= <> module hoppet_interface use lhapdf !NODEP! <> public :: hoppet_init, hoppet_eval contains subroutine hoppet_init (pdf_builtin, pdf, pdf_id) logical, intent(in) :: pdf_builtin type(lhapdf_pdf_t), intent(inout), optional :: pdf integer, intent(in), optional :: pdf_id external InitForWhizard call InitForWhizard (pdf_builtin, pdf, pdf_id) end subroutine hoppet_init subroutine hoppet_eval (x, q, f) double precision, intent(in) :: x, q double precision, intent(out) :: f(-6:6) external EvalForWhizard call EvalForWhizard (x, q, f) end subroutine hoppet_eval end module hoppet_interface @ %def hoppet_interface @ \clearpage %------------------------------------------------------------------------ \section{Builtin PDF sets} For convenience in order not to depend on the external package LHAPDF, we ship some PDFs with WHIZARD. @ \subsection{The module} <<[[sf_pdf_builtin.f90]]>>= <> module sf_pdf_builtin <> use kinds, only: double <> use io_units use format_defs, only: FMT_17 use diagnostics use os_interface use physics_defs, only: PROTON, PHOTON, GLUON use physics_defs, only: HADRON_REMNANT_SINGLET use physics_defs, only: HADRON_REMNANT_TRIPLET use physics_defs, only: HADRON_REMNANT_OCTET use sm_qcd use lorentz use pdg_arrays use model_data use flavors use colors use quantum_numbers use state_matrices use polarizations use sf_base use pdf_builtin !NODEP! use hoppet_interface <> <> <> <> contains <> end module sf_pdf_builtin @ %def sf_pdf_builtin @ \subsection{Codes for default PDF sets} <>= character(*), parameter :: PDF_BUILTIN_DEFAULT_PROTON = "CTEQ6L" ! character(*), parameter :: PDF_BUILTIN_DEFAULT_PION = "NONE" ! character(*), parameter :: PDF_BUILTIN_DEFAULT_PHOTON = "MRST2004QEDp" @ %def PDF_BUILTIN_DEFAULT_SET @ \subsection{The PDF builtin data block} The data block holds the incoming flavor (which has to be proton, pion, or photon), the corresponding pointer to the global access data (1, 2, or 3), the flag [[invert]] which is set for an antiproton, the bounds as returned by LHAPDF for the specified set, and a mask that determines which partons will be actually in use. <>= public :: pdf_builtin_data_t <>= type, extends (sf_data_t) :: pdf_builtin_data_t private integer :: id = -1 type (string_t) :: name class(model_data_t), pointer :: model => null () type(flavor_t) :: flv_in logical :: invert logical :: has_photon logical :: photon logical, dimension(-6:6) :: mask logical :: mask_photon logical :: hoppet_b_matching = .false. contains <> end type pdf_builtin_data_t @ %def pdf_builtin_data_t @ Generate PDF data and initialize the requested set. Pion and photon PDFs are disabled at the moment until we ship appropiate structure functions. needed. <>= procedure :: init => pdf_builtin_data_init <>= subroutine pdf_builtin_data_init (data, & model, pdg_in, name, path, hoppet_b_matching) class(pdf_builtin_data_t), intent(out) :: data class(model_data_t), intent(in), target :: model type(pdg_array_t), intent(in) :: pdg_in type(string_t), intent(in) :: name type(string_t), intent(in) :: path logical, intent(in), optional :: hoppet_b_matching data%model => model if (pdg_array_get_length (pdg_in) /= 1) & call msg_fatal ("PDF: incoming particle must be unique") call data%flv_in%init (pdg_array_get (pdg_in, 1), model) data%mask = .true. data%mask_photon = .true. select case (pdg_array_get (pdg_in, 1)) case (PROTON) data%name = var_str (PDF_BUILTIN_DEFAULT_PROTON) data%invert = .false. data%photon = .false. case (-PROTON) data%name = var_str (PDF_BUILTIN_DEFAULT_PROTON) data%invert = .true. data%photon = .false. ! case (PIPLUS) ! data%name = var_str (PDF_BUILTIN_DEFAULT_PION) ! data%invert = .false. ! data%photon = .false. ! case (-PIPLUS) ! data%name = var_str (PDF_BUILTIN_DEFAULT_PION) ! data%invert = .true. ! data%photon = .false. ! case (PHOTON) ! data%name = var_str (PDF_BUILTIN_DEFAULT_PHOTON) ! data%invert = .false. ! data%photon = .true. case default call msg_fatal ("PDF: " & // "incoming particle must either proton or antiproton.") return end select data%name = name data%id = pdf_get_id (data%name) if (data%id < 0) call msg_fatal ("unknown PDF set " // char (data%name)) data%has_photon = pdf_provides_photon (data%id) if (present (hoppet_b_matching)) data%hoppet_b_matching = hoppet_b_matching call pdf_init (data%id, path) if (data%hoppet_b_matching) call hoppet_init (.true., pdf_id = data%id) end subroutine pdf_builtin_data_init @ %def pdf_builtin_data_init @ Enable/disable partons explicitly. If a mask entry is true, applying the PDF will generate the corresponding flavor on output. <>= procedure :: set_mask => pdf_builtin_data_set_mask <>= subroutine pdf_builtin_data_set_mask (data, mask) class(pdf_builtin_data_t), intent(inout) :: data logical, dimension(-6:6), intent(in) :: mask data%mask = mask end subroutine pdf_builtin_data_set_mask @ %def pdf_builtin_data_set_mask @ Output. <>= procedure :: write => pdf_builtin_data_write <>= subroutine pdf_builtin_data_write (data, unit, verbose) class(pdf_builtin_data_t), intent(in) :: data integer, intent(in), optional :: unit logical, intent(in), optional :: verbose integer :: u u = given_output_unit (unit); if (u < 0) return write (u, "(1x,A)") "PDF builtin data:" if (data%id < 0) then write (u, "(3x,A)") "[undefined]" return end if write (u, "(3x,A)", advance="no") "flavor = " call data%flv_in%write (u); write (u, *) write (u, "(3x,A,A)") "name = ", char (data%name) write (u, "(3x,A,L1)") "invert = ", data%invert write (u, "(3x,A,L1)") "has photon = ", data%has_photon write (u, "(3x,A,6(1x,L1),1x,A,1x,L1,1x,A,6(1x,L1))") & "mask =", & data%mask(-6:-1), "*", data%mask(0), "*", data%mask(1:6) write (u, "(3x,A,L1)") "photon mask = ", data%mask_photon write (u, "(3x,A,L1)") "hoppet_b = ", data%hoppet_b_matching end subroutine pdf_builtin_data_write @ %def pdf_builtin_data_write @ The number of parameters is one. We do not generate transverse momentum. <>= procedure :: get_n_par => pdf_builtin_data_get_n_par <>= function pdf_builtin_data_get_n_par (data) result (n) class(pdf_builtin_data_t), intent(in) :: data integer :: n n = 1 end function pdf_builtin_data_get_n_par @ %def pdf_builtin_data_get_n_par @ Return the outgoing particle PDG codes. This is based on the mask. <>= procedure :: get_pdg_out => pdf_builtin_data_get_pdg_out <>= subroutine pdf_builtin_data_get_pdg_out (data, pdg_out) class(pdf_builtin_data_t), intent(in) :: data type(pdg_array_t), dimension(:), intent(inout) :: pdg_out integer, dimension(:), allocatable :: pdg1 integer :: n, np, i n = count (data%mask) np = 0; if (data%has_photon .and. data%mask_photon) np = 1 allocate (pdg1 (n + np)) pdg1(1:n) = pack ([(i, i = -6, 6)], data%mask) if (np == 1) pdg1(n+np) = PHOTON pdg_out(1) = pdg1 end subroutine pdf_builtin_data_get_pdg_out @ %def pdf_builtin_data_get_pdg_out @ Allocate the interaction record. <>= procedure :: allocate_sf_int => pdf_builtin_data_allocate_sf_int <>= subroutine pdf_builtin_data_allocate_sf_int (data, sf_int) class(pdf_builtin_data_t), intent(in) :: data class(sf_int_t), intent(inout), allocatable :: sf_int allocate (pdf_builtin_t :: sf_int) end subroutine pdf_builtin_data_allocate_sf_int @ %def pdf_builtin_data_allocate_sf_int @ Return the numerical PDF set index. <>= procedure :: get_pdf_set => pdf_builtin_data_get_pdf_set <>= elemental function pdf_builtin_data_get_pdf_set (data) result (pdf_set) class(pdf_builtin_data_t), intent(in) :: data integer :: pdf_set pdf_set = data%id end function pdf_builtin_data_get_pdf_set @ %def pdf_builtin_data_get_pdf_set @ \subsection{The PDF object} The PDF $1\to 2$ interaction which describes the splitting of an (anti)proton into a parton and a beam remnant. We stay in the strict forward-splitting limit, but allow some invariant mass for the beam remnant such that the outgoing parton is exactly massless. For a real event, we would replace this by a parton cascade, where the outgoing partons have virtuality as dictated by parton-shower kinematics, and transverse momentum is generated. The PDF application is a $1\to 2$ splitting process, where the particles are ordered as (hadron, remnant, parton). Polarization is ignored completely. The beam particle is colorless, while partons and beam remnant carry color. The remnant gets a special flavor code. <>= public :: pdf_builtin_t <>= type, extends (sf_int_t) :: pdf_builtin_t type(pdf_builtin_data_t), pointer :: data => null () real(default) :: x = 0 real(default) :: q = 0 contains <> end type pdf_builtin_t @ %def pdf_builtin_t @ Type string: display the chosen PDF set. <>= procedure :: type_string => pdf_builtin_type_string <>= function pdf_builtin_type_string (object) result (string) class(pdf_builtin_t), intent(in) :: object type(string_t) :: string if (associated (object%data)) then string = "PDF builtin: " // object%data%name else string = "PDF builtin: [undefined]" end if end function pdf_builtin_type_string @ %def pdf_builtin_type_string @ Output. Call the interaction routine after displaying the configuration. <>= procedure :: write => pdf_builtin_write <>= subroutine pdf_builtin_write (object, unit, testflag) class(pdf_builtin_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u u = given_output_unit (unit) if (associated (object%data)) then call object%data%write (u) if (object%status >= SF_DONE_KINEMATICS) then write (u, "(1x,A)") "SF parameters:" write (u, "(3x,A," // FMT_17 // ")") "x =", object%x if (object%status >= SF_FAILED_EVALUATION) then write (u, "(3x,A," // FMT_17 // ")") "Q =", object%q end if end if call object%base_write (u, testflag) else write (u, "(1x,A)") "PDF builtin data: [undefined]" end if end subroutine pdf_builtin_write @ %def pdf_builtin_write @ Initialize. We know that [[data]] will be of concrete type [[sf_test_data_t]], but we have to cast this explicitly. For this implementation, we set the incoming and outgoing masses equal to the physical particle mass, but keep the radiated mass zero. Optionally, we can provide minimum and maximum values for the momentum transfer. <>= procedure :: init => pdf_builtin_init <>= subroutine pdf_builtin_init (sf_int, data) class(pdf_builtin_t), intent(out) :: sf_int class(sf_data_t), intent(in), target :: data type(quantum_numbers_mask_t), dimension(3) :: mask type(flavor_t) :: flv, flv_remnant type(color_t) :: col0 type(quantum_numbers_t), dimension(3) :: qn integer :: i select type (data) type is (pdf_builtin_data_t) mask = quantum_numbers_mask (.false., .false., .true.) call col0%init () call sf_int%base_init (mask, [0._default], [0._default], [0._default]) sf_int%data => data do i = -6, 6 if (data%mask(i)) then call qn(1)%init (data%flv_in, col = col0) if (i == 0) then call flv%init (GLUON, data%model) call flv_remnant%init (HADRON_REMNANT_OCTET, data%model) else call flv%init (i, data%model) call flv_remnant%init & (sign (HADRON_REMNANT_TRIPLET, -i), data%model) end if call qn(2)%init ( & flv = flv_remnant, col = color_from_flavor (flv_remnant, 1)) call qn(2)%tag_radiated () call qn(3)%init ( & flv = flv, col = color_from_flavor (flv, 1, reverse=.true.)) call sf_int%add_state (qn) end if end do if (data%has_photon .and. data%mask_photon) then call flv%init (PHOTON, data%model) call flv_remnant%init (HADRON_REMNANT_SINGLET, data%model) call qn(2)%init (flv = flv_remnant, & col = color_from_flavor (flv_remnant, 1)) call qn(2)%tag_radiated () call qn(3)%init (flv = flv, & col = color_from_flavor (flv, 1, reverse = .true.)) call sf_int%add_state (qn) end if call sf_int%freeze () call sf_int%set_incoming ([1]) call sf_int%set_radiated ([2]) call sf_int%set_outgoing ([3]) sf_int%status = SF_INITIAL end select end subroutine pdf_builtin_init @ %def pdf_builtin_init @ \subsection{Kinematics} Set kinematics. If [[map]] is unset, the $r$ and $x$ values coincide, and the Jacobian $f(r)$ is trivial. If [[map]] is set, we are asked to provide an efficient mapping. For the test case, we set $x=r^2$ and consequently $f(r)=2r$. <>= procedure :: complete_kinematics => pdf_builtin_complete_kinematics <>= subroutine pdf_builtin_complete_kinematics (sf_int, x, xb, f, r, rb, map) class(pdf_builtin_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: x real(default), dimension(:), intent(out) :: xb real(default), intent(out) :: f real(default), dimension(:), intent(in) :: r real(default), dimension(:), intent(in) :: rb logical, intent(in) :: map if (map) then call msg_fatal ("PDF builtin: map flag not supported") else x(1) = r(1) xb(1)= rb(1) f = 1 end if call sf_int%split_momentum (x, xb) select case (sf_int%status) case (SF_DONE_KINEMATICS) sf_int%x = x(1) case (SF_FAILED_KINEMATICS) sf_int%x = 0 f = 0 end select end subroutine pdf_builtin_complete_kinematics @ %def pdf_builtin_complete_kinematics @ Overriding the default method: we compute the [[x]] value from the momentum configuration. In this specific case, we also set the internally stored $x$ value, so it can be used in the following routine. <>= procedure :: recover_x => pdf_builtin_recover_x <>= subroutine pdf_builtin_recover_x (sf_int, x, xb, x_free) class(pdf_builtin_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: x real(default), dimension(:), intent(out) :: xb real(default), intent(inout), optional :: x_free call sf_int%base_recover_x (x, xb, x_free) sf_int%x = x(1) end subroutine pdf_builtin_recover_x @ %def sf_pdf_builtin_recover_x @ Compute inverse kinematics. Here, we start with the $x$ array and compute the ``input'' $r$ values and the Jacobian $f$. After this, we can set momenta by the same formula as for normal kinematics. <>= procedure :: inverse_kinematics => pdf_builtin_inverse_kinematics <>= subroutine pdf_builtin_inverse_kinematics (sf_int, x, xb, f, r, rb, map, set_momenta) class(pdf_builtin_t), intent(inout) :: sf_int real(default), dimension(:), intent(in) :: x real(default), dimension(:), intent(in) :: xb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: r real(default), dimension(:), intent(out) :: rb logical, intent(in) :: map logical, intent(in), optional :: set_momenta logical :: set_mom set_mom = .false.; if (present (set_momenta)) set_mom = set_momenta if (map) then call msg_fatal ("PDF builtin: map flag not supported") else r(1) = x(1) rb(1)= xb(1) f = 1 end if if (set_mom) then call sf_int%split_momentum (x, xb) select case (sf_int%status) case (SF_FAILED_KINEMATICS); f = 0 end select end if end subroutine pdf_builtin_inverse_kinematics @ %def pdf_builtin_inverse_kinematics @ \subsection{Structure function} Once the scale is also known, we can actually call the PDF and set the values. Contrary to LHAPDF, the wrapper already takes care of adjusting to the $x$ and $Q$ bounds. Account for the Jacobian. The class [[rescale]] gives rescaling prescription for NLO convolution of the structure function in combination with [[i_sub]]. <>= procedure :: apply => pdf_builtin_apply <>= subroutine pdf_builtin_apply (sf_int, scale, rescale, i_sub) class(pdf_builtin_t), intent(inout) :: sf_int real(default), intent(in) :: scale class(sf_rescale_t), intent(in), optional :: rescale integer, intent(in), optional :: i_sub real(default), dimension(-6:6) :: ff real(double), dimension(-6:6) :: ff_dbl real(default) :: x, fph real(double) :: xx, qq complex(default), dimension(:), allocatable :: fc integer :: i, j_sub, i_sub_opt i_sub_opt = 0; if (present (i_sub)) i_sub_opt = i_sub associate (data => sf_int%data) sf_int%q = scale x = sf_int%x if (present (rescale)) call rescale%apply (x) if (debug2_active (D_BEAMS)) then call msg_debug2 (D_BEAMS, "pdf_builtin_apply") call msg_debug2 (D_BEAMS, "rescale: ", present(rescale)) call msg_debug2 (D_BEAMS, "i_sub: ", i_sub_opt) call msg_debug2 (D_BEAMS, "x: ", x) end if xx = x qq = scale if (data%invert) then if (data%has_photon) then call pdf_evolve (data%id, x, scale, ff(6:-6:-1), fph) else if (data%hoppet_b_matching) then call hoppet_eval (xx, qq, ff_dbl(6:-6:-1)) ff = ff_dbl else call pdf_evolve (data%id, x, scale, ff(6:-6:-1)) end if end if else if (data%has_photon) then call pdf_evolve (data%id, x, scale, ff, fph) else if (data%hoppet_b_matching) then call hoppet_eval (xx, qq, ff_dbl) ff = ff_dbl else call pdf_evolve (data%id, x, scale, ff) end if end if end if if (data%has_photon) then allocate (fc (count ([data%mask, data%mask_photon]))) fc = max (pack ([ff, fph], & [data%mask, data%mask_photon]), 0._default) else allocate (fc (count (data%mask))) fc = max (pack (ff, data%mask), 0._default) end if end associate if (debug_active (D_BEAMS)) print *, 'Set pdfs: ', real (fc) call sf_int%set_matrix_element (fc, [(i_sub_opt * size(fc) + i, i = 1, size(fc))]) sf_int%status = SF_EVALUATED end subroutine pdf_builtin_apply @ %def pdf_builtin_apply @ \subsection{Strong Coupling} Since the PDF codes provide a function for computing the running $\alpha_s$ value, we make this available as an implementation of the abstract [[alpha_qcd_t]] type, which is used for matrix element evaluation. <>= public :: alpha_qcd_pdf_builtin_t <>= type, extends (alpha_qcd_t) :: alpha_qcd_pdf_builtin_t type(string_t) :: pdfset_name integer :: pdfset_id = -1 contains <> end type alpha_qcd_pdf_builtin_t @ %def alpha_qcd_pdf_builtin_t @ Output. <>= procedure :: write => alpha_qcd_pdf_builtin_write <>= subroutine alpha_qcd_pdf_builtin_write (object, unit) class(alpha_qcd_pdf_builtin_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(3x,A)") "QCD parameters (pdf_builtin):" write (u, "(5x,A,A)") "PDF set = ", char (object%pdfset_name) write (u, "(5x,A,I0)") "PDF ID = ", object%pdfset_id end subroutine alpha_qcd_pdf_builtin_write @ %def alpha_qcd_pdf_builtin_write @ Calculation: the numeric ID selects the correct PDF set, which must be properly initialized. <>= procedure :: get => alpha_qcd_pdf_builtin_get <>= function alpha_qcd_pdf_builtin_get (alpha_qcd, scale) result (alpha) class(alpha_qcd_pdf_builtin_t), intent(in) :: alpha_qcd real(default), intent(in) :: scale real(default) :: alpha alpha = pdf_alphas (alpha_qcd%pdfset_id, scale) end function alpha_qcd_pdf_builtin_get @ %def alpha_qcd_pdf_builtin_get @ Initialization. We need to access the global initialization status. <>= procedure :: init => alpha_qcd_pdf_builtin_init <>= subroutine alpha_qcd_pdf_builtin_init (alpha_qcd, name, path) class(alpha_qcd_pdf_builtin_t), intent(out) :: alpha_qcd type(string_t), intent(in) :: name type(string_t), intent(in) :: path alpha_qcd%pdfset_name = name alpha_qcd%pdfset_id = pdf_get_id (name) if (alpha_qcd%pdfset_id < 0) & call msg_fatal ("QCD parameter initialization: PDF set " & // char (name) // " is unknown") call pdf_init (alpha_qcd%pdfset_id, path) end subroutine alpha_qcd_pdf_builtin_init @ %def alpha_qcd_pdf_builtin_init @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[sf_pdf_builtin_ut.f90]]>>= <> module sf_pdf_builtin_ut use unit_tests use sf_pdf_builtin_uti <> <> contains <> end module sf_pdf_builtin_ut @ %def sf_pdf_builtin_ut @ <<[[sf_pdf_builtin_uti.f90]]>>= <> module sf_pdf_builtin_uti <> <> use os_interface use physics_defs, only: PROTON use sm_qcd use lorentz use pdg_arrays use flavors use interactions, only: reset_interaction_counter use model_data use sf_base use sf_pdf_builtin <> <> contains <> end module sf_pdf_builtin_uti @ %def sf_pdf_builtin_ut @ API: driver for the unit tests below. <>= public :: sf_pdf_builtin_test <>= subroutine sf_pdf_builtin_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine sf_pdf_builtin_test @ %def sf_pdf_builtin_test @ \subsubsection{Test structure function data} Construct and display a test structure function data object. <>= call test (sf_pdf_builtin_1, "sf_pdf_builtin_1", & "structure function configuration", & u, results) <>= public :: sf_pdf_builtin_1 <>= subroutine sf_pdf_builtin_1 (u) integer, intent(in) :: u type(os_data_t) :: os_data type(model_data_t), target :: model type(pdg_array_t) :: pdg_in type(pdg_array_t), dimension(1) :: pdg_out integer, dimension(:), allocatable :: pdg1 class(sf_data_t), allocatable :: data type(string_t) :: name write (u, "(A)") "* Test output: sf_pdf_builtin_1" write (u, "(A)") "* Purpose: initialize and display & &test structure function data" write (u, "(A)") write (u, "(A)") "* Create empty data object" write (u, "(A)") call os_data%init () call model%init_sm_test () pdg_in = PROTON allocate (pdf_builtin_data_t :: data) call data%write (u) write (u, "(A)") write (u, "(A)") "* Initialize" write (u, "(A)") name = "CTEQ6L" select type (data) type is (pdf_builtin_data_t) call data%init (model, pdg_in, name, & os_data%pdf_builtin_datapath) end select call data%write (u) write (u, "(A)") write (u, "(1x,A)") "Outgoing particle codes:" call data%get_pdg_out (pdg_out) pdg1 = pdg_out(1) write (u, "(2x,99(1x,I0))") pdg1 call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_pdf_builtin_1" end subroutine sf_pdf_builtin_1 @ %def sf_pdf_builtin_1 @ \subsubsection{Test and probe structure function} Construct and display a structure function object based on the PDF builtin structure function. <>= call test (sf_pdf_builtin_2, "sf_pdf_builtin_2", & "structure function instance", & u, results) <>= public :: sf_pdf_builtin_2 <>= subroutine sf_pdf_builtin_2 (u) integer, intent(in) :: u type(os_data_t) :: os_data type(model_data_t), target :: model type(flavor_t) :: flv type(pdg_array_t) :: pdg_in class(sf_data_t), allocatable, target :: data class(sf_int_t), allocatable :: sf_int type(string_t) :: name type(vector4_t) :: k type(vector4_t), dimension(2) :: q real(default) :: E real(default), dimension(:), allocatable :: r, rb, x, xb real(default) :: f write (u, "(A)") "* Test output: sf_pdf_builtin_2" write (u, "(A)") "* Purpose: initialize and fill & &test structure function object" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call os_data%init () call model%init_sm_test () call flv%init (PROTON, model) pdg_in = PROTON call reset_interaction_counter () name = "CTEQ6L" allocate (pdf_builtin_data_t :: data) select type (data) type is (pdf_builtin_data_t) call data%init (model, pdg_in, name, & os_data%pdf_builtin_datapath) end select write (u, "(A)") "* Initialize structure-function object" write (u, "(A)") call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1]) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Initialize incoming momentum with E=500" write (u, "(A)") E = 500 k = vector4_moving (E, sqrt (E**2 - flv%get_mass ()**2), 3) call vector4_write (k, u) call sf_int%seed_kinematics ([k]) write (u, "(A)") write (u, "(A)") "* Set kinematics for x=0.5" write (u, "(A)") allocate (r (data%get_n_par ())) allocate (rb(size (r))) allocate (x (size (r))) allocate (xb(size (r))) r = 0.5_default rb = 1 - r call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%write (u) write (u, "(A)") write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Recover x from momenta" write (u, "(A)") q = sf_int%get_momenta (outgoing=.true.) call sf_int%final () deallocate (sf_int) call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1]) call sf_int%seed_kinematics ([k]) call sf_int%set_momenta (q, outgoing=.true.) call sf_int%recover_x (x, xb) write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A)") write (u, "(A)") "* Evaluate for Q = 100 GeV" write (u, "(A)") call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%apply (scale = 100._default) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call sf_int%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_pdf_builtin_2" end subroutine sf_pdf_builtin_2 @ %def sf_pdf_builtin_2 @ \subsubsection{Strong Coupling} Test $\alpha_s$ as an implementation of the [[alpha_qcd_t]] abstract type. <>= call test (sf_pdf_builtin_3, "sf_pdf_builtin_3", & "running alpha_s", & u, results) <>= public :: sf_pdf_builtin_3 <>= subroutine sf_pdf_builtin_3 (u) integer, intent(in) :: u type(os_data_t) :: os_data type(qcd_t) :: qcd type(string_t) :: name write (u, "(A)") "* Test output: sf_pdf_builtin_3" write (u, "(A)") "* Purpose: initialize and evaluate alpha_s" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call os_data%init () name = "CTEQ6L" write (u, "(A)") "* Initialize qcd object" write (u, "(A)") allocate (alpha_qcd_pdf_builtin_t :: qcd%alpha) select type (alpha => qcd%alpha) type is (alpha_qcd_pdf_builtin_t) call alpha%init (name, os_data%pdf_builtin_datapath) end select call qcd%write (u) write (u, "(A)") write (u, "(A)") "* Evaluate for Q = 100" write (u, "(A)") write (u, "(1x,A,F8.5)") "alpha = ", qcd%alpha%get (100._default) write (u, "(A)") write (u, "(A)") "* Cleanup" write (u, "(A)") write (u, "(A)") "* Test output end: sf_pdf_builtin_3" end subroutine sf_pdf_builtin_3 @ %def sf_pdf_builtin_3 @ \clearpage %------------------------------------------------------------------------ \section{LHAPDF} Parton distribution functions (PDFs) are available via an interface to the LHAPDF standard library. @ \subsection{The module} <<[[sf_lhapdf.f90]]>>= <> module sf_lhapdf <> <> use format_defs, only: FMT_17, FMT_19 use io_units use system_dependencies, only: LHAPDF_PDFSETS_PATH use system_dependencies, only: LHAPDF5_AVAILABLE use system_dependencies, only: LHAPDF6_AVAILABLE use diagnostics use physics_defs, only: PROTON, PHOTON, PIPLUS, GLUON use physics_defs, only: HADRON_REMNANT_SINGLET use physics_defs, only: HADRON_REMNANT_TRIPLET use physics_defs, only: HADRON_REMNANT_OCTET use lorentz use sm_qcd use pdg_arrays use model_data use flavors use colors use quantum_numbers use state_matrices use polarizations use sf_base use lhapdf !NODEP! use hoppet_interface <> <> <> <> <> <> contains <> end module sf_lhapdf @ %def sf_lhapdf @ \subsection{Codes for default PDF sets} The default PDF for protons set is chosen to be CTEQ6ll (LO fit with LO $\alpha_s$). <>= character(*), parameter :: LHAPDF5_DEFAULT_PROTON = "cteq6ll.LHpdf" character(*), parameter :: LHAPDF5_DEFAULT_PION = "ABFKWPI.LHgrid" character(*), parameter :: LHAPDF5_DEFAULT_PHOTON = "GSG960.LHgrid" character(*), parameter :: LHAPDF6_DEFAULT_PROTON = "CT10" @ %def LHAPDF5_DEFAULT_PROTON LHAPDF5_DEFAULT_PION @ %def LHAPDF5_DEFAULT_PHOTON LHAPDF6_DEFAULT_PROTON @ \subsection{LHAPDF library interface} Here we specify explicit interfaces for all LHAPDF routines that we use below. <>= interface subroutine InitPDFsetM (set, file) integer, intent(in) :: set character(*), intent(in) :: file end subroutine InitPDFsetM end interface @ %def InitPDFsetM <>= interface subroutine InitPDFM (set, mem) integer, intent(in) :: set, mem end subroutine InitPDFM end interface @ %def InitPDFM <>= interface subroutine numberPDFM (set, n_members) integer, intent(in) :: set integer, intent(out) :: n_members end subroutine numberPDFM end interface @ %def numberPDFM <>= interface subroutine evolvePDFM (set, x, q, ff) integer, intent(in) :: set double precision, intent(in) :: x, q double precision, dimension(-6:6), intent(out) :: ff end subroutine evolvePDFM end interface @ %def evolvePDFM <>= interface subroutine evolvePDFphotonM (set, x, q, ff, fphot) integer, intent(in) :: set double precision, intent(in) :: x, q double precision, dimension(-6:6), intent(out) :: ff double precision, intent(out) :: fphot end subroutine evolvePDFphotonM end interface @ %def evolvePDFphotonM <>= interface subroutine evolvePDFpM (set, x, q, s, scheme, ff) integer, intent(in) :: set double precision, intent(in) :: x, q, s integer, intent(in) :: scheme double precision, dimension(-6:6), intent(out) :: ff end subroutine evolvePDFpM end interface @ %def evolvePDFpM <>= interface subroutine GetXminM (set, mem, xmin) integer, intent(in) :: set, mem double precision, intent(out) :: xmin end subroutine GetXminM end interface @ %def GetXminM <>= interface subroutine GetXmaxM (set, mem, xmax) integer, intent(in) :: set, mem double precision, intent(out) :: xmax end subroutine GetXmaxM end interface @ %def GetXmaxM <>= interface subroutine GetQ2minM (set, mem, q2min) integer, intent(in) :: set, mem double precision, intent(out) :: q2min end subroutine GetQ2minM end interface @ %def GetQ2minM <>= interface subroutine GetQ2maxM (set, mem, q2max) integer, intent(in) :: set, mem double precision, intent(out) :: q2max end subroutine GetQ2maxM end interface @ %def GetQ2maxM <>= interface function has_photon () result(flag) logical :: flag end function has_photon end interface @ %def has_photon @ \subsection{The LHAPDF status} This type holds the initialization status of the LHAPDF system. Entry 1 is for proton PDFs, entry 2 for pion PDFs, entry 3 for photon PDFs. Since it is connected to the external LHAPDF library, this is a truly global object. We implement it as a a private module variable. To access it from elsewhere, the caller has to create and initialize an object of type [[lhapdf_status_t]], which acts as a proxy. <>= type :: lhapdf_global_status_t private logical, dimension(3) :: initialized = .false. end type lhapdf_global_status_t @ %def lhapdf_global_status_t <>= type(lhapdf_global_status_t), save :: lhapdf_global_status @ %def lhapdf_global_status <>= function lhapdf_global_status_is_initialized (set) result (flag) logical :: flag integer, intent(in), optional :: set if (present (set)) then select case (set) case (1:3); flag = lhapdf_global_status%initialized(set) case default; flag = .false. end select else flag = any (lhapdf_global_status%initialized) end if end function lhapdf_global_status_is_initialized @ %def lhapdf_global_status_is_initialized <>= subroutine lhapdf_global_status_set_initialized (set) integer, intent(in) :: set lhapdf_global_status%initialized(set) = .true. end subroutine lhapdf_global_status_set_initialized @ %def lhapdf_global_status_set_initialized @ This is the only public procedure, it tells the system to forget about previous initialization, allowing for changing the chosen PDF set. Note that such a feature works only if the global program flow is serial, so no two distinct sets are accessed simultaneously. But this applies to LHAPDF anyway. <>= public :: lhapdf_global_reset <>= subroutine lhapdf_global_reset () lhapdf_global_status%initialized = .false. end subroutine lhapdf_global_reset @ %def lhapdf_global_status_reset @ \subsection{LHAPDF initialization} Before using LHAPDF, we have to initialize it with a particular data set and member. This applies not just if we use structure functions, but also if we just use an $\alpha_s$ formula. The integer [[set]] should be $1$ for proton, $2$ for pion, and $3$ for photon, but this is just convention. It appears as if LHAPDF does not allow for multiple data sets being used concurrently (?), so multi-threaded usage with different sets (e.g., a scan) is excluded. The current setup with a global flag that indicates initialization is fine as long as Whizard itself is run in serial mode at the Sindarin level. If we introduce multithreading in any form from Sindarin, we have to rethink the implementation of the LHAPDF interface. (The same considerations apply to builtin PDFs.) If the particular set has already been initialized, do nothing. This implies that whenever we want to change the setup for a particular set, we have to reset the LHAPDF status. [[lhapdf_initialize]] has an obvious name clash with [[lhapdf_init]], the reason it works for [[pdf_builtin]] is that there things are outsourced to a separate module (inc. [[lhapdf_status]] etc.). <>= public :: lhapdf_initialize <>= subroutine lhapdf_initialize (set, prefix, file, member, pdf, b_match) integer, intent(in) :: set type(string_t), intent(inout) :: prefix type(string_t), intent(inout) :: file type(lhapdf_pdf_t), intent(inout), optional :: pdf integer, intent(inout) :: member logical, intent(in), optional :: b_match if (prefix == "") prefix = LHAPDF_PDFSETS_PATH if (LHAPDF5_AVAILABLE) then if (lhapdf_global_status_is_initialized (set)) return if (file == "") then select case (set) case (1); file = LHAPDF5_DEFAULT_PROTON case (2); file = LHAPDF5_DEFAULT_PION case (3); file = LHAPDF5_DEFAULT_PHOTON end select end if if (data_file_exists (prefix // "/" // file)) then call InitPDFsetM (set, char (prefix // "/" // file)) else call msg_fatal ("LHAPDF: Data file '" & // char (file) // "' not found in '" // char (prefix) // "'.") return end if if (.not. dataset_member_exists (set, member)) then call msg_error (" LHAPDF: Chosen member does not exist for set '" & // char (file) // "', using default.") member = 0 end if call InitPDFM (set, member) else if (LHAPDF6_AVAILABLE) then ! TODO: (bcn 2015-07-07) we should have a closer look why this global ! check must not be executed ! if (lhapdf_global_status_is_initialized (set) .and. & ! pdf%is_associated ()) return if (file == "") then select case (set) case (1); file = LHAPDF6_DEFAULT_PROTON case (2); call msg_fatal ("LHAPDF6: no pion PDFs supported") case (3); call msg_fatal ("LHAPDF6: no photon PDFs supported") end select end if if (data_file_exists (prefix // "/" // file // "/" // file // ".info")) then call pdf%init (char (file), member) else call msg_fatal ("LHAPDF: Data file '" & // char (file) // "' not found in '" // char (prefix) // "'.") return end if end if if (present (b_match)) then if (b_match) then if (LHAPDF5_AVAILABLE) then call hoppet_init (.false.) else if (LHAPDF6_AVAILABLE) then call hoppet_init (.false., pdf) end if end if end if call lhapdf_global_status_set_initialized (set) contains function data_file_exists (fq_name) result (exist) type(string_t), intent(in) :: fq_name logical :: exist inquire (file = char(fq_name), exist = exist) end function data_file_exists function dataset_member_exists (set, member) result (exist) integer, intent(in) :: set, member logical :: exist integer :: n_members call numberPDFM (set, n_members) exist = member >= 0 .and. member <= n_members end function dataset_member_exists end subroutine lhapdf_initialize @ %def lhapdf_initialize @ \subsection{Kinematics} Set kinematics. If [[map]] is unset, the $r$ and $x$ values coincide, and the Jacobian $f(r)$ is trivial. If [[map]] is set, we are asked to provide an efficient mapping. For the test case, we set $x=r^2$ and consequently $f(r)=2r$. <>= procedure :: complete_kinematics => lhapdf_complete_kinematics <>= subroutine lhapdf_complete_kinematics (sf_int, x, xb, f, r, rb, map) class(lhapdf_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: x real(default), dimension(:), intent(out) :: xb real(default), intent(out) :: f real(default), dimension(:), intent(in) :: r real(default), dimension(:), intent(in) :: rb logical, intent(in) :: map if (map) then call msg_fatal ("LHAPDF: map flag not supported") else x(1) = r(1) xb(1)= rb(1) f = 1 end if call sf_int%split_momentum (x, xb) select case (sf_int%status) case (SF_DONE_KINEMATICS) sf_int%x = x(1) case (SF_FAILED_KINEMATICS) sf_int%x = 0 f = 0 end select end subroutine lhapdf_complete_kinematics @ %def lhapdf_complete_kinematics @ Overriding the default method: we compute the [[x]] value from the momentum configuration. In this specific case, we also set the internally stored $x$ value, so it can be used in the following routine. <>= procedure :: recover_x => lhapdf_recover_x <>= subroutine lhapdf_recover_x (sf_int, x, xb, x_free) class(lhapdf_t), intent(inout) :: sf_int real(default), dimension(:), intent(out) :: x real(default), dimension(:), intent(out) :: xb real(default), intent(inout), optional :: x_free call sf_int%base_recover_x (x, xb, x_free) sf_int%x = x(1) end subroutine lhapdf_recover_x @ %def lhapdf_recover_x @ Compute inverse kinematics. Here, we start with the $x$ array and compute the ``input'' $r$ values and the Jacobian $f$. After this, we can set momenta by the same formula as for normal kinematics. <>= procedure :: inverse_kinematics => lhapdf_inverse_kinematics <>= subroutine lhapdf_inverse_kinematics (sf_int, x, xb, f, r, rb, map, set_momenta) class(lhapdf_t), intent(inout) :: sf_int real(default), dimension(:), intent(in) :: x real(default), dimension(:), intent(in) :: xb real(default), intent(out) :: f real(default), dimension(:), intent(out) :: r real(default), dimension(:), intent(out) :: rb logical, intent(in) :: map logical, intent(in), optional :: set_momenta logical :: set_mom set_mom = .false.; if (present (set_momenta)) set_mom = set_momenta if (map) then call msg_fatal ("LHAPDF: map flag not supported") else r(1) = x(1) rb(1)= xb(1) f = 1 end if if (set_mom) then call sf_int%split_momentum (x, xb) select case (sf_int%status) case (SF_FAILED_KINEMATICS); f = 0 end select end if end subroutine lhapdf_inverse_kinematics @ %def lhapdf_inverse_kinematics @ \subsection{The LHAPDF data block} The data block holds the incoming flavor (which has to be proton, pion, or photon), the corresponding pointer to the global access data (1, 2, or 3), the flag [[invert]] which is set for an antiproton, the bounds as returned by LHAPDF for the specified set, and a mask that determines which partons will be actually in use. <>= public :: lhapdf_data_t <>= type, extends (sf_data_t) :: lhapdf_data_t private type(string_t) :: prefix type(string_t) :: file type(lhapdf_pdf_t) :: pdf integer :: member = 0 class(model_data_t), pointer :: model => null () type(flavor_t) :: flv_in integer :: set = 0 logical :: invert = .false. logical :: photon = .false. logical :: has_photon = .false. integer :: photon_scheme = 0 real(default) :: xmin = 0, xmax = 0 real(default) :: qmin = 0, qmax = 0 logical, dimension(-6:6) :: mask = .true. logical :: mask_photon = .true. logical :: hoppet_b_matching = .false. contains <> end type lhapdf_data_t @ %def lhapdf_data_t @ Generate PDF data. This is provided as a function, but it has the side-effect of initializing the requested PDF set. A finalizer is not needed. The library uses double precision, so since the default precision may be extended or quadruple, we use auxiliary variables for type casting. <>= procedure :: init => lhapdf_data_init <>= subroutine lhapdf_data_init & (data, model, pdg_in, prefix, file, member, photon_scheme, & hoppet_b_matching) class(lhapdf_data_t), intent(out) :: data class(model_data_t), intent(in), target :: model type(pdg_array_t), intent(in) :: pdg_in type(string_t), intent(in), optional :: prefix, file integer, intent(in), optional :: member integer, intent(in), optional :: photon_scheme logical, intent(in), optional :: hoppet_b_matching double precision :: xmin, xmax, q2min, q2max external :: InitPDFsetM, InitPDFM, numberPDFM external :: GetXminM, GetXmaxM, GetQ2minM, GetQ2maxM if (.not. LHAPDF5_AVAILABLE .and. .not. LHAPDF6_AVAILABLE) then call msg_fatal ("LHAPDF requested but library is not linked") return end if data%model => model if (pdg_array_get_length (pdg_in) /= 1) & call msg_fatal ("PDF: incoming particle must be unique") call data%flv_in%init (pdg_array_get (pdg_in, 1), model) select case (pdg_array_get (pdg_in, 1)) case (PROTON) data%set = 1 case (-PROTON) data%set = 1 data%invert = .true. case (PIPLUS) data%set = 2 case (-PIPLUS) data%set = 2 data%invert = .true. case (PHOTON) data%set = 3 data%photon = .true. if (present (photon_scheme)) data%photon_scheme = photon_scheme case default call msg_fatal (" LHAPDF: " & // "incoming particle must be (anti)proton, pion, or photon.") return end select if (present (prefix)) then data%prefix = prefix else data%prefix = "" end if if (present (file)) then data%file = file else data%file = "" end if if (present (hoppet_b_matching)) data%hoppet_b_matching = hoppet_b_matching if (LHAPDF5_AVAILABLE) then call lhapdf_initialize (data%set, & data%prefix, data%file, data%member, & b_match = data%hoppet_b_matching) call GetXminM (data%set, data%member, xmin) call GetXmaxM (data%set, data%member, xmax) call GetQ2minM (data%set, data%member, q2min) call GetQ2maxM (data%set, data%member, q2max) data%xmin = xmin data%xmax = xmax data%qmin = sqrt (q2min) data%qmax = sqrt (q2max) data%has_photon = has_photon () else if (LHAPDF6_AVAILABLE) then call lhapdf_initialize (data%set, & data%prefix, data%file, data%member, & data%pdf, data%hoppet_b_matching) data%xmin = data%pdf%getxmin () data%xmax = data%pdf%getxmax () data%qmin = sqrt(data%pdf%getq2min ()) data%qmax = sqrt(data%pdf%getq2max ()) data%has_photon = data%pdf%has_photon () end if end subroutine lhapdf_data_init @ %def lhapdf_data_init @ Enable/disable partons explicitly. If a mask entry is true, applying the PDF will generate the corresponding flavor on output. <>= procedure :: set_mask => lhapdf_data_set_mask <>= subroutine lhapdf_data_set_mask (data, mask) class(lhapdf_data_t), intent(inout) :: data logical, dimension(-6:6), intent(in) :: mask data%mask = mask end subroutine lhapdf_data_set_mask @ %def lhapdf_data_set_mask @ Return the public part of the data set. <>= public :: lhapdf_data_get_public_info <>= subroutine lhapdf_data_get_public_info & (data, lhapdf_dir, lhapdf_file, lhapdf_member) type(lhapdf_data_t), intent(in) :: data type(string_t), intent(out) :: lhapdf_dir, lhapdf_file integer, intent(out) :: lhapdf_member lhapdf_dir = data%prefix lhapdf_file = data%file lhapdf_member = data%member end subroutine lhapdf_data_get_public_info @ %def lhapdf_data_get_public_info @ Return the number of the member of the data set. <>= public :: lhapdf_data_get_set <>= function lhapdf_data_get_set(data) result(set) type(lhapdf_data_t), intent(in) :: data integer :: set set = data%set end function lhapdf_data_get_set @ %def lhapdf_data_get_set @ Output <>= procedure :: write => lhapdf_data_write <>= subroutine lhapdf_data_write (data, unit, verbose) class(lhapdf_data_t), intent(in) :: data integer, intent(in), optional :: unit logical, intent(in), optional :: verbose logical :: verb integer :: u if (present (verbose)) then verb = verbose else verb = .false. end if u = given_output_unit (unit); if (u < 0) return write (u, "(1x,A)") "LHAPDF data:" if (data%set /= 0) then write (u, "(3x,A)", advance="no") "flavor = " call data%flv_in%write (u); write (u, *) if (verb) then write (u, "(3x,A,A)") " prefix = ", char (data%prefix) else write (u, "(3x,A,A)") " prefix = ", & " " end if write (u, "(3x,A,A)") " file = ", char (data%file) write (u, "(3x,A,I3)") " member = ", data%member write (u, "(3x,A," // FMT_19 // ")") " x(min) = ", data%xmin write (u, "(3x,A," // FMT_19 // ")") " x(max) = ", data%xmax write (u, "(3x,A," // FMT_19 // ")") " Q(min) = ", data%qmin write (u, "(3x,A," // FMT_19 // ")") " Q(max) = ", data%qmax write (u, "(3x,A,L1)") " invert = ", data%invert if (data%photon) write (u, "(3x,A,I3)") & " IP2 (scheme) = ", data%photon_scheme write (u, "(3x,A,6(1x,L1),1x,A,1x,L1,1x,A,6(1x,L1))") & " mask = ", & data%mask(-6:-1), "*", data%mask(0), "*", data%mask(1:6) write (u, "(3x,A,L1)") " photon mask = ", data%mask_photon if (data%set == 1) write (u, "(3x,A,L1)") & " hoppet_b = ", data%hoppet_b_matching else write (u, "(3x,A)") "[undefined]" end if end subroutine lhapdf_data_write @ %def lhapdf_data_write @ The number of parameters is one. We do not generate transverse momentum. <>= procedure :: get_n_par => lhapdf_data_get_n_par <>= function lhapdf_data_get_n_par (data) result (n) class(lhapdf_data_t), intent(in) :: data integer :: n n = 1 end function lhapdf_data_get_n_par @ %def lhapdf_data_get_n_par @ Return the outgoing particle PDG codes. This is based on the mask. <>= procedure :: get_pdg_out => lhapdf_data_get_pdg_out <>= subroutine lhapdf_data_get_pdg_out (data, pdg_out) class(lhapdf_data_t), intent(in) :: data type(pdg_array_t), dimension(:), intent(inout) :: pdg_out integer, dimension(:), allocatable :: pdg1 integer :: n, np, i n = count (data%mask) np = 0; if (data%has_photon .and. data%mask_photon) np = 1 allocate (pdg1 (n + np)) pdg1(1:n) = pack ([(i, i = -6, 6)], data%mask) if (np == 1) pdg1(n+np) = PHOTON pdg_out(1) = pdg1 end subroutine lhapdf_data_get_pdg_out @ %def lhapdf_data_get_pdg_out @ Allocate the interaction record. <>= procedure :: allocate_sf_int => lhapdf_data_allocate_sf_int <>= subroutine lhapdf_data_allocate_sf_int (data, sf_int) class(lhapdf_data_t), intent(in) :: data class(sf_int_t), intent(inout), allocatable :: sf_int allocate (lhapdf_t :: sf_int) end subroutine lhapdf_data_allocate_sf_int @ %def lhapdf_data_allocate_sf_int @ Return the numerical PDF set index. <>= procedure :: get_pdf_set => lhapdf_data_get_pdf_set <>= elemental function lhapdf_data_get_pdf_set (data) result (pdf_set) class(lhapdf_data_t), intent(in) :: data integer :: pdf_set pdf_set = data%set end function lhapdf_data_get_pdf_set @ %def lhapdf_data_get_pdf_set @ \subsection{The LHAPDF object} The [[lhapdf_t]] data type is a $1\to 2$ interaction which describes the splitting of an (anti)proton into a parton and a beam remnant. We stay in the strict forward-splitting limit, but allow some invariant mass for the beam remnant such that the outgoing parton is exactly massless. For a real event, we would replace this by a parton cascade, where the outgoing partons have virtuality as dictated by parton-shower kinematics, and transverse momentum is generated. This is the LHAPDF object which holds input data together with the interaction. We also store the $x$ momentum fraction and the scale, since kinematics and function value are requested at different times. The PDF application is a $1\to 2$ splitting process, where the particles are ordered as (hadron, remnant, parton). Polarization is ignored completely. The beam particle is colorless, while partons and beam remnant carry color. The remnant gets a special flavor code. <>= public :: lhapdf_t <>= type, extends (sf_int_t) :: lhapdf_t type(lhapdf_data_t), pointer :: data => null () real(default) :: x = 0 real(default) :: q = 0 real(default) :: s = 0 contains <> end type lhapdf_t @ %def lhapdf_t @ Type string: display the chosen PDF set. <>= procedure :: type_string => lhapdf_type_string <>= function lhapdf_type_string (object) result (string) class(lhapdf_t), intent(in) :: object type(string_t) :: string if (associated (object%data)) then string = "LHAPDF: " // object%data%file else string = "LHAPDF: [undefined]" end if end function lhapdf_type_string @ %def lhapdf_type_string @ Output. Call the interaction routine after displaying the configuration. <>= procedure :: write => lhapdf_write <>= subroutine lhapdf_write (object, unit, testflag) class(lhapdf_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u u = given_output_unit (unit) if (associated (object%data)) then call object%data%write (u) if (object%status >= SF_DONE_KINEMATICS) then write (u, "(1x,A)") "SF parameters:" write (u, "(3x,A," // FMT_17 // ")") "x =", object%x if (object%status >= SF_FAILED_EVALUATION) then write (u, "(3x,A," // FMT_17 // ")") "Q =", object%q end if end if call object%base_write (u, testflag) else write (u, "(1x,A)") "LHAPDF data: [undefined]" end if end subroutine lhapdf_write @ %def lhapdf_write @ Initialize. We know that [[data]] will be of concrete type [[sf_lhapdf_data_t]], but we have to cast this explicitly. For this implementation, we set the incoming and outgoing masses equal to the physical particle mass, but keep the radiated mass zero. <>= procedure :: init => lhapdf_init <>= subroutine lhapdf_init (sf_int, data) class(lhapdf_t), intent(out) :: sf_int class(sf_data_t), intent(in), target :: data type(quantum_numbers_mask_t), dimension(3) :: mask type(flavor_t) :: flv, flv_remnant type(color_t) :: col0 type(quantum_numbers_t), dimension(3) :: qn integer :: i select type (data) type is (lhapdf_data_t) mask = quantum_numbers_mask (.false., .false., .true.) call col0%init () call sf_int%base_init (mask, [0._default], [0._default], [0._default]) sf_int%data => data do i = -6, 6 if (data%mask(i)) then call qn(1)%init (data%flv_in, col = col0) if (i == 0) then call flv%init (GLUON, data%model) call flv_remnant%init (HADRON_REMNANT_OCTET, data%model) else call flv%init (i, data%model) call flv_remnant%init & (sign (HADRON_REMNANT_TRIPLET, -i), data%model) end if call qn(2)%init ( & flv = flv_remnant, col = color_from_flavor (flv_remnant, 1)) call qn(2)%tag_radiated () call qn(3)%init ( & flv = flv, col = color_from_flavor (flv, 1, reverse=.true.)) call sf_int%add_state (qn) end if end do if (data%has_photon .and. data%mask_photon) then call flv%init (PHOTON, data%model) call flv_remnant%init (HADRON_REMNANT_SINGLET, data%model) call qn(2)%init (flv = flv_remnant, & col = color_from_flavor (flv_remnant, 1)) call qn(2)%tag_radiated () call qn(3)%init (flv = flv, & col = color_from_flavor (flv, 1, reverse=.true.)) call sf_int%add_state (qn) end if call sf_int%freeze () call sf_int%set_incoming ([1]) call sf_int%set_radiated ([2]) call sf_int%set_outgoing ([3]) sf_int%status = SF_INITIAL end select end subroutine lhapdf_init @ %def lhapdf_init @ \subsection{Structure function} We have to cast the LHAPDF arguments to/from double precision (possibly from/to extended/quadruple precision), if necessary. Furthermore, some structure functions can yield negative results (sea quarks close to $x=1$). We set these unphysical values to zero. <>= procedure :: apply => lhapdf_apply <>= subroutine lhapdf_apply (sf_int, scale, rescale, i_sub) class(lhapdf_t), intent(inout) :: sf_int real(default), intent(in) :: scale class(sf_rescale_t), intent(in), optional :: rescale integer, intent(in), optional :: i_sub real(default) :: x, s double precision :: xx, qq, ss double precision, dimension(-6:6) :: ff double precision :: fphot complex(default), dimension(:), allocatable :: fc integer :: i, i_sub_opt, j_sub external :: evolvePDFM, evolvePDFpM i_sub_opt = 0; if (present (i_sub)) i_sub_opt = i_sub associate (data => sf_int%data) sf_int%q = scale x = sf_int%x if (present (rescale)) call rescale%apply (x) s = sf_int%s xx = x if (debug2_active (D_BEAMS)) then call msg_debug2 (D_BEAMS, "lhapdf_apply") call msg_debug2 (D_BEAMS, "rescale: ", present(rescale)) call msg_debug2 (D_BEAMS, "i_sub: ", i_sub_opt) call msg_debug2 (D_BEAMS, "x: ", x) end if qq = min (data%qmax, scale) qq = max (data%qmin, qq) if (.not. data%photon) then if (data%invert) then if (data%has_photon) then if (LHAPDF5_AVAILABLE) then call evolvePDFphotonM & (data%set, xx, qq, ff(6:-6:-1), fphot) else if (LHAPDF6_AVAILABLE) then call data%pdf%evolve_pdfphotonm & (xx, qq, ff(6:-6:-1), fphot) end if else if (data%hoppet_b_matching) then call hoppet_eval (xx, qq, ff(6:-6:-1)) else if (LHAPDF5_AVAILABLE) then call evolvePDFM (data%set, xx, qq, ff(6:-6:-1)) else if (LHAPDF6_AVAILABLE) then call data%pdf%evolve_pdfm (xx, qq, ff(6:-6:-1)) end if end if end if else if (data%has_photon) then if (LHAPDF5_AVAILABLE) then call evolvePDFphotonM (data%set, xx, qq, ff, fphot) else if (LHAPDF6_AVAILABLE) then call data%pdf%evolve_pdfphotonm (xx, qq, ff, fphot) end if else if (data%hoppet_b_matching) then call hoppet_eval (xx, qq, ff) else if (LHAPDF5_AVAILABLE) then call evolvePDFM (data%set, xx, qq, ff) else if (LHAPDF6_AVAILABLE) then call data%pdf%evolve_pdfm (xx, qq, ff) end if end if end if end if else ss = s if (LHAPDF5_AVAILABLE) then call evolvePDFpM (data%set, xx, qq, & ss, data%photon_scheme, ff) else if (LHAPDF6_AVAILABLE) then call data%pdf%evolve_pdfpm (xx, qq, ss, & data%photon_scheme, ff) end if end if if (data%has_photon) then allocate (fc (count ([data%mask, data%mask_photon]))) fc = max (pack ([ff, fphot] / x, & [data%mask, data%mask_photon]), 0._default) else allocate (fc (count (data%mask))) fc = max (pack (ff / x, data%mask), 0._default) end if end associate if (debug_active (D_BEAMS)) print *, 'Set pdfs: ', real (fc) call sf_int%set_matrix_element (fc, [(i_sub_opt * size(fc) + i, i = 1, size(fc))]) sf_int%status = SF_EVALUATED end subroutine lhapdf_apply @ %def apply_lhapdf @ \subsection{Strong Coupling} Since the PDF codes provide a function for computing the running $\alpha_s$ value, we make this available as an implementation of the abstract [[alpha_qcd_t]] type, which is used for matrix element evaluation. <>= public :: alpha_qcd_lhapdf_t <>= type, extends (alpha_qcd_t) :: alpha_qcd_lhapdf_t type(string_t) :: pdfset_dir type(string_t) :: pdfset_file integer :: pdfset_member = -1 type(lhapdf_pdf_t) :: pdf contains <> end type alpha_qcd_lhapdf_t @ %def alpha_qcd_lhapdf_t @ Output. As in earlier versions we leave the LHAPDF path out. <>= procedure :: write => alpha_qcd_lhapdf_write <>= subroutine alpha_qcd_lhapdf_write (object, unit) class(alpha_qcd_lhapdf_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(3x,A)") "QCD parameters (lhapdf):" write (u, "(5x,A,A)") "PDF set = ", char (object%pdfset_file) write (u, "(5x,A,I0)") "PDF member = ", object%pdfset_member end subroutine alpha_qcd_lhapdf_write @ %def alpha_qcd_lhapdf_write @ Calculation: the numeric member ID selects the correct PDF set, which must be properly initialized. <>= interface double precision function alphasPDF (Q) double precision, intent(in) :: Q end function alphasPDF end interface @ %def alphasPDF @ <>= procedure :: get => alpha_qcd_lhapdf_get <>= function alpha_qcd_lhapdf_get (alpha_qcd, scale) result (alpha) class(alpha_qcd_lhapdf_t), intent(in) :: alpha_qcd real(default), intent(in) :: scale real(default) :: alpha if (LHAPDF5_AVAILABLE) then alpha = alphasPDF (dble (scale)) else if (LHAPDF6_AVAILABLE) then alpha = alpha_qcd%pdf%alphas_pdf (dble (scale)) end if end function alpha_qcd_lhapdf_get @ %def alpha_qcd_lhapdf_get @ Initialization. We need to access the (quasi-global) initialization status. <>= procedure :: init => alpha_qcd_lhapdf_init <>= subroutine alpha_qcd_lhapdf_init (alpha_qcd, file, member, path) class(alpha_qcd_lhapdf_t), intent(out) :: alpha_qcd type(string_t), intent(inout) :: file integer, intent(inout) :: member type(string_t), intent(inout) :: path alpha_qcd%pdfset_file = file alpha_qcd%pdfset_member = member if (alpha_qcd%pdfset_member < 0) & call msg_fatal ("QCD parameter initialization: PDF set " & // char (file) // " is unknown") if (LHAPDF5_AVAILABLE) then call lhapdf_initialize (1, path, file, member) else if (LHAPDF6_AVAILABLE) then call lhapdf_initialize & (1, path, file, member, alpha_qcd%pdf) end if end subroutine alpha_qcd_lhapdf_init @ %def alpha_qcd_lhapdf_init @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[sf_lhapdf_ut.f90]]>>= <> module sf_lhapdf_ut use unit_tests use system_dependencies, only: LHAPDF5_AVAILABLE use system_dependencies, only: LHAPDF6_AVAILABLE use sf_lhapdf_uti <> <> contains <> end module sf_lhapdf_ut @ %def sf_lhapdf_ut @ <<[[sf_lhapdf_uti.f90]]>>= <> module sf_lhapdf_uti <> <> use system_dependencies, only: LHAPDF5_AVAILABLE use system_dependencies, only: LHAPDF6_AVAILABLE use os_interface use physics_defs, only: PROTON use sm_qcd use lorentz use pdg_arrays use flavors use interactions, only: reset_interaction_counter use model_data use sf_base use sf_lhapdf <> <> contains <> end module sf_lhapdf_uti @ %def sf_lhapdf_ut @ API: driver for the unit tests below. <>= public :: sf_lhapdf_test <>= subroutine sf_lhapdf_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine sf_lhapdf_test @ %def sf_lhapdf_test @ \subsubsection{Test structure function data} Construct and display a test structure function data object. <>= if (LHAPDF5_AVAILABLE) then call test (sf_lhapdf_1, "sf_lhapdf5_1", & "structure function configuration", & u, results) else if (LHAPDF6_AVAILABLE) then call test (sf_lhapdf_1, "sf_lhapdf6_1", & "structure function configuration", & u, results) end if <>= public :: sf_lhapdf_1 <>= subroutine sf_lhapdf_1 (u) integer, intent(in) :: u type(model_data_t), target :: model type(pdg_array_t) :: pdg_in type(pdg_array_t), dimension(1) :: pdg_out integer, dimension(:), allocatable :: pdg1 class(sf_data_t), allocatable :: data write (u, "(A)") "* Test output: sf_lhapdf_1" write (u, "(A)") "* Purpose: initialize and display & &test structure function data" write (u, "(A)") write (u, "(A)") "* Create empty data object" write (u, "(A)") call model%init_sm_test () pdg_in = PROTON allocate (lhapdf_data_t :: data) call data%write (u) write (u, "(A)") write (u, "(A)") "* Initialize" write (u, "(A)") select type (data) type is (lhapdf_data_t) call data%init (model, pdg_in) end select call data%write (u) write (u, "(A)") write (u, "(1x,A)") "Outgoing particle codes:" call data%get_pdg_out (pdg_out) pdg1 = pdg_out(1) write (u, "(2x,99(1x,I0))") pdg1 call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_lhapdf_1" end subroutine sf_lhapdf_1 @ %def sf_lhapdf_1 @ \subsubsection{Test and probe structure function} Construct and display a structure function object based on the PDF builtin structure function. <>= if (LHAPDF5_AVAILABLE) then call test (sf_lhapdf_2, "sf_lhapdf5_2", & "structure function instance", & u, results) else if (LHAPDF6_AVAILABLE) then call test (sf_lhapdf_2, "sf_lhapdf6_2", & "structure function instance", & u, results) end if <>= public :: sf_lhapdf_2 <>= subroutine sf_lhapdf_2 (u) integer, intent(in) :: u type(model_data_t), target :: model type(flavor_t) :: flv type(pdg_array_t) :: pdg_in class(sf_data_t), allocatable, target :: data class(sf_int_t), allocatable :: sf_int type(vector4_t) :: k type(vector4_t), dimension(2) :: q real(default) :: E real(default), dimension(:), allocatable :: r, rb, x, xb real(default) :: f write (u, "(A)") "* Test output: sf_lhapdf_2" write (u, "(A)") "* Purpose: initialize and fill & &test structure function object" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call model%init_sm_test () call flv%init (PROTON, model) pdg_in = PROTON call lhapdf_global_reset () call reset_interaction_counter () allocate (lhapdf_data_t :: data) select type (data) type is (lhapdf_data_t) call data%init (model, pdg_in) end select write (u, "(A)") "* Initialize structure-function object" write (u, "(A)") call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1]) call sf_int%write (u) write (u, "(A)") write (u, "(A)") "* Initialize incoming momentum with E=500" write (u, "(A)") E = 500 k = vector4_moving (E, sqrt (E**2 - flv%get_mass ()**2), 3) call vector4_write (k, u) call sf_int%seed_kinematics ([k]) write (u, "(A)") write (u, "(A)") "* Set kinematics for x=0.5" write (u, "(A)") allocate (r (data%get_n_par ())) allocate (rb(size (r))) allocate (x (size (r))) allocate (xb(size (r))) r = 0.5_default rb = 1 - r call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%write (u) write (u, "(A)") write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A,9(1x,F10.7))") "f =", f write (u, "(A)") write (u, "(A)") "* Recover x from momenta" write (u, "(A)") q = sf_int%get_momenta (outgoing=.true.) call sf_int%final () deallocate (sf_int) call data%allocate_sf_int (sf_int) call sf_int%init (data) call sf_int%set_beam_index ([1]) call sf_int%seed_kinematics ([k]) call sf_int%set_momenta (q, outgoing=.true.) call sf_int%recover_x (x, xb) write (u, "(A,9(1x,F10.7))") "x =", x write (u, "(A,9(1x,F10.7))") "xb=", xb write (u, "(A)") write (u, "(A)") "* Evaluate for Q = 100 GeV" write (u, "(A)") call sf_int%complete_kinematics (x, xb, f, r, rb, map=.false.) call sf_int%apply (scale = 100._default) call sf_int%write (u, testflag = .true.) write (u, "(A)") write (u, "(A)") "* Cleanup" call sf_int%final () call model%final () write (u, "(A)") write (u, "(A)") "* Test output end: sf_lhapdf_2" end subroutine sf_lhapdf_2 @ %def sf_lhapdf_2 @ \subsubsection{Strong Coupling} Test $\alpha_s$ as an implementation of the [[alpha_qcd_t]] abstract type. <>= if (LHAPDF5_AVAILABLE) then call test (sf_lhapdf_3, "sf_lhapdf5_3", & "running alpha_s", & u, results) else if (LHAPDF6_AVAILABLE) then call test (sf_lhapdf_3, "sf_lhapdf6_3", & "running alpha_s", & u, results) end if <>= public :: sf_lhapdf_3 <>= subroutine sf_lhapdf_3 (u) integer, intent(in) :: u type(qcd_t) :: qcd type(string_t) :: name, path integer :: member write (u, "(A)") "* Test output: sf_lhapdf_3" write (u, "(A)") "* Purpose: initialize and evaluate alpha_s" write (u, "(A)") write (u, "(A)") "* Initialize configuration data" write (u, "(A)") call lhapdf_global_reset () if (LHAPDF5_AVAILABLE) then name = "cteq6ll.LHpdf" member = 1 path = "" else if (LHAPDF6_AVAILABLE) then name = "CT10" member = 1 path = "" end if write (u, "(A)") "* Initialize qcd object" write (u, "(A)") allocate (alpha_qcd_lhapdf_t :: qcd%alpha) select type (alpha => qcd%alpha) type is (alpha_qcd_lhapdf_t) call alpha%init (name, member, path) end select call qcd%write (u) write (u, "(A)") write (u, "(A)") "* Evaluate for Q = 100" write (u, "(A)") write (u, "(1x,A,F8.5)") "alpha = ", qcd%alpha%get (100._default) write (u, "(A)") write (u, "(A)") "* Cleanup" write (u, "(A)") write (u, "(A)") "* Test output end: sf_lhapdf_3" end subroutine sf_lhapdf_3 @ %def sf_lhapdf_3 @ \section{Easy PDF Access} For the shower, subtraction and matching, it is very useful to have direct access to $f(x,Q)$ independently of the used library. <<[[pdf.f90]]>>= <> module pdf <> use io_units use system_dependencies, only: LHAPDF5_AVAILABLE, LHAPDF6_AVAILABLE use diagnostics use beam_structures use lhapdf !NODEP! use pdf_builtin !NODEP! <> <> <> <> contains <> end module pdf @ %def pdf We support the following implementations: <>= integer, parameter, public :: STRF_NONE = 0 integer, parameter, public :: STRF_LHAPDF6 = 1 integer, parameter, public :: STRF_LHAPDF5 = 2 integer, parameter, public :: STRF_PDF_BUILTIN = 3 @ %def STRF_NONE STRF_LHAPDF6 STRF_LHAPDF5 STRF_PDF_BUILTIN @ A container to bundle all necessary PDF data. Could be moved to a more central location. <>= public :: pdf_data_t <>= type :: pdf_data_t type(lhapdf_pdf_t) :: pdf real(default) :: xmin, xmax, qmin, qmax integer :: type = STRF_NONE integer :: set = 0 contains <> end type pdf_data_t @ %def pdf_data @ <>= procedure :: init => pdf_data_init <>= subroutine pdf_data_init (pdf_data, pdf_data_in) class(pdf_data_t), intent(out) :: pdf_data type(pdf_data_t), target, intent(in) :: pdf_data_in pdf_data%xmin = pdf_data_in%xmin pdf_data%xmax = pdf_data_in%xmax pdf_data%qmin = pdf_data_in%qmin pdf_data%qmax = pdf_data_in%qmax pdf_data%set = pdf_data_in%set pdf_data%type = pdf_data_in%type if (pdf_data%type == STRF_LHAPDF6) then if (pdf_data_in%pdf%is_associated ()) then call lhapdf_copy_pointer (pdf_data_in%pdf, pdf_data%pdf) else call msg_bug ('pdf_data_init: pdf_data%pdf was not associated!') end if end if end subroutine pdf_data_init @ %def pdf_data_init @ <>= procedure :: write => pdf_data_write <>= subroutine pdf_data_write (pdf_data, unit) class(pdf_data_t), intent(in) :: pdf_data integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit); if (u < 0) return write (u, "(3x,A,I0)") "PDF set = ", pdf_data%set write (u, "(3x,A,I0)") "PDF type = ", pdf_data%type end subroutine pdf_data_write @ %def pdf_data_write @ <>= procedure :: setup => pdf_data_setup <>= subroutine pdf_data_setup (pdf_data, caller, beam_structure, lhapdf_member, set) class(pdf_data_t), intent(inout) :: pdf_data character(len=*), intent(in) :: caller type(beam_structure_t), intent(in) :: beam_structure integer, intent(in) :: lhapdf_member, set real(default) :: xmin, xmax, q2min, q2max pdf_data%set = set if (beam_structure%contains ("lhapdf")) then if (LHAPDF6_AVAILABLE) then pdf_data%type = STRF_LHAPDF6 else if (LHAPDF5_AVAILABLE) then pdf_data%type = STRF_LHAPDF5 end if write (msg_buffer, "(A,I0)") caller & // ": interfacing LHAPDF set #", pdf_data%set call msg_message () else if (beam_structure%contains ("pdf_builtin")) then pdf_data%type = STRF_PDF_BUILTIN write (msg_buffer, "(A,I0)") caller & // ": interfacing PDF builtin set #", pdf_data%set call msg_message () end if select case (pdf_data%type) case (STRF_LHAPDF6) pdf_data%xmin = pdf_data%pdf%getxmin () pdf_data%xmax = pdf_data%pdf%getxmax () pdf_data%qmin = sqrt(pdf_data%pdf%getq2min ()) pdf_data%qmax = sqrt(pdf_data%pdf%getq2max ()) case (STRF_LHAPDF5) call GetXminM (1, lhapdf_member, xmin) call GetXmaxM (1, lhapdf_member, xmax) call GetQ2minM (1, lhapdf_member, q2min) call GetQ2maxM (1, lhapdf_member, q2max) pdf_data%xmin = xmin pdf_data%xmax = xmax pdf_data%qmin = sqrt(q2min) pdf_data%qmax = sqrt(q2max) end select end subroutine pdf_data_setup @ %def pdf_data_setup @ This could be overloaded with a version that only asks for a specific flavor as it is supported by LHAPDF6. <>= procedure :: evolve => pdf_data_evolve <>= subroutine pdf_data_evolve (pdf_data, x, q_in, f) class(pdf_data_t), intent(inout) :: pdf_data real(double), intent(in) :: x, q_in real(double), dimension(-6:6), intent(out) :: f real(double) :: q select case (pdf_data%type) case (STRF_PDF_BUILTIN) call pdf_evolve_LHAPDF (pdf_data%set, x, q_in, f) case (STRF_LHAPDF6) q = min (pdf_data%qmax, q_in) q = max (pdf_data%qmin, q) call pdf_data%pdf%evolve_pdfm (x, q, f) case (STRF_LHAPDF5) q = min (pdf_data%qmax, q_in) q = max (pdf_data%qmin, q) call evolvePDFM (pdf_data%set, x, q, f) case default call msg_fatal ("PDF function: unknown PDF method.") end select end subroutine pdf_data_evolve @ %def pdf_data_evolve @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Dispatch} @ <<[[dispatch_beams.f90]]>>= <> module dispatch_beams <> <> use diagnostics use os_interface, only: os_data_t use variables, only: var_list_t use constants, only: PI use numeric_utils, only: vanishes use physics_defs, only: PHOTON use rng_base, only: rng_factory_t use pdg_arrays use model_data, only: model_data_t use dispatch_rng, only: dispatch_rng_factory use dispatch_rng, only: update_rng_seed_in_var_list use flavors, only: flavor_t use sm_qcd, only: qcd_t, alpha_qcd_fixed_t, alpha_qcd_from_scale_t use sm_qcd, only: alpha_qcd_from_lambda_t use physics_defs, only: MZ_REF, ALPHA_QCD_MZ_REF use beam_structures use sf_base use sf_mappings use sf_isr use sf_epa use sf_ewa use sf_escan use sf_gaussian use sf_beam_events use sf_circe1 use sf_circe2 use sf_pdf_builtin use sf_lhapdf <> <> <> <> contains <> end module dispatch_beams @ %def dispatch_beams @ This data type is a container for transferring structure-function specific data from the [[dispatch_sf_data]] to the [[dispatch_sf_channels]] subroutine. <>= public :: sf_prop_t <>= type :: sf_prop_t real(default), dimension(2) :: isr_eps = 1 end type sf_prop_t @ %def sf_prop_t @ Allocate a structure-function configuration object according to the [[sf_method]] string. The [[sf_prop]] object can be used to transfer structure-function specific data up and to the [[dispatch_sf_channels]] subroutine below, so they can be used for particular mappings. The [[var_list_global]] object is used for the RNG generator seed. It is intent(inout) because the RNG generator seed may change during initialization. The [[pdg_in]] array is the array of incoming flavors, corresponding to the upstream structure function or the beam array. This will be checked for the structure function in question and replaced by the outgoing flavors. The [[pdg_prc]] array is the array of incoming flavors (beam index, component index) for the hard process. <>= public :: dispatch_sf_data <>= subroutine dispatch_sf_data (data, sf_method, i_beam, sf_prop, & var_list, var_list_global, model, & os_data, sqrts, pdg_in, pdg_prc, polarized) class(sf_data_t), allocatable, intent(inout) :: data type(string_t), intent(in) :: sf_method integer, dimension(:), intent(in) :: i_beam type(pdg_array_t), dimension(:), intent(inout) :: pdg_in type(pdg_array_t), dimension(:,:), intent(in) :: pdg_prc type(sf_prop_t), intent(inout) :: sf_prop type(var_list_t), intent(in) :: var_list type(var_list_t), intent(inout) :: var_list_global integer :: next_rng_seed class(model_data_t), target, intent(in) :: model type(os_data_t), intent(in) :: os_data real(default), intent(in) :: sqrts logical, intent(in) :: polarized type(pdg_array_t), dimension(:), allocatable :: pdg_out real(default) :: isr_alpha, isr_q_max, isr_mass integer :: isr_order logical :: isr_recoil, isr_keep_energy real(default) :: epa_alpha, epa_x_min, epa_q_min, epa_q_max, epa_mass logical :: epa_recoil, epa_keep_energy integer :: epa_int_mode type(string_t) :: epa_mode real(default) :: ewa_x_min, ewa_pt_max, ewa_mass logical :: ewa_recoil, ewa_keep_energy type(pdg_array_t), dimension(:), allocatable :: pdg_prc1 integer :: ewa_id type(string_t) :: pdf_name type(string_t) :: lhapdf_dir, lhapdf_file type(string_t), dimension(13) :: lhapdf_photon_sets integer :: lhapdf_member, lhapdf_photon_scheme logical :: hoppet_b_matching class(rng_factory_t), allocatable :: rng_factory logical :: circe1_photon1, circe1_photon2, circe1_generate, & circe1_with_radiation real(default) :: circe1_sqrts, circe1_eps integer :: circe1_version, circe1_chattiness, & circe1_revision character(6) :: circe1_accelerator logical :: circe2_polarized type(string_t) :: circe2_design, circe2_file real(default), dimension(2) :: gaussian_spread logical :: beam_events_warn_eof type(string_t) :: beam_events_dir, beam_events_file logical :: escan_normalize integer :: i lhapdf_photon_sets = [var_str ("DOG0.LHgrid"), var_str ("DOG1.LHgrid"), & var_str ("DGG.LHgrid"), var_str ("LACG.LHgrid"), & var_str ("GSG0.LHgrid"), var_str ("GSG1.LHgrid"), & var_str ("GSG960.LHgrid"), var_str ("GSG961.LHgrid"), & var_str ("GRVG0.LHgrid"), var_str ("GRVG1.LHgrid"), & var_str ("ACFGPG.LHgrid"), var_str ("WHITG.LHgrid"), & var_str ("SASG.LHgrid")] select case (char (sf_method)) case ("pdf_builtin") allocate (pdf_builtin_data_t :: data) select type (data) type is (pdf_builtin_data_t) pdf_name = & var_list%get_sval (var_str ("$pdf_builtin_set")) hoppet_b_matching = & var_list%get_lval (var_str ("?hoppet_b_matching")) call data%init ( & model, pdg_in(i_beam(1)), & name = pdf_name, & path = os_data%pdf_builtin_datapath, & hoppet_b_matching = hoppet_b_matching) end select case ("pdf_builtin_photon") call msg_fatal ("Currently, there are no photon PDFs built into WHIZARD,", & [var_str ("for the photon content inside a proton or neutron use"), & var_str ("the 'lhapdf_photon' structure function.")]) case ("lhapdf") allocate (lhapdf_data_t :: data) if (pdg_array_get (pdg_in(i_beam(1)), 1) == PHOTON) then call msg_fatal ("The 'lhapdf' structure is intended only for protons and", & [var_str ("pions, please use 'lhapdf_photon' for photon beams.")]) end if lhapdf_dir = & var_list%get_sval (var_str ("$lhapdf_dir")) lhapdf_file = & var_list%get_sval (var_str ("$lhapdf_file")) lhapdf_member = & var_list%get_ival (var_str ("lhapdf_member")) lhapdf_photon_scheme = & var_list%get_ival (var_str ("lhapdf_photon_scheme")) hoppet_b_matching = & var_list%get_lval (var_str ("?hoppet_b_matching")) select type (data) type is (lhapdf_data_t) call data%init & (model, pdg_in(i_beam(1)), & lhapdf_dir, lhapdf_file, lhapdf_member, & lhapdf_photon_scheme, hoppet_b_matching) end select case ("lhapdf_photon") allocate (lhapdf_data_t :: data) if (pdg_array_get_length (pdg_in(i_beam(1))) /= 1 .or. & pdg_array_get (pdg_in(i_beam(1)), 1) /= PHOTON) then call msg_fatal ("The 'lhapdf_photon' structure function is exclusively for", & [var_str ("photon PDFs, i.e. for photons as beam particles")]) end if lhapdf_dir = & var_list%get_sval (var_str ("$lhapdf_dir")) lhapdf_file = & var_list%get_sval (var_str ("$lhapdf_photon_file")) lhapdf_member = & var_list%get_ival (var_str ("lhapdf_member")) lhapdf_photon_scheme = & var_list%get_ival (var_str ("lhapdf_photon_scheme")) if (.not. any (lhapdf_photon_sets == lhapdf_file)) then call msg_fatal ("This PDF set is not supported or not " // & "intended for photon beams.") end if select type (data) type is (lhapdf_data_t) call data%init & (model, pdg_in(i_beam(1)), & lhapdf_dir, lhapdf_file, lhapdf_member, & lhapdf_photon_scheme) end select case ("isr") allocate (isr_data_t :: data) isr_alpha = & var_list%get_rval (var_str ("isr_alpha")) if (vanishes (isr_alpha)) then isr_alpha = (var_list%get_rval (var_str ("ee"))) & ** 2 / (4 * PI) end if isr_q_max = & var_list%get_rval (var_str ("isr_q_max")) if (vanishes (isr_q_max)) then isr_q_max = sqrts end if isr_mass = var_list%get_rval (var_str ("isr_mass")) isr_order = var_list%get_ival (var_str ("isr_order")) isr_recoil = var_list%get_lval (var_str ("?isr_recoil")) isr_keep_energy = var_list%get_lval (var_str ("?isr_keep_energy")) select type (data) type is (isr_data_t) call data%init & (model, pdg_in (i_beam(1)), isr_alpha, isr_q_max, & isr_mass, isr_order, recoil = isr_recoil, keep_energy = & isr_keep_energy) call data%check () sf_prop%isr_eps(i_beam(1)) = data%get_eps () end select case ("epa") allocate (epa_data_t :: data) epa_mode = var_list%get_sval (var_str ("$epa_mode")) epa_int_mode = 0 - select case (char (epa_mode)) - case ("default", "Budnev_617") - epa_int_mode = 0 - case ("Budnev_616e") - epa_int_mode = 1 - case default - call msg_fatal ("EPA: unsupported EPA mode; please choose " // & - "'default', 'Budnev_616' or 'Budnev_616e'") - end select epa_alpha = var_list%get_rval (var_str ("epa_alpha")) if (vanishes (epa_alpha)) then epa_alpha = (var_list%get_rval (var_str ("ee"))) & ** 2 / (4 * PI) end if epa_x_min = var_list%get_rval (var_str ("epa_x_min")) epa_q_min = var_list%get_rval (var_str ("epa_q_min")) epa_q_max = var_list%get_rval (var_str ("epa_q_max")) if (vanishes (epa_q_max)) then epa_q_max = sqrts end if + select case (char (epa_mode)) + case ("default", "Budnev_617") + epa_int_mode = 0 + case ("Budnev_616e") + epa_int_mode = 1 + case ("log_power") + epa_int_mode = 2 + epa_q_max = sqrts + case ("log_simple") + epa_int_mode = 3 + epa_q_max = sqrts + case ("log") + epa_int_mode = 4 + epa_q_max = sqrts + case default + call msg_fatal ("EPA: unsupported EPA mode; please choose " // & + "'default', 'Budnev_616', 'Budnev_616e', 'log_power', " // & + "'log_simple', or 'log'") + end select epa_mass = var_list%get_rval (var_str ("epa_mass")) epa_recoil = var_list%get_lval (var_str ("?epa_recoil")) epa_keep_energy = var_list%get_lval (var_str ("?epa_keep_energy")) select type (data) type is (epa_data_t) call data%init & (model, epa_int_mode, pdg_in (i_beam(1)), epa_alpha, & epa_x_min, epa_q_min, epa_q_max, epa_mass, & recoil = epa_recoil, keep_energy = epa_keep_energy) call data%check () end select case ("ewa") allocate (ewa_data_t :: data) allocate (pdg_prc1 (size (pdg_prc, 2))) pdg_prc1 = pdg_prc(i_beam(1),:) if (any (pdg_array_get_length (pdg_prc1) /= 1) & .or. any (pdg_prc1 /= pdg_prc1(1))) then call msg_fatal & ("EWA: process incoming particle (W/Z) must be unique") end if ewa_id = abs (pdg_array_get (pdg_prc1(1), 1)) ewa_x_min = var_list%get_rval (var_str ("ewa_x_min")) ewa_pt_max = var_list%get_rval (var_str ("ewa_pt_max")) if (vanishes (ewa_pt_max)) then ewa_pt_max = sqrts end if ewa_mass = var_list%get_rval (var_str ("ewa_mass")) ewa_recoil = var_list%get_lval (& var_str ("?ewa_recoil")) ewa_keep_energy = var_list%get_lval (& var_str ("?ewa_keep_energy")) select type (data) type is (ewa_data_t) call data%init & (model, pdg_in (i_beam(1)), ewa_x_min, & ewa_pt_max, sqrts, ewa_recoil, & ewa_keep_energy, ewa_mass) call data%set_id (ewa_id) call data%check () end select case ("circe1") allocate (circe1_data_t :: data) select type (data) type is (circe1_data_t) circe1_photon1 = & var_list%get_lval (var_str ("?circe1_photon1")) circe1_photon2 = & var_list%get_lval (var_str ("?circe1_photon2")) circe1_sqrts = & var_list%get_rval (var_str ("circe1_sqrts")) circe1_eps = & var_list%get_rval (var_str ("circe1_eps")) if (circe1_sqrts <= 0) circe1_sqrts = sqrts circe1_generate = & var_list%get_lval (var_str ("?circe1_generate")) circe1_version = & var_list%get_ival (var_str ("circe1_ver")) circe1_revision = & var_list%get_ival (var_str ("circe1_rev")) circe1_accelerator = & char (var_list%get_sval (var_str ("$circe1_acc"))) circe1_chattiness = & var_list%get_ival (var_str ("circe1_chat")) circe1_with_radiation = & var_list%get_lval (var_str ("?circe1_with_radiation")) call data%init (model, pdg_in, circe1_sqrts, circe1_eps, & [circe1_photon1, circe1_photon2], & circe1_version, circe1_revision, circe1_accelerator, & circe1_chattiness, circe1_with_radiation) if (circe1_generate) then call msg_message ("CIRCE1: activating generator mode") call dispatch_rng_factory & (rng_factory, var_list_global, next_rng_seed) call update_rng_seed_in_var_list (var_list_global, next_rng_seed) call data%set_generator_mode (rng_factory) end if end select case ("circe2") allocate (circe2_data_t :: data) select type (data) type is (circe2_data_t) circe2_polarized = & var_list%get_lval (var_str ("?circe2_polarized")) circe2_file = & var_list%get_sval (var_str ("$circe2_file")) circe2_design = & var_list%get_sval (var_str ("$circe2_design")) call data%init (os_data, model, pdg_in, sqrts, & circe2_polarized, polarized, circe2_file, circe2_design) call msg_message ("CIRCE2: activating generator mode") call dispatch_rng_factory & (rng_factory, var_list_global, next_rng_seed) call update_rng_seed_in_var_list (var_list_global, next_rng_seed) call data%set_generator_mode (rng_factory) end select case ("gaussian") allocate (gaussian_data_t :: data) select type (data) type is (gaussian_data_t) gaussian_spread = & [var_list%get_rval (var_str ("gaussian_spread1")), & var_list%get_rval (var_str ("gaussian_spread2"))] call dispatch_rng_factory & (rng_factory, var_list_global, next_rng_seed) call update_rng_seed_in_var_list (var_list_global, next_rng_seed) call data%init (model, pdg_in, gaussian_spread, rng_factory) end select case ("beam_events") allocate (beam_events_data_t :: data) select type (data) type is (beam_events_data_t) beam_events_dir = os_data%whizard_beamsimpath beam_events_file = var_list%get_sval (& var_str ("$beam_events_file")) beam_events_warn_eof = var_list%get_lval (& var_str ("?beam_events_warn_eof")) call data%init (model, pdg_in, & beam_events_dir, beam_events_file, beam_events_warn_eof) end select case ("energy_scan") escan_normalize = & var_list%get_lval (var_str ("?energy_scan_normalize")) allocate (escan_data_t :: data) select type (data) type is (escan_data_t) if (escan_normalize) then call data%init (model, pdg_in) else call data%init (model, pdg_in, sqrts) end if end select case default if (associated (dispatch_sf_data_extra)) then call dispatch_sf_data_extra (data, sf_method, i_beam, & sf_prop, var_list, var_list_global, model, os_data, sqrts, pdg_in, & pdg_prc, polarized) end if if (.not. allocated (data)) then call msg_fatal ("Structure function '" & // char (sf_method) // "' not implemented") end if end select if (allocated (data)) then allocate (pdg_out (size (pdg_prc, 1))) call data%get_pdg_out (pdg_out) do i = 1, size (i_beam) pdg_in(i_beam(i)) = pdg_out(i) end do end if end subroutine dispatch_sf_data @ %def dispatch_sf_data @ This is a hook that allows us to inject further handlers for structure-function objects, in particular a test structure function. <>= public :: dispatch_sf_data_extra <>= procedure (dispatch_sf_data), pointer :: & dispatch_sf_data_extra => null () @ %def dispatch_sf_data_extra @ This is an auxiliary procedure, used by the beam-structure expansion: tell for a given structure function name, whether it corresponds to a pair spectrum ($n=2$), a single-particle structure function ($n=1$), or nothing ($n=0$). Though [[energy_scan]] can in principle also be a pair spectrum, it always has only one parameter. <>= public :: strfun_mode <>= function strfun_mode (name) result (n) type(string_t), intent(in) :: name integer :: n select case (char (name)) case ("none") n = 0 case ("sf_test_0", "sf_test_1") n = 1 case ("pdf_builtin","pdf_builtin_photon", & "lhapdf","lhapdf_photon") n = 1 case ("isr","epa","ewa") n = 1 case ("circe1", "circe2") n = 2 case ("gaussian") n = 2 case ("beam_events") n = 2 case ("energy_scan") n = 2 case default n = -1 call msg_bug ("Structure function '" // char (name) & // "' not supported yet") end select end function strfun_mode @ %def strfun_mode @ Dispatch a whole structure-function chain, given beam data and beam structure data. This could be done generically, but we should look at the specific combination of structure functions in order to select appropriate mappings. The [[beam_structure]] argument gets copied because we want to expand it to canonical form (one valid structure-function entry per record) before proceeding further. The [[pdg_prc]] argument is the array of incoming flavors. The first index is the beam index, the second one the process component index. Each element is itself a PDG array, notrivial if there is a flavor sum for the incoming state of this component. The dispatcher is divided in two parts. The first part configures the structure function data themselves. After this, we can configure the phase space for the elementary process. <>= public :: dispatch_sf_config <>= subroutine dispatch_sf_config (sf_config, sf_prop, beam_structure, & var_list, var_list_global, model, os_data, sqrts, pdg_prc) type(sf_config_t), dimension(:), allocatable, intent(out) :: sf_config type(sf_prop_t), intent(out) :: sf_prop type(beam_structure_t), intent(inout) :: beam_structure type(var_list_t), intent(in) :: var_list type(var_list_t), intent(inout) :: var_list_global class(model_data_t), target, intent(in) :: model type(os_data_t), intent(in) :: os_data real(default), intent(in) :: sqrts class(sf_data_t), allocatable :: sf_data type(beam_structure_t) :: beam_structure_tmp type(pdg_array_t), dimension(:,:), intent(in) :: pdg_prc type(string_t), dimension(:), allocatable :: prt_in type(pdg_array_t), dimension(:), allocatable :: pdg_in type(flavor_t) :: flv_in integer :: n_beam, n_record, i beam_structure_tmp = beam_structure call beam_structure_tmp%expand (strfun_mode) n_record = beam_structure_tmp%get_n_record () allocate (sf_config (n_record)) n_beam = beam_structure_tmp%get_n_beam () if (n_beam > 0) then allocate (prt_in (n_beam), pdg_in (n_beam)) prt_in = beam_structure_tmp%get_prt () do i = 1, n_beam call flv_in%init (prt_in(i), model) pdg_in(i) = flv_in%get_pdg () end do else n_beam = size (pdg_prc, 1) allocate (pdg_in (n_beam)) pdg_in = pdg_prc(:,1) end if do i = 1, n_record call dispatch_sf_data (sf_data, & beam_structure_tmp%get_name (i), & beam_structure_tmp%get_i_entry (i), & sf_prop, var_list, var_list_global, model, os_data, sqrts, & pdg_in, pdg_prc, & beam_structure_tmp%polarized ()) call sf_config(i)%init (beam_structure_tmp%get_i_entry (i), sf_data) deallocate (sf_data) end do end subroutine dispatch_sf_config @ %def dispatch_sf_config @ \subsection{QCD coupling} Allocate the [[alpha]] (running coupling) component of the [[qcd]] block with a concrete implementation, depending on the variable settings in the [[global]] record. If a fixed $\alpha_s$ is requested, we do not allocate the [[qcd%alpha]] object. In this case, the matrix element code will just take the model parameter as-is, which implies fixed $\alpha_s$. If the object is allocated, the $\alpha_s$ value is computed and updated for each matrix-element call. Also fetch the [[alphas_nf]] variable from the list and store it in the QCD record. This is not used in the $\alpha_s$ calculation, but the QCD record thus becomes a messenger for this user parameter. <>= public :: dispatch_qcd <>= subroutine dispatch_qcd (qcd, var_list, os_data) type(qcd_t), intent(inout) :: qcd type(var_list_t), intent(in) :: var_list type(os_data_t), intent(in) :: os_data logical :: fixed, from_mz, from_pdf_builtin, from_lhapdf, from_lambda_qcd real(default) :: mz, alpha_val, lambda integer :: nf, order, lhapdf_member type(string_t) :: pdfset, lhapdf_dir, lhapdf_file call unpack_variables () if (allocated (qcd%alpha)) deallocate (qcd%alpha) if (from_lhapdf .and. from_pdf_builtin) then call msg_fatal (" Mixing alphas evolution", & [var_str (" from LHAPDF and builtin PDF is not permitted")]) end if select case (count ([from_mz, from_pdf_builtin, from_lhapdf, from_lambda_qcd])) case (0) if (fixed) then allocate (alpha_qcd_fixed_t :: qcd%alpha) else call msg_fatal ("QCD alpha: no calculation mode set") end if case (2:) call msg_fatal ("QCD alpha: calculation mode is ambiguous") case (1) if (fixed) then call msg_fatal ("QCD alpha: use '?alphas_is_fixed = false' for " // & "running alphas") else if (from_mz) then allocate (alpha_qcd_from_scale_t :: qcd%alpha) else if (from_pdf_builtin) then allocate (alpha_qcd_pdf_builtin_t :: qcd%alpha) else if (from_lhapdf) then allocate (alpha_qcd_lhapdf_t :: qcd%alpha) else if (from_lambda_qcd) then allocate (alpha_qcd_from_lambda_t :: qcd%alpha) end if call msg_message ("QCD alpha: using a running strong coupling") end select call init_alpha () qcd%n_f = var_list%get_ival (var_str ("alphas_nf")) contains <> end subroutine dispatch_qcd @ %def dispatch_qcd @ <>= subroutine unpack_variables () fixed = var_list%get_lval (var_str ("?alphas_is_fixed")) from_mz = var_list%get_lval (var_str ("?alphas_from_mz")) from_pdf_builtin = & var_list%get_lval (var_str ("?alphas_from_pdf_builtin")) from_lhapdf = & var_list%get_lval (var_str ("?alphas_from_lhapdf")) from_lambda_qcd = & var_list%get_lval (var_str ("?alphas_from_lambda_qcd")) pdfset = var_list%get_sval (var_str ("$pdf_builtin_set")) lambda = var_list%get_rval (var_str ("lambda_qcd")) nf = var_list%get_ival (var_str ("alphas_nf")) order = var_list%get_ival (var_str ("alphas_order")) lhapdf_dir = var_list%get_sval (var_str ("$lhapdf_dir")) lhapdf_file = var_list%get_sval (var_str ("$lhapdf_file")) lhapdf_member = var_list%get_ival (var_str ("lhapdf_member")) if (var_list%contains (var_str ("mZ"))) then mz = var_list%get_rval (var_str ("mZ")) else mz = MZ_REF end if if (var_list%contains (var_str ("alphas"))) then alpha_val = var_list%get_rval (var_str ("alphas")) else alpha_val = ALPHA_QCD_MZ_REF end if end subroutine unpack_variables @ <>= subroutine init_alpha () select type (alpha => qcd%alpha) type is (alpha_qcd_fixed_t) alpha%val = alpha_val type is (alpha_qcd_from_scale_t) alpha%mu_ref = mz alpha%ref = alpha_val alpha%order = order alpha%nf = nf type is (alpha_qcd_from_lambda_t) alpha%lambda = lambda alpha%order = order alpha%nf = nf type is (alpha_qcd_pdf_builtin_t) call alpha%init (pdfset, & os_data%pdf_builtin_datapath) type is (alpha_qcd_lhapdf_t) call alpha%init (lhapdf_file, lhapdf_member, lhapdf_dir) end select end subroutine init_alpha @ Index: trunk/src/variables/variables.nw =================================================================== --- trunk/src/variables/variables.nw (revision 8402) +++ trunk/src/variables/variables.nw (revision 8403) @@ -1,6829 +1,6830 @@ % -*- ess-noweb-default-code-mode: f90-mode; noweb-default-code-mode: f90-mode; -*- % WHIZARD code as NOWEB source: variables for processes %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \chapter{Variables for Processes} \includemodulegraph{variables} This part introduces variables as user-controlled objects that influence the behavior of objects and calculations. Variables contain objects of intrinsic type or of a type as introced above. \begin{description} \item[variables] Store values of various kind, used by expressions and accessed by the command interface. This provides an implementation of the [[vars_t]] abstract type. \item[observables] Concrete implementation of observables (functions in the variable tree), applicable for \whizard. abstract type. \end{description} \clearpage %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Variables: Implementation} The user interface deals with variables that are handled similarly to full-flegded programming languages. The system will add a lot of predefined variables (model parameters, flags, etc.) that are accessible to the user by the same methods. Variables can be of various type: logical (boolean/flag), integer, real (default precision), subevents (used in cut expressions), arrays of PDG codes (aliases for particles), strings. Furthermore, in cut expressions we have unary and binary observables, which are used like real parameters but behave like functions. <<[[variables.f90]]>>= <> module variables <> <> use io_units use format_utils, only: pac_fmt use format_defs, only: FMT_12, FMT_19 use constants, only: eps0 use os_interface, only: paths_t use physics_defs, only: LAMBDA_QCD_REF use system_dependencies use fastjet !NODEP! use diagnostics use pdg_arrays use subevents use var_base <> <> <> <> <> contains <> end module variables @ %def variables @ \subsection{Variable list entries} Variable (and constant) values can be of one of the following types: <>= integer, parameter, public :: V_NONE = 0, V_LOG = 1, V_INT = 2, V_REAL = 3 integer, parameter, public :: V_CMPLX = 4, V_SEV = 5, V_PDG = 6, V_STR = 7 integer, parameter, public :: V_OBS1_INT = 11, V_OBS2_INT = 12 integer, parameter, public :: V_OBS1_REAL = 21, V_OBS2_REAL = 22 integer, parameter, public :: V_UOBS1_INT = 31, V_UOBS2_INT = 32 integer, parameter, public :: V_UOBS1_REAL = 41, V_UOBS2_REAL = 42 @ %def V_NONE V_LOG V_INT V_REAL V_CMPLX V_PRT V_SEV V_PDG @ %def V_OBS1_INT V_OBS2_INT V_OBS1_REAL V_OBS2_REAL @ %def V_UOBS1_INT V_UOBS2_INT V_UOBS1_REAL V_UOBS2_REAL @ \subsubsection{The type} This is an entry in the variable list. It can be of any type; in each case only one value is allocated. It may be physically allocated upon creation, in which case [[is_allocated]] is true, or it may contain just a pointer to a value somewhere else, in which case [[is_allocated]] is false. The flag [[is_defined]] is set when the variable is given a value, even the undefined value. (Therefore it is distinct from [[is_known]].) This matters for variable declaration in the SINDARIN language. The variable is set up in the compilation step and initially marked as defined, but after compilation all variables are set undefined. Each variable becomes defined when it is explicitly set. The difference matters in loops. [[is_locked]] means that it cannot be given a value using the interface routines [[var_list_set_XXX]] below. It can only be initialized, or change automatically due to a side effect. [[is_copy]] means that this is a local copy of a global variable. The copy has a pointer to the original, which can be used to restore a previous value. [[is_intrinsic]] means that this variable is defined by the program, not by the user. Intrinsic variables cannot be (re)declared, but their values can be reset unless they are locked. [[is_user_var]] means that the variable has been declared by the user. It could be a new variable, or a local copy of an intrinsic variable. The flag [[is_known]] is a pointer which parallels the use of the value pointer. For pointer variables, it is set if the value should point to a known value. For ordinary variables, it should be true. The value is implemented as a set of alternative type-specific pointers. This emulates polymorphism, and it allows for actual pointer variables. Observable-type variables have function pointers as values, so they behave like macros. The functions make use of the particle objects accessible via the pointers [[prt1]] and [[prt2]]. Finally, the [[next]] pointer indicates that we are making lists of variables. A more efficient implementation might switch to hashes or similar; the current implementation has $O(N)$ lookup. <>= public :: var_entry_t <>= type :: var_entry_t private integer :: type = V_NONE type(string_t) :: name logical :: is_allocated = .false. logical :: is_defined = .false. logical :: is_locked = .false. logical :: is_intrinsic = .false. logical :: is_user_var = .false. logical, pointer :: is_known => null () logical, pointer :: lval => null () integer, pointer :: ival => null () real(default), pointer :: rval => null () complex(default), pointer :: cval => null () type(subevt_t), pointer :: pval => null () type(pdg_array_t), pointer :: aval => null () type(string_t), pointer :: sval => null () procedure(obs_unary_int), nopass, pointer :: obs1_int => null () procedure(obs_unary_real), nopass, pointer :: obs1_real => null () procedure(obs_binary_int), nopass, pointer :: obs2_int => null () procedure(obs_binary_real), nopass, pointer :: obs2_real => null () type(prt_t), pointer :: prt1 => null () type(prt_t), pointer :: prt2 => null () type(var_entry_t), pointer :: next => null () type(var_entry_t), pointer :: previous => null () type(string_t) :: description end type var_entry_t @ %def var_entry_t @ \subsubsection{Interfaces for the observable functions} <>= public :: obs_unary_int public :: obs_unary_real public :: obs_binary_int public :: obs_binary_real <>= abstract interface function obs_unary_int (prt1) result (ival) import integer :: ival type(prt_t), intent(in) :: prt1 end function obs_unary_int end interface abstract interface function obs_unary_real (prt1) result (rval) import real(default) :: rval type(prt_t), intent(in) :: prt1 end function obs_unary_real end interface abstract interface function obs_binary_int (prt1, prt2) result (ival) import integer :: ival type(prt_t), intent(in) :: prt1, prt2 end function obs_binary_int end interface abstract interface function obs_binary_real (prt1, prt2) result (rval) import real(default) :: rval type(prt_t), intent(in) :: prt1, prt2 end function obs_binary_real end interface @ %def obs_unary_int obs_unary_real obs_binary_real @ \subsubsection{Initialization} Initialize an entry, optionally with a physical value. We also allocate the [[is_known]] flag and set it if the value is set. <>= public :: var_entry_init_int <>= subroutine var_entry_init_log (var, name, lval, intrinsic, user) type(var_entry_t), intent(out) :: var type(string_t), intent(in) :: name logical, intent(in), optional :: lval logical, intent(in), optional :: intrinsic, user var%name = name var%type = V_LOG allocate (var%lval, var%is_known) if (present (lval)) then var%lval = lval var%is_defined = .true. var%is_known = .true. else var%is_known = .false. end if if (present (intrinsic)) var%is_intrinsic = intrinsic if (present (user)) var%is_user_var = user var%is_allocated = .true. end subroutine var_entry_init_log subroutine var_entry_init_int (var, name, ival, intrinsic, user) type(var_entry_t), intent(out) :: var type(string_t), intent(in) :: name integer, intent(in), optional :: ival logical, intent(in), optional :: intrinsic, user var%name = name var%type = V_INT allocate (var%ival, var%is_known) if (present (ival)) then var%ival = ival var%is_defined = .true. var%is_known = .true. else var%is_known = .false. end if if (present (intrinsic)) var%is_intrinsic = intrinsic if (present (user)) var%is_user_var = user var%is_allocated = .true. end subroutine var_entry_init_int subroutine var_entry_init_real (var, name, rval, intrinsic, user) type(var_entry_t), intent(out) :: var type(string_t), intent(in) :: name real(default), intent(in), optional :: rval logical, intent(in), optional :: intrinsic, user var%name = name var%type = V_REAL allocate (var%rval, var%is_known) if (present (rval)) then var%rval = rval var%is_defined = .true. var%is_known = .true. else var%is_known = .false. end if if (present (intrinsic)) var%is_intrinsic = intrinsic if (present (user)) var%is_user_var = user var%is_allocated = .true. end subroutine var_entry_init_real subroutine var_entry_init_cmplx (var, name, cval, intrinsic, user) type(var_entry_t), intent(out) :: var type(string_t), intent(in) :: name complex(default), intent(in), optional :: cval logical, intent(in), optional :: intrinsic, user var%name = name var%type = V_CMPLX allocate (var%cval, var%is_known) if (present (cval)) then var%cval = cval var%is_defined = .true. var%is_known = .true. else var%is_known = .false. end if if (present (intrinsic)) var%is_intrinsic = intrinsic if (present (user)) var%is_user_var = user var%is_allocated = .true. end subroutine var_entry_init_cmplx subroutine var_entry_init_subevt (var, name, pval, intrinsic, user) type(var_entry_t), intent(out) :: var type(string_t), intent(in) :: name type(subevt_t), intent(in), optional :: pval logical, intent(in), optional :: intrinsic, user var%name = name var%type = V_SEV allocate (var%pval, var%is_known) if (present (pval)) then var%pval = pval var%is_defined = .true. var%is_known = .true. else var%is_known = .false. end if if (present (intrinsic)) var%is_intrinsic = intrinsic if (present (user)) var%is_user_var = user var%is_allocated = .true. end subroutine var_entry_init_subevt subroutine var_entry_init_pdg_array (var, name, aval, intrinsic, user) type(var_entry_t), intent(out) :: var type(string_t), intent(in) :: name type(pdg_array_t), intent(in), optional :: aval logical, intent(in), optional :: intrinsic, user var%name = name var%type = V_PDG allocate (var%aval, var%is_known) if (present (aval)) then var%aval = aval var%is_defined = .true. var%is_known = .true. else var%is_known = .false. end if if (present (intrinsic)) var%is_intrinsic = intrinsic if (present (user)) var%is_user_var = user var%is_allocated = .true. end subroutine var_entry_init_pdg_array subroutine var_entry_init_string (var, name, sval, intrinsic, user) type(var_entry_t), intent(out) :: var type(string_t), intent(in) :: name type(string_t), intent(in), optional :: sval logical, intent(in), optional :: intrinsic, user var%name = name var%type = V_STR allocate (var%sval, var%is_known) if (present (sval)) then var%sval = sval var%is_defined = .true. var%is_known = .true. else var%is_known = .false. end if if (present (intrinsic)) var%is_intrinsic = intrinsic if (present (user)) var%is_user_var = user var%is_allocated = .true. end subroutine var_entry_init_string @ %def var_entry_init_log @ %def var_entry_init_int @ %def var_entry_init_real @ %def var_entry_init_cmplx @ %def var_entry_init_subevt @ %def var_entry_init_pdg_array @ %def var_entry_init_string @ Initialize an entry with a pointer to the value and, for numeric/logical values, a pointer to the [[is_known]] flag. <>= subroutine var_entry_init_log_ptr (var, name, lval, is_known, intrinsic) type(var_entry_t), intent(out) :: var type(string_t), intent(in) :: name logical, intent(in), target :: lval logical, intent(in), target :: is_known logical, intent(in), optional :: intrinsic var%name = name var%type = V_LOG var%lval => lval var%is_known => is_known if (present (intrinsic)) var%is_intrinsic = intrinsic var%is_defined = .true. end subroutine var_entry_init_log_ptr subroutine var_entry_init_int_ptr (var, name, ival, is_known, intrinsic) type(var_entry_t), intent(out) :: var type(string_t), intent(in) :: name integer, intent(in), target :: ival logical, intent(in), target :: is_known logical, intent(in), optional :: intrinsic var%name = name var%type = V_INT var%ival => ival var%is_known => is_known if (present (intrinsic)) var%is_intrinsic = intrinsic var%is_defined = .true. end subroutine var_entry_init_int_ptr subroutine var_entry_init_real_ptr (var, name, rval, is_known, intrinsic) type(var_entry_t), intent(out) :: var type(string_t), intent(in) :: name real(default), intent(in), target :: rval logical, intent(in), target :: is_known logical, intent(in), optional :: intrinsic var%name = name var%type = V_REAL var%rval => rval var%is_known => is_known if (present (intrinsic)) var%is_intrinsic = intrinsic var%is_defined = .true. end subroutine var_entry_init_real_ptr subroutine var_entry_init_cmplx_ptr (var, name, cval, is_known, intrinsic) type(var_entry_t), intent(out) :: var type(string_t), intent(in) :: name complex(default), intent(in), target :: cval logical, intent(in), target :: is_known logical, intent(in), optional :: intrinsic var%name = name var%type = V_CMPLX var%cval => cval var%is_known => is_known if (present (intrinsic)) var%is_intrinsic = intrinsic var%is_defined = .true. end subroutine var_entry_init_cmplx_ptr subroutine var_entry_init_pdg_array_ptr (var, name, aval, is_known, intrinsic) type(var_entry_t), intent(out) :: var type(string_t), intent(in) :: name type(pdg_array_t), intent(in), target :: aval logical, intent(in), target :: is_known logical, intent(in), optional :: intrinsic var%name = name var%type = V_PDG var%aval => aval var%is_known => is_known if (present (intrinsic)) var%is_intrinsic = intrinsic var%is_defined = .true. end subroutine var_entry_init_pdg_array_ptr subroutine var_entry_init_subevt_ptr (var, name, pval, is_known, intrinsic) type(var_entry_t), intent(out) :: var type(string_t), intent(in) :: name type(subevt_t), intent(in), target :: pval logical, intent(in), target :: is_known logical, intent(in), optional :: intrinsic var%name = name var%type = V_SEV var%pval => pval var%is_known => is_known if (present (intrinsic)) var%is_intrinsic = intrinsic var%is_defined = .true. end subroutine var_entry_init_subevt_ptr subroutine var_entry_init_string_ptr (var, name, sval, is_known, intrinsic) type(var_entry_t), intent(out) :: var type(string_t), intent(in) :: name type(string_t), intent(in), target :: sval logical, intent(in), target :: is_known logical, intent(in), optional :: intrinsic var%name = name var%type = V_STR var%sval => sval var%is_known => is_known if (present (intrinsic)) var%is_intrinsic = intrinsic var%is_defined = .true. end subroutine var_entry_init_string_ptr @ %def var_entry_init_log_ptr @ %def var_entry_init_int_ptr @ %def var_entry_init_real_ptr @ %def var_entry_init_cmplx_ptr @ %def var_entry_init_pdg_array_ptr @ %def var_entry_init_subevt_ptr @ %def var_entry_init_string_ptr @ Initialize an entry with an observable. The procedure pointer is not yet set. <>= subroutine var_entry_init_obs (var, name, type, prt1, prt2) type(var_entry_t), intent(out) :: var type(string_t), intent(in) :: name integer, intent(in) :: type type(prt_t), intent(in), target :: prt1 type(prt_t), intent(in), optional, target :: prt2 var%type = type var%name = name var%prt1 => prt1 if (present (prt2)) var%prt2 => prt2 var%is_intrinsic = .true. var%is_defined = .true. end subroutine var_entry_init_obs @ %def var_entry_init_obs @ Mark an entry as undefined it it is a user-defined variable object, so force re-initialization. <>= subroutine var_entry_undefine (var) type(var_entry_t), intent(inout) :: var var%is_defined = .not. var%is_user_var var%is_known = var%is_defined .and. var%is_known end subroutine var_entry_undefine @ %def var_entry_undefine @ Clear an entry: mark it as unknown. <>= subroutine var_entry_clear (var) type(var_entry_t), intent(inout) :: var var%is_known = .false. end subroutine var_entry_clear @ %def var_entry_clear @ Lock an entry: forbid resetting the entry after initialization. <>= subroutine var_entry_lock (var, locked) type(var_entry_t), intent(inout) :: var logical, intent(in), optional :: locked if (present (locked)) then var%is_locked = locked else var%is_locked = .true. end if end subroutine var_entry_lock @ %def var_entry_lock @ \subsubsection{Finalizer} <>= subroutine var_entry_final (var) type(var_entry_t), intent(inout) :: var if (var%is_allocated) then select case (var%type) case (V_LOG); deallocate (var%lval) case (V_INT); deallocate (var%ival) case (V_REAL);deallocate (var%rval) case (V_CMPLX);deallocate (var%cval) case (V_SEV); deallocate (var%pval) case (V_PDG); deallocate (var%aval) case (V_STR); deallocate (var%sval) end select deallocate (var%is_known) var%is_allocated = .false. var%is_defined = .false. end if end subroutine var_entry_final @ %def var_entry_final @ \subsubsection{Output} <>= recursive subroutine var_entry_write (var, unit, model_name, & intrinsic, pacified, descriptions, ascii_output) type(var_entry_t), intent(in) :: var integer, intent(in), optional :: unit type(string_t), intent(in), optional :: model_name logical, intent(in), optional :: intrinsic logical, intent(in), optional :: pacified logical, intent(in), optional :: descriptions logical, intent(in), optional :: ascii_output type(string_t) :: col_string logical :: show_desc, ao integer :: u u = given_output_unit (unit); if (u < 0) return show_desc = .false.; if (present (descriptions)) show_desc = descriptions ao = .false.; if (present (ascii_output)) ao = ascii_output if (show_desc) then if (ao) then col_string = create_col_string (COL_BLUE) if (var%is_locked) then write (u, "(A)", advance="no") char (achar(27) // col_string) // & char (var%name) // achar(27) // "[0m" //" fixed-value=" else write (u, "(A)", advance="no") char (achar(27) // col_string) // & char (var%name) // achar(27) // "[0m" //" default=" end if col_string = create_col_string (COL_RED) write (u, "(A)", advance="no") char (achar(27) // col_string) call var_write_val (var, u, "no", pacified=.true.) write (u, "(A)") achar(27) // "[0m" write (u, "(A)") char (var%description) return else write (u, "(A)") "\item" write (u, "(A)", advance="no") "\ttt{" // char ( & replace (replace (var%name, "_", "\_", every=.true.), "$", "\$" )) // & "} " if (var%is_known) then if (var%is_locked) then write (u, "(A)", advance="no") "\qquad (fixed value: \ttt{" else write (u, "(A)", advance="no") "\qquad (default: \ttt{" end if call var_write_val (var, u, "no", pacified=.true., escape_tex=.true.) write (u, "(A)", advance="no") "})" end if write (u, "(A)") " \newline" write (u, "(A)") char (var%description) write (u, "(A)") "%%%%%" return end if end if if (present (intrinsic)) then if (var%is_intrinsic .neqv. intrinsic) return end if if (.not. var%is_defined) then write (u, "(A,1x)", advance="no") "[undefined]" end if if (.not. var%is_intrinsic) then write (u, "(A,1x)", advance="no") "[user variable]" end if if (present (model_name)) then write (u, "(A,A)", advance="no") char(model_name), "." end if write (u, "(A)", advance="no") char (var%name) if (var%is_locked) write (u, "(A)", advance="no") "*" if (var%is_allocated) then write (u, "(A)", advance="no") " = " else if (var%type /= V_NONE) then write (u, "(A)", advance="no") " => " end if call var_write_val (var, u, "yes", pacified) end subroutine var_entry_write @ %def var_entry_write @ <>= subroutine var_write_val (var, u, advance, pacified, escape_tex) type(var_entry_t), intent(in) :: var integer, intent(in) :: u character(*), intent(in) :: advance logical, intent(in), optional :: pacified, escape_tex logical :: num_pac, et real(default) :: rval complex(default) :: cval character(len=7) :: fmt call pac_fmt (fmt, FMT_19, FMT_12, pacified) num_pac = .false.; if (present (pacified)) num_pac = pacified et = .false.; if (present (escape_tex)) et = escape_tex select case (var%type) case (V_NONE); write (u, '()', advance=advance) case (V_LOG) if (var%is_known) then if (var%lval) then write (u, "(A)", advance=advance) "true" else write (u, "(A)", advance=advance) "false" end if else write (u, "(A)", advance=advance) "[unknown logical]" end if case (V_INT) if (var%is_known) then write (u, "(I0)", advance=advance) var%ival else write (u, "(A)", advance=advance) "[unknown integer]" end if case (V_REAL) if (var%is_known) then rval = var%rval if (num_pac) then call pacify (rval, 10 * eps0) end if write (u, "(" // fmt // ")", advance=advance) rval else write (u, "(A)", advance=advance) "[unknown real]" end if case (V_CMPLX) if (var%is_known) then cval = var%cval if (num_pac) then call pacify (cval, 10 * eps0) end if write (u, "('('," // fmt // ",','," // fmt // ",')')", advance=advance) cval else write (u, "(A)", advance=advance) "[unknown complex]" end if case (V_SEV) if (var%is_known) then call subevt_write (var%pval, u, prefix=" ", & pacified = pacified) else write (u, "(A)", advance=advance) "[unknown subevent]" end if case (V_PDG) if (var%is_known) then call pdg_array_write (var%aval, u); write (u, *) else write (u, "(A)", advance=advance) "[unknown PDG array]" end if case (V_STR) if (var%is_known) then if (et) then write (u, "(A)", advance=advance) '"' // char (replace ( & replace (var%sval, "_", "\_", every=.true.), "$", "\$" )) // '"' else write (u, "(A)", advance=advance) '"' // char (var%sval) // '"' end if else write (u, "(A)", advance=advance) "[unknown string]" end if case (V_OBS1_INT); write (u, "(A)", advance=advance) "[int] = unary observable" case (V_OBS2_INT); write (u, "(A)", advance=advance) "[int] = binary observable" case (V_OBS1_REAL); write (u, "(A)", advance=advance) "[real] = unary observable" case (V_OBS2_REAL); write (u, "(A)", advance=advance) "[real] = binary observable" case (V_UOBS1_INT); write (u, "(A)", advance=advance) "[int] = unary user observable" case (V_UOBS2_INT); write (u, "(A)", advance=advance) "[int] = binary user observable" case (V_UOBS1_REAL); write (u, "(A)", advance=advance) "[real] = unary user observable" case (V_UOBS2_REAL); write (u, "(A)", advance=advance) "[real] = binary user observable" end select end subroutine var_write_val @ %def procedure @ \subsubsection{Accessing contents} <>= function var_entry_get_name (var) result (name) type(string_t) :: name type(var_entry_t), intent(in) :: var name = var%name end function var_entry_get_name function var_entry_get_type (var) result (type) integer :: type type(var_entry_t), intent(in) :: var type = var%type end function var_entry_get_type @ %def var_entry_get_name var_entry_get_type @ Return true if the variable is defined. This the case if it is allocated and known, or if it is a pointer. <>= function var_entry_is_defined (var) result (defined) logical :: defined type(var_entry_t), intent(in) :: var defined = var%is_defined end function var_entry_is_defined @ %def var_entry_is_defined @ Return true if the variable is locked. If [[force]] is active, always return false. <>= function var_entry_is_locked (var, force) result (locked) logical :: locked type(var_entry_t), intent(in) :: var logical, intent(in), optional :: force if (present (force)) then if (force) then locked = .false.; return end if end if locked = var%is_locked end function var_entry_is_locked @ %def var_entry_is_locked @ Return true if the variable is intrinsic <>= function var_entry_is_intrinsic (var) result (flag) logical :: flag type(var_entry_t), intent(in) :: var flag = var%is_intrinsic end function var_entry_is_intrinsic @ %def var_entry_is_intrinsic @ Return components <>= function var_entry_is_known (var) result (flag) logical :: flag type(var_entry_t), intent(in) :: var flag = var%is_known end function var_entry_is_known function var_entry_get_lval (var) result (lval) logical :: lval type(var_entry_t), intent(in) :: var lval = var%lval end function var_entry_get_lval function var_entry_get_ival (var) result (ival) integer :: ival type(var_entry_t), intent(in) :: var ival = var%ival end function var_entry_get_ival function var_entry_get_rval (var) result (rval) real(default) :: rval type(var_entry_t), intent(in) :: var rval = var%rval end function var_entry_get_rval function var_entry_get_cval (var) result (cval) complex(default) :: cval type(var_entry_t), intent(in) :: var cval = var%cval end function var_entry_get_cval function var_entry_get_aval (var) result (aval) type(pdg_array_t) :: aval type(var_entry_t), intent(in) :: var aval = var%aval end function var_entry_get_aval function var_entry_get_pval (var) result (pval) type(subevt_t) :: pval type(var_entry_t), intent(in) :: var pval = var%pval end function var_entry_get_pval function var_entry_get_sval (var) result (sval) type(string_t) :: sval type(var_entry_t), intent(in) :: var sval = var%sval end function var_entry_get_sval @ %def var_entry_get_lval @ %def var_entry_get_ival @ %def var_entry_get_rval @ %def var_entry_get_cval @ %def var_entry_get_aval @ %def var_entry_get_pval @ %def var_entry_get_sval @ Return pointers to components. <>= function var_entry_get_known_ptr (var) result (ptr) logical, pointer :: ptr type(var_entry_t), intent(in), target :: var ptr => var%is_known end function var_entry_get_known_ptr function var_entry_get_lval_ptr (var) result (ptr) logical, pointer :: ptr type(var_entry_t), intent(in), target :: var ptr => var%lval end function var_entry_get_lval_ptr function var_entry_get_ival_ptr (var) result (ptr) integer, pointer :: ptr type(var_entry_t), intent(in), target :: var ptr => var%ival end function var_entry_get_ival_ptr function var_entry_get_rval_ptr (var) result (ptr) real(default), pointer :: ptr type(var_entry_t), intent(in), target :: var ptr => var%rval end function var_entry_get_rval_ptr function var_entry_get_cval_ptr (var) result (ptr) complex(default), pointer :: ptr type(var_entry_t), intent(in), target :: var ptr => var%cval end function var_entry_get_cval_ptr function var_entry_get_pval_ptr (var) result (ptr) type(subevt_t), pointer :: ptr type(var_entry_t), intent(in), target :: var ptr => var%pval end function var_entry_get_pval_ptr function var_entry_get_aval_ptr (var) result (ptr) type(pdg_array_t), pointer :: ptr type(var_entry_t), intent(in), target :: var ptr => var%aval end function var_entry_get_aval_ptr function var_entry_get_sval_ptr (var) result (ptr) type(string_t), pointer :: ptr type(var_entry_t), intent(in), target :: var ptr => var%sval end function var_entry_get_sval_ptr @ %def var_entry_get_known_ptr @ %def var_entry_get_lval_ptr var_entry_get_ival_ptr var_entry_get_rval_ptr @ %def var_entry_get_cval_ptr var_entry_get_aval_ptr var_entry_get_pval_ptr @ %def var_entry_get_sval_ptr @ Furthermore, <>= function var_entry_get_prt1_ptr (var) result (ptr) type(prt_t), pointer :: ptr type(var_entry_t), intent(in), target :: var ptr => var%prt1 end function var_entry_get_prt1_ptr function var_entry_get_prt2_ptr (var) result (ptr) type(prt_t), pointer :: ptr type(var_entry_t), intent(in), target :: var ptr => var%prt2 end function var_entry_get_prt2_ptr @ %def var_entry_get_prt1_ptr @ %def var_entry_get_prt2_ptr @ Subroutines might be safer than functions for procedure pointer transfer. <>= subroutine var_entry_assign_obs1_int_ptr (ptr, var) procedure(obs_unary_int), pointer :: ptr type(var_entry_t), intent(in), target :: var ptr => var%obs1_int end subroutine var_entry_assign_obs1_int_ptr subroutine var_entry_assign_obs1_real_ptr (ptr, var) procedure(obs_unary_real), pointer :: ptr type(var_entry_t), intent(in), target :: var ptr => var%obs1_real end subroutine var_entry_assign_obs1_real_ptr subroutine var_entry_assign_obs2_int_ptr (ptr, var) procedure(obs_binary_int), pointer :: ptr type(var_entry_t), intent(in), target :: var ptr => var%obs2_int end subroutine var_entry_assign_obs2_int_ptr subroutine var_entry_assign_obs2_real_ptr (ptr, var) procedure(obs_binary_real), pointer :: ptr type(var_entry_t), intent(in), target :: var ptr => var%obs2_real end subroutine var_entry_assign_obs2_real_ptr @ %def var_entry_assign_obs1_int_ptr var_entry_assign_obs1_real_ptr @ %def var_entry_assign_obs2_int_ptr var_entry_assign_obs2_real_ptr @ \subsection{Setting values} Undefine the value. <>= subroutine var_entry_clear_value (var) type(var_entry_t), intent(inout) :: var var%is_known = .false. end subroutine var_entry_clear_value @ %def var_entry_clear_value <>= recursive subroutine var_entry_set_log & (var, lval, is_known, verbose, model_name) type(var_entry_t), intent(inout) :: var logical, intent(in) :: lval logical, intent(in) :: is_known logical, intent(in), optional :: verbose type(string_t), intent(in), optional :: model_name integer :: u u = logfile_unit () var%lval = lval var%is_known = is_known var%is_defined = .true. if (present (verbose)) then if (verbose) then call var_entry_write (var, model_name=model_name) call var_entry_write (var, model_name=model_name, unit=u) if (u >= 0) flush (u) end if end if end subroutine var_entry_set_log recursive subroutine var_entry_set_int & (var, ival, is_known, verbose, model_name) type(var_entry_t), intent(inout) :: var integer, intent(in) :: ival logical, intent(in) :: is_known logical, intent(in), optional :: verbose type(string_t), intent(in), optional :: model_name integer :: u u = logfile_unit () var%ival = ival var%is_known = is_known var%is_defined = .true. if (present (verbose)) then if (verbose) then call var_entry_write (var, model_name=model_name) call var_entry_write (var, model_name=model_name, unit=u) if (u >= 0) flush (u) end if end if end subroutine var_entry_set_int recursive subroutine var_entry_set_real & (var, rval, is_known, verbose, model_name, pacified) type(var_entry_t), intent(inout) :: var real(default), intent(in) :: rval logical, intent(in) :: is_known logical, intent(in), optional :: verbose, pacified type(string_t), intent(in), optional :: model_name integer :: u u = logfile_unit () var%rval = rval var%is_known = is_known var%is_defined = .true. if (present (verbose)) then if (verbose) then call var_entry_write & (var, model_name=model_name, pacified = pacified) call var_entry_write & (var, model_name=model_name, unit=u, pacified = pacified) if (u >= 0) flush (u) end if end if end subroutine var_entry_set_real recursive subroutine var_entry_set_cmplx & (var, cval, is_known, verbose, model_name, pacified) type(var_entry_t), intent(inout) :: var complex(default), intent(in) :: cval logical, intent(in) :: is_known logical, intent(in), optional :: verbose, pacified type(string_t), intent(in), optional :: model_name integer :: u u = logfile_unit () var%cval = cval var%is_known = is_known var%is_defined = .true. if (present (verbose)) then if (verbose) then call var_entry_write & (var, model_name=model_name, pacified = pacified) call var_entry_write & (var, model_name=model_name, unit=u, pacified = pacified) if (u >= 0) flush (u) end if end if end subroutine var_entry_set_cmplx recursive subroutine var_entry_set_pdg_array & (var, aval, is_known, verbose, model_name) type(var_entry_t), intent(inout) :: var type(pdg_array_t), intent(in) :: aval logical, intent(in) :: is_known logical, intent(in), optional :: verbose type(string_t), intent(in), optional :: model_name integer :: u u = logfile_unit () var%aval = aval var%is_known = is_known var%is_defined = .true. if (present (verbose)) then if (verbose) then call var_entry_write (var, model_name=model_name) call var_entry_write (var, model_name=model_name, unit=u) if (u >= 0) flush (u) end if end if end subroutine var_entry_set_pdg_array recursive subroutine var_entry_set_subevt & (var, pval, is_known, verbose, model_name) type(var_entry_t), intent(inout) :: var type(subevt_t), intent(in) :: pval logical, intent(in) :: is_known logical, intent(in), optional :: verbose type(string_t), intent(in), optional :: model_name integer :: u u = logfile_unit () var%pval = pval var%is_known = is_known var%is_defined = .true. if (present (verbose)) then if (verbose) then call var_entry_write (var, model_name=model_name) call var_entry_write (var, model_name=model_name, unit=u) if (u >= 0) flush (u) end if end if end subroutine var_entry_set_subevt recursive subroutine var_entry_set_string & (var, sval, is_known, verbose, model_name) type(var_entry_t), intent(inout) :: var type(string_t), intent(in) :: sval logical, intent(in) :: is_known logical, intent(in), optional :: verbose type(string_t), intent(in), optional :: model_name integer :: u u = logfile_unit () var%sval = sval var%is_known = is_known var%is_defined = .true. if (present (verbose)) then if (verbose) then call var_entry_write (var, model_name=model_name) call var_entry_write (var, model_name=model_name, unit=u) if (u >= 0) flush (u) end if end if end subroutine var_entry_set_string @ %def var_entry_set_log @ %def var_entry_set_int @ %def var_entry_set_real @ %def var_entry_set_cmplx @ %def var_entry_set_pdg_array @ %def var_entry_set_subevt @ %def var_entry_set_string @ <>= public :: var_entry_set_description <>= pure subroutine var_entry_set_description (var_entry, description) type(var_entry_t), intent(inout) :: var_entry type(string_t), intent(in) :: description var_entry%description = description end subroutine var_entry_set_description @ %def var_entry_set_description @ \subsection{Copies and pointer variables} Initialize an entry with a copy of an existing variable entry. The copy is physically allocated with the same type as the original. <>= subroutine var_entry_init_copy (var, original, user) type(var_entry_t), intent(out) :: var type(var_entry_t), intent(in), target :: original logical, intent(in), optional :: user type(string_t) :: name logical :: intrinsic name = var_entry_get_name (original) intrinsic = original%is_intrinsic select case (original%type) case (V_LOG) call var_entry_init_log (var, name, intrinsic=intrinsic, user=user) case (V_INT) call var_entry_init_int (var, name, intrinsic=intrinsic, user=user) case (V_REAL) call var_entry_init_real (var, name, intrinsic=intrinsic, user=user) case (V_CMPLX) call var_entry_init_cmplx (var, name, intrinsic=intrinsic, user=user) case (V_SEV) call var_entry_init_subevt (var, name, intrinsic=intrinsic, user=user) case (V_PDG) call var_entry_init_pdg_array (var, name, intrinsic=intrinsic, user=user) case (V_STR) call var_entry_init_string (var, name, intrinsic=intrinsic, user=user) end select end subroutine var_entry_init_copy @ %def var_entry_init_copy @ Copy the value of an entry. The target variable entry must be initialized correctly. <>= subroutine var_entry_copy_value (var, original) type(var_entry_t), intent(inout) :: var type(var_entry_t), intent(in), target :: original if (var_entry_is_known (original)) then select case (original%type) case (V_LOG) call var_entry_set_log (var, var_entry_get_lval (original), .true.) case (V_INT) call var_entry_set_int (var, var_entry_get_ival (original), .true.) case (V_REAL) call var_entry_set_real (var, var_entry_get_rval (original), .true.) case (V_CMPLX) call var_entry_set_cmplx (var, var_entry_get_cval (original), .true.) case (V_SEV) call var_entry_set_subevt (var, var_entry_get_pval (original), .true.) case (V_PDG) call var_entry_set_pdg_array (var, var_entry_get_aval (original), .true.) case (V_STR) call var_entry_set_string (var, var_entry_get_sval (original), .true.) end select else call var_entry_clear (var) end if end subroutine var_entry_copy_value @ %def var_entry_copy_value @ \subsection{Variable lists} \subsubsection{The type} Variable lists can be linked together. No initializer needed. They are deleted separately. <>= public :: var_list_t <>= type, extends (vars_t) :: var_list_t private type(var_entry_t), pointer :: first => null () type(var_entry_t), pointer :: last => null () type(var_list_t), pointer :: next => null () contains <> end type var_list_t @ %def var_list_t @ \subsubsection{Constructors} Implementation of the [[link]] deferred method. The implementation restricts itself to var lists of the same type. We might need to relax this constraint. <>= procedure :: link => var_list_link <>= subroutine var_list_link (vars, target_vars) class(var_list_t), intent(inout) :: vars class(vars_t), intent(in), target :: target_vars select type (target_vars) type is (var_list_t) vars%next => target_vars class default call msg_bug ("var_list_link: unsupported target type") end select end subroutine var_list_link @ %def var_list_link @ Append a new entry to an existing list. <>= subroutine var_list_append (var_list, var, verbose) type(var_list_t), intent(inout), target :: var_list type(var_entry_t), intent(inout), target :: var logical, intent(in), optional :: verbose if (associated (var_list%last)) then var%previous => var_list%last var_list%last%next => var else var%previous => null () var_list%first => var end if var_list%last => var if (present (verbose)) then if (verbose) call var_entry_write (var) end if end subroutine var_list_append @ %def var_list_append @ Sort a list. <>= procedure :: sort => var_list_sort <>= subroutine var_list_sort (var_list) class(var_list_t), intent(inout) :: var_list type(var_entry_t), pointer :: var, previous if (associated (var_list%first)) then var => var_list%first do while (associated (var)) previous => var%previous do while (associated (previous)) if (larger_var (previous, var)) then call var_list%swap_with_next (previous) end if previous => previous%previous end do var => var%next end do end if end subroutine var_list_sort @ %def var_list_sort @ <>= pure function larger_var (var1, var2) result (larger) logical :: larger type(var_entry_t), intent(in) :: var1, var2 type(string_t) :: str1, str2 str1 = replace (var1%name, "?", "") str1 = replace (str1, "$", "") str2 = replace (var2%name, "?", "") str2 = replace (str2, "$", "") larger = str1 > str2 end function larger_var @ %def larger_var @ <>= procedure :: get_previous => var_list_get_previous <>= function var_list_get_previous (var_list, var_entry) result (previous) type(var_entry_t), pointer :: previous class(var_list_t), intent(in) :: var_list type(var_entry_t), intent(in) :: var_entry previous => var_list%first if (previous%name == var_entry%name) then previous => null () else do while (associated (previous)) if (previous%next%name == var_entry%name) exit previous => previous%next end do end if end function var_list_get_previous @ %def var_list_get_previous @ <>= procedure :: swap_with_next => var_list_swap_with_next <>= subroutine var_list_swap_with_next (var_list, var_entry) class(var_list_t), intent(inout) :: var_list type(var_entry_t), intent(in) :: var_entry type(var_entry_t), pointer :: previous, this, next, next_next previous => var_list%get_previous (var_entry) if (.not. associated (previous)) then this => var_list%first else this => previous%next end if next => this%next next_next => next%next if (associated (previous)) then previous%next => next next%previous => previous else var_list%first => next next%previous => null () end if this%next => next_next if (associated (next_next)) then next_next%previous => this end if next%next => this this%previous => next if (.not. associated (next%next)) then var_list%last => next end if end subroutine var_list_swap_with_next @ %def var_list_swap_with_next @ Public methods for expanding the variable list (as subroutines) <>= generic :: append_log => var_list_append_log_s, var_list_append_log_c procedure, private :: var_list_append_log_s procedure, private :: var_list_append_log_c generic :: append_int => var_list_append_int_s, var_list_append_int_c procedure, private :: var_list_append_int_s procedure, private :: var_list_append_int_c generic :: append_real => var_list_append_real_s, var_list_append_real_c procedure, private :: var_list_append_real_s procedure, private :: var_list_append_real_c generic :: append_cmplx => var_list_append_cmplx_s, var_list_append_cmplx_c procedure, private :: var_list_append_cmplx_s procedure, private :: var_list_append_cmplx_c generic :: append_subevt => var_list_append_subevt_s, var_list_append_subevt_c procedure, private :: var_list_append_subevt_s procedure, private :: var_list_append_subevt_c generic :: append_pdg_array => var_list_append_pdg_array_s, var_list_append_pdg_array_c procedure, private :: var_list_append_pdg_array_s procedure, private :: var_list_append_pdg_array_c generic :: append_string => var_list_append_string_s, var_list_append_string_c procedure, private :: var_list_append_string_s procedure, private :: var_list_append_string_c <>= public :: var_list_append_log public :: var_list_append_int public :: var_list_append_real public :: var_list_append_cmplx public :: var_list_append_subevt public :: var_list_append_pdg_array public :: var_list_append_string <>= interface var_list_append_log module procedure var_list_append_log_s module procedure var_list_append_log_c end interface interface var_list_append_int module procedure var_list_append_int_s module procedure var_list_append_int_c end interface interface var_list_append_real module procedure var_list_append_real_s module procedure var_list_append_real_c end interface interface var_list_append_cmplx module procedure var_list_append_cmplx_s module procedure var_list_append_cmplx_c end interface interface var_list_append_subevt module procedure var_list_append_subevt_s module procedure var_list_append_subevt_c end interface interface var_list_append_pdg_array module procedure var_list_append_pdg_array_s module procedure var_list_append_pdg_array_c end interface interface var_list_append_string module procedure var_list_append_string_s module procedure var_list_append_string_c end interface <>= subroutine var_list_append_log_s & (var_list, name, lval, locked, verbose, intrinsic, user, description) class(var_list_t), intent(inout) :: var_list type(string_t), intent(in) :: name logical, intent(in), optional :: lval logical, intent(in), optional :: locked, verbose, intrinsic, user type(string_t), intent(in), optional :: description type(var_entry_t), pointer :: var allocate (var) call var_entry_init_log (var, name, lval, intrinsic, user) if (present (description)) call var_entry_set_description (var, description) if (present (locked)) call var_entry_lock (var, locked) call var_list_append (var_list, var, verbose) end subroutine var_list_append_log_s subroutine var_list_append_int_s & (var_list, name, ival, locked, verbose, intrinsic, user, description) class(var_list_t), intent(inout) :: var_list type(string_t), intent(in) :: name integer, intent(in), optional :: ival logical, intent(in), optional :: locked, verbose, intrinsic, user type(string_t), intent(in), optional :: description type(var_entry_t), pointer :: var allocate (var) call var_entry_init_int (var, name, ival, intrinsic, user) if (present (description)) call var_entry_set_description (var, description) if (present (locked)) call var_entry_lock (var, locked) call var_list_append (var_list, var, verbose) end subroutine var_list_append_int_s subroutine var_list_append_real_s & (var_list, name, rval, locked, verbose, intrinsic, user, description) class(var_list_t), intent(inout) :: var_list type(string_t), intent(in) :: name real(default), intent(in), optional :: rval logical, intent(in), optional :: locked, verbose, intrinsic, user type(string_t), intent(in), optional :: description type(var_entry_t), pointer :: var allocate (var) call var_entry_init_real (var, name, rval, intrinsic, user) if (present (description)) call var_entry_set_description (var, description) if (present (locked)) call var_entry_lock (var, locked) call var_list_append (var_list, var, verbose) end subroutine var_list_append_real_s subroutine var_list_append_cmplx_s & (var_list, name, cval, locked, verbose, intrinsic, user, description) class(var_list_t), intent(inout) :: var_list type(string_t), intent(in) :: name complex(default), intent(in), optional :: cval logical, intent(in), optional :: locked, verbose, intrinsic, user type(string_t), intent(in), optional :: description type(var_entry_t), pointer :: var allocate (var) call var_entry_init_cmplx (var, name, cval, intrinsic, user) if (present (description)) call var_entry_set_description (var, description) if (present (locked)) call var_entry_lock (var, locked) call var_list_append (var_list, var, verbose) end subroutine var_list_append_cmplx_s subroutine var_list_append_subevt_s & (var_list, name, pval, locked, verbose, intrinsic, user, description) class(var_list_t), intent(inout) :: var_list type(string_t), intent(in) :: name type(subevt_t), intent(in), optional :: pval logical, intent(in), optional :: locked, verbose, intrinsic, user type(string_t), intent(in), optional :: description type(var_entry_t), pointer :: var allocate (var) call var_entry_init_subevt (var, name, pval, intrinsic, user) if (present (description)) call var_entry_set_description (var, description) if (present (locked)) call var_entry_lock (var, locked) call var_list_append (var_list, var, verbose) end subroutine var_list_append_subevt_s subroutine var_list_append_pdg_array_s & (var_list, name, aval, locked, verbose, intrinsic, user, description) class(var_list_t), intent(inout) :: var_list type(string_t), intent(in) :: name type(pdg_array_t), intent(in), optional :: aval logical, intent(in), optional :: locked, verbose, intrinsic, user type(string_t), intent(in), optional :: description type(var_entry_t), pointer :: var allocate (var) call var_entry_init_pdg_array (var, name, aval, intrinsic, user) if (present (description)) call var_entry_set_description (var, description) if (present (locked)) call var_entry_lock (var, locked) call var_list_append (var_list, var, verbose) end subroutine var_list_append_pdg_array_s subroutine var_list_append_string_s & (var_list, name, sval, locked, verbose, intrinsic, user, description) class(var_list_t), intent(inout) :: var_list type(string_t), intent(in) :: name type(string_t), intent(in), optional :: sval logical, intent(in), optional :: locked, verbose, intrinsic, user type(string_t), intent(in), optional :: description type(var_entry_t), pointer :: var allocate (var) call var_entry_init_string (var, name, sval, intrinsic, user) if (present (description)) call var_entry_set_description (var, description) if (present (locked)) call var_entry_lock (var, locked) call var_list_append (var_list, var, verbose) end subroutine var_list_append_string_s subroutine var_list_append_log_c & (var_list, name, lval, locked, verbose, intrinsic, user, description) class(var_list_t), intent(inout) :: var_list character(*), intent(in) :: name logical, intent(in), optional :: lval logical, intent(in), optional :: locked, verbose, intrinsic, user type(string_t), intent(in), optional :: description call var_list_append_log_s & (var_list, var_str (name), lval, locked, verbose, & intrinsic, user, description) end subroutine var_list_append_log_c subroutine var_list_append_int_c & (var_list, name, ival, locked, verbose, intrinsic, user, description) class(var_list_t), intent(inout) :: var_list character(*), intent(in) :: name integer, intent(in), optional :: ival logical, intent(in), optional :: locked, verbose, intrinsic, user type(string_t), intent(in), optional :: description call var_list_append_int_s & (var_list, var_str (name), ival, locked, verbose, & intrinsic, user, description) end subroutine var_list_append_int_c subroutine var_list_append_real_c & (var_list, name, rval, locked, verbose, intrinsic, user, description) class(var_list_t), intent(inout) :: var_list character(*), intent(in) :: name real(default), intent(in), optional :: rval logical, intent(in), optional :: locked, verbose, intrinsic, user type(string_t), intent(in), optional :: description call var_list_append_real_s & (var_list, var_str (name), rval, locked, verbose, & intrinsic, user, description) end subroutine var_list_append_real_c subroutine var_list_append_cmplx_c & (var_list, name, cval, locked, verbose, intrinsic, user, description) class(var_list_t), intent(inout) :: var_list character(*), intent(in) :: name complex(default), intent(in), optional :: cval logical, intent(in), optional :: locked, verbose, intrinsic, user type(string_t), intent(in), optional :: description call var_list_append_cmplx_s & (var_list, var_str (name), cval, locked, verbose, & intrinsic, user, description) end subroutine var_list_append_cmplx_c subroutine var_list_append_subevt_c & (var_list, name, pval, locked, verbose, intrinsic, user, description) class(var_list_t), intent(inout) :: var_list character(*), intent(in) :: name type(subevt_t), intent(in), optional :: pval logical, intent(in), optional :: locked, verbose, intrinsic, user type(string_t), intent(in), optional :: description call var_list_append_subevt_s & (var_list, var_str (name), pval, locked, verbose, & intrinsic, user, description) end subroutine var_list_append_subevt_c subroutine var_list_append_pdg_array_c & (var_list, name, aval, locked, verbose, intrinsic, user, description) class(var_list_t), intent(inout) :: var_list character(*), intent(in) :: name type(pdg_array_t), intent(in), optional :: aval logical, intent(in), optional :: locked, verbose, intrinsic, user type(string_t), intent(in), optional :: description call var_list_append_pdg_array_s & (var_list, var_str (name), aval, locked, verbose, & intrinsic, user, description) end subroutine var_list_append_pdg_array_c subroutine var_list_append_string_c & (var_list, name, sval, locked, verbose, intrinsic, user, description) class(var_list_t), intent(inout) :: var_list character(*), intent(in) :: name character(*), intent(in), optional :: sval logical, intent(in), optional :: locked, verbose, intrinsic, user type(string_t), intent(in), optional :: description if (present (sval)) then call var_list_append_string_s & (var_list, var_str (name), var_str (sval), & locked, verbose, intrinsic, user, description) else call var_list_append_string_s & (var_list, var_str (name), & locked=locked, verbose=verbose, intrinsic=intrinsic, & user=user, description=description) end if end subroutine var_list_append_string_c @ %def var_list_append_log @ %def var_list_append_int @ %def var_list_append_real @ %def var_list_append_cmplx @ %def var_list_append_subevt @ %def var_list_append_pdg_array @ %def var_list_append_string <>= public :: var_list_append_log_ptr public :: var_list_append_int_ptr public :: var_list_append_real_ptr public :: var_list_append_cmplx_ptr public :: var_list_append_pdg_array_ptr public :: var_list_append_subevt_ptr public :: var_list_append_string_ptr <>= procedure :: append_log_ptr => var_list_append_log_ptr procedure :: append_int_ptr => var_list_append_int_ptr procedure :: append_real_ptr => var_list_append_real_ptr procedure :: append_cmplx_ptr => var_list_append_cmplx_ptr procedure :: append_pdg_array_ptr => var_list_append_pdg_array_ptr procedure :: append_subevt_ptr => var_list_append_subevt_ptr procedure :: append_string_ptr => var_list_append_string_ptr <>= subroutine var_list_append_log_ptr & (var_list, name, lval, is_known, locked, verbose, intrinsic, description) class(var_list_t), intent(inout) :: var_list type(string_t), intent(in) :: name logical, intent(in), target :: lval logical, intent(in), target :: is_known logical, intent(in), optional :: locked, verbose, intrinsic type(string_t), intent(in), optional :: description type(var_entry_t), pointer :: var allocate (var) call var_entry_init_log_ptr (var, name, lval, is_known, intrinsic) if (present (description)) call var_entry_set_description (var, description) if (present (locked)) call var_entry_lock (var, locked) call var_list_append (var_list, var, verbose) end subroutine var_list_append_log_ptr subroutine var_list_append_int_ptr & (var_list, name, ival, is_known, locked, verbose, intrinsic, description) class(var_list_t), intent(inout) :: var_list type(string_t), intent(in) :: name integer, intent(in), target :: ival logical, intent(in), target :: is_known logical, intent(in), optional :: locked, verbose, intrinsic type(string_t), intent(in), optional :: description type(var_entry_t), pointer :: var allocate (var) call var_entry_init_int_ptr (var, name, ival, is_known, intrinsic) if (present (description)) call var_entry_set_description (var, description) if (present (locked)) call var_entry_lock (var, locked) call var_list_append (var_list, var, verbose) end subroutine var_list_append_int_ptr subroutine var_list_append_real_ptr & (var_list, name, rval, is_known, locked, verbose, intrinsic, description) class(var_list_t), intent(inout) :: var_list type(string_t), intent(in) :: name real(default), intent(in), target :: rval logical, intent(in), target :: is_known logical, intent(in), optional :: locked, verbose, intrinsic type(string_t), intent(in), optional :: description type(var_entry_t), pointer :: var allocate (var) call var_entry_init_real_ptr (var, name, rval, is_known, intrinsic) if (present (description)) call var_entry_set_description (var, description) if (present (locked)) call var_entry_lock (var, locked) call var_list_append (var_list, var, verbose) end subroutine var_list_append_real_ptr subroutine var_list_append_cmplx_ptr & (var_list, name, cval, is_known, locked, verbose, intrinsic, description) class(var_list_t), intent(inout) :: var_list type(string_t), intent(in) :: name complex(default), intent(in), target :: cval logical, intent(in), target :: is_known logical, intent(in), optional :: locked, verbose, intrinsic type(string_t), intent(in), optional :: description type(var_entry_t), pointer :: var allocate (var) call var_entry_init_cmplx_ptr (var, name, cval, is_known, intrinsic) if (present (description)) call var_entry_set_description (var, description) if (present (locked)) call var_entry_lock (var, locked) call var_list_append (var_list, var, verbose) end subroutine var_list_append_cmplx_ptr subroutine var_list_append_pdg_array_ptr & (var_list, name, aval, is_known, locked, verbose, intrinsic, description) class(var_list_t), intent(inout) :: var_list type(string_t), intent(in) :: name type(pdg_array_t), intent(in), target :: aval logical, intent(in), target :: is_known logical, intent(in), optional :: locked, verbose, intrinsic type(string_t), intent(in), optional :: description type(var_entry_t), pointer :: var allocate (var) call var_entry_init_pdg_array_ptr (var, name, aval, is_known, intrinsic) if (present (description)) call var_entry_set_description (var, description) if (present (locked)) call var_entry_lock (var, locked) call var_list_append (var_list, var, verbose) end subroutine var_list_append_pdg_array_ptr subroutine var_list_append_subevt_ptr & (var_list, name, pval, is_known, locked, verbose, intrinsic, description) class(var_list_t), intent(inout) :: var_list type(string_t), intent(in) :: name type(subevt_t), intent(in), target :: pval logical, intent(in), target :: is_known logical, intent(in), optional :: locked, verbose, intrinsic type(string_t), intent(in), optional :: description type(var_entry_t), pointer :: var allocate (var) call var_entry_init_subevt_ptr (var, name, pval, is_known, intrinsic) if (present (description)) call var_entry_set_description (var, description) if (present (locked)) call var_entry_lock (var, locked) call var_list_append (var_list, var, verbose) end subroutine var_list_append_subevt_ptr subroutine var_list_append_string_ptr & (var_list, name, sval, is_known, locked, verbose, intrinsic, description) class(var_list_t), intent(inout) :: var_list type(string_t), intent(in) :: name type(string_t), intent(in), target :: sval logical, intent(in), target :: is_known logical, intent(in), optional :: locked, verbose, intrinsic type(string_t), intent(in), optional :: description type(var_entry_t), pointer :: var allocate (var) call var_entry_init_string_ptr (var, name, sval, is_known, intrinsic) if (present (description)) call var_entry_set_description (var, description) if (present (locked)) call var_entry_lock (var, locked) call var_list_append (var_list, var, verbose) end subroutine var_list_append_string_ptr @ %def var_list_append_log_ptr @ %def var_list_append_int_ptr @ %def var_list_append_real_ptr @ %def var_list_append_cmplx_ptr @ %def var_list_append_pdg_array_ptr @ %def var_list_append_subevt_ptr @ \subsubsection{Finalizer} Finalize, delete the list entry by entry. The link itself is kept intact. Follow link and delete recursively only if requested explicitly. <>= procedure :: final => var_list_final <>= recursive subroutine var_list_final (vars, follow_link) class(var_list_t), intent(inout) :: vars logical, intent(in), optional :: follow_link type(var_entry_t), pointer :: var vars%last => null () do while (associated (vars%first)) var => vars%first vars%first => var%next call var_entry_final (var) deallocate (var) end do if (present (follow_link)) then if (follow_link) then if (associated (vars%next)) then call vars%next%final (follow_link) deallocate (vars%next) end if end if end if end subroutine var_list_final @ %def var_list_final @ \subsubsection{Output} Show variable list with precise control over options. E.g., show only variables of a certain type. Many options, thus not an ordinary [[write]] method. <>= public :: var_list_write <>= procedure :: write => var_list_write <>= recursive subroutine var_list_write & (var_list, unit, follow_link, only_type, prefix, model_name, & intrinsic, pacified, descriptions, ascii_output) class(var_list_t), intent(in), target :: var_list integer, intent(in), optional :: unit logical, intent(in), optional :: follow_link integer, intent(in), optional :: only_type character(*), intent(in), optional :: prefix type(string_t), intent(in), optional :: model_name logical, intent(in), optional :: intrinsic logical, intent(in), optional :: pacified logical, intent(in), optional :: descriptions logical, intent(in), optional :: ascii_output type(var_entry_t), pointer :: var integer :: u, length logical :: write_this, write_next u = given_output_unit (unit); if (u < 0) return if (present (prefix)) length = len (prefix) var => var_list%first if (associated (var)) then do while (associated (var)) if (present (only_type)) then write_this = only_type == var%type else write_this = .true. end if if (write_this .and. present (prefix)) then if (prefix /= extract (var%name, 1, length)) & write_this = .false. end if if (write_this) then call var_entry_write & (var, unit, model_name=model_name, & intrinsic=intrinsic, pacified=pacified, & descriptions=descriptions, ascii_output=ascii_output) end if var => var%next end do end if if (present (follow_link)) then write_next = follow_link .and. associated (var_list%next) else write_next = associated (var_list%next) end if if (write_next) then call var_list_write (var_list%next, & unit, follow_link, only_type, prefix, model_name, & intrinsic, pacified) end if end subroutine var_list_write @ %def var_list_write @ Write only a certain variable. <>= public :: var_list_write_var <>= procedure :: write_var => var_list_write_var <>= recursive subroutine var_list_write_var & (var_list, name, unit, type, follow_link, & model_name, pacified, defined, descriptions, ascii_output) class(var_list_t), intent(in), target :: var_list type(string_t), intent(in) :: name integer, intent(in), optional :: unit integer, intent(in), optional :: type logical, intent(in), optional :: follow_link type(string_t), intent(in), optional :: model_name logical, intent(in), optional :: pacified logical, intent(in), optional :: defined logical, intent(in), optional :: descriptions logical, intent(in), optional :: ascii_output type(var_entry_t), pointer :: var integer :: u u = given_output_unit (unit); if (u < 0) return var => var_list_get_var_ptr & (var_list, name, type, follow_link=follow_link, defined=defined) if (associated (var)) then call var_entry_write & (var, unit, model_name = model_name, & pacified = pacified, & descriptions=descriptions, ascii_output=ascii_output) else write (u, "(A)") char (name) // " = [undefined]" end if end subroutine var_list_write_var @ %def var_list_write_var @ \subsection{Tools} Return a pointer to the variable list linked to by the current one. <>= function var_list_get_next_ptr (var_list) result (next_ptr) type(var_list_t), pointer :: next_ptr type(var_list_t), intent(in) :: var_list next_ptr => var_list%next end function var_list_get_next_ptr @ %def var_list_get_next_ptr @ Used by [[eval_trees]]: Return a pointer to the variable with the requested name. If no such name exists, return a null pointer. In that case, try the next list if present, unless [[follow_link]] is unset. If [[defined]] is set, ignore entries that exist but are undefined. <>= public :: var_list_get_var_ptr <>= recursive function var_list_get_var_ptr & (var_list, name, type, follow_link, defined) result (var) type(var_entry_t), pointer :: var type(var_list_t), intent(in), target :: var_list type(string_t), intent(in) :: name integer, intent(in), optional :: type logical, intent(in), optional :: follow_link, defined logical :: ignore_undef, search_next ignore_undef = .true.; if (present (defined)) ignore_undef = .not. defined var => var_list%first if (present (type)) then do while (associated (var)) if (var%type == type) then if (var%name == name) then if (ignore_undef .or. var%is_defined) return end if end if var => var%next end do else do while (associated (var)) if (var%name == name) then if (ignore_undef .or. var%is_defined) return end if var => var%next end do end if search_next = associated (var_list%next) if (present (follow_link)) & search_next = search_next .and. follow_link if (search_next) & var => var_list_get_var_ptr & (var_list%next, name, type, defined=defined) end function var_list_get_var_ptr @ %def var_list_get_var_ptr @ Return the variable type <>= procedure :: get_type => var_list_get_type <>= function var_list_get_type (var_list, name, follow_link) result (type) class(var_list_t), intent(in), target :: var_list type(string_t), intent(in) :: name logical, intent(in), optional :: follow_link integer :: type type(var_entry_t), pointer :: var var => var_list_get_var_ptr (var_list, name, follow_link=follow_link) if (associated (var)) then type = var%type else type = V_NONE end if end function var_list_get_type @ %def var_list_get_type @ Return true if the variable exists in the current list. <>= procedure :: contains => var_list_exists <>= function var_list_exists (vars, name, follow_link) result (lval) logical :: lval type(string_t), intent(in) :: name class(var_list_t), intent(in) :: vars logical, intent(in), optional :: follow_link type(var_entry_t), pointer :: var var => var_list_get_var_ptr (vars, name, follow_link=follow_link) lval = associated (var) end function var_list_exists @ %def var_list_exists @ Return true if the variable is declared as intrinsic. (This is not a property of the abstract [[vars_t]] type, and therefore the method is not inherited.) <>= procedure :: is_intrinsic => var_list_is_intrinsic <>= function var_list_is_intrinsic (vars, name, follow_link) result (lval) logical :: lval type(string_t), intent(in) :: name class(var_list_t), intent(in) :: vars logical, intent(in), optional :: follow_link type(var_entry_t), pointer :: var var => var_list_get_var_ptr (vars, name, follow_link=follow_link) if (associated (var)) then lval = var%is_intrinsic else lval = .false. end if end function var_list_is_intrinsic @ %def var_list_is_intrinsic @ Return true if the value is known. <>= procedure :: is_known => var_list_is_known <>= function var_list_is_known (vars, name, follow_link) result (lval) logical :: lval type(string_t), intent(in) :: name class(var_list_t), intent(in) :: vars logical, intent(in), optional :: follow_link type(var_entry_t), pointer :: var var => var_list_get_var_ptr (vars, name, follow_link=follow_link) if (associated (var)) then lval = var%is_known else lval = .false. end if end function var_list_is_known @ %def var_list_is_known @ Return true if the value is locked. (This is not a property of the abstract [[vars_t]] type, and therefore the method is not inherited.) <>= procedure :: is_locked => var_list_is_locked <>= function var_list_is_locked (vars, name, follow_link) result (lval) logical :: lval type(string_t), intent(in) :: name class(var_list_t), intent(in) :: vars logical, intent(in), optional :: follow_link type(var_entry_t), pointer :: var var => var_list_get_var_ptr (vars, name, follow_link=follow_link) if (associated (var)) then lval = var_entry_is_locked (var) else lval = .false. end if end function var_list_is_locked @ %def var_list_is_locked @ Return several properties at once. <>= procedure :: get_var_properties => var_list_get_var_properties <>= subroutine var_list_get_var_properties (vars, name, req_type, follow_link, & type, is_defined, is_known, is_locked) class(var_list_t), intent(in) :: vars type(string_t), intent(in) :: name integer, intent(in), optional :: req_type logical, intent(in), optional :: follow_link integer, intent(out), optional :: type logical, intent(out), optional :: is_defined, is_known, is_locked type(var_entry_t), pointer :: var var => var_list_get_var_ptr & (vars, name, type=req_type, follow_link=follow_link) if (associated (var)) then if (present (type)) type = var_entry_get_type (var) if (present (is_defined)) is_defined = var_entry_is_defined (var) if (present (is_known)) is_known = var_entry_is_known (var) if (present (is_locked)) is_locked = var_entry_is_locked (var) else if (present (type)) type = V_NONE if (present (is_defined)) is_defined = .false. if (present (is_known)) is_known = .false. if (present (is_locked)) is_locked = .false. end if end subroutine var_list_get_var_properties @ %def var_list_get_var_properties @ Return the value, assuming that the type is correct. We consider only variable entries that have been [[defined]]. For convenience, allow both variable and fixed-length (literal) strings. <>= procedure :: get_lval => var_list_get_lval procedure :: get_ival => var_list_get_ival procedure :: get_rval => var_list_get_rval procedure :: get_cval => var_list_get_cval procedure :: get_pval => var_list_get_pval procedure :: get_aval => var_list_get_aval procedure :: get_sval => var_list_get_sval <>= function var_list_get_lval (vars, name, follow_link) result (lval) logical :: lval type(string_t), intent(in) :: name class(var_list_t), intent(in) :: vars logical, intent(in), optional :: follow_link type(var_entry_t), pointer :: var var => var_list_get_var_ptr & (vars, name, V_LOG, follow_link, defined=.true.) if (associated (var)) then if (var_has_value (var)) then lval = var%lval else lval = .false. end if else lval = .false. end if end function var_list_get_lval function var_list_get_ival (vars, name, follow_link) result (ival) integer :: ival type(string_t), intent(in) :: name class(var_list_t), intent(in) :: vars logical, intent(in), optional :: follow_link type(var_entry_t), pointer :: var var => var_list_get_var_ptr & (vars, name, V_INT, follow_link, defined=.true.) if (associated (var)) then if (var_has_value (var)) then ival = var%ival else ival = 0 end if else ival = 0 end if end function var_list_get_ival function var_list_get_rval (vars, name, follow_link) result (rval) real(default) :: rval type(string_t), intent(in) :: name class(var_list_t), intent(in) :: vars logical, intent(in), optional :: follow_link type(var_entry_t), pointer :: var var => var_list_get_var_ptr & (vars, name, V_REAL, follow_link, defined=.true.) if (associated (var)) then if (var_has_value (var)) then rval = var%rval else rval = 0 end if else rval = 0 end if end function var_list_get_rval function var_list_get_cval (vars, name, follow_link) result (cval) complex(default) :: cval type(string_t), intent(in) :: name class(var_list_t), intent(in) :: vars logical, intent(in), optional :: follow_link type(var_entry_t), pointer :: var var => var_list_get_var_ptr & (vars, name, V_CMPLX, follow_link, defined=.true.) if (associated (var)) then if (var_has_value (var)) then cval = var%cval else cval = 0 end if else cval = 0 end if end function var_list_get_cval function var_list_get_aval (vars, name, follow_link) result (aval) type(pdg_array_t) :: aval type(string_t), intent(in) :: name class(var_list_t), intent(in) :: vars logical, intent(in), optional :: follow_link type(var_entry_t), pointer :: var var => var_list_get_var_ptr & (vars, name, V_PDG, follow_link, defined=.true.) if (associated (var)) then if (var_has_value (var)) then aval = var%aval end if end if end function var_list_get_aval function var_list_get_pval (vars, name, follow_link) result (pval) type(subevt_t) :: pval type(string_t), intent(in) :: name class(var_list_t), intent(in) :: vars logical, intent(in), optional :: follow_link type(var_entry_t), pointer :: var var => var_list_get_var_ptr & (vars, name, V_SEV, follow_link, defined=.true.) if (associated (var)) then if (var_has_value (var)) then pval = var%pval end if end if end function var_list_get_pval function var_list_get_sval (vars, name, follow_link) result (sval) type(string_t) :: sval type(string_t), intent(in) :: name class(var_list_t), intent(in) :: vars logical, intent(in), optional :: follow_link type(var_entry_t), pointer :: var var => var_list_get_var_ptr & (vars, name, V_STR, follow_link, defined=.true.) if (associated (var)) then if (var_has_value (var)) then sval = var%sval else sval = "" end if else sval = "" end if end function var_list_get_sval @ %def var_list_get_lval @ %def var_list_get_ival @ %def var_list_get_rval @ %def var_list_get_cval @ %def var_list_get_pval @ %def var_list_get_aval @ %def var_list_get_sval @ Check for a valid value, given a pointer. Issue error messages if invalid. <>= function var_has_value (var) result (valid) logical :: valid type(var_entry_t), pointer :: var if (associated (var)) then if (var%is_known) then valid = .true. else call msg_error ("The value of variable '" // char (var%name) & // "' is unknown but must be known at this point.") valid = .false. end if else call msg_error ("Variable '" // char (var%name) & // "' is undefined but must have a known value at this point.") valid = .false. end if end function var_has_value @ %def var_has_value @ Return pointers instead of values, including a pointer to the [[known]] entry. <>= procedure :: get_lptr => var_list_get_lptr procedure :: get_iptr => var_list_get_iptr procedure :: get_rptr => var_list_get_rptr procedure :: get_cptr => var_list_get_cptr procedure :: get_aptr => var_list_get_aptr procedure :: get_pptr => var_list_get_pptr procedure :: get_sptr => var_list_get_sptr <>= subroutine var_list_get_lptr (var_list, name, lptr, known) class(var_list_t), intent(in) :: var_list type(string_t), intent(in) :: name logical, pointer, intent(out) :: lptr logical, pointer, intent(out), optional :: known type(var_entry_t), pointer :: var var => var_list_get_var_ptr (var_list, name, V_LOG) if (associated (var)) then lptr => var_entry_get_lval_ptr (var) if (present (known)) known => var_entry_get_known_ptr (var) else lptr => null () if (present (known)) known => null () end if end subroutine var_list_get_lptr subroutine var_list_get_iptr (var_list, name, iptr, known) class(var_list_t), intent(in) :: var_list type(string_t), intent(in) :: name integer, pointer, intent(out) :: iptr logical, pointer, intent(out), optional :: known type(var_entry_t), pointer :: var var => var_list_get_var_ptr (var_list, name, V_INT) if (associated (var)) then iptr => var_entry_get_ival_ptr (var) if (present (known)) known => var_entry_get_known_ptr (var) else iptr => null () if (present (known)) known => null () end if end subroutine var_list_get_iptr subroutine var_list_get_rptr (var_list, name, rptr, known) class(var_list_t), intent(in) :: var_list type(string_t), intent(in) :: name real(default), pointer, intent(out) :: rptr logical, pointer, intent(out), optional :: known type(var_entry_t), pointer :: var var => var_list_get_var_ptr (var_list, name, V_REAL) if (associated (var)) then rptr => var_entry_get_rval_ptr (var) if (present (known)) known => var_entry_get_known_ptr (var) else rptr => null () if (present (known)) known => null () end if end subroutine var_list_get_rptr subroutine var_list_get_cptr (var_list, name, cptr, known) class(var_list_t), intent(in) :: var_list type(string_t), intent(in) :: name complex(default), pointer, intent(out) :: cptr logical, pointer, intent(out), optional :: known type(var_entry_t), pointer :: var var => var_list_get_var_ptr (var_list, name, V_CMPLX) if (associated (var)) then cptr => var_entry_get_cval_ptr (var) if (present (known)) known => var_entry_get_known_ptr (var) else cptr => null () if (present (known)) known => null () end if end subroutine var_list_get_cptr subroutine var_list_get_aptr (var_list, name, aptr, known) class(var_list_t), intent(in) :: var_list type(string_t), intent(in) :: name type(pdg_array_t), pointer, intent(out) :: aptr logical, pointer, intent(out), optional :: known type(var_entry_t), pointer :: var var => var_list_get_var_ptr (var_list, name, V_PDG) if (associated (var)) then aptr => var_entry_get_aval_ptr (var) if (present (known)) known => var_entry_get_known_ptr (var) else aptr => null () if (present (known)) known => null () end if end subroutine var_list_get_aptr subroutine var_list_get_pptr (var_list, name, pptr, known) class(var_list_t), intent(in) :: var_list type(string_t), intent(in) :: name type(subevt_t), pointer, intent(out) :: pptr logical, pointer, intent(out), optional :: known type(var_entry_t), pointer :: var var => var_list_get_var_ptr (var_list, name, V_SEV) if (associated (var)) then pptr => var_entry_get_pval_ptr (var) if (present (known)) known => var_entry_get_known_ptr (var) else pptr => null () if (present (known)) known => null () end if end subroutine var_list_get_pptr subroutine var_list_get_sptr (var_list, name, sptr, known) class(var_list_t), intent(in) :: var_list type(string_t), intent(in) :: name type(string_t), pointer, intent(out) :: sptr logical, pointer, intent(out), optional :: known type(var_entry_t), pointer :: var var => var_list_get_var_ptr (var_list, name, V_STR) if (associated (var)) then sptr => var_entry_get_sval_ptr (var) if (present (known)) known => var_entry_get_known_ptr (var) else sptr => null () if (present (known)) known => null () end if end subroutine var_list_get_sptr @ %def var_list_get_lptr @ %def var_list_get_iptr @ %def var_list_get_rptr @ %def var_list_get_cptr @ %def var_list_get_aptr @ %def var_list_get_pptr @ %def var_list_get_sptr @ This bunch of methods handles the procedure-pointer cases. <>= procedure :: get_obs1_iptr => var_list_get_obs1_iptr procedure :: get_obs2_iptr => var_list_get_obs2_iptr procedure :: get_obs1_rptr => var_list_get_obs1_rptr procedure :: get_obs2_rptr => var_list_get_obs2_rptr <>= subroutine var_list_get_obs1_iptr (var_list, name, obs1_iptr, p1) class(var_list_t), intent(in) :: var_list type(string_t), intent(in) :: name procedure(obs_unary_int), pointer, intent(out) :: obs1_iptr type(prt_t), pointer, intent(out) :: p1 type(var_entry_t), pointer :: var var => var_list_get_var_ptr (var_list, name, V_OBS1_INT) if (associated (var)) then call var_entry_assign_obs1_int_ptr (obs1_iptr, var) p1 => var_entry_get_prt1_ptr (var) else obs1_iptr => null () p1 => null () end if end subroutine var_list_get_obs1_iptr subroutine var_list_get_obs2_iptr (var_list, name, obs2_iptr, p1, p2) class(var_list_t), intent(in) :: var_list type(string_t), intent(in) :: name procedure(obs_binary_int), pointer, intent(out) :: obs2_iptr type(prt_t), pointer, intent(out) :: p1, p2 type(var_entry_t), pointer :: var var => var_list_get_var_ptr (var_list, name, V_OBS2_INT) if (associated (var)) then call var_entry_assign_obs2_int_ptr (obs2_iptr, var) p1 => var_entry_get_prt1_ptr (var) p2 => var_entry_get_prt2_ptr (var) else obs2_iptr => null () p1 => null () p2 => null () end if end subroutine var_list_get_obs2_iptr subroutine var_list_get_obs1_rptr (var_list, name, obs1_rptr, p1) class(var_list_t), intent(in) :: var_list type(string_t), intent(in) :: name procedure(obs_unary_real), pointer, intent(out) :: obs1_rptr type(prt_t), pointer, intent(out) :: p1 type(var_entry_t), pointer :: var var => var_list_get_var_ptr (var_list, name, V_OBS1_REAL) if (associated (var)) then call var_entry_assign_obs1_real_ptr (obs1_rptr, var) p1 => var_entry_get_prt1_ptr (var) else obs1_rptr => null () p1 => null () end if end subroutine var_list_get_obs1_rptr subroutine var_list_get_obs2_rptr (var_list, name, obs2_rptr, p1, p2) class(var_list_t), intent(in) :: var_list type(string_t), intent(in) :: name procedure(obs_binary_real), pointer, intent(out) :: obs2_rptr type(prt_t), pointer, intent(out) :: p1, p2 type(var_entry_t), pointer :: var var => var_list_get_var_ptr (var_list, name, V_OBS2_REAL) if (associated (var)) then call var_entry_assign_obs2_real_ptr (obs2_rptr, var) p1 => var_entry_get_prt1_ptr (var) p2 => var_entry_get_prt2_ptr (var) else obs2_rptr => null () p1 => null () p2 => null () end if end subroutine var_list_get_obs2_rptr @ %def var_list_get_obs1_iptr @ %def var_list_get_obs2_iptr @ %def var_list_get_obs1_rptr @ %def var_list_get_obs2_rptr @ \subsection{Process Result Variables} These variables are associated to process (integration) runs and their results. Their names contain brackets (so they look like function evaluations), therefore we need to special-case them. <>= public :: var_list_set_procvar_int public :: var_list_set_procvar_real <>= subroutine var_list_set_procvar_int (var_list, proc_id, name, ival) type(var_list_t), intent(inout) :: var_list type(string_t), intent(in) :: proc_id type(string_t), intent(in) :: name integer, intent(in), optional :: ival type(string_t) :: var_name type(var_entry_t), pointer :: var var_name = name // "(" // proc_id // ")" var => var_list_get_var_ptr (var_list, var_name) if (.not. associated (var)) then call var_list%append_int (var_name, ival, intrinsic=.true.) else if (present (ival)) then call var_list%set_int (var_name, ival, is_known=.true.) end if end subroutine var_list_set_procvar_int subroutine var_list_set_procvar_real (var_list, proc_id, name, rval) type(var_list_t), intent(inout) :: var_list type(string_t), intent(in) :: proc_id type(string_t), intent(in) :: name real(default), intent(in), optional :: rval type(string_t) :: var_name type(var_entry_t), pointer :: var var_name = name // "(" // proc_id // ")" var => var_list_get_var_ptr (var_list, var_name) if (.not. associated (var)) then call var_list%append_real (var_name, rval, intrinsic=.true.) else if (present (rval)) then call var_list%set_real (var_name, rval, is_known=.true.) end if end subroutine var_list_set_procvar_real @ %def var_list_set_procvar_int @ %def var_list_set_procvar_real @ \subsection{Observable initialization} Observables are formally treated as variables, which however are evaluated each time the observable is used. The arguments (pointers) to evaluate and the function are part of the variable-list entry. <>= public :: var_list_append_obs1_iptr public :: var_list_append_obs2_iptr public :: var_list_append_obs1_rptr public :: var_list_append_obs2_rptr <>= subroutine var_list_append_obs1_iptr (var_list, name, obs1_iptr, p1) type(var_list_t), intent(inout) :: var_list type(string_t), intent(in) :: name procedure(obs_unary_int) :: obs1_iptr type(prt_t), intent(in), target :: p1 type(var_entry_t), pointer :: var allocate (var) call var_entry_init_obs (var, name, V_OBS1_INT, p1) var%obs1_int => obs1_iptr call var_list_append (var_list, var) end subroutine var_list_append_obs1_iptr subroutine var_list_append_obs2_iptr (var_list, name, obs2_iptr, p1, p2) type(var_list_t), intent(inout) :: var_list type(string_t), intent(in) :: name procedure(obs_binary_int) :: obs2_iptr type(prt_t), intent(in), target :: p1, p2 type(var_entry_t), pointer :: var allocate (var) call var_entry_init_obs (var, name, V_OBS2_INT, p1, p2) var%obs2_int => obs2_iptr call var_list_append (var_list, var) end subroutine var_list_append_obs2_iptr subroutine var_list_append_obs1_rptr (var_list, name, obs1_rptr, p1) type(var_list_t), intent(inout) :: var_list type(string_t), intent(in) :: name procedure(obs_unary_real) :: obs1_rptr type(prt_t), intent(in), target :: p1 type(var_entry_t), pointer :: var allocate (var) call var_entry_init_obs (var, name, V_OBS1_REAL, p1) var%obs1_real => obs1_rptr call var_list_append (var_list, var) end subroutine var_list_append_obs1_rptr subroutine var_list_append_obs2_rptr (var_list, name, obs2_rptr, p1, p2) type(var_list_t), intent(inout) :: var_list type(string_t), intent(in) :: name procedure(obs_binary_real) :: obs2_rptr type(prt_t), intent(in), target :: p1, p2 type(var_entry_t), pointer :: var allocate (var) call var_entry_init_obs (var, name, V_OBS2_REAL, p1, p2) var%obs2_real => obs2_rptr call var_list_append (var_list, var) end subroutine var_list_append_obs2_rptr @ %def var_list_append_obs1_iptr @ %def var_list_append_obs2_iptr @ %def var_list_append_obs1_rptr @ %def var_list_append_obs2_rptr @ User observables: no pointer needs to be stored. <>= public :: var_list_append_uobs_int public :: var_list_append_uobs_real <>= subroutine var_list_append_uobs_int (var_list, name, p1, p2) type(var_list_t), intent(inout) :: var_list type(string_t), intent(in) :: name type(prt_t), intent(in), target :: p1 type(prt_t), intent(in), target, optional :: p2 type(var_entry_t), pointer :: var allocate (var) if (present (p2)) then call var_entry_init_obs (var, name, V_UOBS2_INT, p1, p2) else call var_entry_init_obs (var, name, V_UOBS1_INT, p1) end if call var_list_append (var_list, var) end subroutine var_list_append_uobs_int subroutine var_list_append_uobs_real (var_list, name, p1, p2) type(var_list_t), intent(inout) :: var_list type(string_t), intent(in) :: name type(prt_t), intent(in), target :: p1 type(prt_t), intent(in), target, optional :: p2 type(var_entry_t), pointer :: var allocate (var) if (present (p2)) then call var_entry_init_obs (var, name, V_UOBS2_REAL, p1, p2) else call var_entry_init_obs (var, name, V_UOBS1_REAL, p1) end if call var_list_append (var_list, var) end subroutine var_list_append_uobs_real @ %def var_list_append_uobs_int @ %def var_list_append_uobs_real @ \subsection{API for variable lists} Set a new value. If the variable holds a pointer, this pointer is followed, e.g., a model parameter is actually set. If [[ignore]] is set, do nothing if the variable does not exist. If [[verbose]] is set, echo the new value. Clear a variable (all variables), i.e., undefine the value. <>= procedure :: unset => var_list_clear <>= subroutine var_list_clear (vars, name, follow_link) class(var_list_t), intent(inout) :: vars type(string_t), intent(in) :: name logical, intent(in), optional :: follow_link type(var_entry_t), pointer :: var var => var_list_get_var_ptr (vars, name, follow_link=follow_link) if (associated (var)) then call var_entry_clear (var) end if end subroutine var_list_clear @ %def var_list_clear @ Setting the value, concise specific versions (implementing deferred TBP): <>= procedure :: set_ival => var_list_set_ival procedure :: set_rval => var_list_set_rval procedure :: set_cval => var_list_set_cval procedure :: set_lval => var_list_set_lval procedure :: set_sval => var_list_set_sval <>= subroutine var_list_set_ival (vars, name, ival, follow_link) class(var_list_t), intent(inout) :: vars type(string_t), intent(in) :: name integer, intent(in) :: ival logical, intent(in), optional :: follow_link type(var_entry_t), pointer :: var var => var_list_get_var_ptr (vars, name, follow_link=follow_link) if (associated (var)) then call var_entry_set_int (var, ival, is_known=.true.) end if end subroutine var_list_set_ival subroutine var_list_set_rval (vars, name, rval, follow_link) class(var_list_t), intent(inout) :: vars type(string_t), intent(in) :: name real(default), intent(in) :: rval logical, intent(in), optional :: follow_link type(var_entry_t), pointer :: var var => var_list_get_var_ptr (vars, name, follow_link=follow_link) if (associated (var)) then call var_entry_set_real (var, rval, is_known=.true.) end if end subroutine var_list_set_rval subroutine var_list_set_cval (vars, name, cval, follow_link) class(var_list_t), intent(inout) :: vars type(string_t), intent(in) :: name complex(default), intent(in) :: cval logical, intent(in), optional :: follow_link type(var_entry_t), pointer :: var var => var_list_get_var_ptr (vars, name, follow_link=follow_link) if (associated (var)) then call var_entry_set_cmplx (var, cval, is_known=.true.) end if end subroutine var_list_set_cval subroutine var_list_set_lval (vars, name, lval, follow_link) class(var_list_t), intent(inout) :: vars type(string_t), intent(in) :: name logical, intent(in) :: lval logical, intent(in), optional :: follow_link type(var_entry_t), pointer :: var var => var_list_get_var_ptr (vars, name, follow_link=follow_link) if (associated (var)) then call var_entry_set_log (var, lval, is_known=.true.) end if end subroutine var_list_set_lval subroutine var_list_set_sval (vars, name, sval, follow_link) class(var_list_t), intent(inout) :: vars type(string_t), intent(in) :: name type(string_t), intent(in) :: sval logical, intent(in), optional :: follow_link type(var_entry_t), pointer :: var var => var_list_get_var_ptr (vars, name, follow_link=follow_link) if (associated (var)) then call var_entry_set_string (var, sval, is_known=.true.) end if end subroutine var_list_set_sval @ %def var_list_set_ival @ %def var_list_set_rval @ %def var_list_set_cval @ %def var_list_set_lval @ %def var_list_set_sval @ Setting the value, verbose specific versions (as subroutines): <>= procedure :: set_log => var_list_set_log procedure :: set_int => var_list_set_int procedure :: set_real => var_list_set_real procedure :: set_cmplx => var_list_set_cmplx procedure :: set_subevt => var_list_set_subevt procedure :: set_pdg_array => var_list_set_pdg_array procedure :: set_string => var_list_set_string <>= subroutine var_list_set_log & (var_list, name, lval, is_known, ignore, force, verbose, model_name) class(var_list_t), intent(inout), target :: var_list type(string_t), intent(in) :: name logical, intent(in) :: lval logical, intent(in) :: is_known logical, intent(in), optional :: ignore, force, verbose type(string_t), intent(in), optional :: model_name type(var_entry_t), pointer :: var var => var_list_get_var_ptr (var_list, name, V_LOG) if (associated (var)) then if (.not. var_entry_is_locked (var, force)) then select case (var%type) case (V_LOG) call var_entry_set_log (var, lval, is_known, verbose, model_name) case default call var_mismatch_error (name) end select else call var_locked_error (name) end if else call var_missing_error (name, ignore) end if end subroutine var_list_set_log subroutine var_list_set_int & (var_list, name, ival, is_known, ignore, force, verbose, model_name) class(var_list_t), intent(inout), target :: var_list type(string_t), intent(in) :: name integer, intent(in) :: ival logical, intent(in) :: is_known logical, intent(in), optional :: ignore, force, verbose type(string_t), intent(in), optional :: model_name type(var_entry_t), pointer :: var var => var_list_get_var_ptr (var_list, name, V_INT) if (associated (var)) then if (.not. var_entry_is_locked (var, force)) then select case (var%type) case (V_INT) call var_entry_set_int (var, ival, is_known, verbose, model_name) case default call var_mismatch_error (name) end select else call var_locked_error (name) end if else call var_missing_error (name, ignore) end if end subroutine var_list_set_int subroutine var_list_set_real & (var_list, name, rval, is_known, ignore, force, & verbose, model_name, pacified) class(var_list_t), intent(inout), target :: var_list type(string_t), intent(in) :: name real(default), intent(in) :: rval logical, intent(in) :: is_known logical, intent(in), optional :: ignore, force, verbose, pacified type(string_t), intent(in), optional :: model_name type(var_entry_t), pointer :: var var => var_list_get_var_ptr (var_list, name, V_REAL) if (associated (var)) then if (.not. var_entry_is_locked (var, force)) then select case (var%type) case (V_REAL) call var_entry_set_real & (var, rval, is_known, verbose, model_name, pacified) case default call var_mismatch_error (name) end select else call var_locked_error (name) end if else call var_missing_error (name, ignore) end if end subroutine var_list_set_real subroutine var_list_set_cmplx & (var_list, name, cval, is_known, ignore, force, & verbose, model_name, pacified) class(var_list_t), intent(inout), target :: var_list type(string_t), intent(in) :: name complex(default), intent(in) :: cval logical, intent(in) :: is_known logical, intent(in), optional :: ignore, force, verbose, pacified type(string_t), intent(in), optional :: model_name type(var_entry_t), pointer :: var var => var_list_get_var_ptr (var_list, name, V_CMPLX) if (associated (var)) then if (.not. var_entry_is_locked (var, force)) then select case (var%type) case (V_CMPLX) call var_entry_set_cmplx & (var, cval, is_known, verbose, model_name, pacified) case default call var_mismatch_error (name) end select else call var_locked_error (name) end if else call var_missing_error (name, ignore) end if end subroutine var_list_set_cmplx subroutine var_list_set_pdg_array & (var_list, name, aval, is_known, ignore, force, verbose, model_name) class(var_list_t), intent(inout), target :: var_list type(string_t), intent(in) :: name type(pdg_array_t), intent(in) :: aval logical, intent(in) :: is_known logical, intent(in), optional :: ignore, force, verbose type(string_t), intent(in), optional :: model_name type(var_entry_t), pointer :: var var => var_list_get_var_ptr (var_list, name, V_PDG) if (associated (var)) then if (.not. var_entry_is_locked (var, force)) then select case (var%type) case (V_PDG) call var_entry_set_pdg_array & (var, aval, is_known, verbose, model_name) case default call var_mismatch_error (name) end select else call var_locked_error (name) end if else call var_missing_error (name, ignore) end if end subroutine var_list_set_pdg_array subroutine var_list_set_subevt & (var_list, name, pval, is_known, ignore, force, verbose, model_name) class(var_list_t), intent(inout), target :: var_list type(string_t), intent(in) :: name type(subevt_t), intent(in) :: pval logical, intent(in) :: is_known logical, intent(in), optional :: ignore, force, verbose type(string_t), intent(in), optional :: model_name type(var_entry_t), pointer :: var var => var_list_get_var_ptr (var_list, name, V_SEV) if (associated (var)) then if (.not. var_entry_is_locked (var, force)) then select case (var%type) case (V_SEV) call var_entry_set_subevt & (var, pval, is_known, verbose, model_name) case default call var_mismatch_error (name) end select else call var_locked_error (name) end if else call var_missing_error (name, ignore) end if end subroutine var_list_set_subevt subroutine var_list_set_string & (var_list, name, sval, is_known, ignore, force, verbose, model_name) class(var_list_t), intent(inout), target :: var_list type(string_t), intent(in) :: name type(string_t), intent(in) :: sval logical, intent(in) :: is_known logical, intent(in), optional :: ignore, force, verbose type(string_t), intent(in), optional :: model_name type(var_entry_t), pointer :: var var => var_list_get_var_ptr (var_list, name, V_STR) if (associated (var)) then if (.not. var_entry_is_locked (var, force)) then select case (var%type) case (V_STR) call var_entry_set_string & (var, sval, is_known, verbose, model_name) case default call var_mismatch_error (name) end select else call var_locked_error (name) end if else call var_missing_error (name, ignore) end if end subroutine var_list_set_string subroutine var_mismatch_error (name) type(string_t), intent(in) :: name call msg_fatal ("Type mismatch for variable '" // char (name) // "'") end subroutine var_mismatch_error subroutine var_locked_error (name) type(string_t), intent(in) :: name call msg_error ("Variable '" // char (name) // "' is not user-definable") end subroutine var_locked_error subroutine var_missing_error (name, ignore) type(string_t), intent(in) :: name logical, intent(in), optional :: ignore logical :: error if (present (ignore)) then error = .not. ignore else error = .true. end if if (error) then call msg_fatal ("Variable '" // char (name) // "' has not been declared") end if end subroutine var_missing_error @ %def var_list_set_log @ %def var_list_set_int @ %def var_list_set_real @ %def var_list_set_cmplx @ %def var_list_set_subevt @ %def var_list_set_pdg_array @ %def var_list_set_string @ %def var_mismatch_error @ %def var_missing_error @ Import values for the current variable list from another list. <>= public :: var_list_import <>= procedure :: import => var_list_import <>= subroutine var_list_import (var_list, src_list) class(var_list_t), intent(inout) :: var_list type(var_list_t), intent(in) :: src_list type(var_entry_t), pointer :: var, src var => var_list%first do while (associated (var)) src => var_list_get_var_ptr (src_list, var%name) if (associated (src)) then call var_entry_copy_value (var, src) end if var => var%next end do end subroutine var_list_import @ %def var_list_import @ Mark all entries in the current variable list as undefined. This is done when a local variable list is discarded. If the local list is used again (by a loop), the entries will be re-initialized. <>= public :: var_list_undefine <>= procedure :: undefine => var_list_undefine <>= recursive subroutine var_list_undefine (var_list, follow_link) class(var_list_t), intent(inout) :: var_list logical, intent(in), optional :: follow_link type(var_entry_t), pointer :: var logical :: rec rec = .true.; if (present (follow_link)) rec = follow_link var => var_list%first do while (associated (var)) call var_entry_undefine (var) var => var%next end do if (rec .and. associated (var_list%next)) then call var_list_undefine (var_list%next, follow_link=follow_link) end if end subroutine var_list_undefine @ %def var_list_undefine @ Make a deep copy of a variable list. <>= public :: var_list_init_snapshot <>= procedure :: init_snapshot => var_list_init_snapshot <>= recursive subroutine var_list_init_snapshot (var_list, vars_in, follow_link) class(var_list_t), intent(out) :: var_list type(var_list_t), intent(in) :: vars_in logical, intent(in), optional :: follow_link type(var_entry_t), pointer :: var, var_in type(var_list_t), pointer :: var_list_next logical :: rec rec = .true.; if (present (follow_link)) rec = follow_link var_in => vars_in%first do while (associated (var_in)) allocate (var) call var_entry_init_copy (var, var_in) call var_entry_copy_value (var, var_in) call var_list_append (var_list, var) var_in => var_in%next end do if (rec .and. associated (vars_in%next)) then allocate (var_list_next) call var_list_init_snapshot (var_list_next, vars_in%next) call var_list%link (var_list_next) end if end subroutine var_list_init_snapshot @ %def var_list_init_snapshot @ Check if a user variable can be set. The [[new]] flag is set if the user variable has an explicit declaration. If an error occurs, return [[V_NONE]] as variable type. Also determine the actual type of generic numerical variables, which enter the procedure with type [[V_NONE]]. <>= public :: var_list_check_user_var <>= procedure :: check_user_var => var_list_check_user_var <>= subroutine var_list_check_user_var (var_list, name, type, new) class(var_list_t), intent(in), target :: var_list type(string_t), intent(in) :: name integer, intent(inout) :: type logical, intent(in) :: new type(var_entry_t), pointer :: var var => var_list_get_var_ptr (var_list, name) if (associated (var)) then if (type == V_NONE) then type = var_entry_get_type (var) end if if (var_entry_is_locked (var)) then call msg_fatal ("Variable '" // char (name) & // "' is not user-definable") type = V_NONE return else if (new) then if (var_entry_is_intrinsic (var)) then call msg_fatal ("Intrinsic variable '" & // char (name) // "' redeclared") type = V_NONE return end if if (var_entry_get_type (var) /= type) then call msg_fatal ("Variable '" // char (name) // "' " & // "redeclared with different type") type = V_NONE return end if end if end if end subroutine var_list_check_user_var @ %def var_list_check_user_var @ \subsection{Default values for global var list} <>= procedure :: init_defaults => var_list_init_defaults <>= subroutine var_list_init_defaults (var_list, seed, paths) class(var_list_t), intent(out) :: var_list integer, intent(in) :: seed type(paths_t), intent(in), optional :: paths call var_list%set_beams_defaults (paths) call var_list%set_core_defaults (seed) call var_list%set_integration_defaults () call var_list%set_phase_space_defaults () call var_list%set_gamelan_defaults () call var_list%set_clustering_defaults () call var_list%set_isolation_defaults () call var_list%set_eio_defaults () call var_list%set_shower_defaults () call var_list%set_hadronization_defaults () call var_list%set_tauola_defaults () call var_list%set_mlm_matching_defaults () call var_list%set_powheg_matching_defaults () call var_list%append_log (var_str ("?ckkw_matching"), .false., & intrinsic=.true., description=var_str ('Master flag that switches ' // & 'on the CKKW(-L) (LO) matching between hard scattering matrix ' // & 'elements and QCD parton showers. Note that this is not yet ' // & '(completely) implemented in \whizard. (cf. also \ttt{?allow\_shower}, ' // & '\ttt{?ps\_ ...}, \ttt{\$ps\_ ...}, \ttt{?mlm\_ ...})')) call var_list%set_openmp_defaults () call var_list%set_mpi_defaults () call var_list%set_nlo_defaults () end subroutine var_list_init_defaults @ %def var_list_init_defaults @ <>= procedure :: set_beams_defaults => var_list_set_beams_defaults <>= subroutine var_list_set_beams_defaults (var_list, paths) type(paths_t), intent(in), optional :: paths class(var_list_t), intent(inout) :: var_list call var_list%append_real (var_str ("sqrts"), & intrinsic=.true., & description=var_str ('Real variable in order to set the center-of-mass ' // & 'energy for the collisions (collider energy $\sqrt{s}$, not ' // & 'hard interaction energy $\sqrt{\hat{s}}$): \ttt{sqrts = {\em ' // & '} [ {\em } ]}. The physical unit can be one ' // & 'of the following \ttt{eV}, \ttt{keV}, \ttt{MeV}, \ttt{GeV}, ' // & 'and \ttt{TeV}. If absent, \whizard\ takes \ttt{GeV} as its ' // & 'standard unit. Note that this variable is absolutely mandatory ' // & 'for integration and simulation of scattering processes.')) call var_list%append_real (var_str ("luminosity"), 0._default, & intrinsic=.true., & description=var_str ('This specifier \ttt{luminosity = {\em ' // & '}} sets the integrated luminosity (in inverse femtobarns, ' // & 'fb${}^{-1}$) for the event generation of the processes in the ' // & '\sindarin\ input files. Note that WHIZARD itself chooses the ' // & 'number from the \ttt{luminosity} or from the \ttt{n\_events} ' // & 'specifier, whichever would give the larger number of events. ' // & 'As this depends on the cross section under consideration, it ' // & 'might be different for different processes in the process list. ' // & '(cf. \ttt{n\_events}, \ttt{\$sample}, \ttt{sample\_format}, \ttt{?unweighted})')) call var_list%append_log (var_str ("?sf_trace"), .false., & intrinsic=.true., & description=var_str ('Debug flag that writes out detailed information ' // & 'about the structure function setup into the file \ttt{{\em ' // & '}\_sftrace.dat}. This file name can be changed ' // & 'with ($\to$) \ttt{\$sf\_trace\_file}.')) call var_list%append_string (var_str ("$sf_trace_file"), var_str (""), & intrinsic=.true., & description=var_str ('\ttt{\$sf\_trace\_file = "{\em }"} ' // & 'allows to change the detailed structure function information ' // & 'switched on by the debug flag ($\to$) \ttt{?sf\_trace} into ' // & 'a different file \ttt{{\em }} than the default ' // & '\ttt{{\em }\_sftrace.dat}.')) call var_list%append_log (var_str ("?sf_allow_s_mapping"), .true., & intrinsic=.true., & description=var_str ('Flag that determines whether special mappings ' // & 'for processes with structure functions and $s$-channel resonances ' // & 'are applied, e.g. Drell-Yan at hadron colliders, or $Z$ production ' // & 'at linear colliders with beamstrahlung and ISR.')) if (present (paths)) then call var_list%append_string (var_str ("$lhapdf_dir"), paths%lhapdfdir, & intrinsic=.true., & description=var_str ('String variable that tells the path ' // & 'where the \lhapdf\ library and PDF sets can be found. When ' // & 'the library has been correctly recognized during configuration, ' // & 'this is automatically set by \whizard. (cf. also \ttt{lhapdf}, ' // & '\ttt{\$lhapdf\_file}, \ttt{lhapdf\_photon}, \ttt{\$lhapdf\_photon\_file}, ' // & '\ttt{lhapdf\_member}, \ttt{lhapdf\_photon\_scheme})')) else call var_list%append_string (var_str ("$lhapdf_dir"), var_str(""), & intrinsic=.true., & description=var_str ('String variable that tells the path ' // & 'where the \lhapdf\ library and PDF sets can be found. When ' // & 'the library has been correctly recognized during configuration, ' // & 'this is automatically set by \whizard. (cf. also \ttt{lhapdf}, ' // & '\ttt{\$lhapdf\_file}, \ttt{lhapdf\_photon}, \ttt{\$lhapdf\_photon\_file}, ' // & '\ttt{lhapdf\_member}, \ttt{lhapdf\_photon\_scheme})')) end if call var_list%append_string (var_str ("$lhapdf_file"), var_str (""), & intrinsic=.true., & description=var_str ('This string variable \ttt{\$lhapdf\_file ' // & '= "{\em }"} allows to specify the PDF set \ttt{{\em ' // & '}} from the external \lhapdf\ library. It must match ' // & 'the exact name of the PDF set from the \lhapdf\ library. The ' // & 'default is empty, and the default set from \lhapdf\ is taken. ' // & 'Only one argument is possible, the PDF set must be identical ' // & 'for both beams, unless there are fundamentally different beam ' // & 'particles like proton and photon. (cf. also \ttt{lhapdf}, \ttt{\$lhapdf\_dir}, ' // & '\ttt{lhapdf\_photon}, \ttt{\$lhapdf\_photon\_file}, \ttt{lhapdf\_photon\_scheme}, ' // & '\ttt{lhapdf\_member})')) call var_list%append_string (var_str ("$lhapdf_photon_file"), var_str (""), & intrinsic=.true., & description=var_str ('String variable \ttt{\$lhapdf\_photon\_file ' // & '= "{\em }"} analagous to ($\to$) \ttt{\$lhapdf\_file} ' // & 'for photon PDF structure functions from the external \lhapdf\ ' // & 'library. The name must exactly match the one of the set from ' // & '\lhapdf. (cf. \ttt{beams}, \ttt{lhapdf}, \ttt{\$lhapdf\_dir}, ' // & '\ttt{\$lhapdf\_file}, \ttt{\$lhapdf\_photon\_file}, \ttt{lhapdf\_member}, ' // & '\ttt{lhapdf\_photon\_scheme})')) call var_list%append_int (var_str ("lhapdf_member"), 0, & intrinsic=.true., & description=var_str ('Integer variable that specifies the number ' // & 'of the corresponding PDF set chosen via the command ($\to$) ' // & '\ttt{\$lhapdf\_file} or ($\to$) \ttt{\$lhapdf\_photon\_file} ' // & 'from the external \lhapdf\ library. E.g. error PDF sets can ' // & 'be chosen by this. (cf. also \ttt{lhapdf}, \ttt{\$lhapdf\_dir}, ' // & '\ttt{\$lhapdf\_file}, \ttt{lhapdf\_photon}, \ttt{\$lhapdf\_photon\_file}, ' // & '\ttt{lhapdf\_photon\_scheme})')) call var_list%append_int (var_str ("lhapdf_photon_scheme"), 0, & intrinsic=.true., & description=var_str ('Integer parameter that controls the different ' // & 'available schemes for photon PDFs inside the external \lhapdf\ ' // & 'library. For more details see the \lhapdf\ manual. (cf. also ' // & '\ttt{lhapdf}, \ttt{\$lhapdf\_dir}, \ttt{\$lhapdf\_file}, \ttt{lhapdf\_photon}, ' // & '\ttt{\$lhapdf\_photon\_file}, \ttt{lhapdf\_member})')) call var_list%append_string (var_str ("$pdf_builtin_set"), var_str ("CTEQ6L"), & intrinsic=.true., & description=var_str ("For \whizard's internal PDF structure functions " // & 'for hadron colliders, this string variable allows to set the ' // & 'particular PDF set. (cf. also \ttt{pdf\_builtin}, \ttt{pdf\_builtin\_photon})')) call var_list%append_log (var_str ("?hoppet_b_matching"), .false., & intrinsic=.true., & description=var_str ('Flag that switches on the matching between ' // & '4- and 5-flavor schemes for hadron collider $b$-parton initiated ' // & 'processes. Works either with builtin PDFs or with the external ' // & '\lhapdf\ interface. Needs the external \ttt{HOPPET} library ' // & 'to be linked. (cf. \ttt{beams}, \ttt{pdf\_builtin}, \ttt{lhapdf})')) call var_list%append_real (var_str ("isr_alpha"), 0._default, & intrinsic=.true., & description=var_str ('For lepton collider initial-state QED ' // & 'radiation (ISR), this real parameter sets the value of $\alpha_{em}$ ' // & 'used in the structure function. If not set, it is taken from ' // & 'the parameter set of the physics model in use (cf. also \ttt{isr}, ' // & '\ttt{isr\_q\_max}, \ttt{isr\_mass}, \ttt{isr\_order}, \ttt{?isr\_recoil}, ' // & '\ttt{?isr\_keep\_energy})')) call var_list%append_real (var_str ("isr_q_max"), 0._default, & intrinsic=.true., & description=var_str ('This real parameter allows to set the ' // & 'scale of the initial-state QED radiation (ISR) structure function. ' // & 'If not set, it is taken internally to be $\sqrt{s}$. (cf. ' // & 'also \ttt{isr}, \ttt{isr\_alpha}, \ttt{isr\_mass}, \ttt{isr\_order}, ' // & '\ttt{?isr\_recoil}, \ttt{?isr\_keep\_energy})')) call var_list%append_real (var_str ("isr_mass"), 0._default, & intrinsic=.true., & description=var_str ('This real parameter allows to set by hand ' // & 'the mass of the incoming particle for lepton collider initial-state ' // & 'QED radiation (ISR). If not set, the mass for the initial beam ' // & 'particle is taken from the model in use. (cf. also \ttt{isr}, ' // & '\ttt{isr\_q\_max}, \ttt{isr\_alpha}, \ttt{isr\_order}, \ttt{?isr\_recoil}, ' // & '\ttt{?isr\_keep\_energy})')) call var_list%append_int (var_str ("isr_order"), 3, & intrinsic=.true., & description=var_str ('For lepton collider initial-state QED ' // & 'radiation (ISR), this integer parameter allows to set the order ' // & 'up to which hard-collinear radiation is taken into account. ' // & 'Default is the highest available, namely third order. (cf. ' // & 'also \ttt{isr}, \ttt{isr\_q\_max}, \ttt{isr\_mass}, \ttt{isr\_alpha}, ' // & '\ttt{?isr\_recoil}, \ttt{?isr\_keep\_energy})')) call var_list%append_log (var_str ("?isr_recoil"), .false., & intrinsic=.true., & description=var_str ('Flag to switch on recoil, i.e. a non-vanishing ' // & '$p_T$-kick for the lepton collider initial-state QED radiation ' // & '(ISR). (cf. also \ttt{isr}, \ttt{isr}, \ttt{isr\_alpha}, \ttt{isr\_mass}, ' // & '\ttt{isr\_order}, \ttt{isr\_q\_max})')) call var_list%append_log (var_str ("?isr_keep_energy"), .false., & intrinsic=.true., & description=var_str ('As the splitting kinematics for the ISR ' // & 'structure function violates Lorentz invariance when the recoil ' // & 'is switched on, this flag forces energy conservation when set ' // & 'to true, otherwise violating energy conservation. (cf. also ' // & '\ttt{isr}, \ttt{isr\_q\_max}, \ttt{isr\_mass}, \ttt{isr\_order}, ' // & '\ttt{?isr\_recoil}, \ttt{?isr\_alpha})')) call var_list%append_log (var_str ("?isr_handler"), .false., & intrinsic=.true., & description=var_str ('Activate ISR ' // & 'handler for event generation (no effect on integration). ' // & 'Requires \ttt{isr\_recoil = false}')) call var_list%append_string (var_str ("$isr_handler_mode"), & var_str ("trivial"), & intrinsic=.true., & description=var_str ('Operation mode for the ISR ' // & 'event handler. Allowed values: \ttt{trivial} (no effect), ' // & '\ttt{recoil} (recoil kinematics with two photons)')) call var_list%append_log (var_str ("?isr_handler_keep_mass"), .true., & intrinsic=.true., & description=var_str ('If \ttt{true} (default), force the incoming ' // & 'partons of the hard process (after radiation) on their mass ' // & 'shell. Otherwise, insert massless on-shell momenta. This ' // & 'applies only for event generation (no effect on integration, ' // & 'cf.\ also \ttt{?isr\_handler})')) call var_list%append_string (var_str ("$epa_mode"), & var_str ("default"), intrinsic=.true., & description=var_str ('For the equivalent photon approximation ' // & '(EPA), this string variable defines the mode, i.e. the explicit ' // & 'formula for the EPA distribution. For more details cf. the manual. ' // & - 'Possible are \ttt{default} (\ttt{Budnev\_617}), \ttt{Budnev\_616e}. ' // & + 'Possible are \ttt{default} (\ttt{Budnev\_617}), \ttt{Budnev\_616e}, ' // & + '\ttt{log\_power}, \ttt{log\_simple}, and \ttt{log}. ' // & '(cf. also \ttt{epa}, \ttt{epa\_x\_min}, \ttt{epa\_mass}, \ttt{epa\_e\_max}, ' // & '\ttt{epa\_q\_min}, \ttt{?epa\_recoil}, \ttt{?epa\_keep\_energy}, ' // & '\ttt{?epa\_handler}, \ttt{\$epa\_handler\_mode})')) call var_list%append_real (var_str ("epa_alpha"), 0._default, & intrinsic=.true., & description=var_str ('For the equivalent photon approximation ' // & '(EPA), this real parameter sets the value of $\alpha_{em}$ ' // & 'used in the structure function. If not set, it is taken from ' // & 'the parameter set of the physics model in use (cf. also \ttt{epa}, ' // & '\ttt{epa\_x\_min}, \ttt{epa\_mass}, \ttt{epa\_e\_max}, \ttt{epa\_q\_min}, ' // & '\ttt{?epa\_recoil}, \ttt{?epa\_keep\_energy}, \ttt{\$epa\_mode}, ' // & '\ttt{?epa\_handler}, \ttt{\$epa\_handler\_mode})')) call var_list%append_real (var_str ("epa_x_min"), 0._default, & intrinsic=.true., & description=var_str ('Real parameter that sets the lower cutoff ' // & 'for the energy fraction in the splitting for the equivalent-photon ' // & 'approximation (EPA). This parameter has to be set by the user ' // & 'to a non-zero value smaller than one. (cf. also \ttt{epa}, ' // & '\ttt{epa\_e\_max}, \ttt{epa\_mass}, \ttt{epa\_alpha}, \ttt{epa\_q\_min}, ' // & '\ttt{?epa\_recoil}, \ttt{?epa\_keep\_energy}, \ttt{\$epa\_mode}, ' // & '\ttt{?epa\_handler}, \ttt{\$epa\_handler\_mode})')) call var_list%append_real (var_str ("epa_q_min"), 0._default, & intrinsic=.true., & description=var_str ('In the equivalent-photon approximation ' // & '(EPA), this real parameters sets the minimal value for the ' // & 'transferred momentum. Either this parameter or the mass of ' // & 'the beam particle has to be non-zero. (cf. also \ttt{epa}, ' // & '\ttt{epa\_x\_min}, \ttt{epa\_mass}, \ttt{epa\_alpha}, \ttt{epa\_q\_max}, ' // & '\ttt{?epa\_recoil}, \ttt{?epa\_keep\_energy}, \ttt{\$epa\_mode}, ' // & '\ttt{?epa\_handler}, \ttt{\$epa\_handler\_mode})')) call var_list%append_real (var_str ("epa_q_max"), 0._default, & intrinsic=.true., & description=var_str ('This real parameter allows to set the ' // & 'upper energy cutoff for the equivalent-photon approximation ' // & '(EPA). If not set, \whizard\ simply takes the collider energy, ' // & '$\sqrt{s}$. (cf. also \ttt{epa}, \ttt{epa\_x\_min}, \ttt{epa\_mass}, ' // & '\ttt{epa\_alpha}, \ttt{epa\_q\_min}, \ttt{?epa\_recoil}, \ttt{\$epa\_mode}, ' // & '\ttt{?epa\_keep\_energy}, \ttt{?epa\_handler}, \ttt{\$epa\_handler\_mode})')) call var_list%append_real (var_str ("epa_mass"), 0._default, & intrinsic=.true., & description=var_str ('This real parameter allows to set by hand ' // & 'the mass of the incoming particle for the equivalent-photon ' // & 'approximation (EPA). If not set, the mass for the initial beam ' // & 'particle is taken from the model in use. (cf. also \ttt{epa}, ' // & '\ttt{epa\_x\_min}, \ttt{epa\_e\_max}, \ttt{epa\_alpha}, \ttt{epa\_q\_min}, ' // & '\ttt{?epa\_recoil}, \ttt{?epa\_keep\_energy}, \ttt{\$epa\_mode}. ' // & '\ttt{?epa\_handler}, \ttt{\$epa\_handler\_mode})')) call var_list%append_log (var_str ("?epa_recoil"), .false., & intrinsic=.true., & description=var_str ('Flag to switch on recoil, i.e. a non-vanishing ' // & '$p_T$-kick for the equivalent-photon approximation (EPA). ' // & '(cf. also \ttt{epa}, \ttt{epa\_x\_min}, \ttt{epa\_mass}, \ttt{epa\_alpha}, ' // & '\ttt{epa\_e\_max}, \ttt{epa\_q\_min}, \ttt{?epa\_keep\_energy}, ' // & '\ttt{\$epa\_mode}, \ttt{?epa\_handler}, \ttt{\$epa\_handler\_mode})')) call var_list%append_log (var_str ("?epa_keep_energy"), .false., & intrinsic=.true., & description=var_str ('As the splitting kinematics for the EPA ' // & 'structure function violates Lorentz invariance when the recoil ' // & 'is switched on, this flag forces energy conservation when set ' // & 'to true, otherwise violating energy conservation. (cf. also ' // & '\ttt{epa}, \ttt{epa\_x\_min}, \ttt{epa\_mass}, \ttt{epa\_alpha}, ' // & '\ttt{epa\_q\_min}, \ttt{?epa\_recoil}, \ttt{\$epa\_mode}, ' // & '\ttt{?epa\_handler}, \ttt{\$epa\_handler\_mode})')) call var_list%append_log (var_str ("?epa_handler"), .false., & intrinsic=.true., & description=var_str ('Activate EPA ' // & 'handler for event generation (no effect on integration). ' // & 'Requires \ttt{epa\_recoil = false}')) call var_list%append_string (var_str ("$epa_handler_mode"), & var_str ("trivial"), & intrinsic=.true., & description=var_str ('Operation mode for the EPA ' // & 'event handler. Allowed values: \ttt{trivial} (no effect), ' // & '\ttt{recoil} (recoil kinematics with two beams)')) call var_list%append_real (var_str ("ewa_x_min"), 0._default, & intrinsic=.true., & description=var_str ('Real parameter that sets the lower cutoff ' // & 'for the energy fraction in the splitting for the equivalent ' // & '$W$ approximation (EWA). This parameter has to be set by the ' // & 'user to a non-zero value smaller than one. (cf. also \ttt{ewa}, ' // & '\ttt{ewa\_pt\_max}, \ttt{ewa\_mass}, \ttt{?ewa\_keep\_energy}, ' // & '\ttt{?ewa\_recoil})')) call var_list%append_real (var_str ("ewa_pt_max"), 0._default, & intrinsic=.true., & description=var_str ('This real parameter allows to set the ' // & 'upper $p_T$ cutoff for the equivalent $W$ approximation (EWA). ' // & 'If not set, \whizard\ simply takes the collider energy, $\sqrt{s}$. ' // & '(cf. also \ttt{ewa}, \ttt{ewa\_x\_min}, \ttt{ewa\_mass}, \ttt{?ewa\_keep\_energy}, ' // & '\ttt{?ewa\_recoil})')) call var_list%append_real (var_str ("ewa_mass"), 0._default, & intrinsic=.true., & description=var_str ('This real parameter allows to set by hand ' // & 'the mass of the incoming particle for the equivalent $W$ approximation ' // & '(EWA). If not set, the mass for the initial beam particle is ' // & 'taken from the model in use. (cf. also \ttt{ewa}, \ttt{ewa\_x\_min}, ' // & '\ttt{ewa\_pt\_max}, \ttt{?ewa\_keep\_energy}, \ttt{?ewa\_recoil})')) call var_list%append_log (var_str ("?ewa_recoil"), .false., & intrinsic=.true., & description=var_str ('For the equivalent $W$ approximation (EWA), ' // & 'this flag switches on recoil, i.e. non-collinear splitting. ' // & '(cf. also \ttt{ewa}, \ttt{ewa\_x\_min}, \ttt{ewa\_pt\_max}, ' // & '\ttt{ewa\_mass}, \ttt{?ewa\_keep\_energy})')) call var_list%append_log (var_str ("?ewa_keep_energy"), .false., & intrinsic=.true., & description=var_str ('As the splitting kinematics for the equivalent ' // & '$W$ approximation (EWA) violates Lorentz invariance when the ' // & 'recoil is switched on, this flag forces energy conservation ' // & 'when set to true, otherwise violating energy conservation. ' // & '(cf. also \ttt{ewa}, \ttt{ewa\_x\_min}, \ttt{ewa\_pt\_max}, ' // & '\ttt{ewa\_mass}, \ttt{?ewa\_recoil})')) call var_list%append_log (var_str ("?circe1_photon1"), .false., & intrinsic=.true., & description=var_str ('Flag to tell \whizard\ to use the photon ' // & 'of the \circeone\ beamstrahlung structure function as initiator ' // & 'for the hard scattering process in the first beam. (cf. also ' // & '\ttt{circe1}, \ttt{?circe1\_photon2}, \ttt{circe1\_sqrts}, ' // & '\ttt{?circe1\_generate}, \ttt{?circe1\_map}, \ttt{circe1\_eps}, ' // & '\newline \ttt{circe1\_mapping\_slope}, \ttt{circe1\_ver}, ' // & '\ttt{circe1\_rev}, \ttt{\$circe1\_acc}, \ttt{circe1\_chat}, \newline' // & '\ttt{?circe1\_with\_radiation})')) call var_list%append_log (var_str ("?circe1_photon2"), .false., & intrinsic=.true., & description=var_str ('Flag to tell \whizard\ to use the photon ' // & 'of the \circeone\ beamstrahlung structure function as initiator ' // & 'for the hard scattering process in the second beam. (cf. also ' // & '\ttt{circe1}, \ttt{?circe1\_photon1}, \ttt{circe1\_sqrts}, ' // & '\ttt{?circe1\_generate}, \ttt{?circe1\_map}, \ttt{circe1\_eps}, ' // & '\newline \ttt{circe1\_mapping\_slope}, \ttt{circe1\_ver}, ' // & '\ttt{circe1\_rev}, \ttt{\$circe1\_acc}, \ttt{circe1\_chat}, ' // & '\newline\ttt{?circe1\_with\_radiation})')) call var_list%append_real (var_str ("circe1_sqrts"), & intrinsic=.true., & description=var_str ('Real parameter that allows to set the ' // & 'value of the collider energy for the lepton collider beamstrahlung ' // & 'structure function \circeone. If not set, $\sqrt{s}$ is taken. ' // & '(cf. also \ttt{circe1}, \ttt{?circe1\_photon1}, \ttt{?circe1\_photon2}, ' // & '\ttt{?circe1\_generate}, \ttt{?circe1\_map}, \ttt{circe1\_eps}, ' // & '\newline \ttt{circe1\_mapping\_slope}, \ttt{circe1\_ver}, ' // & '\ttt{circe1\_rev}, \ttt{\$circe1\_acc}, \ttt{circe1\_chat}, \newline' // & '\ttt{?circe1\_with\_radiation})')) call var_list%append_log (var_str ("?circe1_generate"), .true., & intrinsic=.true., & description=var_str ('Flag that determines whether the \circeone\ ' // & 'structure function for lepton collider beamstrahlung uses the ' // & 'generator mode for the spectrum, or a pre-defined (semi-)analytical ' // & 'parameterization. Default is the generator mode. (cf. also ' // & '\ttt{circe1}, \ttt{?circe1\_photon1}, \newline \ttt{?circe1\_photon2}, ' // & '\ttt{circe1\_sqrts}, \ttt{?circe1\_map}, \ttt{circe1\_mapping\_slope}, ' // & '\ttt{circe1\_eps}, \newline \ttt{circe1\_ver}, \ttt{circe1\_rev}, ' // & '\ttt{\$circe1\_acc}, \ttt{circe1\_chat}, \ttt{?circe1\_with\_radiation})')) call var_list%append_log (var_str ("?circe1_map"), .true., & intrinsic=.true., & description=var_str ('Flag that determines whether the \circeone\ ' // & 'structure function for lepton collider beamstrahlung uses special ' // & 'mappings for $s$-channel resonances. (cf. also \ttt{circe1}, ' // & '\ttt{?circe1\_photon1}, \newline \ttt{?circe1\_photon2}, ' // & '\ttt{circe1\_sqrts}, \ttt{?circe1\_generate}, ' // & '\ttt{circe1\_mapping\_slope}, \ttt{circe1\_eps}, \newline ' // & '\ttt{circe1\_ver}, \ttt{circe1\_rev}, \ttt{\$circe1\_acc}, ' // & '\ttt{circe1\_chat}, \ttt{?circe1\_with\_radiation})')) call var_list%append_real (var_str ("circe1_mapping_slope"), 2._default, & intrinsic=.true., & description=var_str ('Real parameter that allows to vary the ' // & 'slope of the mapping function for the \circeone\ structure ' // & 'function for lepton collider beamstrahlung from the default ' // & 'value \ttt{2.}. (cf. also \ttt{circe1}, \ttt{?circe1\_photon1}, ' // & '\ttt{?circe1\_photon2}, \ttt{circe1\_sqrts}, \ttt{?circe1\_generate}, ' // & '\ttt{?circe1\_map}, \ttt{circe1\_eps}, \ttt{circe1\_ver}, ' // & '\ttt{circe1\_rev}, \ttt{\$circe1\_acc}, \ttt{circe1\_chat}, \newline' // & '\ttt{?circe1\_with\_radiation})')) call var_list%append_real (var_str ("circe1_eps"), 1e-5_default, & intrinsic=.true., & description=var_str ('Real parameter, that takes care of the ' // & 'mapping of the peak in the lepton collider beamstrahlung structure ' // & 'function spectrum of \circeone. (cf. also \ttt{circe1}, \ttt{?circe1\_photons}, ' // & '\ttt{?circe1\_photon2}, \ttt{circe1\_sqrts}, \ttt{?circe1\_generate}, ' // & '\ttt{?circe1\_map}, \ttt{circe1\_eps}, \newline ' // & '\ttt{circe1\_mapping\_slope}, \ttt{circe1\_ver}, \ttt{circe1\_rev}, ' // & '\ttt{\$circe1\_acc}, \ttt{circe1\_chat}, \newline\ttt{?circe1\_with\_radiation})')) call var_list%append_int (var_str ("circe1_ver"), 0, intrinsic=.true., & description=var_str ('Integer parameter that sets the internal ' // & 'versioning number of the \circeone\ structure function for lepton-collider ' // & 'beamstrahlung. It has to be set by the user explicitly, it takes ' // & 'values from one to ten. (cf. also \ttt{circe1}, \ttt{?circe1\_photon1}, ' // & '\ttt{?circe1\_photon2}, \ttt{?circe1\_generate}, \ttt{?circe1\_map}, ' // & '\ttt{circe1\_eps}, \ttt{circe1\_mapping\_slope}, \ttt{circe1\_sqrts}, ' // & '\ttt{circe1\_rev}, \ttt{\$circe1\_acc}, \ttt{circe1\_chat}, ' // & '\ttt{?circe1\_with\_radiation})')) call var_list%append_int (var_str ("circe1_rev"), 0, intrinsic=.true., & description=var_str ('Integer parameter that sets the internal ' // & 'revision number of the \circeone\ structure function for lepton-collider ' // & 'beamstrahlung. The default \ttt{0} translates always into the ' // & 'most recent version; older versions have to be accessed through ' // & 'the explicit revision date. For more details cf.~the \circeone ' // & 'manual. (cf. also \ttt{circe1}, \ttt{?circe1\_photon1}, \ttt{?circe1\_photon2}, ' // & '\ttt{?circe1\_generate}, \ttt{?circe1\_map}, \ttt{circe1\_eps}, ' // & '\ttt{circe1\_mapping\_slope}, \ttt{circe1\_sqrts}, \ttt{circe1\_ver}, ' // & '\ttt{\$circe1\_acc}, \ttt{circe1\_chat}, \ttt{?circe1\_with\_radiation})')) call var_list%append_string (var_str ("$circe1_acc"), var_str ("SBAND"), & intrinsic=.true., & description=var_str ('String variable that specifies the accelerator ' // & 'type for the \circeone\ structure function for lepton-collider ' // & 'beamstrahlung. (\ttt{?circe1\_photons}, \ttt{?circe1\_photon2}, ' // & '\ttt{circe1\_sqrts}, \ttt{?circe1\_generate}, \ttt{?circe1\_map}, ' // & '\ttt{circe1\_eps}, \ttt{circe1\_mapping\_slope}, \ttt{circe1\_ver}, ' // & '\newline \ttt{circe1\_rev}, \ttt{circe1\_chat}, \ttt{?circe1\_with\_radiation})')) call var_list%append_int (var_str ("circe1_chat"), 0, intrinsic=.true., & description=var_str ('Chattiness of the \circeone\ structure ' // & 'function for lepton-collider beamstrahlung. The higher the integer ' // & 'value, the more information will be given out by the \circeone\ ' // & 'package. (\ttt{?circe1\_photons}, \ttt{?circe1\_photon2}, ' // & '\ttt{circe1\_sqrts}, \ttt{?circe1\_generate}, \ttt{?circe1\_map}, ' // & '\ttt{circe1\_eps}, \ttt{circe1\_mapping\_slope}, \ttt{circe1\_ver}, ' // & '\newline \ttt{circe1\_rev}, \ttt{\$circe1\_acc}, \ttt{?circe1\_with\_radiation})')) call var_list%append_log (var_str ("?circe1_with_radiation"), .false., & intrinsic=.true., & description=var_str ('This logical decides whether the additional photon ' // & 'or electron ("beam remnant") will be considered in the event record or ' // & 'not. (\ttt{?circe1\_photons}, \ttt{?circe1\_photon2}, ' // & '\ttt{circe1\_sqrts}, \ttt{?circe1\_generate}, \ttt{?circe1\_map}, ' // & '\ttt{circe1\_eps}, \ttt{circe1\_mapping\_slope}, \ttt{circe1\_ver}, ' // & '\newline \ttt{circe1\_rev}, \ttt{\$circe1\_acc})')) call var_list%append_log (var_str ("?circe2_polarized"), .true., & intrinsic=.true., & description=var_str ('Flag whether the photon spectra from the ' // & '\circetwo\ structure function for lepton colliders should be ' // & 'treated polarized. (cf. also \ttt{circe2}, \ttt{\$circe2\_file}, ' // & '\ttt{\$circe2\_design})')) call var_list%append_string (var_str ("$circe2_file"), & intrinsic=.true., & description=var_str ('String variable by which the corresponding ' // & 'photon collider spectrum for the \circetwo\ structure function ' // & 'can be selected. (cf. also \ttt{circe2}, \ttt{?circe2\_polarized}, ' // & '\ttt{\$circe2\_design})')) call var_list%append_string (var_str ("$circe2_design"), var_str ("*"), & intrinsic=.true., & description=var_str ('String variable that sets the collider ' // & 'design for the \circetwo\ structure function for photon collider ' // & 'spectra. (cf. also \ttt{circe2}, \ttt{\$circe2\_file}, \ttt{?circe2\_polarized})')) call var_list%append_real (var_str ("gaussian_spread1"), 0._default, & intrinsic=.true., & description=var_str ('Parameter that sets the energy spread ' // & '($\sigma$ value) of the first beam for a Gaussian spectrum. ' // & '(cf. \ttt{gaussian})')) call var_list%append_real (var_str ("gaussian_spread2"), 0._default, & intrinsic=.true., & description=var_str ('Ditto, for the second beam.')) call var_list%append_string (var_str ("$beam_events_file"), & intrinsic=.true., & description=var_str ('String variable that allows to set the ' // & "name of the external file from which a beamstrahlung's spectrum " // & 'for lepton colliders as pairs of energy fractions is read in. ' // & '(cf. also \ttt{beam\_events}, \ttt{?beam\_events\_warn\_eof})')) call var_list%append_log (var_str ("?beam_events_warn_eof"), .true., & intrinsic=.true., & description=var_str ('Flag that tells \whizard\ to ' // & 'issue a warning when in a simulation the end of an external ' // & "file for beamstrahlung's spectra for lepton colliders are reached, " // & 'and energy fractions from the beginning of the file are reused. ' // & '(cf. also \ttt{beam\_events}, \ttt{\$beam\_events\_file})')) call var_list%append_log (var_str ("?energy_scan_normalize"), .false., & intrinsic=.true., & description=var_str ('Normalization flag for the energy scan ' // & 'structure function: if set the total cross section is normalized ' // & 'to unity. (cf. also \ttt{energy\_scan})')) end subroutine var_list_set_beams_defaults @ %def var_list_set_beams_defaults @ <>= procedure :: set_core_defaults => var_list_set_core_defaults <>= subroutine var_list_set_core_defaults (var_list, seed) class(var_list_t), intent(inout) :: var_list integer, intent(in) :: seed logical, target, save :: known = .true. !!! ?????? real(default), parameter :: real_specimen = 1. call var_list_append_log_ptr & (var_list, var_str ("?logging"), logging, known, & intrinsic=.true., & description=var_str ('This logical -- when set to \ttt{false} ' // & '-- suppresses writing out a logfile (default: \ttt{whizard.log}) ' // & 'for the whole \whizard\ run, or when \whizard\ is run with the ' // & '\ttt{--no-logging} option, to suppress parts of the logging ' // & 'when setting it to \ttt{true} again at a later part of the ' // & '\sindarin\ input file. Mainly for debugging purposes. ' // & '(cf. also \ttt{?openmp\_logging}, \ttt{?mpi\_logging})')) call var_list%append_string (var_str ("$job_id"), & intrinsic=.true., & description=var_str ('Arbitrary string that can be used for ' // & 'creating unique names. The variable is initialized with the ' // & 'value of the \ttt{job\_id} option on startup. (cf. also ' // & '\ttt{\$compile\_workspace}, \ttt{\$run\_id})')) call var_list%append_string (var_str ("$compile_workspace"), & intrinsic=.true., & description=var_str ('If set, create process source code ' // & 'and process-driver library code in a subdirectory with this ' // & 'name. If non-existent, the directory will be created. (cf. ' // & 'also \ttt{\$job\_id}, \ttt{\$run\_id}, \ttt{\$integrate\_workspace})')) call var_list%append_int (var_str ("seed"), seed, & intrinsic=.true., & description=var_str ('Integer variable \ttt{seed = {\em }} ' // & 'that allows to set a specific random seed \ttt{num}. If not ' // & 'set, \whizard\ takes the time from the system clock to determine ' // & 'the random seed.')) call var_list%append_string (var_str ("$model_name"), & intrinsic=.true., & description=var_str ('This variable makes the locally used physics ' // & 'model available as a string, e.g. as \ttt{show (\$model\_name)}. ' // & 'However, the user is not able to change the current model by ' // & 'setting this variable to a different string. (cf. also \ttt{model}, ' // & '\ttt{\$library\_name}, \ttt{printf}, \ttt{show})')) call var_list%append_int (var_str ("process_num_id"), & intrinsic=.true., & description=var_str ('Using the integer \ttt{process\_num\_id ' // & '= {\em }} one can set a numerical identifier for processes ' // & 'within a process library. This can be set either just before ' // & 'the corresponding \ttt{process} definition or as an optional ' // & 'local argument of the latter. (cf. also \ttt{process}, ' // & '\ttt{?proc\_as\_run\_id}, \ttt{lcio\_run\_id})')) call var_list%append_log (var_str ("?proc_as_run_id"), .true., & intrinsic=.true., & description=var_str ('Normally, for LCIO the process ID (cf. ' // & '\ttt{process\_num\_id}) is used as run ID, unless this flag is ' // & 'set to \ttt{false}, cf. also \ttt{process}, \ttt{lcio\_run\_id}.')) call var_list%append_int (var_str ("lcio_run_id"), 0, & intrinsic=.true., & description=var_str ('Allows to set an integer run ID for the LCIO ' // & 'event format. Normally, the process ID is taken as run ID, unless ' // & 'the flag (cf.) \ttt{?proc\_as\_run\_id} is set to \ttt{false}, ' // & 'cf. also \ttt{process}.')) call var_list%append_string (var_str ("$method"), var_str ("omega"), & intrinsic=.true., & description=var_str ('This string variable specifies the method ' // & 'for the matrix elements to be used in the evaluation. The default ' // & "is the intrinsic \oMega\ matrix element generator " // & '(\ttt{"omega"}), other options are: \ttt{"ovm"}, \ttt{"unit\_test"}, ' // & '\ttt{"template\_unity"}, \ttt{"threshold"}. For processes defined ' // & '\ttt{"template"}, with \ttt{nlo\_calculation = ...}, please refer to ' // & '\ttt{\$born\_me\_method}, \ttt{\$real\_tree\_me\_method}, ' // & '\ttt{\$loop\_me\_method} and \ttt{\$correlation\_me\_method}.')) call var_list%append_log (var_str ("?report_progress"), .true., & intrinsic=.true., & description=var_str ('Flag for the \oMega\ matrix element generator ' // & 'whether to print out status messages about progress during ' // & 'matrix element generation. (cf. also \ttt{\$method}, \ttt{\$omega\_flags})')) call var_list%append_log (var_str ("?me_verbose"), .false., & description=var_str ("Flag determining whether " // & "the makefile command for generating and compiling the \oMega\ matrix " // & "element code is silent or verbose. Default is silent.")) call var_list%append_string (var_str ("$restrictions"), var_str (""), & intrinsic=.true., & description=var_str ('This is an optional argument for process ' // & 'definitions for the matrix element method \ttt{"omega"}. Using ' // & 'the following construction, it defines a string variable, \ttt{process ' // & '\newline {\em } = {\em }, {\em } ' // & '=> {\em }, {\em }, ... \{ \$restrictions ' // & '= "{\em }" \}}. The string argument \ttt{{\em ' // & '}} is directly transferred during the code ' // & 'generation to the ME generator \oMega. It has to be of the form ' // & '\ttt{n1 + n2 + ... \url{~} {\em }}, where ' // & '\ttt{n1} and so on are the numbers of the particles above in ' // & 'the process definition. The tilde specifies a certain intermediate ' // & 'state to be equal to the particle(s) in \ttt{particle (list)}. ' // & 'An example is \ttt{process eemm\_z = e1, E1 => e2, E2 ' // & '\{ \$restrictions = "1+2 \url{~} Z" \} } restricts the code ' // & 'to be generated for the process $e^- e^+ \to \mu^- \mu^+$ to ' // & 'the $s$-channel $Z$-boson exchange. For more details see Sec.~\ref{sec:omega_me} ' // & '(cf. also \ttt{process})')) call var_list%append_log (var_str ("?omega_write_phs_output"), .false., & intrinsic=.true., & description=var_str ('This flag decides whether a the phase-space ' // & 'output is produced by the \oMega\ matrix element generator. This ' // & 'output is written to file(s) and contains the Feynman diagrams ' // & 'which belong to the process(es) under consideration. The file is ' // & 'mandatory whenever the variable \ttt{\$phs\_method} has the value ' // & '\ttt{fast\_wood}, i.e. if the phase-space file is provided by ' // & 'cascades2.')) call var_list%append_string (var_str ("$omega_flags"), var_str (""), & intrinsic=.true., & description=var_str ('String variable that allows to pass flags ' // & 'to the \oMega\ matrix element generator. Normally, \whizard\ ' // & 'takes care of all flags automatically. Note that for restrictions ' // & 'of intermediate states, there is a special string variable: ' // & '(cf. $\to$) \ttt{\$restrictions}.')) call var_list%append_log (var_str ("?read_color_factors"), .true., & intrinsic=.true., & description=var_str ('This flag decides whether to read QCD ' // & 'color factors from the matrix element provided by each method, ' // & 'or to try and calculate the color factors in \whizard\ internally.')) call var_list%append_log (var_str ("?slha_read_input"), .true., & intrinsic=.true., & description=var_str ('Flag which decides whether \whizard\ reads ' // & 'in the SM and parameter information from the \ttt{SMINPUTS} ' // & 'and \ttt{MINPAR} common blocks of the SUSY Les Houches Accord ' // & 'files. (cf. also \ttt{read\_slha}, \ttt{write\_slha}, \ttt{?slha\_read\_spectrum}, ' // & '\ttt{?slha\_read\_decays})')) call var_list%append_log (var_str ("?slha_read_spectrum"), .true., & intrinsic=.true., & description=var_str ('Flag which decides whether \whizard\ reads ' // & 'in the whole spectrum and mixing angle information from the ' // & 'common blocks of the SUSY Les Houches Accord files. (cf. also ' // & '\ttt{read\_slha}, \ttt{write\_slha}, \ttt{?slha\_read\_decays}, ' // & '\ttt{?slha\_read\_input})')) call var_list%append_log (var_str ("?slha_read_decays"), .false., & intrinsic=.true., & description=var_str ('Flag which decides whether \whizard\ reads ' // & 'in the widths and branching ratios from the \ttt{DCINFO} common ' // & 'block of the SUSY Les Houches Accord files. (cf. also \ttt{read\_slha}, ' // & '\ttt{write\_slha}, \ttt{?slha\_read\_spectrum}, \ttt{?slha\_read\_input})')) call var_list%append_string (var_str ("$library_name"), & intrinsic=.true., & description=var_str ('Similar to \ttt{\$model\_name}, this string ' // & 'variable is used solely to access the name of the active process ' // & 'library, e.g. in \ttt{printf} statements. (cf. \ttt{compile}, ' // & '\ttt{library}, \ttt{printf}, \ttt{show}, \ttt{\$model\_name})')) call var_list%append_log (var_str ("?alphas_is_fixed"), .true., & intrinsic=.true., & description=var_str ('Flag that tells \whizard\ to use a non-running ' // & '$\alpha_s$. Note that this has to be set explicitly to $\ttt{false}$ ' // & 'if the user wants to use one of the running $\alpha_s$ options. ' // & '(cf. also \ttt{alphas\_order}, \ttt{?alphas\_from\_lhapdf}, ' // & '\ttt{?alphas\_from\_pdf\_builtin}, \ttt{alphas\_nf}, \ttt{?alphas\_from\_mz}, ' // & '\newline \ttt{?alphas\_from\_lambda\_qcd}, \ttt{lambda\_qcd})')) call var_list%append_log (var_str ("?alphas_from_lhapdf"), .false., & intrinsic=.true., & description=var_str ('Flag that tells \whizard\ to use a running ' // & '$\alpha_s$ from the \lhapdf\ library (which has to be correctly ' // & 'linked). Note that \ttt{?alphas\_is\_fixed} has to be set ' // & 'explicitly to $\ttt{false}$. (cf. also \ttt{alphas\_order}, ' // & '\ttt{?alphas\_is\_fixed}, \ttt{?alphas\_from\_pdf\_builtin}, ' // & '\ttt{alphas\_nf}, \ttt{?alphas\_from\_mz}, \ttt{?alphas\_from\_lambda\_qcd}, ' // & '\ttt{lambda\_qcd})')) call var_list%append_log (var_str ("?alphas_from_pdf_builtin"), .false., & intrinsic=.true., & description=var_str ('Flag that tells \whizard\ to use a running ' // & '$\alpha_s$ from the internal PDFs. Note that in that case \ttt{?alphas\_is\_fixed} ' // & 'has to be set explicitly to $\ttt{false}$. (cf. also ' // & '\ttt{alphas\_order}, \ttt{?alphas\_is\_fixed}, \ttt{?alphas\_from\_lhapdf}, ' // & '\ttt{alphas\_nf}, \ttt{?alphas\_from\_mz}, \newline \ttt{?alphas\_from\_lambda\_qcd}, ' // & '\ttt{lambda\_qcd})')) call var_list%append_int (var_str ("alphas_order"), 0, & intrinsic=.true., & description=var_str ('Integer parameter that sets the order ' // & 'of the internal evolution for running $\alpha_s$ in \whizard: ' // & 'the default, \ttt{0}, is LO running, \ttt{1} is NLO, \ttt{2} ' // & 'is NNLO. (cf. also \ttt{alphas\_is\_fixed}, \ttt{?alphas\_from\_lhapdf}, ' // & '\ttt{?alphas\_from\_pdf\_builtin}, \ttt{alphas\_nf}, \ttt{?alphas\_from\_mz}, ' // & '\newline \ttt{?alphas\_from\_lambda\_qcd}, \ttt{lambda\_qcd})')) call var_list%append_int (var_str ("alphas_nf"), 5, & intrinsic=.true., & description=var_str ('Integer parameter that sets the number ' // & 'of active quark flavors for the internal evolution for running ' // & '$\alpha_s$ in \whizard: the default is \ttt{5}. (cf. also ' // & '\ttt{alphas\_is\_fixed}, \ttt{?alphas\_from\_lhapdf}, \ttt{?alphas\_from\_pdf\_builtin}, ' // & '\ttt{alphas\_order}, \ttt{?alphas\_from\_mz}, \newline ' // & '\ttt{?alphas\_from\_lambda\_qcd}, \ttt{lambda\_qcd})')) call var_list%append_log (var_str ("?alphas_from_mz"), .false., & intrinsic=.true., & description=var_str ('Flag that tells \whizard\ to use its internal ' // & 'running $\alpha_s$ from $\alpha_s(M_Z)$. Note that in that ' // & 'case \ttt{?alphas\_is\_fixed} has to be set explicitly to ' // & '$\ttt{false}$. (cf. also \ttt{alphas\_order}, \ttt{?alphas\_is\_fixed}, ' // & '\ttt{?alphas\_from\_lhapdf}, \ttt{alphas\_nf}, \ttt{?alphas\_from\_pdf\_builtin}, ' // & '\newline \ttt{?alphas\_from\_lambda\_qcd}, \ttt{lambda\_qcd})')) call var_list%append_log (var_str ("?alphas_from_lambda_qcd"), .false., & intrinsic=.true., & description=var_str ('Flag that tells \whizard\ to use its internal ' // & 'running $\alpha_s$ from $\alpha_s(\Lambda_{QCD})$. Note that ' // & 'in that case \ttt{?alphas\_is\_fixed} has to be set explicitly ' // & 'to $\ttt{false}$. (cf. also \ttt{alphas\_order}, \ttt{?alphas\_is\_fixed}, ' // & '\ttt{?alphas\_from\_lhapdf}, \ttt{alphas\_nf}, \ttt{?alphas\_from\_pdf\_builtin}, ' // & '\newline \ttt{?alphas\_from\_mz}, \ttt{lambda\_qcd})')) call var_list%append_real (var_str ("lambda_qcd"), 200.e-3_default, & intrinsic=.true., & description=var_str ('Real parameter that sets the value for ' // & '$\Lambda_{QCD}$ used in the internal evolution for running ' // & '$\alpha_s$ in \whizard. (cf. also \ttt{alphas\_is\_fixed}, ' // & '\ttt{?alphas\_from\_lhapdf}, \ttt{alphas\_nf}, ' // & '\newline \ttt{?alphas\_from\_pdf\_builtin}, ' // & '\ttt{?alphas\_from\_mz}, \ttt{?alphas\_from\_lambda\_qcd}, ' // & '\ttt{alphas\_order})')) call var_list%append_log (var_str ("?fatal_beam_decay"), .true., & intrinsic=.true., & description=var_str ('Logical variable that let the user decide ' // & 'whether the possibility of a beam decay is treated as a fatal ' // & 'error or only as a warning. An example is a process $b t \to ' // & 'X$, where the bottom quark as an inital state particle appears ' // & 'as a possible decay product of the second incoming particle, ' // & 'the top quark. This might trigger inconsistencies or instabilities ' // & 'in the phase space set-up.')) call var_list%append_log (var_str ("?helicity_selection_active"), .true., & intrinsic=.true., & description=var_str ('Flag that decides whether \whizard\ uses ' // & 'a numerical selection rule for vanishing helicities: if active, ' // & 'then, if a certain helicity combination yields an absolute ' // & '(\oMega) matrix element smaller than a certain threshold ($\to$ ' // & '\ttt{helicity\_selection\_threshold}) more often than a certain ' // & 'cutoff ($\to$ \ttt{helicity\_selection\_cutoff}), it will be dropped.')) call var_list%append_real (var_str ("helicity_selection_threshold"), & 1E10_default, & intrinsic=.true., & description=var_str ('Real parameter that gives the threshold ' // & 'for the absolute value of a certain helicity combination of ' // & 'an (\oMega) amplitude. If a certain number ($\to$ ' // & '\ttt{helicity\_selection\_cutoff}) of calls stays below this ' // & 'threshold, that combination will be dropped from then on. (cf. ' // & 'also \ttt{?helicity\_selection\_active})')) call var_list%append_int (var_str ("helicity_selection_cutoff"), 1000, & intrinsic=.true., & description=var_str ('Integer parameter that gives the number ' // & "a certain helicity combination of an (\oMega) amplitude has " // & 'to be below a certain threshold ($\to$ \ttt{helicity\_selection\_threshold}) ' // & 'in order to be dropped from then on. (cf. also \ttt{?helicity\_selection\_active})')) call var_list%append_string (var_str ("$rng_method"), var_str ("tao"), & intrinsic=.true., & description=var_str ('String variable that allows to set the ' // & 'method for the random number generation. Default is Donald ' // & "Knuth' RNG method \ttt{TAO}.")) call var_list%append_log (var_str ("?vis_diags"), .false., & intrinsic=.true., & description=var_str ('Logical variable that allows to give out ' // & "a Postscript or PDF file for the Feynman diagrams for a \oMega\ " // & 'process. (cf. \ttt{?vis\_diags\_color}).')) call var_list%append_log (var_str ("?vis_diags_color"), .false., & intrinsic=.true., & description=var_str ('Same as \ttt{?vis\_diags}, but switches ' // & 'on color flow instead of Feynman diagram generation. (cf. \ttt{?vis\_diags}).')) call var_list%append_log (var_str ("?check_event_file"), .true., & intrinsic=.true., & description=var_str ('Setting this to false turns off all sanity ' // & 'checks when reading a raw event file with previously generated ' // & 'events. Use this at your own risk; the program may return ' // & 'wrong results or crash if data do not match. (cf. also \ttt{?check\_grid\_file}, ' // & '\ttt{?check\_phs\_file})')) call var_list%append_string (var_str ("$event_file_version"), var_str (""), & intrinsic=.true., & description=var_str ('String variable that allows to set the ' // & 'format version of the \whizard\ internal binary event format.')) call var_list%append_int (var_str ("n_events"), 0, & intrinsic=.true., & description=var_str ('This specifier \ttt{n\_events = {\em }} ' // & 'sets the number of events for the event generation of the processes ' // & 'in the \sindarin\ input files. Note that WHIZARD itself chooses ' // & 'the number from the \ttt{n\_events} or from the \ttt{luminosity} ' // & 'specifier, whichever would give the larger number of events. ' // & 'As this depends on the cross section under consideration, it ' // & 'might be different for different processes in the process list. ' // & '(cf. \ttt{luminosity}, \ttt{\$sample}, \ttt{sample\_format}, ' // & '\ttt{?unweighted}, \ttt{event\_index\_offset})')) call var_list%append_int (var_str ("event_index_offset"), 0, & intrinsic=.true., & description=var_str ('The value ' // & '\ttt{event\_index\_offset = {\em }} ' // & 'initializes the event counter for a subsequent ' // & 'event sample. By default (value 0), the first event ' // & 'gets index value 1, incrementing by one for each generated event ' // & 'within a sample. The event counter is initialized again ' // & 'for each new sample (i.e., \ttt{integrate} command). ' // & 'If events are read from file, and the ' // & 'event file format supports event numbering, the event numbers ' // & 'will be taken from file instead, and the value of ' // & '\ttt{event\_index\_offset} has no effect. ' // & '(cf. \ttt{luminosity}, \ttt{\$sample}, \ttt{sample\_format}, ' // & '\ttt{?unweighted}, \ttt{n\_events})')) call var_list%append_log (var_str ("?unweighted"), .true., & intrinsic=.true., & description=var_str ('Flag that distinguishes between unweighted ' // & 'and weighted event generation. (cf. also \ttt{simulate}, \ttt{n\_events}, ' // & '\ttt{luminosity}, \ttt{event\_index\_offset})')) call var_list%append_real (var_str ("safety_factor"), 1._default, & intrinsic=.true., & description=var_str ('This real variable \ttt{safety\_factor ' // & '= {\em }} reduces the acceptance probability for unweighting. ' // & 'If greater than one, excess events become less likely, but ' // & 'the reweighting efficiency also drops. (cf. \ttt{simulate}, \ttt{?unweighted})')) call var_list%append_log (var_str ("?negative_weights"), .false., & intrinsic=.true., & description=var_str ('Flag that tells \whizard\ to allow negative ' // & 'weights in integration and simulation. (cf. also \ttt{simulate}, ' // & '\ttt{?unweighted})')) call var_list%append_log (var_str ("?resonance_history"), .false., & intrinsic=.true., & description=var_str ( & 'The logical variable \texttt{?resonance\_history ' // & '= true/false} specifies whether during a simulation pass, ' // & 'the event generator should try to reconstruct intermediate ' // & 'resonances. If activated, appropriate resonant subprocess ' // & 'matrix element code will be automatically generated. ')) call var_list%append_real (var_str ("resonance_on_shell_limit"), & 4._default, & intrinsic=.true., & description=var_str ( & 'The real variable \texttt{resonance\_on\_shell\_limit ' // & '= {\em }} specifies the maximum relative distance from a ' // & 'resonance peak, such that the kinematical configuration ' // & 'can still be considered on-shell. This is relevant only if ' // & '\texttt{?resonance\_history = true}.')) call var_list%append_real (var_str ("resonance_on_shell_turnoff"), & 0._default, & intrinsic=.true., & description=var_str ( & 'The real variable \texttt{resonance\_on\_shell\_turnoff ' // & '= {\em }}, if positive, ' // & 'controls the smooth transition from resonance-like ' // & 'to background-like events. The relative strength of a ' // & 'resonance is reduced by a Gaussian with width given by this ' // & 'variable. In any case, events are treated as background-like ' // & 'when the off-shellness is greater than ' // & '\texttt{resonance\_on\_shell\_limit}. All of this applies ' // & 'only if \texttt{?resonance\_history = true}.')) call var_list%append_real (var_str ("resonance_background_factor"), & 1._default, & intrinsic=.true., & description=var_str ( & 'The real variable \texttt{resonance\_background\_factor} ' // & 'controls resonance insertion if a resonance ' // & 'history applies to a particular event. In determining '// & 'whether event kinematics qualifies as resonant or non-resonant, ' //& 'the non-resonant probability is multiplied by this factor ' // & 'Setting the factor to zero removes the background ' // & 'configuration as long as the kinematics qualifies as on-shell ' // & 'as qualified by \texttt{resonance\_on\_shell\_limit}.')) call var_list%append_log (var_str ("?keep_beams"), .false., & intrinsic=.true., & description=var_str ('The logical variable \ttt{?keep\_beams ' // & '= true/false} specifies whether beam particles and beam remnants ' // & 'are included when writing event files. For example, in order ' // & 'to read Les Houches accord event files into \pythia, no beam ' // & 'particles are allowed.')) call var_list%append_log (var_str ("?keep_remnants"), .true., & intrinsic=.true., & description=var_str ('The logical variable \ttt{?keep\_beams ' // & '= true/false} is respected only if \ttt{?keep\_beams} is set. ' // & 'If \ttt{true}, beam remnants are tagged as outgoing particles ' // & 'if they have been neither showered nor hadronized, i.e., have ' // & 'no children. If \ttt{false}, beam remnants are also included ' // & 'in the event record, but tagged as unphysical. Note that for ' // & 'ISR and/or beamstrahlung spectra, the radiated photons are ' // & 'considered as beam remnants.')) call var_list%append_log (var_str ("?recover_beams"), .true., & intrinsic=.true., & description=var_str ('Flag that decides whether the beam particles ' // & 'should be reconstructed when reading event/rescanning files ' // & 'into \whizard. (cf. \ttt{rescan}, \ttt{?update\_event}, \ttt{?update\_sqme}, ' // & '\newline \ttt{?update\_weight})')) call var_list%append_log (var_str ("?update_event"), .false., & intrinsic=.true., & description=var_str ('Flag that decides whether the events in ' // & 'an event file should be rebuilt from the hard process when ' // & 'reading event/rescanning files into \whizard. (cf. \ttt{rescan}, ' // & '\ttt{?recover\_beams}, \ttt{?update\_sqme}, \ttt{?update\_weight})')) call var_list%append_log (var_str ("?update_sqme"), .false., & intrinsic=.true., & description=var_str ('Flag that decides whehter the squared ' // & 'matrix element in an event file should be updated/recalculated ' // & 'when reading event/rescanning files into \whizard. (cf. \ttt{rescan}, ' // & '\newline \ttt{?recover\_beams}, \ttt{?update\_event}, \ttt{?update\_weight})')) call var_list%append_log (var_str ("?update_weight"), .false., & intrinsic=.true., & description=var_str ('Flag that decides whether the weights ' // & 'in an event file should be updated/recalculated when reading ' // & 'event/rescanning files into \whizard. (cf. \ttt{rescan}, \ttt{?recover\_beams}, ' // & '\newline \ttt{?update\_event}, \ttt{?update\_sqme})')) call var_list%append_log (var_str ("?use_alphas_from_file"), .false., & intrinsic=.true., & description=var_str ('Flag that decides whether the current ' // & '$\alpha_s$ definition should be used when recalculating matrix ' // & 'elements for events read from file, or the value that is stored ' // & 'in the file for that event. (cf. \ttt{rescan}, \ttt{?update\_sqme}, ' // & '\ttt{?use\_scale\_from\_file})')) call var_list%append_log (var_str ("?use_scale_from_file"), .false., & intrinsic=.true., & description=var_str ('Flag that decides whether the current ' // & 'energy-scale expression should be used when recalculating matrix ' // & 'elements for events read from file, or the value that is stored ' // & 'in the file for that event. (cf. \ttt{rescan}, \ttt{?update\_sqme}, ' // & '\ttt{?use\_alphas\_from\_file})')) call var_list%append_log (var_str ("?allow_decays"), .true., & intrinsic=.true., & description=var_str ('Master flag to switch on cascade decays ' // & 'for final state particles as an event transform. As a default, ' // & 'it is switched on. (cf. also \ttt{?auto\_decays}, ' // & '\ttt{auto\_decays\_multiplicity}, \ttt{?auto\_decays\_radiative}, ' // & '\ttt{?decay\_rest\_frame})')) call var_list%append_log (var_str ("?auto_decays"), .false., & intrinsic=.true., & description=var_str ('Flag, particularly as optional argument of the ($\to$) ' // & '\ttt{unstable} command, that tells \whizard\ to automatically ' // & 'determine the decays of that particle up to the final state ' // & 'multplicity ($\to$) \ttt{auto\_decays\_multiplicity}. Depending ' // & 'on the flag ($\to$) \ttt{?auto\_decays\_radiative}, radiative ' // & 'decays will be taken into account or not. (cf. also \ttt{unstable}, ' // & '\ttt{?isotropic\_decay}, \ttt{?diagonal\_decay})')) call var_list%append_int (var_str ("auto_decays_multiplicity"), 2, & intrinsic=.true., & description=var_str ('Integer parameter, that sets -- ' // & 'for the ($\to$) \ttt{?auto\_decays} option to let \whizard\ ' // & 'automatically determine the decays of a particle set as ($\to$) ' // & '\ttt{unstable} -- the maximal final state multiplicity that ' // & 'is taken into account. The default is \ttt{2}. The flag \ttt{?auto\_decays\_radiative} ' // & 'decides whether radiative decays are taken into account. (cf.\ ' // & 'also \ttt{unstable}, \ttt{?auto\_decays})')) call var_list%append_log (var_str ("?auto_decays_radiative"), .false., & intrinsic=.true., & description=var_str ("If \whizard's automatic detection " // & 'of decay channels are switched on ($\to$ \ttt{?auto\_decays} ' // & 'for the ($\to$) \ttt{unstable} command, this flags decides ' // & 'whether radiative decays (e.g. containing additional photon(s)/gluon(s)) ' // & 'are taken into account or not. (cf. also \ttt{unstable}, \ttt{auto\_decays\_multiplicity})')) call var_list%append_log (var_str ("?decay_rest_frame"), .false., & intrinsic=.true., & description=var_str ('Flag that allows to force a particle decay ' // & 'to be simulated in its rest frame. This simplifies the calculation ' // & 'for decays as stand-alone processes, but makes the process ' // & 'unsuitable for use in a decay chain.')) call var_list%append_log (var_str ("?isotropic_decay"), .false., & intrinsic=.true., & description=var_str ('Flag that -- in case of using factorized ' // & 'production and decays using the ($\to$) \ttt{unstable} command ' // & '-- tells \whizard\ to switch off spin correlations completely ' // & '(isotropic decay). (cf. also \ttt{unstable}, \ttt{?auto\_decays}, ' // & '\ttt{decay\_helicity}, \ttt{?diagonal\_decay})')) call var_list%append_log (var_str ("?diagonal_decay"), .false., & intrinsic=.true., & description=var_str ('Flag that -- in case of using factorized ' // & 'production and decays using the ($\to$) \ttt{unstable} command ' // & '-- tells \whizard\ instead of full spin correlations to take ' // & 'only the diagonal entries in the spin-density matrix (i.e. ' // & 'classical spin correlations). (cf. also \ttt{unstable}, \ttt{?auto\_decays}, ' // & '\ttt{decay\_helicity}, \ttt{?isotropic\_decay})')) call var_list%append_int (var_str ("decay_helicity"), & intrinsic=.true., & description=var_str ('If this parameter is given an integer ' // & 'value, any particle decay triggered by a subsequent \ttt{unstable} ' // & 'declaration will receive a projection on the given helicity ' // & 'state for the unstable particle. (cf. also \ttt{unstable}, ' // & '\ttt{?isotropic\_decay}, \ttt{?diagonal\_decay}. The latter ' // & 'parameters, if true, take precdence over any \ttt{?decay\_helicity} setting.)')) call var_list%append_log (var_str ("?polarized_events"), .false., & intrinsic=.true., & description=var_str ('Flag that allows to select certain helicity ' // & 'combinations in final state particles in the event files, ' // & 'and perform analysis on polarized event samples. (cf. also ' // & '\ttt{simulate}, \ttt{polarized}, \ttt{unpolarized})')) call var_list%append_string (var_str ("$polarization_mode"), & var_str ("helicity"), & intrinsic=.true., & description=var_str ('String variable that specifies the mode in ' // & 'which the polarization of particles is handled when polarized events ' // & 'are written out. Possible options are \ttt{"ignore"}, \ttt{"helicity"}, ' // & '\ttt{"factorized"}, and \ttt{"correlated"}. For more details cf. the ' // & 'detailed section.')) call var_list%append_log (var_str ("?colorize_subevt"), .false., & intrinsic=.true., & description=var_str ('Flag that enables color-index tracking ' // & 'in the subevent (\ttt{subevt}) objects that are used for ' // & 'internal event analysis.')) call var_list%append_real (var_str ("tolerance"), 0._default, & intrinsic=.true., & description=var_str ('Real variable that defines the absolute ' // & 'tolerance with which the (logical) function \ttt{expect} accepts ' // & 'equality or inequality: \ttt{tolerance = {\em }}. This ' // & 'can e.g. be used for cross-section tests and backwards compatibility ' // & 'checks. (cf. also \ttt{expect})')) call var_list%append_int (var_str ("checkpoint"), 0, & intrinsic = .true., & description=var_str ('Setting this integer variable to a positive ' // & 'integer $n$ instructs simulate to print out a progress summary ' // & 'every $n$ events.')) call var_list%append_int (var_str ("event_callback_interval"), 0, & intrinsic = .true., & description=var_str ('Setting this integer variable to a positive ' // & 'integer $n$ instructs simulate to print out a progress summary ' // & 'every $n$ events.')) call var_list%append_log (var_str ("?pacify"), .false., & intrinsic=.true., & description=var_str ('Flag that allows to suppress numerical ' // & 'noise and give screen and log file output with a lower number ' // & 'of significant digits. Mainly for debugging purposes. (cf. also ' // & '\ttt{?sample\_pacify})')) call var_list%append_string (var_str ("$out_file"), var_str (""), & intrinsic=.true., & description=var_str ('This character variable allows to specify ' // & 'the name of the data file to which the histogram and plot data ' // & 'are written (cf. also \ttt{write\_analysis}, \ttt{open\_out}, ' // & '\ttt{close\_out})')) call var_list%append_log (var_str ("?out_advance"), .true., & intrinsic=.true., & description=var_str ('Flag that sets advancing in the \ttt{printf} ' // & 'output commands, i.e. continuous printing with no line feed ' // & 'etc. (cf. also \ttt{printf})')) !!! JRR: WK please check (#542) ! call var_list%append_log (var_str ("?out_custom"), .false., & ! intrinsic=.true.) ! call var_list%append_string (var_str ("$out_comment"), var_str ("# "), & ! intrinsic=.true.) ! call var_list%append_log (var_str ("?out_header"), .true., & ! intrinsic=.true.) ! call var_list%append_log (var_str ("?out_yerr"), .true., & ! intrinsic=.true.) ! call var_list%append_log (var_str ("?out_xerr"), .true., & ! intrinsic=.true.) call var_list%append_int (var_str ("real_range"), & range (real_specimen), intrinsic = .true., locked = .true., & description=var_str ('This integer gives the decimal exponent ' // & 'range of the numeric model for the real float type in use. It cannot ' // & 'be set by the user. (cf. also \ttt{real\_precision}, ' // & '\ttt{real\_epsilon}, \ttt{real\_tiny}).')) call var_list%append_int (var_str ("real_precision"), & precision (real_specimen), intrinsic = .true., locked = .true., & description=var_str ('This integer gives the precision of ' // & 'the numeric model for the real float type in use. It cannot ' // & 'be set by the user. (cf. also \ttt{real\_range}, ' // & '\ttt{real\_epsilon}, \ttt{real\_tiny}).')) call var_list%append_real (var_str ("real_epsilon"), & epsilon (real_specimen), intrinsic = .true., locked = .true., & description=var_str ('This gives the smallest number $E$ ' // & 'of the same kind as the float type for which $1 + E > 1$. ' // & 'It cannot be set by the user. (cf. also \ttt{real\_range}, ' // & '\ttt{real\_tiny}, \ttt{real\_precision}).')) call var_list%append_real (var_str ("real_tiny"), & tiny (real_specimen), intrinsic = .true., locked = .true., & description=var_str ('This gives the smallest positive (non-zero) ' // & 'number in the numeric model for the real float type in use. ' // & 'It cannot be set by the user. (cf. also \ttt{real\_range}, ' // & '\ttt{real\_epsilon}, \ttt{real\_precision}).')) end subroutine var_list_set_core_defaults @ %def var_list_set_core_defaults @ <>= procedure :: set_integration_defaults => var_list_set_integration_defaults <>= subroutine var_list_set_integration_defaults (var_list) class(var_list_t), intent(inout) :: var_list call var_list%append_string (var_str ("$integration_method"), var_str ("vamp"), & intrinsic=.true., & description=var_str ('This string variable specifies the method ' // & 'for performing the multi-dimensional phase-space integration. ' // & 'The default is the \vamp\ algorithm (\ttt{"vamp"}), other options ' // & 'are via the numerical midpoint rule (\ttt{"midpoint"}) or an ' // & 'alternate \vamptwo\ implementation that is MPI-parallelizable ' // & '(\ttt{"vamp2"}).')) call var_list%append_int (var_str ("threshold_calls"), 10, & intrinsic=.true., & description=var_str ('This integer variable gives a limit for ' // & 'the number of calls in a given channel which acts as a lower ' // & 'threshold for the channel weight. If the number of calls in ' // & 'that channel falls below this threshold, the weight is not ' // & 'lowered further but kept at this threshold. (cf. also ' // & '\ttt{channel\_weights\_power})')) call var_list%append_int (var_str ("min_calls_per_channel"), 10, & intrinsic=.true., & description=var_str ('Integer parameter that modifies the settings ' // & "of the \vamp\ integrator's grid parameters. It sets the minimal " // & 'number every channel must be called. If the number of calls ' // & 'from the iterations is too small, \whizard\ will automatically ' // & 'increase the number of calls. (cf. \ttt{iterations}, \ttt{min\_calls\_per\_bin}, ' // & '\ttt{min\_bins}, \ttt{max\_bins})')) call var_list%append_int (var_str ("min_calls_per_bin"), 10, & intrinsic=.true., & description=var_str ('Integer parameter that modifies the settings ' // & "of the \vamp\ integrator's grid parameters. It sets the minimal " // & 'number every bin in an integration dimension must be called. ' // & 'If the number of calls from the iterations is too small, \whizard\ ' // & 'will automatically increase the number of calls. (cf. \ttt{iterations}, ' // & '\ttt{min\_calls\_per\_channel}, \ttt{min\_bins}, \ttt{max\_bins})')) call var_list%append_int (var_str ("min_bins"), 3, & intrinsic=.true., & description=var_str ('Integer parameter that modifies the settings ' // & "of the \vamp\ integrator's grid parameters. It sets the minimal " // & 'number of bins per integration dimension. (cf. \ttt{iterations}, ' // & '\ttt{max\_bins}, \ttt{min\_calls\_per\_channel}, \ttt{min\_calls\_per\_bin})')) call var_list%append_int (var_str ("max_bins"), 20, & intrinsic=.true., & description=var_str ('Integer parameter that modifies the settings ' // & "of the \vamp\ integrator's grid parameters. It sets the maximal " // & 'number of bins per integration dimension. (cf. \ttt{iterations}, ' // & '\ttt{min\_bins}, \ttt{min\_calls\_per\_channel}, \ttt{min\_calls\_per\_bin})')) call var_list%append_log (var_str ("?stratified"), .true., & intrinsic=.true., & description=var_str ('Flag that switches between stratified ' // & 'and importance sampling for the \vamp\ integration method.')) call var_list%append_log (var_str ("?use_vamp_equivalences"), .true., & intrinsic=.true., & description=var_str ('Flag that decides whether equivalence ' // & 'relations (symmetries) between different integration channels ' // & 'are used by the \vamp\ integrator.')) call var_list%append_log (var_str ("?vamp_verbose"), .false., & intrinsic=.true., & description=var_str ('Flag that sets the chattiness of the \vamp\ ' // & 'integrator. If set, not only errors, but also all warnings and ' // & 'messages will be written out (not the default). (cf. also \newline ' // & '\ttt{?vamp\_history\_global}, \ttt{?vamp\_history\_global\_verbose}, ' // & '\ttt{?vamp\_history\_channels}, \newline \ttt{?vamp\_history\_channels\_verbose})')) call var_list%append_log (var_str ("?vamp_history_global"), & .true., intrinsic=.true., & description=var_str ('Flag that decides whether the global history ' // & 'of the grid adaptation of the \vamp\ integrator are written ' // & 'into the process logfiles. (cf. also \ttt{?vamp\_history\_global\_verbose}, ' // & '\ttt{?vamp\_history\_channels}, \ttt{?vamp\_history\_channels\_verbose}, ' // & '\ttt{?vamp\_verbose})')) call var_list%append_log (var_str ("?vamp_history_global_verbose"), & .false., intrinsic=.true., & description=var_str ('Flag that decides whether the global history ' // & 'of the grid adaptation of the \vamp\ integrator are written ' // & 'into the process logfiles in an extended version. Only for debugging ' // & 'purposes. (cf. also \ttt{?vamp\_history\_global}, \ttt{?vamp\_history\_channels}, ' // & '\ttt{?vamp\_verbose}, \ttt{?vamp\_history\_channels\_verbose})')) call var_list%append_log (var_str ("?vamp_history_channels"), & .false., intrinsic=.true., & description=var_str ('Flag that decides whether the history of ' // & 'the grid adaptation of the \vamp\ integrator for every single ' // & 'channel are written into the process logfiles. Only for debugging ' // & 'purposes. (cf. also \ttt{?vamp\_history\_global\_verbose}, ' // & '\ttt{?vamp\_history\_global}, \ttt{?vamp\_verbose}, \newline ' // & '\ttt{?vamp\_history\_channels\_verbose})')) call var_list%append_log (var_str ("?vamp_history_channels_verbose"), & .false., intrinsic=.true., & description=var_str ('Flag that decides whether the history of ' // & 'the grid adaptation of the \vamp\ integrator for every single ' // & 'channel are written into the process logfiles in an extended ' // & 'version. Only for debugging purposes. (cf. also \ttt{?vamp\_history\_global}, ' // & '\ttt{?vamp\_history\_channels}, \ttt{?vamp\_verbose}, \ttt{?vamp\_history\_global\_verbose})')) call var_list%append_string (var_str ("$run_id"), var_str (""), & intrinsic=.true., & description=var_str ('String variable \ttt{\$run\_id = "{\em ' // & '}"} that allows to set a special ID for a particular process ' // & 'run, e.g. in a scan. The run ID is then attached to the process ' // & 'log file: \newline \ttt{{\em }\_{\em }.{\em ' // & '}.log}, the \vamp\ grid file: \newline \ttt{{\em }\_{\em ' // & '}.{\em }.vg}, and the phase space file: \newline ' // & '\ttt{{\em }\_{\em }.{\em }.phs}. ' // & '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. (cf.\ also ' // & '\ttt{\$job\_id}, \ttt{\$compile\_workspace}')) call var_list%append_int (var_str ("n_calls_test"), 0, & intrinsic=.true., & description=var_str ('Integer variable that allows to set a ' // & 'certain number of matrix element sampling test calls without ' // & 'actually integrating the process under consideration. (cf. ' // & '\ttt{integrate})')) call var_list%append_log (var_str ("?integration_timer"), .true., & intrinsic=.true., & description=var_str ('This flag switches the integration timer ' // & 'on and off, that gives the estimate for the duration of the ' // & 'generation of 10,000 unweighted events for each integrated ' // & 'process.')) call var_list%append_log (var_str ("?check_grid_file"), .true., & intrinsic=.true., & description=var_str ('Setting this to false turns off all sanity ' // & 'checks when reading a grid file with previous integration data. ' // & 'Use this at your own risk; the program may return wrong results ' // & 'or crash if data do not match. (cf. also \ttt{?check\_event\_file}, \ttt{?check\_phs\_file}) ')) call var_list%append_real (var_str ("accuracy_goal"), 0._default, & intrinsic=.true., & description=var_str ('Real parameter that allows the user to ' // & 'set a minimal accuracy that should be achieved in the Monte-Carlo ' // & 'integration of a certain process. If that goal is reached, ' // & 'grid and weight adapation stop, and this result is used for ' // & 'simulation. (cf. also \ttt{integrate}, \ttt{iterations}, ' // & '\ttt{error\_goal}, \ttt{relative\_error\_goal}, ' // & '\ttt{error\_threshold})')) call var_list%append_real (var_str ("error_goal"), 0._default, & intrinsic=.true., & description=var_str ('Real parameter that allows the user to ' // & 'set a minimal absolute error that should be achieved in the ' // & 'Monte-Carlo integration of a certain process. If that goal ' // & 'is reached, grid and weight adapation stop, and this result ' // & 'is used for simulation. (cf. also \ttt{integrate}, \ttt{iterations}, ' // & '\ttt{accuracy\_goal}, \ttt{relative\_error\_goal}, \ttt{error\_threshold})')) call var_list%append_real (var_str ("relative_error_goal"), 0._default, & intrinsic=.true., & description=var_str ('Real parameter that allows the user to ' // & 'set a minimal relative error that should be achieved in the ' // & 'Monte-Carlo integration of a certain process. If that goal ' // & 'is reached, grid and weight adaptation stop, and this result ' // & 'is used for simulation. (cf. also \ttt{integrate}, \ttt{iterations}, ' // & '\ttt{accuracy\_goal}, \ttt{error\_goal}, \ttt{error\_threshold})')) call var_list%append_int (var_str ("integration_results_verbosity"), 1, & intrinsic=.true., & description=var_str ('Integer parameter for the verbosity of ' // & 'the integration results in the process-specific logfile.')) call var_list%append_real (var_str ("error_threshold"), & 0._default, intrinsic=.true., & description=var_str ('The real parameter \ttt{error\_threshold ' // & '= {\em }} declares that any error value (in absolute numbers) ' // & 'smaller than \ttt{{\em }} is to be considered zero. The ' // & 'units are \ttt{fb} for scatterings and \ttt{GeV} for decays. ' // & '(cf. also \ttt{integrate}, \ttt{iterations}, \ttt{accuracy\_goal}, ' // & '\ttt{error\_goal}, \ttt{relative\_error\_goal})')) call var_list%append_real (var_str ("channel_weights_power"), 0.25_default, & intrinsic=.true., & description=var_str ('Real parameter that allows to vary the ' // & 'exponent of the channel weights for the \vamp\ integrator.')) call var_list%append_string (var_str ("$integrate_workspace"), & intrinsic=.true., & description=var_str ('Character string that tells \whizard\ ' // & 'the subdirectory where to find the run-specific phase-space ' // & 'configuration and the \vamp\ and \vamptwo\ grid files. ' // & 'If undefined (as per default), \whizard\ creates them and ' // & 'searches for them in the ' // & 'current directory. (cf. also \ttt{\$job\_id}, ' // & '\ttt{\$run\_id}, \ttt{\$compile\_workspace})')) call var_list%append_string (var_str ("$vamp_grid_format"), var_str ("ascii"), & intrinsic=.true., & description=var_str ('Character string that tells \whizard\ ' // & 'the file format for \ttt{vamp2} to use for writing and reading ' // & 'the configuration for the multi-channel integration setup and the ' // & '\vamptwo\ (only) grid data. The values can be \ttt{ascii} for a single ' // & 'human-readable grid file with ending \ttt{.vg2} or \ttt{binary} for two files, ' // & 'a human-readable header file with ending \ttt{.vg2} and binary file with ending ' // & '\ttt{.vgx2} storing the grid data.' // & 'The main purpose of the binary format is to perform faster I/O, e.g. for HPC runs.' // & '\whizard\ can convert between the different file formats automatically.')) end subroutine var_list_set_integration_defaults @ %def var_list_set_integration_defaults @ <>= procedure :: set_phase_space_defaults => var_list_set_phase_space_defaults <>= subroutine var_list_set_phase_space_defaults (var_list) class(var_list_t), intent(inout) :: var_list call var_list%append_string (var_str ("$phs_method"), var_str ("default"), & intrinsic=.true., & description=var_str ('String variable that allows to choose ' // & 'the phase-space parameterization method. The default is the ' // & '\ttt{"wood"} method that takes into account electroweak/BSM ' // & 'resonances. Note that this might not be the best choice for ' // & '(pure) QCD amplitudes. (cf. also \ttt{\$phs\_file})')) call var_list%append_log (var_str ("?vis_channels"), .false., & intrinsic=.true., & description=var_str ('Optional logical argument for the \ttt{integrate} ' // & 'command that demands \whizard\ to generate a PDF or postscript ' // & 'output showing the classification of the found phase space ' // & 'channels (if the phase space method \ttt{wood} has been used) ' // & 'according to their properties: \ttt{integrate (foo) \{ iterations=3:10000 ' // & '?vis\_channels = true \}}. The default is \ttt{false}. (cf. ' // & 'also \ttt{integrate}, \ttt{?vis\_history})')) call var_list%append_log (var_str ("?check_phs_file"), .true., & intrinsic=.true., & description=var_str ('Setting this to false turns off all sanity ' // & 'checks when reading a previously generated phase-space configuration ' // & 'file. Use this at your own risk; the program may return wrong ' // & 'results or crash if data do not match. (cf. also \ttt{?check\_event\_file}, ' // & '\ttt{?check\_grid\_file})')) call var_list%append_string (var_str ("$phs_file"), var_str (""), & intrinsic=.true., & description=var_str ('This string variable allows the user to ' // & 'set an individual file name for the phase space parameterization ' // & 'for a particular process: \ttt{\$phs\_file = "{\em }"}. ' // & 'If not set, the default is \ttt{{\em }\_{\em }.{\em ' // & '}.phs}. (cf. also \ttt{\$phs\_method})')) call var_list%append_log (var_str ("?phs_only"), .false., & intrinsic=.true., & description=var_str ('Flag (particularly as optional argument ' // & 'of the $\to$ \ttt{integrate} command) that allows to only generate ' // & 'the phase space file, but not perform the integration. (cf. ' // & 'also \ttt{\$phs\_method}, \ttt{\$phs\_file})')) call var_list%append_real (var_str ("phs_threshold_s"), 50._default, & intrinsic=.true., & description=var_str ('For the phase space method \ttt{wood}, ' // & 'this real parameter sets the threshold below which particles ' // & 'are assumed to be massless in the $s$-channel like kinematic ' // & 'regions. (cf. also \ttt{phs\_threshold\_t}, \ttt{phs\_off\_shell}, ' // & '\ttt{phs\_t\_channel}, \ttt{phs\_e\_scale}, \ttt{phs\_m\_scale}, ' // & '\newline \ttt{phs\_q\_scale}, \ttt{?phs\_keep\_resonant}, \ttt{?phs\_step\_mapping}, ' // & '\ttt{?phs\_step\_mapping\_exp}, \newline \ttt{?phs\_s\_mapping})')) call var_list%append_real (var_str ("phs_threshold_t"), 100._default, & intrinsic=.true., & description=var_str ('For the phase space method \ttt{wood}, ' // & 'this real parameter sets the threshold below which particles ' // & 'are assumed to be massless in the $t$-channel like kinematic ' // & 'regions. (cf. also \ttt{phs\_threshold\_s}, \ttt{phs\_off\_shell}, ' // & '\ttt{phs\_t\_channel}, \ttt{phs\_e\_scale}, \ttt{phs\_m\_scale}, ' // & '\newline \ttt{phs\_q\_scale}, \ttt{?phs\_keep\_resonant}, \ttt{?phs\_step\_mapping}, ' // & '\ttt{?phs\_step\_mapping\_exp}, \newline \ttt{?phs\_s\_mapping})')) call var_list%append_int (var_str ("phs_off_shell"), 2, & intrinsic=.true., & description=var_str ('Integer parameter that sets the number ' // & 'of off-shell (not $t$-channel-like, non-resonant) lines that ' // & 'are taken into account to find a valid phase-space setup in ' // & 'the \ttt{wood} phase-space method. (cf. also \ttt{phs\_threshold\_t}, ' // & '\ttt{phs\_threshold\_s}, \ttt{phs\_t\_channel}, \ttt{phs\_e\_scale}, ' // & '\ttt{phs\_m\_scale}, \ttt{phs\_q\_scale}, \ttt{?phs\_keep\_resonant}, ' // & '\ttt{?phs\_step\_mapping}, \newline \ttt{?phs\_step\_mapping\_exp}, ' // & '\ttt{?phs\_s\_mapping})')) call var_list%append_int (var_str ("phs_t_channel"), 6, & intrinsic=.true., & description=var_str ('Integer parameter that sets the number ' // & 'of $t$-channel propagators in multi-peripheral diagrams that ' // & 'are taken into account to find a valid phase-space setup in ' // & 'the \ttt{wood} phase-space method. (cf. also \ttt{phs\_threshold\_t}, ' // & '\ttt{phs\_threshold\_s}, \ttt{phs\_off\_shell}, \ttt{phs\_e\_scale}, ' // & '\ttt{phs\_m\_scale}, \ttt{phs\_q\_scale}, \ttt{?phs\_keep\_resonant}, ' // & '\ttt{?phs\_step\_mapping}, \newline \ttt{?phs\_step\_mapping\_exp}, ' // & '\ttt{?phs\_s\_mapping})')) call var_list%append_real (var_str ("phs_e_scale"), 10._default, & intrinsic=.true., & description=var_str ('Real parameter that sets the energy scale ' // & 'that acts as a cutoff for parameterizing radiation-like kinematics ' // & 'in the \ttt{wood} phase space method. \whizard\ takes the maximum ' // & 'of this value and the width of the propagating particle as ' // & 'a cutoff. (cf. also \ttt{phs\_threshold\_t}, \ttt{phs\_threshold\_s}, ' // & '\ttt{phs\_t\_channel}, \ttt{phs\_off\_shell}, \ttt{phs\_m\_scale}, ' // & '\ttt{phs\_q\_scale}, \newline \ttt{?phs\_keep\_resonant}, \ttt{?phs\_step\_mapping}, ' // & '\ttt{?phs\_step\_mapping\_exp}, \ttt{?phs\_s\_mapping})')) call var_list%append_real (var_str ("phs_m_scale"), 10._default, & intrinsic=.true., & description=var_str ('Real parameter that sets the mass scale ' // & 'that acts as a cutoff for parameterizing collinear and infrared ' // & 'kinematics in the \ttt{wood} phase space method. \whizard\ ' // & 'takes the maximum of this value and the mass of the propagating ' // & 'particle as a cutoff. (cf. also \ttt{phs\_threshold\_t}, \ttt{phs\_threshold\_s}, ' // & '\ttt{phs\_t\_channel}, \ttt{phs\_off\_shell}, \ttt{phs\_e\_scale}, ' // & '\ttt{phs\_q\_scale}, \newline \ttt{?phs\_keep\_resonant}, \ttt{?phs\_step\_mapping}, ' // & '\ttt{?phs\_step\_mapping\_exp}, \ttt{?phs\_s\_mapping})')) call var_list%append_real (var_str ("phs_q_scale"), 10._default, & intrinsic=.true., & description=var_str ('Real parameter that sets the momentum ' // & 'transfer scale that acts as a cutoff for parameterizing $t$- ' // & 'and $u$-channel like kinematics in the \ttt{wood} phase space ' // & 'method. \whizard\ takes the maximum of this value and the mass ' // & 'of the propagating particle as a cutoff. (cf. also \ttt{phs\_threshold\_t}, ' // & '\ttt{phs\_threshold\_s}, \ttt{phs\_t\_channel}, \ttt{phs\_off\_shell}, ' // & '\ttt{phs\_e\_scale}, \ttt{phs\_m\_scale}, \ttt{?phs\_keep\_resonant}, ' // & '\ttt{?phs\_step\_mapping}, \ttt{?phs\_step\_mapping\_exp}, ' // & '\newline \ttt{?phs\_s\_mapping})')) call var_list%append_log (var_str ("?phs_keep_nonresonant"), .true., & intrinsic=.true., & description=var_str ('Flag that decides whether the \ttt{wood} ' // & 'phase space method takes into account also non-resonant contributions. ' // & '(cf. also \ttt{phs\_threshold\_t}, \ttt{phs\_threshold\_s}, ' // & '\ttt{phs\_t\_channel}, \ttt{phs\_off\_shell}, \ttt{phs\_m\_scale}, ' // & '\ttt{phs\_q\_scale}, \ttt{phs\_e\_scale}, \ttt{?phs\_step\_mapping}, ' // & '\newline \ttt{?phs\_step\_mapping\_exp}, \ttt{?phs\_s\_mapping})')) call var_list%append_log (var_str ("?phs_step_mapping"), .true., & intrinsic=.true., & description=var_str ('Flag that switches on (or off) a particular ' // & 'phase space mapping for resonances, where the mass and width ' // & 'of the resonance are explicitly set as channel cutoffs. (cf. ' // & 'also \ttt{phs\_threshold\_t}, \ttt{phs\_threshold\_s}, \ttt{phs\_t\_channel}, ' // & '\ttt{phs\_off\_shell}, \ttt{phs\_e\_scale}, \newline \ttt{phs\_m\_scale}, ' // & '\ttt{?phs\_keep\_resonant}, \ttt{?phs\_q\_scale}, \ttt{?phs\_step\_mapping\_exp}, ' // & '\newline \ttt{?phs\_s\_mapping})')) call var_list%append_log (var_str ("?phs_step_mapping_exp"), .true., & intrinsic=.true., & description=var_str ('Flag that switches on (or off) a particular ' // & 'phase space mapping for resonances, where the mass and width ' // & 'of the resonance are explicitly set as channel cutoffs. This ' // & 'is an exponential mapping in contrast to ($\to$) \ttt{?phs\_step\_mapping}. ' // & '(cf. also \ttt{phs\_threshold\_t}, \ttt{phs\_threshold\_s}, ' // & '\ttt{phs\_t\_channel}, \ttt{phs\_off\_shell}, \ttt{phs\_e\_scale}, ' // & '\ttt{phs\_m\_scale}, \newline \ttt{?phs\_q\_scale}, \ttt{?phs\_keep\_resonant}, ' // & '\ttt{?phs\_step\_mapping}, \ttt{?phs\_s\_mapping})')) call var_list%append_log (var_str ("?phs_s_mapping"), .true., & intrinsic=.true., & description=var_str ('Flag that allows special mapping for $s$-channel ' // & 'resonances. (cf. also \ttt{phs\_threshold\_t}, \ttt{phs\_threshold\_s}, ' // & '\ttt{phs\_t\_channel}, \ttt{phs\_off\_shell}, \ttt{phs\_e\_scale}, ' // & '\ttt{phs\_m\_scale}, \newline \ttt{?phs\_keep\_resonant}, \ttt{?phs\_q\_scale}, ' // & '\ttt{?phs\_step\_mapping}, \ttt{?phs\_step\_mapping\_exp})')) call var_list%append_log (var_str ("?vis_history"), .false., & intrinsic=.true., & description=var_str ('Optional logical argument for the \ttt{integrate} ' // & 'command that demands \whizard\ to generate a PDF or postscript ' // & 'output showing the adaptation history of the Monte-Carlo integration ' // & 'of the process under consideration. (cf. also \ttt{integrate}, ' // & '\ttt{?vis\_channels})')) end subroutine var_list_set_phase_space_defaults @ %def var_list_set_phase_space_defaults @ <>= procedure :: set_gamelan_defaults => var_list_set_gamelan_defaults <>= subroutine var_list_set_gamelan_defaults (var_list) class(var_list_t), intent(inout) :: var_list call var_list%append_int (& var_str ("n_bins"), 20, & intrinsic=.true., & description=var_str ("Settings for \whizard's internal graphics " // & 'output: integer value that sets the number of bins in histograms. ' // & '(cf. also \ttt{?normalize\_bins}, \ttt{\$obs\_label}, \ttt{\$obs\_unit}, ' // & '\ttt{\$title}, \ttt{\$description}, \ttt{\$x\_label}, \ttt{\$y\_label}, ' // & '\ttt{graph\_width\_mm}, \ttt{graph\_height\_mm}, \ttt{?y\_log}, ' // & '\ttt{?x\_log}, \ttt{x\_min}, \ttt{x\_max}, \ttt{y\_min}, \ttt{y\_max}, ' // & '\ttt{\$gmlcode\_bg}, \ttt{\$gmlcode\_fg}, \ttt{?draw\_histogram}, ' // & '\ttt{?draw\_base}, \ttt{?draw\_piecewise}, \ttt{?fill\_curve}, ' // & '\ttt{?draw\_curve}, \ttt{?draw\_errors}, \ttt{?draw\_symbols}, ' // & '\newline \ttt{\$fill\_options}, \ttt{\$draw\_options}, \ttt{\$err\_options}, ' // & '\ttt{\$symbol})')) call var_list%append_log (& var_str ("?normalize_bins"), .false., & intrinsic=.true., & description=var_str ("Settings for \whizard's internal graphics " // & 'output: flag that determines whether the weights shall be normalized ' // & 'to the bin width or not. (cf. also \ttt{n\_bins}, \ttt{\$obs\_label}, ' // & '\ttt{\$obs\_unit}, \ttt{\$title}, \ttt{\$description}, \ttt{\$x\_label}, ' // & '\ttt{\$y\_label}, \ttt{graph\_width\_mm}, \ttt{graph\_height\_mm}, ' // & '\ttt{?y\_log}, \ttt{?x\_log}, \ttt{x\_min}, \ttt{x\_max}, \ttt{y\_min}, ' // & '\ttt{y\_max}, \ttt{\$gmlcode\_bg}, \ttt{\$gmlcode\_fg}, \ttt{?draw\_histogram}, ' // & '\newline \ttt{?draw\_base}, \ttt{?draw\_piecewise}, \ttt{?fill\_curve}, ' // & '\ttt{?draw\_curve}, \ttt{?draw\_errors}, \ttt{\$symbol}, \newline ' // & '\ttt{?draw\_symbols}, \ttt{\$fill\_options}, \ttt{\$draw\_options}, ' // & '\ttt{\$err\_options})')) call var_list%append_string (var_str ("$obs_label"), var_str (""), & intrinsic=.true., & description=var_str ("Settings for \whizard's internal graphics " // & 'output: this is a string variable \ttt{\$obs\_label = "{\em ' // & '}"} that allows to attach a label to a plotted ' // & 'or histogrammed observable. (cf. also \ttt{n\_bins}, \ttt{?normalize\_bins}, ' // & '\ttt{\$obs\_unit}, \ttt{\$title}, \ttt{\$description}, \ttt{\$x\_label}, ' // & '\ttt{\$y\_label}, \ttt{?y\_log}, \ttt{?x\_log}, \ttt{graph\_width\_mm}, ' // & '\ttt{graph\_height\_mm}, \ttt{x\_min}, \ttt{x\_max}, \ttt{y\_min}, ' // & '\ttt{y\_max}, \ttt{\$gmlcode\_bg}, \ttt{\$gmlcode\_fg}, \ttt{?draw\_base}, ' // & '\ttt{?draw\_histogram}, \ttt{?draw\_piecewise}, \newline \ttt{?fill\_curve}, ' // & '\ttt{?draw\_curve}, \ttt{?draw\_errors}, \ttt{\$symbol}, \ttt{?draw\_symbols}, ' // & '\ttt{\$fill\_options}, \ttt{\$draw\_options}, \ttt{\$err\_options})')) call var_list%append_string (var_str ("$obs_unit"), var_str (""), & intrinsic=.true., & description=var_str ("Settings for \whizard's internal graphics " // & 'output: this is a string variable \ttt{\$obs\_unit = "{\em ' // & '}"} that allows to attach a \LaTeX\ physical unit ' // & 'to a plotted or histogrammed observable. (cf. also \ttt{n\_bins}, ' // & '\ttt{?normalize\_bins}, \ttt{\$obs\_unit}, \ttt{\$title}, \ttt{\$description}, ' // & '\ttt{\$x\_label}, \ttt{\$y\_label}, \ttt{?y\_log}, \ttt{?x\_log}, ' // & '\ttt{graph\_width\_mm}, \ttt{graph\_height\_mm}, \ttt{x\_min}, ' // & '\ttt{x\_max}, \ttt{y\_min}, \ttt{y\_max}, \ttt{\$gmlcode\_bg}, ' // & '\ttt{\$gmlcode\_fg}, \ttt{?draw\_base}, \ttt{?draw\_histogram}, ' // & '\ttt{?fill\_curve}, \ttt{?draw\_piecewise}, \ttt{?draw\_curve}, ' // & '\ttt{?draw\_errors}, \ttt{\$symbol}, \ttt{?draw\_symbols}, ' // & '\ttt{\$fill\_options}, \ttt{\$draw\_options}, \ttt{\$err\_options})')) call var_list%append_string (var_str ("$title"), var_str (""), & intrinsic=.true., & description=var_str ('This string variable sets the title of ' // & 'a plot in a \whizard\ analysis setup, e.g. a histogram or an ' // & 'observable. The syntax is \ttt{\$title = "{\em }"}. ' // & 'This title appears as a section header in the analysis file, ' // & 'but not in the screen output of the analysis. (cf. also \ttt{n\_bins}, ' // & '\ttt{?normalize\_bins}, \ttt{\$obs\_unit}, \ttt{\$description}, ' // & '\ttt{\$x\_label}, \ttt{\$y\_label}, \ttt{?y\_log}, \ttt{?x\_log}, ' // & '\ttt{graph\_width\_mm}, \ttt{graph\_height\_mm}, \ttt{x\_min}, ' // & '\ttt{x\_max}, \ttt{y\_min}, \ttt{y\_max}, \ttt{\$gmlcode\_bg}, ' // & '\ttt{\$gmlcode\_fg}, \ttt{?draw\_base}, \ttt{?draw\_histogram}, ' // & '\ttt{?fill\_curve}, \ttt{?draw\_piecewise}, \newline \ttt{?draw\_curve}, ' // & '\ttt{?draw\_errors}, \ttt{\$symbol}, \ttt{?draw\_symbols}, ' // & '\ttt{\$fill\_options}, \ttt{\$draw\_options}, \ttt{\$err\_options})')) call var_list%append_string (var_str ("$description"), var_str (""), & intrinsic=.true., & description=var_str ('String variable that allows to specify ' // & 'a description text for the analysis, \ttt{\$description = "{\em ' // & '}"}. This line appears below the title ' // & 'of a corresponding analysis, on top of the respective plot. ' // & '(cf. also \ttt{analysis}, \ttt{n\_bins}, \ttt{?normalize\_bins}, ' // & '\ttt{\$obs\_unit}, \ttt{\$x\_label}, \ttt{\$y\_label}, \ttt{?y\_log}, ' // & '\ttt{?x\_log}, \ttt{graph\_width\_mm}, \ttt{graph\_height\_mm}, ' // & '\ttt{x\_min}, \ttt{x\_max}, \ttt{y\_min}, \ttt{y\_max}, \ttt{\$gmlcode\_bg}, ' // & '\ttt{\$gmlcode\_fg}, \ttt{?draw\_base}, \ttt{?draw\_histogram}, ' // & '\ttt{?fill\_curve}, \ttt{?draw\_piecewise}, \ttt{?draw\_curve}, ' // & '\ttt{?draw\_errors}, \ttt{\$symbol}, \ttt{?draw\_symbols}, ' // & '\ttt{\$fill\_options}, \ttt{\$draw\_options}, \ttt{\$err\_options})')) call var_list%append_string (var_str ("$x_label"), var_str (""), & intrinsic=.true., & description=var_str ('String variable, \ttt{\$x\_label = "{\em ' // & '}"}, that sets the $x$ axis label in a plot or ' // & 'histogram in a \whizard\ analysis. (cf. also \ttt{analysis}, ' // & '\ttt{n\_bins}, \ttt{?normalize\_bins}, \ttt{\$obs\_unit}, \ttt{\$y\_label}, ' // & '\ttt{?y\_log}, \ttt{?x\_log}, \ttt{graph\_width\_mm}, \ttt{graph\_height\_mm}, ' // & '\ttt{x\_min}, \ttt{x\_max}, \ttt{y\_min}, \ttt{y\_max}, \newline ' // & '\ttt{\$gmlcode\_bg}, \ttt{\$gmlcode\_fg}, \ttt{?draw\_base}, ' // & '\ttt{?draw\_histogram}, \ttt{?fill\_curve}, \newline \ttt{?draw\_piecewise}, ' // & '\ttt{?draw\_curve}, \ttt{?draw\_errors}, \ttt{\$symbol}, \ttt{?draw\_symbols}, ' // & '\ttt{\$fill\_options}, \ttt{\$draw\_options}, \ttt{\$err\_options})')) call var_list%append_string (var_str ("$y_label"), var_str (""), & intrinsic=.true., & description=var_str ('String variable, \ttt{\$y\_label = "{\em ' // & '}"}, that sets the $y$ axis label in a plot or ' // & 'histogram in a \whizard\ analysis. (cf. also \ttt{analysis}, ' // & '\ttt{n\_bins}, \ttt{?normalize\_bins}, \ttt{\$obs\_unit}, \ttt{?y\_log}, ' // & '\ttt{?x\_log}, \ttt{graph\_width\_mm}, \ttt{graph\_height\_mm}, ' // & '\ttt{x\_min}, \ttt{x\_max}, \ttt{y\_min}, \ttt{y\_max}, \newline ' // & '\ttt{\$gmlcode\_bg}, \ttt{\$gmlcode\_fg}, \ttt{?draw\_base}, ' // & '\ttt{?draw\_histogram}, \ttt{?fill\_curve}, \newline \ttt{?draw\_piecewise}, ' // & '\ttt{?draw\_curve}, \ttt{?draw\_errors}, \ttt{\$symbol}, \ttt{?draw\_symbols}, ' // & '\newline \ttt{\$fill\_options}, \ttt{\$draw\_options}, \ttt{\$err\_options})')) call var_list%append_int (var_str ("graph_width_mm"), 130, & intrinsic=.true., & description=var_str ("Settings for \whizard's internal graphics " // & 'output: integer value that sets the width of a graph or histogram ' // & 'in millimeters. (cf. also \ttt{?normalize\_bins}, \ttt{\$obs\_label}, ' // & '\ttt{\$obs\_unit}, \ttt{\$title}, \ttt{\$description}, \ttt{\$x\_label}, ' // & '\ttt{\$y\_label}, \ttt{graph\_height\_mm}, \ttt{?y\_log}, \ttt{?x\_log}, ' // & '\ttt{x\_min}, \ttt{x\_max}, \ttt{y\_min}, \ttt{y\_max}, \ttt{\$gmlcode\_bg}, ' // & '\ttt{\$gmlcode\_fg}, \ttt{?draw\_histogram}, \ttt{?draw\_base}, ' // & '\newline \ttt{?draw\_piecewise}, \ttt{?fill\_curve}, \ttt{?draw\_curve}, ' // & '\ttt{?draw\_errors}, \ttt{?draw\_symbols}, \newline \ttt{\$fill\_options}, ' // & '\ttt{\$draw\_options}, \ttt{\$err\_options}, \ttt{\$symbol})')) call var_list%append_int (var_str ("graph_height_mm"), 90, & intrinsic=.true., & description=var_str ("Settings for \whizard's internal graphics " // & 'output: integer value that sets the height of a graph or histogram ' // & 'in millimeters. (cf. also \ttt{?normalize\_bins}, \ttt{\$obs\_label}, ' // & '\ttt{\$obs\_unit}, \ttt{\$title}, \ttt{\$description}, \ttt{\$x\_label}, ' // & '\ttt{\$y\_label}, \ttt{graph\_width\_mm}, \ttt{?y\_log}, \ttt{?x\_log}, ' // & '\ttt{x\_min}, \ttt{x\_max}, \ttt{y\_min}, \ttt{y\_max}, \ttt{\$gmlcode\_bg}, ' // & '\ttt{\$gmlcode\_fg}, \ttt{?draw\_histogram}, \ttt{?draw\_base}, ' // & '\newline \ttt{?draw\_piecewise}, \ttt{?fill\_curve}, \ttt{?draw\_curve}, ' // & '\ttt{?draw\_errors}, \ttt{?draw\_symbols}, \newline \ttt{\$fill\_options}, ' // & '\ttt{\$draw\_options}, \ttt{\$err\_options}, \ttt{\$symbol})')) call var_list%append_log (var_str ("?y_log"), .false., & intrinsic=.true., & description=var_str ("Settings for \whizard's internal graphics " // & 'output: flag that makes the $y$ axis logarithmic. (cf. also ' // & '\ttt{?normalize\_bins}, \ttt{\$obs\_label}, \ttt{\$obs\_unit}, ' // & '\ttt{\$title}, \ttt{\$description}, \ttt{\$x\_label}, \ttt{\$y\_label}, ' // & '\ttt{graph\_height\_mm}, \ttt{graph\_width\_mm}, \ttt{?y\_log}, ' // & '\ttt{x\_min}, \ttt{x\_max}, \ttt{y\_min}, \ttt{y\_max}, \newline ' // & '\ttt{\$gmlcode\_bg}, \ttt{\$gmlcode\_fg}, \ttt{?draw\_histogram}, ' // & '\ttt{?draw\_base}, \ttt{?draw\_piecewise}, \newline \ttt{?fill\_curve}, ' // & '\ttt{?draw\_curve}, \ttt{?draw\_errors}, \ttt{?draw\_symbols}, ' // & '\ttt{\$fill\_options}, \newline \ttt{\$draw\_options}, \ttt{\$err\_options}, ' // & '\ttt{\$symbol})')) call var_list%append_log (var_str ("?x_log"), .false., & intrinsic=.true., & description=var_str ("Settings for \whizard's internal graphics " // & 'output: flag that makes the $x$ axis logarithmic. (cf. also ' // & '\ttt{?normalize\_bins}, \ttt{\$obs\_label}, \ttt{\$obs\_unit}, ' // & '\ttt{\$title}, \ttt{\$description}, \ttt{\$x\_label}, \ttt{\$y\_label}, ' // & '\ttt{graph\_height\_mm}, \ttt{graph\_width\_mm}, \ttt{?y\_log}, ' // & '\ttt{x\_min}, \ttt{x\_max}, \ttt{y\_min}, \ttt{y\_max}, \newline ' // & '\ttt{\$gmlcode\_bg}, \ttt{\$gmlcode\_fg}, \ttt{?draw\_histogram}, ' // & '\ttt{?draw\_base}, \ttt{?draw\_piecewise}, \newline \ttt{?fill\_curve}, ' // & '\ttt{?draw\_curve}, \ttt{?draw\_errors}, \ttt{?draw\_symbols}, ' // & '\ttt{\$fill\_options}, \newline \ttt{\$draw\_options}, \ttt{\$err\_options}, ' // & '\ttt{\$symbol})')) call var_list%append_real (var_str ("x_min"), & intrinsic=.true., & description=var_str ("Settings for \whizard's internal graphics " // & 'output: real parameter that sets the lower limit of the $x$ ' // & 'axis plotting or histogram interval. (cf. also \ttt{?normalize\_bins}, ' // & '\ttt{\$obs\_label}, \ttt{\$obs\_unit}, \ttt{\$title}, \ttt{\$description}, ' // & '\ttt{\$x\_label}, \ttt{\$y\_label}, \ttt{graph\_height\_mm}, ' // & '\ttt{?y\_log}, \newline \ttt{?x\_log}, \ttt{graph\_width\_mm}, ' // & '\ttt{x\_max}, \ttt{y\_min}, \ttt{y\_max}, \ttt{\$gmlcode\_bg}, ' // & '\ttt{\$gmlcode\_fg}, \ttt{?draw\_base}, \newline \ttt{?draw\_histogram}, ' // & '\ttt{?draw\_piecewise}, \ttt{?fill\_curve}, \ttt{?draw\_curve}, ' // & '\ttt{?draw\_errors}, \newline \ttt{?draw\_symbols}, \ttt{\$fill\_options}, ' // & '\ttt{\$draw\_options}, \ttt{\$err\_options}, \ttt{\$symbol})')) call var_list%append_real (var_str ("x_max"), & intrinsic=.true., & description=var_str ("Settings for \whizard's internal graphics " // & 'output: real parameter that sets the upper limit of the $x$ ' // & 'axis plotting or histogram interval. (cf. also \ttt{?normalize\_bins}, ' // & '\ttt{\$obs\_label}, \ttt{\$obs\_unit}, \ttt{\$title}, \ttt{\$description}, ' // & '\ttt{\$x\_label}, \ttt{\$y\_label}, \ttt{graph\_height\_mm}, ' // & '\ttt{?y\_log}, \newline \ttt{?x\_log}, \ttt{graph\_width\_mm}, ' // & '\ttt{x\_min}, \ttt{y\_min}, \ttt{y\_max}, \ttt{\$gmlcode\_bg}, ' // & '\ttt{\$gmlcode\_fg}, \ttt{?draw\_base}, \newline \ttt{?draw\_histogram}, ' // & '\ttt{?draw\_piecewise}, \ttt{?fill\_curve}, \ttt{?draw\_curve}, ' // & '\ttt{?draw\_errors}, \newline \ttt{?draw\_symbols}, \ttt{\$fill\_options}, ' // & '\ttt{\$draw\_options}, \ttt{\$err\_options}, \ttt{\$symbol})')) call var_list%append_real (var_str ("y_min"), & intrinsic=.true., & description=var_str ("Settings for \whizard's internal graphics " // & 'output: real parameter that sets the lower limit of the $y$ ' // & 'axis plotting or histogram interval. (cf. also \ttt{?normalize\_bins}, ' // & '\ttt{\$obs\_label}, \ttt{\$obs\_unit}, \ttt{\$title}, \ttt{\$description}, ' // & '\ttt{\$x\_label}, \ttt{\$y\_label}, \ttt{graph\_height\_mm}, ' // & '\ttt{?y\_log}, \newline \ttt{?x\_log}, \ttt{graph\_width\_mm}, ' // & '\ttt{x\_max}, \ttt{y\_max}, \ttt{x\_min}, \ttt{\$gmlcode\_bg}, ' // & '\ttt{\$gmlcode\_fg}, \ttt{?draw\_base}, \newline \ttt{?draw\_histogram}, ' // & '\ttt{?draw\_piecewise}, \ttt{?fill\_curve}, \ttt{?draw\_curve}, ' // & '\ttt{?draw\_errors}, \newline \ttt{?draw\_symbols}, \ttt{\$fill\_options}, ' // & '\ttt{\$draw\_options}, \ttt{\$err\_options}, \ttt{\$symbol})')) call var_list%append_real (var_str ("y_max"), & intrinsic=.true., & description=var_str ("Settings for \whizard's internal graphics " // & 'output: real parameter that sets the upper limit of the $y$ ' // & 'axis plotting or histogram interval. (cf. also \ttt{?normalize\_bins}, ' // & '\ttt{\$obs\_label}, \ttt{\$obs\_unit}, \ttt{\$title}, \ttt{\$description}, ' // & '\ttt{\$x\_label}, \ttt{\$y\_label}, \ttt{graph\_height\_mm}, ' // & '\ttt{?y\_log}, \newline \ttt{?x\_log}, \ttt{graph\_width\_mm}, ' // & '\ttt{x\_max}, \ttt{x\_min}, \ttt{y\_max}, \ttt{\$gmlcode\_bg}, ' // & '\ttt{\$gmlcode\_fg}, \ttt{?draw\_base}, \newline \ttt{?draw\_histogram}, ' // & '\ttt{?draw\_piecewise}, \ttt{?fill\_curve}, \ttt{?draw\_curve}, ' // & '\ttt{?draw\_errors}, \newline \ttt{?draw\_symbols}, \ttt{\$fill\_options}, ' // & '\ttt{\$draw\_options}, \ttt{\$err\_options}, \ttt{\$symbol})')) call var_list%append_string (var_str ("$gmlcode_bg"), var_str (""), & intrinsic=.true., & description=var_str ("Settings for \whizard's internal graphics " // & 'output: string variable that allows to define a background ' // & 'for plots and histograms (i.e. it is overwritten by the plot/histogram), ' // & 'e.g. a grid: \ttt{\$gmlcode\_bg = "standardgrid.lr(5);"}. For ' // & 'more details, see the \gamelan\ manual. (cf. also \ttt{?normalize\_bins}, ' // & '\ttt{\$obs\_label}, \ttt{\$obs\_unit}, \ttt{\$title}, \ttt{\$description}, ' // & '\ttt{\$x\_label}, \ttt{\$y\_label}, \ttt{graph\_width\_mm}, ' // & '\ttt{graph\_height\_mm}, \ttt{?y\_log}, \ttt{?x\_log}, \ttt{x\_min}, ' // & '\ttt{x\_max}, \ttt{y\_min}, \ttt{y\_max}, \ttt{\$gmlcode\_fg}, ' // & '\ttt{?draw\_histogram}, \ttt{?draw\_base}, \ttt{?draw\_piecewise}, ' // & '\newline \ttt{?fill\_curve}, \ttt{?draw\_curve}, \ttt{?draw\_errors}, ' // & '\ttt{?draw\_symbols}, \ttt{\$fill\_options}, \newline \ttt{\$draw\_options}, ' // & '\ttt{\$err\_options}, \ttt{\$symbol})')) call var_list%append_string (var_str ("$gmlcode_fg"), var_str (""), & intrinsic=.true., & description=var_str ("Settings for \whizard's internal graphics " // & 'output: string variable that allows to define a foreground ' // & 'for plots and histograms (i.e. it overwrites the plot/histogram), ' // & 'e.g. a grid: \ttt{\$gmlcode\_bg = "standardgrid.lr(5);"}. For ' // & 'more details, see the \gamelan\ manual. (cf. also \ttt{?normalize\_bins}, ' // & '\ttt{\$obs\_label}, \ttt{\$obs\_unit}, \ttt{\$title}, \ttt{\$description}, ' // & '\ttt{\$x\_label}, \ttt{\$y\_label}, \ttt{graph\_width\_mm}, ' // & '\ttt{graph\_height\_mm}, \ttt{?y\_log}, \ttt{?x\_log}, \ttt{x\_min}, ' // & '\ttt{x\_max}, \ttt{y\_min}, \ttt{y\_max}, \ttt{\$gmlcode\_bg}, ' // & '\ttt{?draw\_histogram}, \ttt{?draw\_base}, \ttt{?draw\_piecewise}, ' // & '\newline \ttt{?fill\_curve}, \ttt{?draw\_curve}, \ttt{?draw\_errors}, ' // & '\ttt{?draw\_symbols}, \ttt{\$fill\_options}, \newline \ttt{\$draw\_options}, ' // & '\ttt{\$err\_options}, \ttt{\$symbol})')) call var_list%append_log (var_str ("?draw_histogram"), & intrinsic=.true., & description=var_str ("Settings for \whizard's internal graphics " // & 'output: flag that tells \whizard\ to either plot data as a ' // & 'histogram or as a continuous line (if $\to$ \ttt{?draw\_curve} ' // & 'is set \ttt{true}). (cf. also \ttt{?normalize\_bins}, \ttt{\$obs\_label}, ' // & '\ttt{\$obs\_unit}, \ttt{\$title}, \ttt{\$description}, \ttt{\$x\_label}, ' // & '\ttt{\$y\_label}, \ttt{graph\_width\_mm}, \ttt{graph\_height\_mm}, ' // & '\ttt{?y\_log}, \ttt{?x\_log}, \ttt{x\_min}, \ttt{x\_max}, \ttt{y\_min}, ' // & '\ttt{y\_max}, \newline \ttt{\$gmlcode\_fg}, \ttt{\$gmlcode\_bg}, ' // & '\ttt{?draw\_base}, \ttt{?draw\_piecewise}, \ttt{?fill\_curve}, ' // & '\ttt{?draw\_curve}, \ttt{?draw\_errors}, \ttt{?draw\_symbols}, ' // & '\ttt{\$fill\_options}, \ttt{\$draw\_options}, \ttt{\$err\_options}, ' // & '\ttt{\$symbol})')) call var_list%append_log (var_str ("?draw_base"), & intrinsic=.true., & description=var_str ("Settings for \whizard's internal graphics " // & 'output: flag that tells \whizard\ to insert a \ttt{base} statement ' // & 'in the analysis code to calculate the plot data from a data ' // & 'set. (cf. also \ttt{?normalize\_bins}, \ttt{\$obs\_label}, ' // & '\ttt{\$obs\_unit}, \ttt{\$title}, \ttt{\$description}, \ttt{\$x\_label}, ' // & '\ttt{\$y\_label}, \ttt{graph\_width\_mm}, \ttt{graph\_height\_mm}, ' // & '\ttt{?y\_log}, \ttt{?x\_log}, \ttt{x\_min}, \ttt{x\_max}, \ttt{y\_min}, ' // & '\ttt{y\_max}, \newline \ttt{\$gmlcode\_fg}, \ttt{\$gmlcode\_bg}, ' // & '\ttt{?draw\_curve}, \ttt{?draw\_piecewise}, \ttt{?fill\_curve}, ' // & '\ttt{\$symbol}, \newline \ttt{?draw\_histogram}, \ttt{?draw\_errors}, ' // & '\ttt{?draw\_symbols}, \ttt{\$fill\_options}, \ttt{\$draw\_options}, ' // & '\newline \ttt{\$err\_options})')) call var_list%append_log (var_str ("?draw_piecewise"), & intrinsic=.true., & description=var_str ("Settings for \whizard's internal graphics " // & 'output: flag that tells \whizard\ to data from a data set piecewise, ' // & 'i.e. histogram style. (cf. also \ttt{?normalize\_bins}, \ttt{\$obs\_label}, ' // & '\ttt{\$obs\_unit}, \ttt{\$title}, \ttt{\$description}, \ttt{\$x\_label}, ' // & '\ttt{\$y\_label}, \ttt{graph\_width\_mm}, \ttt{graph\_height\_mm}, ' // & '\ttt{?y\_log}, \ttt{?x\_log}, \ttt{x\_min}, \ttt{x\_max}, ' // & '\ttt{y\_min}, \ttt{y\_max}, \ttt{\$gmlcode\_fg}, \ttt{\$gmlcode\_bg}, ' // & '\ttt{?draw\_curve}, \ttt{?draw\_base}, \ttt{?fill\_curve}, ' // & '\ttt{\$symbol}, \ttt{?draw\_histogram}, \ttt{?draw\_errors}, ' // & '\ttt{?draw\_symbols}, \ttt{\$fill\_options}, \ttt{\$draw\_options}, ' // & '\ttt{\$err\_options})')) call var_list%append_log (var_str ("?fill_curve"), & intrinsic=.true., & description=var_str ("Settings for \whizard's internal graphics " // & 'output: flag that tells \whizard\ to fill data curves (e.g. ' // & 'as a histogram). The style can be set with $\to$ \ttt{\$fill\_options ' // & '= "{\em }"}. (cf. also \ttt{?normalize\_bins}, ' // & '\ttt{\$obs\_label}, \ttt{\$obs\_unit}, \ttt{\$title}, \ttt{\$description}, ' // & '\ttt{\$x\_label}, \ttt{\$y\_label}, \ttt{graph\_width\_mm}, ' // & '\ttt{graph\_height\_mm}, \ttt{?y\_log}, \ttt{?x\_log}, \ttt{x\_min}, ' // & '\ttt{x\_max}, \ttt{y\_min}, \ttt{y\_max}, \newline \ttt{\$gmlcode\_fg}, ' // & '\ttt{\$gmlcode\_bg}, \ttt{?draw\_base}, \ttt{?draw\_piecewise}, ' // & '\ttt{?draw\_curve}, \ttt{?draw\_histogram}, \ttt{?draw\_errors}, ' // & '\ttt{?draw\_symbols}, \ttt{\$fill\_options}, \ttt{\$draw\_options}, ' // & '\ttt{\$err\_options}, \ttt{\$symbol})')) call var_list%append_log (var_str ("?draw_curve"), & intrinsic=.true., & description=var_str ("Settings for \whizard's internal graphics " // & 'output: flag that tells \whizard\ to either plot data as a ' // & 'continuous line or as a histogram (if $\to$ \ttt{?draw\_histogram} ' // & 'is set \ttt{true}). (cf. also \ttt{?normalize\_bins}, \ttt{\$obs\_label}, ' // & '\ttt{\$obs\_unit}, \ttt{\$title}, \ttt{\$description}, \ttt{\$x\_label}, ' // & '\ttt{\$y\_label}, \ttt{graph\_width\_mm}, \ttt{graph\_height\_mm}, ' // & '\ttt{?y\_log}, \ttt{?x\_log}, \ttt{x\_min}, \ttt{x\_max}, \ttt{y\_min}, ' // & '\ttt{y\_max}, \newline \ttt{\$gmlcode\_fg}, \ttt{\$gmlcode\_bg}, ' // & '\ttt{?draw\_base}, \ttt{?draw\_piecewise}, \ttt{?fill\_curve}, ' // & '\ttt{?draw\_histogram}, \ttt{?draw\_errors}, \ttt{?draw\_symbols}, ' // & '\ttt{\$fill\_options}, \ttt{\$draw\_options}, \ttt{\$err\_options}, ' // & '\ttt{\$symbol})')) call var_list%append_log (var_str ("?draw_errors"), & intrinsic=.true., & description=var_str ("Settings for \whizard's internal graphics " // & 'output: flag that determines whether error bars should be drawn ' // & 'or not. (cf. also \ttt{?normalize\_bins}, \ttt{\$obs\_label}, ' // & '\ttt{\$obs\_unit}, \ttt{\$title}, \ttt{\$description}, \ttt{\$x\_label}, ' // & '\ttt{\$y\_label}, \ttt{graph\_width\_mm}, \ttt{graph\_height\_mm}, ' // & '\ttt{?y\_log}, \ttt{?x\_log}, \ttt{x\_min}, \ttt{x\_max}, \ttt{y\_min}, ' // & '\ttt{y\_max}, \ttt{\$gmlcode\_fg}, \ttt{\$gmlcode\_bg}, \ttt{?draw\_base}, ' // & '\ttt{?draw\_piecewise}, \ttt{?fill\_curve}, \ttt{?draw\_histogram}, ' // & '\ttt{?draw\_curve}, \ttt{?draw\_symbols}, \ttt{\$fill\_options}, ' // & '\newline \ttt{\$draw\_options}, \ttt{\$err\_options}, \ttt{\$symbol})')) call var_list%append_log (var_str ("?draw_symbols"), & intrinsic=.true., & description=var_str ("Settings for \whizard's internal graphics " // & 'output: flag that determines whether particular symbols (specified ' // & 'by $\to$ \ttt{\$symbol = "{\em }"}) should be ' // & 'used for plotting data points (cf. also \ttt{?normalize\_bins}, ' // & '\ttt{\$obs\_label}, \ttt{\$obs\_unit}, \ttt{\$title}, \ttt{\$description}, ' // & '\ttt{\$x\_label}, \ttt{\$y\_label}, \ttt{graph\_width\_mm}, ' // & '\ttt{graph\_height\_mm}, \ttt{?y\_log}, \ttt{?x\_log}, \ttt{x\_min}, ' // & '\ttt{x\_max}, \ttt{y\_min}, \ttt{y\_max}, \ttt{\$gmlcode\_fg}, ' // & '\ttt{\$gmlcode\_bg}, \ttt{?draw\_base}, \ttt{?draw\_piecewise}, ' // & '\ttt{?fill\_curve}, \ttt{?draw\_histogram}, \ttt{?draw\_curve}, ' // & '\ttt{?draw\_errors}, \ttt{\$fill\_options}, \ttt{\$draw\_options}, ' // & '\newline \ttt{\$err\_options}, \ttt{\$symbol})')) call var_list%append_string (var_str ("$fill_options"), & intrinsic=.true., & description=var_str ("Settings for \whizard's internal graphics " // & 'output: \ttt{\$fill\_options = "{\em }"} is a ' // & 'string variable that allows to set fill options when plotting ' // & 'data as filled curves with the $\to$ \ttt{?fill\_curve} flag. ' // & 'For more details see the \gamelan\ manual. (cf. also \ttt{?normalize\_bins}, ' // & '\ttt{\$obs\_label}, \ttt{\$obs\_unit}, \ttt{\$title}, \ttt{\$description}, ' // & '\ttt{\$x\_label}, \ttt{\$y\_label}, \ttt{graph\_width\_mm}, ' // & '\ttt{graph\_height\_mm}, \ttt{?y\_log}, \ttt{?x\_log}, \ttt{x\_min}, ' // & '\ttt{x\_max}, \ttt{y\_min}, \ttt{y\_max}, \ttt{\$gmlcode\_fg}, ' // & '\ttt{\$gmlcode\_bg}, \ttt{?draw\_base}, \ttt{?draw\_piecewise}, ' // & '\ttt{?draw\_curve}, \ttt{?draw\_histogram}, \ttt{?draw\_errors}, ' // & '\newline \ttt{?draw\_symbols}, \ttt{?fill\_curve}, \ttt{\$draw\_options}, ' // & '\ttt{\$err\_options}, \ttt{\$symbol})')) call var_list%append_string (var_str ("$draw_options"), & intrinsic=.true., & description=var_str ("Settings for \whizard's internal graphics " // & 'output: \ttt{\$draw\_options = "{\em }"} is a ' // & 'string variable that allows to set specific drawing options ' // & 'for plots and histograms. For more details see the \gamelan\ ' // & 'manual. (cf. also \ttt{?normalize\_bins}, \ttt{\$obs\_label}, ' // & '\ttt{\$obs\_unit}, \ttt{\$title}, \ttt{\$description}, \ttt{\$x\_label}, ' // & '\ttt{\$y\_label}, \ttt{graph\_width\_mm}, \ttt{graph\_height\_mm}, ' // & '\ttt{?y\_log}, \ttt{?x\_log}, \ttt{x\_min}, \ttt{x\_max}, \ttt{y\_min}, ' // & '\ttt{y\_max}, \ttt{\$gmlcode\_fg}, \ttt{\$gmlcode\_bg}, \ttt{?draw\_base}, ' // & '\newline \ttt{?draw\_piecewise}, \ttt{?fill\_curve}, \ttt{?draw\_histogram}, ' // & '\ttt{?draw\_errors}, \ttt{?draw\_symbols}, \newline \ttt{\$fill\_options}, ' // & '\ttt{?draw\_histogram}, \ttt{\$err\_options}, \ttt{\$symbol})')) call var_list%append_string (var_str ("$err_options"), & intrinsic=.true., & description=var_str ("Settings for \whizard's internal graphics " // & 'output: \ttt{\$err\_options = "{\em }"} is a string ' // & 'variable that allows to set specific drawing options for errors ' // & 'in plots and histograms. For more details see the \gamelan\ ' // & 'manual. (cf. also \ttt{?normalize\_bins}, \ttt{\$obs\_label}, ' // & '\ttt{\$obs\_unit}, \ttt{\$title}, \ttt{\$description}, \ttt{\$x\_label}, ' // & '\ttt{\$y\_label}, \ttt{graph\_width\_mm}, \ttt{graph\_height\_mm}, ' // & '\ttt{?y\_log}, \ttt{?x\_log}, \ttt{x\_min}, \ttt{x\_max}, \ttt{y\_min}, ' // & '\ttt{y\_max}, \ttt{\$gmlcode\_fg}, \ttt{\$gmlcode\_bg}, \ttt{?draw\_base}, ' // & '\ttt{?draw\_piecewise}, \ttt{?fill\_curve}, \ttt{?draw\_histogram}, ' // & '\ttt{?draw\_errors}, \newline \ttt{?draw\_symbols}, \ttt{\$fill\_options}, ' // & '\ttt{?draw\_histogram}, \ttt{\$draw\_options}, \ttt{\$symbol})')) call var_list%append_string (var_str ("$symbol"), & intrinsic=.true., & description=var_str ("Settings for \whizard's internal graphics " // & 'output: \ttt{\$symbol = "{\em }"} is a string ' // & 'variable for the symbols that should be used for plotting data ' // & 'points. (cf. also \ttt{\$obs\_label}, \ttt{?normalize\_bins}, ' // & '\ttt{\$obs\_unit}, \ttt{\$title}, \ttt{\$description}, \ttt{\$x\_label}, ' // & '\ttt{\$y\_label}, \newline \ttt{graph\_width\_mm}, \ttt{graph\_height\_mm}, ' // & '\ttt{?y\_log}, \ttt{?x\_log}, \ttt{x\_min}, \ttt{x\_max}, \ttt{y\_min}, ' // & '\ttt{y\_max}, \newline \ttt{\$gmlcode\_fg}, \ttt{\$gmlcode\_bg}, ' // & '\ttt{?draw\_base}, \ttt{?draw\_piecewise}, \ttt{?fill\_curve}, ' // & '\newline \ttt{?draw\_histogram}, \ttt{?draw\_curve}, \ttt{?draw\_errors}, ' // & '\ttt{\$fill\_options}, \ttt{\$draw\_options}, \newline \ttt{\$err\_options}, ' // & '\ttt{?draw\_symbols})')) call var_list%append_log (& var_str ("?analysis_file_only"), .false., & intrinsic=.true., & description=var_str ('Allows to specify that only \LaTeX\ files ' // & "for \whizard's graphical analysis are written out, but not processed. " // & '(cf. \ttt{compile\_analysis}, \ttt{write\_analysis})')) end subroutine var_list_set_gamelan_defaults @ %def var_list_set_gamelan_defaults @ FastJet parameters and friends <>= procedure :: set_clustering_defaults => var_list_set_clustering_defaults <>= subroutine var_list_set_clustering_defaults (var_list) class(var_list_t), intent(inout) :: var_list call var_list%append_int (& var_str ("kt_algorithm"), & kt_algorithm, & intrinsic = .true., locked = .true., & description=var_str ('Specifies a jet algorithm for the ($\to$) ' // & '\ttt{jet\_algorithm} command, used in the ($\to$) \ttt{cluster} ' // & 'subevent function. At the moment only available for the ' // & 'interfaced external \fastjet\ package. (cf. also ' // & '\ttt{cambridge\_[for\_passive\_]algorithm}, ' // & '\ttt{plugin\_algorithm}, ' // & '\newline\ttt{genkt\_[for\_passive\_]algorithm}, ' // & '\ttt{ee\_[gen]kt\_algorithm}, \ttt{jet\_r})')) call var_list%append_int (& var_str ("cambridge_algorithm"), & cambridge_algorithm, intrinsic = .true., locked = .true., & description=var_str ('Specifies a jet algorithm for the ($\to$) ' // & '\ttt{jet\_algorithm} command, used in the ($\to$) \ttt{cluster} ' // & 'subevent function. At the moment only available for the interfaced ' // & 'external \fastjet\ package. (cf. also \ttt{kt\_algorithm}, ' // & '\ttt{cambridge\_for\_passive\_algorithm}, \ttt{plugin\_algorithm}, ' // & '\ttt{genkt\_[for\_passive\_]algorithm}, \ttt{ee\_[gen]kt\_algorithm}, ' // & '\ttt{jet\_r})')) call var_list%append_int (& var_str ("antikt_algorithm"), & antikt_algorithm, & intrinsic = .true., locked = .true., & description=var_str ('Specifies a jet algorithm for the ($\to$) ' // & '\ttt{jet\_algorithm} command, used in the ($\to$) \ttt{cluster} ' // & 'subevent function. At the moment only available for the interfaced ' // & 'external \fastjet\ package. (cf. also \ttt{kt\_algorithm}, ' // & '\ttt{cambridge\_[for\_passive\_]algorithm}, \ttt{plugin\_algorithm}, ' // & '\ttt{genkt\_[for\_passive\_]algorithm}, \ttt{ee\_[gen]kt\_algorithm}, ' // & '\ttt{jet\_r})')) call var_list%append_int (& var_str ("genkt_algorithm"), & genkt_algorithm, & intrinsic = .true., locked = .true., & description=var_str ('Specifies a jet algorithm for the ($\to$) ' // & '\ttt{jet\_algorithm} command, used in the ($\to$) \ttt{cluster} ' // & 'subevent function. At the moment only available for the interfaced ' // & 'external \fastjet\ package. (cf. also \ttt{kt\_algorithm}, ' // & '\ttt{cambridge\_for\_passive\_algorithm}, \ttt{plugin\_algorithm}, ' // & '\ttt{genkt\_for\_passive\_algorithm}, \ttt{ee\_[gen]kt\_algorithm}, ' // & '\ttt{jet\_r})')) call var_list%append_int (& var_str ("cambridge_for_passive_algorithm"), & cambridge_for_passive_algorithm, & intrinsic = .true., locked = .true., & description=var_str ('Specifies a jet algorithm for the ($\to$) ' // & '\ttt{jet\_algorithm} command, used in the ($\to$) \ttt{cluster} ' // & 'subevent function. At the moment only available for the interfaced ' // & 'external \fastjet\ package. (cf. also \ttt{kt\_algorithm}, ' // & '\ttt{cambridge\_algorithm}, \ttt{plugin\_algorithm}, \newline ' // & '\ttt{genkt\_[for\_passive\_]algorithm}, \ttt{ee\_[gen]kt\_algorithm}, ' // & '\ttt{jet\_r})')) call var_list%append_int (& var_str ("genkt_for_passive_algorithm"), & genkt_for_passive_algorithm, & intrinsic = .true., locked = .true., & description=var_str ('Specifies a jet algorithm for the ($\to$) ' // & '\ttt{jet\_algorithm} command, used in the ($\to$) \ttt{cluster} ' // & 'subevent function. At the moment only available for the interfaced ' // & 'external \fastjet\ package. (cf. also \ttt{kt\_algorithm}, ' // & '\ttt{cambridge\_for\_passive\_algorithm}, \ttt{plugin\_algorithm}, ' // & '\ttt{genkt\_algorithm}, \ttt{ee\_[gen]kt\_algorithm}, \ttt{jet\_r})')) call var_list%append_int (& var_str ("ee_kt_algorithm"), & ee_kt_algorithm, & intrinsic = .true., locked = .true., & description=var_str ('Specifies a jet algorithm for the ($\to$) ' // & '\ttt{jet\_algorithm} command, used in the ($\to$) \ttt{cluster} ' // & 'subevent function. At the moment only available for the interfaced ' // & 'external \fastjet\ package. (cf. also \ttt{kt\_algorithm}, ' // & '\ttt{cambridge\_[for\_passive\_]algorithm}, \ttt{plugin\_algorithm}, ' // & '\ttt{genkt\_[for\_passive\_]algorithm}, \ttt{ee\_genkt\_algorithm}, ' // & '\ttt{jet\_r})')) call var_list%append_int (& var_str ("ee_genkt_algorithm"), & ee_genkt_algorithm, & intrinsic = .true., locked = .true., & description=var_str ('Specifies a jet algorithm for the ($\to$) ' // & '\ttt{jet\_algorithm} command, used in the ($\to$) \ttt{cluster} ' // & 'subevent function. At the moment only available for the interfaced ' // & 'external \fastjet\ package. (cf. also \ttt{kt\_algorithm}, ' // & '\ttt{cambridge\_[for\_passive\_]algorithm}, \ttt{plugin\_algorithm}, ' // & '\ttt{genkt\_[for\_passive\_]algorithm}, \ttt{ee\_kt\_algorithm}, ' // & '\ttt{jet\_r})')) call var_list%append_int (& var_str ("plugin_algorithm"), & plugin_algorithm, & intrinsic = .true., locked = .true., & description=var_str ('Specifies a jet algorithm for the ($\to$) ' // & '\ttt{jet\_algorithm} command, used in the ($\to$) \ttt{cluster} ' // & 'subevent function. At the moment only available for the interfaced ' // & 'external \fastjet\ package. (cf. also \ttt{kt\_algorithm}, ' // & '\ttt{cambridge\_for\_passive\_algorithm}, \newline ' // & '\ttt{genkt\_[for\_passive\_]algorithm}, \ttt{ee\_[gen]kt\_algorithm}, ' // & '\ttt{jet\_r})')) call var_list%append_int (& var_str ("undefined_jet_algorithm"), & undefined_jet_algorithm, & intrinsic = .true., locked = .true., & description=var_str ('This is just a place holder for any kind of jet ' // & 'jet algorithm that is not further specified. (cf. also \ttt{kt\_algorithm}, ' // & '\ttt{cambridge\_for\_passive\_algorithm}, \newline ' // & '\ttt{genkt\_[for\_passive\_]algorithm}, \ttt{ee\_[gen]kt\_algorithm}, ' // & '\ttt{jet\_r}, \ttt{plugin\_algorithm})')) call var_list%append_int (& var_str ("jet_algorithm"), undefined_jet_algorithm, & intrinsic = .true., & description=var_str ('Variable that allows to set the type of ' // & 'jet algorithm when using the external \fastjet\ library. It ' // & 'accepts one of the following algorithms: ($\to$) \ttt{kt\_algorithm}, ' // & '\newline ($\to$) \ttt{cambridge\_[for\_passive\_]algorithm}, ' // & '($\to$) \ttt{antikt\_algorithm}, ($\to$) \ttt{plugin\_algorithm}, ' // & '($\to$) \ttt{genkt\_[for\_passive\_]algorithm}, ($\to$) ' // & '\ttt{ee\_[gen]kt\_algorithm}). (cf. also \ttt{cluster}, ' // & '\ttt{jet\_p}, \ttt{jet\_r}, \ttt{jet\_ycut})')) call var_list%append_real (& var_str ("jet_r"), 0._default, & intrinsic = .true., & description=var_str ('Value for the distance measure $R$ used in ' // & 'the (non-Cambridge) algorithms that are available via the interface ' // & 'to the \fastjet\ package. (cf. also \ttt{cluster}, \ttt{combine}, ' // & '\ttt{jet\_algorithm}, \ttt{kt\_algorithm}, ' // & '\ttt{cambridge\_[for\_passive\_]algorithm}, \ttt{antikt\_algorithm}, ' // & '\newline \ttt{plugin\_algorithm}, \ttt{genkt\_[for\_passive\_]algorithm}, ' // & '\ttt{ee\_[gen]kt\_algorithm}, \ttt{jet\_p}, \newline\ttt{jet\_ycut})')) call var_list%append_real (& var_str ("jet_p"), 0._default, & intrinsic = .true., & description=var_str ('Value for the exponent of the distance measure $R$ in ' // & 'the generalized $k_T$ algorithms that are available via the interface ' // & 'to the \fastjet\ package. (cf. also \ttt{cluster}, \ttt{combine}, ' // & '\ttt{jet\_algorithm}, \ttt{kt\_algorithm}, ' // & '\ttt{cambridge\_[for\_passive\_]algorithm}, \ttt{antikt\_algorithm}, ' // & '\newline \ttt{plugin\_algorithm}, \ttt{genkt\_[for\_passive\_]algorithm}, ' // & '\ttt{ee\_[gen]kt\_algorithm}, \ttt{jet\_r}, \newline\ttt{jet\_ycut})')) call var_list%append_real (& var_str ("jet_ycut"), 0._default, & intrinsic = .true., & description=var_str ('Value for the $y$ separation measure used in ' // & 'the Cambridge-Aachen algorithms that are available via the interface ' // & 'to the \fastjet\ package. (cf. also \ttt{cluster}, \ttt{combine}, ' // & '\ttt{kt\_algorithm}, \ttt{jet\_algorithm}, ' // & '\ttt{cambridge\_[for\_passive\_]algorithm}, \ttt{antikt\_algorithm}, ' // & '\newline \ttt{plugin\_algorithm}, \ttt{genkt\_[for\_passive\_]algorithm}, ' // & '\ttt{ee\_[gen]kt\_algorithm}, \ttt{jet\_p}, \newline\ttt{jet\_r})')) call var_list%append_log (& var_str ("?keep_flavors_when_clustering"), .false., & intrinsic = .true., & description=var_str ('The logical variable \ttt{?keep\_flavors\_when\_clustering ' // & '= true/false} specifies whether the flavor of a jet should be ' // & 'kept during \ttt{cluster} when a jet consists of one quark and ' // & 'zero or more gluons. Especially useful for cuts on b-tagged ' // & 'jets (cf. also \ttt{cluster}).')) end subroutine var_list_set_clustering_defaults @ %def var_list_set_clustering_defaults @ Frixione isolation parameters and all that: <>= procedure :: set_isolation_defaults => var_list_set_isolation_defaults <>= subroutine var_list_set_isolation_defaults (var_list) class(var_list_t), intent(inout) :: var_list call var_list%append_real (var_str ("photon_iso_eps"), 1._default, & intrinsic=.true., & description=var_str ('Photon isolation parameter $\epsilon_\gamma$ ' // & '(energy fraction) from hep-ph/9801442 (cf. also ' // & '\ttt{photon\_iso\_n}, \ttt{photon\_iso\_r0})')) call var_list%append_real (var_str ("photon_iso_n"), 1._default, & intrinsic=.true., & description=var_str ('Photon isolation parameter $n$ ' // & '(cone function exponent) from hep-ph/9801442 (cf. also ' // & '\ttt{photon\_iso\_eps}, \ttt{photon\_iso\_r0})')) call var_list%append_real (var_str ("photon_iso_r0"), 0.4_default, & intrinsic=.true., & description=var_str ('Photon isolation parameter $R_0^\gamma$ ' // & '(isolation cone radius) from hep-ph/9801442 (cf. also ' // & '\ttt{photon\_iso\_eps}, \ttt{photon\_iso\_n})')) end subroutine var_list_set_isolation_defaults @ %def var_list_set_isolation_defaults <>= procedure :: set_eio_defaults => var_list_set_eio_defaults <>= subroutine var_list_set_eio_defaults (var_list) class(var_list_t), intent(inout) :: var_list call var_list%append_string (var_str ("$sample"), var_str (""), & intrinsic=.true., & description=var_str ('String variable to set the (base) name ' // & 'of the event output format, e.g. \ttt{\$sample = "foo"} will ' // & 'result in an intrinsic binary format event file \ttt{foo.evx}. ' // & '(cf. also \ttt{sample\_format}, \ttt{simulate}, \ttt{hepevt}, ' // & '\ttt{ascii}, \ttt{athena}, \ttt{debug}, \ttt{long}, \ttt{short}, ' // & '\ttt{hepmc}, \ttt{lhef}, \ttt{lha}, \ttt{stdhep}, \ttt{stdhep\_up}, ' // & '\ttt{\$sample\_normalization}, \ttt{?sample\_pacify}, \ttt{sample\_max\_tries})')) call var_list%append_string (var_str ("$sample_normalization"), var_str ("auto"),& intrinsic=.true., & description=var_str ('String variable that allows to set the ' // & 'normalization of generated events. There are four options: ' // & 'option \ttt{"1"} (events normalized to one), \ttt{"1/n"} (sum ' // & 'of all events in a sample normalized to one), \ttt{"sigma"} ' // & '(events normalized to the cross section of the process), and ' // & '\ttt{"sigma/n"} (sum of all events normalized to the cross ' // & 'section). The default is \ttt{"auto"} where unweighted events ' // & 'are normalized to one, and weighted ones to the cross section. ' // & '(cf. also \ttt{simulate}, \ttt{\$sample}, \ttt{sample\_format}, ' // & '\ttt{?sample\_pacify}, \ttt{sample\_max\_tries}, \ttt{sample\_split\_n\_evt}, ' // & '\ttt{sample\_split\_n\_kbytes})')) call var_list%append_log (var_str ("?sample_pacify"), .false., & intrinsic=.true., & description=var_str ('Flag, mainly for debugging purposes: suppresses ' // & 'numerical noise in the output of a simulation. (cf. also \ttt{simulate}, ' // & '\ttt{\$sample}, \ttt{sample\_format}, \ttt{\$sample\_normalization}, ' // & '\ttt{sample\_max\_tries}, \ttt{sample\_split\_n\_evt}, ' // & '\ttt{sample\_split\_n\_kbytes})')) call var_list%append_log (var_str ("?sample_select"), .true., & intrinsic=.true., & description=var_str ('Logical that determines whether a selection should ' // & 'be applied to the output event format or not. If set to \ttt{false} a ' // & 'selection is only considered for the evaluation of observables. (cf. ' // & '\ttt{select}, \ttt{selection}, \ttt{analysis})')) call var_list%append_int (var_str ("sample_max_tries"), 10000, & intrinsic = .true., & description=var_str ('Integer variable that sets the maximal ' // & 'number of tries for generating a single event. The event might ' // & 'be vetoed because of a very low unweighting efficiency, errors ' // & 'in the event transforms like decays, shower, matching, hadronization ' // & 'etc. (cf. also \ttt{simulate}, \ttt{\$sample}, \ttt{sample\_format}, ' // & '\ttt{?sample\_pacify}, \ttt{\$sample\_normalization}, ' // & '\ttt{sample\_split\_n\_evt}, \newline\ttt{sample\_split\_n\_kbytes})')) call var_list%append_int (var_str ("sample_split_n_evt"), 0, & intrinsic = .true., & description=var_str ('When generating events, this integer parameter ' // & '\ttt{sample\_split\_n\_evt = {\em }} gives the number \ttt{{\em ' // & '}} of breakpoints in the event files, i.e. it splits the ' // & 'event files into \ttt{{\em } + 1} parts. The parts are ' // & 'denoted by \ttt{{\em }.{\em }.{\em ' // & '}}. Here, \ttt{{\em }} is an integer ' // & 'running from \ttt{0} to \ttt{{\em }}. The start can be ' // & 'reset by ($\to$) \ttt{sample\_split\_index}. (cf. also \ttt{simulate}, ' // & '\ttt{\$sample}, \ttt{sample\_format}, \ttt{sample\_max\_tries}, ' // & '\ttt{\$sample\_normalization}, \ttt{?sample\_pacify}, ' // & '\ttt{sample\_split\_n\_kbytes})')) call var_list%append_int (var_str ("sample_split_n_kbytes"), 0, & intrinsic = .true., & description=var_str ('When generating events, this integer parameter ' // & '\ttt{sample\_split\_n\_kbytes = {\em }} limits the file ' // & 'size of event files. Whenever an event file has exceeded this ' // & 'size, counted in kilobytes, the following events will be written ' // & 'to a new file. The naming conventions are the same as for ' // & '\ttt{sample\_split\_n\_evt}. (cf. also \ttt{simulate}, \ttt{\$sample}, ' // & '\ttt{sample\_format}, \ttt{sample\_max\_tries}, \ttt{\$sample\_normalization}, ' // & '\ttt{?sample\_pacify})')) call var_list%append_int (var_str ("sample_split_index"), 0, & intrinsic = .true., & description=var_str ('Integer number that gives the starting ' // & 'index \ttt{sample\_split\_index = {\em }} for ' // & 'the numbering of event samples \ttt{{\em }.{\em ' // & '}.{\em }} split by the \ttt{sample\_split\_n\_evt ' // & '= {\em }}. The index runs from \ttt{{\em }} ' // & 'to \newline \ttt{{\em } + {\em }}. (cf. also \ttt{simulate}, ' // & '\ttt{\$sample}, \ttt{sample\_format}, \newline\ttt{\$sample\_normalization}, ' // & '\ttt{sample\_max\_tries}, \ttt{?sample\_pacify})')) call var_list%append_string (var_str ("$rescan_input_format"), var_str ("raw"), & intrinsic=.true., & description=var_str ('String variable that allows to set the ' // & 'event format of the event file that is to be rescanned by the ' // & '($\to$) \ttt{rescan} command.')) call var_list%append_log (var_str ("?read_raw"), .true., & intrinsic=.true., & description=var_str ('This flag demands \whizard\ to (try to) ' // & 'read events (from the internal binary format) first before ' // & 'generating new ones. (cf. \ttt{simulate}, \ttt{?write\_raw}, ' // & '\ttt{\$sample}, \ttt{sample\_format})')) call var_list%append_log (var_str ("?write_raw"), .true., & intrinsic=.true., & description=var_str ("Flag to write out events in \whizard's " // & 'internal binary format. (cf. \ttt{simulate}, \ttt{?read\_raw}, ' // & '\ttt{sample\_format}, \ttt{\$sample})')) call var_list%append_string (var_str ("$extension_raw"), var_str ("evx"), & intrinsic=.true., & description=var_str ('String variable that allows via \ttt{\$extension\_raw ' // & '= "{\em }"} to specify the suffix for the file \ttt{name.suffix} ' // & "to which events in \whizard's internal format are written. If " // & 'not set, the default file name and suffix is \ttt{{\em }.evx}. ' // & '(cf. also \ttt{sample\_format}, \ttt{\$sample})')) call var_list%append_string (var_str ("$extension_default"), var_str ("evt"), & intrinsic=.true., & description=var_str ('String variable that allows via \ttt{\$extension\_default ' // & '= "{\em }"} to specify the suffix for the file \ttt{name.suffix} ' // & 'to which events in a the standard \whizard\ verbose ASCII format ' // & 'are written. If not set, the default file name and suffix is ' // & '\ttt{{\em }.evt}. (cf. also \ttt{sample\_format}, ' // & '\ttt{\$sample})')) call var_list%append_string (var_str ("$debug_extension"), var_str ("debug"), & intrinsic=.true., & description=var_str ('String variable that allows via \ttt{\$debug\_extension ' // & '= "{\em }"} to specify the suffix for the file \ttt{name.suffix} ' // & 'to which events in a long verbose format with debugging information ' // & 'are written. If not set, the default file name and suffix is ' // & '\ttt{{\em }.debug}. (cf. also \ttt{sample\_format}, ' // & '\ttt{\$sample}, \ttt{?debug\_process}, \ttt{?debug\_transforms}, ' // & '\ttt{?debug\_decay}, \ttt{?debug\_verbose})')) call var_list%append_log (var_str ("?debug_process"), .true., & intrinsic=.true., & description=var_str ('Flag that decides whether process information ' // & 'will be displayed in the ASCII debug event format ($\to$) \ttt{debug}. ' // & '(cf. also \ttt{sample\_format}, \ttt{\$sample}, \ttt{\$debug\_extension}, ' // & '\ttt{?debug\_decay}, \ttt{?debug\_transforms}, \ttt{?debug\_verbose})')) call var_list%append_log (var_str ("?debug_transforms"), .true., & intrinsic=.true., & description=var_str ('Flag that decides whether information ' // & 'about event transforms will be displayed in the ASCII debug ' // & 'event format ($\to$) \ttt{debug}. (cf. also \ttt{sample\_format}, ' // & '\ttt{\$sample}, \ttt{?debug\_decay}, \ttt{\$debug\_extension}, ' // & '\ttt{?debug\_process}, \ttt{?debug\_verbose})')) call var_list%append_log (var_str ("?debug_decay"), .true., & intrinsic=.true., & description=var_str ('Flag that decides whether decay information ' // & 'will be displayed in the ASCII debug event format ($\to$) \ttt{debug}. ' // & '(cf. also \ttt{sample\_format}, \ttt{\$sample}, \ttt{\$debug\_extension}, ' // & '\ttt{?debug\_process}, \ttt{?debug\_transforms}, \ttt{?debug\_verbose})')) call var_list%append_log (var_str ("?debug_verbose"), .true., & intrinsic=.true., & description=var_str ('Flag that decides whether extensive verbose ' // & 'information will be included in the ASCII debug event format ' // & '($\to$) \ttt{debug}. (cf. also \ttt{sample\_format}, \ttt{\$sample}, ' // & '\ttt{\$debug\_extension}, \ttt{?debug\_decay}, \ttt{?debug\_transforms}, ' // & '\ttt{?debug\_process})')) call var_list%append_string (var_str ("$dump_extension"), var_str ("pset.dat"), & intrinsic=.true., & description=var_str ('String variable that allows via \ttt{\$dump\_extension ' // & '= "{\em }"} to specify the suffix for the file \ttt{name.suffix} ' // & "to which events in \whizard's internal particle set format " // & 'are written. If not set, the default file name and suffix is ' // & '\ttt{{\em }.pset.dat}. (cf. also \ttt{sample\_format}, ' // & '\ttt{\$sample}, \ttt{dump}, \ttt{?dump\_compressed}, ' // & '\ttt{?dump\_screen}, \ttt{?dump\_summary}, \ttt{?dump\_weights})')) call var_list%append_log (var_str ("?dump_compressed"), .false., & intrinsic=.true., & description=var_str ('Flag that, if set to \ttt{true}, issues ' // & 'a very compressed and clear version of the \ttt{dump} ($\to$) ' // & 'event format. (cf. also \ttt{sample\_format}, ' // & '\ttt{\$sample}, \ttt{dump}, \ttt{\$dump\_extension}, ' // & '\ttt{?dump\_screen}, \ttt{?dump\_summary}, \ttt{?dump\_weights})')) call var_list%append_log (var_str ("?dump_weights"), .false., & intrinsic=.true., & description=var_str ('Flag that, if set to \ttt{true}, includes ' // & 'cross sections, weights and excess in the \ttt{dump} ($\to$) ' // & 'event format. (cf. also \ttt{sample\_format}, ' // & '\ttt{\$sample}, \ttt{dump}, \ttt{?dump\_compressed}, ' // & '\ttt{\$dump\_extension}, \ttt{?dump\_screen}, \ttt{?dump\_summary})')) call var_list%append_log (var_str ("?dump_summary"), .false., & intrinsic=.true., & description=var_str ('Flag that, if set to \ttt{true}, includes ' // & 'a summary with momentum sums for incoming and outgoing particles ' // & 'as well as for beam remnants in the \ttt{dump} ($\to$) ' // & 'event format. (cf. also \ttt{sample\_format}, ' // & '\ttt{\$sample}, \ttt{dump}, \ttt{?dump\_compressed}, ' // & '\ttt{\$dump\_extension}, \ttt{?dump\_screen}, \ttt{?dump\_weights})')) call var_list%append_log (var_str ("?dump_screen"), .false., & intrinsic=.true., & description=var_str ('Flag that, if set to \ttt{true}, outputs ' // & 'events for the \ttt{dump} ($\to$) event format on screen ' // & ' instead of to a file. (cf. also \ttt{sample\_format}, ' // & '\ttt{\$sample}, \ttt{dump}, \ttt{?dump\_compressed}, ' // & '\ttt{\$dump\_extension}, \ttt{?dump\_summary}, \ttt{?dump\_weights})')) call var_list%append_log (var_str ("?hepevt_ensure_order"), .false., & intrinsic=.true., & description=var_str ('Flag to ensure that the particle set confirms ' // & 'the HEPEVT standard. This involves some copying and reordering ' // & 'to guarantee that mothers and daughters are always next to ' // & 'each other. Usually this is not necessary.')) call var_list%append_string (var_str ("$extension_hepevt"), var_str ("hepevt"), & intrinsic=.true., & description=var_str ('String variable that allows via \ttt{\$extension\_hepevt ' // & '= "{\em }"} to specify the suffix for the file \ttt{name.suffix} ' // & 'to which events in the \whizard\ version 1 style HEPEVT ASCII ' // & 'format are written. If not set, the default file name and suffix ' // & 'is \ttt{{\em }.hepevt}. (cf. also \ttt{sample\_format}, ' // & '\ttt{\$sample})')) call var_list%append_string (var_str ("$extension_ascii_short"), & var_str ("short.evt"), intrinsic=.true., & description=var_str ('String variable that allows via \ttt{\$extension\_ascii\_short ' // & '= "{\em }"} to specify the suffix for the file \ttt{name.suffix} ' // & 'to which events in the so called short variant of the \whizard\ ' // & 'version 1 style HEPEVT ASCII format are written. If not set, ' // & 'the default file name and suffix is \ttt{{\em }.short.evt}. ' // & '(cf. also \ttt{sample\_format}, \ttt{\$sample})')) call var_list%append_string (var_str ("$extension_ascii_long"), & var_str ("long.evt"), intrinsic=.true., & description=var_str ('String variable that allows via \ttt{\$extension\_ascii\_long ' // & '= "{\em }"} to specify the suffix for the file \ttt{name.suffix} ' // & 'to which events in the so called long variant of the \whizard\ ' // & 'version 1 style HEPEVT ASCII format are written. If not set, ' // & 'the default file name and suffix is \ttt{{\em }.long.evt}. ' // & '(cf. also \ttt{sample\_format}, \ttt{\$sample})')) call var_list%append_string (var_str ("$extension_athena"), & var_str ("athena.evt"), intrinsic=.true., & description=var_str ('String variable that allows via \ttt{\$extension\_athena ' // & '= "{\em }"} to specify the suffix for the file \ttt{name.suffix} ' // & 'to which events in the ATHENA file format are written. If not ' // & 'set, the default file name and suffix is \ttt{{\em }.athena.evt}. ' // & '(cf. also \ttt{sample\_format}, \ttt{\$sample})')) call var_list%append_string (var_str ("$extension_mokka"), & var_str ("mokka.evt"), intrinsic=.true., & description=var_str ('String variable that allows via \ttt{\$extension\_mokka ' // & '= "{\em }"} to specify the suffix for the file \ttt{name.suffix} ' // & 'to which events in the MOKKA format are written. If not set, ' // & 'the default file name and suffix is \ttt{{\em }.mokka.evt}. ' // & '(cf. also \ttt{sample\_format}, \ttt{\$sample})')) call var_list%append_string (var_str ("$lhef_version"), var_str ("2.0"), & intrinsic = .true., & description=var_str ('Specifier for the Les Houches Accord (LHEF) ' // & 'event format files with XML headers to discriminate among different ' // & 'versions of this format. (cf. also \ttt{\$sample}, \ttt{sample\_format}, ' // & '\ttt{lhef}, \ttt{\$lhef\_extension}, \ttt{\$lhef\_extension}, ' // & '\ttt{?lhef\_write\_sqme\_prc}, \ttt{?lhef\_write\_sqme\_ref}, ' // & '\ttt{?lhef\_write\_sqme\_alt})')) call var_list%append_string (var_str ("$lhef_extension"), var_str ("lhe"), & intrinsic=.true., & description=var_str ('String variable that allows via \ttt{\$lhef\_extension ' // & '= "{\em }"} to specify the suffix for the file \ttt{name.suffix} ' // & 'to which events in the LHEF format are written. If not set, ' // & 'the default file name and suffix is \ttt{{\em }.lhe}. ' // & '(cf. also \ttt{sample\_format}, \ttt{\$sample}, \ttt{lhef}, ' // & '\ttt{\$lhef\_extension}, \ttt{\$lhef\_version}, \ttt{?lhef\_write\_sqme\_prc}, ' // & '\ttt{?lhef\_write\_sqme\_ref}, \ttt{?lhef\_write\_sqme\_alt})')) call var_list%append_log (var_str ("?lhef_write_sqme_prc"), .true., & intrinsic = .true., & description=var_str ('Flag that decides whether in the ($\to$) ' // & '\ttt{lhef} event format the weights of the squared matrix element ' // & 'of the corresponding process shall be written in the LHE file. ' // & '(cf. also \ttt{\$sample}, \ttt{sample\_format}, \ttt{lhef}, ' // & '\ttt{\$lhef\_extension}, \ttt{\$lhef\_extension}, \ttt{?lhef\_write\_sqme\_ref}, ' // & '\newline \ttt{?lhef\_write\_sqme\_alt})')) call var_list%append_log (var_str ("?lhef_write_sqme_ref"), .false., & intrinsic = .true., & description=var_str ('Flag that decides whether in the ($\to$) ' // & '\ttt{lhef} event format reference weights of the squared matrix ' // & 'element shall be written in the LHE file. (cf. also \ttt{\$sample}, ' // & '\ttt{sample\_format}, \ttt{lhef}, \ttt{\$lhef\_extension}, \ttt{\$lhef\_extension}, ' // & '\ttt{?lhef\_write\_sqme\_prc}, \ttt{?lhef\_write\_sqme\_alt})')) call var_list%append_log (var_str ("?lhef_write_sqme_alt"), .true., & intrinsic = .true., & description=var_str ('Flag that decides whether in the ($\to$) ' // & '\ttt{lhef} event format alternative weights of the squared matrix ' // & 'element shall be written in the LHE file. (cf. also \ttt{\$sample}, ' // & '\ttt{sample\_format}, \ttt{lhef}, \ttt{\$lhef\_extension}, \ttt{\$lhef\_extension}, ' // & '\ttt{?lhef\_write\_sqme\_prc}, \ttt{?lhef\_write\_sqme\_ref})')) call var_list%append_string (var_str ("$extension_lha"), var_str ("lha"), & intrinsic=.true., & description=var_str ('String variable that allows via \ttt{\$extension\_lha ' // & '= "{\em }"} to specify the suffix for the file \ttt{name.suffix} ' // & 'to which events in the (deprecated) LHA format are written. ' // & 'If not set, the default file name and suffix is \ttt{{\em }.lha}. ' // & '(cf. also \ttt{sample\_format}, \ttt{\$sample})')) call var_list%append_string (var_str ("$extension_hepmc"), var_str ("hepmc"), & intrinsic=.true., & description=var_str ('String variable that allows via \ttt{\$extension\_hepmc ' // & '= "{\em }"} to specify the suffix for the file \ttt{name.suffix} ' // & 'to which events in the HepMC format are written. If not set, ' // & 'the default file name and suffix is \ttt{{\em }.hepmc}. ' // & '(cf. also \ttt{sample\_format}, \ttt{\$sample})')) call var_list%append_log (var_str ("?hepmc_output_cross_section"), .false., & intrinsic = .true., & description=var_str ('Flag for the HepMC event format that allows ' // & 'to write out the cross section (and error) from the integration ' // & 'together with each HepMC event. This can be used by programs ' // & 'like Rivet to scale histograms according to the cross section. ' // & '(cf. also \ttt{hepmc})')) call var_list%append_string (var_str ("$hepmc3_mode"), var_str ("HepMC3"), & intrinsic = .true., & description=var_str ('This specifies the writer mode for HepMC3. ' // & 'Possible values are \ttt{HepMC2}, \ttt{HepMC3} (default), ' // & '\ttt{HepEVT}, \ttt{Root}. and \ttt{RootTree} (cf. also \ttt{hepmc})')) call var_list%append_string (var_str ("$extension_lcio"), var_str ("slcio"), & intrinsic=.true., & description=var_str ('String variable that allows via \ttt{\$extension\_lcio ' // & '= "{\em }"} to specify the suffix for the file \ttt{name.suffix} ' // & 'to which events in the LCIO format are written. If not set, ' // & 'the default file name and suffix is \ttt{{\em }.slcio}. ' // & '(cf. also \ttt{sample\_format}, \ttt{\$sample})')) call var_list%append_string (var_str ("$extension_stdhep"), var_str ("hep"), & intrinsic=.true., & description=var_str ('String variable that allows via \ttt{\$extension\_stdhep ' // & '= "{\em }"} to specify the suffix for the file \ttt{name.suffix} ' // & 'to which events in the StdHEP format via the HEPEVT common ' // & 'block are written. If not set, the default file name and suffix ' // & 'is \ttt{{\em }.hep}. (cf. also \ttt{sample\_format}, ' // & '\ttt{\$sample})')) call var_list%append_string (var_str ("$extension_stdhep_up"), & var_str ("up.hep"), intrinsic=.true., & description=var_str ('String variable that allows via \ttt{\$extension\_stdhep\_up ' // & '= "{\em }"} to specify the suffix for the file \ttt{name.suffix} ' // & 'to which events in the StdHEP format via the HEPRUP/HEPEUP ' // & 'common blocks are written. \ttt{{\em }.up.hep} ' // & 'is the default file name and suffix, if this variable not set. ' // & '(cf. also \ttt{sample\_format}, \ttt{\$sample})')) call var_list%append_string (var_str ("$extension_stdhep_ev4"), & var_str ("ev4.hep"), intrinsic=.true., & description=var_str ('String variable that allows via \ttt{\$extension\_stdhep\_ev4 ' // & '= "{\em }"} to specify the suffix for the file \ttt{name.suffix} ' // & 'to which events in the StdHEP format via the HEPEVT/HEPEV4 ' // & 'common blocks are written. \ttt{{\em }.up.hep} ' // & 'is the default file name and suffix, if this variable not set. ' // & '(cf. also \ttt{sample\_format}, \ttt{\$sample})')) call var_list%append_string (var_str ("$extension_hepevt_verb"), & var_str ("hepevt.verb"), intrinsic=.true., & description=var_str ('String variable that allows via \ttt{\$extension\_hepevt\_verb ' // & '= "{\em }"} to specify the suffix for the file \ttt{name.suffix} ' // & 'to which events in the \whizard\ version 1 style extended or ' // & 'verbose HEPEVT ASCII format are written. If not set, the default ' // & 'file name and suffix is \ttt{{\em }.hepevt.verb}. ' // & '(cf. also \ttt{sample\_format}, \ttt{\$sample})')) call var_list%append_string (var_str ("$extension_lha_verb"), & var_str ("lha.verb"), intrinsic=.true., & description=var_str ('String variable that allows via \ttt{\$extension\_lha\_verb ' // & '= "{\em }"} to specify the suffix for the file \ttt{name.suffix} ' // & 'to which events in the (deprecated) extended or verbose LHA ' // & 'format are written. If not set, the default file name and suffix ' // & 'is \ttt{{\em }.lha.verb}. (cf. also \ttt{sample\_format}, ' // & '\ttt{\$sample})')) end subroutine var_list_set_eio_defaults @ %def var_list_set_eio_defaults @ <>= procedure :: set_shower_defaults => var_list_set_shower_defaults <>= subroutine var_list_set_shower_defaults (var_list) class(var_list_t), intent(inout) :: var_list call var_list%append_log (var_str ("?allow_shower"), .true., & intrinsic=.true., & description=var_str ('Master flag to switch on (initial and ' // & 'final state) parton shower, matching/merging as an event ' // & 'transform. As a default, it is switched on. (cf. also \ttt{?ps\_ ' // & '....}, \ttt{\$ps\_ ...}, \ttt{?mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_log (var_str ("?ps_fsr_active"), .false., & intrinsic=.true., & description=var_str ('Flag that switches final-state QCD radiation ' // & '(FSR) on. (cf. also \ttt{?allow\_shower}, \ttt{?ps\_ ...}, ' // & '\ttt{\$ps\_ ...}, \ttt{?mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_log (var_str ("?ps_isr_active"), .false., & intrinsic=.true., & description=var_str ('Flag that switches initial-state QCD ' // & 'radiation (ISR) on. (cf. also \ttt{?allow\_shower}, \ttt{?ps\_ ' // & '...}, \ttt{\$ps\_ ...}, \ttt{?mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_log (var_str ("?ps_taudec_active"), .false., & intrinsic=.true., & description=var_str ('Flag to switch on $\tau$ decays, at ' // & 'the moment only via the included external package \ttt{TAUOLA} ' // & 'and \ttt{PHOTOS}. (cf. also \ttt{?allow\_shower}, \ttt{?ps\_ ' // & '...}, \ttt{\$ps\_ ...}, \ttt{?mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_log (var_str ("?muli_active"), .false., & intrinsic=.true., & description=var_str ("Master flag that switches on \whizard's " // & 'module for multiple interaction with interleaved QCD parton ' // & 'showers for hadron colliders. Note that this feature is still ' // & 'experimental. (cf. also \ttt{?allow\_shower}, \ttt{?ps\_ ' // & '...}, \ttt{\$ps\_ ...}, \ttt{?mlm\_ ...})')) call var_list%append_string (var_str ("$shower_method"), var_str ("WHIZARD"), & intrinsic=.true., & description=var_str ('String variable that allows to specify ' // & 'which parton shower is being used, the default, \ttt{"WHIZARD"}, ' // & 'is one of the in-house showers of \whizard. Other possibilities ' // & 'at the moment are only \ttt{"PYTHIA6"}.')) call var_list%append_log (var_str ("?shower_verbose"), .false., & intrinsic=.true., & description=var_str ('Flag to switch on verbose messages when ' // & 'using shower and/or hadronization. (cf. also \ttt{?allow\_shower}, ' // & '\ttt{?ps\_ ...}, \ttt{\$ps\_ ...}, \ttt{?mlm\_ ...},')) call var_list%append_string (var_str ("$ps_PYTHIA_PYGIVE"), var_str (""), & intrinsic=.true., & description=var_str ('String variable that allows to pass options ' // & 'for tunes etc. to the attached \pythia\ parton shower or hadronization, ' // & 'e.g.: \ttt{\$ps\_PYTHIA\_PYGIVE = "MSTJ(41)=1"}. (cf. also ' // & '\newline \ttt{?allow\_shower}, \ttt{?ps\_ ...}, \ttt{\$ps\_ ' // & '...}, \ttt{?mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_string (var_str ("$ps_PYTHIA8_config"), var_str (""), & intrinsic=.true., & description=var_str ('String variable that allows to pass options ' // & 'for tunes etc. to the attached \pythia\ttt{8} parton shower or hadronization, ' // & 'e.g.: \ttt{\$ps\_PYTHIA8\_config = "PartonLevel:MPI = off"}. (cf. also ' // & '\newline \ttt{?allow\_shower}, \ttt{?ps\_ ...}, \ttt{\$ps\_ ' // & '...}, \ttt{?mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_string (var_str ("$ps_PYTHIA8_config_file"), var_str (""), & intrinsic=.true., & description=var_str ('String variable that allows to pass a filename to a ' // & '\pythia\ttt{8} configuration file.')) call var_list%append_real (& var_str ("ps_mass_cutoff"), 1._default, intrinsic = .true., & description=var_str ('Real value that sets the QCD parton shower ' // & 'lower cutoff scale, where hadronization sets in. (cf. also \ttt{?allow\_shower}, ' // & '\ttt{?ps\_ ...}, \ttt{\$ps\_ ...}, \ttt{?mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_real (& var_str ("ps_fsr_lambda"), 0.29_default, intrinsic = .true., & description=var_str ('By this real parameter, the value of $\Lambda_{QCD}$ ' // & 'used in running $\alpha_s$ for time-like showers is set (except ' // & 'for showers in the decay of a resonance). (cf. also \ttt{?allow\_shower}, ' // & '\ttt{?ps\_ ...}, \ttt{\$ps\_ ...}, \ttt{?mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_real (& var_str ("ps_isr_lambda"), 0.29_default, intrinsic = .true., & description=var_str ('By this real parameter, the value of $\Lambda_{QCD}$ ' // & 'used in running $\alpha_s$ for space-like showers is set. (cf. ' // & 'also \ttt{?allow\_shower}, \ttt{?ps\_ ...}, \ttt{\$ps\_ ...}, ' // & '\ttt{?mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_int (& var_str ("ps_max_n_flavors"), 5, intrinsic = .true., & description=var_str ('This integer parameter sets the maxmimum ' // & 'number of flavors that can be produced in a QCD shower $g\to ' // & 'q\bar q$. It is also used as the maximal number of active flavors ' // & 'for the running of $\alpha_s$ in the shower (with a minimum ' // & 'of 3). (cf. also \ttt{?allow\_shower}, \ttt{?ps\_ ...}, \ttt{\$ps\_ ' // & '...}, \ttt{?mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_log (var_str ("?ps_isr_alphas_running"), .true., & intrinsic=.true., & description=var_str ('Flag that decides whether a running ' // & '$\alpha_s$ is taken in space-like QCD parton showers. (cf. ' // & 'also \ttt{?allow\_shower}, \ttt{?ps\_ ...}, \ttt{\$ps\_ ...}, ' // & '\ttt{?mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_log (var_str ("?ps_fsr_alphas_running"), .true., & intrinsic=.true., & description=var_str ('Flag that decides whether a running ' // & '$\alpha_s$ is taken in time-like QCD parton showers. (cf. ' // & 'also \ttt{?allow\_shower}, \ttt{?ps\_ ...}, \ttt{\$ps\_ ...}, ' // & '\ttt{?mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_real (var_str ("ps_fixed_alphas"), & 0._default, intrinsic = .true., & description=var_str ('This real parameter sets the value of $\alpha_s$ ' // & 'if it is (cf. $\to$ \ttt{?ps\_isr\_alphas\_running}, \newline ' // & '\ttt{?ps\_fsr\_alphas\_running}) not running in initial and/or ' // & 'final-state QCD showers. (cf. also \ttt{?allow\_shower}, \ttt{?ps\_ ' // & '...}, \ttt{\$ps\_ ...}, \ttt{?mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_log (var_str ("?ps_isr_pt_ordered"), .false., & intrinsic=.true., & description=var_str ('By this flag, it can be switched between ' // & 'the analytic QCD ISR shower (\ttt{false}, default) and the ' // & '$p_T$ ISR QCD shower (\ttt{true}). (cf. also \ttt{?allow\_shower}, ' // & '\ttt{?ps\_ ...}, \ttt{\$ps\_ ...}, \ttt{?mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_log (var_str ("?ps_isr_angular_ordered"), .true., & intrinsic=.true., & description=var_str ('If switched one, this flag forces opening ' // & 'angles of emitted partons in the QCD ISR shower to be strictly ' // & 'ordered, i.e. increasing towards the hard interaction. (cf. ' // & 'also \ttt{?allow\_shower}, \ttt{?ps\_ ...}, \ttt{\$ps\_ ...}, ' // & '\ttt{?mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_real (var_str & ("ps_isr_primordial_kt_width"), 0._default, intrinsic = .true., & description=var_str ('This real parameter sets the width $\sigma ' // & '= \braket{k_T^2}$ for the Gaussian primordial $k_T$ distribution ' // & 'inside the hadron, given by: $\exp[-k_T^2/\sigma^2] k_T dk_T$. ' // & '(cf. also \ttt{?allow\_shower}, \ttt{?ps\_ ...}, \ttt{\$ps\_ ' // & '...}, \ttt{?mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_real (var_str & ("ps_isr_primordial_kt_cutoff"), 5._default, intrinsic = .true., & description=var_str ('Real parameter that sets the upper cutoff ' // & 'for the primordial $k_T$ distribution inside a hadron. (cf. ' // & 'also \ttt{?allow\_shower}, \ttt{?ps\_ ...}, \ttt{\$ps\_ ...}, ' // & '\ttt{?hadronization\_active}, \ttt{?mlm\_ ...})')) call var_list%append_real (var_str & ("ps_isr_z_cutoff"), 0.999_default, intrinsic = .true., & description=var_str ('This real parameter allows to set the upper ' // & 'cutoff on the splitting variable $z$ in space-like QCD parton ' // & 'showers. (cf. also \ttt{?allow\_shower}, \ttt{?ps\_ ...}, ' // & '\ttt{\$ps\_ ...}, \ttt{?mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_real (var_str & ("ps_isr_minenergy"), 1._default, intrinsic = .true., & description=var_str ('By this real parameter, the minimal effective ' // & 'energy (in the c.m. frame) of a time-like or on-shell-emitted ' // & 'parton in a space-like QCD shower is set. For a hard subprocess ' // & 'that is not in the rest frame, this number is roughly reduced ' // & 'by a boost factor $1/\gamma$ to the rest frame of the hard scattering ' // & 'process. (cf. also \ttt{?allow\_shower}, \ttt{?ps\_ ...}, ' // & '\ttt{\$ps\_ ...}, \ttt{?mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_real (var_str & ("ps_isr_tscalefactor"), 1._default, intrinsic = .true., & description=var_str ('The $Q^2$ scale of the hard scattering ' // & 'process is multiplied by this real factor to define the maximum ' // & 'parton virtuality allowed in time-like QCD showers. This does ' // & 'only apply to $t$- and $u$-channels, while for $s$-channel resonances ' // & 'the maximum virtuality is set by $m^2$. (cf. also \ttt{?allow\_shower}, ' // & '\ttt{?ps\_ ...}, \ttt{\$ps\_ ...}, \ttt{?mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_log (var_str & ("?ps_isr_only_onshell_emitted_partons"), .false., intrinsic=.true., & description=var_str ('This flag if set true sets all emitted ' // & 'partons off space-like showers on-shell, i.e. it would not allow ' // & 'associated time-like showers. (cf. also \ttt{?allow\_shower}, ' // & '\ttt{?ps\_ ...}, \ttt{\$ps\_ ...}, \ttt{?mlm\_ ...}, \ttt{?hadronization\_active})')) end subroutine var_list_set_shower_defaults @ %def var_list_set_shower_defaults @ <>= procedure :: set_hadronization_defaults => var_list_set_hadronization_defaults <>= subroutine var_list_set_hadronization_defaults (var_list) class(var_list_t), intent(inout) :: var_list call var_list%append_log & (var_str ("?allow_hadronization"), .true., intrinsic=.true., & description=var_str ('Master flag to switch on hadronization ' // & 'as an event transform. As a default, it is switched on. (cf. ' // & 'also \ttt{?ps\_ ....}, \ttt{\$ps\_ ...}, \ttt{?mlm\_ ...}, ' // & '\ttt{?hadronization\_active})')) call var_list%append_log & (var_str ("?hadronization_active"), .false., intrinsic=.true., & description=var_str ('Master flag to switch hadronization (through ' // & 'the attached \pythia\ package) on or off. As a default, it is ' // & 'off. (cf. also \ttt{?allow\_shower}, \ttt{?ps\_ ...}, \ttt{\$ps\_ ' // & '...}, \ttt{?mlm\_ ...})')) call var_list%append_string & (var_str ("$hadronization_method"), var_str ("PYTHIA6"), intrinsic = .true., & description=var_str ("Determines whether \whizard's own " // & "hadronization or the (internally included) \pythiasix\ should be used.")) call var_list%append_real & (var_str ("hadron_enhanced_fraction"), 0.01_default, intrinsic = .true., & description=var_str ('Fraction of Lund strings that break with enhanced ' // & 'width. [not yet active]')) call var_list%append_real & (var_str ("hadron_enhanced_width"), 2.0_default, intrinsic = .true., & description=var_str ('Enhancement factor for the width of breaking ' // & 'Lund strings. [not yet active]')) end subroutine var_list_set_hadronization_defaults @ %def var_list_set_hadronization_defaults @ <>= procedure :: set_tauola_defaults => var_list_set_tauola_defaults <>= subroutine var_list_set_tauola_defaults (var_list) class(var_list_t), intent(inout) :: var_list call var_list%append_log (& var_str ("?ps_tauola_photos"), .false., intrinsic=.true., & description=var_str ('Flag to switch on \ttt{PHOTOS} for photon ' // & 'showering inside the \ttt{TAUOLA} package. (cf. also \ttt{?allow\_shower}, ' // & '\ttt{?ps\_ ...}, \ttt{\$ps\_ ...}, \ttt{?mlm\_ ...}, \ttt{?ps\_taudec\_active})')) call var_list%append_log (& var_str ("?ps_tauola_transverse"), .false., intrinsic=.true., & description=var_str ('Flag to switch transverse $\tau$ polarization ' // & 'on or off for Higgs decays into $\tau$ leptons. (cf. also \ttt{?allow\_shower}, ' // & '\ttt{?ps\_ ...}, \ttt{\$ps\_ ...}, \ttt{?mlm\_ ...}, \ttt{?ps\_taudec\_active})')) call var_list%append_log (& var_str ("?ps_tauola_dec_rad_cor"), .true., intrinsic=.true., & description=var_str ('Flag to switch radiative corrections for ' // & '$\tau$ decays in \ttt{TAUOLA} on or off. (cf. also \ttt{?allow\_shower}, ' // & '\ttt{?ps\_ ...}, \ttt{\$ps\_ ...}, \ttt{?mlm\_ ...}, \ttt{?ps\_taudec\_active})')) call var_list%append_int (& var_str ("ps_tauola_dec_mode1"), 0, intrinsic = .true., & description=var_str ('Integer code to request a specific $\tau$ ' // & 'decay within \ttt{TAUOLA} for the decaying $\tau$, and -- ' // & 'in correlated decays -- for the second $\tau$. For more information ' // & 'cf. the comments in the code or the \ttt{TAUOLA} manual. ' // & '(cf. also \ttt{?allow\_shower}, \ttt{?ps\_ ...}, \ttt{\$ps\_ ' // & '...}, \ttt{?mlm\_ ...}, \ttt{?ps\_taudec\_active})')) call var_list%append_int (& var_str ("ps_tauola_dec_mode2"), 0, intrinsic = .true., & description=var_str ('Integer code to request a specific $\tau$ ' // & 'decay within \ttt{TAUOLA} for the decaying $\tau$, and -- ' // & 'in correlated decays -- for the second $\tau$. For more information ' // & 'cf. the comments in the code or the \ttt{TAUOLA} manual. ' // & '(cf. also \ttt{?allow\_shower}, \ttt{?ps\_ ...}, \ttt{\$ps\_ ' // & '...}, \ttt{?mlm\_ ...}, \ttt{?ps\_taudec\_active})')) call var_list%append_real (& var_str ("ps_tauola_mh"), 125._default, intrinsic = .true., & description=var_str ('Real option to set the Higgs mass for Higgs ' // & 'decays into $\tau$ leptons in the interface to \ttt{TAUOLA}. ' // & '(cf. also \ttt{?allow\_shower}, \ttt{?ps\_ ...}, \ttt{\$ps\_ ' // & '...}, \ttt{?mlm\_ ...}, \ttt{?ps\_taudec\_active})')) call var_list%append_real (& var_str ("ps_tauola_mix_angle"), 90._default, intrinsic = .true., & description=var_str ('Option to set the mixing angle between ' // & 'scalar and pseudoscalar Higgs bosons for Higgs decays into $\tau$ ' // & 'leptons in the interface to \ttt{TAUOLA}. (cf. also \ttt{?allow\_shower}, ' // & '\ttt{?ps\_ ...}, \ttt{\$ps\_ ...}, \ttt{?mlm\_ ...}, \ttt{?ps\_taudec\_active})')) call var_list%append_log (& var_str ("?ps_tauola_pol_vector"), .false., intrinsic = .true., & description=var_str ('Flag to decide whether for transverse $\tau$ ' // & 'polarization, polarization information should be taken from ' // & '\ttt{TAUOLA} or not. The default is just based on random numbers. ' // & '(cf. also \ttt{?allow\_shower}, \ttt{?ps\_ ...}, \ttt{\$ps\_ ' // & '...}, \ttt{?mlm\_ ...}, \ttt{?ps\_taudec\_active})')) end subroutine var_list_set_tauola_defaults @ %def var_list_set_tauola_defaults @ <>= procedure :: set_mlm_matching_defaults => var_list_set_mlm_matching_defaults <>= subroutine var_list_set_mlm_matching_defaults (var_list) class(var_list_t), intent(inout) :: var_list call var_list%append_log (var_str ("?mlm_matching"), .false., & intrinsic=.true., & description=var_str ('Master flag to switch on MLM (LO) jet ' // & 'matching between hard matrix elements and the QCD parton ' // & 'shower. (cf. also \ttt{?allow\_shower}, \ttt{?ps\_ ...}, ' // & '\ttt{\$ps\_ ...}, \ttt{mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_real (var_str & ("mlm_Qcut_ME"), 0._default, intrinsic = .true., & description=var_str ('Real parameter that in the MLM jet matching ' // & 'between hard matrix elements and QCD parton shower sets a possible ' // & 'virtuality cut on jets from the hard matrix element. (cf. also ' // & '\ttt{?allow\_shower}, \ttt{?ps\_ ...}, \ttt{\$ps\_ ...}, \ttt{mlm\_ ' // & '...}, \ttt{?hadronization\_active})')) call var_list%append_real (var_str & ("mlm_Qcut_PS"), 0._default, intrinsic = .true., & description=var_str ('Real parameter that in the MLM jet matching ' // & 'between hard matrix elements and QCD parton shower sets a possible ' // & 'virtuality cut on jets from the parton shower. (cf. also \ttt{?allow\_shower}, ' // & '\ttt{?ps\_ ...}, \ttt{\$ps\_ ...}, \ttt{mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_real (var_str & ("mlm_ptmin"), 0._default, intrinsic = .true., & description=var_str ('This real parameter sets a minimal $p_T$ ' // & 'that enters the $y_{cut}$ jet clustering measure in the MLM ' // & 'jet matching between hard matrix elements and QCD parton showers. ' // & '(cf. also \ttt{?allow\_shower}, \ttt{?ps\_ ...}, \ttt{\$ps\_ ' // & '...}, \ttt{mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_real (var_str & ("mlm_etamax"), 0._default, intrinsic = .true., & description=var_str ('This real parameter sets a maximal pseudorapidity ' // & 'that enters the MLM jet matching between hard matrix elements ' // & 'and QCD parton showers. (cf. also \ttt{?allow\_shower}, \ttt{?ps\_ ' // & '...}, \ttt{\$ps\_ ...}, \ttt{mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_real (var_str & ("mlm_Rmin"), 0._default, intrinsic = .true., & description=var_str ('Real parameter that sets a minimal $R$ ' // & 'distance value that enters the $y_{cut}$ jet clustering measure ' // & 'in the MLM jet matching between hard matrix elements and QCD ' // & 'parton showers. (cf. also \ttt{?allow\_shower}, \ttt{?ps\_ ' // & '...}, \ttt{\$ps\_ ...}, \ttt{mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_real (var_str & ("mlm_Emin"), 0._default, intrinsic = .true., & description=var_str ('Real parameter that sets a minimal energy ' // & '$E_{min}$ value as an infrared cutoff in the MLM jet matching ' // & 'between hard matrix elements and QCD parton showers. (cf. also ' // & '\ttt{?allow\_shower}, \ttt{?ps\_ ...}, \ttt{\$ps\_ ...}, \ttt{mlm\_ ' // & '...}, \ttt{?hadronization\_active})')) call var_list%append_int (var_str & ("mlm_nmaxMEjets"), 0, intrinsic = .true., & description=var_str ('This integer sets the maximal number of ' // & 'jets that are available from hard matrix elements in the MLM ' // & 'jet matching between hard matrix elements and QCD parton shower. ' // & '(cf. also \ttt{?allow\_shower}, \ttt{?ps\_ ...}, \ttt{\$ps\_ ' // & '...}, \ttt{mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_real (var_str & ("mlm_ETclusfactor"), 0.2_default, intrinsic = .true., & description=var_str ('This real parameter is a factor that enters ' // & 'the calculation of the $y_{cut}$ measure for jet clustering ' // & 'after the parton shower in the MLM jet matching between hard ' // & 'matrix elements and QCD parton showers. (cf. also \ttt{?allow\_shower}, ' // & '\ttt{?ps\_ ...}, \ttt{\$ps\_ ...}, \ttt{mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_real (var_str & ("mlm_ETclusminE"), 5._default, intrinsic = .true., & description=var_str ('This real parameter is a minimal energy ' // & 'that enters the calculation of the $y_{cut}$ measure for jet ' // & 'clustering after the parton shower in the MLM jet matching between ' // & 'hard matrix elements and QCD parton showers. (cf. also \ttt{?allow\_shower}, ' // & '\ttt{?ps\_ ...}, \ttt{\$ps\_ ...}, \ttt{mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_real (var_str & ("mlm_etaclusfactor"), 1._default, intrinsic = .true., & description=var_str ('This real parameter is a factor that enters ' // & 'the calculation of the $y_{cut}$ measure for jet clustering ' // & 'after the parton shower in the MLM jet matching between hard ' // & 'matrix elements and QCD parton showers. (cf. also \ttt{?allow\_shower}, ' // & '\ttt{?ps\_ ...}, \ttt{\$ps\_ ...}, \ttt{mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_real (var_str & ("mlm_Rclusfactor"), 1._default, intrinsic = .true., & description=var_str ('This real parameter is a factor that enters ' // & 'the calculation of the $y_{cut}$ measure for jet clustering ' // & 'after the parton shower in the MLM jet matching between hard ' // & 'matrix elements and QCD parton showers. (cf. also \ttt{?allow\_shower}, ' // & '\ttt{?ps\_ ...}, \ttt{\$ps\_ ...}, \ttt{mlm\_ ...}, \ttt{?hadronization\_active})')) call var_list%append_real (var_str & ("mlm_Eclusfactor"), 1._default, intrinsic = .true., & description=var_str ('This real parameter is a factor that enters ' // & 'the calculation of the $y_{cut}$ measure for jet clustering ' // & 'after the parton shower in the MLM jet matching between hard ' // & 'matrix elements and QCD parton showers. (cf. also \ttt{?allow\_shower}, ' // & '\ttt{?ps\_ ...}, \ttt{\$ps\_ ...}, \ttt{mlm\_ ...}, \ttt{?hadronization\_active})')) end subroutine var_list_set_mlm_matching_defaults @ %def var_list_set_mlm_matching_defaults @ <>= procedure :: set_powheg_matching_defaults => & var_list_set_powheg_matching_defaults <>= subroutine var_list_set_powheg_matching_defaults (var_list) class(var_list_t), intent(inout) :: var_list call var_list%append_log (var_str ("?powheg_matching"), & .false., intrinsic = .true., & description=var_str ('Activates Powheg matching. Needs to be ' // & 'combined with the \ttt{?combined\_nlo\_integration}-method.')) call var_list%append_log (var_str ("?powheg_use_singular_jacobian"), & .false., intrinsic = .true., & description=var_str ('This allows to give a different ' // & 'normalization of the Jacobian, resulting in an alternative ' // & 'POWHEG damping in the singular regions.')) call var_list%append_int (var_str ("powheg_grid_size_xi"), & 5, intrinsic = .true., & description=var_str ('Number of $\xi$ points in the POWHEG grid.')) call var_list%append_int (var_str ("powheg_grid_size_y"), & 5, intrinsic = .true., & description=var_str ('Number of $y$ points in the POWHEG grid.')) call var_list%append_int (var_str ("powheg_grid_sampling_points"), & 500000, intrinsic = .true., & description=var_str ('Number of calls used to initialize the ' // & 'POWHEG grid.')) call var_list%append_real (var_str ("powheg_pt_min"), & 1._default, intrinsic = .true., & description=var_str ('Lower $p_T$-cut-off for the POWHEG ' // & 'hardest emission.')) call var_list%append_real (var_str ("powheg_lambda"), & LAMBDA_QCD_REF, intrinsic = .true., & description=var_str ('Reference scale of the $\alpha_s$ evolution ' // & 'in the POWHEG matching algorithm.')) call var_list%append_log (var_str ("?powheg_rebuild_grids"), & .false., intrinsic = .true., & description=var_str ('If set to \ttt{true}, the existing POWHEG ' // & 'grid is discarded and a new one is generated.')) call var_list%append_log (var_str ("?powheg_test_sudakov"), & .false., intrinsic = .true., & description=var_str ('Performs an internal consistency check ' // & 'on the POWHEG event generation.')) call var_list%append_log (var_str ("?powheg_disable_sudakov"), & .false., intrinsic = .true., & description=var_str ('This flag allows to set the Sudakov form ' // & 'factor to one. This effectively results in a version of ' // & 'the matrix-element method (MEM) at NLO.')) end subroutine var_list_set_powheg_matching_defaults @ %def var_list_set_powheg_matching_defaults @ <>= procedure :: set_openmp_defaults => var_list_set_openmp_defaults <>= subroutine var_list_set_openmp_defaults (var_list) class(var_list_t), intent(inout) :: var_list call var_list%append_log (var_str ("?omega_openmp"), & openmp_is_active (), & intrinsic=.true., & description=var_str ('Flag to switch on or off OpenMP multi-threading ' // & "for \oMega\ matrix elements. (cf. also \ttt{\$method}, \ttt{\$omega\_flag})")) call var_list%append_log (var_str ("?openmp_is_active"), & openmp_is_active (), & locked=.true., intrinsic=.true., & description=var_str ('Flag to switch on or off OpenMP multi-threading ' // & 'for \whizard. (cf. also \ttt{?openmp\_logging}, \ttt{openmp\_num\_threads}, ' // & '\ttt{openmp\_num\_threads\_default}, \ttt{?omega\_openmp})')) call var_list%append_int (var_str ("openmp_num_threads_default"), & openmp_get_default_max_threads (), & locked=.true., intrinsic=.true., & description=var_str ('Integer parameter that shows the number ' // & 'of default OpenMP threads for multi-threading. Note that this ' // & 'parameter can only be accessed, but not reset by the user. (cf. ' // & 'also \ttt{?openmp\_logging}, \ttt{openmp\_num\_threads}, \ttt{?omega\_openmp})')) call var_list%append_int (var_str ("openmp_num_threads"), & openmp_get_max_threads (), & intrinsic=.true., & description=var_str ('Integer parameter that sets the number ' // & 'of OpenMP threads for multi-threading. (cf. also \ttt{?openmp\_logging}, ' // & '\ttt{openmp\_num\_threads\_default}, \ttt{?omega\_openmp})')) call var_list%append_log (var_str ("?openmp_logging"), & .true., intrinsic=.true., & description=var_str ('This logical -- when set to \ttt{false} ' // & '-- suppresses writing out messages about OpenMP parallelization ' // & '(number of used threads etc.) on screen and into the logfile ' // & '(default name \ttt{whizard.log}) for the whole \whizard\ run. ' // & 'Mainly for debugging purposes. (cf. also \ttt{?logging}, ' // & '\ttt{?mpi\_logging})')) end subroutine var_list_set_openmp_defaults @ %def var_list_set_openmp_defaults @ <>= procedure :: set_mpi_defaults => var_list_set_mpi_defaults <>= subroutine var_list_set_mpi_defaults (var_list) class(var_list_t), intent(inout) :: var_list call var_list%append_log (var_str ("?mpi_logging"), & .false., intrinsic=.true., & description=var_str('This logical -- when set to \ttt{false} ' // & '-- suppresses writing out messages about MPI parallelization ' // & '(number of used workers etc.) on screen and into the logfile ' // & '(default name \ttt{whizard.log}) for the whole \whizard\ run. ' // & 'Mainly for debugging purposes. (cf. also \ttt{?logging}, ' // & '\ttt{?openmp\_logging})')) end subroutine var_list_set_mpi_defaults @ %def var_list_set_mpi_defaults @ <>= procedure :: set_nlo_defaults => var_list_set_nlo_defaults <>= subroutine var_list_set_nlo_defaults (var_list) class(var_list_t), intent(inout) :: var_list call var_list%append_string (var_str ("$born_me_method"), & var_str (""), intrinsic = .true., & description=var_str ("This string variable specifies the method " // & "for the matrix elements to be used in the evaluation of the " // & "Born part of the NLO computation. The default is the empty string, " // & "i.e. the \ttt{\$method} being the intrinsic \oMega\ matrix element " // & 'generator (\ttt{"omega"}), other options ' // & 'are: \ttt{"ovm"}, \ttt{"unit\_test"}, \ttt{"template"}, ' // & '\ttt{"template\_unity"}, \ttt{"threshold"}, \ttt{"gosam"}, ' // & '\ttt{"openloops"}. Note that this option is inoperative if ' // & 'no NLO calculation is specified in the process definition. ' // & 'If you want ot use different matrix element methods in a LO ' // & 'computation, use the usual \ttt{method} command. (cf. also ' // & '\ttt{\$correlation\_me\_method}, ' // & '\ttt{\$dglap\_me\_method}, \ttt{\$loop\_me\_method} and ' // & '\ttt{\$real\_tree\_me\_method}.)')) call var_list%append_string (var_str ("$loop_me_method"), & var_str (""), intrinsic = .true., & description=var_str ('This string variable specifies the method ' // & 'for the matrix elements to be used in the evaluation of the ' // & 'virtual part of the NLO computation. The default is the empty string,' // & 'i.e. the same as \ttt{\$method}. Working options are: ' // & '\ttt{"threshold"}, \ttt{"openloops"}, \ttt{"recola"}, \ttt{gosam}. ' // & '(cf. also \ttt{\$real\_tree\_me\_method}, \ttt{\$correlation\_me\_method} ' // & 'and \ttt{\$born\_me\_method}.)')) call var_list%append_string (var_str ("$correlation_me_method"), & var_str (""), intrinsic = .true., & description=var_str ('This string variable specifies ' // & 'the method for the matrix elements to be used in the evaluation ' // & 'of the color (and helicity) correlated part of the NLO computation. ' // & "The default is the same as the \ttt{\$method}, i.e. the intrinsic " // & "\oMega\ matrix element generator " // & '(\ttt{"omega"}), other options are: \ttt{"ovm"}, \ttt{"unit\_test"}, ' // & '\ttt{"template"}, \ttt{"template\_unity"}, \ttt{"threshold"}, ' // & '\ttt{"gosam"}, \ttt{"openloops"}. (cf. also ' // & '\ttt{\$born\_me\_method}, \ttt{\$dglap\_me\_method}, ' // & '\ttt{\$loop\_me\_method} and \newline' // & '\ttt{\$real\_tree\_me\_method}.)')) call var_list%append_string (var_str ("$real_tree_me_method"), & var_str (""), intrinsic = .true., & description=var_str ('This string variable specifies the method ' // & 'for the matrix elements to be used in the evaluation of the ' // & 'real part of the NLO computation. The default is the same as ' // & 'the \ttt{\$method}, i.e. the intrinsic ' // & "\oMega\ matrix element generator " // & '(\ttt{"omega"}), other options ' // & 'are: \ttt{"ovm"}, \ttt{"unit\_test"}, \ttt{"template"}, \ttt{"template\_unity"}, ' // & '\ttt{"threshold"}, \ttt{"gosam"}, \ttt{"openloops"}. (cf. also ' // & '\ttt{\$born\_me\_method}, \ttt{\$correlation\_me\_method}, ' // & '\ttt{\$dglap\_me\_method} and \ttt{\$loop\_me\_method}.)')) call var_list%append_string (var_str ("$dglap_me_method"), & var_str (""), intrinsic = .true., & description=var_str ('This string variable specifies the method ' // & 'for the matrix elements to be used in the evaluation of the ' // & 'DGLAP remnants of the NLO computation. The default is the same as ' // & "\ttt{\$method}, i.e. the \oMega\ matrix element generator " // & '(\ttt{"omega"}), other options ' // & 'are: \ttt{"ovm"}, \ttt{"unit\_test"}, \ttt{"template"}, \ttt{"template\_unity"}, ' // & '\ttt{"threshold"}, \ttt{"gosam"}, \ttt{"openloops"}. (cf. also \newline' // & '\ttt{\$born\_me\_method}, \ttt{\$correlation\_me\_method}, ' // & '\ttt{\$loop\_me\_method} and \ttt{\$real\_tree\_me\_method}.)')) call var_list%append_log (& var_str ("?test_soft_limit"), .false., intrinsic = .true., & description=var_str ('Sets the fixed values $\tilde{\xi} = 0.00001$ ' // & 'and $y = 0.5$ as radiation variables. This way, only soft, ' // & 'but non-collinear phase space points are generated, which allows ' // & 'for testing subtraction in this region.')) call var_list%append_log (& var_str ("?test_coll_limit"), .false., intrinsic = .true., & description=var_str ('Sets the fixed values $\tilde{\xi} = 0.5$ ' // & 'and $y = 0.9999999$ as radiation variables. This way, only collinear, ' // & 'but non-soft phase space points are generated, which allows ' // & 'for testing subtraction in this region. Can be combined with ' // & '\ttt{?test\_soft\_limit} to probe soft-collinear regions.')) call var_list%append_log (& var_str ("?test_anti_coll_limit"), .false., intrinsic = .true., & description=var_str ('Sets the fixed values $\tilde{\xi} = 0.5$ ' // & 'and $y = -0.9999999$ as radiation variables. This way, only anti-collinear, ' // & 'but non-soft phase space points are generated, which allows ' // & 'for testing subtraction in this region. Can be combined with ' // & '\ttt{?test\_soft\_limit} to probe soft-collinear regions.')) call var_list%append_string (var_str ("$select_alpha_regions"), & var_str (""), intrinsic = .true., & description=var_str ('Fixes the $\alpha_r$ in the real ' // & ' subtraction component. Allows for testing in one individual ' // & 'singular region.')) call var_list%append_string (var_str ("$virtual_selection"), & var_str ("Full"), intrinsic = .true., & description=var_str ('String variable to select either the full ' // & 'or only parts of the virtual components of an NLO calculation. ' // & 'Possible modes are \ttt{"Full"}, \ttt{"OLP"} and ' // & '\ttt{"Subtraction."}. Mainly for debugging purposes.')) call var_list%append_log (var_str ("?virtual_collinear_resonance_aware"), & .true., intrinsic = .true., & description=var_str ('This flag allows to switch between two ' // & 'different implementations of the collinear subtraction in the ' // & 'resonance-aware FKS setup.')) call var_list%append_real (& var_str ("blha_top_yukawa"), -1._default, intrinsic = .true., & description=var_str ('If this value is set, the given value will ' // & 'be used as the top Yukawa coupling instead of the top mass. ' // & 'Note that having different values for $y_t$ and $m_t$ must be ' // & 'supported by your OLP-library and yield errors if this is not the case.')) call var_list%append_string (var_str ("$blha_ew_scheme"), & var_str ("alpha_internal"), intrinsic = .true., & description=var_str ('String variable that transfers the electroweak ' // & 'renormalization scheme via BLHA to the one-loop provider. Possible ' // & 'values are \ttt{GF} or \ttt{Gmu} for the $G_\mu$ scheme, ' // & '\ttt{alpha\_internal} (default, $G_\mu$ scheme, but value of ' // & '$\alpha_S$ calculated internally by \whizard), \ttt{alpha\_mz} ' // & 'and \ttt{alpha\_0} (or \ttt{alpha\_thompson}) for different schemes ' // & 'with $\alpha$ as input.')) call var_list%append_int (var_str ("openloops_verbosity"), 1, & intrinsic = .true., & description=var_str ('Decides how much \openloops\ output is printed. ' // & 'Can have values 0, 1 and 2, where 2 is the highest verbosity level.')) call var_list%append_log (var_str ("?openloops_use_cms"), & .true., intrinsic = .true., & description=var_str ('Activates the complex mass scheme in ' // & '\openloops. (cf. also ' // & '\ttt{openloos\_verbosity}, \ttt{\$method}, ' // & '\ttt{?openloops\_switch\_off\_muon\_yukawa}, ' // & '\ttt{openloops\_stability\_log}, \newline' // & '\ttt{\$openloops\_extra\_cmd})')) call var_list%append_int (var_str ("openloops_phs_tolerance"), 7, & intrinsic = .true., & description=var_str ('This integer parameter gives via ' // & '\ttt{openloops\_phs\_tolerance = } the relative numerical ' // & 'tolerance $10^{-n}$ for the momentum conservation of the ' // & 'external particles within \openloops. (cf. also ' // & '\ttt{openloos\_verbosity}, \ttt{\$method}, ' // & '\ttt{?openloops\_switch\_off\_muon\_yukawa}, ' // & '\newline\ttt{openloops\_stability\_log}, ' // & '\ttt{\$openloops\_extra\_cmd})')) call var_list%append_int (var_str ("openloops_stability_log"), 0, & intrinsic = .true., & description=var_str ('Creates the directory \ttt{stability\_log} ' // & 'containing information about the performance of the \openloops ' // & 'matrix elements. Possible values are 0 (No output), 1 (On ' // & '\ttt{finish()}-call), 2 (Adaptive) and 3 (Always).')) call var_list%append_log (var_str ("?openloops_switch_off_muon_yukawa"), & .false., intrinsic = .true., & description=var_str ('Sets the Yukawa coupling of muons for ' // & '\openloops\ to zero. (cf. also ' // & '\ttt{openloos\_verbosity}, \ttt{\$method}, ' // & '\ttt{?openloops\_use\_cms}, \ttt{openloops\_stability\_log}, ' // & '\ttt{\$openloops\_extra\_cmd})')) call var_list%append_string (var_str ("$openloops_extra_cmd"), & var_str (""), intrinsic = .true., & description=var_str ('String variable to transfer customized ' // & 'special commands to \openloops. The three supported examples ' // & '\ttt{\$openloops\_extra\_command = "extra approx top/stop/not"} ' // & 'are for selection of subdiagrams in top production. (cf. also ' // & '\ttt{\$method}, \ttt{openloos\_verbosity}, ' // & '\ttt{?openloops\_use\_cms}, \ttt{openloops\_stability\_log}, ' // & '\ttt{?openloops\_switch\_off\_muon\_yukawa})')) call var_list%append_real (var_str ("ellis_sexton_scale"), & -1._default, intrinsic = .true., & description = var_str ('Real positive paramter for the Ellis-Sexton scale' // & '$\mathcal{Q}$ used both in the finite one-loop contribution provided by' // & 'the OLP and in the virtual counter terms. The NLO cross section is' // & 'independend of $\mathcal{Q}$. Therefore, this allows for debugging of' // & 'the implemention of the virtual counter terms. As the default' // & '$\mathcal{Q} = \mu_{\rm{R}}$ is chosen. So far, setting this parameter' // & 'only works for OpenLoops2, otherwise the default behaviour is invoked.')) call var_list%append_log (var_str ("?disable_subtraction"), & .false., intrinsic = .true., & description=var_str ('Disables the subtraction of soft and collinear ' // & 'divergences from the real matrix element.')) call var_list%append_real (var_str ("fks_dij_exp1"), & 1._default, intrinsic = .true., & description=var_str ('Fine-tuning parameters of the FKS ' // & 'partition functions. The exact meaning depends on the mapping ' // & 'implementation. (cf. also \ttt{fks\_dij\_exp2}, ' // & '\ttt{\$fks\_mapping\_type}, \ttt{fks\_xi\_min}, \ttt{fks\_y\_max})')) call var_list%append_real (var_str ("fks_dij_exp2"), & 1._default, intrinsic = .true., & description=var_str ('Fine-tuning parameters of the FKS ' // & 'partition functions. The exact meaning depends on the mapping ' // & 'implementation. (cf. also \ttt{fks\_dij\_exp1}, ' // & '\ttt{\$fks\_mapping\_type}, \ttt{fks\_xi\_min}, \ttt{fks\_y\_max})')) call var_list%append_real (var_str ("fks_xi_min"), & 0.0000001_default, intrinsic = .true., & description=var_str ('Real parameter for the FKS ' // & 'phase space that sets the numerical lower value of the $\xi$ ' // & 'variable. (cf. also \ttt{fks\_dij\_exp1}, ' // & '\ttt{fks\_dij\_exp2}, \ttt{\$fks\_mapping\_type}, \ttt{fks\_y\_max})')) call var_list%append_real (var_str ("fks_y_max"), & 1._default, intrinsic = .true., & description=var_str ('Real parameter for the FKS ' // & 'phase space that sets the numerical upper value of the $y$ ' // & 'variable. (cf. also \ttt{fks\_dij\_exp1}, ' // & '\ttt{\$fks\_mapping\_type}, \ttt{fks\_dij\_exp2}, \ttt{fks\_y\_max})')) call var_list%append_log (var_str ("?vis_fks_regions"), & .false., intrinsic = .true., & description=var_str ('Logical variable that, if set to ' // & '\ttt{true}, generates \LaTeX\ code and executes it into a PDF ' // & ' to produce a table of all singular FKS regions and their ' // & ' flavor structures. The default is \ttt{false}.')) call var_list%append_real (var_str ("fks_xi_cut"), & 1.0_default, intrinsic = .true., & description = var_str ('Real paramter for the FKS ' // & 'phase space that applies a cut to $\xi$ variable with $0 < \xi_{\text{cut}}' // & '\leq \xi_{\text{max}}$. The dependence on the parameter vanishes between ' // & 'real subtraction and integrated subtraction term.')) call var_list%append_real (var_str ("fks_delta_o"), & 2._default, intrinsic = .true., & description = var_str ('Real paramter for the FKS ' // & 'phase space that applies a cut to the $y$ variable with $0 < \delta_o \leq 2$. ' // & 'The dependence on the parameter vanishes between real subtraction and integrated ' // & 'subtraction term.')) call var_list%append_real (var_str ("fks_delta_i"), & 2._default, intrinsic = .true., & description = var_str ('Real paramter for the FKS ' // & 'phase space that applies a cut to the $y$ variable with ' // & '$0 < \delta_{\mathrm{I}} \leq 2$ '// & 'for initial state singularities only. ' // & 'The dependence on the parameter vanishes between real subtraction and integrated ' // & 'subtraction term.')) call var_list%append_string (var_str ("$fks_mapping_type"), & var_str ("default"), intrinsic = .true., & description=var_str ('Sets the FKS mapping type. Possible values ' // & 'are \ttt{"default"} and \ttt{"resonances"}. The latter option ' // & 'activates the resonance-aware subtraction mode and induces the ' // & 'generation of a soft mismatch component. (cf. also ' // & '\ttt{fks\_dij\_exp1}, \ttt{fks\_dij\_exp2}, \ttt{fks\_xi\_min}, ' // & '\ttt{fks\_y\_max})')) call var_list%append_string (var_str ("$resonances_exclude_particles"), & var_str ("default"), intrinsic = .true., & description=var_str ('Accepts a string of particle names. These ' // & 'particles will be ignored when the resonance histories are generated. ' // & 'If \ttt{\$fks\_mapping\_type} is not \ttt{"resonances"}, this ' // & 'option does nothing.')) call var_list%append_int (var_str ("alpha_power"), & 2, intrinsic = .true., & description=var_str ('Fixes the electroweak coupling ' // & 'powers used by BLHA matrix element generators. Setting these ' // & 'values is necessary for the correct generation of OLP-files. ' // & 'Having inconsistent values yields to error messages by the corresponding ' // & 'OLP-providers.')) call var_list%append_int (var_str ("alphas_power"), & 0, intrinsic = .true., & description=var_str ('Fixes the strong coupling ' // & 'powers used by BLHA matrix element generators. Setting these ' // & 'values is necessary for the correct generation of OLP-files. ' // & 'Having inconsistent values yields to error messages by the corresponding ' // & 'OLP-providers.')) call var_list%append_log (var_str ("?combined_nlo_integration"), & .false., intrinsic = .true., & description=var_str ('When this option is set to \ttt{true}, ' // & 'the NLO integration will not be performed in the separate components, ' // & 'but instead the sum of all components will be integrated directly. ' // & 'When fixed-order NLO events are requested, this integration ' // & 'mode is possible, but not necessary. However, it is necessary ' // & 'for POWHEG events.')) call var_list%append_log (var_str ("?fixed_order_nlo_events"), & .false., intrinsic = .true., & description=var_str ('Induces the generation of fixed-order ' // & 'NLO events. Deprecated name: \ttt{?nlo\_fixed\_order}.')) call var_list%append_log (var_str ("?check_event_weights_against_xsection"), & .false., intrinsic = .true., & description=var_str ('Activates an internal recording of event ' // & 'weights when unweighted events are generated. At the end of ' // & 'the simulation, the mean value of the weights and its standard ' // & 'deviation are displayed. This allows to cross-check event generation ' // & 'and integration, because the value displayed must be equal to ' // & 'the integration result.')) call var_list%append_log (var_str ("?keep_failed_events"), & .false., intrinsic = .true., & description=var_str ('In the context of weighted event generation, ' // & 'if set to \ttt{true}, events with failed kinematics will be ' // & 'written to the event output with an associated weight of zero. ' // & 'This way, the total cross section can be reconstructed from the event output.')) call var_list%append_int (var_str ("gks_multiplicity"), & 0, intrinsic = .true., & description=var_str ('Jet multiplicity for the GKS merging scheme.')) call var_list%append_string (var_str ("$gosam_filter_lo"), & var_str (""), intrinsic = .true., & description=var_str ('The filter string given to \gosam\ in order to ' // & 'filter out tree-level diagrams. (cf. also \ttt{\$gosam\_filter\_nlo}, ' // & '\ttt{\$gosam\_symmetries})')) call var_list%append_string (var_str ("$gosam_filter_nlo"), & var_str (""), intrinsic = .true., & description=var_str ('The same as \ttt{\$gosam\_filter\_lo}, but for ' // & 'loop matrix elements. (cf. also \ttt{\$gosam\_filter\_nlo}, ' // & '\ttt{\$gosam\_symmetries})')) call var_list%append_string (var_str ("$gosam_symmetries"), & var_str ("family,generation"), intrinsic = .true., & description=var_str ('String variable that is transferred to \gosam\ ' // & 'configuration file to determine whether certain helicity configurations ' // & 'are considered to be equal. Possible values are \ttt{flavour}, ' // & '\ttt{family} etc. For more info see the \gosam\ manual.')) call var_list%append_int (var_str ("form_threads"), & 2, intrinsic = .true., & description=var_str ('The number of threads used by \gosam when ' // & 'matrix elements are evaluated using \ttt{FORM}')) call var_list%append_int (var_str ("form_workspace"), & 1000, intrinsic = .true., & description=var_str ('The size of the workspace \gosam requires ' // & 'from \ttt{FORM}. Inside \ttt{FORM}, it corresponds to the heap ' // & 'size used by the algebra processor.')) call var_list%append_string (var_str ("$gosam_fc"), & var_str (""), intrinsic = .true., & description=var_str ('The Fortran compiler used by \gosam.')) call var_list%append_real (& var_str ("mult_call_real"), 1._default, & intrinsic = .true., & description=var_str ('(Real-valued) multiplier for the number ' // & 'of calls used in the integration of the real subtraction ' // & 'NLO component. This way, a higher accuracy can be achieved for ' // & 'the real component, while simultaneously avoiding redundant ' // & 'integration calls for the other components. (cf. also ' // & '\ttt{mult\_call\_dglap}, \ttt{mult\_call\_virt})')) call var_list%append_real (& var_str ("mult_call_virt"), 1._default, & intrinsic = .true., & description=var_str ('(Real-valued) multiplier for the number ' // & 'of calls used in the integration of the virtual NLO ' // & 'component. This way, a higher accuracy can be achieved for ' // & 'this component, while simultaneously avoiding redundant ' // & 'integration calls for the other components. (cf. also ' // & '\ttt{mult\_call\_dglap}, \ttt{mult\_call\_real})')) call var_list%append_real (& var_str ("mult_call_dglap"), 1._default, & intrinsic = .true., & description=var_str ('(Real-valued) multiplier for the number ' // & 'of calls used in the integration of the DGLAP remnant NLO ' // & 'component. This way, a higher accuracy can be achieved for ' // & 'this component, while simultaneously avoiding redundant ' // & 'integration calls for the other components. (cf. also ' // & '\ttt{mult\_call\_real}, \ttt{mult\_call\_virt})')) call var_list%append_string (var_str ("$dalitz_plot"), & var_str (''), intrinsic = .true., & description=var_str ('This string variable has two purposes: ' // & 'when different from the empty string, it switches on generation ' // & 'of the Dalitz plot file (ASCII tables) for the real emitters. ' // & 'The string variable itself provides the file name.')) call var_list%append_string (var_str ("$nlo_correction_type"), & var_str ("QCD"), intrinsic = .true., & description=var_str ('String variable which sets the NLO correction ' // & 'type via \ttt{nlo\_correction\_type = "{\em }"} to either ' // & '\ttt{"QCD"}, \ttt{"EW"}, or to all with \ttt{\em{}} ' // & 'set to \ttt{"Full"}. Must be set before the \texttt{process} statement.')) call var_list%append_string (var_str ("$exclude_gauge_splittings"), & var_str ("c:b:t:e2:e3"), intrinsic = .true., & description=var_str ('String variable that allows via ' // & '\ttt{\$exclude\_gauge\_splittings = "{\em ::\dots}"} ' // & 'to exclude fermion flavors from gluon/photon splitting into ' // & 'fermion pairs beyond LO. For example \ttt{\$exclude\_gauge\_splittings ' // & '= "c:s:b:t"} would lead to \ttt{gl => u U} and \ttt{gl => d ' // & 'D} as possible splittings in QCD. It is important to keep in ' // & 'mind that only the particles listed in the string are excluded! ' // & 'In QED this string would additionally allow for all splittings into ' // & 'lepton pairs \ttt{A => l L}. Therefore, once set the variable ' // & 'acts as a replacement of the default value, not as an addition! ' // & 'Note: \ttt{"\em "} can be both particle or antiparticle. It ' // & 'will always exclude the corresponding fermion pair. An empty ' // & 'string allows for all fermion flavors to take part in the splitting! ' // & 'Also, particles included in an \ttt{alias} are not excluded by ' // & '\ttt{\$exclude\_gauge\_splittings}!')) call var_list%append_log (var_str ("?nlo_use_born_scale"), & .false., intrinsic = .true., & description=var_str ('Flag that decides whether a scale expression ' // & 'defined for the Born component of an NLO process shall be applied ' // & 'to all other components as well or not. ' // & '(cf. also \ttt{?nlo\_cut\_all\_sqmes})')) call var_list%append_log (var_str ("?nlo_cut_all_sqmes"), & .false., intrinsic = .true., & description=var_str ('Flag that decides whether in the case that ' // & 'some NLO component does not pass a cut, all other components ' // & 'shall be discarded for that phase space point as well or not. ' // & '(cf. also \ttt{?nlo\_use\_born\_scale})')) call var_list%append_log (var_str ("?nlo_use_real_partition"), & .false., intrinsic = .true., & description=var_str (' If set to \ttt{true}, the real matrix ' // & 'element is split into a finite and a singular part using a ' // & 'partition function $f$, such that $\mathcal{R} ' // & '= [1-f(p_T^2)]\mathcal{R} + f(p_T^2)\mathcal{R} = ' // & '\mathcal{R}_{\text{fin}} ' // & '+ \mathcal{R}_{\text{sing}}$. The emission ' // & 'generation is then performed using $\mathcal{R}_{\text{sing}}$, ' // & 'whereas $\mathcal{R}_{\text{fin}}$ is treated separately. ' // & '(cf. also \ttt{real\_partition\_scale})')) call var_list%append_real (var_str ("real_partition_scale"), & 10._default, intrinsic = .true., & description=var_str ('This real variable sets the invariant mass ' // & 'of the FKS pair used as a separator between the singular and the ' // & 'finite part of the real subtraction terms in an NLO calculation, ' // & 'e.g. in $e^+e^- \to ' // & 't\bar tj$. (cf. also \ttt{?nlo\_use\_real\_partition})')) end subroutine var_list_set_nlo_defaults @ %def var_list_set_nlo_defaults @ \clearpage %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Observables} In this module we define concrete variables and operators (observables) that we want to support in expressions. <<[[observables.f90]]>>= <> module observables <> <> use io_units use diagnostics use lorentz use subevents use variables <> <> contains <> end module observables @ %def observables @ \subsection{Process-specific variables} We allow the user to set a numeric process ID for each declared process. <>= public :: var_list_init_num_id <>= subroutine var_list_init_num_id (var_list, proc_id, num_id) type(var_list_t), intent(inout) :: var_list type(string_t), intent(in) :: proc_id integer, intent(in), optional :: num_id call var_list_set_procvar_int (var_list, proc_id, & var_str ("num_id"), num_id) end subroutine var_list_init_num_id @ %def var_list_init_num_id @ Integration results are stored in special variables. They are initialized by this subroutine. The values may or may not already known. Note: the values which are accessible are those that are unique for a process with multiple MCI records. The rest has been discarded. <>= public :: var_list_init_process_results <>= subroutine var_list_init_process_results (var_list, proc_id, & n_calls, integral, error, accuracy, chi2, efficiency) type(var_list_t), intent(inout) :: var_list type(string_t), intent(in) :: proc_id integer, intent(in), optional :: n_calls real(default), intent(in), optional :: integral, error, accuracy real(default), intent(in), optional :: chi2, efficiency call var_list_set_procvar_real (var_list, proc_id, & var_str ("integral"), integral) call var_list_set_procvar_real (var_list, proc_id, & var_str ("error"), error) end subroutine var_list_init_process_results @ %def var_list_init_process_results @ \subsection{Observables as Pseudo-Variables} Unary and binary observables are different. Most unary observables can be equally well evaluated for particle pairs. Binary observables cannot be evaluated for single particles. <>= public :: var_list_set_observables_unary public :: var_list_set_observables_binary <>= subroutine var_list_set_observables_unary (var_list, prt1) type(var_list_t), intent(inout) :: var_list type(prt_t), intent(in), target :: prt1 call var_list_append_obs1_iptr & (var_list, var_str ("PDG"), obs_pdg1, prt1) call var_list_append_obs1_iptr & (var_list, var_str ("Hel"), obs_helicity1, prt1) call var_list_append_obs1_iptr & (var_list, var_str ("Ncol"), obs_n_col1, prt1) call var_list_append_obs1_iptr & (var_list, var_str ("Nacl"), obs_n_acl1, prt1) call var_list_append_obs1_rptr & (var_list, var_str ("M"), obs_signed_mass1, prt1) call var_list_append_obs1_rptr & (var_list, var_str ("M2"), obs_mass_squared1, prt1) call var_list_append_obs1_rptr & (var_list, var_str ("E"), obs_energy1, prt1) call var_list_append_obs1_rptr & (var_list, var_str ("Px"), obs_px1, prt1) call var_list_append_obs1_rptr & (var_list, var_str ("Py"), obs_py1, prt1) call var_list_append_obs1_rptr & (var_list, var_str ("Pz"), obs_pz1, prt1) call var_list_append_obs1_rptr & (var_list, var_str ("P"), obs_p1, prt1) call var_list_append_obs1_rptr & (var_list, var_str ("Pl"), obs_pl1, prt1) call var_list_append_obs1_rptr & (var_list, var_str ("Pt"), obs_pt1, prt1) call var_list_append_obs1_rptr & (var_list, var_str ("Theta"), obs_theta1, prt1) call var_list_append_obs1_rptr & (var_list, var_str ("Phi"), obs_phi1, prt1) call var_list_append_obs1_rptr & (var_list, var_str ("Rap"), obs_rap1, prt1) call var_list_append_obs1_rptr & (var_list, var_str ("Eta"), obs_eta1, prt1) call var_list_append_obs1_rptr & (var_list, var_str ("Theta_star"), obs_theta_star1, prt1) call var_list_append_obs1_rptr & (var_list, var_str ("Dist"), obs_dist1, prt1) call var_list_append_uobs_real & (var_list, var_str ("_User_obs_real"), prt1) call var_list_append_uobs_int & (var_list, var_str ("_User_obs_int"), prt1) end subroutine var_list_set_observables_unary subroutine var_list_set_observables_binary (var_list, prt1, prt2) type(var_list_t), intent(inout) :: var_list type(prt_t), intent(in), target :: prt1 type(prt_t), intent(in), optional, target :: prt2 call var_list_append_obs2_iptr & (var_list, var_str ("PDG"), obs_pdg2, prt1, prt2) call var_list_append_obs2_iptr & (var_list, var_str ("Hel"), obs_helicity2, prt1, prt2) call var_list_append_obs2_iptr & (var_list, var_str ("Ncol"), obs_n_col2, prt1, prt2) call var_list_append_obs2_iptr & (var_list, var_str ("Nacl"), obs_n_acl2, prt1, prt2) call var_list_append_obs2_rptr & (var_list, var_str ("M"), obs_signed_mass2, prt1, prt2) call var_list_append_obs2_rptr & (var_list, var_str ("M2"), obs_mass_squared2, prt1, prt2) call var_list_append_obs2_rptr & (var_list, var_str ("E"), obs_energy2, prt1, prt2) call var_list_append_obs2_rptr & (var_list, var_str ("Px"), obs_px2, prt1, prt2) call var_list_append_obs2_rptr & (var_list, var_str ("Py"), obs_py2, prt1, prt2) call var_list_append_obs2_rptr & (var_list, var_str ("Pz"), obs_pz2, prt1, prt2) call var_list_append_obs2_rptr & (var_list, var_str ("P"), obs_p2, prt1, prt2) call var_list_append_obs2_rptr & (var_list, var_str ("Pl"), obs_pl2, prt1, prt2) call var_list_append_obs2_rptr & (var_list, var_str ("Pt"), obs_pt2, prt1, prt2) call var_list_append_obs2_rptr & (var_list, var_str ("Theta"), obs_theta2, prt1, prt2) call var_list_append_obs2_rptr & (var_list, var_str ("Phi"), obs_phi2, prt1, prt2) call var_list_append_obs2_rptr & (var_list, var_str ("Rap"), obs_rap2, prt1, prt2) call var_list_append_obs2_rptr & (var_list, var_str ("Eta"), obs_eta2, prt1, prt2) call var_list_append_obs2_rptr & (var_list, var_str ("Theta_star"), obs_theta_star2, prt1, prt2) call var_list_append_obs2_rptr & (var_list, var_str ("Dist"), obs_dist2, prt1, prt2) call var_list_append_obs2_rptr & (var_list, var_str ("kT"), obs_ktmeasure, prt1, prt2) call var_list_append_uobs_real & (var_list, var_str ("_User_obs_real"), prt1, prt2) call var_list_append_uobs_int & (var_list, var_str ("_User_obs_int"), prt1, prt2) end subroutine var_list_set_observables_binary @ %def var_list_set_observables_unary var_list_set_observables_binary @ \subsection{Checks} <>= public :: var_list_check_observable <>= subroutine var_list_check_observable (var_list, name, type) class(var_list_t), intent(in), target :: var_list type(string_t), intent(in) :: name integer, intent(inout) :: type if (string_is_observable_id (name)) then call msg_fatal ("Variable name '" // char (name) & // "' is reserved for an observable") type = V_NONE return end if end subroutine var_list_check_observable @ %def var_list_check_observable @ Check if a variable name is defined as an observable: <>= function string_is_observable_id (string) result (flag) logical :: flag type(string_t), intent(in) :: string select case (char (string)) case ("PDG", "Hel", "Ncol", & "M", "M2", "E", "Px", "Py", "Pz", "P", "Pl", "Pt", & "Theta", "Phi", "Rap", "Eta", "Theta_star", "Dist", "kT") flag = .true. case default flag = .false. end select end function string_is_observable_id @ %def string_is_observable_id @ Check for result and process variables. <>= public :: var_list_check_result_var <>= subroutine var_list_check_result_var (var_list, name, type) class(var_list_t), intent(in), target :: var_list type(string_t), intent(in) :: name integer, intent(inout) :: type if (string_is_integer_result_var (name)) type = V_INT if (.not. var_list%contains (name)) then if (string_is_result_var (name)) then call msg_fatal ("Result variable '" // char (name) // "' " & // "set without prior integration") type = V_NONE return else if (string_is_num_id (name)) then call msg_fatal ("Numeric process ID '" // char (name) // "' " & // "set without process declaration") type = V_NONE return end if end if end subroutine var_list_check_result_var @ %def var_list_check_result_var @ Check if a variable name is a result variable of integer type: <>= function string_is_integer_result_var (string) result (flag) logical :: flag type(string_t), intent(in) :: string type(string_t) :: buffer, name, separator buffer = string call split (buffer, name, "(", separator=separator) ! ")" if (separator == "(") then select case (char (name)) case ("num_id", "n_calls") flag = .true. case default flag = .false. end select else flag = .false. end if end function string_is_integer_result_var @ %def string_is_integer_result_var @ Check if a variable name is an integration-result variable: <>= function string_is_result_var (string) result (flag) logical :: flag type(string_t), intent(in) :: string type(string_t) :: buffer, name, separator buffer = string call split (buffer, name, "(", separator=separator) ! ")" if (separator == "(") then select case (char (name)) case ("integral", "error") flag = .true. case default flag = .false. end select else flag = .false. end if end function string_is_result_var @ %def string_is_result_var @ Check if a variable name is a numeric process ID: <>= function string_is_num_id (string) result (flag) logical :: flag type(string_t), intent(in) :: string type(string_t) :: buffer, name, separator buffer = string call split (buffer, name, "(", separator=separator) ! ")" if (separator == "(") then select case (char (name)) case ("num_id") flag = .true. case default flag = .false. end select else flag = .false. end if end function string_is_num_id @ %def string_is_num_id @ \subsection{Observables} These are analogous to the unary and binary numeric functions listed above. An observable takes the [[pval]] component(s) of its one or two argument nodes and produces an integer or real value. \subsubsection{Integer-valued unary observables} The PDG code <>= integer function obs_pdg1 (prt1) result (pdg) type(prt_t), intent(in) :: prt1 pdg = prt_get_pdg (prt1) end function obs_pdg1 @ %def obs_pdg @ The helicity. The return value is meaningful only if the particle is polarized, otherwise an invalid value is returned (-9). <>= integer function obs_helicity1 (prt1) result (h) type(prt_t), intent(in) :: prt1 if (prt_is_polarized (prt1)) then h = prt_get_helicity (prt1) else h = -9 end if end function obs_helicity1 @ %def obs_helicity1 @ The number of open color (anticolor) lines. The return value is meaningful only if the particle is colorized (i.e., the subevent has been given color information), otherwise the function returns zero. <>= integer function obs_n_col1 (prt1) result (n) type(prt_t), intent(in) :: prt1 if (prt_is_colorized (prt1)) then n = prt_get_n_col (prt1) else n = 0 end if end function obs_n_col1 integer function obs_n_acl1 (prt1) result (n) type(prt_t), intent(in) :: prt1 if (prt_is_colorized (prt1)) then n = prt_get_n_acl (prt1) else n = 0 end if end function obs_n_acl1 @ %def obs_n_col1 @ %def obs_n_acl1 @ \subsubsection{Real-valued unary observables} The invariant mass squared, obtained from the separately stored value. <>= real(default) function obs_mass_squared1 (prt1) result (p2) type(prt_t), intent(in) :: prt1 p2 = prt_get_msq (prt1) end function obs_mass_squared1 @ %def obs_mass_squared1 @ The signed invariant mass, which is the signed square root of the previous observable. <>= real(default) function obs_signed_mass1 (prt1) result (m) type(prt_t), intent(in) :: prt1 real(default) :: msq msq = prt_get_msq (prt1) m = sign (sqrt (abs (msq)), msq) end function obs_signed_mass1 @ %def obs_signed_mass1 @ The particle energy <>= real(default) function obs_energy1 (prt1) result (e) type(prt_t), intent(in) :: prt1 e = energy (prt_get_momentum (prt1)) end function obs_energy1 @ %def obs_energy1 @ Particle momentum (components) <>= real(default) function obs_px1 (prt1) result (p) type(prt_t), intent(in) :: prt1 p = vector4_get_component (prt_get_momentum (prt1), 1) end function obs_px1 real(default) function obs_py1 (prt1) result (p) type(prt_t), intent(in) :: prt1 p = vector4_get_component (prt_get_momentum (prt1), 2) end function obs_py1 real(default) function obs_pz1 (prt1) result (p) type(prt_t), intent(in) :: prt1 p = vector4_get_component (prt_get_momentum (prt1), 3) end function obs_pz1 real(default) function obs_p1 (prt1) result (p) type(prt_t), intent(in) :: prt1 p = space_part_norm (prt_get_momentum (prt1)) end function obs_p1 real(default) function obs_pl1 (prt1) result (p) type(prt_t), intent(in) :: prt1 p = longitudinal_part (prt_get_momentum (prt1)) end function obs_pl1 real(default) function obs_pt1 (prt1) result (p) type(prt_t), intent(in) :: prt1 p = transverse_part (prt_get_momentum (prt1)) end function obs_pt1 @ %def obs_px1 obs_py1 obs_pz1 @ %def obs_p1 obs_pl1 obs_pt1 @ Polar and azimuthal angle (lab frame). <>= real(default) function obs_theta1 (prt1) result (p) type(prt_t), intent(in) :: prt1 p = polar_angle (prt_get_momentum (prt1)) end function obs_theta1 real(default) function obs_phi1 (prt1) result (p) type(prt_t), intent(in) :: prt1 p = azimuthal_angle (prt_get_momentum (prt1)) end function obs_phi1 @ %def obs_theta1 obs_phi1 @ Rapidity and pseudorapidity <>= real(default) function obs_rap1 (prt1) result (p) type(prt_t), intent(in) :: prt1 p = rapidity (prt_get_momentum (prt1)) end function obs_rap1 real(default) function obs_eta1 (prt1) result (p) type(prt_t), intent(in) :: prt1 p = pseudorapidity (prt_get_momentum (prt1)) end function obs_eta1 @ %def obs_rap1 obs_eta1 @ Meaningless: Polar angle in the rest frame of the two arguments combined. <>= real(default) function obs_theta_star1 (prt1) result (dist) type(prt_t), intent(in) :: prt1 call msg_fatal (" 'Theta_star' is undefined as unary observable") dist = 0 end function obs_theta_star1 @ %def obs_theta_star1 @ [Obsolete] Meaningless: Polar angle in the rest frame of the 2nd argument. <>= real(default) function obs_theta_rf1 (prt1) result (dist) type(prt_t), intent(in) :: prt1 call msg_fatal (" 'Theta_RF' is undefined as unary observable") dist = 0 end function obs_theta_rf1 @ %def obs_theta_rf1 @ Meaningless: Distance on the $\eta$-$\phi$ cylinder. <>= real(default) function obs_dist1 (prt1) result (dist) type(prt_t), intent(in) :: prt1 call msg_fatal (" 'Dist' is undefined as unary observable") dist = 0 end function obs_dist1 @ %def obs_dist1 @ \subsubsection{Integer-valued binary observables} These observables are meaningless as binary functions. <>= integer function obs_pdg2 (prt1, prt2) result (pdg) type(prt_t), intent(in) :: prt1, prt2 call msg_fatal (" PDG_Code is undefined as binary observable") pdg = 0 end function obs_pdg2 integer function obs_helicity2 (prt1, prt2) result (h) type(prt_t), intent(in) :: prt1, prt2 call msg_fatal (" Helicity is undefined as binary observable") h = 0 end function obs_helicity2 integer function obs_n_col2 (prt1, prt2) result (n) type(prt_t), intent(in) :: prt1, prt2 call msg_fatal (" Ncol is undefined as binary observable") n = 0 end function obs_n_col2 integer function obs_n_acl2 (prt1, prt2) result (n) type(prt_t), intent(in) :: prt1, prt2 call msg_fatal (" Nacl is undefined as binary observable") n = 0 end function obs_n_acl2 @ %def obs_pdg2 @ %def obs_helicity2 @ %def obs_n_col2 @ %def obs_n_acl2 @ \subsubsection{Real-valued binary observables} The invariant mass squared, obtained from the separately stored value. <>= real(default) function obs_mass_squared2 (prt1, prt2) result (p2) type(prt_t), intent(in) :: prt1, prt2 type(prt_t) :: prt call prt_init_combine (prt, prt1, prt2) p2 = prt_get_msq (prt) end function obs_mass_squared2 @ %def obs_mass_squared2 @ The signed invariant mass, which is the signed square root of the previous observable. <>= real(default) function obs_signed_mass2 (prt1, prt2) result (m) type(prt_t), intent(in) :: prt1, prt2 type(prt_t) :: prt real(default) :: msq call prt_init_combine (prt, prt1, prt2) msq = prt_get_msq (prt) m = sign (sqrt (abs (msq)), msq) end function obs_signed_mass2 @ %def obs_signed_mass2 @ The particle energy <>= real(default) function obs_energy2 (prt1, prt2) result (e) type(prt_t), intent(in) :: prt1, prt2 type(prt_t) :: prt call prt_init_combine (prt, prt1, prt2) e = energy (prt_get_momentum (prt)) end function obs_energy2 @ %def obs_energy2 @ Particle momentum (components) <>= real(default) function obs_px2 (prt1, prt2) result (p) type(prt_t), intent(in) :: prt1, prt2 type(prt_t) :: prt call prt_init_combine (prt, prt1, prt2) p = vector4_get_component (prt_get_momentum (prt), 1) end function obs_px2 real(default) function obs_py2 (prt1, prt2) result (p) type(prt_t), intent(in) :: prt1, prt2 type(prt_t) :: prt call prt_init_combine (prt, prt1, prt2) p = vector4_get_component (prt_get_momentum (prt), 2) end function obs_py2 real(default) function obs_pz2 (prt1, prt2) result (p) type(prt_t), intent(in) :: prt1, prt2 type(prt_t) :: prt call prt_init_combine (prt, prt1, prt2) p = vector4_get_component (prt_get_momentum (prt), 3) end function obs_pz2 real(default) function obs_p2 (prt1, prt2) result (p) type(prt_t), intent(in) :: prt1, prt2 type(prt_t) :: prt call prt_init_combine (prt, prt1, prt2) p = space_part_norm (prt_get_momentum (prt)) end function obs_p2 real(default) function obs_pl2 (prt1, prt2) result (p) type(prt_t), intent(in) :: prt1, prt2 type(prt_t) :: prt call prt_init_combine (prt, prt1, prt2) p = longitudinal_part (prt_get_momentum (prt)) end function obs_pl2 real(default) function obs_pt2 (prt1, prt2) result (p) type(prt_t), intent(in) :: prt1, prt2 type(prt_t) :: prt call prt_init_combine (prt, prt1, prt2) p = transverse_part (prt_get_momentum (prt)) end function obs_pt2 @ %def obs_px2 obs_py2 obs_pz2 @ %def obs_p2 obs_pl2 obs_pt2 @ Enclosed angle and azimuthal distance (lab frame). <>= real(default) function obs_theta2 (prt1, prt2) result (p) type(prt_t), intent(in) :: prt1, prt2 p = enclosed_angle (prt_get_momentum (prt1), prt_get_momentum (prt2)) end function obs_theta2 real(default) function obs_phi2 (prt1, prt2) result (p) type(prt_t), intent(in) :: prt1, prt2 type(prt_t) :: prt call prt_init_combine (prt, prt1, prt2) p = azimuthal_distance (prt_get_momentum (prt1), prt_get_momentum (prt2)) end function obs_phi2 @ %def obs_theta2 obs_phi2 @ Rapidity and pseudorapidity distance <>= real(default) function obs_rap2 (prt1, prt2) result (p) type(prt_t), intent(in) :: prt1, prt2 p = rapidity_distance & (prt_get_momentum (prt1), prt_get_momentum (prt2)) end function obs_rap2 real(default) function obs_eta2 (prt1, prt2) result (p) type(prt_t), intent(in) :: prt1, prt2 type(prt_t) :: prt call prt_init_combine (prt, prt1, prt2) p = pseudorapidity_distance & (prt_get_momentum (prt1), prt_get_momentum (prt2)) end function obs_eta2 @ %def obs_rap2 obs_eta2 @ [This doesn't work! The principle of no common particle for momentum combination prohibits us from combining a decay particle with the momentum of its parent.] Polar angle in the rest frame of the 2nd argument. <>= real(default) function obs_theta_rf2 (prt1, prt2) result (theta) type(prt_t), intent(in) :: prt1, prt2 theta = enclosed_angle_rest_frame & (prt_get_momentum (prt1), prt_get_momentum (prt2)) end function obs_theta_rf2 @ %def obs_theta_rf2 @ Polar angle of the first particle in the rest frame of the two particles combined. <>= real(default) function obs_theta_star2 (prt1, prt2) result (theta) type(prt_t), intent(in) :: prt1, prt2 theta = enclosed_angle_rest_frame & (prt_get_momentum (prt1), & prt_get_momentum (prt1) + prt_get_momentum (prt2)) end function obs_theta_star2 @ %def obs_theta_star2 @ Distance on the $\eta$-$\phi$ cylinder. <>= real(default) function obs_dist2 (prt1, prt2) result (dist) type(prt_t), intent(in) :: prt1, prt2 dist = eta_phi_distance & (prt_get_momentum (prt1), prt_get_momentum (prt2)) end function obs_dist2 @ %def obs_dist2 @ Durham kT measure. <>= real(default) function obs_ktmeasure (prt1, prt2) result (kt) type(prt_t), intent(in) :: prt1, prt2 real (default) :: q2, e1, e2 ! Normalized scale to one for now! (#67) q2 = 1 e1 = energy (prt_get_momentum (prt1)) e2 = energy (prt_get_momentum (prt2)) kt = (2/q2) * min(e1**2,e2**2) * & (1 - enclosed_angle_ct(prt_get_momentum (prt1), & prt_get_momentum (prt2))) end function obs_ktmeasure @ %def obs_ktmeasure Index: trunk/share/tests/functional_tests/epa_4.sin =================================================================== --- trunk/share/tests/functional_tests/epa_4.sin (revision 8402) +++ trunk/share/tests/functional_tests/epa_4.sin (revision 8403) @@ -1,47 +1,72 @@ # SINDARIN input for WHIZARD self-test ?logging = true ?openmp_logging = false ?vis_history = false ?integration_timer = false ?pacify = true process epa_4a = A, A => e2, E2 process epa_4b = A, A => e2, E2 +process epa_4c = A, A => e2, E2 +process epa_4d = A, A => e2, E2 +process epa_4e = A, A => e2, E2 compile sqrts = 100 GeV cuts = all M > 10 GeV [e2, E2] !!! Tests should be run single-threaded openmp_num_threads = 1 iterations = 1:1000 me = 0 epa_mass = 511 keV epa_x_min = 0.01 ?epa_recoil = false beams = e1, E1 => epa seed = 0 $epa_mode = "Budnev_617" integrate (epa_4a) seed = 0 $epa_mode = "Budnev_616e" integrate (epa_4b) +seed = 0 +$epa_mode = "log_power" +integrate (epa_4c) +seed = 0 +$epa_mode = "log_simple" +integrate (epa_4d) +seed = 0 +$epa_mode = "log" +integrate (epa_4e) + ?keep_beams = true ?keep_remnants = true ?epa_handler = false $sample = "epa_4a" sample_format = lhef simulate (epa_4a) { n_events = 1 } $sample = "epa_4b" sample_format = lhef simulate (epa_4b) { n_events = 1 } + +$sample = "epa_4c" +sample_format = lhef +simulate (epa_4c) { n_events = 1 } + +$sample = "epa_4d" +sample_format = lhef +simulate (epa_4d) { n_events = 1 } + +$sample = "epa_4e" +sample_format = lhef +simulate (epa_4e) { n_events = 1 } Index: trunk/share/tests/functional_tests/ref-output/epa_4.ref =================================================================== --- trunk/share/tests/functional_tests/ref-output/epa_4.ref (revision 8402) +++ trunk/share/tests/functional_tests/ref-output/epa_4.ref (revision 8403) @@ -1,138 +1,309 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false ?pacify = true | Process library 'epa_4_lib': recorded process 'epa_4a' | Process library 'epa_4_lib': recorded process 'epa_4b' +| Process library 'epa_4_lib': recorded process 'epa_4c' +| Process library 'epa_4_lib': recorded process 'epa_4d' +| Process library 'epa_4_lib': recorded process 'epa_4e' | Process library 'epa_4_lib': compiling ... | Process library 'epa_4_lib': writing makefile | Process library 'epa_4_lib': removing old files | Process library 'epa_4_lib': writing driver | Process library 'epa_4_lib': creating source code | Process library 'epa_4_lib': compiling sources | Process library 'epa_4_lib': linking | Process library 'epa_4_lib': loading | Process library 'epa_4_lib': ... success. sqrts = 1.00000E+02 openmp_num_threads = 1 SM.me => 0.00000E+00 epa_mass = 5.11000E-04 epa_x_min = 1.00000E-02 ?epa_recoil = false seed = 0 $epa_mode = "Budnev_617" | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 0 | Initializing integration for process epa_4a: | Beam structure: e-, e+ => epa | Beam data (collision): | e- (mass = 0.0000000E+00 GeV) | e+ (mass = 0.0000000E+00 GeV) | sqrts = 1.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'epa_4a.i1.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'epa_4a' | Library name = 'epa_4_lib' | Process index = 1 | Process components: | 1: 'epa_4a_i1': A, A => mu-, mu+ [omega] | ------------------------------------------------------------------------ | Phase space: 4 channels, 2 dimensions | Phase space: found 4 channels, collected in 1 grove. | Phase space: Using 8 equivalences between channels. | Phase space: wood | Beam structure: epa, none => none, epa | Beam structure: 1 channels, 2 dimensions | Applying user-defined cuts. | Starting integration for process 'epa_4a' | Integrate: iterations = 1:1000 | Integrator: 1 chains, 4 channels, 4 dimensions | Integrator: Using VAMP channel equivalences | Integrator: 1000 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 1000 1.446E+05 3.54E+04 24.48 7.74 1.3 |-----------------------------------------------------------------------------| 1 1000 1.446E+05 3.54E+04 24.48 7.74 1.3 |=============================================================================| seed = 0 $epa_mode = "Budnev_616e" | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 0 | Initializing integration for process epa_4b: | Beam structure: e-, e+ => epa | Beam data (collision): | e- (mass = 0.0000000E+00 GeV) | e+ (mass = 0.0000000E+00 GeV) | sqrts = 1.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'epa_4b.i1.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'epa_4b' | Library name = 'epa_4_lib' | Process index = 2 | Process components: | 1: 'epa_4b_i1': A, A => mu-, mu+ [omega] | ------------------------------------------------------------------------ | Phase space: 4 channels, 2 dimensions | Phase space: found 4 channels, collected in 1 grove. | Phase space: Using 8 equivalences between channels. | Phase space: wood | Beam structure: epa, none => none, epa | Beam structure: 1 channels, 2 dimensions | Applying user-defined cuts. | Starting integration for process 'epa_4b' | Integrate: iterations = 1:1000 | Integrator: 1 chains, 4 channels, 4 dimensions | Integrator: Using VAMP channel equivalences | Integrator: 1000 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 1000 2.145E+05 5.34E+04 24.90 7.87 1.3 |-----------------------------------------------------------------------------| 1 1000 2.145E+05 5.34E+04 24.90 7.87 1.3 |=============================================================================| +seed = 0 +$epa_mode = "log_power" +| RNG: Initializing TAO random-number generator +| RNG: Setting seed for random-number generator to 0 +| Initializing integration for process epa_4c: +| Beam structure: e-, e+ => epa +| Beam data (collision): +| e- (mass = 0.0000000E+00 GeV) +| e+ (mass = 0.0000000E+00 GeV) +| sqrts = 1.000000000000E+02 GeV +| Phase space: generating configuration ... +| Phase space: ... success. +| Phase space: writing configuration file 'epa_4c.i1.phs' +| ------------------------------------------------------------------------ +| Process [scattering]: 'epa_4c' +| Library name = 'epa_4_lib' +| Process index = 3 +| Process components: +| 1: 'epa_4c_i1': A, A => mu-, mu+ [omega] +| ------------------------------------------------------------------------ +| Phase space: 4 channels, 2 dimensions +| Phase space: found 4 channels, collected in 1 grove. +| Phase space: Using 8 equivalences between channels. +| Phase space: wood +| Beam structure: epa, none => none, epa +| Beam structure: 1 channels, 2 dimensions +| Applying user-defined cuts. +| Starting integration for process 'epa_4c' +| Integrate: iterations = 1:1000 +| Integrator: 1 chains, 4 channels, 4 dimensions +| Integrator: Using VAMP channel equivalences +| Integrator: 1000 initial calls, 20 bins, stratified = T +| Integrator: VAMP +|=============================================================================| +| It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | +|=============================================================================| + 1 1000 1.693E+05 4.09E+04 24.17 7.64 1.4 +|-----------------------------------------------------------------------------| + 1 1000 1.693E+05 4.09E+04 24.17 7.64 1.4 +|=============================================================================| +seed = 0 +$epa_mode = "log_simple" +| RNG: Initializing TAO random-number generator +| RNG: Setting seed for random-number generator to 0 +| Initializing integration for process epa_4d: +| Beam structure: e-, e+ => epa +| Beam data (collision): +| e- (mass = 0.0000000E+00 GeV) +| e+ (mass = 0.0000000E+00 GeV) +| sqrts = 1.000000000000E+02 GeV +| Phase space: generating configuration ... +| Phase space: ... success. +| Phase space: writing configuration file 'epa_4d.i1.phs' +| ------------------------------------------------------------------------ +| Process [scattering]: 'epa_4d' +| Library name = 'epa_4_lib' +| Process index = 4 +| Process components: +| 1: 'epa_4d_i1': A, A => mu-, mu+ [omega] +| ------------------------------------------------------------------------ +| Phase space: 4 channels, 2 dimensions +| Phase space: found 4 channels, collected in 1 grove. +| Phase space: Using 8 equivalences between channels. +| Phase space: wood +| Beam structure: epa, none => none, epa +| Beam structure: 1 channels, 2 dimensions +| Applying user-defined cuts. +| Starting integration for process 'epa_4d' +| Integrate: iterations = 1:1000 +| Integrator: 1 chains, 4 channels, 4 dimensions +| Integrator: Using VAMP channel equivalences +| Integrator: 1000 initial calls, 20 bins, stratified = T +| Integrator: VAMP +|=============================================================================| +| It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | +|=============================================================================| + 1 1000 1.794E+05 4.38E+04 24.39 7.71 1.3 +|-----------------------------------------------------------------------------| + 1 1000 1.794E+05 4.38E+04 24.39 7.71 1.3 +|=============================================================================| +seed = 0 +$epa_mode = "log" +| RNG: Initializing TAO random-number generator +| RNG: Setting seed for random-number generator to 0 +| Initializing integration for process epa_4e: +| Beam structure: e-, e+ => epa +| Beam data (collision): +| e- (mass = 0.0000000E+00 GeV) +| e+ (mass = 0.0000000E+00 GeV) +| sqrts = 1.000000000000E+02 GeV +| Phase space: generating configuration ... +| Phase space: ... success. +| Phase space: writing configuration file 'epa_4e.i1.phs' +| ------------------------------------------------------------------------ +| Process [scattering]: 'epa_4e' +| Library name = 'epa_4_lib' +| Process index = 5 +| Process components: +| 1: 'epa_4e_i1': A, A => mu-, mu+ [omega] +| ------------------------------------------------------------------------ +| Phase space: 4 channels, 2 dimensions +| Phase space: found 4 channels, collected in 1 grove. +| Phase space: Using 8 equivalences between channels. +| Phase space: wood +| Beam structure: epa, none => none, epa +| Beam structure: 1 channels, 2 dimensions +| Applying user-defined cuts. +| Starting integration for process 'epa_4e' +| Integrate: iterations = 1:1000 +| Integrator: 1 chains, 4 channels, 4 dimensions +| Integrator: Using VAMP channel equivalences +| Integrator: 1000 initial calls, 20 bins, stratified = T +| Integrator: VAMP +|=============================================================================| +| It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | +|=============================================================================| + 1 1000 1.825E+05 4.42E+04 24.24 7.67 1.4 +|-----------------------------------------------------------------------------| + 1 1000 1.825E+05 4.42E+04 24.24 7.67 1.4 +|=============================================================================| ?keep_beams = true ?keep_remnants = true ?epa_handler = false $sample = "epa_4a" n_events = 1 | Starting simulation for process 'epa_4a' | Simulate: using integration grids from file 'epa_4a.m1.vg' | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 1 | Simulation: requested number of events = 1 | corr. to luminosity [fb-1] = 6.9158E-06 | Events: writing to LHEF file 'epa_4a.lhe' | Events: writing to raw file 'epa_4a.evx' | Events: generating 1 unweighted, unpolarized events ... | Events: event normalization mode '1' | ... event sample complete. | Events: actual unweighting efficiency = 1.59 % | Events: closing LHEF file 'epa_4a.lhe' | Events: closing raw file 'epa_4a.evx' $sample = "epa_4b" n_events = 1 | Starting simulation for process 'epa_4b' | Simulate: using integration grids from file 'epa_4b.m1.vg' | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 2 | Simulation: requested number of events = 1 | corr. to luminosity [fb-1] = 4.6614E-06 | Events: writing to LHEF file 'epa_4b.lhe' | Events: writing to raw file 'epa_4b.evx' | Events: generating 1 unweighted, unpolarized events ... | Events: event normalization mode '1' | ... event sample complete. | Events: actual unweighting efficiency = 1.59 % | Events: closing LHEF file 'epa_4b.lhe' | Events: closing raw file 'epa_4b.evx' +$sample = "epa_4c" +n_events = 1 +| Starting simulation for process 'epa_4c' +| Simulate: using integration grids from file 'epa_4c.m1.vg' +| RNG: Initializing TAO random-number generator +| RNG: Setting seed for random-number generator to 3 +| Simulation: requested number of events = 1 +| corr. to luminosity [fb-1] = 5.9082E-06 +| Events: writing to LHEF file 'epa_4c.lhe' +| Events: writing to raw file 'epa_4c.evx' +| Events: generating 1 unweighted, unpolarized events ... +| Events: event normalization mode '1' +| ... event sample complete. +| Events: actual unweighting efficiency = 1.59 % +| Events: closing LHEF file 'epa_4c.lhe' +| Events: closing raw file 'epa_4c.evx' +$sample = "epa_4d" +n_events = 1 +| Starting simulation for process 'epa_4d' +| Simulate: using integration grids from file 'epa_4d.m1.vg' +| RNG: Initializing TAO random-number generator +| RNG: Setting seed for random-number generator to 4 +| Simulation: requested number of events = 1 +| corr. to luminosity [fb-1] = 5.5741E-06 +| Events: writing to LHEF file 'epa_4d.lhe' +| Events: writing to raw file 'epa_4d.evx' +| Events: generating 1 unweighted, unpolarized events ... +| Events: event normalization mode '1' +| ... event sample complete. +| Events: actual unweighting efficiency = 1.59 % +| Events: closing LHEF file 'epa_4d.lhe' +| Events: closing raw file 'epa_4d.evx' +$sample = "epa_4e" +n_events = 1 +| Starting simulation for process 'epa_4e' +| Simulate: using integration grids from file 'epa_4e.m1.vg' +| RNG: Initializing TAO random-number generator +| RNG: Setting seed for random-number generator to 5 +| Simulation: requested number of events = 1 +| corr. to luminosity [fb-1] = 5.4808E-06 +| Events: writing to LHEF file 'epa_4e.lhe' +| Events: writing to raw file 'epa_4e.evx' +| Events: generating 1 unweighted, unpolarized events ... +| Events: event normalization mode '1' +| ... event sample complete. +| Events: actual unweighting efficiency = 1.59 % +| Events: closing LHEF file 'epa_4e.lhe' +| Events: closing raw file 'epa_4e.evx' | WHIZARD run finished. |=============================================================================| Index: trunk/share/doc/manual.tex =================================================================== --- trunk/share/doc/manual.tex (revision 8402) +++ trunk/share/doc/manual.tex (revision 8403) @@ -1,17215 +1,17228 @@ \documentclass[12pt]{book} % \usepackage{feynmp} \usepackage{microtype} \usepackage{graphics,graphicx} \usepackage{color} \usepackage{amsmath,amssymb} \usepackage[colorlinks,bookmarks,bookmarksnumbered=true]{hyperref} \usepackage{thophys} \usepackage{fancyvrb} \usepackage{makeidx} \usepackage{units} \usepackage{ifpdf} %HEVEA\pdftrue \makeindex \usepackage{url} \usepackage[latin1]{inputenc} %HEVEA\@def@charset{UTF-8} %BEGIN LATEX \usepackage{supertabular,fancyvrb} \usepackage{hevea} %END LATEX \renewcommand{\topfraction}{0.9} \renewcommand{\bottomfraction}{0.8} \renewcommand{\textfraction}{0.1} %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%% Macro section %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \newcommand{\email}[2]{\thanks{\ahref{#1@{}#2}{#1@{}#2}}} \newcommand{\hepforgepage}{\url{https://whizard.hepforge.org}} \newcommand{\whizardwiki}{\url{https://whizard.hepforge.org/trac/wiki}} \tocnumber %BEGIN LATEX \DeclareMathOperator{\diag}{diag} %END LATEX %BEGIN LATEX \makeatletter \newif\if@preliminary \@preliminaryfalse \def\preliminary{\@preliminarytrue} %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%% Changes referring to article.cls % %%% Title page \def\preprintno#1{\def\@preprintno{#1}} \def\address#1{\def\@address{#1}} \def\email#1#2{\thanks{\tt #1@{}#2}} \def\abstract#1{\def\@abstract{#1}} \newcommand\abstractname{ABSTRACT} \newlength\preprintnoskip \setlength\preprintnoskip{\textwidth\@plus -1cm} \newlength\abstractwidth \setlength\abstractwidth{\textwidth\@plus -3cm} % \@titlepagetrue \renewcommand\maketitle{\begin{titlepage}% \let\footnotesize\small \hfill\parbox{\preprintnoskip}{% \begin{flushright}\@preprintno\end{flushright}}\hspace*{1cm} \vskip 60\p@ \begin{center}% {\Large\bf\boldmath \@title \par}\vskip 1cm% {\sc\@author \par}\vskip 3mm% {\@address \par}% \if@preliminary \vskip 2cm {\large\sf PRELIMINARY DRAFT \par \@date}% \fi \end{center}\par \@thanks \vfill \begin{center}% \parbox{\abstractwidth}{\centerline{\abstractname}% \vskip 3mm% \@abstract} \end{center} \end{titlepage}% \setcounter{footnote}{0}% \let\thanks\relax\let\maketitle\relax \gdef\@thanks{}\gdef\@author{}\gdef\@address{}% \gdef\@title{}\gdef\@abstract{}\gdef\@preprintno{} }% % %%% New settings of dimensions \topmargin -1.5cm \textheight 22cm \textwidth 17cm \oddsidemargin 0cm \evensidemargin 0cm % %%% Original Latex definition of citex, except for the removal of %%% 'space' following a ','. \citerange replaces the ',' by '--'. \def\@citex[#1]#2{\if@filesw\immediate\write\@auxout{\string\citation{#2}}\fi \def\@citea{}\@cite{\@for\@citeb:=#2\do {\@citea\def\@citea{,\penalty\@m}\@ifundefined {b@\@citeb}{{\bf ?}\@warning {Citation `\@citeb' on page \thepage \space undefined}}% \hbox{\csname b@\@citeb\endcsname}}}{#1}} \def\citerange{\@ifnextchar [{\@tempswatrue\@citexr}{\@tempswafalse\@citexr[]}} \def\@citexr[#1]#2{\if@filesw\immediate\write\@auxout{\string\citation{#2}}\fi \def\@citea{}\@cite{\@for\@citeb:=#2\do {\@citea\def\@citea{--\penalty\@m}\@ifundefined {b@\@citeb}{{\bf ?}\@warning {Citation `\@citeb' on page \thepage \space undefined}}% \hbox{\csname b@\@citeb\endcsname}}}{#1}} % %%% Captions set in italics \long\def\@makecaption#1#2{% \vskip\abovecaptionskip \sbox\@tempboxa{#1: \emph{#2}}% \ifdim \wd\@tempboxa >\hsize #1: \emph{#2}\par \else \hbox to\hsize{\hfil\box\@tempboxa\hfil}% \fi \vskip\belowcaptionskip} % %%% Other useful macros \def\fmslash{\@ifnextchar[{\fmsl@sh}{\fmsl@sh[0mu]}} \def\fmsl@sh[#1]#2{% \mathchoice {\@fmsl@sh\displaystyle{#1}{#2}}% {\@fmsl@sh\textstyle{#1}{#2}}% {\@fmsl@sh\scriptstyle{#1}{#2}}% {\@fmsl@sh\scriptscriptstyle{#1}{#2}}} \def\@fmsl@sh#1#2#3{\m@th\ooalign{$\hfil#1\mkern#2/\hfil$\crcr$#1#3$}} \makeatother % Labelling command for Feynman graphs generated by package FEYNMF %\def\fmfL(#1,#2,#3)#4{\put(#1,#2){\makebox(0,0)[#3]{#4}}} %END LATEX %%%% Environment for showing user input and program response \newenvironment{interaction}% {\begingroup\small \Verbatim}% {\endVerbatim \endgroup\noindent} %BEGIN LATEX %%%% Environment for typesetting listings verbatim \newenvironment{code}% {\begingroup\footnotesize \quote \Verbatim}% {\endVerbatim \endquote \endgroup\noindent} %%%% Boxed environment for typesetting listings verbatim \newenvironment{Code}% {\begingroup\footnotesize \quote \Verbatim[frame=single]}% {\endVerbatim \endquote \endgroup\noindent} %%% Environment for displaying syntax \newenvironment{syntax}% {\begin{quote} \begin{flushleft}\tt}% {\end{flushleft} \end{quote}} \newcommand{\var}[1]{$\langle$\textit{#1}$\rangle$} %END LATEX %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% % Macros specific for this paper %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \newcommand{\ttt}[1]{\texttt{#1}} \newcommand{\whizard}{\ttt{WHIZARD}} \newcommand{\oMega}{\ttt{O'Mega}} \newcommand{\vamp}{\ttt{VAMP}} \newcommand{\vamptwo}{\ttt{VAMP2}} \newcommand{\vegas}{\ttt{VEGAS}} \newcommand{\madgraph}{\ttt{MadGraph}} \newcommand{\CalcHep}{\ttt{CalcHep}} \newcommand{\helas}{\ttt{HELAS}} \newcommand{\herwig}{\ttt{HERWIG}} \newcommand{\isajet}{\ttt{ISAJET}} \newcommand{\pythia}{\ttt{PYTHIA}} \newcommand{\pythiasix}{\ttt{PYTHIA6}} \newcommand{\pythiaeight}{\ttt{PYTHIA8}} \newcommand{\jetset}{\ttt{JETSET}} \newcommand{\comphep}{\ttt{CompHEP}} \newcommand{\circe}{\ttt{CIRCE}} \newcommand{\circeone}{\ttt{CIRCE1}} \newcommand{\circetwo}{\ttt{CIRCE2}} \newcommand{\gamelan}{\textsf{gamelan}} \newcommand{\stdhep}{\ttt{STDHEP}} \newcommand{\lcio}{\ttt{LCIO}} \newcommand{\pdflib}{\ttt{PDFLIB}} \newcommand{\lhapdf}{\ttt{LHAPDF}} \newcommand{\hepmc}{\ttt{HepMC}} \newcommand{\fastjet}{\ttt{FastJet}} \newcommand{\hoppet}{\ttt{HOPPET}} \newcommand{\metapost}{\ttt{MetaPost}} \newcommand{\sarah}{\ttt{SARAH}} \newcommand{\spheno}{\ttt{SPheno}} \newcommand{\Mathematica}{\ttt{Mathematica}} \newcommand{\FeynRules}{\ttt{FeynRules}} \newcommand{\UFO}{\ttt{UFO}} \newcommand{\gosam}{\ttt{Gosam}} \newcommand{\openloops}{\ttt{OpenLoops}} \newcommand{\recola}{\ttt{Recola}} \newcommand{\collier}{\ttt{Collier}} \newcommand{\powheg}{\ttt{POWHEG}} %%%%% \newcommand{\sindarin}{\ttt{SINDARIN}} \newcommand{\cpp}{\ttt{C++}} \newcommand{\fortran}{\ttt{Fortran}} \newcommand{\fortranSeventySeven}{\ttt{FORTRAN77}} \newcommand{\fortranNinetyFive}{\ttt{Fortran95}} \newcommand{\fortranOThree}{\ttt{Fortran2003}} \newcommand{\ocaml}{\ttt{OCaml}} \newcommand{\python}{\ttt{Python}} \newenvironment{commands}{\begin{quote}\tt}{\end{quote}} \newcommand{\eemm}{$e^+e^- \to \mu^+\mu^-$} %\def\~{$\sim$} \newcommand{\sgn}{\mathop{\rm sgn}\nolimits} \newcommand{\GeV}{\textrm{GeV}} \newcommand{\fb}{\textrm{fb}} \newcommand{\ab}{\textrm{ab}} \newenvironment{parameters}{% \begin{center} \begin{tabular}{lccp{65mm}} \hline Parameter & Value & Default & Description \\ \hline }{% \hline \end{tabular} \end{center} } \newenvironment{options}{% \begin{center} \begin{tabular}{llcp{80mm}} \hline Option & Long version & Value & Description \\ \hline }{% \hline \end{tabular} \end{center} } %BEGIN LATEX \renewenvironment{options}{% \begin{center} \tablehead{\hline Option & Long version & Value & Description \\ \hline } \begin{supertabular}{llcp{80mm}} }{% \hline \end{supertabular} \end{center} } %END LATEX %BEGIN LATEX \renewenvironment{parameters}{% \begin{center} \tablehead{\hline Parameter & Value & Default & Description \\ \hline } \begin{supertabular}{lccp{65mm}} }{% \hline \end{supertabular} \end{center} } %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %END LATEX \newcommand{\thisversion}{2.8.3} %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \begin{document} %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %BEGIN LATEX \preprintno{} %%%\preprintno{arXiv:0708.4233 (also based on LC-TOOL-2001-039 (revised))} %END LATEX \title{% %HEVEA WHIZARD 2.8 \\ %BEGIN LATEX \ttt{\huge WHIZARD 2.8} \\[\baselineskip] %END LATEX A generic \\ Monte-Carlo integration and event generation package \\ for multi-particle processes\\[\baselineskip] MANUAL \footnote{% This work is supported by Helmholtz-Alliance ``Physics at the Terascale''. In former stages this work has also been supported by the Helmholtz-Gemeinschaft VH--NG--005 \\ E-mail: \ttt{whizard@desy.de} } \\[\baselineskip] } % \def\authormail{\ttt{kilian@physik.uni-siegen.de}, % \ttt{ohl@physik.uni-wuerzburg.de}, % \ttt{juergen.reuter@desy.de}, \ttt{cnspeckn@googlemail.com}} \author{% Wolfgang Kilian,% Thorsten Ohl,% J\"urgen Reuter,% with contributions from Fabian Bach, % Simon Bra\ss, Bijan Chokouf\'{e} Nejad, % Christian Fleper, % Vincent Rothe, % Sebastian Schmidt, % Marco Sekulla, % Christian Speckner, % So Young Shim, % Florian Staub, % Christian Weiss} %BEGIN LATEX \address{% Universit\"at Siegen, Emmy-Noether-Campus, Walter-Flex-Str. 3, D--57068 Siegen, Germany \\ Universit\"at W\"urzburg, Emil-Hilb-Weg 22, D--97074 W\"urzburg, Germany \\ Deutsches Elektronen-Synchrotron DESY, Notkestr. 85, D--22603 Hamburg, Germany \\ %% \authormail \vspace{1cm} \begin{center} \includegraphics[width=4cm]{Whizard-Logo} \end{center} \mbox{} \\ \vspace{2cm} \mbox{} when using \whizard\ please cite: \\ W. Kilian, T. Ohl, J. Reuter, \\ {\em WHIZARD: Simulating Multi-Particle Processes at LHC and ILC}, \\ Eur.Phys.J.{\bf C71} (2011) 1742, arXiv: 0708.4233 [hep-ph]; \\ M. Moretti, T. Ohl, J. Reuter, \\ {\em O'Mega: An Optimizing Matrix Element Generator}, \\ arXiv: hep-ph/0102195 } %END LATEX %BEGIN LATEX \abstract{% \whizard\ is a program system designed for the efficient calculation of multi-particle scattering cross sections and simulated event samples. The generated events can be written to file in various formats (including HepMC, LHEF, STDHEP, LCIO, and ASCII) or analyzed directly on the parton or hadron level using a built-in \LaTeX-compatible graphics package. \\[\baselineskip] Complete tree-level matrix elements are generated automatically for arbitrary partonic multi-particle processes by calling the built-in matrix-element generator \oMega. Beyond hard matrix elements, \whizard\ can generate (cascade) decays with complete spin correlations. Various models beyond the SM are implemented, in particular, the MSSM is supported with an interface to the SUSY Les Houches Accord input format. Matrix elements obtained by alternative methods (e.g., including loop corrections) may be interfaced as well. \\[\baselineskip] The program uses an adaptive multi-channel method for phase space integration, which allows to calculate numerically stable signal and background cross sections and generate unweighted event samples with reasonable efficiency for processes with up to eight and more final-state particles. Polarization is treated exactly for both the initial and final states. Quark or lepton flavors can be summed over automatically where needed. \\[\baselineskip] For hadron collider physics, we ship the package with the most recent PDF sets from the MSTW/MMHT and CTEQ/CT10/CJ12/CJ15/CT14 collaborations. Furthermore, an interface to the \lhapdf\ library is provided. \\[\baselineskip] For Linear Collider physics, beamstrahlung (\circeone, \circetwo), Compton and ISR spectra are included for electrons and photons, including the most recent ILC and CLIC collider designs. Alternatively, beam-crossing events can be read directly from file. \\[\baselineskip] For parton showering and matching/merging with hard matrix elements , fragmenting and hadronizing the final state, a first version of two different parton shower algorithms are included in the \whizard\ package. This also includes infrastructure for the MLM matching and merging algorithm. For hadronization and hadronic decays, \pythia\ and \herwig\ interfaces are provided which follow the Les Houches Accord. In addition, the last and final version of (\fortran) \pythia\ is included in the package. \\[\baselineskip] The \whizard\ distribution is available at %%% \begin{center} %%% \ttt{http://whizard.event-generator.org} %%% \end{center} %%% or at \begin{center} \url{https://whizard.hepforge.org} \end{center} where also the \ttt{svn} repository is located. } %END LATEX % \maketitle %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%% Text %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %\begin{fmffile} \tableofcontents \newpage \chapter{Introduction} \section{Disclaimer} \emph{This is a preliminary version of the WHIZARD manual. Many parts are still missing or incomplete, and some parts will be rewritten and improved soon. To find updated versions of the manual, visit the \whizard\ website} \begin{center} \hepforgepage \end{center} \emph{or consult the current version in the \ttt{svn} repository on \hepforgepage\ directly. Note, that the most recent version of the manual might contain information about features of the current \ttt{svn} version, which are not contained in the last official release version!} \emph{For information that is not (yet) written in the manual, please consult the examples in the \whizard\ distribution. You will find these in the subdirectory \ttt{share/examples} of the main directory where \whizard\ is installed. More information about the examples can be found on the \whizard\ Wiki page} \begin{center} \whizardwiki . \end{center} %%%%% \clearpage \section{Overview} \whizard\ is a multi-purpose event generator that covers all parts of event generation (unweighted and weighted), either through intrinsic components or interfaces to external packages. Realistic collider environments are covered through sophisticated descriptions for beam structures at hadron colliders, lepton colliders, lepton-hadron colliders, both circular and linear machines. Other options include scattering processes e.g. for dark matter annihilation or particle decays. \whizard\ contains its in-house generator for (tree-level) high-multiplicity matrix elements, \oMega\, that supports the whole Standard Model (SM) of particle physics and basically all possibile extensions of it. QCD parton shower describe high-multiplicity partonic jet events that can be matched with matrix elements. At the moment, only hadron collider parton distribution functions (PDFs) and hadronization are handled by packages not written by the main authors. This manual is organized mainly along the lines of the way how to run \whizard: this is done through a command language, \sindarin\ (Scripting INtegration, Data Analysis, Results display and INterfaces.) Though this seems a complication at first glance, the user is rewarded with a large possibility, flexibility and versatility on how to steer \whizard. After some general remarks in the follow-up sections, in Chap.~\ref{chap:installation} we describe how to get the program, the package structure, the prerequisites, possible external extensions of the program and the basics of the installation (both as superuser and locally). Also, a first technical overview how to work with \whizard\ on single computer, batch clusters and farms are given. Furthermore, some rare uncommon possible build problems are discussed, and a tour through options for debugging, testing and validation is being made. A first dive into the running of the program is made in Chap.~\ref{chap:start}. This is following by an extensive, but rather technical introduction into the steering language \sindarin\ in Chap.~\ref{chap:sindarinintro}. Here, the basic elements of the language like commands, statements, control structures, expressions and variables as well as the form of warnings and error messages are explained in detail. Chap.~\ref{chap:sindarin} contains the application of the \sindarin\ command language to the main tasks in running \whizard\ in a physics framework: the defintion of particles, subevents, cuts, and event selections. The specification of a particular physics models is \begin{figure}[t] \centering \includegraphics[width=0.9\textwidth]{whizstruct} \caption{General structure of the \whizard\ package.} \end{figure} discussed, while the next sections are devoted to the setup and compilation of code for particular processes, the specification of beams, beam structure and polarization. The next step is the integration, controlling the integration, phase space, generator cuts, scales and weights, proceeding further to event generation and decays. At the end of this chapter, \whizard's internal data analysis methods and graphical visualization options are documented. The following chapters are dedicated to the physics implemented in \whizard: methods for hard matrix interactions in Chap.~\ref{chap:hardint}. Then, in Chap.~\ref{chap:physics}, implemented methods for adaptive multi-channel integration, particularly the integrator \vamp\ are explained, together with the algorithms for the generation of the phase-space in \whizard. Finally, an overview is given over the physics models implemented in \whizard\ and its matrix element generator \oMega, together with possibilities for their extension. After that, the next chapter discusses parton showering, matching and hadronization as well as options for event normalizations and supported event formats. Also weighted event generation is explained along the lines with options for negative weights. Chap.~\ref{chap:visualization} is a stand-alone documentation of GAMELAN, the interal graphics support for the visualization of data and analysis. The next chapter, Chap.~\ref{chap:userint} details user interfaces: how to use more options of the \whizard\ command on the command line, how to use \whizard\ interactively, and how to include \whizard\ as a library into the user's own program. Then, an extensive list of examples in Chap.~\ref{chap:examples} documenting physics examples from the LEP, SLC, HERA, Tevatron, and LHC colliders to future linear and circular colliders. This chapter is a particular good reference for the beginning, as the whole chain from choosing a model, setting up processes, the beam structure, the integration, and finally simulation and (graphical) analysis are explained in detail. More technical details about efficiency, tuning and advance usage of \whizard\ are collected in Chap.~\ref{chap:tuning}. Then, Chap.~\ref{chap:extmodels} shows how to set up your own new physics model with the help of external programs like \sarah\ or \FeynRules\ program or the Universal Feynrules Output, UFO, and include it into the \whizard\ event generator. In the appendices, we e.g. give an exhaustive reference list of \sindarin\ commands and built-in variables. Please report any inconsistencies, bugs, problems or simply pose open questions to our contact \url{whizard@desy.de}. %%%%% \section{Historical remarks} This section gives a historical overview over the development of \whizard\ and can be easily skipped in a (first) reading of the manual. \whizard\ has been developed in a first place as a tool for the physics at the then planned linear electron-positron collider TESLA around 1999. The intention was to have a tool at hand to describe electroweak physics of multiple weak bosons and the Higgs boson as precise as possible with full matrix elements. Hence, the acronym: \ttt{WHiZard}, which stood for $\mathbf{W}$, {\bf H}iggs, $\mathbf{Z}$, {\bf a}nd {\bf r}espective {\bf d}ecays. Several components of the \whizard\ package that are also available as independent sub-packages have been published already before the first versions of the \whizard\ generator itself: the multi-channel adaptive Monte-Carlo integration package \vamp\ has been released mid 1998~\cite{VAMP}. The dedicated packages for the simulation of linear lepton collider beamstrahlung and the option for a photon collider on Compton backscattering (\ttt{CIRCE1/2}) date back even to mid 1996~\cite{CIRCE}. Also parts of the code for \whizard's internal graphical analysis (the \gamelan\ module) came into existence already around 1998. After first inofficial versions, the official version 1 of \whizard\ was release in the year 2000. The development, improvement and incorporation of new features continued for roughly a decade. Major milestones in the development were the full support of all kinds of beyond the Standard Model (BSM) models including spin 3/2 and spin 2 particles and the inclusion of the MSSM, the NMSSM, Little Higgs models and models for anomalous couplings as well as extra-dimensional models from version 1.90 on. In the beginning, several methods for matrix elements have been used, until the in-house matrix element generator \oMega\ became available from version 1.20 on. It was included as a part of the \whizard\ package from version 1.90 on. The support for full color amplitudes came with version 1.50, but in a full-fledged version from 2.0 on. Version 1.40 brought the necessary setups for all kinds of collider environments, i.e. asymmetric beams, decay processes, and intrinsic $p_T$ in structure functions. Version 2.0 was released in April 2010 as an almost complete rewriting of the original code. It brought the construction of an internal density-matrix formalism which allowed the use of factorized production and (cascade) decay processes including complete color and spin correlations. Another big new feature was the command-line language \sindarin\ for steering all parts of the program. Also, many performance improvement have taken place in the new release series, like OpenMP parallelization, speed gain in matrix element generation etc. Version 2.2 came out in May 2014 as a major refactoring of the program internals but keeping (almost everywhere) the same user interface. New features are inclusive processes, reweighting, and more interfaces for QCD environments (BLHA/HOPPET). The following tables shows some of the major steps (physics implementation and/or technical improvements) in the development of \whizard: \begin{center} \begin{tabular}{|l|l|l|}\hline 0.99 & 08/1999 & Beta version \\\hline 1.00 & 12/2000 & First public version \\\hline 1.10 & 03/2001 & Libraries; \pythiasix\ interface \\ 1.11 & 04/2001 & PDF support; anomalous couplings \\ \hline 1.20 & 02/2002 & \oMega\ matrix elements; \ttt{CIRCE} support\\ 1.22 & 03/2002 & QED ISR; beam remnants, phase space improvements \\ 1.25 & 05/2003 & MSSM; weighted events; user-code plug-in \\ 1.28 & 04/2004 & Improved phase space; SLHA interface; signal catching \\\hline 1.30 & 09/2004 & Major technical overhaul \\\hline 1.40 & 12/2004 & Asymmetric beams; decays; $p_T$ in structure functions \\\hline 1.50 & 02/2006 & QCD support in \oMega\ (color flows); LHA format \\ 1.51 & 06/2006 & $Hgg$, $H\gamma\gamma$; Spin 3/2 + 2; BSM models \\\hline 1.90 & 11/2007 & \oMega\ included; LHAPDF support; $Z'$; $WW$ scattering \\ 1.92 & 03/2008 & LHE format; UED; parton shower beta version \\ 1.93 & 04/2009 & NMSSM; SLHA2 accord; improved color/flavor sums \\ 1.95 & 02/2010 & MLM matching; development stop in version 1 \\ 1.97 & 05/2011 & Manual for version 1 completed. \\\hline\hline %%% \end{tabular} %%% \end{center} %%% \begin{center} %%% \begin{tabular}{|l|l|l|}\hline 2.0.0 & 04/2010 & Major refactoring: automake setup; dynamic libraries \\ & & improved speed; cascades; OpenMP; \sindarin\ steering language \\ 2.0.3 & 07/2010 & QCD ISR+FSR shower; polarized beams \\ 2.0.5 & 05/2011 & Builtin PDFs; static builds; relocation scripts \\ 2.0.6 & 12/2011 & Anomalous top couplings; unit tests \\\hline 2.1.0 & 06/2012 & Analytic ISR+FSR parton shower; anomalous Higgs couplings \\\hline 2.2.0 & 05/2014 & Major technical refactoring: abstract object-orientation; THDM; \\ & & reweighting; LHE v2/3; BLHA; HOPPET interface; inclusive processes \\ 2.2.1 & 05/2014 & CJ12 PDFs; FastJet interface \\ 2.2.2 & 07/2014 & LHAPDF6 support; correlated LC beams; GuineaPig interface \\ 2.2.3 & 11/2014 & O'Mega virtual machine; lepton collider top pair threshold; Higgs singlet extension \\ 2.2.4 & 02/2015 & LCIO support; progress on NLO; many technical bug fixes \\ 2.2.7 & 08/2015 & progress on POWHEG; fixed-order NLO events; revalidation of ILC event chain \\ 2.2.8 & 11/2015 & support for quadruple precision; StdHEP included; SM dim 6 operators supported \\\hline 2.3.0 & 07/2016 & NLO: resonance mappings for FKS subtraction; more advanced cascade syntax; \\ & & GUI ($\alpha$ version); UFO support ($\alpha$ version); ILC v1.9x-v2.x final validation \\ 2.3.1 & 08/2016 & Complex mass scheme \\\hline 2.4.0 & 11/2016 & Refactoring of NLO setup \\ 2.4.1 & 03/2017 & $\alpha$ version of new VEGAS implementation \\\hline 2.5.0 & 05/2017 & Full UFO support (SM-like models) \\\hline 2.6.0 & 09/2017 & MPI parallel integration and event generation; resonance histories \\ & & for showers; RECOLA support \\ 2.6.1 & 11/2017 & EPA/ISR transverse distributions, handling of shower resonances; \\ & & more efficient (alternative) phase space generation \\ 2.6.2 & 12/2017 & $Hee$ coupling, improved resonance matching \\ 2.6.3 & 02/2018 & Partial NLO refactoring for quantum numbers, unified RECOLA 1/2 interface. \\ 2.6.4 & 08/2018 & Gridpack functionality; Bug fixes: color flows, HSExt model, MPI setup \\\hline 2.7.0 & 01/2019 & PYTHIA8 interface, process setup refactoring, RAMBO PS option; \\ & & \quad gfortran 5.0+ necessary \\\hline 2.8.0 & 08/2019 & (Almost) complete UFO support, general Lorentz structures, n-point vertices \\ 2.8.1 & 09/2019 & HepMC3, NLO QCD pp (almost) complete, b/c jet selection, photon isolation \\ 2.8.2 & 10/2019 & Support for OCaml $\geq$ 4.06.0, UFO Spin-2 support, LCIO alternative weights \\\hline \end{tabular} \end{center} \vspace{.5cm} For a detailed overview over the historical development of the code confer the \ttt{ChangeLog} file and the commit messages in our revision control system repository. %%%%% \section{About examples in this manual} Although \whizard\ has been designed as a Monte Carlo event generator for LHC physics, several elementary steps and aspects of its usage throughout the manual will be demonstrated with the famous textbook example of $e^+e^- \to \mu^+ \mu^-$. This is the same process, the textbook by Peskin/Schroeder \cite{PeskinSchroeder} uses as a prime example to teach the basics of quantum field theory. We use this example not because it is very special for \whizard\ or at the time being a relevant physics case, but simply because it is the easiest fundamental field theoretic process without the complications of structured beams (which can nevertheless be switched on like for ISR and beamstrahlung!), the need for jet definitions/algorithms and flavor sums; furthermore, it easily accomplishes a demonstration of polarized beams. After the basics of \whizard\ usage have been explained, we move on to actual physics cases from LHC (or Tevatron). \newpage \chapter{Installation} \label{chap:installation} \section{Package Structure} \whizard\ is a software package that consists of a main executable program (which is called \ttt{whizard}), libraries, auxiliary executable programs, and machine-independent data files. The whole package can be installed by the system administrator, by default, on a central location in the file system (\ttt{/usr/local} with its proper subdirectories). Alternatively, it is possible to install it in a user's home directory, without administrator privileges, or at any other location. A \whizard\ run requires a workspace, i.e., a writable directory where it can put generated code and data. There are no constraints on the location of this directory, but we recommend to use a separate directory for each \whizard\ project, or even for each \whizard\ run. Since \whizard\ generates the matrix elements for scattering and decay processes in form of \fortran\ code that is automatically compiled and dynamically linked into the running program, it requires a working \fortran\ compiler not just for the installation, but also at runtime. The previous major version \whizard1 did put more constraints on the setup. In a nutshell, not just the matrix element code was compiled at runtime, but other parts of the program as well, so the whole package was interleaved and had to be installed in user space. The workflow was controlled by \ttt{make} and PERL scripts. These constraints are gone in the present version in favor of a clean separation of installation and runtime workspace. \section{\label{sec:prerequisites}Prerequisites} \subsection{No Binary Distribution} \whizard\ is currently not distributed as a binary package, nor is it available as a debian or RPM package. This might change in the future. However, compiling from source is very simple (see below). Since the package needs a compiler also at runtime, it would not work without some development tools installed on the machine, anyway. Note, however, that we support an install script, that downloads all necessary prerequisites, and does the configuration and compilation described below automatically. This is called the ``instant WHIZARD'' and is accessible through the WHIZARD webpage from version 2.1.1 on: \url{https://whizard.hepforge.org/versions/install/install-whizard-2.X.X.sh}. Download this shell script, make it executable by \begin{interaction} chmod +x install-whizard-2.X.X.sh \end{interaction} and execute it. Note that this also involves compilation of the required \ttt{Fortran} compiler which takes 1-3 hours depending on your system. \ttt{Darwin} operating systems (a.k.a. as \ttt{Mac OS X}) have a very similar general system for all sorts of software, called \ttt{MacPorts} (\url{http://www.macports.org}). This offers to install \whizard\ as one of its software ports, and is very similar to ``instant WHIZARD'' described above. \subsection{Tarball Distribution} This is the recommended way of obtaining \whizard. You may download the current stable distribution from the \whizard\ webpage, hosted at the HepForge webpage \begin{quote} \hepforgepage \end{quote} The distribution is a single file, say \ttt{whizard-\thisversion.tgz} for version \thisversion. You need the additional prerequisites: \begin{itemize} \item GNU \ttt{tar} (or \ttt{gunzip} and \ttt{tar}) for unpacking the tarball. \item The \ttt{make} utility. Other standard Unix utilities (\ttt{sed}, \ttt{grep}, etc.) are usually installed by default. \item A modern \fortran\ compiler (see Sec.~\ref{sec:compilers} for details). \item The \ocaml\ system. \ocaml\ is a functional and object-oriented language. Version 4.02.3 or newer is required to compile all components of \whizard. The package is freely available either as a debian/RPM package on your system (it might be necessary to install it from the usual repositories), or you can obtain it directly from \begin{quote} \url{http://caml.inria.fr} \end{quote} and install it yourself. If desired, the package can be installed in user space without administrator privileges\footnote{ Unfortunately, the version of the \ocaml\ compiler from 3.12.0 broke backwards compatibility. Therefore, versions of \oMega/\whizard\ up to 2.0.2 only compile with older versions (3.11.x works). This has been fixed in versions 2.0.3 and later. See also Sec.~\ref{sec:buildproblems}. \whizard\ versions up to 2.7.1 were still backwards compatible with \ocaml\ 3.12.0}. \end{itemize} The following optional external packages are not required, but used for certain purposes. Make sure to check whether you will need any of them, before you install \whizard. \begin{itemize} \item \LaTeX\ and \metapost\ for data visualization. Both are part of the \TeX\ program family. These programs are not absolutely necessary, but \whizard\ will lack the tools for visualization without them. \item The \lhapdf\ structure-function library. See Sec.~\ref{sec:lhapdf_install}. \item The \hoppet\ structure-function matching tool. See Sec.~\ref{sec:hoppet}. \item The \hepmc\ event-format package. See Sec.~\ref{sec:hepmc}. \item The \fastjet\ jet-algorithm package. See Sec.~\ref{sec:fastjet}. \item The \lcio\ event-format package. See Sec.~\ref{sec:lcio}. \end{itemize} Until version v2.2.7 of \whizard, the event-format package \stdhep\ used to be available as an external package. As their distribution is frozen with the final version v5.06.01, and it used to be notoriously difficult to compile and link \stdhep\ into \whizard, it was decided to include \stdhep\ into \whizard. This is the case from version v2.2.8 of \whizard\ on. Linking against an external version of \stdhep\ is precluded from there on. Nevertheless, we list some explanations in Sec.~\ref{sec:stdhep}, particularly on the need to install the \ttt{libtirpc} headers for the legacy support of this event format. Once these prerequisites are met, you may unpack the package in a directory of your choice \begin{quote}\small\tt some-directory> tar xzf whizard-\thisversion.tgz \end{quote} and proceed.\footnote{Without GNU \ttt{tar}, this would read \ttt{\small gunzip -c whizard-\thisversion.tgz | tar xz -}} For using external physics models that are directly supported by \whizard\ and \oMega, the user can use tools like \sarah\ or \FeynRules. There installation and linking to \whizard\ will be explained in Chap.~\ref{chap:extmodels}. Besides this, also new models can be conveniently included via \UFO\ files, which will be explained as well in that chapter. The directory will then contain a subdirectory \ttt{whizard-\thisversion} where the complete source tree is located. To update later to a new version, repeat these steps. Each new version will unpack in a separate directory with the appropriate name. \subsection{SVN Repository Version} If you want to install the latest development version, you have to check it out from the \whizard\ SVN repository. In addition to the prerequisites listed in the previous section, you need: \begin{itemize} \item The \ttt{subversion} package (\ttt{svn}), the tool for dealing with SVN repositories. \item The \ttt{autoconf} package, part of the \ttt{autotools} development system. \ttt{automake} is needed with version \ttt{1.12.2} or newer. \item The \ttt{noweb} package, a light-weight tool for literate programming. This package is nowadays often part of Linux distributions\footnote{In Ubuntu from version 10.04 on, and in Debian since squeeze. For \ttt{Mac OS X}, \ttt{noweb} is available via the \ttt{MacPorts} system.}. You can obtain the source code from\footnote{Please, do not use any of the binary builds from this webpage. Probably all of them are quite old and broken.} \begin{quote} \url{http://www.cs.tufts.edu/~nr/noweb/} \end{quote} \end{itemize} To start, go to a directory of your choice and execute \begin{interaction} your-src-directory> svn checkout svn+ssh://vcs@phab.hepforge.org/source/whizardsvn/trunk \;\; . \end{interaction} Note that for the time being after the HepForge system modernization early September 2018, a HepForge account with a local ssl key is necessary to checkout the subversion repository. This is enforced by the phabricator framework of HepForge, and will hopefully be relaxed in the future. The SVN source tree will appear in the current directory. To update later, you just have to execute \begin{interaction} your-src-directory> svn update \end{interaction} within that directory. After checking out the sources, you first have to create \ttt{configure.ac} by executing the shell script \ttt{build\_master.sh}. In order to build the \ttt{configure} script, the \ttt{autotools} package \ttt{autoreconf} has to be run. On some \ttt{Unix} systems the \ttt{RPC} headers needed for the legacy support of the \stdhep\ event format are provided by the \ttt{TIRPC} library (cf. Sec.~\ref{sec:stdhep}). To easily check for them, \ttt{configure.ac} processed by \ttt{autoreconf} makes use of the \ttt{pkg-config} tool which needs to be installed for the developer version. So now, run\footnote{At least, version 2.65 of the \ttt{autoconf} package is required.} \begin{interaction} your-src-directory> autoreconf \end{interaction} This will generate a \ttt{configure} script. \subsection{\label{sec:compilers}Fortran Compilers} \whizard\ is written in modern \fortran. To be precise, it uses a subset of the \fortranOThree\ standard. At the time of this writing, this subset is supported by, at least, the following compilers: \begin{itemize} \item \ttt{gfortran} (GNU, Open Source). You will need version 5.1.0 or higher\footnote{Note that \whizard\ versions 2.0.0 until 2.3.1 compiled with \ttt{gfortran} 4.7.4, but the object-oriented refactoring of the \whizard\ code from 2.4.0 on until version 2.6.5 made a switch to \ttt{gfortran} 4.8.4 or higher necessary. In the same way, since version 2.7.0, \ttt{gfortran} 5.1.0 or newer is needed}. We recommend to use at least version 5.4 or higher, as especially the the early version of the \texttt{gfortran} experience some bugs. \ttt{gfortran} 6.5.0 has a severe regression and cannot be used. \item \ttt{nagfor} (NAG). You will need version 6.2 or higher. \item \ttt{ifort} (Intel). You will need version 19.0.2 or higher \end{itemize} %%%%% \subsection{LHAPDF} \label{sec:lhapdf_install} For computing scattering processes at hadron colliders such as the LHC, \whizard\ has a small set of standard structure-function parameterizations built in, cf.\ Sec.~\ref{sec:built-in-pdf}. For many applications, this will be sufficient, and you can skip this section. However, if you need structure-function parameterizations that are not in the default set (e.g. PDF error sets), you can use the \lhapdf\ structure-function library, which is an external package. It has to be linked during \whizard\ installation. For use with \whizard, version 5.3.0 or higher of the library is required\footnote{ Note that PDF sets which contain photons as partons are only supported with \whizard\ for \lhapdf\ version 5.7.1 or higher}. The \lhapdf\ package has undergone a major rewriting from \fortran\ version 5 to \ttt{C++} version 6. While still maintaining the interface for the \lhapdf\ version 5 series, from version 2.2.2 of \whizard\ on, the new release series of \lhapdf, version 6.0 and higher, is also supported. If \lhapdf\ is not yet installed on your system, you can download it from \begin{quote} \url{https://lhapdf.hepforge.org} \end{quote} for the most recent LHAPDF version 6 and newer, or \begin{quote} \url{https://lhapdf.hepforge.org/lhapdf5} \end{quote} for version 5 and older, and install it. The website contains comprehensive documentation on the configuring and installation procedure. Make sure that you have downloaded and installed not just the package, but also the data sets. Note that \lhapdf\ version 5 needs both a \fortran\ and a \ttt{C++} compiler. During \whizard\ configuration, \whizard\ looks for the script \ttt{lhapdf} (which is present in \lhapdf\ series 6) first, and then for \ttt{lhapdf-config} (which is present since \lhapdf\ version 4.1.0): if those are in an executable path (or only the latter for \lhapdf\ version 5), the environment variables for \lhapdf\ are automatically recognized by \whizard, as well as the version number. This should look like this in the \ttt{configure} output (for \lhapdf\ version 6 or newer), \begin{footnotesize} \begin{verbatim} configure: -------------------------------------------------------------- configure: --- LHAPDF --- configure: checking for lhapdf... /usr/local/bin/lhapdf checking for lhapdf-config... /usr/local/bin/lhapdf-config checking the LHAPDF version... 6.2.1 checking the major version... 6 checking the LHAPDF pdfsets path... /usr/local/share/LHAPDF checking the standard PDF sets... all standard PDF sets installed checking if LHAPDF is functional... yes checking LHAPDF... yes configure: -------------------------------------------------------------- \end{verbatim} \end{footnotesize} while for \lhapdf\ version 5 and older it looks like this: \begin{footnotesize} \begin{verbatim} configure: -------------------------------------------------------------- configure: --- LHAPDF --- configure: checking for lhapdf... no checking for lhapdf-config... /usr/local/bin/lhapdf-config checking the LHAPDF version... 5.9.1 checking the major version... 5 checking the LHAPDF pdfsets path... /usr/local/share/lhapdf/PDFsets checking the standard PDF sets... all standard PDF sets installed checking for getxminm in -lLHAPDF... yes checking for has_photon in -lLHAPDF... yes configure: -------------------------------------------------------------- \end{verbatim} \end{footnotesize} If you want to use a different \lhapdf\ (e.g. because the one installed on your system by default is an older one), the preferred way to do so is to put the \ttt{lhapdf} (and/or \ttt{lhapdf-config}) scripts in an executable path that is checked before the system paths, e.g. \ttt{/bin}. For the old series, \lhapdf\ version 5, a possible error could arise if \lhapdf\ had been compiled with a different \fortran\ compiler than \whizard, and if the run-time library of that \fortran\ compiler had not been included in the \whizard\ configure process. The output then looks like this: \begin{footnotesize} \begin{verbatim} configure: -------------------------------------------------------------- configure: --- LHAPDF --- configure: checking for lhapdf... no checking for lhapdf-config... /usr/local/bin/lhapdf-config checking the LHAPDF version... 5.9.1 checking the major version... 5 checking the LHAPDF pdfsets path... /usr/local/share/lhapdf/PDFsets checking for standard PDF sets... all standard PDF sets installed checking for getxminm in -lLHAPDF... no checking for has_photon in -lLHAPDF... no configure: -------------------------------------------------------------- \end{verbatim} \end{footnotesize} So, the \whizard\ configure found the \lhapdf\ distribution, but could not link because it could not resolve the symbols inside the library. In case of failure, for more details confer the \ttt{config.log}. If \lhapdf\ is installed in a non-default directory where \whizard\ would not find it, set the environment variable \ttt{LHAPDF\_DIR} to the correct installation path when configuring \whizard. The check for the standard PDF sets are those sets that are used in the default \whizard\ self tests in the case \lhapdf\ is enabled and correctly linked. If some of them are missing, then this test will result in a failure. They are the \ttt{CT10} set for \lhapdf\ version 6 (for version 5, \ttt{cteq61.LHpdf}, \ttt{cteq6ll.LHpdf}, \ttt{cteq5l.LHgrid}, and \ttt{GSG961.LHgrid} are demanded). If you want to use \lhapdf\ inside \whizard\ please install them such that \whizard\ could perform all its sanity checks with them. The last check is for the \ttt{has\_photon} flag, which tests whether photon PDFs are available in the found \lhapdf\ installation. %%%%% \subsection{HOPPET} \label{sec:hoppet} \hoppet\ (not Hobbit) is a tool for the QCD DGLAP evolution of PDFs for hadron colliders. It provides possibilities for matching algorithms for 4- and 5-flavor schemes, that are important for precision simulations of $b$-parton initiated processes at hadron colliders. If you are not interested in those features, you can skip this section. Note that this feature is not enabled by default (unlike e.g. \lhapdf), but has to be explicitly during the configuration (see below): \begin{interaction} your-build-directory> your-src-directory/configure --enable-hoppet \end{interaction} If you \ttt{configure} messages like the following: \begin{footnotesize} \begin{verbatim} configure: -------------------------------------------------------------- configure: --- HOPPET --- configure: checking for hoppet-config... /usr/local/bin/hoppet-config checking for hoppetAssign in -lhoppet_v1... yes checking the HOPPET version... 1.2.0 configure: -------------------------------------------------------------- \end{verbatim} \end{footnotesize} then you know that \hoppet\ has been found and was correctly linked. If that is not the case, you have to specify the location of the \hoppet\ library, e.g. by adding \begin{interaction} HOPPET=/lib \end{interaction} to the \ttt{configure} options above. For more details, please confer the \hoppet\ manual. %%%%% \subsection{HepMC} \label{sec:hepmc} With version 2.8.1, \whizard\ supports both the "classical" version 2 as well as the newly designed version 3 (release 2019). The configure step can successfully recognize the two different versions, the user do not have to specify which version is installed. \hepmc\ is a \ttt{C++} class library for handling collider scattering events. In particular, it provides a portable format for event files. If you want to use this format, you should link \whizard\ with \hepmc, otherwise you can skip this section. If it is not already installed on your system, you may obtain \hepmc\ from one of these two webpages: \begin{quote} \url{http://hepmc.web.cern.ch/hepmc/} \end{quote} or \begin{quote} \url{http://hepmc.web.cern.ch/hepmc/} \end{quote} If the \hepmc\ library is linked with the installation, \whizard\ is able to read and write files in the \hepmc\ format. Detailed information on the installation and usage can be found on the \hepmc\ homepage. We give here only some brief details relevant for the usage with \whizard: For the compilation of HepMC one needs a \ttt{C++} compiler. Then the procedure is the same as for the \whizard\ package, namely configure HepMC: \begin{interaction} configure --with-momentum=GEV --with-length=MM --prefix= \end{interaction} Note that the particle momentum and decay length flags are mandatory, and we highly recommend to set them to the values \ttt{GEV} and \ttt{MM}, respectively. After configuration, do \ttt{make}, an optional \ttt{make check} (which might sometimes fail for non-standard values of momentum and length), and finally \ttt{make install}. The latest version of \hepmc\ (2.6.10) as well as the new relase series use \texttt{cmake} for their build process. For more information, confer the \hepmc\ webpage. A \whizard\ configuration for HepMC looks like this: \begin{footnotesize} \begin{verbatim} configure: -------------------------------------------------------------- configure: --- HepMC --- configure: checking for HepMC-config... no checking HepMC3 or newer... no configure: HepMC3 not found, incompatible, or HepMC-config not found configure: looking for HepMC2 instead ... checking the HepMC version... 2.06.10 checking for GenEvent class in -lHepMC... yes configure: -------------------------------------------------------------- \end{verbatim} \end{footnotesize} If \hepmc\ is installed in a non-default directory where \whizard\ would not find it, set the environment variable \ttt{HEPMC\_DIR} to the correct installation path when configuring \whizard. Furthermore, the environment variable \ttt{CXXFLAGS} allows you to set specific \ttt{C/C++} preprocessor flags, e.g. non-standard include paths for header files. %%%%% \subsection{PYTHIA8} \label{sec:pythia8} \emph{NOTE: This is at the moment not yet supported, but merely a stub with the only purpose to be recognized by the build system.} \pythiaeight\ is a \ttt{C++} class library for handling hadronization, showering and underlying event. If you want to use this feature (once it is fully supported in \whizard), you should link \whizard\ with \pythiaeight, otherwise you can skip this section. If it is not already installed on your system, you may obtain \pythiaeight\ from \begin{quote} \url{http://home.thep.lu.se/~torbjorn/Pythia.html} \end{quote} If the \pythiaeight\ library is linked with the installation, \whizard\ will be able to use its hadronization and showering, once this is fully supported within \whizard. To link a \pythiaeight\ installation to \whizard, you should specify the flag \begin{quote} \ttt{--enable-pythia8} \end{quote} to \ttt{configure}. If \pythiaeight\ is installed in a non-default directory where \whizard\ would not find it, specify also \begin{quote} \ttt{--with-pythia8=\emph{}} \end{quote} A successful \whizard\ configuration should produce a screen output similar to this: \begin{footnotesize} \begin{verbatim} configure: -------------------------------------------------------------- configure: --- SHOWERS PYTHIA6 PYTHIA8 MPI --- configure: [....] checking for pythia8-config... /usr/local/bin/pythia8-config checking if PYTHIA8 is functional... yes checking PYTHIA8... yes configure: WARNING: PYTHIA8 configure is for testing purposes at the moment. configure: -------------------------------------------------------------- \end{verbatim} \end{footnotesize} %%%%% \subsection{FastJet} \label{sec:fastjet} \fastjet\ is a \ttt{C++} class library for handling jet clustering. If you want to use this feature, you should link \whizard\ with \fastjet, otherwise you can skip this section. If it is not already installed on your system, you may obtain \fastjet\ from \begin{quote} \url{http://fastjet.fr} \end{quote} If the \fastjet\ library is linked with the installation, \whizard\ is able to call the jet algorithms provided by this program for the purposes of applying cuts and analysis. To link a \fastjet\ installation to \whizard, you should specify the flag \begin{quote} \ttt{--enable-fastjet} \end{quote} to \ttt{configure}. If \fastjet\ is installed in a non-default directory where \whizard\ would not find it, specify also \begin{quote} \ttt{--with-fastjet=\emph{}} \end{quote} A successful \whizard\ configuration should produce a screen output similar to this: \begin{footnotesize} \begin{verbatim} configure: -------------------------------------------------------------- configure: --- FASTJET --- configure: checking for fastjet-config... /usr/local/bin/fastjet-config checking if FastJet is functional... yes checking FastJet... yes checking the FastJet version... 3.3.0 configure: -------------------------------------------------------------- \end{verbatim} \end{footnotesize} %%%%% \subsection{STDHEP} \label{sec:stdhep} \stdhep\ is a library for handling collider scattering events~\cite{stdhep}. In particular, it provides a portable format for event files. Until version 2.2.7 of \whizard, \stdhep\ that was maintained by Fermilab, could be linked as an externally compiled library. As the \stdhep\ package is frozen in its final release v5.06.1 and no longer maintained, it has from version 2.2.8 been included \whizard. This eases many things, as it was notoriously difficult to compile and link \stdhep\ in a way compatible with \whizard. Not the full package has been included, but only the libraries for file I/O (\ttt{mcfio}, the library for the XDR conversion), while the various translation tools for \pythia, \herwig, etc. have been abandoned. Note that \stdhep\ has largely been replaced in the hadron collider community by the \hepmc\ format, and in the lepton collider community by \lcio. \whizard\ might serve as a conversion tools for all these formats, but other tools also exist, of course. Note that the \ttt{mcfio} framework makes use of the \ttt{RPC} headers. These come -- provided by \ttt{SunOS/Oracle America, Inc.} -- together with the system headers, but on some \ttt{Unix} systems (e.g. \ttt{ArchLinux}, \ttt{Fedora}) have been replaced by the \ttt{libtirpc} headers . The \ttt{configure} script searches for these headers so these have to be installed mandatorily. If the \stdhep\ library is linked with the installation, \whizard\ is able to write files in the \stdhep\ format, the corresponding configure output notifies you that \stdhep\ is always included: \begin{footnotesize} \begin{verbatim} configure: -------------------------------------------------------------- configure: --- STDHEP --- configure: checking for pkg-config... /opt/local/bin/pkg-config checking pkg-config is at least version 0.9.0... yes checking for libtirpc... no configure: for StdHEP legacy code: using SunRPC headers and library configure: StdHEP v5.06.01 is included internally configure: -------------------------------------------------------------- \end{verbatim} \end{footnotesize} %%%%% \subsection{LCIO} \label{sec:lcio} \lcio\ is a \ttt{C++} class library for handling collider scattering events. In particular, it provides a portable format for event files. If you want to use this format, you should link \whizard\ with \lcio, otherwise you can skip this section. If it is not already installed on your system, you may obtain \lcio\ from: \begin{quote} \url{http://lcio.desy.de} \end{quote} If the \lcio\ library is linked with the installation, \whizard\ is able to read and write files in the \lcio\ format. Detailed information on the installation and usage can be found on the \lcio\ homepage. We give here only some brief details relevant for the usage with \whizard: For the compilation of \lcio\ one needs a \ttt{C++} compiler. \lcio\ is based on \ttt{cmake}. For the corresponding options please confer the \lcio\ manual. A \whizard\ configuration for \lcio\ looks like this: \begin{footnotesize} \begin{verbatim} configure: -------------------------------------------------------------- configure: --- LCIO --- configure: checking the LCIO version... 2.12.1 checking for LCEventImpl class in -llcio... yes configure: -------------------------------------------------------------- \end{verbatim} \end{footnotesize} If \lcio\ is installed in a non-default directory where \whizard\ would not find it, set the environment variable \ttt{LCIO} or \ttt{LCIO\_DIR} to the correct installation path when configuring \whizard. The first one is the variable exported by the \ttt{setup.sh} script while the second one is analogous to the environment variables of other external packages. \ttt{LCIO} takes precedence over \ttt{LCIO\_DIR}. Furthermore, the environment variable \ttt{CXXFLAGS} allows you to set specific \ttt{C/C++} preprocessor flags, e.g. non-standard include paths for header files. %%%%% \section{Installation} \label{sec:installation} Once you have unpacked the source (either the tarball or the SVN version), you are ready to compile it. There are several options. \subsection{Central Installation} This is the default and recommended way, but it requires adminstrator privileges. Make sure that all prerequisites are met (Sec.~\ref{sec:prerequisites}). \begin{enumerate} \item Create a fresh directory for the \whizard\ build. It is recommended to keep this separate from the source directory. \item Go to that directory and execute \begin{interaction} your-build-directory> your-src-directory/configure \end{interaction} This will analyze your system and prepare the compilation of \whizard\ in the build directory. Make sure to set the proper options to \ttt{configure}, see Sec.~\ref{sec:configure-options} below. \item Call \ttt{make} to compile and link \whizard: \begin{interaction} your-build-directory> make \end{interaction} \item If you want to make sure that everything works, run \begin{interaction} your-build-directory> make check \end{interaction} This will take some more time. \item Become superuser and say \begin{interaction} your-build-directory> make install \end{interaction} \end{enumerate} \whizard\ should now installed in the default locations, and the executable should be available in the standard path. Try to call \ttt{whizard --help} in order to check this. \subsection{Installation in User Space} You may lack administrator privileges on your system. In that case, you can still install and run \whizard. Make sure that all prerequisites are met (Sec.~\ref{sec:prerequisites}). \begin{enumerate} \item Create a fresh directory for the \whizard\ build. It is recommended to keep this separate from the source directory. \item Reserve a directory in user space for the \whizard\ installation. It should be empty, or yet non-existent. \item Go to that directory and execute \begin{interaction} your-build-directory> your-src-directory/configure --prefix=your-install-directory \end{interaction} This will analyze your system and prepare the compilation of \whizard\ in the build directory. Make sure to set the proper additional options to \ttt{configure}, see Sec.~\ref{sec:configure-options} below. \item Call \ttt{make} to compile and link \whizard: \begin{interaction} your-build-directory> make \end{interaction} \item If you want to make sure that everything works, run \begin{interaction} your-build-directory> make check \end{interaction} This will take some more time. \item Install: \begin{interaction} your-build-directory> make install \end{interaction} \end{enumerate} \whizard\ should now be installed in the installation directory of your choice. If the installation is not in your standard search paths, you have to account for this by extending the paths appropriately, see Sec.~\ref{sec:workspace}. \subsection{Configure Options} \label{sec:configure-options} The configure script accepts environment variables and flags. They can be given as arguments to the \ttt{configure} program in arbitrary order. You may run \ttt{configure --help} for a listing; only the last part of this long listing is specific for the \whizard\ system. Here is an example: \begin{interaction} configure FC=gfortran-5.4 FCFLAGS="-g -O3" --enable-fc-openmp \end{interaction} The most important options are \begin{itemize} \item \ttt{FC} (variable): The \fortran\ compiler. This is necessary if you need a compiler different from the standard compiler on the system, e.g., if the latter is too old. \item \ttt{FCFLAGS} (variable): The flags to be given to the Fortran compiler. The main use is to control the level of optimization. \item \ttt{--prefix=\var{directory-name}}: Specify a non-default directory for installation. \item \ttt{--enable-fc-openmp}: Enable parallel executing via OpenMP on a multi-processor/multi-core machine. This works only if OpenMP is supported by the compiler (e.g., \ttt{gfortran}). When running \whizard, the number of processors that are actually requested can be controlled by the user. Without this option, \whizard\ will run in serial mode on a single core. See Sec.~\ref{sec:openmp} for further details. \item \ttt{--enable-fc-mpi}: Enable parallel executing via MPI on a single machine using several cores or several machines. This works only if a MPI library is installed (e.g. \ttt{OpenMPI}) and \ttt{FC=mpifort CC=mpicc CXX=mpic++} is set. Without this option, \whizard\ will run in serial mode on a single core. The flag can be combined with \ttt{--enable-fc-openmp}. See Sec.~\ref{sec:mpi} for further details. \item \ttt{LHADPF\_DIR} (variable): The location of the optional \lhapdf\ package, if non-default. \item \ttt{LOOPTOOLS\_DIR} (variable): The location of the optional \ttt{LOOPTOOLS} package, if non-default. \item \ttt{OPENLOOPS\_DIR} (variable): The location of the optional \openloops\ package, if non-default. \item \ttt{GOSAM\_DIR} (variable): The location of the optional \gosam\ package, if non-default. \item \ttt{HOPPET\_DIR} (variable): The location of the optional \hoppet\ package, if non-default. \item \ttt{HEPMC\_DIR} (variable): The location of the optional \hepmc\ package, if non-default. \item \ttt{LCIO}/\ttt{LCIO\_DIR} (variable): The location of the optional \lcio\ package, if non-default. \end{itemize} Other flags that might help to work around possible problems are the flags for the $C$ and $C++$ compilers as well as the \ttt{Fortran77} compiler, or the linker flags and additional libraries for the linking process. \begin{itemize} \item \ttt{CC} (variable): \ttt{C} compiler command \item \ttt{F77} (variable): \ttt{Fortran77} compiler command \item \ttt{CXX} (variable): \ttt{C++} compiler command \item \ttt{CPP} (variable): \ttt{C} preprocessor \item \ttt{CXXCPP} (variable): \ttt{C++} preprocessor \item \ttt{CFLAGS} (variable): \ttt{C} compiler flags \item \ttt{FFLAGS} (variable): \ttt{Fortran77} compiler flags \item \ttt{CXXFLAGS} (variable): \ttt{C++} compiler flags \item \ttt{LIBS} (variable): libraries to be passed to the linker as \ttt{-l{\em library}} \item \ttt{LDFLAGS} (variable): non-standard linker flags \end{itemize} For other options (like e.g. \ttt{--with-precision=...} etc.) please see the \ttt{configure --help} option. %%%%% \subsection{Details on the Configure Process} The configure process checks for the build and host system type; only if this is not detected automatically, the user would have to specify this by himself. After that system-dependent files are searched for, LaTeX and Acroread for documentation and plots, the \fortran\ compiler is checked, and finally the \ocaml\ compiler. The next step is the checks for external programs like \lhapdf\ and \ttt{HepMC}. Finally, all the Makefiles are being built. The compilation is done by invoking \ttt{make} and finally \ttt{make install}. You could also do a \ttt{make check} in order to test whether the compilation has produced sane files on your system. This is highly recommended. Be aware that there be problems for the installation if the install path or a user's home directory is part of an AFS file system. Several times problems were encountered connected with conflicts with permissions inside the OS permission environment variables and the AFS permission flags which triggered errors during the \ttt{make install} procedure. Also please avoid using \ttt{make -j} options of parallel execution of \ttt{Makefile} directives as AFS filesystems might not be fast enough to cope with this. For specific problems that might have been encountered in rare circumstances for some FORTRAN compilers confer the webpage \url{https://whizard.hepforge.org/compilers.html}. Note that the \pythia\ bundle for showering and hadronization (and some other external legacy code pieces) do still contain good old \ttt{Fortran77} code. These parts should better be compiled with the very same \ttt{Fortran2003} compiler as the \whizard\ core. There is, however, one subtlety: when the \ttt{configure} flag \ttt{FC} gets a full system path as argument, \ttt{libtool} is not able to recognize this as a valid (GNU) \ttt{Fortran77} compiler. It then searches automatically for binaries like \ttt{f77}, \ttt{g77} etc. or a standard system compiler. This might result in a compilation failure of the \ttt{Fortran77} code. A viable solution is to define an executable link and use this (not the full path!) as \ttt{FC} flag. It is possible to compile \whizard\ without the \ocaml\ parts of \oMega, namely by using the \ttt{--disable-omega} option of the configure. This will result in a built of \whizard\ with the \oMega\ Fortran library, but without the binaries for the matrix element generation. All selftests (cf. \ref{sec:selftests}) requiring \oMega\ matrix elements are thereby switched off. Note that you can install such a built (e.g. on a batch system without \ocaml\ installation), but the try to build a distribution (all \ttt{make distxxx} targets) will fail. %%%%%%%%%%% \subsection{\whizard\ self tests/checks} \label{sec:selftests} \whizard\ has a number of self-consistency checks and tests which assure that most of its features are running in the intended way. The standard procedure to invoke these self tests is to perform a \ttt{make check} from the \ttt{build} directory. If \ttt{src} and \ttt{build} directories are the same, all relevant files for these self-tests reside in the \ttt{tests} subdirectory of the main \whizard\ directory. In that case, one could in principle just call the scripts individually from the command line. Note, that if \ttt{src} and \ttt{build} directory are different as recommended, then the input files will have been installed in \ttt{prefix/share/whizard/test}, while the corresponding test shell scripts remain in the \ttt{srcdir/test} directory. As the main shell script \ttt{run\_whizard.sh} has been built in the \ttt{build} directory, one now has to copy the files over by and set the correct paths by hand, if one wishes to run the test scripts individually. \ttt{make check} still correctly performs all \whizard\ self-consistency tests. The tests itself fall into two categories, unit self test that individually test the modular structure of \whizard, and tests that are run by \sindarin\ files. In future releases of \whizard, these two categories of tests will be better separated than in the 2.2.1 release. There are additional, quite extensiv numerical tests for validation and backwards compatibility checks for SM and MSSM processes. As a standard, these extended self tests are not invoked. However, they can be enabled by executing the corresponding specific \ttt{make check} operations in the subdirectories for these extensive tests. As the new \whizard\ testsuite does very thorough and scrupulous tests of the whole \whizard\ structure, it is always possible that some tests are failing due to some weird circumstances or because of numerical fluctuations. In such a case do not panic, contact the developers (\ttt{whizard@desy.de}) and provide them with the logfiles of the failing test as well as the setup of your configuration. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \clearpage \chapter{Working with \whizard} \label{chap:start} \whizard\ can run as a stand-alone program. You (the user) can steer \whizard\ either interactively or by a script file. We will first describe the latter method, since it will be the most common way to interact with the \whizard\ system. \section{Hello World} The legacy version series 1 of the program relied on a bunch of input files that the user had to provide in some obfuscated format. This approach is sufficient for straightforward applications. However, once you get experienced with a program, you start thinking about uses that the program's authors did not foresee. In case of a Monte Carlo package, typical abuses are parameter scans, complex patterns of cuts and reweighting factors, or data analysis without recourse to external packages. This requires more flexibility. Instead of transferring control over data input to some generic scripting language like PERL or PYTHON (or even C++), which come with their own peculiarities and learning curves, we decided to unify data input and scripting in a dedicated steering language that is particularly adapted to the needs of Monte-Carlo integration, simulation, and simple analysis of the results. Thus we discovered what everybody knew anyway: that W(h)izards communicate in \sindarin, Scripting INtegration, Data Analysis, Results display and INterfaces. \sindarin\ is a DSL -- a domain-specific scripting language -- that is designed for the single purpose of steering and talking to \whizard. Now since \sindarin\ is a programming language, we honor the old tradition of starting with the famous Hello World program. In \sindarin\ this reads simply \begin{quote} \begin{verbatim} printf "Hello World!" \end{verbatim} \end{quote} Open your favorite editor, type this text, and save it into a file named \verb|hello.sin|. \begin{figure} \centering \begin{scriptsize} \begin{Verbatim}[frame=single] | Writing log to 'whizard.log' |=============================================================================| | | | WW WW WW WW WW WWWWWW WW WWWWW WWWW | | WW WW WW WW WW WW WW WWWW WW WW WW WW | | WW WW WW WW WWWWWWW WW WW WW WW WWWWW WW WW | | WWWW WWWW WW WW WW WW WWWWWWWW WW WW WW WW | | WW WW WW WW WW WWWWWW WW WW WW WW WWWW | | | | | | W | | sW | | WW | | sWW | | WWW | | wWWW | | wWWWW | | WW WW | | WW WW | | wWW WW | | wWW WW | | WW WW | | WW WW | | WW WW | | WW WW | | WW WW | | WW WW | | wwwwww WW WW | | WWWWWww WW WW | | WWWWWwwwww WW WW | | wWWWwwwwwWW WW | | wWWWWWWWWWWwWWW WW | | wWWWWW wW WWWWWWW | | WWWW wW WW wWWWWWWWwww | | WWWW wWWWWWWWwwww | | WWWW WWWW WWw | | WWWWww WWWW | | WWWwwww WWWW | | wWWWWwww wWWWWW | | WwwwwwwwwWWW | | | | | | | | by: Wolfgang Kilian, Thorsten Ohl, Juergen Reuter | | with contributions from Christian Speckner | | Contact: | | | | if you use WHIZARD please cite: | | W. Kilian, T. Ohl, J. Reuter, Eur.Phys.J.C71 (2011) 1742 | | [arXiv: 0708.4233 [hep-ph]] | | M. Moretti, T. Ohl, J. Reuter, arXiv: hep-ph/0102195 | | | |=============================================================================| | WHIZARD 2.8.3 |=============================================================================| | Reading model file '/usr/local/share/whizard/models/SM.mdl' | Preloaded model: SM | Process library 'default_lib': initialized | Preloaded library: default_lib | Reading commands from file 'hello.sin' Hello World! | WHIZARD run finished. |=============================================================================| \end{Verbatim} \end{scriptsize} \caption{Output of the \ttt{"Hello world!"} \sindarin\ script.\label{fig:helloworld}} \end{figure} Now we assume that you -- or your kind system administrator -- has installed \whizard\ in your executable path. Then you should open a command shell and execute (we will come to the meaning of the \verb|-r| option later.) \begin{verbatim} /home/user$ whizard -r hello.sin \end{verbatim} and if everything works well, you get the output (the complete output including the \whizard\ banner is shown in Fig.~\ref{fig:helloworld}) \begin{footnotesize} \begin{verbatim} | Writing log to 'whizard.log' \end{verbatim} \centerline{[... here a banner is displayed]} \begin{Verbatim} |=============================================================================| | WHIZARD 2.8.3 |=============================================================================| | Reading model file '/usr/local/share/whizard/models/SM.mdl' | Preloaded model: SM ! Process library 'default_lib': initialized ! Preloaded library: default_lib | Reading commands from file 'hello.sin' Hello World! | WHIZARD run finished. |=============================================================================| \end{Verbatim} \end{footnotesize} If this has just worked for you, you can be confident that you have a working \whizard\ installation, and you have been able to successfully run the program. \section{A Simple Calculation} You may object that \whizard\ is not exactly designed for printing out plain text. So let us demonstrate a more useful example. Looking at the Hello World output, we first observe that the program writes a log file named (by default) \verb|whizard.log|. This file receives all screen output, except for the output of external programs that are called by \whizard. You don't have to cache \whizard's screen output yourself. After the welcome banner, \whizard\ tells you that it reads a physics \emph{model}, and that it initializes and preloads a \emph{process library}. The process library is initially empty. It is ready for receiving definitions of elementary high-energy physics processes (scattering or decay) that you provide. The processes are set in the context of a definite model of high-energy physics. By default this is the Standard Model, dubbed \verb|SM|. Here is the \sindarin\ code for defining a SM physics process, computing its cross section, and generating a simulated event sample in Les Houches event format: \begin{quote} \begin{Verbatim} process ee = e1, E1 => e2, E2 sqrts = 360 GeV n_events = 10 sample_format = lhef simulate (ee) \end{Verbatim} \end{quote} As before, you save this text in a file (named, e.g., \verb|ee.sin|) which is run by \begin{verbatim} /home/user$ whizard -r ee.sin \end{verbatim} (We will come to the meaning of the \verb|-r| option later.) This produces a lot of output which looks similar to this: \begin{footnotesize} \begin{verbatim} | Writing log to 'whizard.log' [... banner ...] |=============================================================================| | WHIZARD 2.8.3 |=============================================================================| | Reading model file '/usr/local/share/whizard/models/SM.mdl' | Preloaded model: SM | Process library 'default_lib': initialized | Preloaded library: default_lib | Reading commands from file 'ee.sin' | Process library 'default_lib': recorded process 'ee' sqrts = 3.600000000000E+02 n_events = 10 \end{verbatim} \begin{verbatim} | Starting simulation for process 'ee' | Simulate: process 'ee' needs integration | Integrate: current process library needs compilation | Process library 'default_lib': compiling ... | Process library 'default_lib': writing makefile | Process library 'default_lib': removing old files rm -f default_lib.la rm -f default_lib.lo default_lib_driver.mod opr_ee_i1.mod ee_i1.lo rm -f ee_i1.f90 | Process library 'default_lib': writing driver | Process library 'default_lib': creating source code rm -f ee_i1.f90 rm -f opr_ee_i1.mod rm -f ee_i1.lo /usr/local/bin/omega_SM.opt -o ee_i1.f90 -target:whizard -target:parameter_module parameters_SM -target:module opr_ee_i1 -target:md5sum '70DB728462039A6DC1564328E2F3C3A5' -fusion:progress -scatter 'e- e+ -> mu- mu+' [1/1] e- e+ -> mu- mu+ ... allowed. [time: 0.00 secs, total: 0.00 secs, remaining: 0.00 secs] all processes done. [total time: 0.00 secs] SUMMARY: 6 fusions, 2 propagators, 2 diagrams | Process library 'default_lib': compiling sources [.....] \end{verbatim} \begin{verbatim} | Process library 'default_lib': loading | Process library 'default_lib': ... success. | Integrate: compilation done | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 9616 | Initializing integration for process ee: | ------------------------------------------------------------------------ | Process [scattering]: 'ee' | Library name = 'default_lib' | Process index = 1 | Process components: | 1: 'ee_i1': e-, e+ => mu-, mu+ [omega] | ------------------------------------------------------------------------ | Beam structure: [any particles] | Beam data (collision): | e- (mass = 5.1099700E-04 GeV) | e+ (mass = 5.1099700E-04 GeV) | sqrts = 3.600000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'ee_i1.phs' | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: Using 2 equivalences between channels. | Phase space: wood Warning: No cuts have been defined. \end{verbatim} \begin{verbatim} | Starting integration for process 'ee' | Integrate: iterations not specified, using default | Integrate: iterations = 3:1000:"gw", 3:10000:"" | Integrator: 2 chains, 2 channels, 2 dimensions | Integrator: Using VAMP channel equivalences | Integrator: 1000 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 784 8.3282892E+02 1.68E+00 0.20 0.06* 39.99 2 784 8.3118961E+02 1.23E+00 0.15 0.04* 76.34 3 784 8.3278951E+02 1.36E+00 0.16 0.05 54.45 |-----------------------------------------------------------------------------| 3 2352 8.3211789E+02 8.01E-01 0.10 0.05 54.45 0.50 3 |-----------------------------------------------------------------------------| 4 9936 8.3331732E+02 1.22E-01 0.01 0.01* 54.51 5 9936 8.3341072E+02 1.24E-01 0.01 0.01 54.52 6 9936 8.3331151E+02 1.23E-01 0.01 0.01* 54.51 |-----------------------------------------------------------------------------| 6 29808 8.3334611E+02 7.10E-02 0.01 0.01 54.51 0.20 3 |=============================================================================| \end{verbatim} \begin{verbatim} [.....] | Simulate: integration done | Simulate: using integration grids from file 'ee_m1.vg' | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 9617 | Simulation: requested number of events = 10 | corr. to luminosity [fb-1] = 1.2000E-02 | Events: writing to LHEF file 'ee.lhe' | Events: writing to raw file 'ee.evx' | Events: generating 10 unweighted, unpolarized events ... | Events: event normalization mode '1' | ... event sample complete. | Events: closing LHEF file 'ee.lhe' | Events: closing raw file 'ee.evx' | There were no errors and 1 warning(s). | WHIZARD run finished. |=============================================================================| \end{verbatim} \end{footnotesize} %$ The final result is the desired event file, \ttt{ee.lhe}. Let us discuss the output quickly to walk you through the procedures of a \whizard\ run: after the logfile message and the banner, the reading of the physics model and the initialization of a process library, the recorded process with tag \ttt{'ee'} is recorded. Next, user-defined parameters like the center-of-mass energy and the number of demanded (unweighted) events are displayed. As a next step, \whizard\ is starting the simulation of the process with tag \ttt{'ee'}. It recognizes that there has not yet been an integration over phase space (done by an optional \ttt{integrate} command, cf. Sec.~\ref{sec:integrate}), and consequently starts the integration. It then acknowledges, that the process code for the process \ttt{'ee'} needs to be compiled first (done by an optional \ttt{compile} command, cf. Sec.~\ref{sec:compilation}). So, \whizard\ compiles the process library, writes the makefile for its steering, and as a safeguard against garbage removes possibly existing files. Then, the source code for the library and its processes are generated: for the process code, the default method -- the matrix element generator \oMega\ is called (cf. Sec.~\ref{sec:omega_me}); and the sources are being compiled. The next steps are the loading of the process library, and \whizard\ reports the completion of the integration. For the Monte-Carlo integration, a random number generator is initialized. Here, it is the default generator, TAO (for more details, cf. Sec.~\ref{sec:tao}, while the random seed is set to a value initialized by the system clock, as no seed has been provided in the \sindarin\ input file. Now, the integration for the process \ttt{'ee'} is initialized, and information about the process (its name, the name of its process library, its index inside the library, and the process components out of which it consists, cf. Sec.~\ref{sec:processcomp}) are displayed. Then, the beam structure is shown, which in that case are symmetric partonic electron and positron beams with the center-of-mass energy provided by the user (360 GeV). The next step is the generation of the phase space, for which the default phase space method \ttt{wood} (for more details cf. Sec.~\ref{sec:wood}) is selected. The integration is performed, and the result with absolute and relative error, unweighting efficiency, accuracy, $\chi^2$ quality is shown. The final step is the event generation (cf. Chap.~\ref{chap:events}). The integration grids are now being used, again the random number generator is initialized. Finally, event generation of ten unweighted events starts (\whizard\ let us know to which integrated luminosity that would correspond), and events are written both in an internal (binary) event format as well as in the demanded LHE format. This concludes the \whizard\ run. After a more comprehensive introduction into the \sindarin\ steering language in the next chapter, Chap.~\ref{chap:sindarinintro}, we will discuss all the details of the different steps of this introductory example. \clearpage \section{WHIZARD in a Computing Environment} \subsection{Working on a Single Computer} \label{sec:workspace} After installation, \whizard\ is ready for use. There is a slight complication if \whizard\ has been installed in a location that is not in your standard search paths. In that case, to successfully run \whizard, you may either \begin{itemize} \item manually add \ttt{your-install-directory/bin} to your execution PATH\\ and \ttt{your-install-directory/lib} to your library search path (LD\_LIBRARY\_PATH), or \item whenever you start a project, execute \begin{interaction} your-workspace> . your-install-directory/bin/whizard-setup.sh \end{interaction} which will enable the paths in your current environment, or \item source \ttt{whizard-setup.sh} script in your shell startup file. \end{itemize} In either case, try to call \ttt{whizard --help} in order to check whether this is done correctly. For a new \whizard\ project, you should set up a new (empty) directory. Depending on the complexity of your task, you may want to set up separate directories for each subproblem that you want to tackle, or even for each separate run. The location of the directories is arbitrary. To run, \whizard\ needs only a single input file, a \sindarin\ command script with extension \ttt{.sin} (by convention). Running \whizard\ is as simple as \begin{interaction} your-workspace> whizard your-input.sin \end{interaction} No other configuration files are needed. The total number of auxiliary and output files generated in a single run may get quite large, however, and they may clutter your workspace. This is the reason behind keeping subdirectories on a per-run basis. Basic usage of \whizard\ is explained in Chapter~\ref{chap:start}, for more details, consult the following chapters. In Sec.~\ref{sec:cmdline-options} we give an account of the command-line options that \whizard\ accepts. \subsection{Working Parallel on Several Computers} \label{sec:mpi} For integration (only VAMP2), \whizard\ supports parallel execution via MPI by communicating between parallel tasks on a single machine or distributed over several machines. During integration the calculation of channels is distributed along several workers where a master worker collects the results and adapts weights and grids. In wortwhile cases (e.g. high number of calls in one channel), the calculation of a single grid is distributed. In order to use these advancements, \whizard\ requires an installed MPI-3.1 capable library (e.g. OpenMPI) and configuration and compilation with the appropriate flags, cf.~Sec.~\ref{sec:installation}. MPI support is only active when the integration method is set to VAMP2. Additionally, to preserve the numerical properties of a single task run, it is recommended to use the RNGstream as random number generator. \begin{code} $integration_method = 'vamp2' $rng_method = 'rng_stream' \end{code} \whizard\ has then to be called by mpirun \begin{footnotesize} \begin{Verbatim}[frame=single] your-workspace> mpirun -f hostfile -np 4 --output-filename mpi.log whizard your-input.sin \end{Verbatim} \end{footnotesize} where the number of parallel tasks can be set by \ttt{-np} and a hostfile can be given by \ttt{--hostfile}. It is recommended to use \ttt{--output-filename} which lets mpirun redirect the standard (error) output to a file, for each worker separatly. \subsubsection{Notes on Parallelization with MPI} The parallelization of \whizard\ requires that all instances of the parallel run be able to write and read all files by produced \whizard\ in a network file system as the current implementation does not handle parallel I/O. Usually, high-performance clusters have support for at least one network filesystem. Furthermore, not all functions of \whizard\ are currently supported or are only supported in a limited way in parallel mode. Currently the \verb|?rebuild_| for the phase space and the matrix element library are not yet available, as well as the calculation of matrix elements with resonance history. Some features that have been missing in the very first implementation of the parallelized integration have now been made available, like the support of run IDs and the parallelization of the event generation. A final remark on the stability of the numerical results in terms of the number of workers involved. Under certain circumstances, results between different numbers of workers but using otherwise an identical \sindarin\ file can lead to slightly numerically different (but statistically compatible) results for integration or event generation This is related to the execution of the computational operations in MPI, which we use to reduce results from all workers. If the order of the numbers in the arithmetical operations changes, for example, by different setups of the workers, then the numerical results change slightly, which in turn is amplified under the influence of the adaptation. Nevertheless, the results are all statistically consistent. \subsection{Stopping and Resuming WHIZARD Jobs} On a Unix-like system, it is possible to prematurely stop running jobs by a \ttt{kill(1)} command, or by entering \ttt{Ctrl-C} on the terminal. If the system supports this, \whizard\ traps these signals. It also traps some signals that a batch operating system might issue, e.g., for exceeding a predefined execution time limit. \whizard\ tries to complete the calculation of the current event and gracefully close open files. Then, the program terminates with a message and a nonzero return code. Usually, this should not take more than a fraction of a second. If, for any reason, the program does not respond to an interrupt, it is always possible to kill it by \ttt{kill -9}. A convenient method, on a terminal, would be to suspend it first by \ttt{Ctrl-Z} and then to kill the suspended process. The program is usually able to recover after being stopped. Simply run the job again from start, with the same input, all output files generated so far left untouched. The results obtained so far will be quickly recovered or gathered from files written in the previous run, and the actual time-consuming calculation is resumed near the point where it was interrupted.\footnote{This holds for simple workflow. In case of scans and repeated integrations of the same process, there may be name clashes on the written files which prevent resuming. A future \whizard\ version will address this problem.} If the interruption happened during an integration step, it is resumed after the last complete iteration. If it was during event generation, the previous events are taken from file and event generation is continued. The same mechanism allows for efficiently redoing a calculation with similar, somewhat modified input. For instance, you might want to add a further observable to event analysis, or write the events in a different format. The time for rerunning the program is determined just by the time it takes to read the existing integration or event files, and the additional calculation is done on the recovered information. By managing various checksums on its input and output files, \whizard\ detects changes that affect further calculations, so it does a real recalculation only where it is actually needed. This applies to all steps that are potentially time-consuming: matrix-element code generation, compilation, phase-space setup, integration, and event generation. If desired, you can set command-line options or \sindarin\ parameters that explicitly discard previously generated information. \subsection{Files and Directories: default and customization} \whizard\ jobs take a small set of files as input. In many cases, this is just a single \sindarin\ script provided by the user. When running, \whizard\ can produce a set of auxiliary and output files: \begin{enumerate} \item \textbf{Job.} Files pertaining to the \whizard\ job as a whole. This is the default log file \ttt{whizard.log}. \item \textbf{Process compilation.} Files that originate from generating and compiling process code. If the default \oMega\ generator is used, these files include Fortran source code as well as compiled libraries that are dynamically linked to the running executable. The file names are derived from either the process-library name or the individual process names, as defined in the \sindarin\ input. The default library name is \ttt{default\_lib}. \item \textbf{Integration.} Files that are created by integration, i.e., when calculating the total cross section for a scattering process using the Monte-Carlo algorithm. The file names are derived from the process name. \item \textbf{Simulation.} Files that are created during simulation, i.e., generating event samples for a process or a set of processes. By default, the file names are derived from the name of the first process. Event-file formats are distinguished by appropriate file name extensions. \item \textbf{Result Analysis.} Files that are created by the internal analysis tools and written by the command \ttt{write\_analysis} (or \ttt{compile\_analysis}). The default base name is \ttt{whizard\_analysis}. \end{enumerate} A complex workflow with several processes, parameter sets, or runs, can easily lead to in file-name clashes or a messy working directory. Furthermore, running a batch job on a dedicated computing environment often requires transferring data from a user directory to the server and back. Custom directory and file names can be used to organize things and facilitate dealing with the environment, along with the available batch-system tools for coordinating file transfer. \begin{enumerate} \item \textbf{Job.} \begin{itemize} \item The \ttt{-L} option on the command line defines a custom base name for the log file. \item The \ttt{-J} option on the command line defines a job ID. For instance, this may be set to the job ID assigned by the batch system. Within the \sindarin\ script, the job ID is available as the string variable \ttt{\$job\_id} and can be used for constructing custom job-specific file and directory names, as described below. \end{itemize} \item \textbf{Process compilation.} \begin{itemize} \item The user can require the program to put all files created during the compilation step including the library to be linked, in a subdirectory of the working directory. To enable this, set the string variable \ttt{\$compile\_workspace} within the \sindarin\ script. \end{itemize} \item \textbf{Integration.} \begin{itemize} \item The value of the string variable \ttt{\$run\_id}, if set, is appended to the base name of all files created by integration, separated by dots. If the \sindarin\ script scans over parameters, varying the run ID avoids repeatedly overwriting files with identical name during the scan. \item The user can require the program to put the important files created during the integration step -- the phase-space configuration file and the \vamp\ grid files -- in a subdirectory of the working directory. To enable this, set the string variable \ttt{\$integrate\_workspace} within the \sindarin\ script. (\ttt{\$compile\_workspace} and \ttt{\$integrate\_workspace} may be set to the same value.) \end{itemize} Log files produced during the integration step are put in the working directory. \item \textbf{Simulation.} \begin{itemize} \item The value of the string variable \ttt{\$run\_id}, if set, identifies the specific integration run that is used for the event sample. It is also inserted into default event-sample file names. \item The variable \ttt{\$sample}, if set, defines an arbitrary base name for the files related to the event sample. \end{itemize} Files resulting from simulation are put in the working directory. \item \textbf{Result Analysis.} \begin{itemize} \item The variable \ttt{\$out\_file}, if set, defines an arbitrary base name for the analysis data and auxiliary files. \end{itemize} Files resulting from result analysis are put in the working directory. \end{enumerate} \subsection{Batch jobs on a different machine} It is possible to separate the tasks of process-code compilation, integration, and simulation, and execute them on different machines. To make use of this feature, the local and remote machines including all installed libraries that are relevant for \whizard, must be binary-compatible. \begin{enumerate} \item Process-code compilation may be done once on a local machine, while the time-consuming tasks of integration and event generation for specific parameter sets are delegated to a remote machine, e.g., a batch cluster. To enable this, prepare a \sindarin\ script that just produces process code (i.e., terminates with a \ttt{compile} command) for the local machine. You may define \ttt{\$compile\_workspace} such that all generated code conveniently ends up in a single subdirectory. To start the batch job, transfer the workspace subdirectory to the remote machine and start \whizard\ there. The \sindarin\ script on the remote machine must include the local script unchanged in all parts that are relevant for process definition. The program will recognize the contents of the workspace, skip compilation and instead link the process library immediately. To proceed further, the script should define the run-specific parameters and contain the appropriate commands for integration and simulation. \item Analogously, you may execute both process-code compilation and integration locally, but generate event samples on a remote machine. To this end, prepare a \sindarin\ script that produces process code and computes integrals (i.e., terminates with an \ttt{integrate} command) for the local machine. You may define \ttt{\$compile\_workspace} and \ttt{\$integrate\_workspace} (which may coincide) such that all generated code, phase-space and integration grid data conveniently end up in subdirectories. To start the batch job, transfer the workspace(s) to the remote machine and start \whizard\ there. The \sindarin\ script on the remote machine must include the local script unchanged in all parts that are relevant for process definition and integration. The program will recognize the contents of the workspace, skip compilation and integration and instead load the process library and integration results immediately. To proceed further, the script should define the sample-specific parameters and contain the appropriate commands for simulation. \end{enumerate} To simplify transferring whole directories, \whizard\ supports the \ttt{--pack} and \ttt{--unpack} options. You may specify any number of these options for a \whizard\ run. (The feature relies on the GNU version of the \ttt{tar} utility.) For instance, \begin{code} whizard script1.sin --pack my_ws \end{code} runs \whizard\ with the \sindarin\ script \ttt{script1.sin} as input, where within the script you have defined \begin{code} $compile_workspace = "my_ws" \end{code} as the target directory for process-compilation files. After completion, the program will tar and gzip the target directory as \ttt{my\_ws.tgz}. You should copy this file to the remote machine as one of the job's input files. On the remote machine, you can then run the program with \begin{code} whizard script2.sin --unpack my_ws.tgz \end{code} where \ttt{script2.sin} should include \ttt{script1.sin}, and add integration or simulation commands. The contents of \ttt{ws.tgz} will thus be unpacked and reused on the remote machine, instead of generating new process code. \subsection{Static Linkage} In its default running mode, \whizard\ compiles process-specific matrix element code on the fly and dynamically links the resulting library. On the computing server, this requires availability of the appropriate Fortran compiler, as well as the \ocaml\ compiler suite, and the dynamical linking feature. Since this may be unavailable or undesired, there is a possibility to distribute \whizard\ as a statically linked executable that contains a pre-compiled library of processes. This removes the need for the Fortran compiler, the \ocaml\ system, and extra dynamic linking. Any external libraries that are accessed (the \fortran\ runtime environment, and possibly some dynamically linked external libraries and/or the C++ runtime library, must still be available on the target system, binary-compatible. Otherwise, there is no need for transferring the complete \whizard\ installation or process-code compilation data. Generating, compiling and linking matrix element code is done in advance on a machine that can access the required tools and produces compatible libraries. This procedure is accomplished by \sindarin\ commands, explained below in Sec.~\ref{sec:static}. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \newpage \section{Troubleshooting} \label{sec:troubleshooting} In this section, we list known issues or problems and give advice on what can be done in case something does not work as intended. \subsection{Possible (uncommon) build problems} \label{sec:buildproblems} \subsubsection{\ocaml\ versions and \oMega\ builds} For the matrix element generator \oMega\ of \whizard\, the functional programming language \ocaml\ is used. Unfortunately, the versions of the \ocaml\ compiler from 3.12.0 on broke backwards compatibility. Therefore, versions of \oMega/\whizard\ up to v2.0.2 only compile with older versions (3.04 to 3.11 works). This has been fixed in all \whizard\ versions from 2.0.3 on. \subsubsection{Identical Build and Source directories} There is a problem that only occurred with version 2.0.0 and has been corected for all follow-up versions. It can only appear if you compile the \whizard\ sources in the source directory. Then an error like this may occur: \begin{footnotesize} \begin{Verbatim}[frame=single] ... libtool: compile: gfortran -I../misc -I../vamp -g -O2 -c processes.f90 -fPIC -o .libs/processes.o libtool: compile: gfortran -I../misc -I../vamp -g -O2 -c processes.f90 -o processes.o >/dev/null 2>&1 make[2]: *** No rule to make target `limits.lo', needed by `decays.lo'. Stop. ... make: *** [all-recursive] Error 1 \end{Verbatim} \end{footnotesize} In this case, please unpack a fresh copy of \whizard\ and configure it in a separate directory (not necessarily a subdirectory). Then the compilation will go through: \begin{footnotesize} \begin{Verbatim}[frame=single] $ zcat whizard-2.0.0.tar.gz | tar xf - $ cd whizard-2.0.0 $ mkdir _build $ cd _build $ ../configure FC=gfortran $ make \end{Verbatim} \end{footnotesize} The developers use this setup to be able to test different compilers. Therefore building in the same directory is not as thoroughly tested. This behavior has been patched from version 2.0.1 on. But note that in general it is always adviced to keep build and source directory apart from each other. %%%%% \subsection{What happens if \whizard\ throws an error?} \label{ref:errors} \subsubsection{Particle name special characters in process declarations} Trying to use a process declaration like \begin{code} process foo = e-, e+ => mu-, mu+ \end{code} will lead to a \sindarin\ syntax error: \begin{Code} process foo = e-, e+ => mu-, mu+ ^^ | Expected syntax: SEQUENCE = process '=' "mu-", "mu+"}. \subsubsection{Missing collider energy} This happens if you forgot to set the collider energy in the integration of a scattering process: \begin{Code} ****************************************************************************** ****************************************************************************** *** FATAL ERROR: Colliding beams: sqrts is zero (please set sqrts) ****************************************************************************** ****************************************************************************** \end{Code} This will solve your problem: \begin{code} sqrts = \end{code} \subsubsection{Missing process declaration} If you try to integrate or simulate a process that has not declared before (and is also not available in a library that might be loaded), \whizard\ will complain: \begin{Code} ****************************************************************************** ****************************************************************************** *** FATAL ERROR: Process library doesn't contain process 'f00' ****************************************************************************** ****************************************************************************** \end{Code} Note that this could sometimes be a simple typo, e.g. in that case an \ttt{integrate (f00)} instead of \ttt{integrate (foo)} \subsubsection{Ambiguous initial state without beam declaration} When the user declares a process with a flavor sum in the initial state, e.g. \begin{code} process qqaa = u:d, U:D => A, A sqrts = integrate (qqaa) \end{code} then a fatal error will be issued: \begin{Code} ****************************************************************************** ****************************************************************************** *** FATAL ERROR: Setting up process 'qqaa': *** -------------------------------------------- *** Inconsistent initial state. This happens if either *** several processes with non-matching initial states *** have been added, or for a single process with an *** initial state flavor sum. In that case, please set beams *** explicitly [singling out a flavor / structure function.] ****************************************************************************** ****************************************************************************** \end{Code} What now? Either a structure function providing a tensor structure in flavors has to be provided like \begin{code} beams = p, pbar => pdf_builtin \end{code} or, if the partonic process was intended, a specific flavor has to be singled out, \begin{code} beams = u, U \end{code} which would take only the up-quarks. Note that a sum over process components with varying initial states is not possible. \subsubsection{Invalid or unsupported beam structure} An error message like \begin{Code} ****************************************************************************** ****************************************************************************** *** FATAL ERROR: Beam structure: [.......] not supported ****************************************************************************** ****************************************************************************** \end{Code} This happens if you try to use a beam structure with is either not supported by \whizard\ (meaning that there is no phase-space parameterization for Monte-Carlo integration available in order to allow an efficient sampling), or you have chosen a combination of beam structure functions that do not make sense physically. Here is an example for the latter (lepton collider ISR applied to protons, then proton PDFs): \begin{code} beams = p, p => isr => pdf_builtin \end{code} \subsubsection{Mismatch in beams} Sometimes you get a rather long error output statement followed by a fatal error: \begin{Code} Evaluator product First interaction Interaction: 6 Virtual: Particle 1 [momentum undefined] [.......] State matrix: norm = 1.000000000000E+00 [f(2212)] [f(11)] [f(92) c(1 )] [f(-6) c(-1 )] => ME(1) = ( 0.000000000000E+00, 0.000000000000E+00) [.......] ****************************************************************************** ****************************************************************************** *** FATAL ERROR: Product of density matrices is empty *** -------------------------------------------- *** This happens when two density matrices are convoluted *** but the processes they belong to (e.g., production *** and decay) do not match. This could happen if the *** beam specification does not match the hard *** process. Or it may indicate a WHIZARD bug. ****************************************************************************** ****************************************************************************** \end{Code} As \whizard\ indicates, this could have happened because the hard process setup did not match the specification of the beams as in: \begin{code} process neutral_current_DIS = e1, u => e1, u beams_momentum = 27.5 GeV, 920 GeV beams = p, e => pdf_builtin, none integrate (neutral_current_DIS) \end{code} In that case, the order of the beam particles simply was wrong, exchange proton and electron (together with the structure functions) into \ttt{beams = e, p => none, pdf\_builtin}, and \whizard\ will be happy. \subsubsection{Unstable heavy beam particles} If you try to use unstable particles as beams that can potentially decay into the final state particles, you might encounter the following error message: \begin{Code} ****************************************************************************** ****************************************************************************** *** FATAL ERROR: Phase space: Initial beam particle can decay ****************************************************************************** ****************************************************************************** \end{Code} This happens basically only for processes in testing/validation (like $t \bar t \to b \bar b$). In principle, it could also happen in a real physics setup, e.g. when simulating electron pairs at a muon collider: \begin{code} process mmee = "mu-", "mu+" => "e-", "e+" \end{code} However, \whizard\ at the moment does not allow a muon width, and so \whizard\ is not able to decay a muon in a scattering process. A possibile decay of the beam particle into (part of) the final state might lead to instabilities in the phase space setup. Hence, \whizard\ do not let you perform such an integration right away. When you nevertheless encounter such a rare occasion in your setup, there is a possibility to convert this fatal error into a simple warning by setting the flag: \begin{code} ?fatal_beam_decay = false \end{code} \subsubsection{Impossible beam polarization} If you specify a beam polarization that cannot correspond to any physically allowed spin density matrix, e.g., \begin{code} beams = e1, E1 beams_pol_density = @(-1), @(1:1:.5, -1, 1:-1) \end{code} \whizard\ will throw a fatal error like this: \begin{Code} Trace of matrix square = 1.4444444444444444 Polarization: spin density matrix spin type = 2 multiplicity = 2 massive = F chirality = 0 pol.degree = 1.0000000 pure state = F @(+1: +1: ( 3.333333333333E-01, 0.000000000000E+00)) @(-1: -1: ( 6.666666666667E-01, 0.000000000000E+00)) @(-1: +1: ( 6.666666666667E-01, 0.000000000000E+00)) ****************************************************************************** ****************************************************************************** *** FATAL ERROR: Spin density matrix: not permissible as density matrix ****************************************************************************** ****************************************************************************** \end{Code} \subsubsection{Beams with crossing angle} Specifying a crossing angle (e.g. at a linear lepton collider) without explicitly setting the beam momenta, \begin{code} sqrts = 1 TeV beams = e1, E1 beams\_theta = 0, 10 degree \end{code} triggers a fatal: \begin{Code} ****************************************************************************** ****************************************************************************** *** FATAL ERROR: Beam structure: angle theta/phi specified but momentum/a p undefined ****************************************************************************** ****************************************************************************** \end{Code} In that case the single beam momenta have to be explicitly set: \begin{code} beams = e1, E1 beams\_momentum = 500 GeV, 500 GeV beams\_theta = 0, 10 degree \end{code} \subsubsection{Phase-space generation failed} Sometimes an error might be issued that \whizard\ could not generate a valid phase-space parameterization: \begin{Code} | Phase space: ... failed. Increasing phs_off_shell ... | Phase space: ... failed. Increasing phs_off_shell ... | Phase space: ... failed. Increasing phs_off_shell ... | Phase space: ... failed. Increasing phs_off_shell ... ****************************************************************************** ****************************************************************************** *** FATAL ERROR: Phase-space: generation failed ****************************************************************************** ****************************************************************************** \end{Code} You see that \whizard\ tried to increase the number of off-shell lines that are taken into account for the phase-space setup. The second most important parameter for the phase-space setup, \ttt{phs\_t\_channel}, however, is not increased automatically. Its default value is $6$, so e.g. for the process $e^+ e^- \to 8\gamma$ you will run into the problem above. Setting \begin{code} phs_off_shell = -1 \end{code} where \ttt{} is the number of final-state particles will solve the problem. \subsubsection{Non-converging process integration} There could be several reasons for this to happen. The most prominent one is that no cuts have been specified for the process (\whizard\ttt{2} does not apply default cuts), and there are singular regions in the phase space over which the integration stumbles. If cuts have been specified, it could be that they are not sufficient. E.g. in $pp \to jj$ a distance cut between the two jets prevents singular collinear splitting in their generation, but if no $p_T$ cut have been set, there is still singular collinear splitting from the beams. \subsubsection{Why is there no event file?} If no event file has been generated, \whizard\ stumled over some error and should have told you, or, you simply forgot to set a \ttt{simulate} command for your process. In case there was a \ttt{simulate} command but the process under consideration is not possible (e.g. a typo, \ttt{e1, E1 => e2, E3} instead of \ttt{e1, E1 => e3, E3}), then you get an error like that: \begin{Code} ****************************************************************************** *** ERROR: Simulate: no process has a valid matrix element. ****************************************************************************** \end{Code} \subsubsection{Why is the event file empty?} In order to get events, you need to set either a desired number of events: \begin{code} n_events = \end{code} or you have to specify a certain integrated luminosity (the default unit being inverse femtobarn: \begin{code} luminosity = / 1 fbarn \end{code} In case you set both, \whizard\ will take the one that leads to the higher number of events. \subsubsection{Parton showering fails} For BSM models containing massive stable or long-lived particles parton showering with \pythiasix\ fails: \begin{Code} Advisory warning type 3 given after 0 PYEXEC calls: (PYRESD:) Failed to decay particle 1000022 with mass 15.000 ****************************************************************************** ****************************************************************************** *** FATAL ERROR: Simulation: failed to generate valid event after 10000 tries ****************************************************************************** ****************************************************************************** \end{Code} The solution to that problem is discussed in Sec.~\ref{sec:pythia6}. \vspace{1cm} %%%%% \subsection{Debugging, testing, and validation} \subsubsection{Catching/tracking arithmetic exceptions} Catching arithmetic exceptions is not automatically supported by \fortran\ compilers. In general, flags that cause the compiler to keep track of arithmetic exceptions are diminishing the maximally possible performance, and hence they should not be used in production runs. Hence, we refrained from making these flags a default. They can be added using the \ttt{FCFLAGS = {\em }} settings during configuration. For the \ttt{NAG} \fortran\ compiler we use the flags \ttt{-C=all -nan -gline} for debugging purposes. For the \ttt{gfortran} compilers, the flags \ttt{-ffpe-trap=invalid,zero,overflow} are the corresponding debugging flags. For tests, debugging or first sanity checks on your setup, you might want to make use of these flags in order to track possible numerical exceptions in the produced code. Some compilers started to include \ttt{IEEE} exception handling support (\ttt{Fortran 2008} status), but we do not use these implementations in the \whizard\ code (yet). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \chapter{Steering WHIZARD: \sindarin\ Overview} \label{chap:sindarinintro} \section{The command language for WHIZARD} A conventional physics application program gets its data from a set of input files. Alternatively, it is called as a library, so the user has to write his own code to interface it, or it combines these two approaches. \whizard~1 was built in this way: there were some input files which were written by the user, and it could be called both stand-alone or as an external library. \whizard~2 is also a stand-alone program. It comes with its own full-fledged script language, called \sindarin. All interaction between the user and the program is done in \sindarin\ expressions, commands, and scripts. Two main reasons led us to this choice: \begin{itemize} \item In any nontrivial physics study, cuts and (parton- or hadron-level) analysis are of central importance. The task of specifying appropriate kinematics and particle selection for a given process is well defined, but it is impossible to cover all possiblities in a simple format like the cut files of \whizard~1. The usual way of dealing with this problem is to write analysis driver code (often in \ttt{C++}), using external libraries for Lorentz algebra etc. However, the overhead of writing correct \ttt{C++} or \ttt{Fortran} greatly blows up problems that could be formulated in a few lines of text. \item While many problems lead to a repetitive workflow (process definition, integration, simulation), there are more involved tasks that involve parameter scans, comparisons of different processes, conditional execution, or writing output in widely different formats. This is easily done by a steering script, which should be formulated in a complete language. \end{itemize} The \sindarin\ language is built specifically around event analysis, suitably extended to support steering, including data types, loops, conditionals, and I/O. It would have been possible to use an established general-purpose language for these tasks. For instance, \ocaml\ which is a functional language would be a suitable candidate, and the matrix-element generator \oMega\ is written in that language. Another candidate would be a popular scripting language such as PYTHON. We started to support interfaces for commonly used languages: prime examples for \ttt{C}, \ttt{C++}, and PYTHON are found in the \ttt{share/interfaces} subdirectory. However, introducing a special-purpose language has the three distinct advantages: First, it is compiled and executed by the very \ttt{Fortran} code that handles data and thus accesses it without interfaces. Second, it can be designed with a syntax especially suited to the task of event handling and Monte-Carlo steering, and third, the user is not forced to learn all those features of a generic language that are of no relevance to the application he/she is interested in. \section{\sindarin\ scripts} A \sindarin\ script tells the \whizard\ program what it has to do. Typically, the script is contained in a file which you (the user) create. The file name is arbitrary; by convention, it has the extension `\verb|.sin|'. \whizard\ takes the file name as its argument on the command line and executes the contained script: \begin{verbatim} /home/user$ whizard script.sin \end{verbatim} Alternatively, you can call \whizard\ interactively and execute statements line by line; we describe this below in Sec.\ref{sec:whish}. A \sindarin\ script is a sequence of \emph{statements}, similar to the statements in any imperative language such as \ttt{Fortran} or \ttt{C}. Examples of statements are commands like \ttt{integrate}, variable declarations like \ttt{logical ?flag} or assigments like \ttt{mH = 130 GeV}. The script is free-form, i.e., indentation, extra whitespace and newlines are syntactically insignificant. In contrast to most languages, there is no statement separator. Statements simply follow each other, just separated by whitespace. \begin{code} statement1 statement2 statement3 statement4 \end{code} Nevertheless, for clarity we recommend to write one statement per line where possible, and to use proper indentation for longer statements, nested and bracketed expressions. A command may consist of a \emph{keyword}, a list of \emph{arguments} in parantheses \ttt{(}\ldots\ttt{)}, and an \emph{option} script which itself is a sequence of statements. \begin{code} command command_with_args (arg1, arg2) command_with_option { option } command_with_options (arg) { option_statement1 option_statement2 } \end{code} As a rule, parentheses \ttt{()} enclose arguments and expressions, as you would expect. Arguments enclosed in square brackets \ttt{[]} also exist. They have a special meaning, they denote subevents (collections of momenta) in event analysis. Braces \ttt{\{\}} enclose blocks of \sindarin\ code. In particular, the option script associated with a command is a block of code that may contain local parameter settings, for instance. Braces always indicate a scoping unit, so parameters will be restored their previous values when the execution of that command is completed. The script can contain comments. Comments are initiated by either a \verb|#| or a \verb|!| character and extend to the end of the current line. \begin{code} statement # This is a comment statement ! This is also a comment \end{code} %%%%%%%%%%%%%%% \section{Errors} \label{sec:errors} Before turning to proper \sindarin\ syntax, let us consider error messages. \sindarin\ distinguishes syntax errors and runtime errors. Syntax errors are recognized when the script is read and compiled, before any part is executed. Look at this example: \begin{code} process foo = u, ubar => d, dbar md = 10 integrade (foo) \end{code} \whizard\ will fail with the error message \begin{interaction} sqrts = 1 TeV integrade (foo) ^^ | Expected syntax: SEQUENCE = '=' | Found token: KEYWORD: '(' ****************************************************************************** ****************************************************************************** *** FATAL ERROR: Syntax error (at or before the location indicated above) ****************************************************************************** ****************************************************************************** WHIZARD run aborted. \end{interaction} which tells you that you have misspelled the command \verb|integrate|, so the compiler tried to interpret it as a variable. Runtime errors are categorized by their severity. A warning is simply printed: \begin{interaction} Warning: No cuts have been defined. \end{interaction} This indicates a condition that is suspicious, but may actually be intended by the user. When an error is encountered, it is printed with more emphasis \begin{interaction} ****************************************************************************** *** ERROR: Variable 'md' set without declaration ****************************************************************************** \end{interaction} and the program tries to continue. However, this usually indicates that there is something wrong. (The $d$ quark is defined massless, so \verb|md| is not a model parameter.) \whizard\ counts errors and warnings and tells you at the end \begin{interaction} | There were 1 error(s) and no warnings. \end{interaction} just in case you missed the message. Other errors are considered fatal, and execution stops at this point. \begin{interaction} ****************************************************************************** ****************************************************************************** *** FATAL ERROR: Colliding beams: sqrts is zero (please set sqrts) ****************************************************************************** ****************************************************************************** \end{interaction} Here, \whizard\ was unable to do anything sensible. But at least (in this case) it told the user what to do to resolve the problem. %%%%%%%%%%%%%%% \section{Statements} \label{sec:statements} \sindarin\ statements are executed one by one. For an overview, we list the most common statements in the order in which they typically appear in a \sindarin\ script, and quote the basic syntax and simple examples. This should give an impression on the \whizard's capabilities and on the user interface. The list is not complete. Note that there are no mandatory commands (although an empty \sindarin\ script is not really useful). The details and options are explained in later sections. \subsection{Process Configuration} \subsubsection{model} \begin{syntax} model = \var{model-name} \end{syntax} This assignment sets or resets the current physics model. The Standard Model is already preloaded, so the \ttt{model} assignment applies to non-default models. Obviously, the model must be known to \whizard. Example: \begin{code} model = MSSM \end{code} See Sec.~\ref{sec:models}. \subsubsection{alias} \begin{syntax} alias \var{alias-name} = \var{alias-definition} \end{syntax} Particles are specified by their names. For most particles, there are various equivalent names. Names containing special characters such as a \verb|+| sign have to be quoted. The \ttt{alias} assignment defines an alias for a list of particles. This is useful for setting up processes with sums over flavors, cut expressions, and more. The alias name is then used like a simple particle name. Example: \begin{syntax} alias jet = u:d:s:U:D:S:g \end{syntax} See Sec.~\ref{sec:alias}. \subsubsection{process} \begin{syntax} process \var{tag} = \var{incoming} \verb|=>| \var{outgoing} \end{syntax} Define a process. You give the process a name \var{tag} by which it is identified later, and specify the incoming and outgoing particles, and possibly options. You can define an arbitrary number of processes as long as they are distinguished by their names. Example: \begin{code} process w_plus_jets = g, g => "W+", jet, jet \end{code} See Sec.~\ref{sec:processes}. \subsubsection{sqrts} \begin{syntax} sqrts = \var{energy-value} \end{syntax} Define the center-of-mass energy for collision processes. The default setup will assume head-on central collisions of two beams. Example: \begin{code} sqrts = 500 GeV \end{code} See Sec.~\ref{sec:beam-setup}. \subsubsection{beams} \begin{syntax} beams = \var{beam-particles} \\ beams = \var{beam-particles} => \var{structure-function-setup} \end{syntax} Declare beam particles and properties. The current value of \ttt{sqrts} is used, unless specified otherwise. Example: \begin{code} beams = u:d:s, U:D:S => lhapdf \end{code} With options, the assignment allows for defining beam structure in some detail. This includes beamstrahlung and ISR for lepton colliders, precise structure function definition for hadron colliders, asymmetric beams, beam polarization, and more. See Sec.~\ref{sec:beams}. \subsection{Parameters} \subsubsection{Parameter settings} \begin{syntax} \var{parameter} = \var{value} \\ \var{type} \var{user-parameter} \\ \var{type} \var{user-parameter} = \var{value} \end{syntax} Specify a value for a parameter. There are predefined parameters that affect the behavior of a command, model-specific parameters (masses, couplings), and user-defined parameters. The latter have to be declared with a type, which may be \ttt{int} (integer), \ttt{real}, \ttt{complex}, \ttt{logical}, \ttt{string}, or \ttt{alias}. Logical parameter names begin with a question mark, string parameter names with a dollar sign. Examples: \begin{code} mb = 4.2 GeV ?rebuild_grids = true real mass_sum = mZ + mW string $message = "This is a string" \end{code} % $ The value need not be a literal, it can be an arbitrary expression of the correct type. See Sec.~\ref{sec:variables}. \subsubsection{read\_slha} \begin{syntax} read\_slha (\var{filename}) \end{syntax} This is useful only for supersymmetric models: read a parameter file in the SUSY Les Houches Accord format. The file defines parameter values and, optionally, decay widths, so this command removes the need for writing assignments for each of them. \begin{code} read_slha ("sps1a.slha") \end{code} See Sec.~\ref{sec:slha}. \subsubsection{show} \begin{syntax} show (\var{data-objects}) \end{syntax} Print the current value of some data object. This includes not just variables, but also models, libraries, cuts, etc. This is rather a debugging aid, so don't expect the output to be concise in the latter cases. Example: \begin{code} show (mH, wH) \end{code} See Sec.~\ref{sec:I/O}. \subsubsection{printf} \begin{syntax} printf \var{format-string} (\var{data-objects}) \end{syntax} Pretty-print the data objects according to the given format string. If there are no data objects, just print the format string. This command is borrowed from the \ttt{C} programming language; it is actually an interface to the system's \ttt{printf(3)} function. The conversion specifiers are restricted to \ttt{d,i,e,f,g,s}, corresponding to the output of integer, real, and string variables. Example: \begin{code} printf "The Higgs mass is %f GeV" (mH) \end{code} See Sec.~\ref{sec:I/O}. \subsection{Integration} \subsubsection{cuts} \begin{syntax} cuts = \var{logical-cut-expression} \end{syntax} The cut expression is a logical macro expression that is evaluated for each phase space point during integration and event generation. You may construct expressions out of various observables that are computed for the (partonic) particle content of the current event. If the expression evaluates to \verb|true|, the matrix element is calculated and the event is used. If it evaluates to \verb|false|, the matrix element is set zero and the event is discarded. Note that for collisions the expression is evaluated in the lab frame, while for decays it is evaluated in the rest frame of the decaying particle. In case you want to impose cuts on a factorized process, i.e. a combination of a production process and one or more decay processes, you have to use the \ttt{selection} keyword instead. Example for the keyword \ttt{cuts}: \begin{code} cuts = all Pt > 20 GeV [jet] and all mZ - 10 GeV < M < mZ + 10 GeV [lepton, lepton] and no abs (Eta) < 2 [jet] \end{code} See Sec.~\ref{sec:cuts}. \subsubsection{integrate} \begin{syntax} integrate (\var{process-tags}) \end{syntax} Compute the total cross section for a process. The command takes into account the definition of the process, the beam setup, cuts, and parameters as defined in the script. Parameters may also be specified as options to the command. Integration is necessary for each process for which you want to know total or differential cross sections, or event samples. Apart from computing a value, it sets up and adapts phase space and integration grids that are used in event generation. If you just need an event sample, you can omit an explicit \ttt{integrate} command; the \ttt{simulate} command will call it automatically. Example: \begin{code} integrate (w_plus_jets, z_plus_jets) \end{code} See Sec.~\ref{sec:integrate}. \subsubsection{?phs\_only/n\_calls\_test} \begin{syntax} integrate (\var{process-tag}) \{ ?phs\_only = true n\_calls\_test = 1000 \} \end{syntax} These are just optional settings for the \ttt{integrate} command discussed just a second ago. The \ttt{?phs\_only = true} (note that variables starting with a question mark are logicals) option tells \whizard\ to prepare a process for integration, but instead of performing the integration, just to generate a phase space parameterization. \ttt{n\_calls\_test = } evaluates the sampling function for random integration channels and random momenta. \vamp\ integration grids are neither generated nor used, so the channel selection corresponds to the first integration pass, before any grids or channel weights are adapted. The number of sampling points is given by \verb||. The output contains information about the timing, number of sampling points that passed the kinematics selection, and the number of matrix-element values that were actually evaluated. This command is useful mainly for debugging and diagnostics. Example: \begin{code} integrate (some_large_process) { ?phs_only = true n_calls_test = 1000 } \end{code} (Note that there used to be a separate command \ttt{matrix\_element\_test} until version 2.1.1 of \whizard\ which has been discarded in order to simplify the \sindarin\ syntax.) \subsection{Events} \subsubsection{histogram} \begin{syntax} histogram \var{tag} (\var{lower-bound}, \var{upper-bound}) \\ histogram \var{tag} (\var{lower-bound}, \var{upper-bound}, \var{step}) \\ \end{syntax} Declare a histogram for event analysis. The histogram is filled by an analysis expression, which is evaluated once for each event during a subsequent simulation step. Example: \begin{code} histogram pt_distribution (0, 150 GeV, 10 GeV) \end{code} See Sec.~\ref{sec:histogram}. \subsubsection{plot} \begin{syntax} plot \var{tag} \end{syntax} Declare a plot for displaying data points. The plot may be filled by an analysis expression that is evaluated for each event; this would result in a scatter plot. More likely, you will use this feature for displaying data such as the energy dependence of a cross section. Example: \begin{code} plot total_cross_section \end{code} See Sec.~\ref{sec:plot}. \subsubsection{selection} \begin{syntax} selection = \var{selection-expression} \end{syntax} The selection expression is a logical macro expression that is evaluated once for each event. It is applied to the event record, after all decays have been executed (if any). It is therefore intended e.g. for modelling detector acceptance cuts etc. For unfactorized processes the usage of \ttt{cuts} or \ttt{selection} leads to the same results. Events for which the selection expression evaluates to false are dropped; they are neither analyzed nor written to any user-defined output file. However, the dropped events are written to \whizard's native event file. For unfactorized processes it is therefore preferable to implement all cuts using the \ttt{cuts} keyword for the integration, see \ttt{cuts} above. Example: \begin{code} selection = all Pt > 50 GeV [lepton] \end{code} The syntax is generically the same as for the \ttt{cuts expression}, see Sec.~\ref{sec:cuts}. For more information see also Sec.~\ref{sec:analysis}. \subsubsection{analysis} \begin{syntax} analysis = \var{analysis-expression} \end{syntax} The analysis expression is a logical macro expression that is evaluated once for each event that passes the integration and selection cuts in a subsequent simulation step. The expression has type logical in analogy with the cut expression; however, its main use will be in side effects caused by embedded \ttt{record} expressions. The \ttt{record} expression books a value, calculated from observables evaluated for the current event, in one of the predefined histograms or plots. Example: \begin{code} analysis = record pt_distribution (eval Pt [photon]) and record mval (eval M [lepton, lepton]) \end{code} See Sec.~\ref{sec:analysis}. \subsubsection{unstable} \begin{syntax} unstable \var{particle} (\var{decay-channels}) \end{syntax} Specify that a particle can decay, if it occurs in the final state of a subsequent simulation step. (In the integration step, all final-state particles are considered stable.) The decay channels are processes which should have been declared before by a \ttt{process} command (alternatively, there are options that \whizard\ takes care of this automatically; cf. Sec.~\ref{sec:decays}). They may be integrated explicitly, otherwise the \ttt{unstable} command will take care of the integration before particle decays are generated. Example: \begin{code} unstable Z (z_ee, z_jj) \end{code} Note that the decay is an on-shell approximation. Alternatively, \whizard\ is capable of generating the final state(s) directly, automatically including the particle as an internal resonance together with irreducible background. Depending on the physical problem and on the complexity of the matrix-element calculation, either option may be more appropriate. See Sec.~\ref{sec:decays}. \subsubsection{n\_events} \begin{syntax} n\_events = \var{integer} \end{syntax} Specify the number of events that a subsequent simulation step should produce. By default, simulated events are unweighted. (Unweighting is done by a rejection operation on weighted events, so the usual caveats on event unweighting by a numerical Monte-Carlo generator do apply.) Example: \begin{code} n_events = 20000 \end{code} See Sec.~\ref{sec:simulation}. \subsubsection{simulate} \begin{syntax} simulate (\var{process-tags}) \end{syntax} Generate an event sample. The command allows for analyzing the generated events by the \ttt{analysis} expression. Furthermore, events can be written to file in various formats. Optionally, the partonic events can be showered and hadronized, partly using included external (\pythia) or truly external programs called by \whizard. Example: \begin{code} simulate (w_plus_jets) { sample_format = lhef } \end{code} See Sec.~\ref{sec:simulation} and Chapter~\ref{chap:events}. \subsubsection{graph} \begin{syntax} graph (\var{tag}) = \var{histograms-and-plots} \end{syntax} Combine existing histograms and plots into a common graph. Also useful for pretty-printing single histograms or plots. Example: \begin{code} graph comparison { $title = "$p_T$ distribution for two different values of $m_h$" } = hist1 & hist2 \end{code} % $ See Sec.~\ref{sec:graphs}. \subsubsection{write\_analysis} \begin{syntax} write\_analysis (\var{analysis-objects}) \end{syntax} Writes out data tables for the specified analysis objects (plots, graphs, histograms). If the argument is empty or absent, write all analysis objects currently available. The tables are available for feeding external programs. Example: \begin{code} write_analysis \end{code} See Sec.~\ref{sec:analysis}. \subsubsection{compile\_analysis} \begin{syntax} compile\_analysis (\var{analysis-objects}) \end{syntax} Analogous to \ttt{write\_analysis}, but the generated data tables are processed by \LaTeX\ and \gamelan, which produces Postscript and PDF versions of the displayed data. Example: \begin{code} compile_analysis \end{code} See Sec.~\ref{sec:analysis}. \section{Control Structures} Like any complete programming language, \sindarin\ provides means for branching and looping the program flow. \subsection{Conditionals} \subsubsection{if} \begin{syntax} if \var{logical\_expression} then \var{statements} \\ elsif \var{logical\_expression} then \var{statements} \\ else \var{statements} \\ endif \end{syntax} Execute statements conditionally, depending on the value of a logical expression. There may be none or multiple \ttt{elsif} branches, and the \ttt{else} branch is also optional. Example: \begin{code} if (sqrts > 2 * mtop) then integrate (top_pair_production) else printf "Top pair production is not possible" endif \end{code} The current \sindarin\ implementation puts some restriction on the statements that can appear in a conditional. For instance, process definitions must be done unconditionally. \subsection{Loops} \subsubsection{scan} \begin{syntax} scan \var{variable} = (\var{value-list}) \{ \var{statements} \} \end{syntax} Execute the statements repeatedly, once for each value of the scan variable. The statements are executed in a local context, analogous to the option statement list for commands. The value list is a comma-separated list of expressions, where each item evaluates to the value that is assigned to \ttt{\var{variable}} for this iteration. The type of the variable is not restricted to numeric, scans can be done for various object types. For instance, here is a scan over strings: \begin{code} scan string $str = ("%.3g", "%.4g", "%.5g") { printf $str (mW) } \end{code} % $ The output: \begin{interaction} [user variable] $str = "%.3g" 80.4 [user variable] $str = "%.4g" 80.42 [user variable] $str = "%.5g" 80.419 \end{interaction} % $ For a numeric scan variable in particular, there are iterators that implement the usual functionality of \ttt{for} loops. If the scan variable is of type integer, an iterator may take one of the forms \begin{syntax} \var{start-value} \verb|=>| \var{end-value} \\ \var{start-value} \verb|=>| \var{end-value} \verb|/+| \var{add-step} \\ \var{start-value} \verb|=>| \var{end-value} \verb|/-| \var{subtract-step} \\ \var{start-value} \verb|=>| \var{end-value} \verb|/*| \var{multiplicator} \\ \var{start-value} \verb|=>| \var{end-value} \verb|//| \var{divisor} \\ \end{syntax} The iterator can be put in place of an expression in the \ttt{\var{value-list}}. Here is an example: \begin{code} scan int i = (1, (3 => 5), (10 => 20 /+ 4)) \end{code} which results in the output \begin{interaction} [user variable] i = 1 [user variable] i = 3 [user variable] i = 4 [user variable] i = 5 [user variable] i = 10 [user variable] i = 14 [user variable] i = 18 \end{interaction} [Note that the \ttt{\var{statements}} part of the scan construct may be empty or absent.] For real scan variables, there are even more possibilities for iterators: \begin{syntax} \var{start-value} \verb|=>| \var{end-value} \\ \var{start-value} \verb|=>| \var{end-value} \verb|/+| \var{add-step} \\ \var{start-value} \verb|=>| \var{end-value} \verb|/-| \var{subtract-step} \\ \var{start-value} \verb|=>| \var{end-value} \verb|/*| \var{multiplicator} \\ \var{start-value} \verb|=>| \var{end-value} \verb|//| \var{divisor} \\ \var{start-value} \verb|=>| \var{end-value} \verb|/+/| \var{n-points-linear} \\ \var{start-value} \verb|=>| \var{end-value} \verb|/*/| \var{n-points-logarithmic} \\ \end{syntax} The first variant is equivalent to \ttt{/+ 1}. The \ttt{/+} and \ttt{/-} operators are intended to add or subtract the given step once for each iteration. Since in floating-point arithmetic this would be plagued by rounding ambiguities, the actual implementation first determines the (integer) number of iterations from the provided step value, then recomputes the step so that the iterations are evenly spaced with the first and last value included. The \ttt{/*} and \ttt{//} operators are analogous. Here, the initial value is intended to be multiplied by the step value once for each iteration. After determining the integer number of iterations, the actual scan values will be evenly spaced on a logarithmic scale. Finally, the \ttt{/+/} and \ttt{/*/} operators allow to specify the number of iterations (not counting the initial value) directly. The \ttt{\var{start-value}} and \ttt{\var{end-value}} are always included, and the intermediate values will be evenly spaced on a linear (\ttt{/+/}) or logarithmic (\ttt{/*/}) scale. Example: \begin{code} scan real mh = (130 GeV, (140 GeV => 160 GeV /+ 5 GeV), 180 GeV, (200 GeV => 1 TeV /*/ 10)) { integrate (higgs_decay) } \end{code} \subsection{Including Files} \subsubsection{include} \begin{syntax} include (\var{file-name}) \end{syntax} Include a \sindarin\ script from the specified file. The contents must be complete commands; they are compiled and executed as if they were part of the current script. Example: \begin{code} include ("default_cuts.sin") \end{code} \section{Expressions} \sindarin\ expressions are classified by their types. The type of an expression is verified when the script is compiled, before it is executed. This provides some safety against simple coding errors. Within expressions, grouping is done using ordinary brackets \ttt{()}. For subevent expressions, use square brackets \ttt{[]}. \subsection{Numeric} The language supports the classical numeric types \begin{itemize} \item \ttt{int} for integer: machine-default, usually 32 bit; \item \ttt{real}, usually \emph{double precision} or 64 bit; \item \ttt{complex}, consisting of real and imaginary part equivalent to a \ttt{real} each. \end{itemize} \sindarin\ supports arithmetic expressions similar to conventional languages. In arithmetic expressions, the three numeric types can be mixed as appropriate. The computation essentially follows the rules for mixed arithmetic in \ttt{Fortran}. The arithmetic operators are \verb|+|, \verb|-|, \verb|*|, \verb|/|, \verb|^|. Standard functions such as \ttt{sin}, \ttt{sqrt}, etc. are available. See Sec.~\ref{sec:real} to Sec.~\ref{sec:complex}. Numeric values can be associated with units. Units evaluate to numerical factors, and their use is optional, but they can be useful in the physics context for which \whizard\ is designed. Note that the default energy/mass unit is \verb|GeV|, and the default unit for cross sections is \verb|fbarn|. \subsection{Logical and String} The language also has the following standard types: \begin{itemize} \item \ttt{logical} (a.k.a.\ boolean). Logical variable names have a \ttt{?} (question mark) as prefix. \item \ttt{string} (arbitrary length). String variable names have a \ttt{\$} (dollar) sign as prefix. \end{itemize} There are comparisons, logical operations, string concatenation, and a mechanism for formatting objects as strings for output. \subsection{Special} Furthermore, \sindarin\ deals with a bunch of data types tailored specifically for Monte Carlo applications: \begin{itemize} \item \ttt{alias} objects denote a set of particle species. \item \ttt{subevt} objects denote a collection of particle momenta within an event. They have their uses in cut and analysis expressions. \item \ttt{process} object are generated by a \ttt{process} statement. There are no expressions involving processes, but they are referred to by \ttt{integrate} and \ttt{simulate} commands. \item \ttt{model}: There is always a current object of type and name \ttt{model}. Several models can be used concurrently by appropriately defining processes, but this happens behind the scenes. \item \ttt{beams}: Similarly, the current implementation allows only for a single object of this type at a given time, which is assigned by a \ttt{beams =} statement and used by \ttt{integrate}. \end{itemize} In the current implementation, \sindarin\ has no container data types derived from basic types, such as lists, arrays, or hashes, and there are no user-defined data types. (The \ttt{subevt} type is a container for particles in the context of events, but there is no type for an individual particle: this is represented as a one-particle \ttt{subevt}). There are also containers for inclusive processes which are however simply handled as an expansion into several components of a master process tag. \section{Variables} \label{sec:variables} \sindarin\ supports global variables, variables local to a scoping unit (the option body of a command, the body of a \ttt{scan} loop), and variables local to an expression. Some variables are predefined by the system (\emph{intrinsic variables}). They are further separated into \emph{independent} variables that can be reset by the user, and \emph{derived} or locked variables that are automatically computed by the program, but not directly user-modifiable. On top of that, the user is free to introduce his own variables (\emph{user variables}). The names of numerical variables consist of alphanumeric characters and underscores. The first character must not be a digit. Logical variable names are furthermore prefixed by a \ttt{?} (question mark) sign, while string variable names begin with a \ttt{\$} (dollar) sign. Character case does matter. In this manual we follow the convention that variable names consist of lower-case letters, digits, and underscores only, but you may also use upper-case letters if you wish. Physics models contain their own, specific set of numeric variables (masses, couplings). They are attached to the model where they are defined, so they appear and disappear with the model that is currently loaded. In particular, if two different models contain a variable with the same name, these two variables are nevertheless distinct: setting one doesn't affect the other. This feature might be called, in computer-science jargon, a \emph{mixin}. User variables -- global or local -- are declared by their type when they are introduced, and acquire an initial value upon declaration. Examples: \begin{quote} \begin{footnotesize} \begin{verbatim} int i = 3 real my_cut_value = 10 GeV complex c = 3 - 4 * I logical ?top_decay_allowed = mH > 2 * mtop string $hello = "Hello world!" alias q = d:u:s:c \end{verbatim} \end{footnotesize} \end{quote} An existing user variable can be assigned a new value without a declaration: \begin{quote} \begin{footnotesize} \begin{verbatim} i = i + 1 \end{verbatim} \end{footnotesize} \end{quote} and it may also be redeclared if the new declaration specifies the same type, this is equivalent to assigning a new value. Variables local to an expression are introduced by the \ttt{let ... in} contruct. Example: \begin{quote} \begin{footnotesize} \begin{verbatim} real a = let int n = 2 in x^n + y^n \end{verbatim} \end{footnotesize} \end{quote} The explicit \ttt{int} declaration is necessary only if the variable \ttt{n} has not been declared before. An intrinsic variable must not be declared: \ttt{let mtop = 175.3 GeV in \ldots} \ttt{let} constructs can be concatenated if several local variables need to be assigned: \ttt{let a = 3 in let b = 4 in \textit{expression}}. Variables of type \ttt{subevt} can only be defined in \ttt{let} constructs. Exclusively in the context of particle selections (event analysis), there are \emph{observables} as special numeric objects. They are used like numeric variables, but they are never declared or assigned. They get their value assigned dynamically, computed from the particle momentum configuration. Hence, they may be understood as (intrinsic and predefined) macros. By convention, observable names begin with a capital letter. Further macros are \begin{itemize} \item \ttt{cuts} and \ttt{analysis}. They are of type logical, and can be assigned an expression by the user. They are evaluated once for each event. \item \ttt{scale}, \ttt{factorization\_scale} and \ttt{renormalization\_scale} are real numeric macros which define the energy scale(s) of an event. The latter two override the former. If no scale is defined, the partonic energy is used as the process scale. \item \ttt{weight} is a real numeric macro. If it is assigned an expression, the expression is evaluated for each valid phase-space point, and the result multiplies the matrix element. \end{itemize} %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \chapter{\sindarin\ in Details} \label{chap:sindarin} \section{Data and expressions} \subsection{Real-valued objects} \label{sec:real} Real literals have their usual form, mantissa and, optionally, exponent: \begin{center} \ttt{0.}\quad \ttt{3.14}\quad \ttt{-.5}\quad \ttt{2.345e-3}\quad \ttt{.890E-023} \end{center} Internally, real values are treated as double precision. The values are read by the Fortran library, so details depend on its implementation. A special feature of \sindarin\ is that numerics (real and integer) can be immediately followed by a physical unit. The supported units are presently hard-coded, they are \begin{center} \ttt{meV}\quad \ttt{eV}\quad \ttt{keV}\quad \ttt{MeV}\quad \ttt{GeV}\quad \ttt{TeV} \\ \ttt{nbarn}\quad \ttt{pbarn}\quad \ttt{fbarn}\quad \ttt{abarn} \\ \ttt{rad}\quad \ttt{mrad}\quad \ttt{degree} \\ \ttt{\%} \end{center} If a number is followed by a unit, it is automatically normalized to the corresponding default unit: \ttt{14.TeV} is transformed into the real number \ttt{14000.} Default units are \ttt{GeV}, \ttt{fbarn}, and \ttt{rad}. The \ttt{\%} sign after a number has the effect that the number is multiplied by $0.01$. Note that no checks for consistency of units are done, so you can add \ttt{1 meV + 3 abarn} if you absolutely wish to. Omitting units is always allowed, in that case, the default unit is assumed. Units are not treated as variables. In particular, you can't write \ttt{theta / degree}, the correct form is \ttt{theta / 1 degree}. There is a single predefined real constant, namely $\pi$ which is referred to by the keyword \ttt{pi}. In addition, there is a single predefined complex constant, which is the complex unit $i$, being referred to by the keyword \ttt{I}. The arithmetic operators are \begin{center} \verb|+| \verb|-| \verb|*| \verb|/| \verb|^| \end{center} with their obvious meaning and the usual precedence rules. \sindarin\ supports a bunch of standard numerical functions, mostly equivalent to their Fortran counterparts: \begin{center} \ttt{abs}\quad \ttt{conjg}\quad \ttt{sgn}\quad \ttt{mod}\quad \ttt{modulo} \\ \ttt{sqrt}\quad \ttt{exp}\quad \ttt{log}\quad \ttt{log10} \\ \ttt{sin}\quad \ttt{cos}\quad \ttt{tan}\quad \ttt{asin}\quad \ttt{acos}\quad \ttt{atan} \\ \ttt{sinh}\quad \ttt{cosh}\quad \ttt{tanh} \end{center} (Unlike Fortran, the \ttt{sgn} function takes only one argument and returns $1.$, or $-1.$) The function argument is enclosed in brackets: \ttt{sqrt (2.)}, \ttt{tan (11.5 degree)}. There are two functions with two real arguments: \begin{center} \ttt{max}\quad \ttt{min} \end{center} Example: \verb|real lighter_mass = min (mZ, mH)| The following functions of a real convert to integer: \begin{center} \ttt{int}\quad \ttt{nint}\quad \ttt{floor}\quad \ttt{ceiling} %% \; . \end{center} and this converts to complex type: \begin{center} \ttt{complex} \end{center} Real values can be compared by the following operators, the result is a logical value: \begin{center} \verb|==|\quad \verb|<>| \\ \verb|>|\quad \verb|<|\quad \verb|>=|\quad \verb|<=| \end{center} In \sindarin, it is possible to have more than two operands in a logical expressions. The comparisons are done from left to right. Hence, \begin{center} \verb|115 GeV < mH < 180 GeV| \end{center} is valid \sindarin\ code and evaluates to \ttt{true} if the Higgs mass is in the given range. Tests for equality and inequality with machine-precision real numbers are notoriously unreliable and should be avoided altogether. To deal with this problem, \sindarin\ has the possibility to make the comparison operators ``fuzzy'' which should be read as ``equal (unequal) up to an absolute tolerance'', where the tolerance is given by the real-valued intrinsic variable \ttt{tolerance}. This variable is initially zero, but can be set to any value (for instance, \ttt{tolerance = 1.e-13} by the user. Note that for non-zero tolerance, operators like \verb|==| and \verb|<>| or \verb|<| and \verb|>| are not mutually exclusive\footnote{In older versions of \whizard, until v2.1.1, there used to be separate comparators for the comparisons up to a tolerance, namely \ttt{==\~{}} and \ttt{<>\~{}}. These have been discarded from v2.2.0 on in order to simplify the syntax.}. %%%%%%%%%%%%%%% \subsection{Integer-valued objects} \label{sec:integer} Integer literals are obvious: \begin{center} \ttt{1}\quad \ttt{-98765}\quad \ttt{0123} \end{center} Integers are always signed. Their range is the default-integer range as determined by the \fortran\ compiler. Like real values, integer values can be followed by a physical unit: \ttt{1 TeV}, \ttt{30 degree}. This actually transforms the integer into a real. Standard arithmetics is supported: \begin{center} \verb|+| \verb|-| \verb|*| \verb|/| \verb|^| \end{center} It is important to note that there is no fraction datatype, and pure integer arithmetics does not convert to real. Hence \ttt{3/4} evaluates to \ttt{0}, but \ttt{3 GeV / 4 GeV} evaluates to \ttt{0.75}. Since all arithmetics is handled by the underlying \fortran\ library, integer overflow is not detected. If in doubt, do real arithmetics. Integer functions are more restricted than real functions. We support the following: \begin{center} \ttt{abs}\quad \ttt{sgn}\quad \ttt{mod}\quad \ttt{modulo} \\ \ttt{max}\quad \ttt{min} \end{center} and the conversion functions \begin{center} \ttt{real}\quad \ttt{complex} \end{center} Comparisons of integers among themselves and with reals are possible using the same set of comparison operators as for real values. This includes the operators with a finite tolerance. %%%%%%%%%%%%%%%% \subsection{Complex-valued objects} \label{sec:complex} Complex variables and values are currently not yet used by the physics models implemented in \whizard. There complex input coupling constants are always split into their real and imaginary parts (or modulus and phase). They are exclusively available for arithmetic calculations. There is no form for complex literals. Complex values must be created via an arithmetic expression, \begin{center} \ttt{complex c = 1 + 2 * I} \end{center} where the imaginary unit \ttt{I} is predefined as a constant. The standard arithmetic operations are supported (also mixed with real and integer). Support for functions is currently still incomplete, among the supported functions there are \ttt{sqrt}, \ttt{log}, \ttt{exp}. \subsection{Logical-valued objects} There are two predefined logical constants, \ttt{true} and \ttt{false}. Logicals are \emph{not} equivalent to integers (like in C) or to strings (like in PERL), but they make up a type of their own. Only in \verb|printf| output, they are treated as strings, that is, they require the \verb|%s| conversion specifier. The names of logical variables begin with a question mark \ttt{?}. Here is the declaration of a logical user variable: \begin{quote} \begin{footnotesize} \begin{footnotesize} \begin{verbatim} logical ?higgs_decays_into_tt = mH > 2 * mtop \end{verbatim} \end{footnotesize} \end{footnotesize} \end{quote} Logical expressions use the standard boolean operations \begin{center} \ttt{or}\quad \ttt{and}\quad \ttt{not} \end{center} The results of comparisons (see above) are logicals. There is also a special logical operator with lower priority, concatenation by a semicolon: \begin{center} \ttt{\textit{lexpr1} ; \textit{lexpr2}} \end{center} This evaluates \textit{lexpr1} and throws its result away, then evaluates \textit{lexpr2} and returns that result. This feature is to used with logical expressions that have a side effect, namely the \ttt{record} function within analysis expressions. The primary use for intrinsic logicals are flags that change the behavior of commands. For instance, \ttt{?unweighted = true} and \ttt{?unweighted = false} switch the unweighting of simulated event samples on and off. \subsection{String-valued objects and string operations} \label{sec:sprintf} String literals are enclosed in double quotes: \ttt{"This is a string."} The empty string is \ttt{""}. String variables begin with the dollar sign: \verb|$|. There is only one string operation, concatenation \begin{quote} \begin{footnotesize} \begin{verbatim} string $foo = "abc" & "def" \end{verbatim} \end{footnotesize} \end{quote} However, it is possible to transform variables and values to a string using the \ttt{sprintf} function. This function is an interface to the system's \ttt{C} function \ttt{sprintf} with some restrictions and modifications. The allowed conversion specifiers are \begin{center} \verb|%d|\quad \verb|%i| (integer) \\ \verb|%e|\quad \verb|%f|\quad \verb|%g|\quad \verb|%E|\quad \verb|%F|\quad \verb|%G| (real) \\ \verb|%s| (string and logical) \end{center} The conversions can use flag parameter, field width, and precision, but length modifiers are not supported since they have no meaning for the application. (See also Sec.~\ref{sec:I/O}.) The \ttt{sprintf} function has the syntax \begin{center} \ttt{sprintf} \textit{format-string} \ttt{(}\textit{arg-list}\ttt{)} \end{center} This is an expression that evaluates to a string. The format string contains the mentioned conversion specifiers. The argument list is optional. The arguments are separated by commas. Allowed arguments are integer, real, logical, and string variables, and numeric expressions. Logical and string expressions can also be printed, but they have to be dressed as \emph{anonymous variables}. A logical anonymous variable has the form \ttt{?(}\textit{logical\_expr}\ttt{)} (example: \ttt{?(mH > 115 GeV)}). A string anonymous variable has the form \ttt{\$(}\textit{string-expr}\ttt{)}. Example: \begin{quote} \begin{footnotesize} \begin{verbatim} string $unit = "GeV" string $str = sprintf "mW = %f %s" (mW, $unit) \end{verbatim} \end{footnotesize} \end{quote} The related \ttt{printf} command with the same syntax prints the formatted string to standard output\footnote{In older versions of \whizard, until v2.1.1, there also used to be a \ttt{sprintd} function and a \ttt{printd} command for default formats without a format string. They have been discarded in order to simplify the syntax from version v2.2.0 on.}. \section{Particles and (sub)events} \subsection{Particle aliases} \label{sec:alias} A particle species is denoted by its name as a string: \verb|"W+"|. Alternatively, it can be addressed by an \ttt{alias}. For instance, the $W^+$ boson has the alias \ttt{Wp}. Aliases are used like variables in a context where a particle species is expected, and the user can specify his/her own aliases. An alias may either denote a single particle species or a class of particles species. A colon \ttt{:} concatenates particle names and aliases to yield multi-species aliases: \begin{quote} \begin{footnotesize} \begin{verbatim} alias quark = u:d:s alias wboson = "W+":"W-" \end{verbatim} \end{footnotesize} \end{quote} Such aliases are used for defining processes with summation over flavors, and for defining classes of particles for analysis. Each model files define both names and (single-particle) aliases for all particles it contains. Furthermore, it defines the class aliases \verb|colored| and \verb|charged| which are particularly useful for event analysis. \subsection{Subevents} Subevents are sets of particles, extracted from an event. The sets are unordered by default, but may be ordered by appropriate functions. Obviously, subevents are meaningful only in a context where an event is available. The possible context may be the specification of a cut, weight, scale, or analysis expression. To construct a simple subevent, we put a particle alias or an expression of type particle alias into square brackets: \begin{quote} \begin{footnotesize} \verb|["W+"]|\quad \verb|[u:d:s]|\quad \verb|[colored]| \end{footnotesize} \end{quote} These subevents evaluate to the set of all $W^+$ bosons (to be precise, their four-momenta), all $u$, $d$, or $s$ quarks, and all colored particles, respectively. A subevent can contain pseudoparticles, i.e., particle combinations. That is, the four-momenta of distinct particles are combined (added conmponent-wise), and the results become subevent elements just like ordinary particles. The (pseudo)particles in a subevent are non-overlapping. That is, for any of the particles in the original event, there is at most one (pseudo)particle in the subevent in which it is contained. Sometimes, variables (actually, named constants) of type subevent are useful. Subevent variables are declared by the \ttt{subevt} keyword, and their names carry the prefix \verb|@|. Subevent variables exist only within the scope of a \verb|cuts| (or \verb|scale|, \verb|analysis|, etc.) macro, which is evaluated in the presence of an actual event. In the macro body, they are assigned via the \ttt{let} construct: \begin{quote} \begin{footnotesize} \begin{verbatim} cuts = let subevt @jets = select if Pt > 10 GeV [colored] in all Theta > 10 degree [@jets, @jets] \end{verbatim} \end{footnotesize} \end{quote} In this expression, we first define \verb|@jets| to stand for the set of all colored partons with $p_T>10\;\mathrm{GeV}$. This abbreviation is then used in a logical expression, which evaluates to true if all relative angles between distinct jets are greater than $10$ degree. We note that the example also introduces pairs of subevents: the square bracket with two entries evaluates to the list of all possible pairs which do not overlap. The objects within square brackets can be either subevents or alias expressions. The latter are transformed into subevents before they are used. As a special case, the original event is always available as the predefined subevent \verb|@evt|. \subsection{Subevent functions} There are several functions that take a subevent (or an alias) as an argument and return a new subevent. Here we describe them: \subsubsection{collect} \begin{quote} \begin{footnotesize} \ttt{collect [\textit{particles}]} \\ \ttt{collect if \textit{condition} [\textit{particles}]} \\ \ttt{collect if \textit{condition} [\textit{particles}, \textit{ref\_particles}]} \end{footnotesize} \end{quote} First version: collect all particle momenta in the argument and combine them to a single four-momentum. The \textit{particles} argument may either be a \ttt{subevt} expression or an \ttt{alias} expression. The result is a one-entry \ttt{subevt}. In the second form, only those particles are collected which satisfy the \textit{condition}, a logical expression. Example: \ttt{collect if Pt > 10 GeV [colored]} The third version is useful if you want to put binary observables (i.e., observables constructed from two different particles) in the condition. The \textit{ref\_particles} provide the second argument for binary observables in the \textit{condition}. A particle is taken into account if the condition is true with respect to all reference particles that do not overlap with this particle. Example: \ttt{collect if Theta > 5 degree [photon, charged]}: combine all photons that are separated by 5 degrees from all charged particles. \subsubsection{cluster} \begin{quote} \begin{footnotesize} \ttt{cluster [\textit{particles}]} \\ \ttt{cluster if \textit{condition} [\textit{particles}]} \\ \end{footnotesize} \end{quote} First version: collect all particle momenta in the argument and cluster them to a set of jets. The \textit{particles} argument may either be a \ttt{subevt} expression or an \ttt{alias} expression. The result is a one-entry \ttt{subevt}. In the second form, only those particles are clustered which satisfy the \textit{condition}, a logical expression. Example: \ttt{cluster if Pt > 10 GeV [colored]} % The third version is usefule if you want to put binary observables (i.e., % observables constructed from two different particles) in the condition. The % \textit{ref\_particles} provide the second argument for binary observables in % the \textit{condition}. A particle is taken into account if the condition is % true with respect to all reference particles that do not overlap with this % particle. Example: \ttt{cluster if Theta > 5 degree [photon, charged]}: % combine all photons that are separated by 5 degrees from all charged % particles. This command is available from \whizard\ version 2.2.1 on, and only if the \fastjet\ package has been installed and linked with \whizard\ (cf. Sec.\ref{sec:fastjet}); in a future version of \whizard\ it is foreseen to have also an intrinsic clustering package inside \whizard\ which will be able to support some of the clustering algorithms below. To use it in an analysis, you have to set the variable \ttt{jet\_algorithm} to one of the predefined jet-algorithm values (integer constants): \begin{quote} \begin{footnotesize} \ttt{kt\_algorithm}\\ \ttt{cambridge\_algorithm}\\ \ttt{antikt\_algorithm}\\ \ttt{genkt\_algorithm}\\ \ttt{cambridge\_for\_passive\_algorithm}\\ \ttt{genkt\_for\_passive\_algorithm}\\ \ttt{ee\_kt\_algorithm}\\ \ttt{ee\_genkt\_algorithm}\\ \ttt{plugin\_algorithm} \end{footnotesize} \end{quote} and the variable \ttt{jet\_r} to the desired $R$ parameter value, as appropriate for the analysis and the jet algorithm. Example: \begin{quote} \begin{footnotesize} \begin{verbatim} jet_algorithm = antikt_algorithm jet_r = 0.7 cuts = all Pt > 15 GeV [cluster if Pt > 5 GeV [colored]] \end{verbatim} \end{footnotesize} \end{quote} \subsubsection{select\_b\_jet, select\_non\_b\_jet, select\_c\_jet, select\_light\_jet} This command is available from \whizard\ version 2.8.1 on, and it only generates anything non-trivial if the \fastjet\ package has been installed and linked with \whizard\ (cf. Sec.\ref{sec:fastjet}). It only returns sensible results when it is applied to subevents after the \ttt{cluster} command (cf. the paragraph before). It is similar to the \ttt{select} command, and accepts a logical expression as a possible condition. The four commands \ttt{select\_b\_jet}, \ttt{select\_non\_b\_jet}, \ttt{select\_c\_jet}, and \ttt{select\_light\_jet} select $b$ jets, non-$b$ jets (anything lighter than $b$s), $c$ jets (neither $b$ nor light) and light jets (anything besides $b$ and $c$), respectively. An example looks like this: \begin{quote} \begin{footnotesize} \begin{verbatim} alias lightjet = u:U:d:D:s:S:c:C:gl alias jet = b:B:lightjet process eebbjj = e1, E1 => b, B, lightjet, lightjet jet_algorithm = antikt_algorithm jet_r = 0.5 cuts = let subevt @clustered_jets = cluster [jet] in let subevt @bjets = select_b_jet [@clustered_jets] in ..... \end{verbatim} \end{footnotesize} \end{quote} \subsubsection{photon\_isolation} This command is available from \whizard\ version 2.8.1 on. It provides isolation of photons from hadronic (and possibly electromagnetic) activity in the event to define a (especially) NLO cross section that is completely perturbative. The isolation criterion according to Frixione, cf.~\cite{Frixione:1998jh}, removes the non-perturbative contribution from the photon fragmentation function. This command can in principle be applied to elementary hard process partons (and leptons), but generates something sensible only if the \fastjet\ package has been installed and linked with \whizard\ (cf. Sec.\ref{sec:fastjet}). There are three parameters which allow to tune the isolation, \ttt{photon\_iso\_r0}, which is the radius $R^0_\gamma$ of the isolation cone, \ttt{photon\_iso\_eps}, which is the fraction $\epsilon_\gamma$ of the photon (transverse) energy that enters the isolation criterion, and the exponent of the isolation cone, \ttt{photon\_iso\_n}, $n^\gamma$. For more information cf.~\cite{Frixione:1998jh}. The command allows also a conditional cut on the photon which is applied before the isolation takes place. The first argument are the photons in the event, the second the particles from which they should be isolated. If also the electromagnetic activity is to be isolated, photons need to be isolated from themselves and must be included in the second argument. This is mandatory if leptons appear in the second argument. Two examples look like this: \begin{quote} \begin{footnotesize} \begin{verbatim} alias jet = u:U:d:D:s:S:c:C:gl process eeaajj = e1, E1 => A, A, jet, jet jet_algorithm = antikt_algorithm jet_r = 0.5 cuts = photon_isolation if Pt > 10 GeV [A, jet] .... cuts = let subevt @jets = cluster [jet] in photon_isolation if Pt > 10 GeV [A, @jets] ..... process eeajmm = e1, E1 => A, jet, e2, E2 cuts = let subevt @jets = cluster [jet] in let subevt @iso = join [@jets, A:e2:E2] photon_isolation [A, @iso] \end{verbatim} \end{footnotesize} \end{quote} \subsubsection{combine} \begin{quote} \begin{footnotesize} \ttt{combine [\textit{particles\_1}, \textit{particles\_2}]} \\ \ttt{combine if \textit{condition}} [\textit{particles\_1}, \textit{particles\_2}] \end{footnotesize} \end{quote} Make a new subevent of composite particles. The composites are generated by combining all particles from subevent \textit{particles\_1} with all particles from subevent \textit{particles\_2} in all possible combinations. Overlapping combinations are excluded, however: if a (composite) particle in the first argument has a constituent in common with a composite particle in the second argument, the combination is dropped. In particular, this applies if the particles are identical. If a \textit{condition} is provided, the combination is done only when the logical expression, applied to the particle pair in question, returns true. For instance, here we reconstruct intermediate $W^-$ bosons: \begin{quote} \begin{footnotesize} \begin{verbatim} let @W_candidates = combine if 70 GeV < M < 80 GeV ["mu-", "numubar"] in ... \end{verbatim} \end{footnotesize} \end{quote} Note that the combination may fail, so the resulting subevent could be empty. \subsubsection{operator +} If there is no condition, the $+$ operator provides a convenient shorthand for the \verb|combine| command. In particular, it can be used if there are several particles to combine. Example: \begin{quote} \begin{footnotesize} \begin{verbatim} cuts = any 170 GeV < M < 180 GeV [b + lepton + invisible] \end{verbatim} \end{footnotesize} \end{quote} \subsubsection{select} \begin{quote} \begin{footnotesize} \ttt{select if \textit{condition} [\textit{particles}]} \\ \ttt{select if \textit{condition} [\textit{particles}, \textit{ref\_particles}]} \end{footnotesize} \end{quote} One argument: select all particles in the argument that satisfy the \textit{condition} and drop the rest. Two arguments: the \textit{ref\_particles} provide a second argument for binary observables. Select particles if the condition is satisfied for all reference particles. \subsubsection{extract} \begin{quote} \begin{footnotesize} \ttt{extract [\textit{particles}]} \\ \ttt{extract index \textit{index-value} [\textit{particles}]} \end{footnotesize} \end{quote} Return a single-particle subevent. In the first version, it contains the first particle in the subevent \textit{particles}. In the second version, the particle with index \textit{index-value} is returned, where \textit{index-value} is an integer expression. If its value is negative, the index is counted from the end of the subevent. The order of particles in an event or subevent is not always well-defined, so you may wish to sort the subevent before applying the \textit{extract} function to it. \subsubsection{sort} \begin{quote} \begin{footnotesize} \ttt{sort [\textit{particles}]} \\ \ttt{sort by \textit{observable} [\textit{particles}]} \\ \ttt{sort by \textit{observable} [\textit{particles}, \textit{ref\_particle}]} \end{footnotesize} \end{quote} Sort the subevent according to some criterion. If no criterion is supplied (first version), the subevent is sorted by increasing PDG code (first particles, then antiparticles). In the second version, the \textit{observable} is a real expression which is evaluated for each particle of the subevent in turn. The subevent is sorted by increasing value of this expression, for instance: \begin{quote} \begin{footnotesize} \begin{verbatim} let @sorted_evt = sort by Pt [@evt] in ... \end{verbatim} \end{footnotesize} \end{quote} In the third version, a reference particle is provided as second argument, so the sorting can be done for binary observables. It doesn't make much sense to have several reference particles at once, so the \ttt{sort} function uses only the first entry in the subevent \textit{ref-particle}, if it has more than one. \subsubsection{join} \begin{quote} \begin{footnotesize} \ttt{join [\textit{particles}, \textit{new\_particles}]} \\ \ttt{join if \textit{condition} [\textit{particles}, \textit{new\_particles}]} \end{footnotesize} \end{quote} This commands appends the particles in subevent \textit{new\_particles} to the subevent \textit{particles}, i.e., it joins the two particle sets. To be precise, a (pseudo)particle from \textit{new\_particles} is only appended if it does not overlap with any of the (pseudo)particles present in \textit{particles}, so the function will not produce overlapping entries. In the second version, each particle from \textit{new\_particles} is also checked with all particles in the first set whether \textit{condition} is fulfilled. If yes, and there is no overlap, it is appended, otherwise it is dropped. \subsubsection{operator \&} Subevents can also be concatenated by the operator \verb|&|. This effectively applies \ttt{join} to all operands in turn. Example: \begin{quote} \begin{footnotesize} \begin{verbatim} let @visible = select if Pt > 10 GeV and E > 5 GeV [photon] & select if Pt > 20 GeV and E > 10 GeV [colored] & select if Pt > 10 GeV [lepton] in ... \end{verbatim} \end{footnotesize} \end{quote} \subsection{Calculating observables} Observables (invariant mass \ttt{M}, energy \ttt{E}, \ldots) are used in expressions just like ordinary numeric variables. By convention, their names start with a capital letter. They are computed using a particle momentum (or two particle momenta) which are taken from a subsequent subevent argument. We can extract the value of an observable for an event and make it available for computing the \ttt{scale} value, or for histogramming etc.: \subsubsection{eval} \begin{quote} \begin{footnotesize} \ttt{eval \textit{expr} [\textit{particles}]} \\ \ttt{eval \textit{expr} [\textit{particles\_1}, \textit{particles\_2}]} \end{footnotesize} \end{quote} The function \ttt{eval} takes an expression involving observables and evaluates it for the first momentum (or momentum pair) of the subevent (or subevent pair) in square brackets that follows the expression. For example, \begin{quote} \begin{footnotesize} \begin{verbatim} eval Pt [colored] \end{verbatim} \end{footnotesize} \end{quote} evaluates to the transverse momentum of the first colored particle, \begin{quote} \begin{footnotesize} \begin{verbatim} eval M [@jets, @jets] \end{verbatim} \end{footnotesize} \end{quote} evaluates to the invariant mass of the first distinct pair of jets (assuming that \verb|@jets| has been defined in a \ttt{let} construct), and \begin{quote} \begin{footnotesize} \begin{verbatim} eval E - M [combine [e1, N1]] \end{verbatim} \end{footnotesize} \end{quote} evaluates to the difference of energy and mass of the combination of the first electron-neutrino pair in the event. The last example illustrates why observables are treated like variables, even though they are functions of particles: the \ttt{eval} construct with the particle reference in square brackets after the expression allows to compute derived observables -- observables which are functions of new observables -- without the need for hard-coding them as new functions. \subsection{Cuts and event selection} \label{sec:cuts} Instead of a numeric value, we can use observables to compute a logical value. \subsubsection{all} \begin{quote} \begin{footnotesize} \ttt{all \textit{logical\_expr} [\textit{particles}]} \\ \ttt{all \textit{logical\_expr} [\textit{particles\_1}, \textit{particles\_2}]} \end{footnotesize} \end{quote} The \ttt{all} construct expects a logical expression and one or two subevent arguments in square brackets. \begin{quote} \begin{footnotesize} \begin{verbatim} all Pt > 10 GeV [charged] all 80 GeV < M < 100 GeV [lepton, antilepton] \end{verbatim} \end{footnotesize} \end{quote} In the second example, \ttt{lepton} and \ttt{antilepton} should be aliases defined in a \ttt{let} construct. (Recall that aliases are promoted to subevents if they occur within square brackets.) This construction defines a cut. The result value is \ttt{true} if the logical expression evaluates to \ttt{true} for all particles in the subevent in square brackets. In the two-argument case it must be \ttt{true} for all non-overlapping combinations of particles in the two subevents. If one of the arguments is the empty subevent, the result is also \ttt{true}. \subsubsection{any} \begin{quote} \begin{footnotesize} \ttt{any \textit{logical\_expr} [\textit{particles}]} \\ \ttt{any \textit{logical\_expr} [\textit{particles\_1}, \textit{particles\_2}]} \end{footnotesize} \end{quote} The \ttt{any} construct is true if the logical expression is true for at least one particle or non-overlapping particle combination: \begin{quote} \begin{footnotesize} \begin{verbatim} any E > 100 GeV [photon] \end{verbatim} \end{footnotesize} \end{quote} This defines a trigger or selection condition. If a subevent argument is empty, it evaluates to \ttt{false} \subsubsection{no} \begin{quote} \begin{footnotesize} \ttt{no \textit{logical\_expr} [\textit{particles}]} \\ \ttt{no \textit{logical\_expr} [\textit{particles\_1}, \textit{particles\_2}]} \end{footnotesize} \end{quote} The \ttt{no} construct is true if the logical expression is true for no single one particle or non-overlapping particle combination: \begin{quote} \begin{footnotesize} \begin{verbatim} no 5 degree < Theta < 175 degree ["e-":"e+"] \end{verbatim} \end{footnotesize} \end{quote} This defines a veto condition. If a subevent argument is empty, it evaluates to \ttt{true}. It is equivalent to \ttt{not any\ldots}, but included for notational convenience. \subsection{More particle functions} \subsubsection{count} \begin{quote} \begin{footnotesize} \ttt{count [\textit{particles}]} \\ \ttt{count [\textit{particles\_1}, \textit{particles\_2}]} \\ \ttt{count if \textit{logical-expr} [\textit{particles}]} \\ \ttt{count if \textit{logical-expr} [\textit{particles}, \textit{ref\_particles}]} \end{footnotesize} \end{quote} This counts the number of events in a subevent, the result is of type \ttt{int}. If there is a conditional expression, it counts the number of \ttt{particle} in the subevent that pass the test. If there are two arguments, it counts the number of non-overlapping particle pairs (that pass the test, if any). \subsubsection{Predefined observables} The following real-valued observables are available in \sindarin\ for use in \ttt{eval}, \ttt{all}, \ttt{any}, \ttt{no}, and \ttt{count} constructs. The argument is always the subevent or alias enclosed in square brackets. \begin{itemize} \item \ttt{M2} \begin{itemize} \item One argument: Invariant mass squared of the (composite) particle in the argument. \item Two arguments: Invariant mass squared of the sum of the two momenta. \end{itemize} \item \ttt{M} \begin{itemize} \item Signed square root of \ttt{M2}: positive if $\ttt{M2}>0$, negative if $\ttt{M2}<0$. \end{itemize} \item \ttt{E} \begin{itemize} \item One argument: Energy of the (composite) particle in the argument. \item Two arguments: Sum of the energies of the two momenta. \end{itemize} \item \ttt{Px}, \ttt{Py}, \ttt{Pz} \begin{itemize} \item Like \ttt{E}, but returning the spatial momentum components. \end{itemize} \item \ttt{P} \begin{itemize} \item Like \ttt{E}, returning the absolute value of the spatial momentum. \end{itemize} \item \ttt{Pt}, \ttt{Pl} \begin{itemize} \item Like \ttt{E}, returning the transversal and longitudinal momentum, respectively. \end{itemize} \item \ttt{Theta} \begin{itemize} \item One argument: Absolute polar angle in the lab frame \item Two arguments: Angular distance of two particles in the lab frame. \end{itemize} \item \ttt{Theta\_star} Only with two arguments, gives the relative polar angle of the two momenta in the rest system of the momentum sum (i.e. mother particle). \item \ttt{Phi} \begin{itemize} \item One argument: Absolute azimuthal angle in the lab frame \item Two arguments: Azimuthal distance of two particles in the lab frame \end{itemize} \item \ttt{Rap}, \ttt{Eta} \begin{itemize} \item One argument: rapidity / pseudorapidity \item Two arguments: rapidity / pseudorapidity difference \end{itemize} \item \ttt{Dist} \begin{itemize} \item Two arguments: Distance on the $\eta$-$\phi$ cylinder, i.e., $\sqrt{\Delta\eta^2 + \Delta\phi^2}$ \end{itemize} \item \ttt{kT} \begin{itemize} \item Two arguments: $k_T$ jet clustering variable: $2 \min (E_{j1}^2, E_{j2}^2) / Q^2 \times (1 - \cos\theta_{j1,j2})$. At the moment, $Q^2 = 1$ GeV$^2$. \end{itemize} \end{itemize} There are also integer-valued observables: \begin{itemize} \item \ttt{PDG} \begin{itemize} \item One argument: PDG code of the particle. For a composite particle, the code is undefined (value 0). For flavor sums in the \ttt{cuts} statement, this observable always returns the same flavor, i.e. the first one from the flavor list. It is thus only sensible to use it in an \ttt{analysis} or \ttt{selection} statement when simulating events. \end{itemize} \item \ttt{Ncol} \begin{itemize} \item One argument: Number of open color lines. Only count color lines, not anticolor lines. This is defined only if the global flag \ttt{?colorize\_subevt} is true. \end{itemize} \item \ttt{Nacl} \begin{itemize} \item One argument: Number of open anticolor lines. Only count anticolor lines, not color lines. This is defined only if the global flag \ttt{?colorize\_subevt} is true. \end{itemize} \end{itemize} %%%%%%%%%%%%%%% \section{Physics Models} \label{sec:models} A physics model is a combination of particles, numerical parameters (masses, couplings, widths), and Feynman rules. Many physics analyses are done in the context of the Standard Model (SM). The SM is also the default model for \whizard. Alternatively, you can choose a subset of the SM (QED or QCD), variants of the SM (e.g., with or without nontrivial CKM matrix), or various extensions of the SM. The complete list is displayed in Table~\ref{tab:models}. The model definitions are contained in text files with filename extension \ttt{.mdl}, e.g., \ttt{SM.mdl}, which are located in the \ttt{share/models} subdirectory of the \whizard\ installation. These files are easily readable, so if you need details of a model implementation, inspect their contents. The model file contains the complete particle and parameter definitions as well as their default values. It also contains a list of vertices. This is used only for phase-space setup; the vertices used for generating amplitudes and the corresponding Feynman rules are stored in different files within the \oMega\ source tree. In a \sindarin\ script, a model is a special object of type \ttt{model}. There is always a \emph{current} model. Initially, this is the SM, so on startup \whizard\ reads the \ttt{SM.mdl} model file and assigns its content to the current model object. (You can change the default model by the \ttt{--model} option on the command line. Also the preloading of a model can be switched off with the \ttt{--no-model} option) Once the model has been loaded, you can define processes for the model, and you have all independent model parameters at your disposal. As noted before, these are intrinsic parameters which need not be declared when you assign them a value, for instance: \begin{quote} \begin{footnotesize} \begin{verbatim} mW = 80.33 GeV wH = 243.1 MeV \end{verbatim} \end{footnotesize} \end{quote} Other parameters are \emph{derived}. They can be used in expressions like any other parameter, they are also intrinsic, but they cannot be modified directly at all. For instance, the electromagnetic coupling \ttt{ee} is a derived parameter. If you change either \ttt{GF} (the Fermi constant), \ttt{mW} (the $W$ mass), or \ttt{mZ} (the $Z$ mass), this parameter will reflect the change, but setting it directly is an error. In other words, the SM is defined within \whizard\ in the $G_F$-$m_W$-$m_Z$ scheme. (While this scheme is unusual for loop calculations, it is natural for a tree-level event generator where the $Z$ and $W$ poles have to be at their experimentally determined location\footnote{In future versions of \whizard\ it is foreseen to implement other electroweak schemes.}.) The model also defines the particle names and aliases that you can use for defining processes, cuts, or analyses. If you would like to generate a SUSY process instead, for instance, you can assign a different model (cf.\ Table~\ref{tab:models}) to the current model object: \begin{quote} \begin{footnotesize} \begin{verbatim} model = MSSM \end{verbatim} \end{footnotesize} \end{quote} This assignment has the consequence that the list of SM parameters and particles is replaced by the corresponding MSSM list (which is much longer). The MSSM contains essentially all SM parameters by the same name, but in fact they are different parameters. This is revealed when you say \begin{quote} \begin{footnotesize} \begin{verbatim} model = SM mb = 5.0 GeV model = MSSM show (mb) \end{verbatim} \end{footnotesize} \end{quote} After the model is reassigned, you will see the MSSM value of $m_b$ which still has its default value, not the one you have given. However, if you revert to the SM later, \begin{quote} \begin{footnotesize} \begin{verbatim} model = SM show (mb) \end{verbatim} \end{footnotesize} \end{quote} you will see that your modification of the SM's $m_b$ value has been remembered. If you want both mass values to agree, you have to set them separately in the context of their respective model. Although this might seem cumbersome at first, it is nevertheless a sensible procedure since the parameters defined by the user might anyhow not be defined or available for all chosen models. When using two different models which need an SLHA input file, these {\em have} to be provided for both models. Within a given scope, there is only one current model. The current model can be reset permanently as above. It can also be temporarily be reset in a local scope, i.e., the option body of a command or the body of a \ttt{scan} loop. It is thus possible to use several models within the same script. For instance, you may define a SUSY signal process and a pure-SM background process. Each process depends only on the respective model's parameter set, and a change to a parameter in one of the models affects only the corresponding process. \section{Processes} \label{sec:processes} The purpose of \whizard\ is the integration and simulation of high-energy physics processes: scatterings and decays. Hence, \ttt{process} objects play the central role in \sindarin\ scripts. A \sindarin\ script may contain an arbitrary number of process definitions. The initial states need not agree, and the processes may belong to different physics models. \subsection{Process definition} \label{sec:procdef} A process object is defined in a straightforward notation. The definition syntax is straightforward: \begin{quote} \begin{footnotesize} \ttt{process \textit{process-id} = \textit{incoming-particles}} \verb|=>| \ttt{\textit{outgoing-particles}} \end{footnotesize} \end{quote} Here are typical examples: \begin{quote} \begin{footnotesize} \begin{verbatim} process w_pair_production = e1, E1 => "W+", "W-" process zdecay = Z => u, ubar \end{verbatim} \end{footnotesize} \end{quote} Throughout the program, the process will be identified by its \textit{process-id}, so this is the name of the process object. This identifier is arbitrary, chosen by the user. It follows the rules for variable names, so it consists of alphanumeric characters and underscores, where the first character is not numeric. As a special rule, it must not contain upper-case characters. The reason is that this name is used for identifying the process not just within the script, but also within the \fortran\ code that the matrix-element generator produces for this process. After the equals sign, there follow the lists of incoming and outgoing particles. The number of incoming particles is either one or two: scattering processes and decay processes. The number of outgoing particles should be two or larger (as $2\to 1$ processes are proportional to a $\delta$ function they can only be sensibly integrated when using a structure function like a hadron collider PDF or a beamstrahlung spectrum.). There is no hard upper limit; the complexity of processes that \whizard\ can handle depends only on the practical computing limitations (CPU time and memory). Roughly speaking, one can assume that processes up to $2\to 6$ particles are safe, $2\to 8$ processes are feasible given sufficient time for reaching a stable integration, while more complicated processes are largely unexplored. We emphasize that in the default setup, the matrix element of a physics process is computed exactly in leading-order perturbation theory, i.e., at tree level. There is no restriction of intermediate states, the result always contains the complete set of Feynman graphs that connect the initial with the final state. If the result would actually be expanded in Feynman graphs (which is not done by the \oMega\ matrix element generator that \whizard\ uses), the number of graphs can easily reach several thousands, depending on the complexity of the process and on the physics model. More details about the different methods for quantum field-theoretical matrix elements can be found in Chap.~\ref{chap:hardint}. In the following, we will discuss particle names, options for processes like restrictions on intermediate states, parallelization, flavor sums and process components for inclusive event samples (process containers). \subsection{Particle names} The particle names are taken from the particle definition in the current model file. Looking at the SM, for instance, the electron entry in \ttt{share/models/SM.mdl} reads \begin{quote} \begin{footnotesize} \begin{verbatim} particle E_LEPTON 11 spin 1/2 charge -1 isospin -1/2 name "e-" e1 electron e anti "e+" E1 positron tex_name "e^-" tex_anti "e^+" mass me \end{verbatim} \end{footnotesize} \end{quote} This tells that you can identify an electron either as \verb|"e-"|, \verb|e1|, \verb|electron|, or simply \verb|e|. The first version is used for output, but needs to be quoted, because otherwise \sindarin\ would interpret the minus sign as an operator. (Technically, unquoted particle identifiers are aliases, while the quoted versions -- you can say either \verb|e1| or \verb|"e1"| -- are names. On input, this makes no difference.) The alternative version \verb|e1| follows a convention, inherited from \comphep~\cite{Boos:2004kh}, that particles are indicated by lower case, antiparticles by upper case, and for leptons, the generation index is appended: \verb|e2| is the muon, \verb|e3| the tau. These alternative names need not be quoted because they contain no special characters. In Table~\ref{tab:SM-particles}, we list the recommended names as well as mass and width parameters for all SM particles. For other models, you may look up the names in the corresponding model file. \begin{table}[p] \begin{center} \begin{tabular}{|l|l|l|l|cc|} \hline & Particle & Output name & Alternative names & Mass & Width\\ \hline\hline Leptons &$e^-$ & \verb|e-| & \ttt{e1}\quad\ttt{electron} & \ttt{me} & \\ &$e^+$ & \verb|e+| & \ttt{E1}\quad\ttt{positron} & \ttt{me} & \\ \hline &$\mu^-$ & \verb|mu-| & \ttt{e2}\quad\ttt{muon} & \ttt{mmu} & \\ &$\mu^+$ & \verb|mu+| & \ttt{E2} & \ttt{mmu} & \\ \hline &$\tau^-$ & \verb|tau-| & \ttt{e3}\quad\ttt{tauon} & \ttt{mtau} & \\ &$\tau^+$ & \verb|tau+| & \ttt{E3} & \ttt{mtau} & \\ \hline\hline Neutrinos &$\nu_e$ & \verb|nue| & \ttt{n1} & & \\ &$\bar\nu_e$ & \verb|nuebar| & \ttt{N1} & & \\ \hline &$\nu_\mu$ & \verb|numu| & \ttt{n2} & & \\ &$\bar\nu_\mu$ & \verb|numubar| & \ttt{N2} & & \\ \hline &$\nu_\tau$ & \verb|nutau| & \ttt{n3} & & \\ &$\bar\nu_\tau$ & \verb|nutaubar| & \ttt{N3} & & \\ \hline\hline Quarks &$d$ & \verb|d| & \ttt{down} & & \\ &$\bar d$ & \verb|dbar| & \ttt{D} & & \\ \hline &$u$ & \verb|u| & \ttt{up} & & \\ &$\bar u$ & \verb|ubar| & \ttt{U} & & \\ \hline &$s$ & \verb|s| & \ttt{strange} & \ttt{ms} & \\ &$\bar s$ & \verb|sbar| & \ttt{S} & \ttt{ms} & \\ \hline &$c$ & \verb|c| & \ttt{charm} & \ttt{mc} & \\ &$\bar c$ & \verb|cbar| & \ttt{C} & \ttt{mc} & \\ \hline &$b$ & \verb|b| & \ttt{bottom} & \ttt{mb} & \\ &$\bar b$ & \verb|bbar| & \ttt{B} & \ttt{mb} & \\ \hline &$t$ & \verb|t| & \ttt{top} & \ttt{mtop} & \ttt{wtop} \\ &$\bar t$ & \verb|tbar| & \ttt{T} & \ttt{mtop} & \ttt{wtop} \\ \hline\hline Vector bosons &$g$ & \verb|gl| & \ttt{g}\quad\ttt{G}\quad\ttt{gluon} & & \\ \hline &$\gamma$ & \verb|A| & \ttt{gamma}\quad\ttt{photon} & & \\ \hline &$Z$ & \verb|Z| & & \ttt{mZ} & \ttt{wZ} \\ \hline &$W^+$ & \verb|W+| & \ttt{Wp} & \ttt{mW} & \ttt{wW} \\ &$W^-$ & \verb|W-| & \ttt{Wm} & \ttt{mW} & \ttt{wW} \\ \hline\hline Scalar bosons &$H$ & \verb|H| & \ttt{h}\quad \ttt{Higgs} & \ttt{mH} & \ttt{wH} \\ \hline \end{tabular} \end{center} \caption{\label{tab:SM-particles} Names that can be used for SM particles. Also shown are the intrinsic variables that can be used to set mass and width, if applicable.} \end{table} Where no mass or width parameters are listed in the table, the particle is assumed to be massless or stable, respectively. This is obvious for particles such as the photon. For neutrinos, the mass is meaningless to particle physics collider experiments, so it is zero. For quarks, the $u$ or $d$ quark mass is unobservable directly, so we also set it zero. For the heavier quarks, the mass may play a role, so it is kept. (The $s$ quark is borderline; one may argue that its mass is also unobservable directly.) On the other hand, the electron mass is relevant, e.g., in photon radiation without cuts, so it is not zero by default. It pays off to set particle masses to zero, if the approximation is justified, since fewer helicity states will contribute to the matrix element. Switching off one of the helicity states of an external fermion speeds up the calculation by a factor of two. Therefore, script files will usually contain the assignments \begin{quote} \begin{footnotesize} \begin{verbatim} me = 0 mmu = 0 ms = 0 mc = 0 \end{verbatim} \end{footnotesize} \end{quote} unless they deal with processes where this simplification is phenomenologically unacceptable. Often $m_\tau$ and $m_b$ can also be neglected, but this excludes processes where the Higgs couplings of $\tau$ or $b$ are relevant. Setting fermion masses to zero enables, furthermore, the possibility to define multi-flavor aliases \begin{quote} \begin{footnotesize} \begin{verbatim} alias q = d:u:s:c alias Q = D:U:S:C \end{verbatim} \end{footnotesize} \end{quote} and handle processes such as \begin{quote} \begin{footnotesize} \begin{verbatim} process two_jets_at_ilc = e1, E1 => q, Q process w_pairs_at_lhc = q, Q => Wp, Wm \end{verbatim} \end{footnotesize} \end{quote} where a sum over all allowed flavor combination is automatically included. For technical reasons, such flavor sums are possible only for massless particles (or more general for mass-degenerate particles). If you want to generate inclusive processes with sums over particles of different masses (e.g. summing over $W/Z$ in the final state etc.), confer below the section about process components, Sec.~\ref{sec:processcomp}. Assignments of masses, widths and other parameters are actually in effect when a process is integrated, not when it is defined. So, these assignments may come before or after the process definition, with no significant difference. However, since flavor summation requires masses to be zero, the assignments may be put before the alias definition which is used in the process. The muon, tau, and the heavier quarks are actually unstable. However, the width is set to zero because their decay is a macroscopic effect and, except for the muon, affected by hadron physics, so it is not described by \whizard. (In the current \whizard\ setup, all decays occur at the production vertex. A future version may describe hadronic physics and/or macroscopic particle propagation, and this restriction may be eventually removed.) \subsection{Options for processes} \label{sec:process options} The \ttt{process} definition may contain an optional argument: \begin{quote} \begin{footnotesize} \ttt{process \textit{process-id} = \textit{incoming-particles}} \verb|=>| \ttt{\textit{outgoing-particles}} \ttt{\{\textit{options\ldots}\}} \end{footnotesize} \end{quote} The \textit{options} are a \sindarin\ script that is executed in a context local to the \ttt{process} command. The assignments it contains apply only to the process that is defined. In the following, we describe the set of potentially useful options (which all can be also set globally): \subsubsection{Model reassignment} It is possible to locally reassign the model via a \ttt{model =} statment, permitting the definition of process using a model other than the globally selected model. The process will retain this association during integration and event generation. \subsubsection{Restrictions on matrix elements} \label{subsec:restrictions} Another useful option is the setting \begin{quote} \begin{footnotesize} \verb|$restrictions =| \ttt{\textit{string}} \end{footnotesize} \end{quote} This option allows to select particular classes of Feynman graphs for the process when using the \oMega\ matrix element generator. The \verb|$restrictions| string specifies e.g. propagators that the graph must contain. Here is an example: \begin{code} process zh_invis = e1, E1 => n1:n2:n3, N1:N2:N3, H { $restrictions = "1+2 ~ Z" } \end{code} The complete process $e^-e^+ \to \nu\bar\nu H$, summed over all neutrino generations, contains both $ZH$ pair production (Higgs-strahlung) and $W^+W^-\to H$ fusion. The restrictions string selects the Higgs-strahlung graph where the initial electrons combine to a $Z$ boson. Here, the particles in the process are consecutively numbered, starting with the initial particles. An alternative for the same selection would be \verb|$restrictions = "3+4 ~ Z"|. Restrictions can be combined using \verb|&&|, for instance \begin{code} $restrictions = "1+2 ~ Z && 3 + 4 ~ Z" \end{code} which is redundant here, however. The restriction keeps the full energy dependence in the intermediate propagator, so the Breit-Wigner shape can be observed in distributions. This breaks gauge invariance, in particular if the intermediate state is off shell, so you should use the feature only if you know the implications. For more details, cf. the Chap.~\ref{chap:hardint} and the \oMega\ manual. Other restrictions that can be combined with the restrictions above on intermediate propagators allow to exclude certain particles from intermediate propagators, or to exclude certain vertices from the matrix elements. For example, \begin{code} process eemm = e1, E1 => e2, E2 { $restrictions = "!A" } \end{code} would exclude all photon propagators from the matrix element and leaves only the $Z$ exchange here. In the same way, \verb|$restrictions = "!gl"| would exclude all gluon exchange. This exclusion of internal propagators works also for lists of particles, like \begin{code} $restrictions = "!Z:H" \end{code} excludes all $Z$ and $H$ propagators from the matrix elements. Besides excluding certain particles as internal lines, it is also possible to exclude certain vertices using the restriction command \begin{code} process eeww = e1, E1 => Wp, Wm { $restrictions = "^[W+,W-,Z]" } \end{code} This would generate the matrix element for the production of two $W$ bosons at LEP without the non-Abelian vertex $W^+W^-Z$. Again, these restrictions are able to work on lists, so \begin{code} $restrictions = "^[W+,W-,A:Z]" \end{code} would exclude all triple gauge boson vertices from the above process and leave only the $t$-channel neutrino exchange. It is also possible to exlude vertices by their coupling constants, e.g. the photon exchange in the process $e^+ e^- \to \mu^+ \mu^-$ can also be removed by the following restriction: \begin{code} $restrictions = "^qlep" \end{code} Here, \ttt{qlep} is the \fortran\ variable for the coupling constant of the electron-positron-photon vertex. \begin{table} \begin{center} \begin{tabular}{|l|l|} \hline \verb|3+4~Z| & external particles 3 and 4 must come from intermediate $Z$ \\\hline \verb| && | & logical ``and'', e.g. in \verb| 3+5~t && 4+6~tbar| \\\hline \verb| !A | & exclude all $\gamma$ propagators \\\hline \verb| !e+:nue | & exclude a list of propagators, here $\gamma$, $\nu_e$ \\\hline \verb|^qlep:gnclep| & exclude all vertices with \ttt{qlep},\ttt{gnclep} coupling constants \\\hline \verb|^[A:Z,W+,W-]| & exclude all vertices $W^+W^-Z$, $W^+W^-\gamma$ \\\hline \verb|^c1:c2:c3[H,H,H]| & exclude all triple Higgs couplings with $c_i$ constants \\\hline \end{tabular} \end{center} \caption{List of possible restrictions that can be applied to \oMega\ matrix elements.} \label{tab:restrictions} \end{table} The Tab.~\ref{tab:restrictions} gives a list of options that can be applied to the \oMega\ matrix elements. \subsubsection{Other options} There are some further options that the \oMega\ matrix-element generator can take. If desired, any string of options that is contained in this variable \begin{quote} \begin{footnotesize} \verb|$omega_flags =| \ttt{\textit{string}} \end{footnotesize} \end{quote} will be copied verbatim to the \oMega\ call, after all other options. One important application is the scheme of treating the width of unstable particles in the $t$-channel. This is modified by the \verb|model:| class of \oMega\ options. It is well known that for some processes, e.g., single $W$ production from photon-$W$ fusion, gauge invariance puts constraints on the treatment of the unstable-particle width. By default, \oMega\ puts a nonzero width in the $s$ channel only. This correctly represents the resummed Dyson series for the propagator, but it violates QED gauge invariance, although the effect is only visible if the cuts permit the photon to be almost on-shell. An alternative is \begin{quote} \begin{footnotesize} \verb|$omega_flags = "-model:fudged_width"| \end{footnotesize} \end{quote} which puts zero width in the matrix element, so that gauge cancellations hold, and reinstates the $s$-channel width in the appropriate places by an overall factor that multiplies the whole matrix element. Another possibility is \begin{quote} \begin{footnotesize} \verb|$omega_flags = "-model:constant_width"| \end{footnotesize} \end{quote} which puts the width both in the $s$ and in the $t$ channel everywhere. Note that both options apply only to charged unstable particles, such as the $W$ boson. \subsubsection{Multithreaded calculation of helicity sums via OpenMP} \label{sec:openmp} On multicore and / or multiprocessor systems, it is possible to speed up the calculation by using multiple threads to perform the helicity sum in the matrix element calculation. As the processing time used by \whizard\ is not used up solely in the matrix element, the speedup thus achieved varies greatly depending on the process under consideration; while simple processes without flavor sums do not profit significantly from this parallelization, the computation time for processes involving flavor sums with four or more particles in the final state is typically reduced by a factor between two and three when utilizing four parallel threads. The parallization is implemented using \ttt{OpenMP} and requires \whizard\ to be compiled with an \ttt{OpenMP} aware compiler and the appropiate compiler flags This is done in the configuration step, cf.\ Sec.~\ref{sec:installation}. As with all \ttt{OpenMP} programs, the default number of threads used at runtime is up to the compiler runtime support and typically set to the number of independent hardware threads (cores / processors / hyperthreads) available in the system. This default can be adjusted by setting the \ttt{OMP\_NUM\_THREADS} environment variable prior to calling WHIZARD. Alternatively, the available number of threads can be reset anytime by the \sindarin\ parameter \ttt{openmp\_num\_threads}. Note however that the total number of threads that can be sensibly used is limited by the number of nonvanishing helicity combinations. %%%%%%%%%%%%%%% \subsection{Process components} \label{sec:processcomp} It was mentioned above that processes with flavor sums (in the initial or final state or both) have to be mass-degenerate (in most cases massless) in all particles that are summed over at a certain position. This condition is necessary in order to use the same phase-space parameterization and integration for the flavor-summed process. However, in many applications the user wants to handle inclusive process definitions, e.g. by defining inclusive decays, inclusive SUSY samples at hadron colliders (gluino pairs, squark pairs, gluino-squark associated production), or maybe lepton-inclusive samples where the tau and muon mass should be kept at different values. In \whizard\, from version v2.2.0 on, there is the possibility to define such inclusive process containers. The infrastructure for this feature is realized via so-called process components: processes are allowed to contain several process components. Those components need not be provided by the same matrix element generator, e.g. internal matrix elements, \oMega\ matrix elements, external matrix element (e.g. from a one-loop program, OLP) can be mixed. The very same infrastructure can also be used for next-to-leading order (NLO) calculations, containing the born with real emission, possible subtraction terms to make the several components infrared- and collinear finite, as well as the virtual corrections. Here, we want to discuss the use for inclusive particle samples. There are several options, the simplest of which to add up different final states by just using the \ttt{+} operator in \sindarin, e.g.: \begin{quote} \begin{footnotesize} \begin{verbatim} process multi_comp = e1, E1 => (e2, E2) + (e3, E3) + (A, A) \end{verbatim} \end{footnotesize} \end{quote} The brackets are not only used for a better grouping of the expressions, they are not mandatory for \whizard\ to interpret the sum correctly. When integrating, \whizard\ tells you that this a process with three different components: \begin{footnotesize} \begin{Verbatim} | Initializing integration for process multi_comp_1_p1: | ------------------------------------------------------------------------ | Process [scattering]: 'multi_comp' | Library name = 'default_lib' | Process index = 1 | Process components: | 1: 'multi_comp_i1': e-, e+ => m-, m+ [omega] | 2: 'multi_comp_i2': e-, e+ => t-, t+ [omega] | 3: 'multi_comp_i3': e-, e+ => A, A [omega] | ------------------------------------------------------------------------ \end{Verbatim} \end{footnotesize} A different phase-space setup is used for each different component. The integration for each different component is performed separately, and displayed on screen. At the end, a sum of all components is shown. All files that depend on the components are being attached an \ttt{\_i{\em }} where \ttt{{\em }} is the number of the process component that appears in the list above: the \fortran\ code for the matrix element, the \ttt{.phs} file for the phase space parameterization, and the grid files for the \vamp\ Monte-Carlo integration (or any other integration method). However, there will be only one event file for the inclusive process, into which a mixture of events according to the size of the individual process component cross section enter. More options are to specify additive lists of particles. \whizard\ then expands the final states according to tensor product algebra: \begin{quote} \begin{footnotesize} \begin{verbatim} process multi_tensor = e1, E1 => e2 + e3 + A, E2 + E3 + A \end{verbatim} \end{footnotesize} \end{quote} This gives the same three process components as above, but \whizard\ recognized that e.g. $e^- e^+ \to \mu^- \gamma$ is a vanishing process, hence the numbering is different: \begin{footnotesize} \begin{Verbatim} | Process component 'multi_tensor_i2': matrix element vanishes | Process component 'multi_tensor_i3': matrix element vanishes | Process component 'multi_tensor_i4': matrix element vanishes | Process component 'multi_tensor_i6': matrix element vanishes | Process component 'multi_tensor_i7': matrix element vanishes | Process component 'multi_tensor_i8': matrix element vanishes | ------------------------------------------------------------------------ | Process [scattering]: 'multi_tensor' | Library name = 'default_lib' | Process index = 1 | Process components: | 1: 'multi_tensor_i1': e-, e+ => m-, m+ [omega] | 5: 'multi_tensor_i5': e-, e+ => t-, t+ [omega] | 9: 'multi_tensor_i9': e-, e+ => A, A [omega] | ------------------------------------------------------------------------ \end{Verbatim} \end{footnotesize} Identical copies of the same process that would be created by expanding the tensor product of final states are eliminated and appear only once in the final sum of process components. Naturally, inclusive process definitions are also available for decays: \begin{quote} \begin{footnotesize} \begin{Verbatim} process multi_dec = Wp => E2 + E3, n2 + n3 \end{Verbatim} \end{footnotesize} \end{quote} This yields: \begin{footnotesize} \begin{Verbatim} | Process component 'multi_dec_i2': matrix element vanishes | Process component 'multi_dec_i3': matrix element vanishes | ------------------------------------------------------------------------ | Process [decay]: 'multi_dec' | Library name = 'default_lib' | Process index = 2 | Process components: | 1: 'multi_dec_i1': W+ => mu+, numu [omega] | 4: 'multi_dec_i4': W+ => tau+, nutau [omega] | ------------------------------------------------------------------------ \end{Verbatim} \end{footnotesize} %%%%%%%%%%%%%%% \subsection{Compilation} \label{sec:compilation} Once processes have been set up, to make them available for integration they have to be compiled. More precisely, the matrix-element generator \oMega\ (and it works similarly if a different matrix element method is chosen) is called to generate matrix element code, the compiler is called to transform this \fortran\ code into object files, and the linker is called to collect this in a dynamically loadable library. Finally, this library is linked to the program. From version v2.2.0 of \whizard\ this is no longer done by system calls of the OS but steered via process library Makefiles. Hence, the user can execute and manipulate those Makefiles in order to manually intervene in the particular steps, if he/she wants to do so. All this is done automatically when an \ttt{integrate}, \ttt{unstable}, or \ttt{simulate} command is encountered for the first time. You may also force compilation explicitly by the command \begin{quote} \begin{footnotesize} \begin{verbatim} compile \end{verbatim} \end{footnotesize} \end{quote} which performs all steps as listed above, including loading the generated library. The \fortran\ part of the compilation will be done using the \fortran\ compiler specified by the string variable \verb|$fc| and the compiler flags specified as \verb|$fcflags|. The default settings are those that have been used for compiling \whizard\ itself during installation. For library compatibility, you should stick to the compiler. The flags may be set differently. They are applied in the compilation and loading steps, and they are processed by \ttt{libtool}, so \ttt{libtool}-specific flags can also be given. \whizard\ has some precautions against unnecessary repetitions. Hence, when a \ttt{compile} command is executed (explicitly, or implicitly by the first integration), the program checks first whether the library is already loaded, and whether source code already exists for the requested processes. If yes, this code is used and no calls to \oMega\ (or another matrix element method) or to the compiler are issued. Otherwise, it will detect any modification to the process configuration and regenerate the matrix element or recompile accordingly. Thus, a \sindarin\ script can be executed repeatedly without rebuilding everything from scratch, and you can safely add more processes to a script in a subsequent run without having to worry about the processes that have already been treated. This default behavior can be changed. By setting \begin{quote} \begin{footnotesize} \begin{verbatim} ?rebuild_library = true \end{verbatim} \end{footnotesize} \end{quote} code will be re-generated and re-compiled even if \whizard\ would think that this is unncessary. The same effect is achieved by calling \whizard\ with a command-line switch, \begin{quote} \begin{footnotesize} \begin{verbatim} /home/user$ whizard --rebuild_library \end{verbatim} \end{footnotesize} \end{quote} There are further \ttt{rebuild} switches which are described below. If everything is to be rebuilt, you can set a master switch \ttt{?rebuild} or the command line option \verb|--rebuild|. The latter can be abbreviated as a short command-line option: \begin{quote} \begin{footnotesize} \begin{verbatim} /home/user$ whizard -r \end{verbatim} \end{footnotesize} \end{quote} Setting this switch is always a good idea when starting a new project, just in case some old files clutter the working directory. When re-running the same script, possibly modified, the \verb|-r| switch should be omitted, so the existing files can be reused. \subsection{Process libraries} Processes are collected in \emph{libraries}. A script may use more than one library, although for most applications a single library will probably be sufficient. The default library is \ttt{default\_lib}. If you do not specify anything else, the processes you compile will be collected by a driver file \ttt{default\_lib.f90} which is compiled together with the process code and combined as a libtool archive \ttt{default\_lib.la}, which is dynamically linked to the running \whizard\ process. Once in a while, you work on several projects at once, and you didn't care about opening a new working directory for each. If the \verb|-r| option is given, a new run will erase the existing library, which may contain processes needed for the other project. You could omit \verb|-r|, so all processes will be collected in the same library (this does not hurt), but you may wish to cleanly separate the projects. In that case, you should open a separate library for each project. Again, there are two possibilities. You may start the script with the specification \begin{quote} \begin{footnotesize} \begin{verbatim} library = "my_lhc_proc" \end{verbatim} \end{footnotesize} \end{quote} to open a library \verb|my_lhc_proc| in place of the default library. Repeating the command with different arguments, you may introduce several libraries in the script. The active library is always the one specified last. It is possible to issue this command locally, so a particular process goes into its own library. Alternatively, you may call \whizard\ with the option \begin{quote} \begin{footnotesize} \begin{verbatim} /home/user$ whizard --library=my_lhc_proc \end{verbatim} \end{footnotesize} \end{quote} If several libraries are open simultaneously, the \ttt{compile} command will compile all libraries that the script has referenced so far. If this is not intended, you may give the command an argument, \begin{quote} \begin{footnotesize} \begin{verbatim} compile ("my_lhc_proc", "my_other_proc") \end{verbatim} \end{footnotesize} \end{quote} to compile only a specific subset. The command \begin{quote} \begin{footnotesize} \begin{verbatim} show (library) \end{verbatim} \end{footnotesize} \end{quote} will display the contents of the actually loaded library together with a status code which indicates the status of the library and the processes within. %%%%%%%%%%%%%%% \subsection{Stand-alone \whizard\ with precompiled processes} \label{sec:static} Once you have set up a process library, it is straightforward to make a special stand-alone \whizard\ executable which will have this library preloaded on startup. This is a matter of convenience, and it is also useful if you need a statically linked executable for reasons of profiling, batch processing, etc. For this task, there is a variant of the \ttt{compile} command: \begin{quote} \begin{footnotesize} \begin{verbatim} compile as "my_whizard" () \end{verbatim} \end{footnotesize} \end{quote} which produces an executable \verb|my_whizard|. You can omit the library argument if you simply want to include everything. (Note that this command will \emph{not} load a library into the current process, it is intended for creating a separate program that will be started independently.) As an example, the script \begin{quote} \begin{footnotesize} \begin{verbatim} process proc1 = e1, E1 => e1, E1 process proc2 = e1, E1 => e2, E2 process proc3 = e1, E1 => e3, E3 compile as "whizard-leptons" () \end{verbatim} \end{footnotesize} \end{quote} will make a new executable program \verb|whizard-leptons|. This program behaves completely identical to vanilla \whizard, except for the fact that the processes \ttt{proc1}, \ttt{proc2}, and \ttt{proc3} are available without configuring them or loading any library. % This feature is particularly useful when compiling with the \ttt{-static} % flag. As long as the architecture is compatible, the resulting binary may be % run on a different computer where no \whizard\ libraries are present. (The % program will still need to find its model files, however.) \section{Beams} \label{sec:beams} Before processes can be integrated and simulated, the program has to know about the collider properties. They can be specified by the \ttt{beams} statement. In the command script, it is irrelevant whether a \ttt{beams} statement comes before or after process specification. The \ttt{integrate} or \ttt{simulate} commands will use the \ttt{beams} statement that was issued last. \subsection{Beam setup} \label{sec:beam-setup} If the beams have no special properties, and the colliding particles are the incoming particles in the process themselves, there is no need for a \ttt{beams} statement at all. You only \emph{must} specify the center-of-momentum energy of the collider by setting the value of $\sqrt{s}$, for instance \begin{quote} \begin{footnotesize} \begin{verbatim} sqrts = 14 TeV \end{verbatim} \end{footnotesize} \end{quote} The \ttt{beams} statement comes into play if \begin{itemize} \item the beams have nontrivial structure, e.g., parton structure in hadron collision or photon radiation in lepton collision, or \item the beams have non-standard properties: polarization, asymmetry, crossing angle. \end{itemize} Note that some of the abovementioned beam properties had not yet been reimplemented in the \whizard\ttt{2} release series. From version v2.2.0 on all options of the legacy series \whizard\ttt{1} are available again. From version v2.1 to version v2.2 of \whizard\ there has also been a change in possible options to the \ttt{beams} statement: in the early versions of \whizard\ttt{2} (v2.0/v2.1), local options could be specified within the beam settings, e.g. \ttt{beams = p, p { sqrts = 14 TeV } => pdf\_builtin}. These possibility has been abandoned from version v2.2 on, and the \ttt{beams} command does not allow for {\em any} optional arguments any more. Hence, beam parameters can -- with the exception of the specification of structure functions -- be specified only globally: \begin{quote} \begin{footnotesize} \begin{verbatim} sqrts = 14 TeV beams = p, p => lhapdf \end{verbatim} \end{footnotesize} \end{quote} It does not make any difference whether the value of \ttt{sqrts} is set before or after the \ttt{beams} statement, the last value found before an \ttt{integrate} or \ttt{simulate} is the relevant one. This in particularly allows to specify the beam structure, and then after that perform a loop or scan over beam energies, beam parameters, or structure function settings. The \ttt{beams} statement also applies to particle decay processes, where there is only a single beam. Here, it is usually redundant because no structure functions are possible, and the energy is fixed to the decaying particle's mass. However, it is needed for computing polarized decay, e.g. \begin{quote} \begin{footnotesize} \begin{verbatim} beams = Z beams_pol_density = @(0) \end{verbatim} \end{footnotesize} \end{quote} where for a boson at rest, the polarization axis is defined to be the $z$ axis. Beam polarization is described in detail below in Sec.~\ref{sec:polarization}. Note also that future versions of \whizard\ might give support for single-beam events, where structure functions for single particles indeed do make sense. In the following sections we list the available options for structure functions or spectra inside \whizard\ and explain their usage. More about the physics of the implemented structure functions can be found in Chap.~\ref{chap:hardint}. %%%%%%%%%%%%%%% \subsection{Asymmetric beams and Crossing angles} \label{sec:asymmetricbeams} \whizard\ not only allows symmetric beam collisions, but basically arbitrary collider setups. In the case there are two different beam energies, the command \begin{quote} \begin{footnotesize} \ttt{beams\_momentum = {\em }, {\em }} \end{footnotesize} \end{quote} allows to specify the momentum (or as well energies for massless particles) for the beams. Note that for scattering processes both values for the beams must be present. So the following to setups for 14 TeV LHC proton-proton collisions are equivalent: \begin{quote} \begin{footnotesize} \ttt{beams = p, p => pdf\_builtin} \newline \ttt{sqrts = 14 TeV} \end{footnotesize} \end{quote} and \begin{quote} \begin{footnotesize} \ttt{beams = p, p => pdf\_builtin} \newline \ttt{beams\_momentum = 7 TeV, 7 TeV} \end{footnotesize} \end{quote} Asymmetric setups can be set by using different values for the two beam momenta, e.g. in a HERA setup: \begin{quote} \begin{footnotesize} \ttt{beams = e, p => none, pdf\_builtin} \ttt{beams\_momentum = 27.5 GeV, 920 GeV} \end{footnotesize} \end{quote} or for the BELLE experiment at the KEKB accelerator: \begin{quote} \begin{footnotesize} \ttt{beams = e1, E1} \ttt{beams\_momentum = 8 GeV, 3.5 GeV} \end{footnotesize} \end{quote} \whizard\ lets you know about the beam structure and calculates for you that the center of mass energy corresponds to 10.58 GeV: \begin{quote} \begin{footnotesize} \begin{Verbatim} | Beam structure: e-, e+ | momentum = 8.000000000000E+00, 3.500000000000E+00 | Beam data (collision): | e- (mass = 5.1099700E-04 GeV) | e+ (mass = 5.1099700E-04 GeV) | sqrts = 1.058300530253E+01 GeV | Beam structure: lab and c.m. frame differ \end{Verbatim} \end{footnotesize} \end{quote} It is also possible to specify beams for decaying particles, where \ttt{beams\_momentum} then only has a single argument, e.g.: \begin{quote} \begin{footnotesize} \ttt{process zee = Z => "e-", "e+"} \\ \ttt{beams = Z} \\ \ttt{beams\_momentum = 500 GeV} \\ \ttt{simulate (zee) \{ n\_events = 100 \} } \end{footnotesize} \end{quote} This would corresponds to a beam of $Z$ bosons with a momentum of 500 GeV. Note, however, that \whizard\ will always do the integration of the particle width in the particle's rest frame, while the moving beam is then only taken into account for the frame of reference for the simulation. Further options then simply having different beam energies describe a non-vanishing between the two incoming beams. Such concepts are quite common e.g. for linear colliders to improve the beam properties in the collimation region at the beam interaction points. Such crossing angles can be specified in the beam setup, too, using the \ttt{beams\_theta} command: \begin{quote} \begin{footnotesize} \ttt{beams = e1, E1} \\ \ttt{beams\_momentum = 500 GeV, 500 GeV} \\ \ttt{beams\_theta = 0, 10 degree} \end{footnotesize} \end{quote} It is important that when a crossing angle is being specified, and the collision system consequently never is the center-of-momentum system, the beam momenta have to explicitly set. Besides a planar crossing angle, one is even able to rotate an azimuthal distance: \begin{quote} \begin{footnotesize} \ttt{beams = e1, E1} \\ \ttt{beams\_momentum = 500 GeV, 500 GeV} \\ \ttt{beams\_theta = 0, 10 degree} \\ \ttt{beams\_phi = 0, 45 degree} \end{footnotesize} \end{quote} %%%%%%%%%%%%%%% \subsection{LHAPDF} \label{sec:lhapdf} For incoming hadron beams, the \ttt{beams} statement specifies which structure functions are used. The simplest example is the study of parton-parton scattering processes at a hadron-hadron collider such as LHC or Tevatron. The \lhapdf\ structure function set is selected by a syntax similar to the process setup, namely the example already shown above: \begin{quote} \begin{footnotesize} \begin{verbatim} beams = p, p => lhapdf \end{verbatim} \end{footnotesize} \end{quote} Note that there are slight differences in using the \lhapdf\ release series 6 and the older \fortran\ \lhapdf\ release series 5, at least concerning the naming conventions for the PDF sets~\footnote{Until \whizard\ version 2.2.1 including, only the \lhapdf\ series 5 was supported, while from version 2.2.2 on also the \lhapdf\ release series 6 has been supported.}. The above \ttt{beams} statement selects a default \lhapdf\ structure-function set for both proton beams (which is the \ttt{CT10} central set for \lhapdf\ 6, and \ttt{cteq6ll.LHpdf} central set for \lhapdf 5). The structure function will apply for all quarks, antiquarks, and the gluon as far as supported by the particular \lhapdf\ set. Choosing a different set is done by adding the filename as a local option to the \ttt{lhapdf} keyword: \begin{quote} \begin{footnotesize} \begin{verbatim} beams = p, p => lhapdf $lhapdf_file = "MSTW2008lo68cl" \end{verbatim} \end{footnotesize} \end{quote} for the actual \lhapdf\ 6 series, and \begin{quote} \begin{footnotesize} \begin{verbatim} beams = p, p => lhapdf $lhapdf_file = "MSTW2008lo68cl.LHgrid" \end{verbatim} \end{footnotesize} \end{quote} for \lhapdf 5.Similarly, a member within the set is selected by the numeric variable \verb|lhapdf_member| (for both release series of \lhapdf). In some cases, different structure functions have to be chosen for the two beams. For instance, we may look at $ep$ collisions: \begin{quote} \begin{footnotesize} \begin{verbatim} beams = "e-", p => none, lhapdf \end{verbatim} \end{footnotesize} \end{quote} Here, there is a list of two independent structure functions (each with its own option set, if applicable) which applies to the two beams. Another mixed case is $p\gamma$ collisions, where the photon is to be resolved as a hadron. The simple assignment \begin{quote} \begin{footnotesize} \begin{verbatim} beams = p, gamma => lhapdf, lhapdf_photon \end{verbatim} \end{footnotesize} \end{quote} will be understood as follows: \whizard\ selects the appropriate default structure functions (here we are using \lhapdf\ 5 as an example as the support of photon and pion PDFs in \lhapdf\ 6 has been dropped), \ttt{cteq6ll.LHpdf} for the proton and \ttt{GSG960.LHgrid} for the photon. The photon case has an additional integer-valued parameter \verb|lhapdf_photon_scheme|. (There are also pion structure functions available.) For modifying the default, you have to specify separate structure functions \begin{quote} \begin{footnotesize} \begin{verbatim} beams = p, gamma => lhapdf, lhapdf_photon $lhapdf_file = ... $lhapdf_photon_file = ... \end{verbatim} \end{footnotesize} \end{quote} Finally, the scattering of elementary photons on partons is described by \begin{quote} \begin{footnotesize} \begin{verbatim} beams = p, gamma => lhapdf, none \end{verbatim} \end{footnotesize} \end{quote} Note that for \lhapdf\ version 5.7.1 or higher and for PDF sets which support it, photons can be used as partons. There is one more option for the \lhapdf\ PDFs, namely to specify the path where the \lhapdf\ PDF sets reside: this is done with the string variable \ttt{\$lhapdf\_dir = "{\em }"}. Usually, it is not necessary to set this because \whizard\ detects this path via the \ttt{lhapdf-config} script during configuration, but in the case paths have been moved, or special files/special locations are to be used, the user can specify this location explicitly. %%%%%%%%%%%%%%% \subsection{Built-in PDFs} \label{sec:built-in-pdf} In addition to the possibility of linking against \lhapdf, \whizard\ comes with a couple of built-in PDFs which are selected via the \verb?pdf_builtin? keyword % \begin{quote} \begin{footnotesize} \begin{verbatim} beams = p, p => pdf_builtin \end{verbatim} \end{footnotesize} \end{quote} % The default PDF set is CTEQ6L, but other choices are also available by setting the string variable \verb?$pdf_builtin_set? to an appropiate value. E.g, modifying the above setup to % \begin{quote} \begin{footnotesize} \begin{verbatim} beams = p, p => pdf_builtin $pdf_builtin_set = "mrst2004qedp" \end{verbatim} \end{footnotesize} \end{quote} % would select the proton PDF from the MRST2004QED set. A list of all currently available PDFs can be found in Table~\ref{tab:pdfs}. % \begin{table} \centerline{\begin{tabular}{|l||l|p{0.2\textwidth}|l|} \hline Tag & Name & Notes & References \\\hline\hline % \ttt{cteq6l} & CTEQ6L & \mbox{}\hfill---\hfill\mbox{} & \cite{Pumplin:2002vw} \\\hline \ttt{cteq6l1} & CTEQ6L1 & \mbox{}\hfill---\hfill\mbox{} & \cite{Pumplin:2002vw} \\\hline \ttt{cteq6d} & CTEQ6D & \mbox{}\hfill---\hfill\mbox{} & \cite{Pumplin:2002vw} \\\hline \ttt{cteq6m} & CTEQ6M & \mbox{}\hfill---\hfill\mbox{} & \cite{Pumplin:2002vw} \\\hline \hline \ttt{mrst2004qedp} & MRST2004QED (proton) & includes photon & \cite{Martin:2004dh} \\\hline \hline \ttt{mrst2004qedn} & MRST2004QED (neutron) & includes photon & \cite{Martin:2004dh} \\\hline \hline \ttt{mstw2008lo} & MSTW2008LO & \mbox{}\hfill---\hfill\mbox{} & \cite{Martin:2009iq} \\\hline \ttt{mstw2008nlo} & MSTW2008NLO & \mbox{}\hfill---\hfill\mbox{} & \cite{Martin:2009iq} \\\hline \ttt{mstw2008nnlo} & MSTW2008NNLO & \mbox{}\hfill---\hfill\mbox{} & \cite{Martin:2009iq} \\\hline \hline \ttt{ct10} & CT10 & \mbox{}\hfill---\hfill\mbox{} & \cite{Lai:2010vv} \\\hline \hline \ttt{CJ12\_max} & CJ12\_max & \mbox{}\hfill---\hfill\mbox{} & \cite{Owens:2012bv} \\\hline \ttt{CJ12\_mid} & CJ12\_mid & \mbox{}\hfill---\hfill\mbox{} & \cite{Owens:2012bv} \\\hline \ttt{CJ12\_min} & CJ12\_min & \mbox{}\hfill---\hfill\mbox{} & \cite{Owens:2012bv} \\\hline \hline \ttt{CJ15LO} & CJ15LO & \mbox{}\hfill---\hfill\mbox{} & \cite{Accardi:2016qay} \\\hline \ttt{CJ15NLO} & CJ15NLO & \mbox{}\hfill---\hfill\mbox{} & \cite{Accardi:2016qay} \\\hline \hline \ttt{mmht2014lo} & MMHT2014LO & \mbox{}\hfill---\hfill\mbox{} & \cite{Harland-Lang:2014zoa} \\\hline \ttt{mmht2014nlo} & MMHT2014NLO & \mbox{}\hfill---\hfill\mbox{} & \cite{Harland-Lang:2014zoa} \\\hline \ttt{mmht2014nnlo} & MMHT2014NNLO & \mbox{}\hfill---\hfill\mbox{} & \cite{Harland-Lang:2014zoa} \\\hline \hline \ttt{CT14LL} & CT14LLO & \mbox{}\hfill---\hfill\mbox{} & \cite{Dulat:2015mca} \\\hline \ttt{CT14L} & CT14LO & \mbox{}\hfill---\hfill\mbox{} & \cite{Dulat:2015mca} \\\hline \ttt{CT14N} & CT1414NLO & \mbox{}\hfill---\hfill\mbox{} & \cite{Dulat:2015mca} \\\hline \ttt{CT14NN} & CT14NNLO & \mbox{}\hfill---\hfill\mbox{} & \cite{Dulat:2015mca} \\\hline \hline % \end{tabular}} \caption{All PDF sets available as builtin sets. The two MRST2004QED sets also contain a photon.} \label{tab:pdfs} \end{table} The two MRST2004QED sets also contain the photon as a parton, which can be used in the same way as for \lhapdf\ from v5.7.1 on. Note, however, that there is no builtin PDF that contains a photon structure function. There is a \ttt{beams} structure function specifier \ttt{pdf\_builtin\_photon}, but at the moment this throws an error. It just has been implemented for the case that in future versions of \whizard\ a photon structure function might be included. Note that in general only the data sets for the central values of the different PDFs ship with \whizard. Using the error sets is possible, i.e. it is supported in the syntax of the code, but you have to download the corresponding data sets from the web pages of the PDF fitting collaborations. %%%%%%%%%%%%%%% \subsection{HOPPET $b$ parton matching} When the \hoppet\ tool~\cite{Salam:2008qg} for hadron-collider PDF structure functions and their manipulations are correctly linked to \whizard, it can be used for advanced calculations and simulations of hadron collider physics. Its main usage inside \whizard\ is for matching schemes between 4-flavor and 5-flavor schemes in $b$-parton initiated processes at hadron colliders. Note that in versions 2.2.0 and 2.2.1 it only worked together with \lhapdf\ version 5, while with the \lhapdf\ version 6 interface from version 2.2.2 on it can be used also with the modern version of PDFs from \lhapdf. Furthermore, from version 2.2.2, the \hoppet\ $b$ parton matching also works for the builtin PDFs. It depends on the corresponding process and the energy scales involved whether it is a better description to use the $g\to b\bar b$ splitting from the DGLAP evolution inside the PDF and just take the $b$ parton content of a PDF, e.g. in BSM Higgs production for large $\tan\beta$: $pp \to H$ with a partonic subprocess $b\bar b \to H$, or directly take the gluon PDFs and use $pp \to b\bar b H$ with a partonic subprocess $gg \to b \bar b H$. Elaborate schemes for a proper matching between the two prescriptions have been developed and have been incorporated into the \hoppet\ interface. Another prime example for using these matching schemes is single top production at hadron colliders. Let us consider the following setup: \begin{quote} \begin{footnotesize} \begin{Verbatim} process proc1 = b, u => t, d process proc2 = u, b => t, d process proc3 = g, u => t, d, B { $restrictions = "2+4 ~ W+" } process proc4 = u, g => t, d, B { $restrictions = "1+4 ~ W+" } beams = p,p => pdf_builtin sqrts = 14 TeV ?hoppet_b_matching = true $sample = "single_top_matched" luminosity = 1 / 1 fbarn simulate (proc1, proc2, proc3, proc4) \end{Verbatim} \end{footnotesize}%$ \end{quote} The first two processes are single top production from $b$ PDFs, the last two processes contain an explicit $g\to b\bar b$ splitting (the restriction, cf. Sec.~\ref{sec:process options} has been placed in order to single out the single top production signal process). PDFs are then chosen from the default builtin PDF (which is \ttt{CTEQ6L}), and the \hoppet\ matching routines are switched on by the flag \ttt{?hoppet\_b\_matching}. %%%%%%%%%%%%%%% \subsection{Lepton Collider ISR structure functions} \label{sec:lepton_isr} Initial state QED radiation off leptons is an important feature at all kinds of lepton colliders: the radiative return to the $Z$ resonance by ISR radiation was in fact the largest higher-order effect for the SLC and LEP I colliders. The soft-collinear and soft photon radiation can indeed be resummed/exponentiated to all orders in perturbation theory~\cite{Gribov:1972rt}, while higher orders in hard-collinear photons have to be explicitly calculated order by order~\cite{Kuraev:1985hb,Skrzypek:1990qs}. \whizard\ has an intrinsic implementation of the lepton ISR structure function that includes all orders of soft and soft-collinear photons as well as up to the third order in hard-collinear photons. It can be switched on by the following statement: \begin{quote} \begin{footnotesize} \begin{Verbatim} beams = e1, E1 => isr \end{Verbatim} \end{footnotesize} \end{quote} As the ISR structure function is a single-beam structure function, this expression is synonymous for \begin{quote} \begin{footnotesize} \begin{Verbatim} beams = e1, E1 => isr, isr \end{Verbatim} \end{footnotesize} \end{quote} The ISR structure function can again be applied to only one of the two beams, e.g. in a HERA-like setup: \begin{quote} \begin{footnotesize} \begin{Verbatim} beams = e1, p => isr, pdf_builtin \end{Verbatim} \end{footnotesize} \end{quote} Their are several options for the lepton-collider ISR structure function that are summarized in the following: \vspace{2mm} \centerline{\begin{tabular}{|l|l|l|}\hline Parameter & Default & Meaning \\\hline\hline \ttt{isr\_alpha} & \ttt{0}/intrinsic & value of $\alpha_{QED}$ for ISR \\\hline \ttt{isr\_order} & \ttt{3} & max. order of hard-collinear photon emission \\\hline \ttt{isr\_mass} & \ttt{0}/intrinsic & mass of the radiating lepton \\\hline \ttt{isr\_q\_max} & \ttt{0}/$\sqrt{s}$ & upper cutoff for ISR \\\hline \hline \ttt{?isr\_recoil} & \ttt{false} & flag to switch on recoil/$p_T$ (\emph{deprecated})\\\hline \ttt{?isr\_keep\_energy} & \ttt{false} & recoil flag: conserve energy in splitting (\emph{deprecated}) \\\hline \end{tabular}}\mbox{} The maximal order of the hard-collinear photon emission taken into account by \whizard\ is set by the integer variable \ttt{isr\_order}; the default is the maximally available order of three. With the variable \ttt{isr\_alpha}, the value of the QED coupling constant $\alpha_{QED}$ used in the ISR structure function can be set. The default is taken from the active physics model. The mass of the radiating lepton (in most cases the electron) is set by \ttt{isr\_mass}; again the default is taken from the active physics model. Furthermore, the upper integration border for the ISR structure function which acts roughly as an upper hardness cutoff for the emitted photons, can be set through \ttt{isr\_q\_max}; if not set, the collider energy (possibly after beamstrahlung, cf. Sec.~\ref{sec:beamstrahlung}) $\sqrt{s}$ (or $\sqrt{\widehat{s}}$) is taken. Note that \whizard\ accounts for the exclusive effects of ISR radiation at the moment by a single (hard, resolved) photon in the event; a more realistic treatment of exclusive ISR photons in simulation is foreseen for a future version. While the ISR structure function is evaluated in the collinear limit, it is possible to generate transverse momentum for both the radiated photons and the recoiling partonic system. We recommend to stick to the collinear approximation for the integration step. Integration cuts should be set up such that they do not significantly depend on photon transverse momentum. In a subsequent simulation step, it is possible to transform the events with collinear ISR radiation into more realistic events with non-collinear radiation. To this end, \whizard\ provides a separate ISR photon handler which can be activated in the simulation step. The algorithm operates on the partonic event: it takes the radiated photons and the partons entering the hard process, and applies a $p_T$ distribution to those particles and their interaction products, i.e., all outgoing particles. Cuts that depend on photon $p_T$ may be applied to the modified events. For details on the ISR photon handler, cf.\ Sec.~\ref{sec:isr-photon-handler}. {\footnotesize The flag \ttt{?isr\_recoil} switches on $p_T$ recoil of the emitting lepton against photon radiation during integration; per default it is off. The flag \ttt{?isr\_keep\_energy} controls the mode of on-shell projection for the splitting process with $p_T$. Note that this feature is kept for backwards compatibility, but should not be used for new simulations. The reason is as follows: For a fraction of events, $p_T$ will become significant, and (i) energy/momentum non-conservation, applied to both beams separately, can lead to unexpected and unphysical effects, and (ii) the modified momenta enter the hard process, so the collinear approximation used in the ISR structure function computation does not hold. } %%%%%%%%%%%%%%% \subsection{Lepton Collider Beamstrahlung} \label{sec:beamstrahlung} At linear lepton colliders, the macroscopic electromagnetic interaction of the bunches leads to a distortion of the spectrum of the bunches that is important for an exact simulation of the beam spectrum. There are several methods to account for these effects. The most important tool to simulate classical beam-beam interactions in lepton-collider physics is \ttt{GuineaPig++}~\cite{Schulte:1998au,Schulte:1999tx,Schulte:2007zz}. A direct interface between this tool \ttt{GuineaPig++} and \whizard\ had existed as an inofficial add-on to the legacy branch \whizard\ttt{1}, but is no longer applicable in \whizard\ttt{2}. A \whizard-internal interface is foreseen for the very near future, most probably within this v2.2 release. Other options are to use parameterizations of the beam spectrum that have been included in the package \circeone~\cite{CIRCE} which has been interfaced to \whizard\ since version v1.20 and been included in the \whizard\ttt{2} release series. Another option is to generate a beam spectrum externally and then read it in as an ASCII data file, cf. Sec.~\ref{sec:beamevents}. More about this can be found in a dedicated section on lepton collider spectra, Sec.~\ref{sec:beamspectra}. In this section, we discuss the usage of beamstrahlung spectra by means of the \circeone\ package. The beamstrahlung spectra are true spectra, so they have to be applied to pairs of beams, and an application to only one beam is meaningless. They are switched on by this \ttt{beams} statement including structure functions: \begin{quote} \begin{footnotesize} \begin{Verbatim} beams = e1, E1 => circe1 \end{Verbatim} \end{footnotesize} \end{quote} It is important to note that the parameterization of the beamstrahlung spectra within \circeone\ contain also processes where $e\to\gamma$ conversions have been taking place, i.e. also hard processes with one (or two) initial photons can be simulated with beamstrahlung switched on. In that case, the explicit photon flags, \ttt{?circe1\_photon1} and \ttt{?circe1\_photon2}, for the two beams have to be properly set, e.g. (ordering in the final state does not play a role): \begin{quote} \begin{footnotesize} \begin{Verbatim} process proc1 = A, e1 => A, e1 sqrts = 500 GeV beams = e1, E1 => circe1 ?circe1_photon1 = true integrate (proc1) process proc2 = e1, A => A, e1 sqrts = 1000 GeV beams = e1, A => circe1 ?circe1_photon2 = true \end{Verbatim} \end{footnotesize} \end{quote} or \begin{quote} \begin{footnotesize} \begin{Verbatim} process proc1 = A, A => Wp, Wm sqrts = 200 GeV beams = e1, E1 => circe1 ?circe1_photon1 = true ?circe1_photon2 = true ?circe1_generate = false \end{Verbatim} \end{footnotesize} \end{quote} In all cases (one or both beams with photon conversion) the beam spectrum applies to both beams simultaneously. In the last example ($\gamma\gamma\to W^+W^-$) the default \circeone\ generator mode was turned off by unsetting \verb|?circe1_generate|. In the other examples this flag is set, by default. For standard use cases, \circeone\ implements a beam-event generator inside the \whizard\ generator, which provides beam-event samples with correctly distributed probability. For electrons, the beamstrahlung spectrum sharply peaks near maximum energy. This distribution is most efficiently handled by the generator mode. By contrast, in the $\gamma\gamma$ mode, the beam-event c.m.\ energy is concentrated at low values. For final states with low invariant mass, which are typically produced by beamstrahlung photons, the generator mode is appropriate. However, the $W^+W^-$ system requires substantial energy, and such events will be very rare in the beam-event sample. Switching off the \circeone\ generator mode solves this problem. This is an overview over all options and flags for the \circeone\ setup for lepton collider beamstrahlung: \vspace{2mm} \centerline{\begin{tabular}{|l|l|l|}\hline Parameter & Default & Meaning \\\hline\hline \ttt{?circe1\_photon1} & \ttt{false} & $e\to\gamma$ conversion for beam 1 \\\hline \ttt{?circe1\_photon2} & \ttt{false} & $e\to\gamma$ conversion for beam 2 \\\hline \ttt{circe1\_sqrts} & $\sqrt{s}$ & collider energy for the beam spectrum \\\hline \ttt{?circe1\_generate} & \ttt{true} & flag for the \circeone\ generator mode \\\hline \ttt{?circe1\_map} & \ttt{true} & flag to apply special phase-space mapping \\\hline \ttt{circe1\_mapping\_slope} & \ttt{2.} & value of PS mapping exponent \\\hline \ttt{circe1\_eps} & \ttt{1E-5} & parameter for mapping of spectrum peak position \\\hline \ttt{circe1\_ver} & \ttt{0} & internal version of \circeone\ package \\\hline \ttt{circe1\_rev} & \ttt{0}/most recent & internal revision of \circeone\ \\\hline \ttt{\$circe1\_acc} & \ttt{SBAND} & accelerator type \\\hline \ttt{circe1\_chat} & \ttt{0} & chattiness/verbosity of \circeone \\\hline \end{tabular}}\mbox{} The collider energy relevant for the beamstrahlung spectrum is set by \ttt{circe1\_sqrts}. As a default, this is always the value of \ttt{sqrts} set in the \sindarin\ script. However, sometimes these values do not match, e.g. the user wants to simulate $t\bar t h$ at \ttt{sqrts = 550 GeV}, but the only available beam spectrum is for 500 GeV. In that case, \ttt{circe1\_sqrts = 500 GeV} has to be set to use the closest possible available beam spectrum. As mentioned in the discussion of the examples above, in \circeone\ there are two options to use the beam spectra for beamstrahlung: intrinsic semi-analytic approximation formulae for the spectra, or a Monte-Carlo sampling of the sampling. The second possibility always give a better description of the spectra, and is the default for \whizard. It can, however, be switched off by setting the flag \ttt{?circe1\_generate} to \ttt{false}. As the beamstrahlung spectra are sharply peaked at the collider energy, but still having long tails, a mapping of the spectra for an efficient phase-space sampling is almost mandatory. This is the default in \whizard, which can be changed by the flag \ttt{?circe1\_map}. Also, the default exponent for the mapping can be changed from its default value \ttt{2.} with the variable \ttt{circe1\_mapping\_slope}. It is important to efficiently sample the peak position of the spectrum; the effective ratio of the peak to the whole sampling interval can be set by the parameter \ttt{circe1\_eps}. The integer parameter \ttt{circe1\_chat} sets the chattiness or verbosity of the \circeone\ package, i.e. how many messages and warnings from the beamstrahlung generation/sampling will be issued. The actual internal version and revision of the \circeone\ package are set by the two integer parameters \ttt{circe1\_ver} and \ttt{circe1\_rev}. The default is in any case always the newest version and revision, while older versions are still kept for backwards compatibility and regression testing. Finally, the geometry and design of the accelerator type is set with the string variable \ttt{\$circe1\_acc}: it contains the possible options for the old \ttt{"SBAND"} and \ttt{"XBAND"} setups, as well as the \ttt{"TESLA"} and JLC/NLC SLAC design \ttt{"JLCNLC"}. The setups for the most important energies of the ILC as they are summarized in the ILC TDR~\cite{Behnke:2013xla,Baer:2013cma,Adolphsen:2013jya,Adolphsen:2013kya} are available as \ttt{ILC}. Beam spectra for the CLIC~\cite{Aicheler:2012bya,Lebrun:2012hj,Linssen:2012hp} linear collider are much more demanding to correctly simulate (due to the drive beam concept; only the low-energy modes where the drive beam is off can be simulated with the same setup as the abovementioned machines). Their setup will be supported soon in one of the upcoming \whizard\ versions within the \circetwo\ package. An example of how to generate beamstrahlung spectra with the help of the package \circetwo\ (that is also a part of \whizard) is this: \begin{quote} \begin{footnotesize} \begin{Verbatim} process eemm = e1, E1 => e2, E2 sqrts = 500 GeV beams = e1, E1 => circe2 $circe2_file = "ilc500.circe" $circe2_design = "ILC" ?circe_polarized = false \end{Verbatim} \end{footnotesize}%$ \end{quote} Here, the ILC design is used for a beamstrahlung spectrum at 500 GeV nominal energy, with polarization averaged (hence, the setting of polarization to \ttt{false}). A list of all available options can be found in Sec.~\ref{sec:photoncoll}. More technical details about the simulation of beamstrahlung spectra see the documented source code of the \circeone\ package, as well as Chap.~\ref{chap:hardint}. In the next section, we discuss how to read in beam spectra from external files. %%%%%%%%%%%%%%% \subsection{Beam events} \label{sec:beamevents} As mentioned in the previous section, beamstrahlung is one of the crucial ingredients for a realistic simulation of linear lepton colliders. One option is to take a pre-generated beam spectrum for such a machine, and make it available for simulation within \whizard\ as an external ASCII data file. Such files basically contain only pairs of energy fractions of the nominal collider energy $\sqrt{s}$ ($x$ values). In \whizard\ they can be used in simulation with the following \ttt{beams} statement: \begin{quote} \begin{footnotesize} \begin{Verbatim} beams = e1, E1 => beam_events $beam_events_file = "" \end{Verbatim} \end{footnotesize}%$ \end{quote} Note that beam spectra must always be pair spectra, i.e. they are automatically applied to both beam simultaneously. Beam spectra via external files are expected to reside in the current working directory. Alternatively, \whizard\ searches for them in the install directory of \whizard\ in \ttt{share/beam-sim}. There you can find an example file, \ttt{uniform\_spread\_2.5\%.dat} for such a beam spectrum. The only possible parameter that can be set is the flag \ttt{?beam\_events\_warn\_eof} whose default is \ttt{true}. This triggers the issuing of a warning when the end of file of an external beam spectrum file is reached. In such a case, \whizard\ starts to reuse the same file again from the beginning. If the available data points in the beam events file are not big enough, this could result in an insufficient sampling of the beam spectrum. %%%%%%%%%%%%%%% \subsection{Gaussian beam-energy spread} \label{sec:gaussian} Real beams have a small energy spread. If beamstrahlung is small, the spread may be approximately described as Gaussian. As a replacement for the full simulation that underlies \ttt{CIRCE2} spectra, it is possible to impose a Gaussian distributed beam energy, separately for each beam. \begin{quote} \begin{footnotesize} \begin{Verbatim} beams = e1, E1 => gaussian gaussian_spread1 = 0.1\% gaussian_spread2 = 0.2\% \end{Verbatim} \end{footnotesize}%$ \end{quote} (Note that the \% sign means multiplication by 0.01, as it should.) The spread values are defined as the $\sigma$ value of the Gaussian distribution, i.e., $2/3$ of the events are within $\pm 1\sigma$ for each beam, respectively. %%%%%%%%%%%%%%%% \subsection{Equivalent photon approximation} \label{sec:epa} The equivalent photon approximation (EPA) uses an on-shell approximation for the $e \to e\gamma$ collinear splitting to allow the simulation of photon-induced backgrounds in lepton collider physics. The original concept is that of the Weizs\"acker-Williams approximation~\cite{vonWeizsacker:1934sx,Williams:1934ad,Budnev:1974de}. This is a single-beam structure function that can be applied to both beams, or also to one beam only. Usually, there are some simplifications being made in the derivation. The formula which is implemented here and seems to be the best for the QCD background for low-$p_T$ hadrons, corresponds to Eq.~(6.17) of Ref.~\cite{Budnev:1974de}. As this reference already found, this leads to an "overshooting" of accuracy, and especially in the high-$x$ (high-energy) region to wrong results. This formula corresponds to \begin{equation} \label{eq:budnev_617} f(x) = \frac{\alpha}{\pi} \frac{1}{x} \biggl[ \left( \bar{x} + \frac{x^2}{2} \right) \log \frac{Q^2_{\text{max}}}{Q^2_{\text{min}}} - \left( 1 - \frac{x}{2} \right)^2 \log \frac{x^2 + \tfrac{Q^2_{\text{max}}}{E^2}}{x^2 + \tfrac{Q^2_{\text{min}}}{E^2}} - \frac{m_e^2 x^2}{Q^2_{\text{min}}} \left( 1 - \frac{Q^2_{\text{min}}}{Q^2_{\text{max}}} \right) \biggr] \qquad . \end{equation} Here, $x$ is the ratio of the photon energy (called frequency $\omega$ in~\cite{Budnev:1974de} over the original electron (or positron) beam energy $E$. The energy of the electron (or positron) after the splitting is given by $\bar{x} = 1-x$. The simplified version is the one that corresponds to many publications about the EPA during SLC and LEP times, and corresponds -to the $q^2$ integration of Eq.~(6.16e) in~\cite{Budnet:1974de}, where +to the $q^2$ integration of Eq.~(6.16e) in~\cite{Budnev:1974de}, where $q^2$ is the virtuality or momentum transfer of the photon in the EPA: \begin{equation} \label{eq:budnev_616e} f(x) = \frac{\alpha}{\pi} \frac{1}{x} \biggl[ \left( \bar{x} + \frac{x^2}{2} \right) \log \frac{Q^2_{\text{max}}}{Q^2_{\text{min}}} - \frac{m_e^2 x^2}{Q^2_{\text{min}}} \left( 1 - \frac{Q^2_{\text{min}}}{Q^2_{\text{max}}} \right) \biggr] \qquad . \end{equation} While Eq.~(\ref{eq:budnev_617}) is supposed to be the better choice for simulating hadronic background like low-$p_T$ hadrons and should be applied for the low-$x$ region of the EPA, Eq.~(\ref{eq:budnev_616e}) seems better suited for high-$x$ simulations like the photoproduction of BSM resonances etc. -Note that the first term in Eqs.~(\ref{eq:budnev617}) and -(\ref{eq:budnev616e}) is the standard Altarelli-Parisi QED splitting +Note that the first term in Eqs.~(\ref{eq:budnev_617}) and +(\ref{eq:budnev_616e}) is the standard Altarelli-Parisi QED splitting function of electron, $P_{e\to e\gamma}(x) \propto 1 + (1-x)^2$, while the last term in both equations is the default power correction. The two parameters $Q^2_{\text{max}}$ and $Q^2_{\text{min}}$ are the integration boundaries of the photon virtuality integration. Usually, they are given by the kinematic limits: \begin{equation} Q^2_{\text{min}} = \frac{m_e^2 x^2}{\bar{x}} \qquad\qquad Q^2_{\text{max}} = 4 E^2 \bar{x} = s \bar{x} \qquad . \end{equation} For low-$p_T$ hadron simulations, it is not a good idea to take the kinematic limit as an upper limit, but one should cut the simulation off at a hadronic scale like e.g. a multiple of the $\rho$ mass. The user can switch between the two different options using the setting \begin{quote} \begin{footnotesize} \begin{Verbatim} $epa_mode = "default" \end{Verbatim} \end{footnotesize} \end{quote} or \begin{quote} \begin{footnotesize} \begin{Verbatim} $epa_mode = "Budnev_617" \end{Verbatim} \end{footnotesize} \end{quote} for Eq.~(\ref{eq:budnev_617}), while Eq.~(\ref{eq:budnev_616e}) can be chosen with \begin{quote} \begin{footnotesize} \begin{Verbatim} $epa_mode = "Budnev_616e" \end{Verbatim} \end{footnotesize} \end{quote} Note that a thorough study for high-energy $e^+e^-$ colliders regarding the suitability of different EPA options is still lacking. +For testing purposes also three more variants or simplifications of +Eq.~(\ref{eq:budnev_616e}) are implemented: the first, steered by +\ttt{\$epa\_mode = log\_power} uses simply $Q^2_{\text{max}} = +s$. This is also the case for the two other method. But the switch +\ttt{\$epa\_mode = log\_simple} uses just \ttt{epa\_mass} (cf. below) +as $Q^2_{\text{min}}$. The final simplification is to drop the power +correction, which can be chosen with \ttt{\$epa\_mode = log}. This +corresponds to the simple formula: +\begin{equation} + f(x) = \frac{\alpha}{2\pi} \frac{1}{x} \, \log\frac{s}{m^2} + \qquad . +\end{equation} + Examples for the application of the EPA in \whizard\ are: \begin{quote} \begin{footnotesize} \begin{Verbatim} beams = e1, E1 => epa \end{Verbatim} \end{footnotesize} \end{quote} or for a single beam: \begin{quote} \begin{footnotesize} \begin{Verbatim} beams = e1, p => epa, pdf_builtin \end{Verbatim} \end{footnotesize} \end{quote} The last process allows the reaction of (quasi-) on-shell photons with protons. In the following, we collect the parameters and flags that can be adjusted when using the EPA inside \whizard: \vspace{2mm} \centerline{\begin{tabular}{|l|l|l|}\hline Parameter & Default & Meaning \\\hline\hline \ttt{epa\_alpha} & \ttt{0}/intrinsic & value of $\alpha_{QED}$ for EPA \\\hline \ttt{epa\_x\_min} & \ttt{0.} & soft photon cutoff in $x$ (mandatory) \\\hline \ttt{epa\_q\_min} & \ttt{0.} & minimal $\gamma$ momentum transfer \\\hline \ttt{epa\_mass} & \ttt{0}/intrinsic & mass of the radiating fermion (mandatory) \\\hline \ttt{epa\_q\_max} & \ttt{0}/$\sqrt{s}$ & upper cutoff for EPA \\\hline \ttt{?epa\_recoil} & \ttt{false} & flag to switch on recoil/$p_T$ \\\hline \ttt{?epa\_keep\_energy} & \ttt{false} & recoil flag to conserve energy in splitting \\\hline \end{tabular}}\mbox{} The adjustable parameters are partially similar to the parameters in the QED initial-state radiation (ISR), cf. Sec.~\ref{sec:lepton_isr}: the parameter \ttt{epa\_alpha} sets the value of the electromagnetic coupling constant, $\alpha_{QED}$ used in the EPA structure function. If not set, this is taken from the value inside the active physics model. The same is true for the mass of the particle that radiates the photon of the hard interaction, which can be reset by the user with the variable \ttt{epa\_mass}. There are two dimensionful scale parameters, the minimal momentum transfer to the photon, \ttt{epa\_q\_min}, which must not be zero, and the upper momentum-transfer cutoff for the EPA structure function, \ttt{epa\_q\_max}. The default for the latter value is the collider energy, $\sqrt{s}$, or the energy reduced by another structure function like e.g. beamstrahlung, $\sqrt{\hat{s}}$. Furthermore, there is a soft-photon regulator for the splitting function in $x$ space, \ttt{epa\_x\_min}, which also has to be explicitly set different from zero. Hence, a minimal viable scenario that will be accepted by \whizard\ looks like this: \begin{quote} \begin{footnotesize} \begin{Verbatim} beams = e1, E1 => epa epa_q_min = 5 GeV epa_x_min = 0.01 \end{Verbatim} \end{footnotesize} \end{quote} Finally, like the ISR case in Sec.~\ref{sec:lepton_isr}, there is a flag to consider the recoil of the photon against the radiating electron by setting \ttt{?epa\_recoil} to \ttt{true} (default: \ttt{false}). Though in principle processes like $e^+ e^- \to e^+ e^- \gamma \gamma$ where the two photons have been created almost collinearly and then initiate a hard process could be described by exact matrix elements and exact kinematics. However, the numerical stability in the very far collinear kinematics is rather challenging, such that the use of the EPA is very often an acceptable trade-off between quality of the description on the one hand and numerical stability and speed on the other hand. In the case, the EPA is set after a second structure function like a hadron collider PDF, there is a flavor summation over the quark constituents inside the proton, which are then the radiating fermions for the EPA. Here, the masses of all fermions have to be identical. More about the physics of the equivalent photon approximation can be found in Chap.~\ref{chap:hardint}. %%%%%%%%%%%%%%% \subsection{Effective $W$ approximation} \label{sec:ewa} An approach similar to the equivalent photon approximation (EPA) discussed in the previous section Sec.~\ref{sec:epa}, is the usage of a collinear splitting function for the radiation of massive electroweak vector bosons $W$/$Z$, the effective $W$ approximation (EWA). It has been developed for the description of high-energy weak vector-boson fusion and scattering processes at hadron colliders, particularly the Superconducting Super-Collider (SSC). This was at a time when the simulation of $2\to 4$ processes war still very challenging and $2\to 6$ processes almost impossible, such that this approximation was the only viable solution for the simulation of processes like $pp \to jjVV$ and subsequent decays of the bosons $V \equiv W, Z$. Unlike the EPA, the EWA is much more involved as the structure functions do depend on the isospin of the radiating fermions, and are also different for transversal and longitudinal polarizations. Also, a truely collinear kinematics is never possible due to the finite $W$ and $Z$ boson masses, which start becoming more and more negligible for energies larger than the nominal LHC energy of 14 TeV. Though in principle all processes for which the EWA might be applicable are technically feasible in \whizard\ to be generated also via full matrix elements, the EWA has been implemented in \whizard\ for testing purposes, backwards compatibility and comparison with older simulations. Like the EPA, it is a single-beam structure function that can be applied to one or both beams. We only give an example for both beams here, this is for a 3 TeV CLIC collider: \begin{quote} \begin{footnotesize} \begin{Verbatim} sqrts = 3 TeV beams = e1, E1 => ewa \end{Verbatim} \end{footnotesize} \end{quote} And this is for LHC or a higher-energy follow-up collider (which also shows the concatenation of the single-beam structure functions, applied to both beams consecutively, cf. Sec.~\ref{sec:concatenation}: \begin{quote} \begin{footnotesize} \begin{Verbatim} sqrts = 14 TeV beams = p, p => pdf_builtin => ewa \end{Verbatim} \end{footnotesize} \end{quote} Again, we list all the options, parameters and flags that can be adapted for the EWA: \vspace{2mm} \centerline{\begin{tabular}{|l|l|l|}\hline Parameter & Default & Meaning \\\hline\hline \ttt{ewa\_x\_min} & \ttt{0.} & soft $W$/$Z$ cutoff in $x$ (mandatory) \\\hline \ttt{ewa\_mass} & \ttt{0}/intrinsic & mass of the radiating fermion \\\hline \ttt{ewa\_pt\_max} & \ttt{0}/$\sqrt{\hat{s}}$ & upper cutoff for EWA \\\hline \ttt{?ewa\_recoil} & \ttt{false} & recoil switch \\\hline \ttt{?ewa\_keep\_energy} & \ttt{false} & energy conservation for recoil in splitting \\\hline \end{tabular}}\mbox{} First of all, all coupling constants are taken from the active physics model as they have to be consistent with electroweak gauge invariance. Like for EPA, there is a soft $x$ cutoff for the $f \to f V$ splitting, \ttt{ewa\_x\_min}, that has to be set different from zero by the user. Again, the mass of the radiating fermion can be set explicitly by the user; and, also again, the masses for the flavor sum of quarks after a PDF as radiators of the electroweak bosons have to be identical. Also for the EWA, there is an upper cutoff for the $p_T$ of the electroweak boson, that can be set via \ttt{eta\_pt\_max}. Indeed, the transversal $W$/$Z$ structure function is logarithmically divergent in that variable. If it is not set by the user, it is estimated from $\sqrt{s}$ and the splitting kinematics. For the EWA, there is a flag to switch on a recoil for the electroweak boson against the radiating fermion, \ttt{?ewa\_recoil}. Note that this is an experimental feature that is not completely tested. In any case, the non-collinear kinematics violates 4-four momentum conservation, so there are two choices: either to conserve the energy (\ttt{?ewa\_keep\_energy = true}) or to conserve 3-momentum (\ttt{?ewa\_keep\_energy = false}). Momentum conservation for the kinematics is the default. This is due to the fact that for energy conservation, there will be a net total momentum in the event including the beam remnants (ISR/EPA/EWA radiated particles) that leeds to unexpected or unphysical features in the energy distributions of the beam remnants recoiling against the rest of the event. More details about the physics can be found in Chap.~\ref{chap:hardint}. %%%%%%%%%%%%%%% \subsection{Energy scans using structure functions} In \whizard, there is an implementation of a pair spectrum, \ttt{energy\_scan}, that allows to scan the energy dependence of a cross section without actually scanning over the collider energies. Instead, only a single integration at the upper end of the scan interval over the process with an additional pair spectrum structure function performed. The structure function is chosen in such a way, that the distribution of $x$ values of the energy scan pair spectrum translates in a plot over the energy of the final state in an energy scan from \ttt{0} to \ttt{sqrts} for the process under consideration. The simplest example is the $1/s$ fall-off with the $Z$ resonance in $e^+e^- \to \mu^+ \mu^-$, where the syntax is very easy: \begin{quote} \begin{footnotesize} \begin{Verbatim} process eemm = e1, E1 => e2, E2 sqrts = 500 GeV cuts = sqrts_hat > 50 beams = e1, E1 => energy_scan integrate (eemm) \end{Verbatim} \end{footnotesize} \end{quote} The value of \ttt{sqrts = 500 GeV} gives the upper limit for the scan, while the cut effectively let the scan start at 50 GeV. There are no adjustable parameters for this structure function. How to plot the invariant mass distribution of the final-state muon pair to show the energy scan over the cross section, will be explained in Sec.~\ref{sec:analysis}. More details can be found in Chap.~\ref{chap:hardint}. %%%%%%%%%%%%%%% \subsection{Photon collider spectra} \label{sec:photoncoll} One option that has been discussed as an alternative possibility for a high-energy linear lepton collider is to convert the electron and positron beam via Compton backscattering off intense laser beams into photon beams~\cite{Ginzburg:1981vm,Telnov:1989sd,Telnov:1995hc}. Naturally, due to the production of the photon beams and the inherent electron spectrum, the photon beams have a characteristic spectrum. The simulation of such spectra is possible within \whizard\ by means of the subpackage \circetwo, which have been mentioned already in Sec.~\ref{sec:beamstrahlung}. It allows to give a much more elaborate description of a linear lepton collider environment than \circeone\ (which, however, is not in all cases necessary, as the ILC beamspectra for electron/positrons can be perfectly well described with \circeone). Here is a typical photon collider setup where we take a photon-initiated process: \begin{quote} \begin{footnotesize} \begin{Verbatim} process aaww = A, A => Wp, Wm beams = A, A => circe2 $circe2_file = "teslagg_500_polavg.circe" $circe2_design = "TESLA/GG" ?circe2_polarized = false \end{Verbatim} \end{footnotesize}%$ \end{quote} Here, the photons are the initial states initiating the hard scattering. The structure function is \ttt{circe2} which always is a pair spectrum. The list of available options are: \vspace{2mm} \centerline{\begin{tabular}{|l|l|l|}\hline Parameter & Default & Meaning \\\hline\hline \ttt{?circe2\_polarized} & \ttt{true} & spectrum respects polarization info \\\hline \ttt{\$circe2\_file} & -- & name of beam spectrum data file \\\hline \ttt{\$circe2\_design} & \ttt{"*"} & collider design \\\hline \end{tabular}}\mbox{} The only logical flag \ttt{?circe2\_polarized} let \whizard\ know whether it should keep polarization information in the beam spectra or average over polarizations. Naturally, because of the Compton backscattering generation of the photons, photon spectra are always polarized. The collider design can be specified by the string variable \ttt{\$circe2\_design}, where the default setting \ttt{"*"} corresponds to the default of \circetwo\ (which is the TESLA 500 GeV machine as discussed in the TESLA Technical Design Report~\cite{AguilarSaavedra:2001rg,Richard:2001qm}). Note that up to now there have not been any setups for a photon collider option for the modern linear collider concepts like ILC and CLIC. The string variable \ttt{\$circe2\_file} then allows to give the name of the file containing the actual beam spectrum; all files that ship with \whizard\ are stored in the directory \ttt{circe2/share/data}. More details about the subpackage \circetwo\ and the physics it covers, can be found in its own manual and the chapter Chap.~\ref{chap:hardint}. %%%%%%%%%%%%%%% \subsection{Concatenation of several structure functions} \label{sec:concatenation} As has been shown already in Sec.~\ref{sec:epa} and Sec.~\ref{sec:ewa}, it is possible within \whizard\ to concatenate more than one structure function, irrespective of the fact, whether the structure functions are single-beam structure functions or pair spectra. One important thing is whether there is a phase-space mapping for these structure functions. Also, there are some combinations which do not make sense from the physics point of view, for example using lepton-collider ISR for protons, and then afterwards switching on PDFs. Such combinations will be vetoed by \whizard, and you will find an error message like (cf. also Sec.~\ref{sec:errors}): \begin{interaction} ****************************************************************************** ****************************************************************************** *** FATAL ERROR: Beam structure: [....] not supported ****************************************************************************** ****************************************************************************** \end{interaction} Common examples for the concatenation of structure functions are linear collider applications, where beamstrahlung (macroscopic electromagnetic beam-beam interactions) and electron QED initial-state radiation are both switched on: \begin{code} beams = e1, E1 => circe1 => isr \end{code} Another possibility is the simulation of photon-induced backgrounds at ILC or CLIC, using beamstrahlung and equivalent photon approximation (EPA): \begin{code} beams = e1, E1 => circe1 => epa \end{code} or with beam events from a data file: \begin{code} beams = e1, E1 => beam_events => isr \end{code} In hadron collider physics, parton distribution functions (PDFs) are basically always switched on, while afterwards the user could specify to use the effective $W$ approximation (EWA) to simulate high-energy vector boson scattering: \begin{code} sqrts = 100 TeV beams = p, p => pdf_builtin => ewa \end{code} Note that this last case involves a flavor sum over the five active quark (and anti-quark) species $u$, $d$, $c$, $s$, $b$ in the proton, all of which act as radiators for the electroweak vector bosons in the EWA. This would be an example with three structure functions: \begin{code} beams = e1, E1 => circe1 => isr => epa \end{code} %%%%%%%%%%%%%%% \section{Polarization} \label{sec:polarization} %%%%% \subsection{Initial state polarization} \label{sec:initialpolarization} \whizard\ supports polarizing the inital state fully or partially by assigning a nontrivial density matrix in helicity space. Initial state polarization requires a beam setup and is initialized by means of the \ttt{beams\_pol\_density} statement\footnote{Note that the syntax for the specification of beam polarization has changed from version v2.1 to v2.2 and is incompatible between the two release series. The old syntax \ttt{beam\_polarization} with its different polarization constructors has been discarded in favor of a unified syntax.}: \begin{quote} \begin{footnotesize} \begin{verbatim} beams_pol_density = @([]), @([]) \end{verbatim} \end{footnotesize} \end{quote} The command \ttt{beams\_pol\_fraction} gives the degree of polarization of the two beams: \begin{quote} \begin{footnotesize} \begin{verbatim} beams_pol_fraction = , \end{verbatim} \end{footnotesize} \end{quote} Both commands in the form written above apply to scattering processes, where the polarization of both beams must be specified. The \ttt{beams\_pol\_density} and \ttt{beams\_pol\_fraction} are possible with a single beam declaration if a decay process is considered, but only then. While the syntax for the command \ttt{beams\_pol\_fraction} is pretty obvious, the syntax for the actual specification of the beam polarization is more intricate. We start with the polarization fraction: for each beam there is a real number between zero (unpolarized) and one (complete polarization) that can be specified either as a floating point number like \ttt{0.4} or with a percentage: \ttt{40 \%}. Note that the actual arithmetics is sometimes counterintuitive: 80 \% left-handed electron polarization means that 80 \% of the electron beam are polarized, 20 \% are unpolarized, i.e. 20 \% have half left- and half right-handed polarization each. Hence, 90 \% of the electron beam is left-handed, 10 \% is right-handed. How does the specification of the polarization work? If there are no entries at all in the polarization constructor, \ttt{@()}, the beam is unpolarized, and the spin density matrix is proportional to the unit/identity matrix. Placing entries into the \ttt{@()} constructor follows the concept of sparse matrices, i.e. the entries that have been specified will be present, while the rest remains zero. Single numbers do specify entries for that particular helicity on the main diagonal of the spin density matrix, e.g. for an electron \ttt{@(-1)} means (100\%) left-handed polarization. Different entries are separated by commas: \ttt{@(1,-1)} sets the two diagonal entries at positions $(1,1)$ and $(-1,-1)$ in the density matrix both equal to one. Two remarks are in order already here. First, note that you do not have to worry about the correct normalization of the spin density matrix, \whizard\ is taking care of this automatically. Second, in the screen output for the beam data, only those entries of the spin density matrix that have been specified by the user, will be displayed. If a \ttt{beams\_pol\_fraction} statement appears, other components will be non-zero, but might not be shown. E.g. ILC-like, 80 \% polarization of the electrons, 30 \% positron polarization will be specified like this for left-handed electrons and right-handed positrons: \begin{code} beams = e1, E1 beams_pol_density = @(-1), @(+1) beams_pol_fraction = 80%, 30% \end{code} The screen output will be like this: \begin{code} | ------------------------------------------------------------------------ | Beam structure: e-, e+ | polarization (beam 1): | @(-1: -1: ( 1.000000000000E+00, 0.000000000000E+00)) | polarization (beam 2): | @(+1: +1: ( 1.000000000000E+00, 0.000000000000E+00)) | polarization degree = 0.8000000, 0.3000000 | Beam data (collision): | e- (mass = 0.0000000E+00 GeV) polarized | e+ (mass = 0.0000000E+00 GeV) polarized \end{code} But because of the fraction of unpolarized electrons and positrons, the spin density matrices for electrons and positrons are: \[ \rho(e^-) = \diag \left ( 0.10, 0.90 \right) \qquad \rho(e^+) = \diag \left ( 0.65, 0.35 \right) \quad , \] respectively. So, in general, only the entries due to the polarized fraction will be displayed on screen. We will come back to more examples below. Again, the setting of a single entry, e.g. \ttt{@($\pm m$)}, which always sets the diagonal component $(\pm m, \pm m)$ of the spin density matrix equal to one. Here $m$ can have the following values for the different spins (in parentheses are entries that exist only for massive particles): \vspace{1mm} \begin{center} \begin{tabular}{|l|l|l|}\hline Spin $j$ & Particle type & possible $m$ values \\\hline 0 & Scalar boson & 0 \\ 1/2 & Spinor & +1, -1 \\ 1 & (Massive) Vector boson & +1, (0), -1 \\ 3/2 & (Massive) Vectorspinor & +2, (+1), (-1), -2 \\ 2 & (Massive) Tensor & +2, (+1), (0), (-1), -2 \\\hline \end{tabular} \end{center} \vspace{1mm} Off-diagonal entries that are equal to one (up to the normalization) of the spin-density matrix can be specified simply by the position, namely: \ttt{@($m$:$m'$, $m''$)}. This would result in a spin density matrix with diagonal entry $1$ for the position $(m'', m'')$, and an entry of $1$ for the off-diagonal position $(m,m')$. Furthermore, entries in the density matrix different from $1$ with a numerical value \ttt{{\em }} can be specified, separated by another colon: \ttt{@($m$:$m'$:{\em })}. Here, it does not matter whether $m$ and $m'$ are different or not. For $m = m'$ also diagonal spin density matrix entries different from one can be specified. Note that because spin density matrices have to be Hermitian, only the entry $(m,m')$ has to be set, while the complex conjugate entry at the transposed position $(m',m)$ is set automatically by \whizard. We will give some general density matrices now, and after that a few more definite examples. In the general setups below, we always give the expression for the spin density matrix only for one single beam. % { \newcommand{\cssparse}[4]{% \begin{pmatrix} #1 & 0 & \cdots & \cdots & #3 \\ 0 & 0 & \ddots & & 0 \\ \vdots & \ddots & \ddots & \ddots & \vdots \\ 0 & & \ddots & 0 & 0 \\ #4 & \cdots & \cdots & 0 & #2 \end{pmatrix}% } % \begin{itemize} \item {\bf Unpolarized:} \begin{center} \begin{footnotesize} \ttt{beams\_pol\_density = @()} \end{footnotesize} \end{center} % \newline This has the same effect as not specifying any polarization at all and is the only constructor available for scalars and fermions declared as left- or right-handed (like the neutrino). Density matrix: \[ \rho = \frac{1}{|m|}\mathbb{I} \] ($|m|$: particle multiplicity which is 2 for massless, $2j + 1$ for massive particles). % \item {\bf Circular polarization:} \begin{center} \begin{footnotesize} \ttt{beams\_pol\_density = @($\pm j$) \qquad beams\_pol\_fraction = $f$} \end{footnotesize} \end{center} A fraction $f$ (parameter range $f \in \left[0\;;\;1\right]$) of the particles are in the maximum / minimum helicity eigenstate $\pm j$, the remainder is unpolarized. For spin $\frac{1}{2}$ and massless particles of spin $>0$, only the maximal / minimal entries of the density matrix are populated, and the density matrix looks like this: \[ \rho = \diag\left(\frac{1\pm f}{2}\;,\;0\;,\;\dots\;,\;0\;, \frac{1\mp f}{2}\right) \] % \item {\bf Longitudinal polarization (massive):} \begin{center} \begin{footnotesize} \ttt{beams\_pol\_density = @(0) \qquad beams\_pol\_fraction = $f$} \end{footnotesize} \end{center} We consider massive particles with maximal spin component $j$, a fraction $f$ of which having longitudinal polarization, the remainder is unpolarized. Longitudinal polarization is (obviously) only available for massive bosons of spin $>0$. Again, the parameter range for the fraction is: $f \in \left[0\;;\;1\right]$. The density matrix has the form: \[ \rho = \diag\left(\frac{1-f}{|m|}\;,\;\dots\;,\;\frac{1-f}{|m|}\;,\; \frac{1+f \left(|m| - 1\right)}{|m|}\;,\;\frac{1-f}{|m|}\;, \;\dots\;,\;\frac{1-f}{|m|}\right) \] ($|m| = 2j+1 $: particle multiplicity) % \item {\bf Transverse polarization (along an axis):} \begin{center} \begin{footnotesize} \ttt{beams\_pol\_density = @(j, -j, j:-j:exp(-I*phi)) \qquad beams\_pol\_fraction = $f$} \end{footnotesize} \end{center} This so called transverse polarization is a polarization along an arbitrary direction in the $x-y$ plane, with $\phi=0$ being the positive $x$ direction and $\phi=90^\circ$ the positive $y$ direction. Note that the value of \ttt{phi} has either to be set inside the beam polarization expression explicitly or by a statement \ttt{real phi = {\em val} degree} before. A fraction $f$ of the particles are polarized, the remainder is unpolarized. Note that, although this yields a valid density matrix for all particles with multiplicity $>1$ (in which the only the highest and lowest helicity states are populated), it is meaningful only for spin $\frac{1}{2}$ particles and massless bosons of spin $>0$. The range of the parameters are: $f \in \left[0\;;\;1\right]$ and $\phi \in \mathbb{R}$. This yields a density matrix: \[ \rho = \cssparse{1}{1} {\frac{f}{2}\,e^{-i\phi}} {\frac{f}{2}\,e^{i\phi}} \] (for antiparticles, the matrix is conjugated). % \item {\bf Polarization along arbitrary axis $\left(\theta, \phi\right)$:} \begin{center} \begin{footnotesize} \ttt{beams\_pol\_density = @(j:j:1-cos(theta), j:-j:sin(theta)*exp(-I*phi), -j:-j:1+cos(theta))} \qquad\quad\qquad \ttt{beams\_pol\_fraction = $f$} \end{footnotesize} \end{center} This example describes polarization along an arbitrary axis in polar coordinates (polar axis in positive $z$ direction, polar angle $\theta$, azimuthal angle $\phi$). A fraction $f$ of the particles are polarized, the remainder is unpolarized. Note that, although axis polarization defines a valid density matrix for all particles with multiplicity $>1$, it is meaningful only for particles with spin $\frac{1}{2}$. Valid ranges for the parameters are $f \in \left[0\;;\;1\right]$, $\theta \in \mathbb{R}$, $\phi \in \mathbb{R}$. The density matrix then has the form: \[ \rho = \frac{1}{2}\cdot \cssparse{1 - f\cos\theta}{1 + f\cos\theta} {f\sin\theta\, e^{-i\phi}}{f\sin\theta\, e^{i\phi}} \] % \item {\bf Diagonal density matrix:} \begin{center} \begin{footnotesize} \ttt{beams\_pol\_density = @(j:j:$h_j$, j-1:j-1:$h_{j-1}$, $\ldots$, -j:-j:$h_{-j}$)} \end{footnotesize} \end{center} This defines an arbitrary diagonal density matrix with entries $\rho_{j,j}\,,\,\dots\,,\,\rho_{-j,-j}$. % \item {\bf Arbitrary density matrix:} \begin{center} \begin{footnotesize} \ttt{beams\_pol\_density = @($\{m:m':x_{m,m'}\}$)}: \end{footnotesize} \end{center} Here, \ttt{$\{m:m':x_{m,m'}\}$} denotes a selection of entries at various positions somewhere in the spin density matrix. \whizard\ will check whether this is a valid spin density matrix, but it does e.g. not have to correspond to a pure state. % \end{itemize} } % The beam polarization statements can be used both globally directly with the \ttt{beams} specification, or locally inside the \ttt{integrate} or \ttt{simulate} command. Some more specific examples are in order to show how initial state polarization works: % \begin{itemize} \item \begin{quote} \begin{footnotesize} \begin{verbatim} beams = A, A beams_pol_density = @(+1), @(1, -1, 1:-1:-I) \end{verbatim} \end{footnotesize} \end{quote} This declares the initial state to be composed of two incoming photons, where the first photon is right-handed, and the second photon has transverse polarization in $y$ direction. % \item \begin{quote} \begin{footnotesize} \begin{verbatim} beams = A, A beams_pol_density = @(+1), @(1, -1, 1:-1:-1) \end{verbatim} \end{footnotesize} \end{quote} Same as before, but this time the second photon has transverse polarization in $x$ direction. % \item \begin{quote} \begin{footnotesize} \begin{verbatim} beams = "W+" beams_pol\_density = @(0) \end{verbatim} \end{footnotesize} \end{quote} This example sets up the decay of a longitudinal vector boson. % \item \begin{quote} \begin{footnotesize} \begin{verbatim} beams = E1, e1 scan int hel_ep = (-1, 1) { scan int hel_em = (-1, 1) { beams_pol_density = @(hel_ep), @(hel_em) integrate (eeww) } } integrate (eeww) \end{verbatim} \end{footnotesize} \end{quote} This example loops over the different positron and electron helicity combinations and calculates the respective integrals. The \ttt{beams\_pol\_density} statement is local to the scan loop(s) and, therefore, the last \ttt{integrate} calculates the unpolarized integral. \end{itemize} % Although beam polarization should be straightforward to use, some pitfalls exist for the unwary: \begin{itemize} \item Once \ttt{beams\_pol\_density} is set globally, it persists and is applied every time \ttt{beams} is executed (unless it is reset). In particular, this means that code like \begin{quote} \begin{footnotesize} \begin{verbatim} process wwaa = Wp, Wm => A, A process zee = Z => e1, E1 sqrts = 200 GeV beams_pol_density = @(1, -1, 1:-1:-1), @() beams = Wp, Wm integrate (wwaa) beams = Z integrate (zee) beams_pol_density = @(0) \end{verbatim} \end{footnotesize} \end{quote} will throw an error, because \whizard\ complains that the spin density matrix has the wrong dimensionality for the second (the decay) process. This kind of trap can be avoided be using \ttt{beams\_pol\_density} only locally in \ttt{integrate} or \ttt{simulate} statements. % \item On-the-fly integrations executed by \ttt{simulate} use the beam setup found at the point of execution. This implies that any polarization settings you have previously done affect the result of the integration. % \item The \ttt{unstable} command also requires integrals of the selected decay processes, and will compute them on-the-fly if they are unavailable. Here, a polarized integral is not meaningful at all. Therefore, this command ignores the current \ttt{beam} setting and issues a warning if a previous polarized integral is available; this will be discarded. \end{itemize} \subsection{Final state polarization} Final state polarization is available in \whizard\ in the sense that the polarization of real final state particles can be retained when generating simulated events. In order for the polarization of a particle to be retained, it must be declared as polarized via the \ttt{polarized} statement \begin{quote} \begin{footnotesize} \begin{verbatim} polarized particle [, particle, ...] \end{verbatim} \end{footnotesize} \end{quote} The effect of \ttt{polarized} can be reversed with the \ttt{unpolarized} statement which has the same syntax. For example, \begin{quote} \begin{footnotesize} \begin{verbatim} polarized "W+", "W-", Z \end{verbatim} \end{footnotesize} \end{quote} will cause the polarization of all final state $W$ and $Z$ bosons to be retained, while \begin{quote} \begin{footnotesize} \begin{verbatim} unpolarized "W+", "W-", Z \end{verbatim} \end{footnotesize} \end{quote} will reverse the effect and cause the polarization to be summed over again. Note that \ttt{polarized} and \ttt{unpolarized} are global statements which cannot be used locally as command arguments and if you use them e.g. in a loop, the effects will persist beyond the loop body. Also, a particle cannot be \ttt{polarized} and \ttt{unstable} at the same time (this restriction might be loosened in future versions of \whizard). After toggling the polarization flag, the generation of polarized events can be requested by using the \ttt{?polarized\_events} option of the \ttt{simulate} command, e.g. \begin{quote} \begin{footnotesize} \begin{verbatim} simulate (eeww) { ?polarized_events = true } \end{verbatim} \end{footnotesize} \end{quote} When \ttt{simulate} is run in this mode, helicity information for final state particles that have been toggled as \ttt{polarized} is written to the event file(s) (provided that polarization is supported by the selected event file format(s) ) and can also be accessed in the analysis by means of the \ttt{Hel} observable. For example, an analysis definition like \begin{quote} \begin{footnotesize} \begin{verbatim} analysis = if (all Hel == -1 ["W+"] and all Hel == -1 ["W-"] ) then record cta_nn (eval cos (Theta) ["W+"]) endif; if (all Hel == -1 ["W+"] and all Hel == 0 ["W-"] ) then record cta_nl (eval cos (Theta) ["W+"]) endif \end{verbatim} \end{footnotesize} \end{quote} can be used to histogram the angular distribution for the production of polarized $W$ pairs (obviously, the example would have to be extended to cover all possible helicity combinations). Note, however, that helicity information is not available in the integration step; therefore, it is not possible to use \ttt{Hel} as a cut observable. While final state polarization is straightforward to use, there is a caveat when used in combination with flavor products. If a particle in a flavor product is defined as \ttt{polarized}, then all particles ``originating'' from the product will act as if they had been declared as \ttt{polarized} --- their polarization will be recorded in the generated events. E.g., the example \begin{quote} \begin{footnotesize} \begin{verbatim} process test = u:d, ubar:dbar => d:u, dbar:ubar, u, ubar ! insert compilation, cuts and integration here polarized d, dbar simulate (test) {?polarized_events = true} \end{verbatim} \end{footnotesize} \end{quote} will generate events including helicity information for all final state $d$ and $\overline{d}$ quarks, but only for part of the final state $u$ and $\overline{u}$ quarks. In this case, if you had wanted to keep the helicity information also for all $u$ and $\overline{u}$, you would have had to explicitely include them into the \ttt{polarized} statement. \section{Cross sections} Integrating matrix elements over phase space is the core of \whizard's activities. For any process where we want the cross section, distributions, or event samples, the cross section has to be determined first. This is done by a doubly adaptive multi-channel Monte-Carlo integration. The integration, in turn, requires a \emph{phase-space setup}, i.e., a collection of phase-space \emph{channels}, which are mappings of the unit hypercube onto the complete space of multi-particle kinematics. This phase-space information is encoded in the file \emph{xxx}\ttt{.phs}, where \emph{xxx} is the process tag. \whizard\ generates the phase-space file on the fly and can reuse it in later integrations. For each phase-space channel, the unit hypercube is binned in each dimension. The bin boundaries are allowed to move during a sequence of iterations, each with a fixed number of sampled phase-space points, so they adapt to the actual phase-space density as far as possible. In addition to this \emph{intrinsic} adaptation, the relative channel weights are also allowed to vary. All these steps are done automatically when the \ttt{integrate} command is executed. At the end of the iterative adaptation procedure, the program has obtained an estimate for the integral of the matrix element over phase space, together with an error estimate, and a set of integration \emph{grids} which contains all information on channel weights and bin boundaries. This information is stored in a file \emph{xxx}\ttt{.vg}, where \emph{xxx} is the process tag, and is used for event generation by the \ttt{simulate} command. \subsection{Integration} \label{sec:integrate} Since everything can be handled automatically using default parameters, it often suffices to write the command \begin{quote} \begin{footnotesize} \begin{verbatim} integrate (proc1) \end{verbatim} \end{footnotesize} \end{quote} for integrating the process with name tag \ttt{proc1}, and similarly \begin{quote} \begin{footnotesize} \begin{verbatim} integrate (proc1, proc2, proc3) \end{verbatim} \end{footnotesize} \end{quote} for integrating several processes consecutively. Options to the integrate command are specified, if not globally, by a local option string \begin{quote} \begin{footnotesize} \begin{verbatim} integrate (proc1, proc2, proc3) { mH = 200 GeV } \end{verbatim} \end{footnotesize} \end{quote} (It is possible to place a \ttt{beams} statement inside the option string, if desired.) If the process is configured but not compiled, compilation will be done automatically. If it is not available at all, integration will fail. The integration method can be specified by the string variable \begin{quote} \begin{footnotesize} \ttt{\$integration\_method = "{\em }"} \end{footnotesize} \end{quote} %$ The default method is called \ttt{"vamp"} and uses the \vamp\ algorithm and code. (At the moment, there is only a single simplistic alternative, using the midpoint rule or rectangle method for integration, \ttt{"midpoint"}. This is mainly for testing purposes. In future versions of \whizard, more methods like e.g. Gauss integration will be made available). \vamp, however, is clearly the main integration method. It is done in several \emph{passes} (usually two), and each pass consists of several \emph{iterations}. An iteration consists of a definite number of \emph{calls} to the matrix-element function. For each iteration, \whizard\ computes an estimate of the integral and an estimate of the error, based on the binned sums of matrix element values and squares. It also computes an estimate of the rejection efficiency for generating unweighted events, i.e., the ratio of the average sampling function value over the maximum value of this function. After each iteration, both the integration grids (the binnings) and the relative weights of the integration channels can be adapted to minimize the variance estimate of the integral. After each pass of several iterations, \whizard\ computes an average of the iterations within the pass, the corresponding error estimate, and a $\chi^2$ value. The integral, error, efficiency and $\chi^2$ value computed for the most recent integration pass, together with the most recent integration grid, are used for any subsequent calculation that involves this process, in particular for event generation. In the default setup, during the first pass(es) both grid binnings and channel weights are adapted. In the final (usually second) pass, only binnings are further adapted. Roughly speaking, the final pass is the actual calculation, while the previous pass(es) are used for ``warming up'' the integration grids, without using the numerical results. Below, in the section about the specification of the iterations, Sec.~\ref{sec:iterations}, we will explain how it is possible to change the behavior of adapting grids and weights. Here is an example of the integration output, which illustrates these properties. The \sindarin\ script describes the process $e^+e^-\to q\bar q q\bar q$ with $q$ being any light quark, i.e., $W^+W^-$ and $ZZ$ production and hadronic decay together will any irreducible background. We cut on $p_T$ and energy of jets, and on the invariant mass of jet pairs. Here is the script: \begin{quote} \begin{footnotesize} \begin{verbatim} alias q = d:u:s:c alias Q = D:U:S:C process proc_4f = e1, E1 => q, Q, q, Q ms = 0 mc = 0 sqrts = 500 GeV cuts = all (Pt > 10 GeV and E > 10 GeV) [q:Q] and all M > 10 GeV [q:Q, q:Q] integrate (proc_4f) \end{verbatim} \end{footnotesize} \end{quote} After the run is finished, the integration output looks like \begin{quote} \begin{footnotesize} \begin{verbatim} | Process library 'default_lib': loading | Process library 'default_lib': ... success. | Integrate: compilation done | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 12511 | Initializing integration for process proc_4f: | ------------------------------------------------------------------------ | Process [scattering]: 'proc_4f' | Library name = 'default_lib' | Process index = 1 | Process components: | 1: 'proc_4f_i1': e-, e+ => d:u:s:c, dbar:ubar:sbar:cbar, | d:u:s:c, dbar:ubar:sbar:cbar [omega] | ------------------------------------------------------------------------ | Beam structure: [any particles] | Beam data (collision): | e- (mass = 5.1099700E-04 GeV) | e+ (mass = 5.1099700E-04 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'proc_4f_i1.phs' | Phase space: 123 channels, 8 dimensions | Phase space: found 123 channels, collected in 15 groves. | Phase space: Using 195 equivalences between channels. | Phase space: wood | Applying user-defined cuts. | OpenMP: Using 8 threads | Starting integration for process 'proc_4f' | Integrate: iterations not specified, using default | Integrate: iterations = 10:10000:"gw", 5:20000:"" | Integrator: 15 chains, 123 channels, 8 dimensions | Integrator: Using VAMP channel equivalences | Integrator: 10000 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 9963 2.3797857E+03 3.37E+02 14.15 14.13* 4.02 2 9887 2.8307603E+03 9.58E+01 3.39 3.37* 4.31 3 9815 3.0132091E+03 5.10E+01 1.69 1.68* 8.37 4 9754 2.9314937E+03 3.64E+01 1.24 1.23* 10.65 5 9704 2.9088284E+03 3.40E+01 1.17 1.15* 12.99 6 9639 2.9725788E+03 3.53E+01 1.19 1.17 15.34 7 9583 2.9812484E+03 3.10E+01 1.04 1.02* 17.97 8 9521 2.9295139E+03 2.88E+01 0.98 0.96* 22.27 9 9435 2.9749262E+03 2.94E+01 0.99 0.96 20.25 10 9376 2.9563369E+03 3.01E+01 1.02 0.99 21.10 |-----------------------------------------------------------------------------| 10 96677 2.9525019E+03 1.16E+01 0.39 1.22 21.10 1.15 10 |-----------------------------------------------------------------------------| 11 19945 2.9599072E+03 2.13E+01 0.72 1.02 15.03 12 19945 2.9367733E+03 1.99E+01 0.68 0.96* 12.68 13 19945 2.9487747E+03 2.03E+01 0.69 0.97 11.63 14 19945 2.9777794E+03 2.03E+01 0.68 0.96* 11.19 15 19945 2.9246612E+03 1.95E+01 0.67 0.94* 10.34 |-----------------------------------------------------------------------------| 15 99725 2.9488622E+03 9.04E+00 0.31 0.97 10.34 1.05 5 |=============================================================================| | Time estimate for generating 10000 events: 0d:00h:00m:51s | Creating integration history display proc_4f-history.ps and proc_4f-history.pdf \end{verbatim} \end{footnotesize} \end{quote} Each row shows the index of a single iteration, the number of matrix element calls for that iteration, and the integral and error estimate. Note that the number of calls displayed are the real calls to the matrix elements after all cuts and possible rejections. The error should be viewed as the $1\sigma$ uncertainty, computed on a statistical \begin{figure} \centering \includegraphics[width=.56\textwidth]{proc_4f-history} \caption{\label{fig:inthistory} Graphical output of the convergence of the adaptation during the integration of a \whizard\ process.} \end{figure} basis. The next two columns display the error in percent, and the \emph{accuracy} which is the same error normalized by $\sqrt{n_{\rm calls}}$. The accuracy value has the property that it is independent of $n_{\rm calls}$, it describes the quality of adaptation of the current grids. Good-quality grids have a number of order one, the smaller the better. The next column is the estimate for the rejection efficiency in percent. Here, the value should be as high as possible, with $100\,\%$ being the possible maximum. In the example, the grids are adapted over ten iterations, after which the accuracy and efficiency have saturated at about $1.0$ and $10\,\%$, respectively. The asterisk in the accuracy column marks those iterations where an improvement over the previous iteration is seen. The average over these iterations exhibits an accuracy of $1.22$, corresponding to $0.39\,\%$ error, and a $\chi^2$ value of $1.15$, which is just right: apparently, the phase-space for this process and set of cuts is well-behaved. The subsequent five iterations are used for obtaining the final integral, which has an accuracy below one (error $0.3\,\%$), while the efficiency settles at about $10\,\%$. In this example, the final $\chi^2$ value happens to be quite small, i.e., the individual results are closer together than the error estimates would suggest. One should nevertheless not scale down the error, but rather scale it up if the $\chi^2$ result happens to be much larger than unity: this often indicates sub-optimally adapted grids, which insufficiently map some corner of phase space. One should note that all values are subject to statistical fluctuations, since the number of calls within each iterations is finite. Typically, fluctuations in the efficiency estimate are considerably larger than fluctuations in the error/accuracy estimate. Two subsequent runs of the same script should yield statistically independent results which may differ in all quantities, within the error estimates, since the seed of the random-number generator will differ by default. It is possible to get exactly reproducible results by setting the random-number seed explicitly, e.g., \begin{quote} \begin{footnotesize} \begin{verbatim} seed = 12345 \end{verbatim} \end{footnotesize} \end{quote} at any point in the \sindarin\ script. \ttt{seed} is a predefined intrinsic variable. The value can be any 32bit integer. Two runs with different seeds can be safely taken as statistically independent. In the example above, no seed has been set, and the seed has therefore been determined internally by \whizard\ from the system clock. The concluding line with the time estimate applies to a subsequent simulation step with unweighted events, which is not actually requested in the current example. It is based on the timing and efficiency estimate of the most recent iteration. As a default, a graphical output of the integration history will be produced (if both \LaTeX\ and \metapost\ have been available during configuration). Fig.~\ref{fig:inthistory} shows how this looks like, and demonstrates how a proper convergence of the integral during the adaptation looks like. The generation of these graphical history files can be switched off using the command \ttt{?vis\_history = false}. %%%%% \subsection{Integration run IDs} A single \sindarin\ script may contain multiple calls to the \ttt{integrate} command with different parameters. By default, files generated for the same process in a subsequent integration will overwrite the previous ones. This is undesirable when the script is re-run: all results that have been overwritten have to be recreated. To avoid this, the user may identify a specific run by a string-valued ID, e.g. \begin{quote} \begin{footnotesize} \begin{verbatim} integrate (foo) { $run_id = "first" } \end{verbatim} \end{footnotesize} \end{quote} This ID will become part of the file name for all files that are created specifically for this run. Often it is useful to create a run ID from a numerical value using \ttt{sprintf}, e.g., in this scan: \begin{quote} \begin{footnotesize} \begin{verbatim} scan real mh = (100 => 200 /+ 10) { $run_id = sprintf "%e" (mh) integrate (h_production) } \end{verbatim} \end{footnotesize} \end{quote} With unique run IDs, a subsequent run of the same \sindarin\ script will be able to reuse all previous results, even if there is more than a single integration per process. \subsection{Controlling iterations} \label{sec:iterations} \whizard\ has some predefined numbers of iterations and calls for the first and second integration pass, respectively, which depend on the number of initial and final-state particles. They are guesses for values that yield good-quality grids and error values in standard situations, where no exceptionally strong peaks or loose cuts are present in the integrand. Actually, the large number of warmup iterations in the previous example indicates some safety margin in that respect. It is possible, and often advisable, to adjust the iteration and call numbers to the particular situation. One may reduce the default numbers to short-cut the integration, if either less accuracy is needed, or CPU time is to be saved. Otherwise, if convergence is bad, the number of iterations or calls might be increased. To set iterations manually, there is the \ttt{iterations} command: \begin{quote} \begin{footnotesize} \begin{verbatim} iterations = 5:50000, 3:100000 \end{verbatim} \end{footnotesize} \end{quote} This is a comma-separated list. Each pair of values corresponds to an integration pass. The value before the colon is the number of iterations for this pass, the other number is the number of calls per iteration. While the default number of passes is two (one for warmup, one for the final result), you may specify a single pass \begin{quote} \begin{footnotesize} \begin{verbatim} iterations = 5:100000 \end{verbatim} \end{footnotesize} \end{quote} where the relative channel weights will \emph{not} be adjusted (because this is the final pass). This is appropriate for well-behaved integrands where weight adaptation is not necessary. You can also define more than two passes. That might be useful when reusing a previous grid file with insufficient quality: specify the previous passes as-is, so the previous results will be read in, and then a new pass for further adaptation. In the final pass, the default behavior is to not adapt grids and weights anymore. Otherwise, different iterations would be correlated, and a final reliable error estimate would not be possible. For all but the final passes, the user can decide whether to adapt grids and weights by attaching a string specifier to the number of iterations: \ttt{"g"} does adapt grids, but not weights, \ttt{"w"} the other way round. \ttt{"gw"} or \ttt{"wg"} does adapt both. By the setting \ttt{""}, all adaptations are switched off. An example looks like this: \begin{code} iterations = 2:10000:"gw", 3:5000 \end{code} Since it is often not known beforehand how many iterations the grid adaptation will need, it is generally a good idea to give the first pass a large number of iterations. However, in many cases these turn out to be not necessary. To shortcut iterations, you can set any of \begin{quote} \begin{footnotesize} \begin{verbatim} accuracy_goal error_goal relative_error_goal \end{verbatim} \end{footnotesize} \end{quote} to a positive value. If this is done, \whizard\ will skip warmup iterations once all of the specified goals are reached by the current iteration. The final iterations (without weight adaptation) are always performed. \subsection{Phase space} Before \ttt{integrate} can start its work, it must have a phase-space configuration for the process at hand. The method for the phase-space parameterization is determined by the string variable \ttt{\$phs\_method}. At the moment there are only two options, \ttt{"single"}, for testing purposes, that is mainly used internally, and \whizard's traditional method, \ttt{"wood"}. This parameterization is particularly adapted and fine-tuned for electroweak processes and might not be the ideal for for pure jet cross sections. In future versions of \whizard, more options for phase-space parameterizations will be made available, e.g. the \ttt{RAMBO} algorithm and its massive cousin, and phase-space parameterizations that take care of the dipole-like emission structure in collinear QCD (or QED) splittings. For the standard method, the phase-space parameterization is laid out in an ASCII file \ttt{\textit{\_}i\textit{}.phs}. Here, \ttt{{\em }} is the process name chosen by the user while \ttt{{\em }} is the number of the process component of the corresponding process. This immediately shows that different components of processes are getting different phase space setups. This is necessary for inclusive processes, e.g. the sum of $pp \to Z + nj$ and $pp \to W + nj$, or in future versions of \whizard\ for NLO processes, where one component is the interference between the virtual and the Born matrix element, and another one is the subtraction terms. Normally, you do not have to deal with this file, since \whizard\ will generate one automatically if it does not find one. (\whizard\ is careful to check for consistency of process definition and parameters before using an existing file.) Experts might find it useful to generate a phase-space file and inspect and/or modify it before proceeding further. To this end, there is the parameter \verb|?phs_only|. If you set this \ttt{true}, \whizard\ skips the actual integration after the phase-space file has been generated. There is also a parameter \verb|?vis_channels| which can be set independently; if this is \ttt{true}, \whizard\ will generate a graphical visualization of the phase-space parameterizations encoded in the phase-space file. This file has to be taken with a grain of salt because phase space channels are represented by sample Feynman diagrams for the corresponding channel. This does however {\em not} mean that in the matrix element other Feynman diagrams are missing (the default matrix element method, \oMega, is not using Feynman-diagrammatic amplitudes at all). Things might go wrong with the default phase-space generation, or manual intervention might be necessary to improve later performance. There are a few parameters that control the algorithm of phase-space generation. To understand their meaning, you should realize that phase-space parameterizations are modeled after (dominant) Feynman graphs for the current process. \subsubsection{The main phase space setup {\em wood}} For the main phase-space parameterization of \whizard, which is called \ttt{"wood"}, there are many different parameters and flags that allow to tune and customize the phase-space setup for every certain process: The parameter \verb|phs_off_shell| controls the number of off-shell lines in those graphs, not counting $s$-channel resonances and logarithmically enhanced $s$- and $t$-channel lines. The default value is $2$. Setting it to zero will drop everything that is not resonant or logarithmically enhanced. Increasing it will include more subdominant graphs. (\whizard\ increases the value automatically if the default value does not work.) There is a similar parameter \verb|phs_t_channel| which controls multiperipheral graphs in the parameterizations. The default value is $6$, so graphs with up to $6$ $t/u$-channel lines are considered. In particular cases, such as $e^+e^-\to n\gamma$, all graphs are multiperipheral, and for $n>7$ \whizard\ would find no parameterizations in the default setup. Increasing the value of \verb|phs_t_channel| solves this problem. (This is presently not done automatically.) There are two numerical parameters that describe whether particles are treated like massless particles in particular situations. The value of \verb|phs_threshold_s| has the default value $50\;\GeV$. Hence, $W$ and $Z$ are considered massive, while $b$ quarks are considered massless. This categorization is used for deciding whether radiation of $b$ quarks can lead to (nearly) singular behavior, i.e., logarithmic enhancement, in the infrared and collinear regions. If yes, logarithmic mappings are applied to phase space. Analogously, \verb|phs_threshold_t| decides about potential $t$-channel singularities. Here, the default value is $100\;\GeV$, so amplitudes with $W$ and $Z$ in the $t$-channel are considered as logarithmically enhanced. For a high-energy hadron collider of 40 or 100 TeV energy, also $W$ and $Z$ in $s$-channel like situations might be necessary to be considered massless. Such logarithmic mappings need a dimensionful scale as parameter. There are three such scales, all with default value $10\;\GeV$: \verb|phs_e_scale| (energy), \verb|phs_m_scale| (invariant mass), and \verb|phs_q_scale| (momentum transfer). If cuts and/or masses are such that energies, invariant masses of particle pairs, and momentum transfer values below $10\;\GeV$ are excluded or suppressed, the values can be kept. In special cases they should be changed: for instance, if you want to describe $\gamma^*\to\mu^+\mu^-$ splitting well down to the muon mass, no cuts, you may set \verb|phs_m_scale = mmu|. The convergence of the Monte-Carlo integration result will be considerably faster. There are more flags. These and more details about the phase space parameterization will be described in Sec.~\ref{sec:wood}. \subsection{Cuts} \whizard~2 does not apply default cuts to the integrand. Therefore, processes with massless particles in the initial, intermediate, or final states may not have a finite cross section. This fact will manifest itself in an integration that does not converge, or is unstable, or does not yield a reasonable error or reweighting efficiency even for very large numbers of iterations or calls per iterations. When doing any calculation, you should verify first that the result that you are going to compute is finite on physical grounds. If not, you have to apply cuts that make it finite. A set of cuts is defined by the \ttt{cuts} statement. Here is an example \begin{quote} \begin{footnotesize} \begin{verbatim} cuts = all Pt > 20 GeV [colored] \end{verbatim} \end{footnotesize} \end{quote} This implies that events are kept only (for integration and simulation) if the transverse momenta of all colored particles are above $20\;\GeV$. Technically, \ttt{cuts} is a special object, which is unique within a given scope, and is defined by the logical expression on the right-hand side of the assignment. It may be defined in global scope, so it is applied to all subsequent processes. It may be redefined by another \ttt{cuts} statement. This overrides the first cuts setting: the \ttt{cuts} statement is not cumulative. Multiple cuts should be specified by the logical operators of \sindarin, for instance \begin{quote} \begin{footnotesize} \begin{verbatim} cuts = all Pt > 20 GeV [colored] and all E > 5 GeV [photon] \end{verbatim} \end{footnotesize} \end{quote} Cuts may also be defined local to an \ttt{integrate} command, i.e., in the options in braces. They will apply only to the processes being integrated, overriding any global cuts. The right-hand side expression in the \ttt{cuts} statement is evaluated at the point where it is used by an \ttt{integrate} command (which could be an implicit one called by \ttt{simulate}). Hence, if the logical expression contains parameters, such as \begin{quote} \begin{footnotesize} \begin{verbatim} mH = 120 GeV cuts = all M > mH [b, bbar] mH = 150 GeV integrate (myproc) \end{verbatim} \end{footnotesize} \end{quote} the Higgs mass value that is inserted is the value in place when \ttt{integrate} is evaluated, $150\;\GeV$ in this example. This same value will also be used when the process is called by a subsequent \ttt{simulate}; it is \ttt{integrate} which compiles the cut expression and stores it among the process data. This behavior allows for scanning over parameters without redefining the cuts every time. The cut expression can make use of all variables and constructs that are defined at the point where it is evaluated. In particular, it can make use of the particle content and kinematics of the hard process, as in the example above. In addition to the predefined variables and those defined by the user, there are the following variables which depend on the hard process: \begin{quote} \begin{tabular}{ll} integer: & \ttt{n\_in}, \ttt{n\_out}, \ttt{n\_tot} \\ real: & \ttt{sqrts}, \ttt{sqrts\_hat} \end{tabular} \end{quote} Example: \begin{quote} \begin{footnotesize} \begin{verbatim} cuts = sqrts_hat > 150 GeV \end{verbatim} \end{footnotesize} \end{quote} The constants \ttt{n\_in} etc.\ are sometimes useful if a generic set of cuts is defined, which applies to various processes simultaneously. The user is encouraged to define his/her own set of cuts, if possible in a process-independent manner, even if it is not required. The \ttt{include} command allows for storing a set of cuts in a separate \sindarin\ script which may be read in anywhere. As an example, the system directories contain a file \verb|default_cuts.sin| which may be invoked by \begin{quote} \begin{footnotesize} \begin{verbatim} include ("default_cuts.sin") \end{verbatim} \end{footnotesize} \end{quote} \subsection{QCD scale and coupling} \whizard\ treats all physical parameters of a model, the coefficients in the Lagrangian, as constants. As a leading-order program, \whizard\ does not make use of running parameters as they are described by renormalization theory. For electroweak interactions where the perturbative expansion is sufficiently well behaved, this is a consistent approach. As far as QCD is concerned, this approach does not yield numerically reliable results, even on the validity scale of the tree approximation. In \whizard\ttt{2}, it is therefore possible to replace the fixed value of $\alpha_s$ (which is accessible as the intrinsic model variable \verb|alphas|), by a function of an energy scale $\mu$. This is controlled by the parameter \verb|?alphas_is_fixed|, which is \ttt{true} by default. Setting it to \ttt{false} enables running~$\alpha_s$. The user has then to decide how $\alpha_s$ is calculated. One option is to set \verb|?alphas_from_lhapdf| (default \ttt{false}). This is recommended if the \lhapdf\ library is used for including structure functions, but it may also be set if \lhapdf\ is not invoked. \whizard\ will then use the $\alpha_s$ formula and value that matches the active \lhapdf\ structure function set and member. In the very same way, the $\alpha_s$ running from the PDFs implemented intrinsically in \whizard\ can be taken by setting \verb|?alphas_from_pdf_builtin| to \ttt{true}. This is the same running then the one from \lhapdf, if the intrinsic PDF coincides with a PDF chosen from \lhapdf. If this is not appropriate, there are again two possibilities. If \verb|?alphas_from_mz| is \ttt{true}, the user input value \verb|alphas| is interpreted as the running value $\alpha_s(m_Z)$, and for the particular event, the coupling is evolved to the appropriate scale $\mu$. The formula is controlled by the further parameters \verb|alphas_order| (default $0$, meaning leading-log; maximum $2$) and \verb|alphas_nf| (default $5$). Otherwise there is the option to set \verb|?alphas_from_lambda_qcd = true| in order to evaluate $\alpha_s$ from the scale $\Lambda_{\rm QCD}$, represented by the intrinsic variable \verb|lambda_qcd|. The reference value for the QCD scale is $\Lambda\_{\rm QCD} = 200$ MeV. \verb|alphas_order| and \verb|alphas_nf| apply analogously. Note that for using one of the running options for $\alpha_s$, always \ttt{?alphas\_is\_fixed = false} has to be invoked. In any case, if $\alpha_s$ is not fixed, each event has to be assigned an energy scale. By default, this is $\sqrt{\hat s}$, the partonic invariant mass of the event. This can be replaced by a user-defined scale, the special object \ttt{scale}. This is assigned and used just like the \ttt{cuts} object. The right-hand side is a real-valued expression. Here is an example: \begin{quote} \begin{footnotesize} \begin{verbatim} scale = eval Pt [sort by -Pt [colored]] \end{verbatim} \end{footnotesize} \end{quote} This selects the $p_T$ value of the first entry in the list of colored particles sorted by decreasing $p_T$, i.e., the $p_T$ of the hardest jet. The \ttt{scale} definition is used not just for running $\alpha_s$ (if enabled), but it is also the factorization scale for the \lhapdf\ structure functions. These two values can be set differently by specifying \ttt{factorization\_scale} for the scale at which the PDFs are evaluated. Analogously, there is a variable \ttt{renormalization\_scale} that sets the scale value for the running $\alpha_s$. Whenever any of these two values is set, it supersedes the \ttt{scale} value. Just like the \ttt{cuts} expression, the expressions for \ttt{scale}, \ttt{factorization\_scale} and also \ttt{renormalization\_scale} are evaluated at the point where it is read by an explicit or implicit \ttt{integrate} command. \subsection{Reweighting factor} It is possible to reweight the integrand by a user-defined function of the event kinematics. This is done by specifying a \ttt{weight} expression. Syntax and usage is exactly analogous to the \ttt{scale} expression. Example: \begin{quote} \begin{footnotesize} \begin{verbatim} weight = eval (1 + cos (Theta) ^ 2) [lepton] \end{verbatim} \end{footnotesize} \end{quote} We should note that the phase-space setup is not aware of this reweighting, so in complicated cases you should not expect adaptation to achieve as accurate results as for plain cross sections. Needless to say, the default \ttt{weight} is unity. \section{Events} After the cross section integral of a scattering process is known (or the partial-width integral of a decay process), \whizard\ can generate event samples. There are two limiting cases or modes of event generation: \begin{enumerate} \item For a physics simulation, one needs \emph{unweighted} events, so the probability of a process and a kinematical configuration in the event sample is given by its squared matrix element. \item Monte-Carlo integration yields \emph{weighted} events, where the probability (without any grid adaptation) is uniformly distributed over phase space, while the weight of the event is given by its squared matrix element. \end{enumerate} The choice of parameterizations and the iterative adaptation of the integration grids gradually shift the generation mode from option 2 to option 1, which obviously is preferred since it simulates the actual outcome of an experiment. Unfortunately, this adaptation is perfect only in trivial cases, such that the Monte-Carlo integration yields non-uniform probability still with weighted events. Unweighted events are obtained by rejection, i.e., accepting an event with a probability equal to its own weight divided by the maximal possible weight. Furthermore, the maximal weight is never precisely known, so this probability can only be estimated. The default generation mode of \whizard\ is unweighted. This is controlled by the parameter \verb|?unweighted| with default value \ttt{true}. Unweighted events are easy to interpret and can be directly compared with experiment, if properly interfaced with detector simulation and analysis. However, when applying rejection to generate unweighted events, the generator discards information, and for a single event it needs, on the average, $1/\epsilon$ calls, where the efficiency $\epsilon$ is the ratio of the average weight over the maximal weight. If \verb|?unweighted| is \ttt{false}, all events are kept and assigned their respective weights in histograms or event files. \subsection{Simulation} \label{sec:simulation} The \ttt{simulate} command generates an event sample. The number of events can be set either by specifying the integer variable \verb|n_events|, or by the real variable \verb|luminosity|. (This holds for unweighted events. If weighted events are requested, the luminosity value is ignored.) The luminosity is measured in femtobarns, but other units can be used, too. Since the cross sections for the processes are known at that point, the number of events is determined as the luminosity multiplied by the cross section. As usual, both parameters can be set either as global or as local parameters: \begin{quote} \begin{footnotesize} \begin{verbatim} n_events = 10000 simulate (proc1) simulate (proc2, proc3) { luminosity = 100 / 1 pbarn } \end{verbatim} \end{footnotesize} \end{quote} In the second example, both \verb|n_events| and \verb|luminosity| are set. In that case, \whizard\ chooses whatever produces the larger number of events. If more than one process is specified in the argument of \ttt{simulate}, events are distributed among the processes with fractions proportional to their cross section values. The processes are mixed randomly, as it would be the case for real data. The raw event sample is written to a file which is named after the first process in the argument of \ttt{simulate}. If the process name is \ttt{proc1}, the file will be named \ttt{proc1.evx}. You can choose another basename by the string variable \verb|$sample|. For instance, \begin{quote} \begin{footnotesize} \begin{verbatim} simulate (proc1) { n_events = 4000 $sample = "my_events" } \end{verbatim} \end{footnotesize} \end{quote} will produce an event file \verb|my_events.evx| which contains $4000$ events. This event file is in a machine-dependent binary format, so it is not of immediate use. Its principal purpose is to serve as a cache: if you re-run the same script, before starting simulation, it will look for an existing event file that matches the input. If nothing has changed, it will find the file previously generated and read in the events, instead of generating them. Thus you can modify the analysis or any further steps without repeating the time-consuming task of generating a large event sample. If you change the number of events to generate, the program will make use of the existing event sample and generate further events only when it is used up. If necessary, you can suppress the writing/reading of the raw event file by the parameters \verb|?write_raw| and \verb|?read_raw|. If you try to reuse an event file that has been written by a previous version of \whizard, you may run into an incompatibility, which will be detected as an error. If this happens, you may enforce a compatibility mode (also for writing) by setting \ttt{\$event\_file\_version} to the appropriate version string, e.g., \verb|"2.0"|. Be aware that this may break some more recent features in the event analysis. Generating an event sample can serve several purposes. First of all, it can be analyzed directly, by \whizard's built-in capabilities, to produce tables, histograms, or calculate inclusive observables. The basic analysis features of \whizard\ are described below in Sec.~\ref{sec:analysis}. It can be written to an external file in a standard format that a human or an external program can understand. In Chap.~\ref{chap:events}, you will find a more thorough discussion of event generation with \whizard, which also covers in detail the available event-file formats. Finally, \whizard\ can rescan an existing event sample. The event sample may either be the result of a previous \ttt{simulate} run or, under certain conditions, an external event sample produced by another generator or reconstructed from data. \begin{quote} \begin{footnotesize} \begin{verbatim} rescan "my_events" (proc1) { $pdf_builtin_set = "MSTW2008LO" } \end{verbatim} \end{footnotesize} \end{quote} The rescanning may apply different parameters and recalculate the matrix element, it may apply a different event selection, it may reweight the events by a different PDF set (as above). The modified event sample can again be analyzed or written to file. For more details, cf.\ Sec.~\ref{sec:rescan}. %%%%%%%%%%%%%%% \subsection{Decays} \label{sec:decays} Normally, the events generated by the \ttt{simulate} command will be identical in structure to the events that the \ttt{integrate} command generates. This implies that for a process such as $pp\to W^+W^-$, the final-state particles are on-shell and stable, so they appear explicitly in the generated event files. If events are desired where the decay products of the $W$ bosons appear, one has to generate another process, e.g., $pp\to u\bar d\bar ud$. In this case, the intermediate vector bosons, if reconstructed, are off-shell as dictated by physics, and the process contains all intermediate states that are possible. In this example, the matrix element contains also $ZZ$, photon, and non-resonant intermediate states. (This can be restricted via the \verb|$restrictions| option, cf.\ \ref{sec:process options}. Another approach is to factorize the process in production (of $W$ bosons) and decays ($W\to q\bar q$). This is actually the traditional approach, since it is much less computing-intensive. The factorization neglects all off-shell effects and irreducible background diagrams that do not have the decaying particles as an intermediate resonance. While \whizard\ is able to deal with multi-particle processes without factorization, the needed computing resources rapidly increase with the number of external particles. Particularly, it is the phase space integration that becomes the true bottleneck for a high multiplicity of final state particles. In order to use the factorized approach, one has to specify particles as \ttt{unstable}. (Also, the \ttt{?allow\_decays} switch must be \ttt{true}; this is however its default value.) We give an example for a $pp \to Wj$ final state: \begin{code} process wj = u, gl => d, Wp process wen = Wp => E1, n1 integrate (wen) sqrts = 7 TeV beams = p, p => pdf_builtin unstable Wp (wen) simulate (wj) { n_events = 1 } \end{code} This defines a $2 \to 2$ hard scattering process of $W + j$ production at the 7 TeV LHC 2011 run. The $W^+$ is marked as unstable, with its decay process being $W^+ \to e^+ \nu_e$. In the \ttt{simulate} command both processes, the production process \ttt{wj} and the decay process \ttt{wen} will be integrated, while the $W$ decays become effective only in the final event sample. This event sample will contain final states with multiplicity $3$, namely $e^+ \nu_e d$. Note that here only one decay process is given, hence the branching ratio for the decay will be taken to be $100 \%$ by \whizard. A natural restriction of the factorized approach is the implied narrow-width approximation. Theoretically, this restriction is necessary since whenever the width plays an important role, the usage of the factorized approach will not be fully justified. In particular, all involved matrix elements must be evaluated on-shell, or otherwise gauge-invariance issues could spoil the calculation. (There are plans for a future \whizard\ version to also include Breit-Wigner or Gaussian distributions when using the factorized approach.) Decays can be concatenated, e.g. for top pair production and decay, $e^+ e^- \to t \bar t$ with decay $t \to W^+ b$, and subsequent leptonic decay of the $W$ as in $W^+ \to \mu^+ \nu_\mu$: \begin{code} process eett = e1, E1 => t, tbar process t_dec = t => Wp, b process W_dec = Wp => E2, n2 unstable t (t_dec) unstable Wp (W_dec) sqrts = 500 simulate (eett) { n_events = 1 } \end{code} Note that in this case the final state in the event file will consist of $\bar t b \mu^+ \nu_\mu$ because the anti-top is not decayed. If more than one decay process is being specified like in \begin{code} process eeww = e1, E1 => Wp, Wm process w_dec1 = Wp => E2, n2 process w_dec2 = Wp => E3, n3 unstable Wp (w_dec1, w_dec2) sqrts = 500 simulate (eeww) { n_events = 100 } \end{code} then \whizard\ takes the integrals of the specified decay processes and distributes the decays statistically according to the calculated branching ratio. Note that this might not be the true branching ratios if decay processes are missing, or loop corrections to partial widths give large(r) deviations. In the calculation of the code above, \whizard\ will issue an output like \begin{code} | Unstable particle W+: computed branching ratios: | w_dec1: 5.0018253E-01 mu+, numu | w_dec2: 4.9981747E-01 tau+, nutau | Total width = 4.5496085E-01 GeV (computed) | = 2.0490000E+00 GeV (preset) | Decay options: helicity treated exactly \end{code} So in this case, \whizard\ uses 50 \% muonic and 50 \% tauonic decays of the positively charged $W$, while the $W^-$ appears directly in the event file. \whizard\ shows the difference between the preset $W$ width from the physics model file and the value computed from the two decay channels. Note that a particle in a \sindarin\ input script can be also explictly marked as being stable, using the \begin{code} stable \end{code} constructor for the particle \ttt{}. \subsubsection{Resetting branching fractions} \label{sec:br-reset} As described above, decay processes that appear in a simulation must first be integrated by the program, either explicitly via the \verb|integrate| command, or implicitly by \verb|unstable|. In either case, \whizard\ will use the computed partial widths in order to determine branching fractions. In the spirit of a purely leading-order calculation, this is consistent. However, it may be desired to rather use different branching-fraction values for the decays of a particle, for instance, NLO-corrected values. In fact, after \whizard\ has integrated any process, the integration result becomes available as an ordinary \sindarin\ variable. For instance, if a decay process has the ID \verb|h_bb|, the integral of this process -- the partial width, in this case -- becomes the variable \verb|integral(h_bb)|. This variable may be reset just like any other variable: \begin{code} integral(h_bb) = 2.40e-3 GeV \end{code} The new value will be used for all subsequent Higgs branching-ratio calculations and decays, if an unstable Higgs appears in a process for simulation. \subsubsection{Spin correlations in decays} \label{sec:spin-correlations} By default, \whizard\ applies full spin and color correlations to the factorized processes, so it keeps both color and spin coherence between productions and decays. Correlations between decay products of distinct unstable particles in the same event are also fully retained. The program sums over all intermediate quantum numbers. Although this approach obviously yields the optimal description with the limits of production-decay factorization, there is support for a simplified handling of particle decays. Essentially, there are four options, taking a decay \ttt{W\_ud}: $W^-\to \bar u d$ as an example: \begin{enumerate} \item Full spin correlations: \verb|unstable Wp (W_ud)| \item Isotropic decay: \verb|unstable Wp (W_ud) { ?isotropic_decay = true }| \item Diagonal decay matrix: \verb|unstable Wp (W_ud) { ?diagonal_decay = true }| \item Project onto specific helicity: \verb|unstable Wp (W_ud) { decay_helicity = -1 }| \end{enumerate} Here, the isotropic option completely eliminates spin correlations. The diagonal-decays option eliminates just the off-diagonal entries of the $W$ spin-density matrix. This is equivalent to a measurement of spin before the decay. As a result, spin correlations are still present in the classical sense, while quantum coherence is lost. The definite-helicity option is similar and additional selects only the specified helicity component for the decaying particle, so its decay distribution assumes the shape for an accordingly polarized particle. All options apply in the rest frame of the decaying particle, with the particle's momentum as the quantization axis. \subsubsection{Automatic decays} A convenient option is if the user did not have to specify the decay mode by hand, but if they were generated automatically. \whizard\ does have this option: the flag \ttt{?auto\_decays} can be set to \ttt{true}, and is taking care of that. In that case the list for the decay processes of the particle marked as unstable is left empty (we take a $W^-$ again as example): \begin{code} unstable Wm () { ?auto_decays = true } \end{code} \whizard\ then inspects at the local position within the \sindarin\ input file where that \ttt{unstable} statement appears the masses of all the particles of the active physics model in order to determine which decays are possible. It then calculates their partial widths. There are a few options to customize the decays. The integer variable \ttt{auto\_decays\_multiplicity} allows to set the maximal multiplicity of the final states considered in the auto decay option. The defaul value of that variable is \ttt{2}; please be quite careful when setting this to values larger than that. If you do so, the flag \ttt{?auto\_decays\_radiative} allows to specify whether final states simply containing additional resolved gluons or photons are taken into account or not. For the example above, you almost hit the PDG value for the $W$ total width: \begin{code} | Unstable particle W-: computed branching ratios: | decay_a24_1: 3.3337068E-01 d, ubar | decay_a24_2: 3.3325864E-01 s, cbar | decay_a24_3: 1.1112356E-01 e-, nuebar | decay_a24_4: 1.1112356E-01 mu-, numubar | decay_a24_5: 1.1112356E-01 tau-, nutaubar | Total width = 2.0478471E+00 GeV (computed) | = 2.0490000E+00 GeV (preset) | Decay options: helicity treated exactly \end{code} \subsubsection{Future shorter notation for decays} {\color{red} In an upcoming \whizard\ version there will be a shorter and more concise notation already in the process definition for such decays, which, however, is current not yet implemented. The two first examples above will then be shorter and have this form:} \begin{code} process wj = u, gl => (Wp => E1, n1), d \end{code} {\color{red} as well as } \begin{code} process eett = e1, E1 => (t => (Wp => E2, n2), b), tbar \end{code} %%%%% \subsection{Event formats} As mentioned above, the internal \whizard\ event format is a machine-dependent event format. There are a series of human-readable ASCII event formats that are supported: very verbose formats intended for debugging, formats that have been agreed upon during the Les Houches workshops like LHA and LHEF, or formats that are steered through external packages like HepMC. More details about event formats can be found in Sec.~\ref{sec:eventformats}. %%%%%%%%%%%%%%% \section{Analysis and Visualization} \label{sec:analysis} \sindarin\ natively supports basic methods of data analysis and visualization which are frequently used in high-energy physics studies. Data generated during script execution, in particular simulated event samples, can be analyzed to evaluate further observables, fill histograms, and draw two-dimensional plots. So the user does not have to rely on his/her own external graphical analysis method (like e.g. \ttt{gnuplot} or \ttt{ROOT} etc.), but can use methods that automatically ship with \whizard. In many cases, the user, however, clearly will use his/her own analysis machinery, especially experimental collaborations. In the following sections, we first summarize the available data structures, before we consider their graphical display. \subsection{Observables} Analyses in high-energy physics often involve averages of quantities other than a total cross section. \sindarin\ supports this by its \ttt{observable} objects. An \ttt{observable} is a container that collects a single real-valued variable with a statistical distribution. It is declared by a command of the form \begin{quote} \begin{footnotesize} \ttt{observable \emph{analysis-tag}} \end{footnotesize} \end{quote} where \ttt{\emph{analysis-tag}} is an identifier that follows the same rules as a variable name. Once the observable has been declared, it can be filled with values. This is done via the \ttt{record} command: \begin{quote} \begin{footnotesize} \ttt{record \emph{analysis-tag} (\emph{value})} \end{footnotesize} \end{quote} To make use of this, after values have been filled, we want to perform the actual analysis and display the results. For an observable, these are the mean value and the standard deviation. There is the command \ttt{write\_analysis}: \begin{quote} \begin{footnotesize} \ttt{write\_analysis (\emph{analysis-tag})} \end{footnotesize} \end{quote} Here is an example: \begin{quote} \begin{footnotesize} \begin{verbatim} observable obs record obs (1.2) record obs (1.3) record obs (2.1) record obs (1.4) write_analysis (obs) \end{verbatim} \end{footnotesize} \end{quote} The result is displayed on screen: \begin{quote} \begin{footnotesize} \begin{verbatim} ############################################################################### # Observable: obs average = 1.500000000000E+00 error[abs] = 2.041241452319E-01 error[rel] = 1.360827634880E-01 n_entries = 4 \end{verbatim} \end{footnotesize} \end{quote} \subsection{The analysis expression} \label{subsec:analysis} The most common application is the computation of event observables -- for instance, a forward-backward asymmetry -- during simulation. To this end, there is an \ttt{analysis} expression, which behaves very similar to the \ttt{cuts} expression. It is defined either globally \begin{quote} \begin{footnotesize} \ttt{analysis = \emph{logical-expr}} \end{footnotesize} \end{quote} or as a local option to the \ttt{simulate} or \ttt{rescan} commands which generate and handle event samples. If this expression is defined, it is not evaluated immediately, but it is evaluated once for each event in the sample. In contrast to the \ttt{cuts} expression, the logical value of the \ttt{analysis} expression is discarded; the expression form has been chosen just by analogy. To make this useful, there is a variant of the \ttt{record} command, namely a \ttt{record} function with exactly the same syntax. As an example, here is a calculation of the forward-backward symmetry in a process \ttt{ee\_mumu} with final state $\mu^+\mu^-$: \begin{quote} \begin{footnotesize} \begin{verbatim} observable a_fb analysis = record a_fb (eval sgn (Pz) ["mu-"]) simulate (ee_mumu) { luminosity = 1 / 1 fbarn } \end{verbatim} \end{footnotesize} \end{quote} The logical return value of \ttt{record} -- which is discarded here -- is \ttt{true} if the recording was successful. In case of histograms (see below) it is true if the value falls within bounds, false otherwise. Note that the function version of \ttt{record} can be used anywhere in expressions, not just in the \ttt{analysis} expression. When \ttt{record} is called for an observable or histogram in simulation mode, the recorded value is weighted appropriately. If \ttt{?unweighted} is true, the weight is unity, otherwise it is the event weight. The \ttt{analysis} expression can involve any other construct that can be expressed as an expression in \sindarin. For instance, this records the energy of the 4th hardest jet in a histogram \ttt{pt\_dist}, if it is in the central region: \begin{quote} \begin{footnotesize} \begin{verbatim} analysis = record pt_dist (eval E [extract index 4 [sort by - Pt [select if -2.5 < Eta < 2.5 [colored]]]]) \end{verbatim} \end{footnotesize} \end{quote} Here, if there is no 4th jet in the event which satisfies the criterion, the result will be an undefined value which is not recorded. In that case, \ttt{record} evaluates to \ttt{false}. Selection cuts can be part of the analysis expression: \begin{code} analysis = if any Pt > 50 GeV [lepton] then record jet_energy (eval E [collect [jet]]) endif \end{code} Alternatively, we can specify a separate selection expression: \begin{code} selection = any Pt > 50 GeV [lepton] analysis = record jet_energy (eval E [collect [jet]]) \end{code} The former version writes all events to file (if requested), but applies the analysis expression only to the selected events. This allows for the simultaneous application of different selections to a single event sample. The latter version applies the selection to all events before they are analyzed or written to file. The analysis expression can make use of all variables and constructs that are defined at the point where it is evaluated. In particular, it can make use of the particle content and kinematics of the hard process, as in the example above. In addition to the predefined variables and those defined by the user, there are the following variables which depend on the hard process. Some of them are constants, some vary event by event: \begin{quote} \begin{tabular}{ll} integer: &\ttt{event\_index} \\ integer: &\ttt{process\_num\_id} \\ string: &\ttt{\$process\_id} \\ integer: &\ttt{n\_in}, \ttt{n\_out}, \ttt{n\_tot} \\ real: &\ttt{sqrts}, \ttt{sqrts\_hat} \\ real: &\ttt{sqme}, \ttt{sqme\_ref} \\ real: &\ttt{event\_weight}, \ttt{event\_excess} \end{tabular} \end{quote} The \ttt{process\_num\_id} is the numeric ID as used by external programs, while the process index refers to the current library. By default, the two are identical. The process index itself is not available as a predefined observable. The \ttt{sqme} and \ttt{sqme\_ref} values indicate the squared matrix element and the reference squared matrix element, respectively. The latter applies when comparing with a reference sample (the \ttt{rescan} command). \ttt{record} evaluates to a logical, so several \ttt{record} functions may be concatenated by the logical operators \ttt{and} or \ttt{or}. However, since usually the further evaluation should not depend on the return value of \ttt{record}, it is more advisable to concatenate them by the semicolon (\ttt{;}) operator. This is an operator (\emph{not} a statement separator or terminator) that connects two logical expressions and evaluates both of them in order. The lhs result is discarded, the result is the value of the rhs: \begin{quote} \begin{footnotesize} \begin{verbatim} analysis = record hist_pt (eval Pt [lepton]) ; record hist_ct (eval cos (Theta) [lepton]) \end{verbatim} \end{footnotesize} \end{quote} \subsection{Histograms} \label{sec:histogram} In \sindarin, a histogram is declared by the command \begin{quote} \begin{footnotesize} \ttt{histogram \emph{analysis-tag} (\emph{lower-bound}, \emph{upper-bound})} \end{footnotesize} \end{quote} This creates a histogram data structure for an (unspecified) observable. The entries are organized in bins between the real values \ttt{\emph{lower-bound}} and \ttt{\emph{upper-bound}}. The number of bins is given by the value of the intrinsic integer variable \ttt{n\_bins}, the default value is 20. The \ttt{histogram} declaration supports an optional argument, so the number of bins can be set locally, for instance \begin{quote} \begin{footnotesize} \ttt{histogram pt\_distribution (0 GeV, 500 GeV) \{ n\_bins = 50 \}} \end{footnotesize} \end{quote} Sometimes it is more convenient to set the bin width directly. This can be done in a third argument to the \ttt{histogram} command. \begin{quote} \begin{footnotesize} \ttt{histogram pt\_distribution (0 GeV, 500 GeV, 10 GeV)} \end{footnotesize} \end{quote} If the bin width is specified this way, it overrides the setting of \ttt{n\_bins}. The \ttt{record} command or function fills histograms. A single call \begin{quote} \begin{footnotesize} \ttt{record (\emph{real-expr})} \end{footnotesize} \end{quote} puts the value of \ttt{\emph{real-expr}} into the appropriate bin. If the call is issued during a simulation where \ttt{unweighted} is false, the entry is weighted appropriately. If the value is outside the range specified in the histogram declaration, it is put into one of the special underflow and overflow bins. The \ttt{write\_analysis} command prints the histogram contents as a table in blank-separated fixed columns. The columns are: $x$ (bin midpoint), $y$ (bin contents), $\Delta y$ (error), excess weight, and $n$ (number of entries). The output also contains comments initiated by a \verb|#| sign, and following the histogram proper, information about underflow and overflow as well as overall contents is added. \subsection{Plots} \label{sec:plot} While a histogram stores only summary information about a data set, a \ttt{plot} stores all data as $(x,y)$ pairs, optionally with errors. A plot declaration is as simple as \begin{quote} \begin{footnotesize} \ttt{plot \emph{analysis-tag}} \end{footnotesize} \end{quote} Like observables and histograms, plots are filled by the \ttt{record} command or expression. To this end, it can take two arguments, \begin{quote} \begin{footnotesize} \ttt{record (\emph{x-expr}, \emph{y-expr})} \end{footnotesize} \end{quote} or up to four: \begin{quote} \begin{footnotesize} \ttt{record (\emph{x-expr}, \emph{y-expr}, \emph{y-error})} \\ \ttt{record (\emph{x-expr}, \emph{y-expr}, \emph{y-error-expr}, \emph{x-error-expr})} \end{footnotesize} \end{quote} Note that the $y$ error comes first. This is because applications will demand errors for the $y$ value much more often than $x$ errors. The plot output, again written by \ttt{write\_analysis} contains the four values for each point, again in the ordering $x,y,\Delta y, \Delta x$. \subsection{Analysis Output} There is a default format for piping information into observables, histograms, and plots. In older versions of \whizard\ there was a first version of a custom format, which was however rather limited. A more versatile custom output format will be coming soon. \begin{enumerate} \item By default, the \ttt{write\_analysis} command prints all data to the standard output. The data are also written to a default file with the name \ttt{whizard\_analysis.dat}. Output is redirected to a file with a different name if the variable \ttt{\$out\_file} has a nonempty value. If the file is already open, the output will be appended to the file, and it will be kept open. If the file is not open, \ttt{write\_analysis} will open the output file by itself, overwriting any previous file with the same name, and close it again after data have been written. The command is able to print more than one dataset, following the syntax \begin{quote} \begin{footnotesize} \ttt{write\_analysis (\emph{analysis-tag1}, \emph{analysis-tag2}, \ldots) \{ \emph{options} \}} \end{footnotesize} \end{quote} The argument in brackets may also be empty or absent; in this case, all currently existing datasets are printed. The default data format is suitable for compiling analysis data by \whizard's built-in \gamelan\ graphics driver (see below and particularly Chap.~\ref{chap:visualization}). Data are written in blank-separated fixed columns, headlines and comments are initiated by the \verb|#| sign, and each data set is terminated by a blank line. However, external programs often require special formatting. The internal graphics driver \gamelan\ of \whizard\ is initiated by the \ttt{compile\_analysis} command. Its syntax is the same, and it contains the \ttt{write\_analysis} if that has not been separately called (which is unnecessary). For more details about the \gamelan\ graphics driver and data visualization within \whizard, confer Chap.~\ref{chap:visualization}. \item Custom format. Not yet (re-)implemented in a general form. \end{enumerate} \section{Custom Input/Output} \label{sec:I/O} \whizard\ is rather chatty. When you run examples or your own scripts, you will observe that the program echoes most operations (assignments, commands, etc.) on the standard output channel, i.e., on screen. Furthermore, all screen output is copied to a log file which by default is named \ttt{whizard.log}. For each integration run, \whizard\ writes additional process-specific information to a file \ttt{\var{tag}.log}, where \ttt{\var{tag}} is the process name. Furthermore, the \ttt{write\_analysis} command dumps analysis data -- tables for histograms and plots -- to its own set of files, cf.\ Sec.~\ref{sec:analysis}. However, there is the occasional need to write data to extra files in a custom format. \sindarin\ deals with that in terms of the following commands: \subsection{Output Files} \subsubsection{open\_out} \begin{syntax} open\_out (\var{filename}) \\ open\_out (\var{filename}) \{ \var{options} \} \end{syntax} Open an external file for writing. If the file exists, it is overwritten without warning, otherwise it is created. Example: \begin{code} open_out ("my_output.dat") \end{code} \subsubsection{close\_out} \begin{syntax} close\_out (\var{filename}) \\ close\_out (\var{filename}) \{ \var{options} \} \end{syntax} Close an external file that is open for writing. Example: \begin{code} close_out ("my_output.dat") \end{code} \subsection{Printing Data} \subsubsection{printf} \begin{syntax} printf \var{format-string-expr} \\ printf \var{format-string-expr} (\var{data-objects}) \end{syntax} Format \ttt{\var{data-objects}} according to \ttt{\var{format-string-expr}} and print the resulting string to standard output if the string variable \ttt{\$out\_file} is undefined. If \ttt{\$out\_file} is defined and the file with this name is open for writing, print to this file instead. Print a newline at the end if \ttt{?out\_advance} is true, otherwise don't finish the line. The \ttt{\var{format-string-expr}} must evaluate to a string. Formatting follows a subset of the rules for the \ttt{printf(3)} command in the \ttt{C} language. The supported rules are: \begin{itemize} \item All characters are printed as-is, with the exception of embedded conversion specifications. \item Conversion specifications are initiated by a percent (\verb|%|) sign and followed by an optional prefix flag, an optional integer value, an optional dot followed by another integer, and a mandatory letter as the conversion specifier. \item A percent sign immediately followed by another percent sign is interpreted as a single percent sign, not as a conversion specification. \item The number of conversion specifiers must be equal to the number of data objects. The data types must also match. \item The first integer indicates the minimum field width, the second one the precision. The field is expanded as needed. \item The conversion specifiers \ttt{d} and \ttt{i} are equivalent, they indicate an integer value. \item The conversion specifier \ttt{e} indicates a real value that should be printed in exponential notation. \item The conversion specifier \ttt{f} indicates a real value that should be printed in decimal notation without exponent. \item The conversion specifier \ttt{g} indicates a real value that should be printed either in exponential or in decimal notation, depending on its value. \item The conversion specifier \ttt{s} indicates a logical or string value that should be printed as a string. \item Possible prefixes are \verb|#| (alternate form, mandatory decimal point for reals), \verb|0| (zero padding), \verb|-| (left adjusted), \verb|+| (always print sign), `\verb| |' (print space before a positive number). \end{itemize} For more details, consult the \verb|printf(3)| manpage. Note that other conversions are not supported and will be rejected by \whizard. The data arguments are numeric, logical or string variables or expressions. Numeric expressions must be enclosed in parantheses. Logical expressions must be enclosed in parantheses prefixed by a question mark \verb|?|. String expressions must be enclosed in parantheses prefixed by a dollar sign \verb|$|. These forms behave as anonymous variables. Note that for simply printing a text string, you may call \ttt{printf} with just a format string and no data arguments. Examples: \begin{code} printf "The W mass is %8f GeV" (mW) int i = 2 int j = 3 printf "%i + %i = %i" (i, j, (i+j)) string $directory = "/usr/local/share" string $file = "foo.dat" printf "File path: %s/%s" ($directory, $file) \end{code} There is a related \ttt{sprintf} function, cf.~Sec.~\ref{sec:sprintf}. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{WHIZARD at next-to-leading order} \subsection{Prerequisites} A full NLO computation requires virtual matrix elements obtained from loop diagrams. Since \oMega\ cannot calculate such diagrams, external programs are used. \whizard\ has a generic interface to matrix-element generators that are BLHA-compatible. Explicit implementations exist for \gosam, \openloops\ and \recola. %%%%% \subsubsection{Setting up \gosam} The installation of \gosam\ is detailed on the HepForge page \url{https://gosam/hepforge.org}. We mention here some of the steps necessary to get it to be linked with \whizard. {\bf Bug in \gosam\ installation scripts:} In many versions of \gosam\ there is a bug in the installation scripts that is only relevant if \gosam\ is installed with superuser privileges. Then all files in \ttt{\$installdir/share/golem} do not have read privileges for normal users. These privileges must be given manually to all files in that directory. Prerequisites for \gosam\ to produce code for one-loop matrix elements are the scientific algebra program \ttt{form} and the generator of loop topologies and diagrams, \ttt{qgraf}. These can be accessed via their respective webpages \url{http://www.nikhef.nl/~form/} and \url{http://cfif.ist.utl.pt/~paulo/qgraf.html}. Note also that both \ttt{Java} and the Java runtime environment have to be installed in order for \gosam\ to properly work. Furthermore, \ttt{libtool} needs to be installed. A more convenient way to install \gosam, is the automatic installation script \url{https://gosam.hepforge.org/gosam_installer.py}. %%%%% \subsubsection{Setting up \openloops} \label{sec:openloops-setup} The installation of \openloops\ is explained in detail on the HepForge page \url{https://openloops.hepforge.org}. In the following, the main steps for usage with \whizard\ are summarized. Please note that at the moment, \openloops\ cannot be installed such that in almost all cases the explicit \openloops\ package directory has to be set via \ttt{--with-openloops=}. \openloops\ can be checked out with \begin{code} git clone https://gitlab.com/openloops/OpenLoops.git \end{code} Note that \whizard\ only supports \openloops\ version that are at least 2.1.1 or newer. Alternatively, one can use the public beta version of \openloops, which can be checked out by the command \begin{code} git clone -b public_beta https://gitlab.com/openloops/OpenLoops.git \end{code} The program can be build by running \ttt{scons} or \ttt{./scons}, a local version that is included in the \openloops\ directory. This produces the script \ttt{./openloops}, which is the main hook for the further usage of the program. \openloops\ works by downloading prebuild process libraries, which have to be installed for each individual process. This requires the file \ttt{openloops.cfg}, which should contain the following content: \begin{code} [OpenLoops] process\_repositories=public, whizard\\ compile\_extra=1 \end{code} The first line instructs \openloops\ to also look for process libraries in an additional lepton collider repository. The second line triggers the inclusion of $N+1$-particle tree-level matrix elements in the process directory, so that a complete NLO calculation including real amplitudes can be performed only with \openloops. The libraries can then be installed via \begin{code} ./openloops libinstall proc_name \end{code} A list of supported library names can be found on the \openloops\ web page. Note that a process library also includes all possible permutated processes. The process library \ttt{ppllj}, for example, can also be used to compute the matrix elements for $e^+ e^- \rightarrow q \bar{q}$ (massless quarks only). The massive case of the top quark is handled in \ttt{eett}. Additionally, there are process libraries for top and gauge boson decays, \ttt{tbw}, \ttt{vjj}, \ttt{tbln} and \ttt{tbqq}. Finally, \openloops\ can be linked to \whizard\ during configuration by including \begin{code} --enable-openloops --with-openloops=$OPENLOOPS_PATH, \end{code} where \ttt{\$OPENLOOPS\_PATH} is the directory the \openloops\ executable is located in. \openloops\ one-loop diagrams can then be used with the \sindarin\ option \begin{code} $loop_me_method = "openloops". \end{code} The functional tests which check the \openloops\ functionality require the libraries \ttt{ppllj}, \ttt{eett} and \ttt{tbw} to be installed (note that \ttt{eett} is not contained in \ttt{ppll}). During the configuration of \whizard, it is automatically checked that these two libraries, as well as the option \ttt{compile\_extra=1}, are present. \subsubsection{\openloops\ \sindarin\ flags} Several \sindarin\ options exist to control the behavior of \openloops. \begin{itemize} \item \ttt{openloops\_verbosity}:\\ Decide how much \openloops\ output is printed. Can have values 0, 1 and 2. \item \ttt{?openloops\_use\_cms}:\\ Activates the complex mass scheme. For computations with decaying resonances like the top quark or W or Z bosons, this is the preferred option to avoid gauge-dependencies. \item \ttt{openloops\_phs\_tolerance}:\\ Controls the exponent of \ttt{extra psp\_tolerance} in the BLHA interface, which is the numerical tolerance for the on-shell condition of external particles \item \ttt{openloops\_switch\_off\_muon\_yukawa}:\\ Sets the Yukawa coupling of muons to zero in order to assure agreement with \oMega, which is possibly used for other components and per default does not take $H\mu\mu$ couplings into account. \item \ttt{openloops\_stability\_log}:\\ Creates the directory \ttt{stability\_log}, which contains information about the performance of the matrix elements. Possible values are \begin{itemize} \item 0: No output (default), \item 1: On finish() call, \item 2: Adaptive, \item 3: Always \end{itemize} \item \ttt{?openloops\_use\_collier}: Use Collier as the reduction method (default true). \end{itemize} %%%%% \subsubsection{Setting up \recola} \label{sec:recola-setup} The installation of \recola\ is explained in detail on the HepForge page \url{https://recola.hepforge.org}. In the following the main steps for usage with \whizard\ are summarized. The minimal required version number of \recola\ is 1.3.0. \recola\ can be linked to \whizard\ during configuration by including \begin{code} --enable-recola \end{code} In case the \recola\ library is not in a standard path or a path accessible in the \ttt{LD\_LIBRARY\_PATH} (or \ttt{DYLD\_LIBRARY\_PATH}) of the operating system, then the option \begin{code} --with-recola=$RECOLA_PATH \end{code} can be set, where \ttt{\$RECOLA\_PATH} is the directory the \recola\ library is located in. \recola\ can then be used with the \sindarin\ option \begin{code} $method = "recola" \end{code} or any other of the matrix element methods. Note that there might be a clash of the \collier\ libraries when you have \collier\ installed both via \recola\ and via \openloops, but have compiled them with different \fortran\ compilers. %%%%% \subsection{NLO cross sections} An NLO computation can be switched on in \sindarin\ with \begin{code} process proc_nlo = in1, in2 => out1, ..., outN { nlo_calculation = }, \end{code} where the \ttt{nlo\_calculation} can be followed by a list of strings specifying the desired NLO-components to be integrated, i.e. \ttt{born}, \ttt{real}, \ttt{virtual}, \ttt{dglap}, (for hadron collisions) or \ttt{mismatch} (for the soft mismatch in resonance-aware computations) and \ttt{full}. The \ttt{full} option switches on all components and is required if the total NLO result is desired. For example, specifying \begin{code} nlo_calculation = born, virtual \end{code} will result in the computation of the Born and virtual component. The integration can be carried out in two different modes: Combined and separate integration. In the separate integration mode, each component is integrated individually, allowing for a good overview of their contributions to the total cross section and a fine tuned control over the iterations in each component. In the combined integration mode, all components are added up during integration so that the sum of them is evaluated. Here, only one integration will be displayed. The default method is the separate integration. The convergence of the integration can crucially be influenced by the presence of resonances. A better convergence is in this case achieved activating the resonance-aware FKS subtraction, \begin{code} $fks_mapping_type = "resonances". \end{code} This mode comes with an additional integration component, the so-called soft mismatch. Note that you can modify the number of iterations in each component with the multipliers: \begin{itemize} \item \ttt{mult\_call\_real} multiplies the number of calls to be used in the integration of the real component. A reasonable choice is \ttt{10.0} as the real phase-space is more complicated than the Born but the matrix elements evaluate faster than the virtuals. \item \ttt{mult\_call\_virt} multiplies the number of calls to be used in the integration of the virtual component. A reasonable choice is \ttt{0.5} to make sure that the fast Born component only contributes a negligible MC error compared to the real and virtual components. \item \ttt{mult\_call\_dglap} multiplies the number of calls to be used in the integration of the DGLAP component. \end{itemize} \subsection{Fixed-order NLO events} \label{ss:fixedorderNLOevents} Fixed-order NLO events can also be produced in three different modes: Combined weighted, combined unweighted and separated weighted. \begin{itemize} \item \textbf{Combined weighted}\\ In the combined mode, one single integration grid is produced, from which events are generated with the total NLO weight. The corresponding event file contains $N$ events with born-like kinematics and weight equal to $\mathcal{B} + \mathcal{V} + \sum_{\alpha_r} \mathcal{C}_{\alpha_r}$, where $\mathcal{B}$ is the Born matrix element, $\mathcal{V}$ is the virtual matrix element and $\mathcal{C}_{\alpha_r}$ are the subtraction terms in each singular region. For resonance-aware processes, also the mismatch value is added. Each born-like event is followed by $N_{\text{phs}}$ associated events with real kinematics, i.e. events where one additional QCD particle is present. The corresponding real matrix-elements $\mathcal{R}_\alpha$ form the weight of these events. $N_{\text{phs}}$ the number of distinct phase spaces. Two phase spaces are distinct if they share the same resonance history but have different emitters. So, two $\alpha_r$ can share the same phase space index. The combined event mode is activated by \begin{code} ?combined_nlo_integration = true ?unweighted = false ?fixed_order_nlo_events = true \end{code} Moreover, the process must be specified at next-to-leading-order in its definition using \ttt{nlo\_calculation = full}. \whizard\ then proceeds as in the usual simulation mode. I.e. it first checks whether integration grids are already present and uses them if they fit. Otherwise, it starts an integration. \item \textbf{Combined unweighted}\\ The unweighted combined events can be generated by using the \powheg\ mode, cf. also the next subsection, but disabling the additional radiation and Sudakov factors with the \ttt{?powheg\_disable\_sudakov} switch: \begin{code} ?combined_nlo_integration = true ?powheg_matching = true ?powheg_disable_sudakov = true \end{code} This will produce events with Born kinematics and unit weights (as \ttt{?unweighted} is \ttt{true} by default). The events are unweighted by using $\mathcal{B} + \mathcal{V} + \sum_{\alpha_r} (\mathcal{C}_{\alpha_r} + \mathcal{R}_{\alpha_r})$. Of course, this only works when these weights are positive over the full phase-space, which is not guaranteed for all scales and regions at NLO. However, for many processes perturbation theory works nicely and this is not an issue. \item \textbf{Separate weighted}\\ In the separate mode, grids and events are generated for each individual component of the NLO process. This method is preferable for complicated processes, since it allows to individually tune each grid generation. Moreover, the grid generation is then trivially parallelized. The event files either contain only Born kinematics with weight $\mathcal{B}$ or $\mathcal{V}$ (and mismatch in case of a resonance-aware process) or mixed Born and real kinematics for the real component like in the combined mode. However, the Born events have only the weight $\sum_{\alpha_r} \mathcal{C}_{\alpha_r}$ in this case. The separate event mode is activated by \begin{code} ?unweighted = false ?negative_weights = true ?fixed_order_nlo_events = true \end{code} Note that negative weights have to be switched on because, in contrast to the combined mode, the total cross sections of the individual components can be negative. Also, the desired component has to appear in the process NLO specification, e.g. using \ttt{nlo\_calculation = real}. \end{itemize} Weighted fixed-order NLO events are supported by any output format that supports weights like the \ttt{HepMC} format and unweighted NLO events work with any format. The output can either be written to disk or put into a FIFO to interface it to an analysis program without writing events to file. The weights in the real event output, both in the combined and separate weighted mode, are divided by a factor $N_{\text{phs}} + 1$. This is to account for the fact that we artificially increase the number of events in the output file. Thus, the sum of all event weights correctly reproduces the total cross section. \subsection{\powheg\ matching} To match the NLO computation with a parton shower, \whizard\ supports the \powheg\ matching. It generates a distribution according to \begin{align} \label{eq:powheg} \text{d}\sigma &= \text{d}\Phi_n \,{\bar{B}_{\text{s}}}\,\biggl( {\Delta_{\text{s}}}(p_T^{\text{min}}\bigr) + \text{d}\Phi_{\text{rad}}\,{\Delta_{\text{s}}}(k_{\text{T}}(\Phi_{\text{rad}})\bigr) {\frac{R_{\text{s}}}B}\biggr) \quad \text{where} \\ {\bar{B}_{\text{s}}} &= {B} + {\mathcal{V}} + \text{d}\Phi_{\text{rad}}\, {\mathcal{R}_{\text{s}}} \quad \text{and} \\ {\Delta_{\text{s}}}(p_T) &= \exp\left[- \int{\text{d}\Phi_{\text{rad}}} {\frac{R_{\text{s}}}{B}}\; \theta\left(k_T^2(\Phi_{\text{rad}}) - p_T^2\right)\right]\;. \end{align} The subscript s refers to the singular part of the real component, cf. to the next subsection. Eq.~\eqref{eq:powheg} produces either no or one additional emission. These events can then either be analyzed directly or passed on to the parton shower\footnote{E.g. \pythiaeight\ has explicit examples for \powheg\ input, see also \url{http://home.thep.lu.se/Pythia/pythia82html/POWHEGMerging.html}.} for the full simulation. You activate this with \begin{code} ?fixed_order_nlo_events = false ?combined_nlo_integration = true ?powheg_matching = true \end{code} The $p_T^{\text{min}}$ of Eq.~\eqref{eq:powheg} can be set with \ttt{powheg\_pt\_min}. It sets the minimal scale for the \powheg\ evolution and should be of order 1 GeV and set accordingly in the interfaced shower. The maximal scale is currently given by \ttt{sqrts} but should in the future be changeable with \ttt{powheg\_pt\_min}. Note that the \powheg\ event generation needs an additional grid for efficient event generation that is automatically generated during integration. Further options that steer the efficiency of this grid are \ttt{powheg\_grid\_size\_xi} and \ttt{powheg\_grid\_size\_y}. \subsection{Separation of finite and singular contributions} For both the pure NLO computations as well as the \powheg\ event generation, \whizard\ supports the partitioning of the real into finite and singular contributions with the flag \begin{code} ?nlo_use_real_partition = true \end{code} The finite contributions, which by definition should not contain soft or collinear emissions, will then integrate like a ordinary LO integration with one additional particle. Similarly, the event generation will produce only real events without subtraction terms with Born kinematics for this additional finite component. The \powheg\ event generation will also only use the singular parts. The current implementation uses the following parametrization \begin{align} R &= R_{\text{fin}} + R_{\text{sing}} \;,\\ R_{\text{sing}} &= R F(\Phi_{n+1}) \;,\\ R_{\text{fin}} &= R (1-F(\Phi_{n+1})) \;,\\ F(\Phi_{n+1}) &= \begin{cases} 1 & \text{if} \quad\exists\,(i,j)\in\mathcal{P}_{\text{FKS}}\quad \text{with} \quad \sqrt{(p_i+p_j)^2} < h + m_i + m_j \\ 0 & \text{else} \end{cases} \;. \end{align} Thus, a point is {singular ($F=1$)}, if {any} of the {FKS tuples} forms an {invariant mass} that is {smaller than the hardness scale $h$}. This parameter is controlled in \sindarin\ with \ttt{real\_partition\_scale}. This simplifies in {massless case} to \begin{align} F(\Phi_{n+1}) = \begin{cases} 1 & \text{if} \;\exists\,(i,j)\in\mathcal{P}_{\text{FKS}}\quad \text{with} \quad 2 E_i E_j (1-\cos\theta_{ij}) < h^2 \\ 0 & \text{else} \end{cases} \;. \end{align} %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \chapter{Random number generators} \label{chap:rng} \section{General remarks} \label{sec:rng} The random number generators (RNG) are one of the crucialer points of Monte Carlo calculations, hence, giving those their ``randomness''. A decent multipurpose random generator covers \begin{itemize} \item reproducibility \item large period \item fast generation \item independence \end{itemize} of the random numbers. Therefore, special care is taken for the choice of the RNGs in \whizard{}. It is stated that \whizard{} utilizes \textit{pseudo}-RNGs, which are based on one (or more) recursive algorithm(s) and start-seed(s) to have reproducible sequences of numbers. In contrast, a genuine random generator relies on physical processes. \whizard\ ships with two completely different random number generators which can be selected by setting the \sindarin\ option \begin{code} $rng_method = "rng_tao" \end{code} Although, \whizard{} sets a default seed, it is adviced to use a different one \begin{code} seed = 175368842 \end{code} note that some RNGs do not allow certain seed values (e.g. zero seed). \section{The TAO Random Number Generator} \label{sec:tao} The TAO (``The Art Of'') random number generator is a lagged Fibonacci generator based upon (signed) 32-bit integer arithmetic and was proposed by Donald E. Knuth and is implemented in the \vamp\ package. The TAO random number generator is the default RNG of \whizard{}, but can additionally be set as \sindarin\ option \begin{code} $rng_method = rng_tao \end{code} The TAO random number generators is a subtractive lagged Fibonacci generator \begin{equation*} x_{j} = \left( x_{j-k} - x_{j-L} \right) \mod 2^{30} \end{equation*} with lags $k = 100$ and $l = 37$ and period length $\rho = 2^{30} - 2$. \section{The RNGStream Generator} \label{sec:rngstream} The RNGStream \cite{L_Ecuyer:2002} was originally implemented in \cpp\ with floating point arithmetic and has been ported to \fortranOThree{}. The RNGstream can be selected by the \sindarin\ option \begin{code} $rng_method = "rng_stream" \end{code} The RNGstream supports multiple independent streams and substreams of random numbers which can be directly accessed. The main advantage of the RNGStream lies in the domain of parallelization where different worker have to access different parts of the random number stream to ensure numerical reproducibility. The RNGstream provides exactly this property with its (sub)stream-driven model. Unfortunately, the RNGStream can only be used in combination with \vamptwo{}. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \chapter{Integration Methods} \section{The Monte-Carlo integration routine: \ttt{VAMP}} \label{sec:vamp} \vamp\ \cite{Ohl:1998jn} is a multichannel extension of the \vegas\ \cite{Lepage:1980dq} algorithm. For all possible singularities in the integrand, suitable maps and integration channels are chosen which are then weighted and superimposed to build the phase space parameterization. Both grids and weights are modified in the adaption phase of the integration. The multichannel integration algorithm is implemented as a \fortranNinetyFive\ library with the task of mapping out the integrand and finding suitable parameterizations being completely delegated to the calling program (\whizard\ core in this case). This makes the actual \vamp\ library completely agnostic of the model under consideration. \section{The next generation integrator: \ttt{VAMP2}} \label{sec:vamp2} \vamptwo\ is a modern implementation of the integrator package \vamp\ written in \fortranOThree\, providing the same features. The backbone integrator is still \vegas\ \cite{Lepage:1980dq}, although implemented differently as in \vamp{}. The main advantage over \vamp\ is the overall faster integration due to the usage of \fortranOThree{}, the possible usage of different random number generators and the complete parallelization of \vegas\ and the multichannel integration. \vamptwo{} can be set by the \sindarin{} option \begin{code} $integration_method = "vamp2" \end{code} It is said that the generated grids between \vamp{} and \vamptwo{} are incompatible. \subsection{Multichannel integration} \label{sec:multi-channel} The usual matrix elements do not factorise with respect to their integration variables, thus making an direct integration ansatz with VEGAS unfavorable.\footnote{One prerequisite for the VEGAS algorithm is that the integral factorises, and such produces only the best results for those.} Instead, we apply the multichannel ansatz and let VEGAS integrate each channel in a factorising mapping. The different structures of the matrix element are separated by a partition of unity and the respective mappings, such that each structure factorise at least once. We define the mappings $\phi_i : U \mapsto \Omega$, where $U$ is the unit hypercube and $\Omega$ the physical phase space. We refer to each mapping as a \textit{channel}. Each channel then gives rise to a probability density $g_i : U \mapsto [0, \infty)$, normalised to unity \begin{equation*} \int_0^1 g_i(\phi_i^{-1}(p)) \left| \frac{\partial \phi_i^{-1}}{\partial p} \right| \mathrm{d}\mu(p) = 1, \quad g_i(\phi_i^{-1}(p)) \geq 0, \end{equation*} written for a phase space point $p$ using the mapping $\phi_i$. The \textit{a-priori} channel weights $\alpha_i$ are defined as partition of unity by $\sum_{i\in I} \alpha_i = 1$ and $0 \leq \alpha_i \leq 1$. The overall probability density $g$ of a random sample is then obtained by \begin{equation*} g(p) = \sum_{i \in I} \alpha_i g_i(\phi_i^{-1}(p)) \left| \frac{\partial \phi_i^{-1}}{\partial p} \right|, \end{equation*} which is also a non-negative and normalized probability density. We reformulate the integral \begin{equation*} I(f) = \sum_{i \in I} \alpha_i \int_\Omega g_i(\phi_i^{-1}(p)) \left| \frac{\partial \phi_i^{-1}}{\partial p} \right| \frac{f(p)}{g(p)} \mathrm{d}\mu(p). \end{equation*} The actual integration of each channel is then done by VEGAS, which shapes the $g_i$. \subsection{VEGAS} \label{sec:vegas} VEGAS is an adaptive and iterative Monte Carlo algorithm for integration using importance sampling. After each iteration, VEGAS adapts the probability density $g_i$ using information collected while sampling. For independent integration variables, the probability density factorises $g_i = \prod_{j = 1}^{d} g_{i,j}$ for each integration axis and each (independent) $g_{i,j}$ is defined by a normalised step function \begin{equation*} g_{i,j} (x_j) = \frac{1}{N\Delta x_{j,k}}, \quad x_{j,k} - \Delta x_{j,k} \leq x_{j} < x_{j,k}, \end{equation*} where the steps are $0 = x_{j, 0} < \cdots < x_{j,k} < \cdots < x_{j,N} = 1$ for each dimension $j$. The algorithm randomly selects for each dimension a bin and a position inside the bin and calculates the respective $g_{i,j}$. \subsection{Channel equivalences} \label{sec:equivalences} The automated mulitchannel phasespace configuration can lead to a surplus of degrees of freedom, e.g. for a highly complex process with a large number of channels (VBS). In order to marginalize the redundant degrees of freedom of phasespace configuration, the adaptation distribution of the grids are aligned in accordance to their phasespace relation, hence the binning of the grids is equialized. These equivalences are activated by default for \vamp{} and \vamptwo{}, but can be steered by: \begin{code} ?use_vamp_equivalences = true \end{code} Be aware, that the usage of equivalences are currently only possible for LO processes. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \chapter{Phase space parameterizations} \section{General remarks} \whizard\ as a default performs an adaptive multi-channel Monte-Carlo integration. Besides its default phase space algorithm, \ttt{wood}, to be detailed in Sec.~\ref{sec:wood}, \whizard\ contains a phase space method \ttt{phs\_none} which is a dummy method that is intended for setups of processes where no phase space integration is needed, but the program flow needs a (dummy) integrator for internal consistency. Then, for testing purposes, there is a single-channel phase space integrator, \ttt{phs\_single}. From version 2.6.0 of \whizard\ on, there is also a second implementation of the \ttt{wood} phase space algorithm, called \ttt{fast\_wood}, cf. Sec.~\ref{sec:fast_wood}, whose implementation differs technically and which therefore solves certain technical flaws of the \ttt{wood} implementation. Additionally, \whizard\ supports single-channel, flat phase-space using RAMBO (on diet). %%% \section{The flat method: \ttt{rambo}} \label{sec:rambo} The \ttt{RAMBO} algorithm produces a flat phase-space with constant volume for massless particles. \ttt{RAMBO} was originally published in \cite{Kleiss:1985gy}. We use the slim version, called \ttt{RAMBO} on diet, published in \cite{Platzer:2013esa}. The overall weighting efficiency of the algorithm is unity for massless final-state particles. For the massive case, the weighting efficiency of unity will decrease rendering the algorithm less efficient. But in most cases, the invariants are in regions of phase space where they are much larger than the masses of the final-state particles. We provide the \ttt{RAMBO} mainly for cross checking our implementation and do not recommend it for real world application, even though it can be used as one. The \ttt{RAMBO} method becomes useful as a fall-back option if the standard algorithm fails for physical reasons, see, e.g., Sec.~\ref{sec:ps_anomalous}. %%% \section{The default method: \ttt{wood}} \label{sec:wood} The \ttt{wood} algorithm classifies different phase space channels according to their importance for a full scattering or decay process following heuristic rules. For that purpose, \whizard\ investigates the kinematics of the different channels depending on the total center-of-mass energy (or the mass of the decaying particle) and the masses of the final-state particles. The \ttt{wood} phase space inherits its name from the naming schemes of structures of increasing complexities, namely trees, forests and groves. Simply stated, a phase-space forest is a collection of phase-space trees. A phase-space tree is a parameterization for a valid channel in the multi-channel adaptive integration, and each variable in the a tree corresponds to an integration dimension, defined by an appropriate mapping of the $(0,1)$ interval of the unit hypercube to the allowed range of the corresponding integration variable. The whole set of these phase-space trees, collected in a phase-space forest object hence contains all parameterizations of the phase space that \whizard\ will use for a single hard process. Note that processes might contain flavor sums of particles in the final state. As \whizard\ will use the same phase space parameterization for all channels for this set of subprocesses, all particles in those flavor sums have to have the same mass. E.g. in the definition of a "light" jet consisting of the first five quarks and antiquarks, \begin{code} alias jet = u:d:s:c:b:U:D:S:C:B \end{code} all quarks including strange, charm and bottom have to be massless for the phase-space integration. \whizard\ can treat processes with subprocesses having final-state particles with different masses in an "additive" way, where each subprocess will become a distinct component of the whole process. Each process component will get its own phase-space parameterization, such that they can allow for different masses. E.g. in a 4-flavor scheme for massless $u,d,s,c$ quarks one can write \begin{code} alias jet = u:d:s:c:U:D:S:C process eeqq = e1, E1 => (jet, jet) + (b, B) \end{code} In that case, the parameterizations will be for massless final state quarks for the first subprocess, and for massive $b$ quarks for the second subprocess. In general, for high-energy lepton colliders, the difference would not matter much, but performing the integration e.g. for $\sqrt{s} = 11$ GeV, the difference will be tremendous. \whizard\ avoids inconsistent phase-space parameterizations in that way. As a multi-particle process will contain hundred or thousands of different channels, the different integration channels (trees) are grouped into so called {\em groves}. All channels/trees in the same grove share a common weight for the phase-space integration, following the assumption that they are related by some approximate symmetry. The \vamp\ adaptive multi-channel integrator (cf. Sec.~\ref{sec:vamp}) allows for equivalences between different integration channels. This means that trees/channels that are related by an exact symmetry are connected by an array of these equivalences. The phase-space setup, i.e. the detailed structure of trees and forests, are written by \whizard\ into a phase-space file that has the same name as the corresponding process (or process component) with the suffix \ttt{.phs}. For the \ttt{wood} phase-space method this file is written by a \fortran\ module which constructs a similar tree-like structure as the directed acyclical graphs (DAGs) in the \oMega\ matrix element generator but in a less efficient way. In some very rare cases with externally generated models (cf. Chapter~\ref{chap:extmodels}) the phase-space generation has been reported to fail as \whizard\ could not find a valid phase-space channel. Such pathological cases cannot occur for the hard-coded model implementations inside \whizard. They can only happen if there are in principle two different Feynman diagrams contributing to the same phase-space channel and \whizard\ considers the second one as extremely subleading (and would hence drop it). If for some reason however the first Feynman diagram is then absent, no phase-space channel could be found. This problem cannot occur with the \ttt{fast\_wood} implementation discussed in the next section, cf.~\ref{sec:fast_wood}. The \ttt{wood} algorithms orders the different groves of phase-space channels according to a heuristic importance depending on the kinematic properties of the different phase-space channels in the groves. A phase-space (\ttt{.phs}) file looks typically like this: \begin{code} process sm_i1 ! List of subprocesses with particle bincodes: ! 8 4 1 2 ! e+ e- => mu+ mu- ! 8 4 1 2 md5sum_process = "1B3B7A30C24664A73D3D027382CFB4EF" md5sum_model_par = "7656C90A0B2C4325AD911301DACF50EB" md5sum_phs_config = "6F72D447E8960F50FDE4AE590AD7044B" sqrts = 1.000000000000E+02 m_threshold_s = 5.000000000000E+01 m_threshold_t = 1.000000000000E+02 off_shell = 2 t_channel = 6 keep_nonresonant = T ! Multiplicity = 2, no resonances, 0 logs, 0 off-shell, s-channel graph grove #1 ! Channel #1 tree 3 ! Multiplicity = 1, 1 resonance, 0 logs, 0 off-shell, s-channel graph grove #2 ! Channel #2 tree 3 map 3 s_channel 23 ! Z \end{code} The first line contains the process name, followed by a list of subprocesses with the external particles and their binary codes. Then there are three lines of MD5 check sums, used for consistency checks. \whizard\ (unless told otherwise) will check for the existence of a phase-space file, and if the check sum matches, it will reuse the existing file and not generate it again. Next, there are several kinematic parameters, namely the center-of-mass energy of the process, \ttt{sqrts}, and two mass thresholds, \ttt{m\_threshold\_s} and \ttt{m\_threshold\_t}. The latter two are kinematical thresholds, below which \whizard\ will consider $s$-channel and $t$-channel-like kinematic configurations as effectively massless, respectively. The default values shown in the example have turned out to be optimal values for Standard Model particles. The two integers \ttt{off\_shell} and \ttt{t\_channel} give the number of off-shell lines and of $t$-channel lines that \whizard\ will allow for finding valid phase-space channels, respectively. This neglects extremley multi-peripheral background-like diagram constellations which are very subdominamnt compared to resonant signal processes. The final flag specifies whether \whizard\ will keep non-resonant phase-space channels (default), or whether it will focus only on resonant situations. After this header, there is a list of all groves, i.e. collections of phase-space channels which are connected by quasi-symmetries, together with the corresponding multiplicity of subchannels in that grove. In the phase-space file behind the multiplicity, \whizard\ denotes the number of (massive) resonances, logarithmcally enhanced kinematics (e.g. collinear regions), and number of off-shell lines, respectively. The final entry in the grove header notifies whether the diagrams in that grove have $s$-channel topologies, or count the number of corresponding $t$-channel lines. Another example is shown here, \begin{code} ! Multiplicity = 3, no resonances, 2 logs, 0 off-shell, 1 t-channel line grove #1 ! Channel #1 tree 3 12 map 3 infrared 22 ! A map 12 t_channel 2 ! u ! Channel #2 tree 3 11 map 3 infrared 22 ! A map 11 t_channel 2 ! u ! Channel #3 tree 3 20 map 3 infrared 22 ! A map 20 t_channel 2 ! u ! Channel #4 tree 3 19 map 3 infrared 22 ! A map 19 t_channel 2 ! u \end{code} where \whizard\ notifies in different situations a photon exchange as \ttt{infrared}. So it detects a possible infrared singularity where a particle can become arbitrarily soft. Such a situation can tell the user that there might be a cut necessary in order to get a meaningful integration result. The phase-space setup that is generated and used by the \ttt{wood} phase-space method can be visualized using the \sindarin\ option \begin{code} ?vis_channels = true \end{code} The \ttt{wood} phase-space method can be invoked with the \sindarin\ command \begin{code} $phs_method = "wood" \end{code} Note that this line is unnecessary, as \ttt{wood} is the default phase-space method of \whizard. %%%%% \section{A new method: \ttt{fast\_wood}} \label{sec:fast_wood} This method (which is available from version 2.6.0 on) is an alternative implementation of the \ttt{wood} phase-space algorithm. It uses the recursive structures inside the \oMega\ matrix element generator to generate all the structures needed for the different phase-space channels. In that way, it can avoid some of the bottlenecks of the \ttt{wood} \fortran\ implementation of the algorithm. On the other hand, it is only available if the \oMega\ matrix element generator has been enabled (which is the default for \whizard). The \ttt{fast\_wood} method is then invoked via \begin{code} ?omega_write_phs_output = true $phs_method = "fast_wood" \end{code} The first option is necessary in order to tell \oMega\ to write out the output needed for the \ttt{fast\_wood} parser in order to generate the phase-space file. This is not enabled by default in order not to generate unnecessary files in case the default method \ttt{wood} is used. So the \ttt{fast\_wood} implementation of the \ttt{wood} phase-space algorithm parses the tree-like represenation of the recursive set of one-particle off-shell wave functions that make up the whole amplitude inside \oMega\ in the form of a directed acyclical graph (DAG) in order to generate the phase-space (\ttt{.phs}) file (cf. Sec.~\ref{sec:wood}). In that way, the algorithm makes sure that only phase-space channels are generated for which there are indeed (sub)amplitudes in the matrix elements, and this also allows to exclude vetoed channels due to restrictions imposed on the matrix elements from the phase-space setup (cf. next Sec.~\ref{sec:ps_restrictions}). %%%%% \section{Phase space respecting restrictions on subdiagrams} \label{sec:ps_restrictions} The \fortran\ implementation of the \ttt{wood} phase-space does not know anything about possible restrictions that maybe imposed on the \oMega\ matrix elements, cf. Sec.~\ref{sec:process options}. Consequently, the \ttt{wood} phase space also generates phase-space channels that might be absent when restrictions are imposed. This is not a principal problem, as in the adaptation of the phase-space channels \whizard's integrator \vamp\ will recognize that there is zero weight in that channel and will drop the channel (stop sampling in that channel) after some iterations. However, this is a waste of ressources as it is in principle known that this channel is absent. Using the \ttt{fast\_wood} phase-space algorithm (cf. Sec.~\ref{sec:fast_wood} will take restrictions into account, as \oMega\ will not generate trees for channels that are removed with the restrictions command. So it advisable for the user in the case of very complicated processes with restrictions to use the \ttt{fast\_wood} phase-space method to make \whizard\ generation and integration of the phase space less cumbersome. %%%%% \section{Phase space for processes forbidden at tree level} \label{sec:ps_anomalous} The phase-space generators \ttt{wood} and \ttt{fast\_wood} are intended for tree-level processes with their typical patterns of singularities, which can be read off from Feynman graphs. They can and should be used for loop-induced or for externally provided matrix elements as long as \whizard\ does not provide a dedicated phase-space module. Some scattering processes do not occur at tree level but become allowed if loop effects are included in the calculation. A simple example is the elastic QED process \begin{displaymath} A\quad A \longrightarrow A\quad A \end{displaymath} which is mediated by a fermion loop. Similarly, certain applications provide externally provided or hand-taylored matrix-element code that replaces the standard \oMega\ code. Currently, \whizard's phase-space parameterization is nevertheless tied to the \oMega\ generator, so for tree-level forbidden processes the phase-space construction process will fail. There are two possible solutions for this problem: \begin{enumerate} \item It is possible to provide the phase-space parameterization information externally, by supplying an appropriately formatted \ttt{.phs} file, bypassing the automatic algorithm. Assuming that this phase-space file has been named \ttt{my\_phase\_space.phs}, the \sindarin\ code should contain the following: \begin{code} ?rebuild_phase_space = false $phs_file = "my_phase_space.phs" \end{code} Regarding the contents of this file, we recommend to generate an appropriate \ttt{.phs} for a similar setup, using the standard algorithm. The generated file can serve as a template, which can be adapted to the particular case. In detail, the \ttt{.phs} file consists of entries that specify the process, then a standard header which contains MD5 sums and such -- these variables must be present but their values are irrelevant for the present case --, and finally at least one \ttt{grove} with \ttt{tree} entries that specify the parameterization. Individual parameterizations are built from the final-state and initial-state momenta (in this order) which we label in binary form as $1,2,4,8,\dots$. The actual tree consists of iterative fusions of those external lines. Each fusion is indicated by the number that results from adding the binary codes of the external momenta that contribute to it. For instance, a valid phase-space tree for the process $AA\to AA$ is given by the simple entry \begin{code} tree 3 \end{code} which indicates that the final-state momenta $1$ and $2$ are combined to a fusion $1+2=3$. The setup is identical to a process such as $e^+e^-\to\mu^+\mu^-$ below the $Z$ threshold. Hence, we can take the \ttt{.phs} file for the latter process, replace the process tag, and use it as an external phase-space file. \item For realistic applications of \whizard\ together with one-loop matrix-element providers, the actual number of final-state particles may be rather small, say $2,3,4$. Furthermore, one-loop processes which are forbidden at tree level do not contain soft or collinear singularities. In this situation, the \ttt{RAMBO} phase-space integration method, cf.\ Sec.~\ref{sec:rambo} is a viable alternative which does not suffer from the problem. \end{enumerate} %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \chapter{Methods for Hard Interactions} \label{chap:hardint} The hard interaction process is the core of any physics simulation within an MC event generator. One tries to describe the dominant particle interaction in the physics process of interest at a given order in perturbation theory, thereby making use of field-theoretic factorization theorems, especially for QCD, in order to separate non-perturbative physics like parton distribution functions (PDFs) or fragmentation functions from the perturbative part. Still, it is in many cases not possible to describe the perturbative part completely by means of fixed-order hard matrix elements: in soft and/or collinear regions of phase space, multiple emission of gluons and quarks (in general QCD jets) and photons necessitates a resummation, as large logarithms accompany the perturbative coupling constants and render fixed-order perturbation theory unreliable. The resummation of these large logarithms can be done analytically or (semi-)numerically, however, usually only for very inclusive quantities. At the level of exclusive events, these phase space regions are the realm of (QCD and also QED) parton showers that approximate multi-leg matrix elements from the hard perturbative into to the soft-/collinear regime. The hard matrix elements are then the core building blocks of the physics description inside the MC event generator. \whizard\ generates these hard matrix elements at tree-level (or sometimes for loop-induced processes using effective operators as insertions) as leading-order processes. This is done by the \oMega\ subpackage that is automatically called by \whizard. Besides these physical matrix elements, there exist a couple of methods to generate dummy matrix elements for testing purposes, or for generating beam profiles and using them with externally linked special matrix elements. Especially for one-loop processes (next-to-leading order for tree-allowed processes or leading-order for loop-induced processes), \whizard\ allows to use matrix elements from external providers, so called OLP programs (one-loop providers). Of course, all of these external packages can also generate tree-level matrix elements, which can then be used as well in \whizard. We start the discussion with the two different options for test matrix elements, internal test matrix elements with no generated compiled code in Sec.~\ref{sec:test_me} and so called template matrix elements with actual \fortran\ code that is compiled and linked, and can also be modified by the user in Sec.~\ref{sec:template_me}. Then, we move to the main matrix element method by the matrix element generator \oMega\ in Sec.~\ref{sec:omega_me}. Matrix elements from the external matrix element generators are discussed in the order of which interfaces for the external tools have been implemented: \gosam\ in Sec.~\ref{sec:gosam_me}, \openloops\ in Sec.~\ref{sec:openloops_me}, and \recola\ in Sec.~\ref{sec:recola_me}. %%%%% \section{Internal test matrix elements} \label{sec:test_me} This method is merely for internal consistency checks inside \whizard, and is not really intended to be utilized by the user. The method is invoked by \begin{code} $method = "unit_test" \end{code} This particular method is only applicable for the internal test model \ttt{Test.mdl}, which just contains a Higgs boson and a top quark. Technically, it will also works within model specifications for the Standard Model, or the Minimal Supersymmetric Standard Model (MSSM), or all models which contain particles named as \ttt{H} and \ttt{t} with PDG codes 25 and 6, respectively. So, the models \ttt{QED} and {QCD} will not work. Irrespective of what is given in the \sindarin\ file as a scattering input process, \whizard\ will always take the process \begin{code} model = SM process = H, H => H, H \end{code} or for the test model: \begin{code} model = Test process = s, s => s, s \end{code} as corresponding process. (This is the same process, just with differing nomenclature in the different models). No matrix element code is generated and compiled, the matrix element is completely internal, included in the \whizard\ executable (or library), with a unit value for the squared amplitude. The integration will always be performed for this particularly process, even if the user provides a different process for that method. Hence, the result will always be the volume of the relativistic two-particle phase space. The only two parameters that influence the result are the collider energy, \ttt{sqrts}, and the mass of the Higgs particle with PDG code 25 (this mass parameter can be changed in the model \ttt{Test} as \ttt{ms}, while it would be \ttt{mH} in the Standard Model \ttt{SM}. It is also possible to use a test matrix element, again internal, for decay processes, where again \whizard\ will take a predefined process: \begin{code} model = SM process = H => t, tbar \end{code} in the \ttt{SM} model or \begin{code} model = Test process = s => f, fbar \end{code} Again, this is the same process with PDG codes $25 \to 6 \; -6$ in the corresponding models. Note that in the model \ttt{SM} the mass of the quark is set via the variable \ttt{mtop}, while it is \ttt{mf} in the model \ttt{Test}. Besides the fact that the user always gets a fixed process and cannot modify any matrix element code by hand, one can do all things as for a normal process like generating events, different weights, testing rebuild flags, using different setups and reweight events accordingly. Also factorized processes with production and decay can be tested that way. In order to avoid confusion, it is highly recommended to use this method \ttt{unit\_test} only with the test model setup, model \ttt{Test}. On the technical side, the method \ttt{unit\_test} does not produce a process library (at least not an externally linked one), and also not a makefile in order to modify any process files (which anyways do not exist for that method). Except for the logfiles and the phase space file, all files are internal. %%%%% \section{Template matrix elements} \label{sec:template_me} Much more versatile for the user than the previous matrix element method in~\ref{sec:test_me}, are two different methods with constant template matrix elements. These are written out as \fortran\ code by the \whizard\ main executable (or library), providing an interface that is (almost) identical to the matrix element code produced by the \oMega\ generator (cf. the next section, Sec.~\ref{sec:omega_me}. There are actually two different methods for that purpose, providing matrix elements with different normalizations: \begin{code} $method = "template" \end{code} generates matrix elements which give after integration over phase space exactly one. Of course, for multi-particle final states the integration can fluctuate numerically and could then give numbers that are only close to one but not exactly one. Furthermore, the normalization is not exact if any of the external particles have non-zero masses, or there are any cuts involved. But otherwise, the integral from \whizard\ should give unity irrespective of the number of final state particles. In contrast to this, the second method, \begin{code} $method = "template_unity" \end{code} gives a unit matrix elements, or rather a matrix element that contains helicity and color averaging factors for the initial state and the square root of the factorials of identical final state particles in the denominator. Hence, integration over the final state momentum configuration gives a cross section that corresponds to the volume of the $n$-particle final state phase space, divided by the corresponding flux factor, resulting in \begin{equation} \sigma(s, 2 \to 2,0) = \frac{3.8937966\cdot 10^{11}}{16\pi} \cdot \frac{1}{s \text{[GeV]}^2} \; \text{fb} \end{equation} for the massless case and \begin{equation} \sigma(s, 2 \to 2,m_i) = \frac{3.8937966\cdot 10^{11}}{16\pi} \cdot \sqrt{\frac{\lambda (s,m_3^2,m_4^2)}{\lambda (s,m_1^2,m_2^2)}} \cdot \frac{1}{s \text{[GeV]}^2} \; \text{fb} \end{equation} for the massive case. Here, $m_1$ and $m_2$ are the masses of the incoming, $m_3$ and $m_4$ the masses of the outgoing particles, and $\lambda(x,y,z) = x^2 + y^2 + z^2 - 2xy - 2xz - 2yz$. For the general massless case with no cuts, the integral should be exactly \begin{equation} \sigma(s, 2\to n, 0) = \frac{(2\pi)^4}{2 s}\Phi_n(s) = \frac{1}{16\pi s}\,\frac{\Phi_n(s)}{\Phi_2(s)}, \end{equation} where the volume of the massless $n$-particle phase space is given by \begin{equation}\label{phi-n} \Phi_n(s) = \frac{1}{4(2\pi)^5} \left(\frac{s}{16\pi^2}\right)^{n-2} \frac{1}{(n-1)!(n-2)!}. \end{equation} For $n\neq2$ the phase space volume is dimensionful, so the units of the integral are $\fb\times\GeV^{2(n-2)}$. (Note that for physical matrix elements this is compensated by momentum factors from wave functions, propagators, vertices and possibly dimensionful coupling constants, but here the matrix element is just equal to unity.) Note that the phase-space integration for the \ttt{template} and \ttt{template\_unity} matrix element methods is organized in the same way as it would be for the real $2\to n$ process. Since such a phase space parameterization is not optimized for the constant matrix element that is supplied instead, good convergence is not guaranteed. (Setting \ttt{?stratified = true} may be helpful here.) The possibility to call a dummy matrix element with this method allows to histogram spectra or structure functions: Choose a trivial process such as $uu\to dd$, select the \ttt{template\_unity} method, switch on structure functions for one (or both) beams, and generate events. The distribution of the final-state mass squared reflects the $x$ dependence of the selected structure function. Furthermore, the constant in the source code of the unit matrix elements can be easily modified by the user with their \fortran\ code in order to study customized matrix elements. Just rerun \whizard\ with the \ttt{--recompile} option after the modification of the matrix element code. Both methods, \ttt{template} and \ttt{template\_unity} will also work even if no \ocaml\ compiler is found or used and consequently the \oMega\ matrix elemente generator (cf. Sec.~\ref{sec:omega_me} is disable. The methods produce a process library for their corresponding processes, and a makefile, by which \whizard\ steers compilation and linking of the process source code. %%%%% \section{The O'Mega matrix elements} \label{sec:omega_me} \oMega\ is a subpackage of \whizard, written in \ocaml, which can produce matrix elements for a wide class of implemented physics models (cf. Sec.~\ref{sec:smandfriends} and \ref{sec:bsmmodels} for a list of all implemented physics models), and even almost arbitrary models when using external Lagrange level tools, cf. Chap.~\ref{chap:extmodels}. There are two different variants for matrix elements from \oMega: the first one is invoked as \begin{code} $method = "omega" \end{code} and is the default method for \whizard. It produces matrix element as \fortran\ code which is then compiled and linked. An alternative method, which for the moment is only available for the Standard Model and its variants as well models which are quite similar to the SM, e.g. the Two-Higgs doublet model or the Higgs-singlet extension. This method is taken when setting \begin{code} $method = "ovm" \end{code} The acronym \ttt{ovm} stands for \oMega\ Virtual Machine (OVM). The first (default) method (\ttt{omega}) of \oMega\ matrix elements produces \fortran\ code for the matrix elements,that is compiled by the same compiler with which \whizard\ has been compiled. The OVM method (\ttt{ovm}) generates an \ttt{ASCII} file with so called op code for operations. These are just numbers which tell what numerical operations are to be performed on momenta, wave functions and vertex expression in order to yield a complex number for the amplitude. The op codes are interpreted by the OVM in the same as a Java Virtual Machine. In both cases, a compiled \fortran\ is generated which for the \ttt{omega} method contains the full expression for the matrix element as \fortran\ code, while for the \ttt{ovm} method this is the driver file of the OVM. Hence, for the \ttt{ovm} method this file always has roughly the same size irrespective of the complexity of the process. For the \ttt{ovm} method, there will also be the \ttt{ASCII} file that contains the op codes, which has a name with an \ttt{.hbc} suffix: \ttt{.hbc}. For both \oMega\ methods, there will be a process library created as for the template matrix elements (cf. Sec.~\ref{sec:template_me}) named \ttt{default\_lib.f90} which can be given a user-defined name using the \ttt{library = ""} command. Again, for both methods \ttt{omega} and \ttt{ovm}, a makefile named \ttt{\_lib.makefile} is generated by which \whizard\ steers compilation, linking and clean-up of the process sources. This makefile can handily be adapted by the user in case she or he wants to modify the source code for the process (in the case of the source code method). Note that \whizard's default ME method via \oMega\ allows the user to specify many different options either globally for all processes in the \sindarin, or locally for each process separately in curly brackets behind the corresponding process definition. Examples are \begin{itemize} \item Restrictions for the matrix elements like the exclusion of intermediate resonances, the appearance of specific vertices or coupling constants in the matrix elments. For more details on this cf. Sec.~\ref{subsec:restrictions}. \item Choice of a specific scheme for the width of massive intermediate resonances, whether to use constant width, widths only in $s$-channel like kinematics (this is the default), a fudged-width scheme or the complex-mass scheme. The latter is actually steered as a specific scheme of the underlying model and not with a specific \oMega\ command. \item Choice of the electroweak gauge for the amplitude. The default is the unitary gauge. \end{itemize} With the exception of the restrictions steered by the \ttt{\$restrictions = ""} string expression, these options have to be set in their specific \oMega\ syntax verbatim via the string command \ttt{\$omega\_flags = ""}. %%%%% \section{Interface to GoSam} \label{sec:gosam_me} One of the supported methods for automated matrix elements from external providers is for the \gosam\ package. This program package which is a combination of \python\ scripts and \fortran\ libraries, allows both for tree and one-loop matrix elements (which is leading or next-to-leading order, depending on whether the corresponding process is allowed at the tree level or not). In principle, the advanced version of \gosam\ also allows for the evaluation of two-loop virtual matrix elements, however, this is currently not supported in \whizard. This method is invoked via the command \begin{code} $method = "gosam" \end{code} Of course, this will only work correctly of \gosam\ with all its subcomponents has been correctly found during configuration of \whizard\ and then subsequently correctly linked. In order to generate the tables for spin, flavor and color states for the corresponding process, first \oMega\ is called to provide \fortran\ code for the interfaces to all the metadata for the process(es) to be evaluated. Next, the \gosam\ \python\ script is automatically invoked that first checks for the necessary ingredients to produce, compile and link the \gosam\ matrix elements. These are the the \ttt{Qgraf} topology generator for the diagrams, \ttt{Form} to perform algebra, the \ttt{Samurai}, \ttt{AVHLoop}, \ttt{QCDLoop} and \ttt{Ninja} libraries for Passarino-Veltman reduction, one-loop tensor integrals etc. As a next step, \gosam\ automatically writes and executes a \ttt{configure} script, and then it exchanges the Binoth Les Houches accord (BLHA) contract files between \whizard\ and itself~\cite{Binoth:2010xt,Alioli:2013nda} to check whether it actually generate code for the demanded process at the given order. Note that the contract and answer files do not have to be written by the user by hand, but are generated automatically within the program work flow initiated by the original \sindarin\ script. \gosam\ then generates \fortran\ code for the different components of the processes, compiles it and links it into a library, which is then automatically accessible (as an external process library) from inside \whizard. The phase space setup and the integration as well as the LO (and NLO) event generation work then in exactly the same way as for \oMega\ matrix elements. As an NLO calculation consists of different components for the Born, the real correction, the virtual correction, the subtraction part and possible further components depending on the details of the calculation, there is the possible to separately choose the matrix element method for those components via the keywords \ttt{\$loop\_me\_method}, \ttt{\$real\_tree\_me\_method}, \ttt{\$correlation\_me\_method} etc. These keywords overwrite the master switch of the \ttt{\$method} keyword. For more information on the switches and details of the functionality of \gosam, cf. \url{http://gosam.hepforge.org}. %%%%% \section{Interface to Openloops} \label{sec:openloops_me} Very similar to the case of \gosam, cf. Sec.~\ref{sec:gosam_me}, is the case for \openloops\ matrix elements. Also here, first \oMega\ is called in order to provide an interface for the spin, flavor and color degrees of freedom for the corresponding process. Information exchange between \whizard\ and \openloops\ then works in the same automatic way as for \gosam\ via the BLHA interface. This matrix element method is invoked via \begin{code} $method = "openloops" \end{code} This again is the master switch that will tell \whizard\ to use \openloops\ for all components, while there are special keywords to tailor-make the setup for the different components of an NLO calculation (cf. Sec.~\ref{sec:gosam_me}. The main difference between \openloops\ and \gosam\ is that for \openloops\ there is no process code to be generated, compiled and linked for a process, but a precompiled library is called and linked, e.g. \ttt{ppllj} for the Drell-Yan process. Of course, this library has to be installed on the system, but if that is not the case, the user can execute the \openloops\ script in the source directory of \openloops\ to download, compile and link the corresponding dynamic library. This limits (for the moment) the usage of \openloops\ to processes where pre-existint libraries for that specific processes have been generated by the \openloops\ authors. A new improved generator for general process libraries for \openloops\ will get rid of that restriction. For more information on the installation, switches and details of the functionality of \openloops, cf. \url{http://openloops.hepforge.org}. %%%%% \section{Interface to Recola} \label{sec:recola_me} The third one-loop provider (OLP) for external matrix elements that is supported by \whizard, is \recola. In contrast to \gosam, cf. Sec.~\ref{sec:gosam_me}, and \openloops, cf. Sec.~\ref{sec:openloops_me}, \recola\ does not use a BLHA interface to exchange information with \whizard, but its own tailor-made C interoperable library interface to communicate to the Monte Carlo side. \recola\ matrix elements are called for via \begin{code} $method = "recola" \end{code} \recola\ uses a highly efficient algorithm to generate process code for LO and NLO SM amplitudes in a fully recursive manner. At the moment, the setup of the interface within \whizard\ does not allow to invoke more than one different process in \recola: this would lead to a repeated initialization of the main setup of \recola\ and would consequently crash it. It is foreseen in the future to have a safeguard mechanism inside \whizard\ in order to guarantee initialization of \recola\ only once, but this is not yet implemented. Further information on the installation, details and parameters of \recola\ can be found at \url{http://recola.hepforge.org}. %%%%% \section{Special applications} \label{sec:special_me} There are also special applications with combinations of matrix elements from different sources for dedicated purposes like e.g. for the matched top--anti-top threshold in $e^+e^-$. For this special application which depending on the order of the matching takes only \oMega\ matrix elements or at NLO combines amplitudes from \oMega\ and \openloops, is invoked by the method: \begin{code} $method = "threshold" \end{code} \newpage %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \chapter{Implemented physics} \label{chap:physics} %%%%% \section{The hard interaction models} In this section, we give a brief overview over the different incarnations of models for the description of the realm of subatomic particles and their interactions inside \whizard. In Sec.~\ref{sec:smandfriends}, the Standard Model (SM) itself and straightforward extensions and modifications thereof in the gauge, fermionic and Higgs sector are described. Then, Sec.~\ref{sec:bsmmodels} gives a list and short description of all genuine beyond the SM models (BSM) that are currently implemented in \whizard\ and its matrix element generator \oMega. Additional models beyond that can be integrated and handled via the interfaces to external tools like \sarah\ and \FeynRules, or the universal model format \UFO, cf. Chap.~\ref{chap:extmodels}. %%%%%%%%%%%%%%% \subsection{The Standard Model and friends} \label{sec:smandfriends} %%%% \subsection{Beyond the Standard Model} \label{sec:bsmmodels} \begin{table} \begin{center} \begin{tabular}{|l|l|l|} \hline MODEL TYPE & with CKM matrix & trivial CKM \\ \hline\hline Yukawa test model & \tt{---} & \tt{Test} \\ \hline QED with $e,\mu,\tau,\gamma$ & \tt{---} & \tt{QED} \\ QCD with $d,u,s,c,b,t,g$ & \tt{---} & \tt{QCD} \\ Standard Model & \tt{SM\_CKM} & \tt{SM} \\ SM with anomalous gauge couplings & \tt{SM\_ac\_CKM} & \tt{SM\_ac} \\ SM with $Hgg$, $H\gamma\gamma$, $H\mu\mu$, $He^+e^-$ & \tt{SM\_Higgs\_CKM} & \tt{SM\_Higgs} \\ SM with bosonic dim-6 operators & \tt{---} & \tt{SM\_dim6} \\ SM with charge 4/3 top & \tt{---} & \tt{SM\_top} \\ SM with anomalous top couplings & \tt{---} & \tt{SM\_top\_anom} \\ SM with anomalous Higgs couplings & \tt{---} & \tt{SM\_rx}/\tt{NoH\_rx}/\tt{SM\_ul} \\\hline SM extensions for $VV$ scattering & \tt{---} & \tt{SSC}/\tt{AltH}/\tt{SSC\_2}/\tt{SSC\_AltT} \\\hline SM with $Z'$ & \tt{---} & \tt{Zprime} \\ \hline Two-Higgs Doublet Model & \tt{THDM\_CKM} & \tt{THDM} \\ \hline\hline MSSM & \tt{MSSM\_CKM} & \tt{MSSM} \\ \hline MSSM with gravitinos & \tt{---} & \tt{MSSM\_Grav} \\ \hline NMSSM & \tt{NMSSM\_CKM} & \tt{NMSSM} \\ \hline extended SUSY models & \tt{---} & \tt{PSSSM} \\ \hline\hline Littlest Higgs & \tt{---} & \tt{Littlest} \\ \hline Littlest Higgs with ungauged $U(1)$ & \tt{---} & \tt{Littlest\_Eta} \\ \hline Littlest Higgs with $T$ parity & \tt{---} & \tt{Littlest\_Tpar} \\ \hline Simplest Little Higgs (anomaly-free) & \tt{---} & \tt{Simplest} \\ \hline Simplest Little Higgs (universal) & \tt{---} & \tt{Simplest\_univ} \\ \hline\hline SM with graviton & \tt{---} & \tt{Xdim} \\ \hline UED & \tt{---} & \tt{UED} \\ \hline ``SQED'' with gravitino & \tt{---} & \tt{GravTest} \\ \hline Augmentable SM template & \tt{---} & \tt{Template} \\ \hline \end{tabular} \end{center} \caption{\label{tab:models} List of models available in \whizard. There are pure test models or models implemented for theoretical investigations, a long list of SM variants as well as a large number of BSM models.} \end{table} \subsubsection{Strongly Interacting Models and Composite Models} Higgsless models have been studied extensively before the Higgs boson discovery at the LHC Run I in 2012 in order to detect possible loopholes in the electroweak Higgs sector discovery potential of this collider. The Threesite Higgsless Model is one of the simplest incarnations of these models, and was one of the first BSM models beyond SUSY and Little Higgs models that have been implemented in \whizard~\cite{Speckner:2010zi}. It is also called the Minimal Higgsless Model (MHM)~\cite{Chivukula:2006cg} is a minimal deconstructed Higgsless model which contains only the first resonance in the tower of Kaluza-Klein modes of a Higgsless extra-dimensional model. It is a non-renormalizable, effective theory whose gauge group is an extension of the SM with an extra $SU(2)$ gauge group. The breaking of the extended electroweak gauge symmetry is accomplished by a set of nonlinear sigma fields which represent the effects of physics at a higher scale and make the theory nonrenormalizable. The physical vector boson spectrum contains the usual photon, $W^\pm$ and $Z$ bosons as well as a $W'^\pm$ and $Z'$ boson. Additionally, a new set of heavy fermions are introduced to accompany the new gauge group ``site'' which mix to form the physical eigenstates. This mixing is controlled by the small mixing parameter $\epsilon_L$ which is adjusted to satisfy constraints from precision observables, such as the S parameter~\cite{Chivukula:2005xm}. Here, additional weak gauge boson production at the LHC was one of the focus of the studies with \whizard~\cite{Ohl:2008ri}. \subsubsection{Supersymmetric Models} \whizard/\oMega\ was the first multi-leg matrix-element/event generator to include the full Minimal Supersymmetric Standard Model (MSSM), and also the NMSSM. The SUSY implementations in \whizard\ have been extensively tested~\cite{Ohl:2002jp,Reuter:2009ex}, and have been used for many theoretical and experimental studies (some prime examples being~\cite{Kalinowski:2008fk,Robens:2008sa,Hagiwara:2005wg}. \subsubsection{Little Higgs Models} \subsubsection{Inofficial models} There have been several models that have been included within the \whizard/\oMega\ framework but never found their way into the official release series. One famous example is the non-commutative extension of the SM, the NCSM. There have been several studies, e.g. simulations on the $s$-channel production of a $Z$ boson at the photon collider option of the ILC~\cite{Ohl:2004tn}. Also, the production of electroweak gauge bosons at the LHC in the framework of the NCSM have been studied~\cite{Ohl:2010zf}. %%%%%%%%%%%%%%% \section{The SUSY Les Houches Accord (SLHA) interface} \label{sec:slha} To be filled in ...~\cite{Skands:2003cj,AguilarSaavedra:2005pw,Allanach:2008qq}. The neutralino sector deserves special attention. After diagonalization of the mass matrix expresssed in terms of the gaugino and higgsino eigenstates, the resulting mass eigenvalues may be either negative or positive. In this case, two procedures can be followed. Either the masses are rendered positive and the associated mixing matrix gets purely imaginary entries or the masses are kept signed, the mixing matrix in this case being real. According to the SLHA agreement, the second option is adopted. For a specific eigenvalue, the phase is absorbed into the definition of the relevant eigenvector, rendering the mass negative. However, \whizard\ has not yet officially tested for negative masses. For external SUSY models (cf.~Chap.~\ref{chap:extmodels}) this means, that one must be careful using a SLHA file with explicit factors of the complex unity in the mixing matrix, and on the other hand, real and positive masses for the neutralinos. For the hard-coded SUSY models, this is completely handled internally. Especially Ref.~\cite{Hagiwara:2005wg} discusses the details of the neutralino (and chargino) mixing matrix. %%%%%%%%%%%%%%%% \section{Lepton Collider Beam Spectra} \label{sec:beamspectra} For the simulation of lepton collider beam spectra there are two dedicated tools, \circeone\ and \circetwo\ that have been written as in principle independent tools. Both attempt to describe the details of electron (and positron) beams in a realistic lepton collider environment. Due to the quest for achieving high peak luminosities at $e^+e^-$ machines, the goal is to make the spatial extension of the beam as small as possible but keeping the area of the beam roughly constant. This is achieved by forcing the beams in the final focus into the shape of a quasi-2D bunch. Due to the high charge density in that bunch, the bunch electron distribution is modified by classical electromagnetic radiation, so called {\em beamstrahlung}. The two \circe\ packages are intended to perform a simulation of this beamstrahlung and its consequences on the electron beam spectrum as realistic as possible. More details about the two packages can be found in their stand-alone documentations. We will discuss the basic features of lepton-collider beam simulations in the next two sections, including the technicalities of passing simulations of the machine beam setup to \whizard. This will be followed by a section on the simulation of photon collider spectra, included for historical reasons. %%%%% \subsection{\circeone} While the bunches in a linear collider cross only once, due to their small size they experience a strong beam-beam effect. There is a code to simulate the impact of this effect on luminosity and background, called \ttt{GuineaPig++}~\cite{Schulte:1998au,Schulte:1999tx,Schulte:2007zz}. This takes into account the details of the accelerator, the final focus etc. on the structure of the beam and the main features of the resulting energy spectrum of the electrons and positrons. It offers the state-of-the-art simulation of lepton-collider beam spectra as close as possible to reality. However, for many high-luminosity simulations, event files produced with \ttt{GuineaPig++} are usually too small, in the sense that not enough independent events are available for physics simulations. Lepton collider beam spectra do peak at the nominal beam energy ($\sqrt{s}/2$) of the collider, and feature very steeply falling tails. Such steeply falling distributions are very poorly mapped by histogrammed distributions with fixed bin widths. The main working assumption to handle such spectra are being followed within \circeone: \begin{enumerate} \label{circe1_assumptions} \item The beam spectra for the two beams $P_1$ and $P_2$ factorize (here $x_1$ and $x_2$ are the energy fractions of the two beams, respectively): \begin{equation*} D_{P_1P_2} (x_1, x_2) = D_{P_1} (x_1) \cdot D_{P_2} (x_2) \end{equation*} \item The peak is described with a delta distribution, and the tail with a power law: \begin{equation*} D(x) = d \cdot \delta(1-x) \; + \; c \cdot x^\alpha \, (1-x)^\beta \end{equation*} \end{enumerate} The two powers $\alpha$ and $\beta$ are the main coefficients that can be tuned in order to describe the spectrum with \circeone\ as close as possible as the original \ttt{GuineaPig++} spectrum. More details about how \circeone\ works and what it does can be found in its own write-up in \ttt{circe1/share/doc}. \subsection{\circetwo} The two conditions listed in \ref{circe1_assumptions} are too restrictive and hence insufficient to describe more complicated lepton-collider beam spectra, as they e.g. occur in the CLIC drive-beam design. Here, the two beams are highly correlated and also a power-law description does not give good enough precision for the tails. To deal with these problems, \circetwo\ starts with a two-dimensional histogram featuring factorized, but variable bin widths in order to simulate the steep parts of the distributions. The limited statistics from too small \ttt{GuineaPig++} event output files leads to correlated fluctuations that would leave strange artifacts in the distributions. To abandon them, Gaussian filters are applied to smooth out the correlated fluctuations. Here care has to be taken when going from the continuum in $x$ momentum fraction space to the corresponding \begin{figure} \centering \includegraphics{circe2-smoothing} \caption{\label{fig:circe2-smoothing} Smoothing the bin at the $x_{e^+} = 1$ boundary with Gaussian filters of 3 and 10 bins width compared to no smoothing.} \end{figure} boundaries: separate smoothing procedures are being applied to the bins in the continuum region and those in the boundary in order to avoid artificial unphysical beam energy spreads. Fig.~\ref{fig:circe2-smoothing} shows the smoothing of the distribution for the bin at the $x_{e^+} = 1$ boundary. The blue dots show the direct \ttt{GuineaPig++} output comprising the fluctuations due to the low statistics. Gaussian filters with widths of 3 and 10 bins, respectively, have been applied (orange and green dots, resp.). While there is still considerable fluctuation for 3 bin width Gaussian filtering, the distribution is perfectly smooth for 10 bin width. Hence, five bin widths seem a reasonable compromise for histograms with a total of 100 bins. Note that the bins are not equidistant, but shrink with a power law towards the $x_{e^-} = 1$ boundary on the right hand side of Fig.~\ref{fig:circe2-smoothing}. \whizard\ ships (inside its subpackage \circetwo) with prepared beam spectra ready to be used within \circetwo\ for the ILC beam spectra used in the ILC TDR~\cite{Behnke:2013xla,Baer:2013cma,Adolphsen:2013jya,Adolphsen:2013kya,Behnke:2013lya}. These comprise the designed staging energies of 200 GeV, 230 GeV, 250 GeV, 350 GeV, and 500 GeV. Note that all of these spectra up to now do not take polarization of the original beams on the beamstrahlung into account, but are polarization-averaged. For backwards compatibility, also the 500 GeV spectra for the TESLA design~\cite{AguilarSaavedra:2001rg,Richard:2001qm}, here both for polarized and polarization-averaged cases, are included. Correlated spectra for CLIC staging energies like 350 GeV, 1400 GeV and 3000 GeV are not yet (as of version 2.2.4) included in the \whizard\ distribution. In the following we describe how to obtain such files with the tools included in \whizard (resp. \circetwo). The procedure is equivalent to the so-called \ttt{lumi-linker} construction used by Timothy Barklow (SLAC) together with the legacy version \whizard\ttt{ 1.95}. The workflow to produce such files is to run \ttt{GuineaPig++} with the following input parameters: \begin{Code} do_lumi = 7; num_lumi = 100000000; num_lumi_eg = 100000000; num_lumi_gg = 100000000; \end{Code} This demands from \ttt{GuineaPig++} the generation of distributions for the $e^-e^+$, $e^\mp \gamma$, and $\gamma\gamma$ components of the beamstrahlung's spectrum, respectively. These are the files \ttt{lumi.ee.out}, \ttt{lumi.eg.out}, \ttt{lumi.ge.out}, and \ttt{lumi.gg.out}, respectively. These contain pairs $(E_1, E_2)$ of beam energies, {\em not} fractions of the original beam energy. Huge event numbers are out in here, as \ttt{GuineaPig++} will produce only a small fraction due to a very low generation efficiency. The next step is to transfer these output files from \ttt{GuineaPig++} into input files used with \circetwo. This is done by means of the tool \ttt{circe\_tool.opt} that is installed together with the \whizard\ main binary and libraries. The user should run this executable with the following input file: \begin{Code} { file="ilc500/ilc500.circe" # to be loaded by WHIZARD { design="ILC" roots=500 bins=100 scale=250 # E in [0,1] { pid/1=electron pid/2=positron pol=0 # unpolarized e-/e+ events="ilc500/lumi.ee.out" columns=2 # <= Guinea-Pig lumi = 1564.763360 # <= Guinea-Pig iterations = 10 # adapting bins smooth = 5 [0,1) [0,1) # Gaussian filter 5 bins smooth = 5 [1] [0,1) smooth = 5 [0,1) [1] } } } \end{Code} The first line defines the output file, that later can be read in into the beamstrahlung's description of \whizard\ (cf. below). Then, in the second line the design of the collider (here: ILC for 500 GeV center-of-mass energy, with the number of bins) is specified. The next line tells the tool to take the unpolarized case, then the \ttt{GuineaPig++} parameters (event file and luminosity) are set. In the last three lines, details concerning the adaptation of the simulation as well as the smoothing procedure are being specified: the number of iterations in the adaptation procedure, and for the smoothing with the Gaussian filter first in the continuum and then at the two edges of the spectrum. For more details confer the documentation in the \circetwo\ subpackage. This produces the corresponding input files that can be used within \whizard\ to describe beamstrahlung for lepton colliders, using a \sindarin\ input file like: \begin{Code} beams = e1, E1 => circe2 $circe2_file = "ilc500.circe" $circe2_design = "ILC" ?circe2_polarized = false \end{Code} %%%%% \subsection{Photon Collider Spectra} For details confer the complete write-up of the \circetwo\ subpackage. %%%%% \section{Transverse momentum for ISR photons} \label{sec:isr-photon-handler} The structure functions that describe the splitting of a beam particle into a particle pair, of which one enters the hard interaction and the other one is radiated, are defined and evaluated in the strict collinear approximation. In particular, this holds for the ISR structure function which describes the radiation of photons off a charged particle in the initial state. The ISR structure function that is used by \whizard\ is understood to be inclusive, i.e., it implicitly contains an integration over transverse momentum. This approach is to be used for computing a total cross section via \ttt{integrate}. In \whizard, it is possible to unfold this integration, as a transformation that is applied by \ttt{simulate} step, event by event. The resulting modified events will show a proper logarithmic momentum-transfer ($Q^2$) distribution for the radiated photons. The recoil is applied to the hard-interaction system, such that four-momentum and $\sqrt{\hat s}$ are conserved. The distribution is cut off by $Q_{\text{max}}^2$ (cf. \ttt{isr\_q\_max}) for large momentum transfer, and smoothly by the parton mass (cf.\ \ttt{isr\_mass}) for small momentum transfer. To activate this modification, set \begin{Code} ?isr_handler = true $isr_handler_mode = "recoil" \end{Code} before, or as an option to, the \ttt{simulate} command. Limitations: the current implementation of the $p_T$ modification works only for the symmetric double-ISR case, i.e., both beams have to be charged particles with identical mass (e.g., $e^+e^-$). The mode \ttt{recoil} generates exactly one photon per beam, i.e., it modifies the momentum of the single collinear photon that the ISR structure function implementation produces, for each beam. (It is foreseen that further modes or options will allow to generate multiple photons. Alternatively, the \pythia\ shower can be used to simulate multiple photons radiated from the initial state.) %%%%% \section{Transverse momentum for the EPA approximation} \label{sec:epa-beam-handler} For the equivalent-photon approximation (EPA), which is also defined in the collinear limit, recoil momentum can be inserted into generated events in an entirely analogous way. The appropriate settings are \begin{Code} ?epa_handler = true $epa_handler_mode = "recoil" \end{Code} Limitations: as for ISR, the current implementation of the $p_T$ modification works only for the symmetric double-EPA case. Both incoming particles of the hard process must be photons, while both beams must be charged particles with identical mass (e.g., $e^+e^-$). Furthermore, the current implementation does not respect the kinematical limit parameter \verb|epa_q_min|, it has to be set to zero. In effect, the lower $Q^2$ cutoff is determined by the beam-particle mass \verb|epa_mass|, and the upper cutoff is either given by $Q_{\text{max}}$ (the parameter \verb|epa_q_max|), or by the limit $\sqrt{s}$ if this is not set. It is possible to combine the ISR and EPA handlers, for processes where ISR is active for one of the beams, EPA for the other beam. For this scenario to work, both handler switches must be on, and both mode strings must coincide. The parameters are set separately for ISR and EPA, as described above. %%%%% \section{Resonances and continuum} \subsection{Complete matrix elements} Many elementary physical processes are composed of contributions that can be qualified as (multiply) \emph{resonant} or \emph{continuum}. For instance, the amplitude for the process $e^+e^-\to q\bar q q\bar q$, evaluated at tree level in perturbation theory, contains Feynman diagrams with zero, one, or two $W$ and $Z$ bosons as virtual lines. If the kinematical constraints allow this, two vector bosons can become simultaneously on-shell in part of phase space. To a first approximation, this situation is understood as $W^+W^-$ or $ZZ$ production with subsequent decay. The kinematical distributions show distinct resonances in the quark-pair spectra. Other graphs contain only one s-channel $W/Z$ boson, or none at all, such as graphs with $q\bar q$ production and subsequent gluon radiation, splitting into another $q\bar q$ pair. A \whizard\ declaration of the form \begin{Code} process q4 = e1, E1 => u, U, d, D \end{Code} produces the full set of graphs for the selected final state, which after squaring and integrating yields the exact tree-level result for the process. The result contains all doubly and singly resonant parts, with correct resonance shapes, as well as the continuum contribution and all interference. This is, to given order in perturbation theory, the best possible approximation to the true result. \subsection{Processes restricted to resonances} For an intuitive separation of a two-boson ``signal'' contribution, it is possible to restrict the set of graphs to a certain intermediate state. For instance, the declaration \begin{Code} process q4_zz = e1, E1 => u, U, d, D { $restrictions = "3+4~Z && 5+6~Z" } \end{Code} generates an amplitude that contains only those Feynman graphs where the specified quarks are connected to a $Z$ virtual line. The result may be understood as $ZZ$ production with subsequent decay, where the $Z$ resonances exhibit a Breit-Wigner shape. Combining this with the analogous $W^+W^-$ restricted process, the user can generate ``signal'' processes. Adding both ``signal'' cross sections $WW$ and $ZZ$ will result in a reasonable approximation to the exact tree-level cross section. The amplitude misses the single-resonant and continuum contributions, and the squared amplitude misses the interference terms, however. More importantly, the restricted processes as such are not gauge-invariant (with respect to the electroweak gauge group), and they are no longer dominant away from resonant kinematics. We therefore strongly recommend that such restricted processes are always accompanied by a cut setup that restricts the kinematics to an approximately on-shell pattern for both resonances. For instance: \begin{Code} cuts = all 85 GeV < M < 95 GeV [u:U] and all 85 GeV < M < 95 GeV [d:D] \end{Code} In this region, the gauge-dependent and continuum contributions are strictly subdominant. Away from the resonance(s), the results for a restricted process are meaningless, and the full process has to be computed instead. \subsection{Factorized processes} Another method for obtaining the signal contribution is a proper factorization into resonance production and decay. We would have to generate a production process and two decay processes: \begin{Code} process z_uu = Z => u, U process z_dd = Z => d, D process zz = e1, E1 => Z, Z \end{Code} All three processes must be integrated. The integration results are partial decay widths and the $ZZ$ production cross section, respectively. (Note that cut expressions in \sindarin\ apply to all integrations, so make sure that no production-process cuts are active when integrating the decay processes.) During a later event-generation step, the $Z$ decays can then be activated by declaring the $Z$ as unstable, \begin{Code} unstable Z (z_uu, z_dd) \end{Code} and then simulating the production process \begin{Code} simulate (zz) \end{Code} The generated events will consist of four-fermion final states, including all combinations of both decay modes. It is important to note that in this setup, the invariant $u\bar u$ and $d\bar d$ masses will be always \emph{exactly} equal to the $Z$ mass. There is no Breit-Wigner shape involved. However, in this approximation the results are gauge-invariant, as there is no off-shell contribution involved. For further details on factorized processes and spin correlations, cf.\ Sec.~\ref{sec:spin-correlations}. \subsection{Resonance insertion in the event record} From the above discussion, we may conclude that it is always preferable to compute the complete process for a given final state, as long as this is computationally feasible. However, in the simulation step this approach also has a drawback. Namely, if a parton-shower module (see below) is switched on, the parton-shower algorithm relies on event details in order to determine the radiation pattern of gluons and further splitting. In the generated event records, the full-process events carry the signature of non-resonant continuum production with no intermediate resonances. The parton shower will thus start the evolution at the process energy scale, the total available energy. By contrast, for an electroweak production and decay process, the evolution should start only at the vector boson mass, $m_Z$. In effect, even though the resonant contribution of $WW$ and $ZZ$ constitutes the bulk of the cross section, the radiation pattern follows the dynamics of four-quark continuum production. In general, the number of radiated hadrons will be too high. \begin{figure} \begin{center} \includegraphics[width=.41\textwidth]{resonance_e_gam} \includegraphics[width=.41\textwidth]{resonance_n_charged} \\ \includegraphics[width=.41\textwidth]{resonance_n_hadron} \includegraphics[width=.41\textwidth]{resonance_n_particles} \\ \includegraphics[width=.41\textwidth]{resonance_n_photons} \includegraphics[width=.41\textwidth]{resonance_n_visible} \end{center} \caption{The process $e^+e^- \to jjjj$ at 250 GeV center-of-mass energy is compared transferring the partonic events naively to the parton shower, i.e. without respecting any intermediate resonances (red lines). The blue lines show the process factorized into $WW$ production and decay, where the shower knows the origin of the two jet pairs. The orange and dark green lines show the resonance treatment as mentioned in the text, with \ttt{resonance\_on\_shell\_limit = 1} and \ttt{= 4}, respectively. \pythiasix\ parton shower and hadronization with the OPAL tune have been used. The observables are: photon energy distribution and number of charged tracks (upper line left/right, number of hadrons and total number of particles (middle left/right), and number of photons and neutral particles (lower line left/right).} \end{figure} To overcome this problem, there is a refinement of the process description available in \whizard. By modifying the process declaration to \begin{Code} ?resonance_history = true resonance_on_shell_limit = 4 process q4 = e1, E1 => u, U, d, D \end{Code} we advise the program to produce not just the complete matrix element, but also all possible restricted matrix elements containing resonant intermediate states. This has no effect at all on the integration step, and thus on the total cross section. However, when subsequently events are generated with this setting, the program checks, for each event, the kinematics and determines the set of potentially resonant contributions. The criterion is whether the off-shellness of a particular would-be resonance is less than the resonance width multiplied by the value of \verb|resonance_on_shell_limit| (default value $=4$). For the set of resonance histories which pass this criterion (which can be empty), their respective squared matrix element is related to the full-process matrix element. The ratio is interpreted as a probability. The random-number generator then selects one or none of the resonance histories, and modifies the event record accordingly. In effect, for an appropriate fraction of the events, depending on the kinematics, the parton-shower module is provided with resonance information, so it can adjust the radiation pattern accordingly. It has to be mentioned that generating the matrix-element code for all possible resonance histories takes additional computing resources. In the current default setup, this feature is switched off. It has to be explicitly activated via the \verb|?resonance_history| flag. Also, the feature can be activated or deactivated individually for each process, such as in \begin{Code} ?resonance_history = true process q4_with_res = e1, E1 => u, U, d, D { ?resonance_history = true } process q4_wo_res = e1, E1 => u, U, d, D { ?resonance_history = false } \end{Code} If the flag is \verb|false| for a process, no resonance code will be generated. Similarly, the flag has to be globally or locally active when \verb|simulate| is called, such that the feature takes effect for event generation. There are two additional parameters that can fine-tune the conditions for resonance insertion in the event record. Firstly, the parameter \verb|resonance_on_shell_turnoff|, if nonzero, enables a Gaussian suppression of the probability for resonance insertion. For instance, setting \begin{Code} ?resonance_history = true resonance_on_shell_turnoff = 4 resonance_on_shell_limit = 8 \end{Code} will reduce the probability for the event to be qualified as resonant by $e^{-1}= 37\,\%$ if the kinematics is off-shell by four units of the width, and by $e^{-4}=2\,\%$ at eight units of the width. Beyond this point, the setting of the \verb|resonance_on_shell_limit| parameter eliminates resonance insertion altogether. In effect, the resonance-background transition is realized in a smooth way. Secondly, within the resonant-kinematics range the probability for qualifying the event as background can be reduced by the parameter \verb|resonance_background_factor| (default value $=1$) to a number between zero and one. Setting this to zero means that the event will be necessarily qualified as resonant, if it falls within the resonant-kinematics range. Note that if an event, by the above mechanism, is identified as following a certain resonance history, the assigned color flow will be chosen to match the resonance history, not the complete matrix element. This may result in a reassignment of color flow with respect to the original partonic event. Finally, we mention the order of execution: any additional matrix element code is compiled and linked when \verb|compile| is executed for the processes in question. If this command is omitted, the \verb|simulate| command will trigger compilation. \section{Parton showers and Hadronization} In order to produce sensible events, final state QCD (and also QED) radiation has to be considered as well as the binding of strongly interacting partons into mesons and baryons. Furthermore, final state hadronic resonances undergo subsequent decays into those particles showing up in (or traversing) the detector. The latter are mostly pions, kaons, photons, electrons and muons. The physics associated with these topics can be divided into the perturbative part which is the regime of the parton shower, and the non-perturbative part which is the regime for the hadronization. \whizard\ comes with its own two different parton shower implementations, an analytic and a so-called $k_T$-ordered parton shower that will be detailed in the next section. Note that in general it is not advisable to use different shower and hadronization methods, or in other words, when using shower and hadronization methods from different programs these would have to be tuned together again with the corresponding data. Parton showers are approximations to full matrix elements taking only the leading color flow into account, and neglecting all interferences between different amplitudes leading to the same exclusive final state. They rely on the QCD (and QED) splitting functions to describe the emissions of partons off other partons. This is encoded in the so-called Sudakov form factor~\cite{Sudakov:1954sw}: \begin{equation*} \Delta( t_1, t_2) = \exp \left[ \int\limits_{t_1}^{t_2} \mbox{d} t \int\limits_{z_-}^{z_+} \mbox{d} z \frac{\alpha_s}{2 \pi t} P(z) \right] \end{equation*} This gives the probability for a parton to evolve from scale $t_2$ to $t_1$ without any further emissions of partons. $t$ is the evolution parameter of the shower, which can be a parton energy, an emission angle, a virtuality, a transverse momentum etc. The variable $z$ relates the two partons after the branching, with the most common choice being the ratio of energies of the parton after and before the branching. For final-state radiation brachings occur after the hard interaction, the evolution of the shower starts at the scale of the hard interaction, $t \sim \hat{s}$, down to a cut-off scale $t = t_{\text{cut}}$ that marks the transition to the non-perturbative regime of hadronization. In the space-like evolution for the initial-state shower, the evolution is from a cut-off representing the factorization scale for the parton distribution functions (PDFs) to the inverse of the hard process scale, $-\hat{s}$. Technically, this evolution is then backwards in (shower) time~\cite{Sjostrand:1985xi}, leading to the necessity to include the PDFs in the Sudakov factors. The main switches for the shower and hadronization which are realized as transformations on the partonic events within \whizard\ are \ttt{?allow\_shower} and \ttt{?allow\_hadronization}, which are true by default and only there for technical reasons. Next, different shower and hadronization methods can be chosen within \whizard: \begin{code} $shower_method = "WHIZARD" $hadronization_method = "PYTHIA6" \end{code} The snippet above shows the default choices in \whizard\, namely \whizard's intrinsic parton shower, but \pythiasix\ as hadronization tool. (Note that \whizard\ does not have its own hadronization module yet.) The usage of \pythiasix\ for showering and hadronization will be explained in Sec.~\ref{sec:pythia6}, while the two different implementations of the \whizard\ homebrew parton showers are discussed in Sec.~\ref{sec:ktordered} and~\ref{sec:analytic}, respectively. %%%%% \subsection{The $k_T$-ordered parton shower} \label{sec:ktordered} %%%%% \subsection{The analytic parton shower} \label{sec:analytic} %%%%% \subsection{Parton shower and hadronization from \pythiasix} \label{sec:pythia6} Development of the \pythiasix\ generator for parton shower and hadronization (the \fortran\ version) has been discontinued by the authors several years ago. Hence, the final release of that program is frozen. This allowed to ship this final version, v6.427, with the \whizard\ distribution without the need of updating it all the time. One of the main reasons for that inclusion -- besides having the standard tool for showering and hadronization for decays at hand -- is to allow for backwards validation within \whizard\ particularly for the event samples generated for the development of linear collider physics: first for TESLA, JLC and NLC, and later on for the Conceptual and Technical Design Report for ILC, for the Conceptual Design Report for CLIC as well as for the Letters of Intent for the LC detectors, ILD and SiD. Usually, an external parton shower and hadronization program (PS) is steered via the transfer of event files that are given to the PS via LHE events, while the PS program then produces hadron level events, usually in HepMC format. These can then be directed towards a full or fast detector simulation program. As \pythiasix\ has been completely integrated inside the \whizard\ framework, the showered or more general hadron level events can be returned to and kept inside \whizard's internal event record, and hence be used in \whizard's internal event analysis. In that way, the events can be also written out in event formats that are not supported by \pythiasix, e.g. \ttt{LCIO} via the output capabilities of \whizard. There are several switches to directly steer \pythiasix\ (the values in brackets correspond to the \pythiasix\ variables): \begin{code} ps_mass_cutoff = 1 GeV [PARJ(82)] ps_fsr_lambda = 0.29 GeV [PARP(72)] ps_isr_lambda = 0.29 GeV [PARP(61)] ps_max_n_flavors = 5 [MSTJ(45)] ?ps_isr_alphas_running = true [MSTP(64)] ?ps_fsr_alphas_running = true [MSTJ(44)] ps_fixed_alphas = 0.2 [PARU(111)] ?ps_isr_angular_ordered = true [MSTP(62)] ps_isr_primordial_kt_width = 1.5 GeV [PARP(91)] ps_isr_primordial_kt_cutoff = 5.0 GeV [PARP(93)] ps_isr_z_cutoff = 0.999 [1-PARP(66)] ps_isr_minenergy = 2 GeV [PARP(65)] ?ps_isr_only_onshell_emitted_partons = true [MSTP(63)] \end{code} The values given above are the default values. The first value corresponds to the \pythiasix\ parameter \ttt{PARJ(82)}, its squared being the minimal virtuality that is allowed for the parton shower, i.e. the cross-over to the hadronization. The same parameter is used also for the \whizard\ showers. \ttt{ps\_fsr\_lambda} is the equivalent of \ttt{PARP(72)} and is the $\Lambda_{\text{QCD}}$ for the final state shower. The corresponding variable for the initial state shower is called \ttt{PARP(61)} in \pythiasix. By the next variable (\ttt{MSTJ(45)}), the maximal number of flavors produced in splittings in the shower is given, together with the number of active flavors in the running of $\alpha_s$. \ttt{?ps\_isr\_alphas\_running} which corresponds to \ttt{MSTP(64)} in \pythiasix\ determines whether or net a running $\alpha_s$ is taken in the space-like initial state showers. The same variable for the final state shower is \ttt{MSTJ(44)}. For fixed $\alpha_s$, the default value is given by \ttt{ps\_fixed\_alpha}, corresponding to \ttt{PARU(111)}. \ttt{MSTP(62)} determines whether the ISR shower is angular order, i.e. whether angles are increasing towards the hard interaction. This is per default true, and set in the variable \ttt{?ps\_isr\_angular\_ordered}. The width of the distribution for the primordial (intrinsic) $k_T$ distribution (which is a non-perturbative quantity) is the \pythiasix\ variable \ttt{PARP(91)}, while in \whizard\ it is given by \ttt{pythia\_isr\_primordial\_kt\_width}. The next variable (\ttt{PARP(93}) gives the upper cutoff for that distribution, which is 5 GeV per default. For splitting in space-like showers, there is a cutoff on the $z$ variable named \ttt{ps\_isr\_z\_cutoff} in \whizard. This corresponds to one minus the value of the \pythiasix\ parameter \ttt{PARP(66)}. \ttt{PARP(65)}, on the other hand, gives the minimal (effective) energy for a time-like or on-shell emitted parton on a space-like QCD shower, given by the \sindarin\ parameter \ttt{ps\_isr\_minenergy}. Whether or not partons emitted from space-like showers are allowed to be only on-shell is given by \ttt{?ps\_isr\_only\_onshell\_emitted\_partons}, \ttt{MSTP(63)} in \pythiasix\ language. For more details confer the \pythiasix\ manual~\cite{Sjostrand:2006za}. Any other non-standard \pythiasix\ parameter can be fed into the parton shower via the string variable \begin{code} $ps_PYTHIA_PYGIVE = "...." \end{code} Variables set here get preference over the ones set explicitly by dedicated \sindarin\ commands. For example, the OPAL tune for hadronic final states can be set via: \begin{code} $ps_PYTHIA_PYGIVE = "MSTJ(28)=0; PMAS(25,1)=120.; PMAS(25,2)=0.3605E-02; MSTJ(41)=2; MSTU(22)=2000; PARJ(21)=0.40000; PARJ(41)=0.11000; PARJ(42)=0.52000; PARJ(81)=0.25000; PARJ(82)=1.90000; MSTJ(11)=3; PARJ(54)=-0.03100; PARJ(55)=-0.00200; PARJ(1)=0.08500; PARJ(3)=0.45000; PARJ(4)=0.02500; PARJ(2)=0.31000; PARJ(11)=0.60000; PARJ(12)=0.40000; PARJ(13)=0.72000; PARJ(14)=0.43000; PARJ(15)=0.08000; PARJ(16)=0.08000; PARJ(17)=0.17000; MSTP(3)=1;MSTP(71)=1" \end{code} \vspace{0.5cm} A very common error that appears quite often when using \pythiasix\ for SUSY or any other model having a stable particle that serves as a possible Dark Matter candidate, is the following warning/error message: \begin{Code} Advisory warning type 3 given after 0 PYEXEC calls: (PYRESD:) Failed to decay particle 1000022 with mass 15.000 ****************************************************************************** ****************************************************************************** *** FATAL ERROR: Simulation: failed to generate valid event after 10000 tries ****************************************************************************** ****************************************************************************** \end{Code} In that case, \pythiasix\ gets a stable particle (here the lightest neutralino with the PDG code 1000022) handed over and does not know what to do with it. Particularly, it wants to treat it as a heavy resonance which should be decayed, but does not know how do that. After a certain number of tries (in the example abobe 10k), \whizard\ ends with a fatal error telling the user that the event transformation for the parton shower in the simulation has failed without producing a valid event. The solution to work around that problem is to let \pythiasix\ know that the neutralino (or any other DM candidate) is stable by means of \begin{code} $ps_PYTHIA_PYGIVE = "MDCY(C1000022,1)=0" \end{code} Here, 1000022 has to be replaced by the stable dark matter candidate or long-lived particle in the user's favorite model. Also note that with other options being passed to \pythiasix\, the \ttt{MDCY} option above has to be added to an existing \ttt{\$ps\_PYTHIA\_PYGIVE} command separated by a semicolon. %%%%% \subsection{Parton shower and hadronization from \pythiaeight} \subsection{Other tools for parton shower and hadronization} %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \chapter{More on Event Generation} \label{chap:events} In order to perform a physics analysis with \whizard\ one has to generate events. This seems to be a trivial statement, but as there have been any questions like "My \whizard\ does not produce plots -- what has gone wrong?" we believe that repeating that rule is worthwile. Of course, it is not mandatory to use \whizard's own analysis set-up, the user can always choose to just generate events and use his/her own analysis package like \ttt{ROOT}, or \ttt{TopDrawer}, or you name it for the analysis. Accordingly, we first start to describe how to generate events and what options there are -- different event formats, renaming output files, using weighted or unweighted events with different normalizations. How to re-use and manipulate already generated event samples, how to limit the number of events per file, etc. etc. \section{Event generation} To explain how event generation works, we again take our favourite example, $e^+e^- \to \mu^+ \mu^-$, \begin{verbatim} process eemm = e1, E1 => e2, E2 \end{verbatim} The command to trigger generation of events is \ttt{simulate () \{ \}}, so in our case -- neglecting any options for now -- simply: \begin{verbatim} simulate (eemm) \end{verbatim} When you run this \sindarin\ file you will experience a fatal error: \ttt{FATAL ERROR: Colliding beams: sqrts is zero (please set sqrts)}. This is because \whizard\ needs to compile and integrate the process \ttt{eemm} first before event simulation, because it needs the information of the corresponding cross section, phase space parameterization and grids. It does both automatically, but you have to provide \whizard\ with the beam setup, or at least with the center-of-momentum energy. A corresponding \ttt{integrate} command like \begin{verbatim} sqrts = 500 GeV integrate (eemm) { iterations = 3:10000 } \end{verbatim} obviously has to appear {\em before} the corresponding \ttt{simulate} command (otherwise you would be punished by the same error message as before). Putting things in the correct order results in an output like: \begin{footnotesize} \begin{verbatim} | Reading model file '/usr/local/share/whizard/models/SM.mdl' | Preloaded model: SM | Process library 'default_lib': initialized | Preloaded library: default_lib | Reading commands from file 'bla.sin' | Process library 'default_lib': recorded process 'eemm' sqrts = 5.000000000000E+02 | Integrate: current process library needs compilation | Process library 'default_lib': compiling ... | Process library 'default_lib': keeping makefile | Process library 'default_lib': keeping driver | Process library 'default_lib': active | Process library 'default_lib': ... success. | Integrate: compilation done | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 29912 | Initializing integration for process eemm: | ------------------------------------------------------------------------ | Process [scattering]: 'eemm' | Library name = 'default_lib' | Process index = 1 | Process components: | 1: 'eemm_i1': e-, e+ => mu-, mu+ [omega] | ------------------------------------------------------------------------ | Beam structure: [any particles] | Beam data (collision): | e- (mass = 5.1099700E-04 GeV) | e+ (mass = 5.1099700E-04 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'eemm_i1.phs' | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: Using 2 equivalences between channels. | Phase space: wood Warning: No cuts have been defined. | OpenMP: Using 8 threads | Starting integration for process 'eemm' | Integrate: iterations = 3:10000 | Integrator: 2 chains, 2 channels, 2 dimensions | Integrator: Using VAMP channel equivalences | Integrator: 10000 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 9216 4.2833237E+02 7.14E-02 0.02 0.02* 40.29 2 9216 4.2829071E+02 7.08E-02 0.02 0.02* 40.29 3 9216 4.2838304E+02 7.04E-02 0.02 0.02* 40.29 |-----------------------------------------------------------------------------| 3 27648 4.2833558E+02 4.09E-02 0.01 0.02 40.29 0.43 3 |=============================================================================| | Time estimate for generating 10000 events: 0d:00h:00m:04s | Creating integration history display eemm-history.ps and eemm-history.pdf | Starting simulation for process 'eemm' | Simulate: using integration grids from file 'eemm_m1.vg' | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 29913 | OpenMP: Using 8 threads | Simulation: requested number of events = 0 | corr. to luminosity [fb-1] = 0.0000E+00 | Events: writing to raw file 'eemm.evx' | Events: generating 0 unweighted, unpolarized events ... | Events: event normalization mode '1' | ... event sample complete. | Events: closing raw file 'eemm.evx' | There were no errors and 1 warning(s). | WHIZARD run finished. |=============================================================================| \end{verbatim} \end{footnotesize} So, \whizard\ tells you that it has entered simulation mode, but besides this, it has not done anything. The next step is that you have to demand event generation -- there are two ways to do this: you could either specify a certain number, say 42, of events you want to have generated by \whizard, or you could provide a number for an integrated luminosity of some experiment. (Note, that if you choose to take both options, \whizard\ will take the one which gives the larger event sample. This, of course, depends on the given process(es) -- as well as cuts -- and its corresponding cross section(s).) The first of these options is set with the command: \ttt{n\_events = }, the second with \ttt{luminosity = }. Another important point already stated several times in the manual is that \whizard\ follows the commands in the steering \sindarin\ file in a chronological order. Hence, a given number of events or luminosity {\em after} a \ttt{simulate} command will be ignored -- or are relevant only for any \ttt{simulate} command potentially following further down in the \sindarin\ file. So, in our case, try: \begin{verbatim} n_events = 500 luminosity = 10 simulate (eemm) \end{verbatim} Per default, numbers for integrated luminosity are understood as inverse femtobarn. So, for the cross section above this would correspond to 4283 events, clearly superseding the demand for 500 events. After reducing the luminosity number from ten to one inverse femtobarn, 500 is the larger number of events taken by \whizard\ for event generation. Now \whizard\ tells you: \begin{verbatim} | Simulation: requested number of events = 500 | corr. to luminosity [fb-1] = 1.1673E+00 | Events: reading from raw file 'eemm.evx' | Events: reading 500 unweighted, unpolarized events ... | Events: event normalization mode '1' | ... event file terminates after 0 events. | Events: appending to raw file 'eemm.evx' | Generating remaining 500 events ... | ... event sample complete. | Events: closing raw file 'eemm.evx' \end{verbatim} I.e., it evaluates the luminosity to which the sample of 500 events would correspond to, which is now, of course, bigger than the $1 \fb^{-1}$ explicitly given for the luminosity. Furthermore, you can read off that a file \ttt{whizard.evx} has been generated, containing the demanded 500 events. (It was there before containing zero events, because to \ttt{n\_events} or \ttt{luminosity} value had been set. \whizard\ then tried to get the events first from file before generating new ones). Files with the suffix \ttt{.evx} are binary format event files, using a machine-dependent \whizard-specific event file format. Before we list the event formats supported by \whizard, the next two sections will tell you more about unweighted and weighted events as well as different possibilities to normalize events in \whizard. As already explained for the libraries, as well as the phase space and grid files in Chap.~\ref{chap:sindarin}, \whizard\ is trying to re-use as much information as possible. This is of course also true for the event files. There are special MD5 check sums testing the integrity and compatibility of the event files. If you demand for a process for which an event file already exists (as in the example above, though it was empty) equally many or less events than generated before, \whizard\ will not generate again but re-use the existing events (as already explained, the events are stored in a \whizard-own binary event format, i.e. in a so-called \ttt{.evx} file. If you suppress generation of that file, as will be described in subsection \ref{sec:eventformats} then \whizard\ has to generate events all the time). From version v2.2.0 of \whizard\ on, the program is also able to read in event from different event formats. However, most event formats do not contain as many information as \whizard's internal format, and a complete reconstruction of the events might not be possible. Re-using event files is very practical for doing several different analyses with the same data, especially if there are many and big data samples. Consider the case, there is an event file with 200 events, and you now ask \whizard\ to generate 300 events, then it will re-use the 200 events (if MD5 check sums are OK!), generate the remaining 100 events and append them to the existing file. If the user for some reason, however, wants to regenerate events (i.e. ignoring possibly existing events), there is the command option \ttt{whizard --rebuild-events}. %%%%%%%%% \section{Unweighted and weighted events} \whizard\ is able to generate unweighted events, i.e. events that are distributed uniformly and each contribute with the same event weight to the whole sample. This is done by mapping out the phase space of the process under consideration according to its different phase space channels (which each get their own weights), and then unweighting the sample of weighted events. Only a sample of unweighted events could in principle be compared to a real data sample from some experiment. The seventh column in the \whizard\ iteration/adaptation procedure tells you about the efficiency of the grids, i.e. how well the phase space is mapped to a flat function. The better this is achieved, the higher the efficiency becomes, and the closer the weights of the different phase space channels are to uniformity. This means, for higher efficiency less weighted events ("calls") are needed to generate a single unweighted event. An efficiency of 10 \% means that ten weighted events are needed to generate one single unweighted event. After the integration is done, \whizard\ uses the duration of calls during the adaptation to estimate a time interval needed to generate 10,000 unweighted events. The ability of the adaptive multi-channel Monte Carlo decreases with the number of integrations, i.e. with the number of final state particles. Adding more and more final state particles in general also increases the complexity of phase space, especially its singularity structure. For a $2 \to 2$ process the efficiency is roughly of the order of several tens of per cent. As a rule of thumb, one can say that with every additional pair of final state particle the average efficiency one can achieve decreases by a factor of five to ten. The default of \whizard\ is to generate {\em unweighted} events. One can use the logical variable \ttt{?unweighted = false} to disable unweighting and generate weighted events. (The command \ttt{?unweighted = true} is a tautology, because \ttt{true} is the default for this variable.) Note that again this command has to appear {\em before} the corresponding \ttt{simulate} command, otherwise it will be ignored or effective only for any \ttt{simulate} command appearing later in the \sindarin\ file. In the unweighted procedure, \whizard\ is keeping track of the highest weight that has been appeared during the adaptation, and the efficiency for the unweighting has been estimated from the average value of the sampling function compared to the maximum value. In principle, during event generation no events should be generated whose sampling function value exceeds the maximum function value encountered during the grid adaptation. Sometimes, however, there are numerical fluctuations and such events are happening. They are called {\em excess events}. \whizard\ does keep track of these excess events during event generation and will report about them, e.g.: \begin{code} Warning: Encountered events with excess weight: 9 events ( 0.090 %) | Maximum excess weight = 6.083E-01 | Average excess weight = 2.112E-04 \end{code} Whenever in an event generation excess events appear, this shows that the adaptation of the sampling function has not been perfect. When the number of excess weights is a finite number of percent, you should inspect the phase-space setup and try to improve its settings to get a better adaptation. Generating \emph{weighted} events is, of course, much faster if the same number of events is requested. Each event carries a weight factor which is taken into account for any internal analysis (histograms), and written to file if an external file format has been selected. The file format must support event weights. In a weighted event sample, there is typically a fraction of events which effectively have weight zero, namely those that have been created by the phase-space sampler but do not pass the requested cuts. In the default setup, those events are silently dropped, such that the events written to file or available for analysis all have nonzero weight. However, dropping such events affects the overall normalization. If this has happened, the program will issue a warning of the form \begin{code} | Dropped events (weight zero) = 1142 (total 2142) Warning: All event weights must be rescaled by f = 4.66853408E-01 \end{code} This factor has to be applied by hand to any external event files (and to internally generated histograms). The program cannot include the factor in the event records, because it is known only after all events have been generated. To avoid this problem, there is the logical flag \ttt{?keep\_failed\_events} which tells \whizard\ not to drop events with weight zero. The normalization will be correct, but the event sample will include invalid events which have to be vetoed by their zero weight, before any operations on the event record are performed. %%%%%%%%% \section{Choice on event normalizations} There are basically four different choices to normalize event weights ($\braket{\ldots}$ denotes the average): \begin{enumerate} \item $\braket{w_i} = 1$, \qquad\qquad $\Braket{\sum_i w_i} = N$ \item $\braket{w_i} = \sigma$, \qquad\qquad $\Braket{\sum_i w_i} = N \times \sigma$ \item $\braket{w_i} = 1/N$, \quad\qquad $\Braket{\sum_i w_i} = 1$ \item $\braket{w_i} = \sigma/N$, \quad\qquad $\Braket{\sum_i w_i} = \sigma$ \end{enumerate} So the four options are to have the average weight equal to unity, to the cross section of the corresponding process, to one over the number of events, or the cross section over the event calls. In these four cases, the event weights sum up to the event number, the event number times the cross section, to unity, and to the cross section, respectively. Note that neither of these really guarantees that all event weights individually lie in the interval $0 \leq w_i \leq 1$. The user can steer the normalization of events by using in \sindarin\ input files the string variable \ttt{\$sample\_normalization}. The default is \ttt{\$sample\_normalization = "auto"}, which uses option 1 for unweighted and 2 for weighted events, respectively. Note that this is also what the Les Houches Event Format (LHEF) demands for both types of events. This is \whizard's preferred mode, also for the reason, that event normalizations are independent from the number of events. Hence, event samples can be cut or expanded without further need to adjust the normalization. The unit normalization (option 1) can be switched on also for weighted events by setting the event normalization variable equal to \ttt{"1"}. Option 2 can be demanded by setting \ttt{\$sample\_normalization = "sigma"}. Options 3 and 4 can be set by \ttt{"1/n"} and \ttt{"sigma/n"}, respectively. \whizard\ accepts small and capital letters for these expressions. In the following section we show some examples when discussing the different event formats available in \whizard. %%%%%%%%% \section{Event selection} The \ttt{selection} expression (cf.\ Sec.~\ref{subsec:analysis}) reduces the event sample during generation or rescanning, selecting only events for which the expression evaluates to \ttt{true}. Apart from internal analysis, the selection also applies to writing external files. For instance, the following code generates a $e^+e^-\to W^+W^-$ sample with longitudinally polarized $W$ bosons only: \begin{footnotesize} \begin{verbatim} process ww = "e+", "e-" => "W-", "W+" polarized "W+" polarized "W-" ?polarized_events = true sqrts = 500 selection = all Hel == 0 ["W+":"W-"] simulate (ww) { n_events = 1000 } \end{verbatim} \end{footnotesize} The number of events that end up in the sample on file is equal to the number of events with longitudinally polarized $W$s in the generated sample, so the file will contain less than 1000 events. %%%%%%%%% \section{Supported event formats} \label{sec:eventformats} Event formats can either be distinguished whether they are plain text (i.e. ASCII) formats or binary formats. Besides this, one can classify event formats according to whether they are natively supported by \whizard\ or need some external program or library to be linked. Table~\ref{tab:eventformats} gives a complete list of all event formats available in \whizard. The second column shows whether these are ASCII or binary formats, the third column contains brief remarks about the corresponding format, while the last column tells whether external programs or libraries are needed (which is the case only for the HepMC formats). \begin{table} \begin{center} \begin{tabular}{|l||l|l|r|}\hline Format & Type & remark & ext. \\\hline ascii & ASCII & \whizard\ verbose format & no \\ Athena & ASCII & variant of HEPEVT & no \\ debug & ASCII & most verbose \whizard\ format & no \\ evx & binary & \whizard's home-brew & no \\ HepMC & ASCII & HepMC format & yes \\ HEPEVT & ASCII & \whizard~1 style & no \\ LCIO & ASCII & LCIO format & yes \\ LHA & ASCII & \whizard~1/old Les Houches style &no \\ LHEF & ASCII & Les Houches accord compliant & no \\ long & ASCII & variant of HEPEVT & no \\ mokka & ASCII & variant of HEPEVT & no \\ short & ASCII & variant of HEPEVT & no \\ StdHEP (HEPEVT) & binary & based on HEPEVT common block & no \\ StdHEP (HEPRUP/EUP) & binary & based on HEPRUP/EUP common block & no \\ Weight stream & ASCII & just weights & no \\ \hline \end{tabular} \end{center} \caption{\label{tab:eventformats} Event formats supported by \whizard, classified according to ASCII/binary formats and whether an external program or library is needed to generate a file of this format. For both the HEPEVT and the LHA format there is a more verbose variant. } \end{table} The "\ttt{.evx}'' is \whizard's native binary event format. If you demand event generation and do not specify anything further, \whizard\ will write out its events exclusively in this binary format. So in the examples discussed in the previous chapters (where we omitted all details about event formats), in all cases this and only this internal binary format has been generated. The generation of this raw format can be suppressed (e.g. if you want to have only one specific event file type) by setting the variable \verb|?write_raw = false|. However, if the raw event file is not present, \whizard\ is not able to re-use existing events (e.g. from an ASCII file) and will regenerate events for a given process. Note that from version v2.2.0 of \whizard\ on, the program is able to (partially) reconstruct complete events also from other formats than its internal format (e.g. LHEF), but this is still under construction and not yet complete. Other event formats can be written out by setting the variable \ttt{sample\_format = }, where \ttt{} can be any of the following supported variables: \begin{itemize} \item \ttt{ascii}: a quite verbose ASCII format which contains lots of information (an example is shown in the appendix). \newline Standard suffix: \ttt{.evt} \item \ttt{debug}: an even more verbose ASCII format intended for debugging which prints out also information about the internal data structures \newline Standard suffix: \ttt{.debug} \item \ttt{hepevt}: ASCII format that writes out a specific incarnation of the HEPEVT common block (\whizard~1 back-compatibility) \newline Standard suffix: \ttt{.hepevt} \item \ttt{hepevt\_verb}: more verbose version of \ttt{hepevt} (\whizard~1 back-compatibility) \newline Standard suffix: \ttt{.hepevt.verb} \item \ttt{short}: abbreviated variant of the previous HEPEVT (\whizard\ 1 back-compatibility) \newline Standard suffix: \ttt{.short.evt} \item \ttt{long}: HEPEVT variant that contains a little bit more information than the short format but less than HEPEVT (\whizard\ 1 back-compatibility) \newline Standard suffix: \ttt{.long.evt} \item \ttt{athena}: HEPEVT variant suitable for read-out in the ATLAS ATHENA software environment (\whizard\ 1 back-compatibility) \newline Standard suffix: \ttt{.athena.evt} \item \ttt{mokka}: HEPEVT variant suitable for read-out in the MOKKA ILC software environment \newline Standard suffix: \ttt{.mokka.evt} \item \ttt{lcio}: LCIO ASCII format (only available if LCIO is installed and correctly linked) \newline Standard suffix: \ttt{.lcio} \item \ttt{lha}: Implementation of the Les Houches Accord as it was in the old MadEvent and \whizard~1 \newline Standard suffix: \ttt{.lha} \item \ttt{lha\_verb}: more verbose version of \ttt{lha} \newline Standard suffix: \ttt{.lha.verb} \item \ttt{lhef}: Formatted Les Houches Accord implementation that contains the XML headers \newline Standard suffix: \ttt{.lhe} \item \ttt{hepmc}: HepMC ASCII format (only available if HepMC is installed and correctly linked) \newline Standard suffix: \ttt{.hepmc} \item \ttt{stdhep}: StdHEP binary format based on the HEPEVT common block \newline Standard suffix: \ttt{.hep} \item \ttt{stdhep\_up}: StdHEP binary format based on the HEPRUP/HEPEUP common blocks \newline Standard suffix: \ttt{.up.hep} \item \ttt{stdhep\_ev4}: StdHEP binary format based on the HEPEVT/HEPEV4 common blocks \newline Standard suffix: \ttt{.ev4.hep} \item \ttt{weight\_stream}: Format that prints out only the event weight (and maybe alternative ones) \newline Standard suffix: \ttt{.weight.dat} \end{itemize} Of course, the variable \ttt{sample\_format} can contain more than one of the above identifiers, in which case more than one different event file format is generated. The list above also shows the standard suffixes for these event formats (remember, that the native binary format of \whizard\ does have the suffix \ttt{.evx}). (The suffix of the different event formats can even be changed by the user by setting the corresponding variable \ttt{\$extension\_lhef = "foo"} or \ttt{\$extension\_ascii\_short = "bread"}. The dot is automatically included.) The name of the corresponding event sample is taken to be the string of the name of the first process in the \ttt{simulate} statement. Remember, that conventionally the events for all processes in one \ttt{simulate} statement will be written into one single event file. So \ttt{simulate (proc1, proc2)} will write events for the two processes \ttt{proc1} and \ttt{proc2} into one single event file with name \ttt{proc1.evx}. The name can be changed by the user with the command \ttt{\$sample = ""}. The commands \ttt{\$sample} and \ttt{sample\_format} are both accepted as optional arguments of a \ttt{simulate} command, so e.g. \ttt{simulate (proc) \{ \$sample = "foo" sample\_format = hepmc \}} generates an event sample in the HepMC format for the process \ttt{proc} in the file \ttt{foo.hepmc}. Examples for event formats, for specifications of the event formats correspond the different accords and publications~\footnote{Some event formats, based on the \ttt{HEPEVT} or \ttt{HEPEUP} common blocks, use fixed-form ASCII output with a two-digit exponent for real numbers. There are rare cases (mainly, ISR photons) where the event record can contain numbers with absolute value less than $10^{-99}$. Since those numbers are not representable in that format, \whizard\ will set all non-zero numbers below that value to $\pm 10^{-99}$, when filling either common block. Obviously, such values are physically irrelevant, but in the output they are representable and distinguishable from zero.}: \paragraph{HEPEVT:} The HEPEVT is an ASCII event format that does not contain an event file header. There is a one-line header for each single event, containing four entries. The number of particles in the event (\ttt{ISTHEP}), which is four for a fictitious example process $hh\to hh$, but could be larger if e.g. beam remnants are demanded to be included in the event. The second entry and third entry are the number of outgoing particles and beam remnants, respectively. The event weight is the last entry. For each particle in the event there are three lines: the first one is the status according to the HEPEVT format, \ttt{ISTHEP}, the second one the PDG code, \ttt{IDHEP}, then there are the one or two possible mother particle, \ttt{JMOHEP}, the first and last possible daughter particle, \ttt{JDAHEP}, and the polarization. The second line contains the three momentum components, $p_x$, $p_y$, $p_z$, the particle energy $E$, and its mass, $m$. The last line contains the position of the vertex in the event reconstruction. \begin{scriptsize} \begin{verbatim} 4 2 0 3.0574068604E+08 2 25 0 0 3 4 0 0.0000000000E+00 0.0000000000E+00 4.8412291828E+02 5.0000000000E+02 1.2500000000E+02 0.0000000000E+00 0.0000000000E+00 0.0000000000E+00 0.0000000000E+00 0.0000000000E+00 2 25 0 0 3 4 0 0.0000000000E+00 0.0000000000E+00 -4.8412291828E+02 5.0000000000E+02 1.2500000000E+02 0.0000000000E+00 0.0000000000E+00 0.0000000000E+00 0.0000000000E+00 0.0000000000E+00 1 25 1 2 0 0 0 -1.4960220911E+02 -4.6042825611E+02 0.0000000000E+00 5.0000000000E+02 1.2500000000E+02 0.0000000000E+00 0.0000000000E+00 0.0000000000E+00 0.0000000000E+00 0.0000000000E+00 1 25 1 2 0 0 0 1.4960220911E+02 4.6042825611E+02 0.0000000000E+00 5.0000000000E+02 1.2500000000E+02 0.0000000000E+00 0.0000000000E+00 0.0000000000E+00 0.0000000000E+00 0.0000000000E+00 \end{verbatim} \end{scriptsize} \paragraph{ASCII SHORT:} This is basically the same as the HEPEVT standard, but very much abbreviated. The header line for each event is identical, but the first line per particle does only contain the PDG and the polarization, while the vertex information line is omitted. \begin{scriptsize} \begin{verbatim} 4 2 0 3.0574068604E+08 25 0 0.0000000000E+00 0.0000000000E+00 4.8412291828E+02 5.0000000000E+02 1.2500000000E+02 25 0 0.0000000000E+00 0.0000000000E+00 -4.8412291828E+02 5.0000000000E+02 1.2500000000E+02 25 0 -1.4960220911E+02 -4.6042825611E+02 0.0000000000E+00 5.0000000000E+02 1.2500000000E+02 25 0 1.4960220911E+02 4.6042825611E+02 0.0000000000E+00 5.0000000000E+02 1.2500000000E+02 \end{verbatim} \end{scriptsize} \paragraph{ASCII LONG:} Identical to the ASCII short format, but after each event there is a line containg two values: the value of the sample function to be integrated over phase space, so basically the squared matrix element including all normalization factors, flux factor, structure functions etc. \begin{scriptsize} \begin{verbatim} 4 2 0 3.0574068604E+08 25 0 0.0000000000E+00 0.0000000000E+00 4.8412291828E+02 5.0000000000E+02 1.2500000000E+02 25 0 0.0000000000E+00 0.0000000000E+00 -4.8412291828E+02 5.0000000000E+02 1.2500000000E+02 25 0 -1.4960220911E+02 -4.6042825611E+02 0.0000000000E+00 5.0000000000E+02 1.2500000000E+02 25 0 1.4960220911E+02 4.6042825611E+02 0.0000000000E+00 5.0000000000E+02 1.2500000000E+02 1.0000000000E+00 1.0000000000E+00 \end{verbatim} \end{scriptsize} \paragraph{ATHENA:} Quite similar to the HEPEVT ASCII format. The header line, however, does contain only two numbers: an event counter, and the number of particles in the event. The first line for each particle lacks the polarization information (irrelevant for the ATHENA environment), but has as leading entry an ordering number counting the particles in the event. The vertex information line has only the four relevant position entries. \begin{scriptsize} \begin{verbatim} 0 4 1 2 25 0 0 3 4 0.0000000000E+00 0.0000000000E+00 4.8412291828E+02 5.0000000000E+02 1.2500000000E+02 0.0000000000E+00 0.0000000000E+00 0.0000000000E+00 0.0000000000E+00 2 2 25 0 0 3 4 0.0000000000E+00 0.0000000000E+00 -4.8412291828E+02 5.0000000000E+02 1.2500000000E+02 0.0000000000E+00 0.0000000000E+00 0.0000000000E+00 0.0000000000E+00 3 1 25 1 2 0 0 -1.4960220911E+02 -4.6042825611E+02 0.0000000000E+00 5.0000000000E+02 1.2500000000E+02 0.0000000000E+00 0.0000000000E+00 0.0000000000E+00 0.0000000000E+00 4 1 25 1 2 0 0 1.4960220911E+02 4.6042825611E+02 0.0000000000E+00 5.0000000000E+02 1.2500000000E+02 0.0000000000E+00 0.0000000000E+00 0.0000000000E+00 0.0000000000E+00 \end{verbatim} \end{scriptsize} \paragraph{MOKKA:} Quite similar to the ASCII short format, but the event entries are the particle status, the PDG code, the first and last daughter, the three spatial components of the momentum, as well as the mass. \begin{scriptsize} \begin{verbatim} 4 2 0 3.0574068604E+08 2 25 3 4 0.0000000000E+00 0.0000000000E+00 4.8412291828E+02 1.2500000000E+02 2 25 3 4 0.0000000000E+00 0.0000000000E+00 -4.8412291828E+02 1.2500000000E+02 1 25 0 0 -1.4960220911E+02 -4.6042825611E+02 0.0000000000E+00 1.2500000000E+02 1 25 0 0 1.4960220911E+02 4.6042825611E+02 0.0000000000E+00 1.2500000000E+02 \end{verbatim} \end{scriptsize} \paragraph{LHA:} This is the implementation of the Les Houches Accord, as it was used in \whizard\ 1 and the old MadEvent. There is a first line containing six entries: 1. the number of particles in the event, \ttt{NUP}, 2. the subprocess identification index, \ttt{IDPRUP}, 3. the event weight, \ttt{XWGTUP}, 4. the scale of the process, \ttt{SCALUP}, 5. the value or status of $\alpha_{QED}$, \ttt{AQEDUP}, 6. the value for $\alpha_s$, \ttt{AQCDUP}. The next seven lines contain as many entries as there are particles in the event: the first one has the PDG codes, \ttt{IDUP}, the next two the first and second mother of the particles, \ttt{MOTHUP}, the fourth and fifth line the two color indices, \ttt{ICOLUP}, the next one the status of the particle, \ttt{ISTUP}, and the last line the polarization information, \ttt{ISPINUP}. At the end of the event there are as lines for each particles with the counter in the event and the four-vector of the particle. For more information on this event format confer~\cite{LesHouches}. \begin{scriptsize} \begin{verbatim} 25 25 5.0000000000E+02 5.0000000000E+02 -1 -1 -1 -1 3 1 1.0000000000E-01 1.0000000000E-03 1.0000000000E+00 42 4 1 3.0574068604E+08 1.000000E+03 -1.000000E+00 -1.000000E+00 25 25 25 25 0 0 1 1 0 0 2 2 0 0 0 0 0 0 0 0 -1 -1 1 1 9 9 9 9 1 5.0000000000E+02 0.0000000000E+00 0.0000000000E+00 4.8412291828E+02 2 5.0000000000E+02 0.0000000000E+00 0.0000000000E+00 -4.8412291828E+02 3 5.0000000000E+02 -1.4960220911E+02 -4.6042825611E+02 0.0000000000E+00 4 5.0000000000E+02 1.4960220911E+02 4.6042825611E+02 0.0000000000E+00 \end{verbatim} \end{scriptsize} \paragraph{LHEF:} This is the modern version of the Les Houches accord event format (LHEF), for the details confer the corresponding publication~\cite{LHEF}. \begin{scriptsize} \begin{verbatim}
WHIZARD 2.8.3
25 25 5.0000000000E+02 5.0000000000E+02 -1 -1 -1 -1 3 1 1.0000000000E-01 1.0000000000E-03 1.0000000000E+00 42 4 42 3.0574068604E+08 1.0000000000E+03 -1.0000000000E+00 -1.0000000000E+00 25 -1 0 0 0 0 0.0000000000E+00 0.0000000000E+00 4.8412291828E+02 5.0000000000E+02 1.2500000000E+02 0.0000000000E+00 9.0000000000E+00 25 -1 0 0 0 0 0.0000000000E+00 0.0000000000E+00 -4.8412291828E+02 5.0000000000E+02 1.2500000000E+02 0.0000000000E+00 9.0000000000E+00 25 1 1 2 0 0 -1.4960220911E+02 -4.6042825611E+02 0.0000000000E+00 5.0000000000E+02 1.2500000000E+02 0.0000000000E+00 9.0000000000E+00 25 1 1 2 0 0 1.4960220911E+02 4.6042825611E+02 0.0000000000E+00 5.0000000000E+02 1.2500000000E+02 0.0000000000E+00 9.0000000000E+00
\end{verbatim} \end{scriptsize} Note that for the LHEF format, there are different versions according to the different stages of agreement. They can be addressed from within the \sindarin\ file by setting the string variable \ttt{\$lhef\_version} to one of (at the moment) three values: \ttt{"1.0"}, \ttt{"2.0"}, or \ttt{"3.0"}. The examples above corresponds (as is indicated in the header) to the version \ttt{"1.0"} of the LHEF format. Additional information in form of alternative squared matrix elements or event weights in the event are the most prominent features of the other two more advanced versions. For more details confer the literature. \vspace{.5cm} Sample files for the default ASCII format as well as for the debug event format are shown in the appendix. %%%%%%%%% \section[Interfaces to Parton Showers, Matching and Hadronization]{Interfaces to Parton Showers, Matching\\and Hadronization} This section describes the interfaces to the internal parton shower as well as the parton shower and hadronization routines from \pythia. Moreover, our implementation of the MLM matching making use of the parton showers is described. Sample \sindarin\ files are located in the \ttt{share/examples} directory. All input files come in two versions, one using the internal shower, ending in \ttt{W.sin}, and one using \pythia's shower, ending in \ttt{P.sin}. Thus we state all file names as ending with \ttt{X.sin}, where \ttt{X} has to be replaced by either \ttt{W} or \ttt{P}. The input files include \ttt{EENoMatchingX.sin} and \ttt{DrellYanNoMatchingX.sin} for $e^+ e^- \to hadrons$ and $p\bar{p} \to Z$ without matching. The corresponding \sindarin\ files with matching enabled are \ttt{EEMatching2X.sin} to \ttt{EEMatching5X.sin} for $e^+ e^- \to hadrons$ with a different number of partons included in the matrix element and \ttt{DrallYanMatchingX.sin} for Drell-Yan with one matched emission. \subsection{Parton Showers and Hadronization} From version 2.1 onwards, \whizard\ contains an implementation of an analytic parton shower as presented in \cite{Kilian:2011ka}, providing the opportunity to perform the parton shower from whithin \whizard. Moreover, an interface to \pythia\ is included, which can be used to delegate the parton shower to \pythia. The same interface can be used to hadronize events using the generated events using \pythia's hadronization routines. Note that by \pythia's default, when performing initial-state radiation multiple interactions are included and when performing the hadronization hadronic decays are included. If required, these additional steps have to be switched off using the corresponding arguments for \pythia's \ttt{PYGIVE} routine vie the \ttt{\$ps\_PYTHIA\_PYGIVE} string. Note that from version 2.2.4 on the earlier flag \ttt{--enable-shower} flag has been abandoned, and there is only a flag to either compile or not compile the interally attached \pythia\ttt{6} package (\ttt{--enable-pythia6}) last release of the \fortran\ \pythia, v6.427) as well as the interface. It can be invoked by the following \sindarin\ keywords:\\[2ex] % \centerline{\begin{tabular}{|l|l|} \hline\ttt{?ps\_fsr\_active = true} & master switch for final-state parton showers\\\hline \ttt{?ps\_isr\_active = true} & master switch for initial-state parton showers\\\hline \ttt{?ps\_taudec\_active = true} & master switch for $\tau$ decays (at the moment only via \ttt{TAUOLA}\\\hline \ttt{?hadronization\_active = true} & master switch to enable hadronization\\\hline \ttt{\$shower\_method = "PYTHIA6"} & switch to use \pythiasix's parton shower instead of \\ & \whizard's own shower\\\hline \end{tabular}}\mbox{} \vspace{4mm} If either \ttt{?ps\_fsr\_active} or \ttt{?ps\_isr\_active} is set to \verb|true|, the event will be transferred to the internal shower routines or the \pythia\ data structures, and the chosen shower steps (initial- and final-state radiation) will be performed. If hadronization is enabled via the \ttt{?hadronization\_active} switch, \whizard\ will call \pythia's hadronization routine. The hadron\-ization can be applied to events showered using the internal shower or showered using \pythia's shower routines, as well as unshowered events. Any necessary transfer of event data to \pythia\ is automatically taken care of within \whizard's shower interface. The resulting (showered and/or hadronized) event will be transferred back to \whizard, the former final particles will be marked as intermediate. The analysis can be applied to a showered and/or hadronized event just like in the unshowered/unhadronized case. Any event file can be used and will contain the showered/hadronized event. Settings for the internal analytic parton shower are set via the following \sindarin\ variables:\\[2ex] \begin{description} \item[\ttt{ps\_mass\_cutoff}] The cut-off in virtuality, below which, partons are assumed to radiate no more. Used for both ISR and FSR. Given in $\mbox{GeV}$. (Default = 1.0) \item[\ttt{ps\_fsr\_lambda}] The value for $\Lambda$ used in calculating the value of the running coupling constant $\alpha_S$ for Final State Radiation. Given in $\mbox{GeV}$. (Default = 0.29) \item[\ttt{ps\_isr\_lambda}] The value for $\Lambda$ used in calculating the value of the running coupling constant $\alpha_S$ for Initial State Radiation. Given in $\mbox{GeV}$. (Default = 0.29) \item[\ttt{ps\_max\_n\_flavors}] Number of quark flavours taken into account during shower evolution. Meaningful choices are 3 to include $u,d,s$-quarks, 4 to include $u,d,s,c$-quarks and 5 to include $u,d,s,c,b$-quarks. (Default = 5) \item[\ttt{?ps\_isr\_alphas\_running}] Switch to decide between a constant $\alpha_S$, given by \ttt{ps\_fixed\_alphas}, and a running $\alpha_S$, calculated using \ttt{ps\_isr\_lambda} for ISR. (Default = true) \item[\ttt{?ps\_fsr\_alphas\_running}] Switch to decide between a constant $\alpha_S$, given by \ttt{ps\_fixed\_alphas}, and a running $\alpha_S$, calculated using \ttt{ps\_fsr\_lambda} for FSR. (Default = true) \item[\ttt{ps\_fixed\_alphas}] Fixed value of $\alpha_S$ for the parton shower. Used if either one of the variables \ttt{?ps\_fsr\_alphas\_running} or \ttt{?ps\_isr\_alphas\_running} are set to \verb|false|. (Default = 0.0) \item[\ttt{?ps\_isr\_angular\_ordered}] Switch for angular ordered ISR. (Default = true )\footnote{The FSR is always simulated with angular ordering enabled.} \item[\ttt{ps\_isr\_primordial\_kt\_width}] The width in $\mbox{GeV}$ of the Gaussian assumed to describe the transverse momentum of partons inside the proton. Other shapes are not yet implemented. (Default = 0.0) \item[\ttt{ps\_isr\_primordial\_kt\_cutoff}] The maximal transverse momentum in $\mbox{GeV}$ of a parton inside the proton. Used as a cut-off for the Gaussian. (Default = 5.0) \item[\ttt{ps\_isr\_z\_cutoff}] Maximal $z$-value in initial state branchings. (Default = 0.999) \item[\ttt{ps\_isr\_minenergy}] Minimal energy in $\mbox{GeV}$ of an emitted timelike or final parton. Note that the energy is not calculated in the labframe but in the center-of-mas frame of the two most initial partons resolved so far, so deviations may occur. (Default = 1.0) \item[\ttt{ps\_isr\_tscalefactor}] Factor for the starting scale in the initial state shower evolution. ( Default = 1.0 ) \item[\ttt{?ps\_isr\_only\_onshell\_emitted\_partons}] Switch to allow only for on-shell emitted partons, thereby rejecting all possible final state parton showers starting from partons emitted during the ISR. (Default = false) \end{description} Settings for the \pythia\ are transferred using the following \sindarin\ variables:\\[2ex] \centerline{\begin{tabular}{|l|l|} \hline\ttt{?ps\_PYTHIA\_verbose} & if set to false, output from \pythia\ will be suppressed\\\hline \ttt{\$ps\_PYTHIA\_PYGIVE} & a string containing settings transferred to \pythia's \ttt{PYGIVE} subroutine.\\ & The format is explained in the \pythia\ manual. The limitation to 100 \\ & characters mentioned there does not apply here, the string is split \\ & appropriately before being transferred to \pythia.\\\hline \end{tabular}}\mbox{} \vspace{4mm} Note that the included version of \pythia\ uses \lhapdf\ for initial state radiation whenever this is available, but the PDF set has to be set manually in that case using the keyword \ttt{ps\_PYTHIA\_PYGIVE}. \subsection{Parton shower -- Matrix Element Matching} Along with the inclusion of the parton showers, \whizard\ includes an implementation of the MLM matching procedure. For a detailed description of the implemented steps see \cite{Kilian:2011ka}. The inclusion of MLM matching still demands some manual settings in the \sindarin\ file. For a given base process and a matching of $N$ additional jets, all processes that can be obtained by attaching up to $N$ QCD splittings, either a quark emitting a gluon or a gluon splitting into two quarks ar two gluons, have to be manually specified as additional processes. These additional processes need to be included in the \ttt{simulate} statement along with the original process. The \sindarin\ variable \ttt{mlm\_nmaxMEjets} has to be set to the maximum number of additional jets $N$. Moreover additional cuts have to be specified for the additional processes. \begin{verbatim} alias quark = u:d:s:c alias antiq = U:D:S:C alias j = quark:antiq:g ?mlm_matching = true mlm_ptmin = 5 GeV mlm_etamax = 2.5 mlm_Rmin = 1 cuts = all Dist > mlm_Rmin [j, j] and all Pt > mlm_ptmin [j] and all abs(Eta) < mlm_etamax [j] \end{verbatim} Note that the variables \ttt{mlm\_ptmin}, \ttt{mlm\_etamax} and \ttt{mlm\_Rmin} are used by the matching routine. Thus, replacing the variables in the \ttt{cut} expression and omitting the assignment would destroy the matching procedure. The complete list of variables introduced to steer the matching procedure is as follows: \begin{description} \item[\ttt{?mlm\_matching\_active}] Master switch to enable MLM matching. (Default = false) \item[\ttt{mlm\_ptmin}] Minimal transverse momentum, also used in the definition of a jet \item[\ttt{mlm\_etamax}] Maximal absolute value of pseudorapidity $\eta$, also used in defining a jet \item[\ttt{mlm\_Rmin}] Minimal $\eta-\phi$ distance $R_{min}$ \item[\ttt{mlm\_nmaxMEjets}] Maximum number of jets $N$ \item[\ttt{mlm\_ETclusfactor}] Factor to vary the jet definition. Should be $\geq 1$ for complete coverage of phase space. (Default = 1) \item[\ttt{mlm\_ETclusminE}] Minimal energy in the variation of the jet definition \item[\ttt{mlm\_etaclusfactor}] Factor in the variation of the jet definition. Should be $\leq 1$ for complete coverage of phase space. (Default = 1) \item[\ttt{mlm\_Rclusfactor}] Factor in the variation of the jet definition. Should be $\ge 1$ for complete coverage of phase space. (Default = 1) \end{description} The variation of the jet definition is a tool to asses systematic uncertainties introduced by the matching procedure (See section 3.1 in \cite{Kilian:2011ka}). %%%%%%%%% \section{Rescanning and recalculating events} \label{sec:rescan} In the simplest mode of execution, \whizard\ handles its events at the point where they are generated. It can apply event transforms such as decays or shower (see above), it can analyze the events, calculate and plot observables, and it can output them to file. However, it is also possible to apply two different operations to those events in parallel, or to reconsider and rescan an event sample that has been previously generated. We first discuss the possibilities that \ttt{simulate} offers. For each event, \whizard\ calculates the matrix element for the hard interaction, supplements this by Jacobian and phase-space factors in order to obtain the event weight, optionally applies a rejection step in order to gather uniformly weighted events, and applies the cuts and analysis setup. We may ask about the event matrix element or weight, or the analysis result, that we would have obtained for a different setting. To this end, there is an \ttt{alt\_setup} option. This option allows us to recalculate, event by event, the matrix element, weight, or analysis contribution with a different parameter set but identical kinematics. For instance, we may evaluate a distribution for both zero and non-zero anomalous coupling \ttt{fw} and enter some observable in separate histograms: \begin{footnotesize} \begin{verbatim} simulate (some_proc) { fw = 0 analysis = record hist1 (eval Pt [H]) alt_setup = { fw = 0.01 analysis = record hist2 (eval Pt [H]) } } \end{verbatim} \end{footnotesize} In fact, the \ttt{alt\_setup} object is not restricted to a single code block (enclosed in curly braces) but can take a list of those, \begin{footnotesize} \begin{verbatim} alt_setup = { fw = 0.01 }, { fw = 0.02 }, ... \end{verbatim} \end{footnotesize} Each block provides the environment for a separate evaluation of the event data. The generation of these events, i.e., their kinematics, is still steered by the primary environment. The \ttt{alt\_setup} blocks may modify various settings that affect the evaluation of an event, including physical parameters, PDF choice, cuts and analysis, output format, etc. This must not (i.e., cannot) affect the kinematics of an event, so don't modify particle masses. When applying cuts, they can only reduce the generated event sample, so they apply on top of the primary cuts for the simulation. Alternatively, it is possible to \ttt{rescan} a sample that has been generated by a previous \ttt{simulate} command: \begin{footnotesize} \begin{verbatim} simulate (some_proc) { $sample = "my_events" analysis = record hist1 (eval Pt [H]) } ?update_sqme = true ?update_weight = true rescan "my_events" (some_proc) { fw = 0.01 analysis = record hist2 (eval Pt [H]) } rescan "my_events" (some_proc) { fw = 0.05 analysis = record hist3 (eval Pt [H]) } \end{verbatim} \end{footnotesize} In more complicated situation, rescanning is more transparent and offers greater flexibility than doing all operations at the very point of event generation. Combining these features with the \ttt{scan} looping construct, we already cover a considerable range of applications. (There are limitations due to the fact that \sindarin\ doesn't provide array objects, yet.) Note that the \ttt{rescan} construct also allows for an \ttt{alt\_setup} option. You may generate a new sample by rescanning, for which you may choose any output format: \begin{footnotesize} \begin{verbatim} rescan "my_events" (some_proc) { selection = all Pt > 100 GeV [H] $sample = "new_events" sample_format = lhef } \end{verbatim} \end{footnotesize} The event sample that you rescan need not be an internal raw \whizard\ file, as above. You may rescan a LHEF file, \begin{footnotesize} \begin{verbatim} rescan "lhef_events" (proc) { $rescan_input_format = "lhef" } \end{verbatim} \end{footnotesize} This file may have any origin, not necessarily from \whizard. To understand such an external file, \whizard\ must be able to reconstruct the hard process and match it to a process with a known name (e.g., \ttt{proc}), that has been defined in the \sindarin\ script previously. Within its limits, \whizard\ can thus be used for translating an event sample from one format to another format. There are three important switches that control the rescanning behavior. They can be set or unset independently. \begin{itemize} \item \ttt{?update\_sqme} (default: false). If true, \whizard\ will recalculate the hard matrix element for each event. When applying an analysis, the recalculated squared matrix element (averaged and summed over quantum numbers as usual) is available as the variable \ttt{sqme\_prc}. This may be related to \ttt{sqme\_ref}, the corresponding value in the event file, if available. (For the \ttt{alt\_env} option, this switch is implied.) \item \ttt{?update\_weight} (default: false). If true, \whizard\ will recalculate the event weight according to the current environment and apply this to the event. In particular, the user may apply a \ttt{reweight} expression. In an analysis, the new weight value is available as \ttt{weight\_prc}, to be related to \ttt{weight\_ref} from the sample. The updated weight will be applied for histograms and averages. An unweighted event sample will thus be transformed into a weighted event sample. (This switch is also implied for the \ttt{alt\_env} option.) \item \ttt{?update\_event} (default: false). If true, \whizard\ will generate a new decay chain etc., if applicable. That is, it reuses just the particles in the hard process. Otherwise, the complete event is kept as it is written to file. \end{itemize} For these options to make sense, \whizard\ must have access to a full process object, so the \sindarin\ script must contain not just a definition but also a \ttt{compile} command for the matrix elements in question. If an event file (other than raw format) contains several processes as a mixture, they must be identifiable by a numeric ID. \whizard\ will recognize the processes if their respective \sindarin\ definitions contain appropriate \ttt{process\_num\_id} options, such as \begin{footnotesize} \begin{verbatim} process foo = u, ubar => d, dbar { process_num_id = 42 } \end{verbatim} \end{footnotesize} Certain event-file formats, such as LHEF, support alternative matrix-element values or weights. \whizard\ can thus write both original and recalculated matrix-element and weight values. Other formats support only a single event weight, so the \ttt{?update\_weight} option is necessary for a visible effect. External event files in formats such as LHEF, HepMC, or LCIO, also may carry information about the value of the strong coupling $\alpha_s$ and the energy scale of each event. This information will also be provided by \whizard\ when writing external event files. When such an event file is rescanned, the user has the choice to either user the $\alpha_s$ value that \whizard\ defines in the current context (or the method for obtaining an event-specific running $\alpha_s$ value), or override this for each event by using the value in the event file. The corresponding parameter is \ttt{?use\_alphas\_from\_file}, which is false by default. Analogously, the parameter \ttt{?use\_scale\_from\_file} may be set to override the scale definition in the current context. Obviously, these settings influence matrix-element recalculation and therefore require \ttt{?update\_sqme} to be set in order to become operational. %%%%%%%%% \section{Negative weight events} For usage at NLO refer to Subsection~\ref{ss:fixedorderNLOevents}. In case, you have some other mechanism to produce events with negative weights (e.g. with the \ttt{weight = {\em }} command), keep in mind that you should activate \ttt{?negative\_weights = true} and \ttt{unweighted = false}. The generation of unweighted events with varying sign (also known as events and counter events) is currently not supported. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \chapter{Data Visualization} \label{chap:visualization} \section{GAMELAN} The data values and tables that we have introduced in the previous section can be visualized using built-in features of \whizard. To be precise, \whizard\ can write \LaTeX\ code which incorporates code in the graphics language GAMELAN to produce a pretty-printed account of observables, histograms, and plots. GAMELAN is a macro package for MetaPost, which is part of the \TeX/\LaTeX\ family. MetaPost, a derivative of Knuth's MetaFont language for font design, is usually bundled with the \TeX\ distribution, but might need a separate switch for installation. The GAMELAN macros are contained in a subdirectory of the \whizard\ package. Upon installation, they will be installed in the appropriate directory, including the \ttt{gamelan.sty} driver for \LaTeX. \whizard\ uses a subset of GAMELAN's graphics macros directly, but it allows for access to the full package if desired. An (incomplete) manual for GAMELAN can be found in the \ttt{share/doc} subdirectory of the \whizard\ system. \whizard\ itself uses a subset of the GAMELAN capabilities, interfaced by \sindarin\ commands and parameters. They are described in this chapter. To process analysis output beyond writing tables to file, the \ttt{write\_analysis} command described in the previous section should be replaced by \ttt{compile\_analysis}, with the same syntax: \begin{quote} \begin{footnotesize} \ttt{compile\_analysis (\emph{analysis-tags}) \{ \ttt{\emph{options}} \}} \end{footnotesize} \end{quote} where \ttt{\emph{analysis-tags}}, a comma-separated list of analysis objects, is optional. If there are no tags, all analysis objects are processed. The \ttt{\emph{options}} script of local commands is also optional, of course. This command will perform the following actions: \begin{enumerate} \item It writes a data file in default format, as \ttt{write\_analysis} would do. The file name is given by \ttt{\$out\_file}, if nonempty. The file must not be already open, since the command needs a self-contained file, but the name is otherwise arbitrary. If the value of \ttt{\$out\_file} is empty, the default file name is \ttt{whizard\_analysis.dat}. \item It writes a driver file for the chosen datasets, whose name is derived from the data file by replacing the file extension of the data file with the extension \ttt{.tex}. The driver file is a \LaTeX\ source file which contains embedded GAMELAN code that handles the selected graphics data. In the \LaTeX\ document, there is a separate section for each contained dataset. Furthermore, a process-/analysis-specific makefile with the name \ttt{\_ana.makefile} is created that can be used to generate postscript or PDF output from the \LaTeX\ source. If the steering flag \ttt{?analysis\_file\_only} is set to \ttt{true}, then the \LaTeX\ file and the makefile are only written, but no execution of the makefile resulting in compilation of the \LaTeX\ code (see the next item) is invoked. \item As mentioned above, if the flag \ttt{?analysis\_file\_only} is set to \ttt{false} (which is the default), the driver file is processed by \LaTeX (invoked by calling the makefile with the name \ttt{\_ana.makefile}), which generates an appropriate GAMELAN source file with extension \ttt{.mp}. This code is executed (calling GAMELAN/MetaPost, and again \LaTeX\ for typesetting embedded labels). There is a second \LaTeX\ pass (automatically done by the makefile) which collects the results, and finally conversion to PostScript and PDF formats. \end{enumerate} The resulting PostScript or PDF file -- the file name is the name of the data file with the extension replaced by \ttt{.ps} or \ttt{.pdf}, respectively -- can be printed or viewed with an appropriate viewer such as \ttt{gv}. The viewing command is not executed automatically by \whizard. Note that \LaTeX\ will write further files with extensions \ttt{.log}, \ttt{.aux}, and \ttt{.dvi}, and GAMELAN will produce auxiliary files with extensions \ttt{.ltp} and \ttt{.mpx}. The log file in particular, could overwrite \whizard's log file if the basename is identical. Be careful to use a value for \ttt{\$out\_file} which is not likely to cause name clashes. \subsection{User-specific changes} In the case, that the \sindarin\ \ttt{compile\_analysis} command is invoked and the flag named \ttt{?analysis\_file\_only} is not changed from its default value \ttt{false}, \whizard\ calls the process-/analysis-specific makefile triggering the compilation of the \LaTeX\ code and the GAMELAN plots and histograms. If the user wants to edit the analysis output, for example changing captions, headlines, labels, properties of the plots, graphs and histograms using GAMELAN specials etc., this is possible and the output can be regenerated using the makefile. The user can also directly invoke the GAMELAN script, \ttt{whizard-gml}, that is installed in the binary directly along with the \whizard\ binary and other scripts. Note however, that the \LaTeX\ environment for the specific style files have to be set by hand (the command line invocation in the makefile does this automatically). Those style files are generally written into \ttt{share/texmf/whizard/} directory. The user can execute the commands in the same way as denoted in the process-/analysis-specific makefile by hand. %%%%% \section{Histogram Display} %%%%% \section{Plot Display} \section{Graphs} \label{sec:graphs} Graphs are an additional type of analysis object. In contrast to histograms and plots, they do not collect data directly, but they rather act as containers for graph elements, which are copies of existing histograms and plots. Their single purpose is to be displayed by the GAMELAN driver. Graphs are declared by simple assignments such as \begin{quote} \begin{footnotesize} \ttt{graph g1 = hist1} \\ \ttt{graph g2 = hist2 \& hist3 \& plot1} \end{footnotesize} \end{quote} The first declaration copies a single histogram into the graph, the second one copies two histograms and a plot. The syntax for collecting analysis objects uses the \ttt{\&} concatenation operator, analogous to string concatenation. In the assignment, the rhs must contain only histograms and plots. Further concatenating previously declared graphs is not supported. After the graph has been declared, its contents can be written to file (\ttt{write\_analysis}) or, usually, compiledd by the \LaTeX/GAMELAN driver via the \ttt{compile\_analysis} command. The graph elements on the right-hand side of the graph assignment are copied with their current data content. This implies a well-defined order of statements: first, histograms and plots are declared, then they are filled via \ttt{record} commands or functions, and finally they can be collected for display by graph declarations. A simple graph declaration without options as above is possible, but usually there are option which affect the graph display. There are two kinds of options: graph options and drawing options. Graph options apply to the graph as a whole (title, labels, etc.) and are placed in braces on the lhs of the assigment. Drawing options apply to the individual graph elements representing the contained histograms and plots, and are placed together with the graph element on the rhs of the assignment. Thus, the complete syntax for assigning multiple graph elements is \begin{quote} \begin{footnotesize} \ttt{graph \emph{graph-tag} \{ \emph{graph-options} \}} \\ \ttt{= \emph{graph-element-tag1} \{ \emph{drawing-options1} \}} \\ \ttt{\& \emph{graph-element-tag2} \{ \emph{drawing-options2} \}} \\ \ldots \end{footnotesize} \end{quote} This form is recommended, but graph and drawing options can also be set as global parameters, as usual. We list the supported graph and drawing options in Tables~\ref{tab:graph-options} and \ref{tab:drawing-options}, respectively. \begin{table} \caption{Graph options. The content of strings of type \LaTeX\ must be valid \LaTeX\ code (containing typesetting commands such as math mode). The content of strings of type GAMELAN must be valid GAMELAN code. If a graph bound is kept \emph{undefined}, the actual graph bound is determined such as not to crop the graph contents in the selected direction.} \label{tab:graph-options} \begin{center} \begin{tabular}{|l|l|l|l|} \hline Variable & Default & Type & Meaning \\ \hline\hline \ttt{\$title} & \ttt{""} & \LaTeX & Title of the graph = subsection headline \\ \hline \ttt{\$description} & \ttt{""} & \LaTeX & Description text for the graph \\ \hline \ttt{\$x\_label} & \ttt{""} & \LaTeX & $x$-axis label \\ \hline \ttt{\$y\_label} & \ttt{""} & \LaTeX & $y$-axis label \\ \hline \ttt{graph\_width\_mm} & 130 & Integer & graph width (on paper) in mm \\ \hline \ttt{graph\_height\_mm} & 90 & Integer & graph height (on paper) in mm \\ \hline \ttt{?x\_log} & false & Logical & Whether the $x$-axis scale is linear or logarithmic \\ \hline \ttt{?y\_log} & false & Logical & Whether the $y$-axis scale is linear or logarithmic \\ \hline \ttt{x\_min} & \emph{undefined} & Real & Lower bound for the $x$ axis \\ \hline \ttt{x\_max} & \emph{undefined} & Real & Upper bound for the $x$ axis \\ \hline \ttt{y\_min} & \emph{undefined} & Real & Lower bound for the $y$ axis \\ \hline \ttt{y\_max} & \emph{undefined} & Real & Upper bound for the $y$ axis \\ \hline \ttt{gmlcode\_bg} & \ttt{""} & GAMELAN & Code to be executed before drawing \\ \hline \ttt{gmlcode\_fg} & \ttt{""} & GAMELAN & Code to be executed after drawing \\ \hline \end{tabular} \end{center} \end{table} \begin{table} \caption{Drawing options. The content of strings of type GAMELAN must be valid GAMELAN code. The behavior w.r.t. the flags with \emph{undefined} default value depends on the type of graph element. Histograms: draw baseline, piecewise, fill area, draw curve, no errors, no symbols; Plots: no baseline, no fill, draw curve, no errors, no symbols.} \label{tab:drawing-options} \begin{center} \begin{tabular}{|l|l|l|l|} \hline Variable & Default & Type & Meaning \\ \hline\hline \ttt{?draw\_base} & \emph{undefined} & Logical & Whether to draw a baseline for the curve \\ \hline \ttt{?draw\_piecewise} & \emph{undefined} & Logical & Whether to draw bins separately (histogram) \\ \hline \ttt{?fill\_curve} & \emph{undefined} & Logical & Whether to fill area between baseline and curve \\ \hline \ttt{\$fill\_options} & \ttt{""} & GAMELAN & Options for filling the area \\ \hline \ttt{?draw\_curve} & \emph{undefined} & Logical & Whether to draw the curve as a line \\ \hline \ttt{\$draw\_options} & \ttt{""} & GAMELAN & Options for drawing the line \\ \hline \ttt{?draw\_errors} & \emph{undefined} & Logical & Whether to draw error bars for data points \\ \hline \ttt{\$err\_options} & \ttt{""} & GAMELAN & Options for drawing the error bars \\ \hline \ttt{?draw\_symbols} & \emph{undefined} & Logical & Whether to draw symbols at data points \\ \hline \ttt{\$symbol} & Black dot & GAMELAN & Symbol to be drawn \\ \hline \ttt{gmlcode\_bg} & \ttt{""} & GAMELAN & Code to be executed before drawing \\ \hline \ttt{gmlcode\_fg} & \ttt{""} & GAMELAN & Code to be executed after drawing \\ \hline \end{tabular} \end{center} \end{table} \section{Drawing options} The options for coloring lines, filling curves, or choosing line styles make use of macros in the GAMELAN language. At this place, we do not intend to give a full account of the possiblities, but we rather list a few basic features that are likely to be useful for drawing graphs. \subsubsection{Colors} GAMELAN knows about basic colors identified by name: \begin{center} \ttt{black}, \ttt{white}, \ttt{red}, \ttt{green}, \ttt{blue}, \ttt{cyan}, \ttt{magenta}, \ttt{yellow} \end{center} More generically, colors in GAMELAN are RGB triplets of numbers (actually, numeric expressions) with values between 0 and 1, enclosed in brackets: \begin{center} \ttt{(\emph{r}, \emph{g}, \emph{b})} \end{center} To draw an object in color, one should apply the construct \ttt{withcolor \emph{color}} to its drawing code. The default color is always black. Thus, this will make a plot drawn in blue: \begin{quote} \begin{footnotesize} \ttt{\$draw\_options = "withcolor blue"} \end{footnotesize} \end{quote} and this will fill the drawing area of some histogram with an RGB color: \begin{quote} \begin{footnotesize} \ttt{\$fill\_options = "withcolor (0.8, 0.7, 1)"} \end{footnotesize} \end{quote} \subsubsection{Dashes} By default, lines are drawn continuously. Optionally, they can be drawn using a \emph{dash pattern}. Predefined dash patterns are \begin{center} \ttt{evenly}, \ttt{withdots}, \ttt{withdashdots} \end{center} Going beyond the predefined patterns, a generic dash pattern has the syntax \begin{center} \ttt{dashpattern (on \emph{l1} off \emph{l2} on} \ldots \ttt{)} \end{center} with an arbitrary repetition of \ttt{on} and \ttt{off} clauses. The numbers \ttt{\emph{l1}}, \ttt{\emph{l2}}, \ldots\ are lengths measured in pt. To apply a dash pattern, the option syntax \ttt{dashed \emph{dash-pattern}} should be used. Options strings can be concatenated. Here is how to draw in color with dashes: \begin{quote} \begin{footnotesize} \ttt{\$draw\_options = "withcolor red dashed evenly"} \end{footnotesize} \end{quote} and this draws error bars consisting of intermittent dashes and dots: \begin{quote} \begin{footnotesize} \ttt{\$err\_options = "dashed (withdashdots scaled 0.5)"} \end{footnotesize} \end{quote} The extra brackets ensure that the scale factor $1/2$ is applied only the dash pattern. \subsubsection{Hatching} Areas (e.g., below a histogram) can be filled with plain colors by the \ttt{withcolor} option. They can also be hatched by stripes, optionally rotated by some angle. The syntax is completely analogous to dashes. There are two predefined \emph{hatch patterns}: \begin{center} \ttt{withstripes}, \ttt{withlines} \end{center} and a generic hatch pattern is written \begin{center} \ttt{hatchpattern (on \emph{w1} off \emph{w2} on} \ldots \ttt{)} \end{center} where the numbers \ttt{\emph{l1}}, \ttt{\emph{l2}}, \ldots\ determine the widths of the stripes, measured in pt. When applying a hatch pattern, the pattern may be rotated by some angle (in degrees) and scaled. This looks like \begin{quote} \begin{footnotesize} \ttt{\$fill\_options = "hatched (withstripes scaled 0.8 rotated 60)"} \end{footnotesize} \end{quote} \subsubsection{Smooth curves} Plot points are normally connected by straight lines. If data are acquired by statistical methods, such as Monte Carlo integration, this is usually recommended. However, if a plot is generated using an analytic mathematical formula, or with sufficient statistics to remove fluctuations, it might be appealing to connect lines by some smooth interpolation. GAMELAN can switch on spline interpolation by the specific drawing option \ttt{linked smoothly}. Note that the results can be surprising if the data points do have sizable fluctuations or sharp kinks. \subsubsection{Error bars} Plots and histograms can be drawn with error bars. For histograms, only vertical error bars are supported, while plot points can have error bars in $x$ and $y$ direction. Error bars are switched on by the \ttt{?draw\_errors} flag. There is an option to draw error bars with ticks: \ttt{withticks} and an alternative option to draw arrow heads: \ttt{witharrows}. These can be used in the \ttt{\$err\_options} string. \subsubsection{Symbols} To draw symbols at plot points (or histogram midpoints), the flag \ttt{?draw\_symbols} has to be switched on. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \chapter{User Interfaces for WHIZARD} \label{chap:userint} \section{Command Line and \sindarin\ Input Files} \label{sec:cmdline-options} The standard way of using \whizard\ involves a command script written in \sindarin. This script is executed by \whizard\ by mentioning it on the command line: \begin{interaction} whizard script-name.sin \end{interaction} You may specify several script files on the command line; they will be executed consecutively. If there is no script file, \whizard\ will read commands from standard input. Hence, this is equivalent: \begin{interaction} cat script-name.sin | whizard \end{interaction} When executed from the command line, \whizard\ accepts several options. They are given in long form, i.e., they begin with two dashes. Values that belong to options follow the option string, separated either by whitespace or by an equals sign. Hence, \ttt{--prefix /usr} and \ttt{--prefix=/usr} are equivalent. Some options are also available in short form, a single dash with a single letter. Short-form options can be concatenated, i.e., a dash followed by several option letters. The first set of options is intended for normal operation. \begin{description} \item[\ttt{--debug AREA}]: Switch on debug output for \ttt{AREA}. \ttt{AREA} can be one of \whizard's source directories or \ttt{all}. \item[\ttt{--debug2 AREA}]: Switch on more verbose debug output for \ttt{AREA}. \item[\ttt{--single-event}]: Only compute one phase-space point (for debugging). \item[\ttt{--execute COMMANDS}]: Execute \ttt{COMMANDS} as a script before the script file (see below). Short version: \ttt{-e} \item[\ttt{--file CMDFILE}]: Execute commands in \ttt{CMDFILE} before the main script file (see below). Short version: \ttt{-f} \item[\ttt{--help}]: List the available options and exit. Short version: \ttt{-h} \item[\ttt{--interactive}]: Run \whizard\ interactively. See Sec.~\ref{sec:whish}. Short version: \ttt{-i}. \item[\ttt{--library LIB}]: Preload process library \ttt{LIB} (instead of the default \ttt{processes}). Short version: \ttt{-l}. \item[\ttt{--localprefix DIR}]: Search in \ttt{DIR} for local models. Default is \ttt{\$HOME/.whizard}. \item[\ttt{--logfile \ttt{FILE}}]: Write log to \ttt{FILE}. Default is \ttt{whizard.log}. Short version: \ttt{-L}. \item[\ttt{--logging}]: Start logging on startup (default). \item[\ttt{--model MODEL}]: Preload model \ttt{MODEL}. Default is the Standard Model \ttt{SM}. Short version: \ttt{-m}. \item[\ttt{--no-banner}]: Do not display banner at startup. \item[\ttt{--no-library}]: Do not preload a library. \item[\ttt{--no-logfile}]: Do not write a logfile. \item[\ttt{--no-logging}]: Do not issue information into the logfile. \item[\ttt{--no-model}]: Do not preload a specific physics model. \item[\ttt{--no-rebuild}]: Do not force a rebuild. \item[\ttt{--query VARIABLE}]: Display documentation of \ttt{VARIABLE}. Short version: \ttt{-q}. \item[\ttt{--rebuild}]: Do not preload a process library and do all calculations from scratch, even if results exist. This combines all rebuild options. Short version: \ttt{-r}. \item[\ttt{--rebuild-library}]: Rebuild the process library, even if code exists. \item[\ttt{--rebuild-phase-space}]: Rebuild the phase space setup, even if it exists. \item[\ttt{--rebuild-grids}]: Redo the integration, even if previous grids and results exist. \item[\ttt{--rebuild-events}]: Redo event generation, discarding previous event files. \item[\ttt{--show-config}]: Show build-time configuration. \item[\ttt{--version}]: Print version information and exit. Short version: \ttt{-V}. \item[-]: Any further options are interpreted as file names. \end{description} The second set of options refers to the configuration. They are relevant when dealing with a relocated \whizard\ installation, e.g., on a batch systems. \begin{description} \item[\ttt{--prefix DIR}]: Specify the actual location of the \whizard\ installation, including all subdirectories. \item[\ttt{--exec-prefix DIR}]: Specify the actual location of the machine-specific parts of the \whizard\ installation (rarely needed). \item[\ttt{--bindir DIR}]: Specify the actual location of the executables contained in the \whizard\ installation (rarely needed). \item[\ttt{--libdir DIR}]: Specify the actual location of the libraries contained in the \whizard\ installation (rarely needed). \item[\ttt{--includedir DIR}]: Specify the actual location of the include files contained in the \whizard\ installation (rarely needed). \item[\ttt{--datarootdir DIR}]: Specify the actual location of the data files contained in the \whizard\ installation (rarely needed). \item[\ttt{--libtool LOCAL\_LIBTOOL}]: Specify the actual location and name of the \ttt{libtool} script that should be used by \whizard. \item[\ttt{--lhapdfdir DIR}]: Specify the actual location and of the \lhapdf\ installation that should be used by \whizard. \end{description} The \ttt{--execute} and \ttt{--file} options allow for fine-tuning the command flow. The \whizard\ main program will concatenate all commands given in \ttt{--execute} commands together with all commands contained in \ttt{--file} options, in the order they are encountered, as a contiguous command stream that is executed \emph{before} the main script (in the example above, \ttt{script-name.sin}). Regarding the \ttt{--execute} option, commands that contain blanks must be enclosed in matching single- or double-quote characters since the individual tokens would otherwise be intepreted as separate option strings. Unfortunately, a Unix/Linux shell interpreter will strip quotes before handing the command string over to the program. In that situation, the quote-characters must be quoted themselves, or the string must be enclosed in quotes twice. Either version should work as a command line interpreted by the shell: \begin{interaction} whizard --execute \'int my_flag = 1\' script-name.sin whizard --execute "'int my_flag = 1'" script-name.sin \end{interaction} \section{WHISH -- The \whizard\ Shell/Interactive mode} \label{sec:whish} \whizard\ can be also run in the interactive mode using its own shell environment. This is called the \whizard\ Shell (WHISH). For this purpose, one starts with the command \begin{interaction} /home/user$ whizard --interactive \end{interaction} or \begin{interaction} /home/user$ whizard -i \end{interaction} \whizard\ will preload the Standard Model and display a command prompt: \begin{interaction} whish? \end{interaction} You now can enter one or more \sindarin\ commands, just as if they were contained in a script file. The commands are compiled and executed after you hit the ENTER key. When done, you get a new prompt. The WHISH can be closed by the \ttt{quit} command: \begin{verbatim} whish? quit \end{verbatim} Obviously, each input must be self-contained: commands must be complete, and conditionals or scans must be closed on the same line. If \whizard\ is run without options and without a script file, it also reads commands interactively, from standard input. The difference is that in this case, interactive input is multi-line, terminated by \ttt{Ctrl-D}, the script is then compiled and executed as a whole, and \whizard\ terminates. In WHISH mode, each input line is compiled and executed individually. Furthermore, fatal errors are masked, so in case of error the program does not terminate but returns to the WHISH command line. (The attempt to recover may fail in some circumstances, however.) \section{Graphical user interface} \emph{This is still experimental.} \whizard\ ships with a graphical interface that can be steered in a browser of your choice. It is located in \ttt{share/gui}. To use it, you have to run \ttt{npm install} (which will install javascript libraries locally in that folder) and \ttt{npm start} (which will start a local web server on your machine) in that folder. More technical details and how to get \ttt{npm} is discussed in \ttt{share/gui/README.md}. When it is running, you can access the GUI by entering \ttt{localhost:3000} as address in your browser. The GUI is separated into different tabs for basic settings, integration, simulation, cuts, scans, NLO and beams. You can select and enter what you are interested in and the GUI will produce a \sindarin\ file. You can use the GUI to run WHIZARD with that \sindarin\ or just produce it with the GUI and then tweak it further with an editor. In case you run it in the GUI, the log file will be updated in the browser as it is produced. Any \sindarin\ features that are not supported by the GUI can be added directly as "Additional Code". \section{WHIZARD as a library} \emph{This is planned, but not implemented yet.} %%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \chapter{Examples} \label{chap:examples} In this chapter we discuss the running and steering of \whizard\ with the help of several examples. These examples can be found in the \ttt{share/examples} directory of your installation. All of these examples are also shown on the \whizard\ Wiki page: \url{https://whizard.hepforge.org/trac/wiki}. \section{$Z$ lineshape at LEP I} By this example, we demonstrate how a scan over collision energies works, using as example the measurement of the $Z$ lineshape at LEP I in 1989. The \sindarin\ script for this example, \ttt{Z-lineshape.sin} can be found in the \ttt{share/examples} folder of the \whizard\ installation. We first use the Standard model as physics model: \begin{code} model = SM \end{code} Aliases for electron, muon and their antiparticles as leptons and those including the photon as particles in general are introduced: \begin{code} alias lep = e1:E1:e2:E2 alias prt = lep:A \end{code} Next, the two processes are defined, \eemm, and the same with an explicit QED photon: $e^+e^- \to \mu^+\mu^-\gamma$, \begin{code} process bornproc = e1, E1 => e2, E2 process rc = e1, E1 => e2, E2, A compile \end{code} and the processes are compiled. Now, we define some very loose cuts to avoid singular regions in phase space, name an infrared cutoff of 100 MeV for all particles, a cut on the angular separation from the beam axis and a di-particle invariant mass cut which regularizes collinear singularities: \begin{code} cuts = all E >= 100 MeV [prt] and all abs (cos(Theta)) <= 0.99 [prt] and all M2 >= (1 GeV)^2 [prt, prt] \end{code} For the graphical analysis, we give a description and labels for the $x$- and $y$-axis in \LaTeX\ syntax: \begin{code} $description = "A WHIZARD Example" $x_label = "$\sqrt{s}$/GeV" $y_label = "$\sigma(s)$/pb" \end{code} We define two plots for the lineshape of the \eemm\ process between 88 and 95 GeV, \begin{code} $title = "The Z Lineshape in $e^+e^-\to\mu^+\mu^-$" plot lineshape_born { x_min = 88 GeV x_max = 95 GeV } \end{code} and the same for the radiative process with an additional photon: \begin{code} $title = "The Z Lineshape in $e^+e^-\to\mu^+\mu^-\gamma$" plot lineshape_rc { x_min = 88 GeV x_max = 95 GeV } \end{code} %$ The next part of the \sindarin\ file actually performs the scan: \begin{code} scan sqrts = ((88.0 GeV => 90.0 GeV /+ 0.5 GeV), (90.1 GeV => 91.9 GeV /+ 0.1 GeV), (92.0 GeV => 95.0 GeV /+ 0.5 GeV)) { beams = e1, E1 integrate (bornproc) { iterations = 2:1000:"gw", 1:2000 } record lineshape_born (sqrts, integral (bornproc) / 1000) integrate (rc) { iterations = 5:3000:"gw", 2:5000 } record lineshape_rc (sqrts, integral (rc) / 1000) } \end{code} So from 88 to 90 GeV, we go in 0.5 GeV steps, then from 90 to 92 GeV in tenth of GeV, and then up to 95 GeV again in half a GeV steps. The partonic beam definition is redundant. Then, the born process is integrated, using a certain specification of calls with adaptation of grids and weights, as well as a final pass. The lineshape of the Born process is defined as a \ttt{record} statement, generating tuples of $\sqrt{s}$ and the Born cross section (converted from femtobarn to picobarn). The same happens for the radiative $2\to3$ process with a bit more iterations because of the complexity, and the definition of the corresponding lineshape record. If you run the \sindarin\ script, you will find an output like: \begin{scriptsize} \begin{Verbatim}[frame=single] | Process library 'default_lib': loading | Process library 'default_lib': ... success. $description = "A WHIZARD Example" $x_label = "$\sqrt{s}$/GeV" $y_label = "$\sigma(s)$/pb" $title = "The Z Lineshape in $e^+e^-\to\mu^+\mu^-$" x_min = 8.800000000000E+01 x_max = 9.500000000000E+01 $title = "The Z Lineshape in $e^+e^-\to\mu^+\mu^-\gamma$" x_min = 8.800000000000E+01 x_max = 9.500000000000E+01 sqrts = 8.800000000000E+01 | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 10713 | Initializing integration for process bornproc: | ------------------------------------------------------------------------ | Process [scattering]: 'bornproc' | Library name = 'default_lib' | Process index = 1 | Process components: | 1: 'bornproc_i1': e-, e+ => mu-, mu+ [omega] | ------------------------------------------------------------------------ | Beam structure: e-, e+ | Beam data (collision): | e- (mass = 5.1099700E-04 GeV) | e+ (mass = 5.1099700E-04 GeV) | sqrts = 8.800000000000E+01 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'bornproc_i1.phs' | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: Using 1 equivalence between channels. | Phase space: wood | Applying user-defined cuts. | OpenMP: Using 8 threads | Starting integration for process 'bornproc' | Integrate: iterations = 2:1000:"gw", 1:2000 | Integrator: 1 chains, 1 channels, 2 dimensions | Integrator: Using VAMP channel equivalences | Integrator: 1000 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 800 2.5881432E+05 1.85E+03 0.72 0.20* 48.97 2 800 2.6368495E+05 9.25E+02 0.35 0.10* 28.32 |-----------------------------------------------------------------------------| 2 1600 2.6271122E+05 8.28E+02 0.32 0.13 28.32 5.54 2 |-----------------------------------------------------------------------------| 3 1988 2.6313791E+05 5.38E+02 0.20 0.09* 35.09 |-----------------------------------------------------------------------------| 3 1988 2.6313791E+05 5.38E+02 0.20 0.09 35.09 |=============================================================================| | Time estimate for generating 10000 events: 0d:00h:00m:05s [.......] \end{Verbatim} \end{scriptsize} %$ and then the integrations for the other energy points of the scan will \begin{figure} \centering \includegraphics[width=.47\textwidth]{Z-lineshape_1} \includegraphics[width=.47\textwidth]{Z-lineshape_2} \caption{\label{fig:zlineshape} $Z$ lineshape in the dimuon final state (left), and with an additional photon (right)} \end{figure} follow, and finally the same is done for the radiative process as well. At the end of the \sindarin\ script we compile the graphical \whizard\ analysis and direct the data for the plots into the file \ttt{Z-lineshape.dat}: \begin{code} compile_analysis { $out_file = "Z-lineshape.dat" } \end{code} %$ In this case there is no event generation, but simply the cross section values for the scan are dumped into a data file: \begin{scriptsize} \begin{Verbatim}[frame=single] $out_file = "Z-lineshape.dat" | Opening file 'Z-lineshape.dat' for output | Writing analysis data to file 'Z-lineshape.dat' | Closing file 'Z-lineshape.dat' for output | Compiling analysis results display in 'Z-lineshape.tex' \end{Verbatim} \end{scriptsize} %$ Fig.~\ref{fig:zlineshape} shows the graphical \whizard\ output of the $Z$ lineshape in the dimuon final state from the scan on the left, and the same for the radiative process with an additional photon on the right. %%%%%%%%%%%%%%% \section{$W$ pairs at LEP II} This example which can be found as file \ttt{LEP\_cc10.sin} in the \ttt{share/examples} directory, shows $W$ pair production in the semileptonic mode at LEP II with its final energy of 209 GeV. Because there are ten contributing Feynman diagrams, the process has been dubbed CC10: charged current process with 10 diagrams. We work within the Standard Model: \begin{code} model = SM \end{code} Then the process is defined, where no flavor summation is done for the jets here: \begin{code} process cc10 = e1, E1 => e2, N2, u, D \end{code} A compilation statement is optional, and then we set the muon mass to zero: \begin{code} mmu = 0 \end{code} The final LEP center-of-momentum energy of 209 GeV is set: \begin{code} sqrts = 209 GeV \end{code} Then, we integrate the process: \begin{code} integrate (cc10) { iterations = 12:20000 } \end{code} Running the \sindarin\ file up to here, results in the output: \begin{scriptsize} \begin{Verbatim}[frame=single] | Process library 'default_lib': loading | Process library 'default_lib': ... success. SM.mmu = 0.000000000000E+00 sqrts = 2.090000000000E+02 | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 31255 | Initializing integration for process cc10: | ------------------------------------------------------------------------ | Process [scattering]: 'cc10' | Library name = 'default_lib' | Process index = 1 | Process components: | 1: 'cc10_i1': e-, e+ => mu-, numubar, u, dbar [omega] | ------------------------------------------------------------------------ | Beam structure: [any particles] | Beam data (collision): | e- (mass = 5.1099700E-04 GeV) | e+ (mass = 5.1099700E-04 GeV) | sqrts = 2.090000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'cc10_i1.phs' | Phase space: 25 channels, 8 dimensions | Phase space: found 25 channels, collected in 7 groves. | Phase space: Using 25 equivalences between channels. | Phase space: wood Warning: No cuts have been defined. | OpenMP: Using 8 threads | Starting integration for process 'cc10' | Integrate: iterations = 12:20000 | Integrator: 7 chains, 25 channels, 8 dimensions | Integrator: Using VAMP channel equivalences | Integrator: 20000 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 19975 6.4714908E+02 2.17E+01 3.36 4.75* 2.33 2 19975 7.3251876E+02 2.45E+01 3.34 4.72* 2.17 3 19975 6.7746497E+02 2.39E+01 3.52 4.98 1.77 4 19975 7.2075198E+02 2.41E+01 3.34 4.72* 1.76 5 19975 6.5976152E+02 2.26E+01 3.43 4.84 1.46 6 19975 6.6633310E+02 2.26E+01 3.39 4.79* 1.43 7 19975 6.7539385E+02 2.29E+01 3.40 4.80 1.43 8 19975 6.6754027E+02 2.11E+01 3.15 4.46* 1.41 9 19975 7.3975817E+02 2.52E+01 3.40 4.81 1.53 10 19975 7.2284275E+02 2.39E+01 3.31 4.68* 1.47 11 19975 6.5476917E+02 2.18E+01 3.33 4.71 1.33 12 19975 7.2963866E+02 2.54E+01 3.48 4.92 1.46 |-----------------------------------------------------------------------------| 12 239700 6.8779583E+02 6.69E+00 0.97 4.76 1.46 2.18 12 |=============================================================================| | Time estimate for generating 10000 events: 0d:00h:01m:16s | Creating integration history display cc10-history.ps and cc10-history.pdf \end{Verbatim} \end{scriptsize} \begin{figure} \centering \includegraphics[width=.6\textwidth]{cc10_1} \\\vspace{5mm} \includegraphics[width=.6\textwidth]{cc10_2} \caption{Histogram of the dijet invariant mass from the CC10 $W$ pair production at LEP II, peaking around the $W$ mass (upper plot), and of the muon energy (lower plot).} \label{fig:cc10} \end{figure} The next step is event generation. In order to get smooth distributions, we set the integrated luminosity to 10 fb${}^{-1}$. (Note that LEP II in its final year 2000 had an integrated luminosity of roughly 0.2 fb${}^{-1}$.) \begin{code} luminosity = 10 \end{code} With the simulated events corresponding to those 10 inverse femtobarn we want to perform a \whizard\ analysis: we are going to plot the dijet invariant mass, as well as the energy of the outgoing muon. For the plot of the analysis, we define a description and label the $y$ axis: \begin{code} $description = "A WHIZARD Example. Charged current CC10 process from LEP 2." $y_label = "$N_{\textrm{events}}$" \end{code} We also use \LaTeX-syntax for the title of the first plot and the $x$-label, and then define the histogram of the dijet invariant mass in the range around the $W$ mass from 70 to 90 GeV in steps of half a GeV: \begin{code} $title = "Di-jet invariant mass $M_{jj}$ in $e^+e^- \to \mu^- \bar\nu_\mu u \bar d$" $x_label = "$M_{jj}$/GeV" histogram m_jets (70 GeV, 90 GeV, 0.5 GeV) \end{code} And we do the same for the second histogram of the muon energy: \begin{code} $title = "Muon energy $E_\mu$ in $e^+e^- \to \mu^- \bar\nu_\mu u \bar d$" $x_label = "$E_\mu$/GeV" histogram e_muon (0 GeV, 209 GeV, 4) \end{code} Now, we define the \ttt{analysis} consisting of two \ttt{record} statements initializing the two observables that are plotted as histograms: \begin{code} analysis = record m_jets (eval M [u,D]); record e_muon (eval E [e2]) \end{code} At the very end, we perform the event generation \begin{code} simulate (cc10) \end{code} and finally the writing and compilation of the analysis in a named data file: \begin{code} compile_analysis { $out_file = "cc10.dat" } \end{code} This event generation part screen output looks like this: \begin{scriptsize} \begin{Verbatim}[frame=single] luminosity = 1.000000000000E+01 $description = "A WHIZARD Example. Charged current CC10 process from LEP 2." $y_label = "$N_{\textrm{events}}$" $title = "Di-jet invariant mass $M_{jj}$ in $e^+e^- \to \mu^- \bar\nu_\mu u \bar d$" $x_label = "$M_{jj}$/GeV" $title = "Muon energy $E_\mu$ in $e^+e^- \to \mu^- \bar\nu_\mu u \bar d$" $x_label = "$E_\mu$/GeV" | Starting simulation for process 'cc10' | Simulate: using integration grids from file 'cc10_m1.vg' | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 9910 | OpenMP: Using 8 threads | Simulation: using n_events as computed from luminosity value | Events: writing to raw file 'cc10.evx' | Events: generating 6830 unweighted, unpolarized events ... | Events: event normalization mode '1' | ... event sample complete. Warning: Encountered events with excess weight: 39 events ( 0.571 %) | Maximum excess weight = 1.027E+00 | Average excess weight = 6.764E-04 | Events: closing raw file 'cc10.evx' $out_file = "cc10.dat" | Opening file 'cc10.dat' for output | Writing analysis data to file 'cc10.dat' | Closing file 'cc10.dat' for output | Compiling analysis results display in 'cc10.tex' \end{Verbatim} \end{scriptsize} %$ Then comes the \LaTeX\ output of the compilation of the graphical analysis. Fig.~\ref{fig:cc10} shows the two histograms as the are produced as result of the \whizard\ internal graphical analysis. %%%%%%%%%%%%%%% \section{Higgs search at LEP II} This example can be found under the name \ttt{LEP\_higgs.sin} in the \ttt{share/doc} folder of \whizard. It displays different search channels for a very light would-be SM Higgs boson of mass 115 GeV at the LEP II machine at its highest energy it finally achieved, 209 GeV. First, we use the Standard Model: \begin{code} model = SM \end{code} Then, we define aliases for neutrinos, antineutrinos, light quarks and light anti-quarks: \begin{code} alias n = n1:n2:n3 alias N = N1:N2:N3 alias q = u:d:s:c alias Q = U:D:S:C \end{code} Now, we define the signal process, which is Higgsstrahlung, \begin{code} process zh = e1, E1 => Z, h \end{code} the missing-energy channel, \begin{code} process nnbb = e1, E1 => n, N, b, B \end{code} and finally the 4-jet as well as dilepton-dijet channels: \begin{code} process qqbb = e1, E1 => q, Q, b, B process bbbb = e1, E1 => b, B, b, B process eebb = e1, E1 => e1, E1, b, B process qqtt = e1, E1 => q, Q, e3, E3 process bbtt = e1, E1 => b, B, e3, E3 compile \end{code} and we compile the code. We set the center-of-momentum energy to the highest energy LEP II achieved, \begin{code} sqrts = 209 GeV \end{code} For the Higgs boson, we take the values of a would-be SM Higgs boson with mass of 115 GeV, which would have had a width of a bit more than 3 MeV: \begin{code} mH = 115 GeV wH = 3.228 MeV \end{code} We take a running $b$ quark mass to take into account NLO corrections to the $Hb\bar b$ vertex, while all other fermions are massless: \begin{code} mb = 2.9 GeV me = 0 ms = 0 mc = 0 \end{code} \begin{scriptsize} \begin{Verbatim}[frame=single] | Process library 'default_lib': loading | Process library 'default_lib': ... success. sqrts = 2.090000000000E+02 SM.mH = 1.150000000000E+02 SM.wH = 3.228000000000E-03 SM.mb = 2.900000000000E+00 SM.me = 0.000000000000E+00 SM.ms = 0.000000000000E+00 SM.mc = 0.000000000000E+00 \end{Verbatim} \end{scriptsize} To avoid soft-collinear singular phase-space regions, we apply an invariant mass cut on light quark pairs: \begin{code} cuts = all M >= 10 GeV [q,Q] \end{code} Now, we integrate the signal process as well as the combined signal and background processes: \begin{code} integrate (zh) { iterations = 5:5000} integrate(nnbb,qqbb,bbbb,eebb,qqtt,bbtt) { iterations = 12:20000 } \end{code} \begin{scriptsize} \begin{Verbatim}[frame=single] | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 21791 | Initializing integration for process zh: | ------------------------------------------------------------------------ | Process [scattering]: 'zh' | Library name = 'default_lib' | Process index = 1 | Process components: | 1: 'zh_i1': e-, e+ => Z, H [omega] | ------------------------------------------------------------------------ | Beam structure: [any particles] | Beam data (collision): | e- (mass = 0.0000000E+00 GeV) | e+ (mass = 0.0000000E+00 GeV) | sqrts = 2.090000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'zh_i1.phs' | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: Using 1 equivalence between channels. | Phase space: wood | Applying user-defined cuts. | OpenMP: Using 8 threads | Starting integration for process 'zh' | Integrate: iterations = 5:5000 | Integrator: 1 chains, 1 channels, 2 dimensions | Integrator: Using VAMP channel equivalences | Integrator: 5000 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 4608 1.6114109E+02 5.52E-04 0.00 0.00* 99.43 2 4608 1.6114220E+02 5.59E-04 0.00 0.00 99.43 3 4608 1.6114103E+02 5.77E-04 0.00 0.00 99.43 4 4608 1.6114111E+02 5.74E-04 0.00 0.00* 99.43 5 4608 1.6114103E+02 5.66E-04 0.00 0.00* 99.43 |-----------------------------------------------------------------------------| 5 23040 1.6114130E+02 2.53E-04 0.00 0.00 99.43 0.82 5 |=============================================================================| [.....] \end{Verbatim} \end{scriptsize} \begin{figure} \centering \includegraphics[width=.48\textwidth]{lep_higgs_1} \includegraphics[width=.48\textwidth]{lep_higgs_2} \\\vspace{5mm} \includegraphics[width=.48\textwidth]{lep_higgs_3} \caption{Upper line: final state $bb + E_{miss}$, histogram of the invisible mass distribution (left), and of the di-$b$ distribution (right). Lower plot: light dijet distribution in the $bbjj$ final state.} \label{fig:lep_higgs} \end{figure} Because the other integrations look rather similar, we refrain from displaying them here, too. As a next step, we define titles, descriptions and axis labels for the histograms we want to generate. There are two of them, one os the invisible mass distribution, the other is the di-$b$-jet invariant mass. Both histograms are taking values between 70 and 130 GeV with bin widths of half a GeV: \begin{code} $description = "A WHIZARD Example. Light Higgs search at LEP. A 115 GeV pseudo-Higgs has been added. Luminosity enlarged by two orders of magnitude." $y_label = "$N_{\textrm{events}}$" $title = "Invisible mass distribution in $e^+e^- \to \nu\bar\nu b \bar b$" $x_label = "$M_{\nu\nu}$/GeV" histogram m_invisible (70 GeV, 130 GeV, 0.5 GeV) $title = "$bb$ invariant mass distribution in $e^+e^- \to \nu\bar\nu b \bar b$" $x_label = "$M_{b\bar b}$/GeV" histogram m_bb (70 GeV, 130 GeV, 0.5 GeV) \end{code} The analysis is initialized by defining the two records for the invisible mass and the invariant mass of the two $b$ jets: \begin{code} analysis = record m_invisible (eval M [n,N]); record m_bb (eval M [b,B]) \end{code} In order to have enough statistics, we enlarge the LEP integrated luminosity at 209 GeV by more than two orders of magnitude: \begin{code} luminosity = 10 \end{code} We start event generation by simulating the process with two $b$ jets and two neutrinos in the final state: \begin{code} simulate (nnbb) \end{code} As a third histogram, we define the dijet invariant mass of two light jets: \begin{code} $title = "Dijet invariant mass distribution in $e^+e^- \to q \bar q b \bar b$" $x_label = "$M_{q\bar q}$/GeV" histogram m_jj (70 GeV, 130 GeV, 0.5 GeV) \end{code} Then we simulate the 4-jet process defining the light-dijet distribution as a local record: \begin{code} simulate (qqbb) { analysis = record m_jj (eval M / 1 GeV [combine [q,Q]]) } \end{code} Finally, we compile the analysis, \begin{code} compile_analysis { $out_file = "lep_higgs.dat" } \end{code} \begin{scriptsize} \begin{Verbatim}[frame=single] | Starting simulation for process 'nnbb' | Simulate: using integration grids from file 'nnbb_m1.vg' | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 21798 | OpenMP: Using 8 threads | Simulation: using n_events as computed from luminosity value | Events: writing to raw file 'nnbb.evx' | Events: generating 1070 unweighted, unpolarized events ... | Events: event normalization mode '1' | ... event sample complete. Warning: Encountered events with excess weight: 207 events ( 19.346 %) | Maximum excess weight = 1.534E+00 | Average excess weight = 4.909E-02 | Events: closing raw file 'nnbb.evx' $title = "Dijet invariant mass distribution in $e^+e^- \to q \bar q b \bar b$" $x_label = "$M_{q\bar q}$/GeV" | Starting simulation for process 'qqbb' | Simulate: using integration grids from file 'qqbb_m1.vg' | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 21799 | OpenMP: Using 8 threads | Simulation: using n_events as computed from luminosity value | Events: writing to raw file 'qqbb.evx' | Events: generating 4607 unweighted, unpolarized events ... | Events: event normalization mode '1' | ... event sample complete. Warning: Encountered events with excess weight: 112 events ( 2.431 %) | Maximum excess weight = 8.875E-01 | Average excess weight = 4.030E-03 | Events: closing raw file 'qqbb.evx' $out_file = "lep_higgs.dat" | Opening file 'lep_higgs.dat' for output | Writing analysis data to file 'lep_higgs.dat' | Closing file 'lep_higgs.dat' for output | Compiling analysis results display in 'lep_higgs.tex' \end{Verbatim} \end{scriptsize} The graphical analysis of the events generated by \whizard\ are shown in Fig.~\ref{fig:lep_higgs}. In the upper left, the invisible mass distribution in the $b\bar b + E_{miss}$ state is shown, peaking around the $Z$ mass. The upper right shows the $M(b\bar b)$ distribution in the same final state, while the lower plot has the invariant mass distribution of the two non-$b$-tagged (light) jets in the $bbjj$ final state. The latter shows only the $Z$ peak, while the former exhibits the narrow would-be 115 GeV Higgs state. %%%%%%%%%%%%%%% \section{Deep Inelastic Scattering at HERA} %%%%%%%%%%%%%%% \section{$W$ endpoint at LHC} %%%%%%%%%%%%%%% \section{SUSY Cascades at LHC} %%%%%%%%%%%%%%% \section{Polarized $WW$ at ILC} %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \chapter{Technical details -- Advanced Spells} \label{chap:tuning} \section{Efficiency and tuning} Since massless fermions and vector bosons (or almost massless states in a certain approximation) lead to restrictive selection rules for allowed helicity combinations in the initial and final state. To make use of this fact for the efficiency of the \whizard\ program, we are applying some sort of heuristics: \whizard\ dices events into all combinatorially possible helicity configuration during a warm-up phase. The user can specify a helicity threshold which sets the number of zeros \whizard\ should have got back from a specific helicity combination in order to ignore that combination from now on. By that mechanism, typically half up to more than three quarters of all helicity combinations are discarded (and hence the corresponding number of matrix element calls). This reduces calculation time up to more than one order of magnitude. \whizard\ shows at the end of the integration those helicity combinations which finally contributed to the process matrix element. Note that this list -- due to the numerical heuristics -- might very well depend on the number of calls for the matrix elements per iteration, and also on the corresponding random number seed. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \chapter{New External Physics Models} \label{chap:extmodels} It is never possible to include all incarnations of physics models that can be described by the maybe weirdest form of a quantum field theory in a tailor-made implementation within a program like \whizard. Users clearly want to be able to use their own special type of model; in order to do so there are external tools to translate models described by their field content and Lagrangian densities into Feynman rules and make them available in an event generator like \whizard. In this chapter, we describe the interfaces to two such external models, \sarah\ and \FeynRules. The \FeynRules\ interface had been started already for the legacy version \whizard\ttt{1} (where it had to be downloaded from \url{https://whizard.hepforge.org} as a separate package), but for the \whizard\ttt{two} release series it has been included in the \FeynRules\ package (from their version v1.6.0 on). Note that there was a regression for the usage of external models (from either \sarah\ or \FeynRules) in the first release of series v2.2, v2.2.0. This has been fixed in all upcoming versions. Besides using \sarah\ or \FeynRules\ via their interfaces, there is now a much easier way to let those programs output model files in the "Universal FeynRules Output" (or \UFO). This option does not have any principle limitations for models, and also does not rely on the never truly constant interfaces between two different tools. Their usage is described in Sec.~\ref{sec:ufo}. %%%%%%%%%%%%%%% \section{New physics models via \sarah} \sarah~\cite{Staub:2008uz,Staub:2009bi,Staub:2010jh,Staub:2012pb,Staub:2013tta} is a \Mathematica~\cite{mathematica} package which derives for a given model the minimum conditions of the vacuum, the mass matrices, and vertices at tree-level as well as expressions for the one-loop corrections for all masses and the full two-loop renormalization group equations (RGEs). The vertices can be exported to be used with \whizard/\oMega. All other information can be used to generate \fortran\ source code for the RGE solution tool and spectrum generator \spheno~\cite{Porod:2003um,Porod:2011nf} to get a spectrum generator for any model. The advantage is that \spheno\ calculates a consistent set of parameters (couplings, masses, rotation matrices, decay widths) which can be used as input for \whizard. \sarah\ and \spheno\ can be also downloaded from the \ttt{HepForge} server: \begin{center} \url{https://sarah.hepforge.org} \\ \url{https://spheno.hepforge.org} \end{center} \subsection{\whizard/\oMega\ model files from \sarah} \subsubsection{Generating the model files} Here we are giving only the information relevant to generate models for \whizard. For more details about the installation of \sarah\ and an exhaustion documentation about its usage, confer the \sarah\ manual. To generate the model files for \whizard/\oMega\ with \sarah, a new \Mathematica\ session has to be started. \sarah\ is loaded via \begin{code} </Output/TMSSM/EWSB/WHIZARD_Omega/ \end{code} and run % \begin{code} ./configure make install \end{code} % By default, the last command installs the compiled model into \verb".whizard" in current user's home directory where it is automatically picked up by \whizard. Alternative installation paths can be specified using the \verb"--prefix" option to \whizard. % \begin{code} ./configure --prefix=/path/to/installation/prefix \end{code} % If the files are installed into the \whizard\ installation prefix, the program will also pick them up automatically, while {\whizard}'s \verb"--localprefix" option must be used to communicate any other choice to \whizard. In case \whizard\ is not available in the binary search path, the \verb"WO_CONFIG" environment variable can be used to point \verb"configure" to the binaries % \begin{code} ./configure WO_CONFIG=/path/to/whizard/binaries \end{code} % More information on the available options and their syntax can be obtained with the \verb"--help" option. After the model is compiled it can be used in \whizard\ as \begin{code} model = tmssm_sarah \end{code} \subsection{Linking \spheno\ and \whizard} As mentioned above, the user can also use \spheno\ to generate spectra for its models. This is done by means of \fortran\ code for \spheno, exported from \sarah. To do so, the user has to apply the command \verb"MakeSPheno[]". For more details about the options of this command and how to compile and use the \spheno\ output, we refer to the \sarah\ manual. \\ As soon as the \spheno\ version for the given model is ready it can be used to generate files with all necessary numerical values for the parameters in a format which is understood by \whizard. For this purpose, the corresponding flag in the Les Houches input file of \spheno\ has to be turned on: \begin{code} Block SPhenoInput # SPheno specific input ... 75 1 # Write WHIZARD files \end{code} Afterwards, \spheno\ returns not only the spectrum file in the standard SUSY Les Houches accord (SLHA) format (for more details about the SLHA and the \whizard\ SLHA interface cf. Sec.~\ref{sec:slha}), but also an additional file called \verb"WHIZARD.par.TMSSM" for our example. This file can be used in the \sindarin\ input file via \begin{code} include ("WHIZARD.par.TMSSM") \end{code} %%%%% \subsection{BSM Toolbox} A convenient way to install \sarah\ together with \whizard, \spheno\ and some other codes are the \ttt{BSM Toolbox} scripts \footnote{Those script have been published under the name SUSY Toolbox but \sarah\ is with version 4 no longer restricted to SUSY models}~\cite{Staub:2011dp}. These scripts are available at \begin{center} \url{https://sarah.hepforge.org/Toolbox.html} \end{center} The \ttt{Toolbox} provides two scripts. First, the \verb"configure" script is used via \begin{code} toolbox-src-dir> mkdir build toolbox-src-dir> cd build toolbox-src-dir> ../configure \end{code} % The \verb"configure" script checks for the requirements of the different packages and downloads all codes. All downloaded archives will be placed in the \verb"tarballs" subdirectory of the directory containing the \verb"configure" script. Command line options can be used to disable specific packages and to point the script to custom locations of compilers and of the \Mathematica\ kernel; a full list of those can be obtained by calling \verb"configure" with the \verb"--help" option. After \verb"configure" finishes successfully, \verb"make" can be called to build all configured packages % \begin{code} toolbox-build-dir> make \end{code} \verb"configure" creates also the second script which automates the implementation of a new model into all packages. The \verb"butler" script takes as argument the name of the model in \sarah, e.g. \begin{code} > ./butler TMSSM \end{code} The \verb"butler" script runs \sarah\ to get the output in the same form as the \whizard/\oMega\ model files and the code for \spheno. Afterwards, it installs the model in all packages and compiles the new \whizard/\oMega\ model files as well as the new \spheno\ module. %%%%% \newpage \section{New physics models via \FeynRules} In this section, we present the interface between the external tool \FeynRules\ \cite{Christensen:2008py,Christensen:2009jx,Duhr:2011se} and \whizard. \FeynRules\ is a \Mathematica~\cite{mathematica} package that allows to derive Feynman rules from any perturbative quantum field theory-based Lagrangian in an automated way. It can be downloaded from \begin{center} \url{http://feynrules.irmp.ucl.ac.be/} \end{center} The input provided by the user is threefold and consists of the Lagrangian defining the model, together with the definitions of all the particles and parameters that appear in the model. Once this information is provided, \FeynRules\ can perform basic checks on the sanity of the implementation (e.g. hermiticity, normalization of the quadratic terms), and finally computes all the interaction vertices associated with the model and store them in an internal format for later processing. After the Feynman rules have been obtained, \FeynRules\ can export the interaction vertices to \whizard\ via a dedicated interface~\cite{Christensen:2010wz}. The interface checks whether all the vertices are compliant with the structures supported by \whizard's matrix element generator \oMega, and discard them in the case they are not supported. The output of the interface consists of a set of files organized in a single directory which can be injected into \whizard/\oMega\ and used as any other built-in models. Together with the model files, a framework is created which allows to communicate the new models to \whizard\ in a well defined way, after which step the model can be used exactly like the built-in ones. This specifically means that the user is not required to manually modify the code of \whizard/\oMega, the models created by the interface can be used directly without any further user intervention. We first describe the installation and general usage of the interface, and then list the general properties like the supported particle types, color quantum numbers and Lorentz structures as well as types of gauge interactions. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \subsection{Installation and Usage of the \whizard-\FeynRules\ interface} \label{sec:interface-usage} \paragraph{{\bf Installation and basic usage:}} % From \FeynRules\ version 1.6.0 onward, the interface to \whizard\ is part of the \FeynRules\ distribution\footnote{Note that though the main interface of \FeynRules\ to \whizard\ is for the most recent \whizard\ release, but also the legacy branch \whizard\ttt{1} is supported.}. In addition, the latest version of the interface can be downloaded from the \whizard\ homepage on \ttt{HepForge}. There you can also find an installer that can be used to inject the interface into an existing \FeynRules\ installation (which allows to use the interface with the \FeynRules\ release series1.4.x where it is not part of the package). Once installed, the interface can be called and used in the same way \FeynRules' other interfaces described in~\cite{Christensen:2008py}. The details of how to install and use \FeynRules\ itself can be found there,~\cite{Christensen:2008py,Christensen:2009jx,Duhr:2011se}. Here, we only describe how to use the interface to inject new models into \whizard. For example, once the \FeynRules\ environment has been initialized and a model has been loaded, the command \begin{code} WriteWOOutput[L] \end{code} will call the \ttt{FeynmanRules} command to extract the Feynman rules from the Lagrangian \ttt{L}, translate them together with the model data and finally write the files necessary for using the model within \whizard\ to an output directory (the name of which is inferred from the model name by default). Options can be added for further control over the translation process (see Sec.~\ref{app:interface-options}). Instead of using a Lagrangian, it is also possible to call the interface on a pure vertex list. For example, the following command \begin{code} WriteWOOutput[Input -> list] \end{code} will directly translate the vertex list \ttt{list}. Note that this vertex list must be given in flavor-expanded form in order for the interface to process it correctly. The interface also supports the \ttt{WriteWOExtParams} command described in~\cite{Christensen:2008py}. Issuing \begin{code} WriteWOExtParams[filename] \end{code} will write a list of all the external parameters to \ttt{filename}. This is done in the form of a \sindarin\ script. The only option accepted by the command above is the target version of \whizard, set by the option \ttt{WOWhizardVersion}. During execution, the interface will print out a series of messages. It is highly advised to carefully read through this output as it not only summarizes the settings and the location of the output files, but also contains information on any skipped vertices or potential incompatibilities of the model with \whizard. After the interface has run successfully and written the model files to the output directory, the model must be imported into \whizard. For doing so, the model files have to be compiled and can then be installed independently of \whizard. In the simplest scenario, assuming that the output directory is the current working directory and that the \whizard\ binaries can be found in the current \ttt{\$\{PATH\}}, the installation is performed by simply executing \begin{code} ./configure~\&\&~make clean~\&\&~make install \end{code} This will compile the model and install it into the directory \ttt{\$\{HOME\}/.whizard}, making it fully available to \whizard\ without any further intervention. The build system can be adapted to more complicated cases through several options to the \ttt{configure} which are listed in the \ttt{INSTALL} file created in the output directory. A detailed explanation of all options can be found in Sec.~\ref{app:interface-options}. \paragraph{\bf Supported fields and vertices:} The following fields are currently supported by the interface: scalars, Dirac and Majorana fermions, vectors and symmetric tensors. The set of accepted operators, the full list of which can be found in Tab.~\ref{tab-operators}, is a subset of all the operators supported by \oMega. While still limited, this list is sufficient for a large number of BSM models. In addition, a future version of \whizard/\oMega\ will support the definition of completely general Lorentz structures in the model, allowing the interface to translate all interactions handled by \FeynRules. This will be done by means of a parser within \oMega\ of the \ttt{UFO} file format for model files from \FeynRules. \begin{table*}[!t] \centerline{\begin{tabular}{|c|c|} \hline Particle spins & Supported Lorentz structures \\\hline\hline FFS & \parbox{0.7\textwidth}{\raggedright All operators of dimension four are supported. \strut}\\\hline FFV & \parbox[t]{0.7\textwidth}{\raggedright All operators of dimension four are supported. \strut}\\\hline SSS & \parbox{0.7\textwidth}{\raggedright All dimension three interactions are supported. \strut}\\\hline SVV & \parbox[t]{0.7\textwidth}{\raggedright Supported operators:\\ \mbox{}\hspace{5ex}$\begin{aligned} \text{dimension 3:} & \quad\mathcal{O}_3 = V_1^\mu V_{2\mu}\phi \mbox{}\\ \text{dimension 5:} & \quad\mathcal{O}_5 = \phi \left(\partial^\mu V_1^\nu - \partial^\nu V_1^\mu\right) \left(\partial_\mu V_{2\nu} - \partial_\nu V_{2\mu}\right) \end{aligned}$\\ Note that $\mathcal{O}_5$ generates the effective gluon-gluon-Higgs couplings obtained by integrating out heavy quarks. \strut}\\\hline SSV & \parbox[t]{0.7\textwidth}{\raggedright $\left(\phi_1\partial^\mu\phi_2 - \phi_2\partial^\mu\phi_1\right)V_\mu\;$ type interactions are supported. \strut}\\\hline SSVV & \parbox{0.7\textwidth}{\raggedright All dimension four interactions are supported. \strut}\\\hline SSSS & \parbox{0.7\textwidth}{\raggedright All dimension four interactions are supported. \strut}\\\hline VVV & \parbox[t]{0.7\textwidth}{\raggedright All parity-conserving dimension four operators are supported, with the restriction that non-gauge interactions may be split into several vertices and can only be handled if all three fields are mutually different.\strut \strut}\\\hline VVVV & \parbox[t]{0.7\textwidth}{\raggedright All parity conserving dimension four operators are supported. \strut}\\\hline TSS, TVV, TFF & \parbox[t]{0.7\textwidth}{\raggedright The three point couplings in the Appendix of Ref.\ \cite{Han:1998sg} are supported. \strut}\\\hline \end{tabular}} \caption{All Lorentz structures currently supported by the \whizard-\FeynRules\ interface, sorted with respect to the spins of the particles. ``S'' stands for scalar, ``F'' for fermion (either Majorana or Dirac) and ``V'' for vector.} \label{tab-operators} \end{table*} \paragraph{\bf Color:} % Color is treated in \oMega\ in the color flow decomposition, with the flow structure being implicitly determined from the representations of the particles present at the vertex. Therefore, the interface has to strip the color structure from the vertices derived by \FeynRules\ before writing them out to the model files. While this process is straightforward for all color structures which correspond only to a single flow assignment, vertices with several possible flow configurations must be treated with care in order to avoid mismatches between the flows assigned by \oMega\ and those actually encoded in the couplings. To this end, the interface derives the color flow decomposition from the color structure determined by \FeynRules\ and rejects all vertices which would lead to a wrong flow assignment by \oMega\ (these rejections are accompanied by warnings from the interface)\footnote{For the old \whizard\ttt{1} legacy branch, there was a maximum number of external color flows that had to explicitly specified. Essentially, this is $n_8 - \frac{1}{2}n_3$ where $n_8$ is the maximum number of external color octets and $n_3$ is the maximum number of external triplets and antitriplets. This can be set in the \whizard/\FeynRules\ interface by the \ttt{WOMaxNcf} command, whose default is \ttt{4}.}. At the moment, the $SU(3)_C$ representations supported by both \whizard\ and the interface are singlets ($1$), triplets ($3$), antitriplets ($\bar{3}$) and octets ($8$). Tab.~\ref{tab:su3struct} shows all combinations of these representations which can form singlets together with the support status of the respective color structures in \whizard\ and the interface. Although the supported color structures do not comprise all possible singlets, the list is sufficient for a large number of SM extensions. Furthermore, a future revision of \whizard/\oMega\ will allow for explicit color flow assignments, thus removing most of the current restrictions. \begin{table*} \centerline{\begin{tabular}{|c|c|} \hline $SU(3)_C$ representations & Support status \\\hline\hline \parbox[t]{0.2\textwidth}{ \centerline{\begin{tabular}[t]{lll} $111,\quad$ & $\bar{3}31,\quad$ & $\bar{3}38,$ \\ $1111,$ & $\bar{3}311,$ & $\bar{3}381$ \end{tabular}}} & \parbox[t]{0.7\textwidth}{\raggedright\strut Fully supported by the interface\strut} \\\hline $888,\quad 8881$ & \parbox{0.7\textwidth}{\raggedright\strut Supported only if at least two of the octets are identical particles.\strut} \\\hline $881,\quad 8811$ & \parbox{0.7\textwidth}{\raggedright\strut Fully supported by the interface\footnote{% Not available in version 1.95 and earlier. Note that in order to use such couplings in 1.96/97, the \oMega\ option \ttt{2g} must be added to the process definition in \ttt{whizard.prc}.}.\strut} \\\hline $\bar{3}388$ & \parbox{0.7\textwidth}{\raggedright\strut Supported only if the octets are identical particles.\strut} \\\hline $8888$ & \parbox{0.7\textwidth}{\raggedright\strut The only supported flow structure is \begin{equation*} \parbox{21mm}{\includegraphics{flow4}}\cdot\;\Gamma(1,2,3,4) \quad+\quad \text{all acyclic permutations} \end{equation*} where $\Gamma(1,2,3,4)$ represents the Lorentz structure associated with the first flow.\strut} \\\hline \parbox[t]{0.2\textwidth}{ \centerline{\begin{tabular}[t]{lll} $333,\quad$ & $\bar{3}\bar{3}\bar{3},\quad$ & $3331$\\ $\bar{3}\bar{3}\bar{3}1,$ & $\bar{3}\bar{3}33$ \end{tabular}}} & \parbox[t]{0.7\textwidth}{\raggedright\strut Unsupported (at the moment)\strut} \\\hline \end{tabular}} \caption{All possible combinations of three or four $SU(3)_C$ representations supported by \FeynRules\ which can be used to build singlets, together with the support status of the corresponding color structures in \whizard\ and the interface.} \label{tab:su3struct} \end{table*} \paragraph{\bf Running $\alpha_S$:} While a running strong coupling is fully supported by the interface, a choice has to be made which quantities are to be reevaluated when the strong coupling is evolved. By default \ttt{aS}, \ttt{G} (see Ref.~\cite{Christensen:2008py} for the nomenclature regarding the QCD coupling) and any vertex factors depending on them are evolved. The list of internal parameters that are to be recalculated (together with the vertex factors depending on them) can be extended (beyond \ttt{aS} and \ttt{G}) by using the option \ttt{WORunParameters} when calling the interface~\footnote{As the legacy branch, \whizard\ttt{1}, does not support a running strong coupling, this is also vetoed by the interface when using \whizard \ttt{1.x}.}. \paragraph{\bf Gauge choices:} \label{sec:gauge-choices} The interface supports the unitarity, Feynman and $R_\xi$ gauges. The choice of gauge must be communicated to the interface via the option \ttt{WOGauge}. Note that massless gauge bosons are always treated in Feynman gauge. If the selected gauge is Feynman or $R_\xi$, the interface can automatically assign the proper masses to the Goldstone bosons. This behavior is requested by using the \ttt{WOAutoGauge} option. In the $R_\xi$ gauges, the symbol representing the gauge $\xi$ must be communicated to the interface by using the \ttt{WOGaugeSymbol} option (the symbol is automatically introduced into the list of external parameters if \ttt{WOAutoGauge} is selected at the same time). This feature can be used to automatically extend models implemented in Feynman gauge to the $R_\xi$ gauges. Since \whizard\ (at least until the release series 2.3) is a tree-level tool working with helicity amplitudes, the ghost sector is irrelevant for \whizard\ and hence dropped by the interface. \subsection{Options of the \whizard-\FeynRules\ interface} \label{app:interface-options} In the following we present a comprehensive list of all the options accepted by \ttt{WriteWOOutput}. Additionally, we note that all options of the \FeynRules\ command \ttt{FeynmanRules} are accepted by \ttt{WriteWOOutput}, which passes them on to \ttt{FeynmanRules}. \begin{description} \item[\ttt{Input}]\mbox{}\\ An optional vertex list to use instead of a Lagrangian (which can then be omitted). % \item[\ttt{WOWhizardVersion}]\mbox{}\\ Select the \whizard\ version for which code is to be generated. The currently available choices are summarized in Tab.~\ref{tab-wowhizardversion}. %% \begin{table} \centerline{\begin{tabular}{|l|l|} \hline \ttt{WOWhizardVersion} & \whizard\ versions supported \\\hline\hline \ttt{"2.0.3"} (default) & 2.0.3+ \\\hline \ttt{"2.0"} & 2.0.0 -- 2.0.2 \\\hline\hline \ttt{"1.96"} & 1.96+ \qquad (deprecated) \\\hline \ttt{"1.93"} & 1.93 -- 1.95 \qquad (deprecated) \\\hline \ttt{"1.92"} & 1.92 \qquad (deprecated) \\\hline \end{tabular}} \caption{Currently available choices for the \ttt{WOWhizardVersion} option, together with the respective \whizard\ versions supported by them.} \label{tab-wowhizardversion} \end{table} %% This list will expand as the program evolves. To get a summary of all choices available in a particular version of the interface, use the command \ttt{?WOWhizardVersion}. % \item[\ttt{WOModelName}]\mbox{}\\ The name under which the model will be known to \whizard\footnote{For versions 1.9x, model names must start with ``\ttt{fr\_}'' if they are to be picked up by \whizard\ automatically.}. The default is determined from the \FeynRules\ model name. % \item[\ttt{Output}]\mbox{}\\ The name of the output directory. The default is determined from the \FeynRules\ model name. % \item[\ttt{WOGauge}]\mbox{}\\ Gauge choice (\emph{cf.} Sec.~\ref{sec:gauge-choices}). Possible values are: \ttt{WOUnitarity} (default), \ttt{WOFeynman}, \ttt{WORxi} % \item[\ttt{WOGaugeParameter}]\mbox{}\\ The external or internal parameter representing the gauge $\xi$ in the $R_\xi$ gauges (\emph{cf.} Sec.~\ref{sec:gauge-choices}). Default: \ttt{Rxi} % \item[\ttt{WOAutoGauge}]\mbox{}\\ Automatically assign the Goldstone boson masses in the Feynman and $R_\xi$ gauges and automatically append the symbol for $\xi$ to the parameter list in the $R_\xi$ gauges. Default: \ttt{False} % \item[\ttt{WORunParameters}]\mbox{}\\ The list of all internal parameters which will be recalculated if $\alpha_S$ is evolved (see above)\footnote{Not available for versions older than 2.0.0}. Default: \mbox{\ttt{\{aS, G\}}} % \item[\ttt{WOFast}]\mbox{}\\ If the interface drops vertices which are supported, this option can be set to \ttt{False} to enable some more time consuming checks which might aid the identification. Default: \ttt{True} % \item[\ttt{WOMaxCouplingsPerFile}]\mbox{}\\ The maximum number of couplings that are written to a single \fortran\ file. If compilation takes too long or fails, this can be lowered. Default: \ttt{500} % \item[\ttt{WOVerbose}]\mbox{}\\ Enable verbose output and in particular more extensive information on any skipped vertices. Default: \ttt{False} \end{description} %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \subsection{Validation of the interface} The output of the interface has been extensively validated. Specifically, the integrated cross sections for all possible $2\rightarrow 2$ processes in the \FeynRules\ SM, the MSSM and the Three-Site Higgsless Model have been compared between \whizard, \madgraph, and \CalcHep, using the respective \FeynRules\ interfaces as well as the in-house implementations of these models (the Three-Site Higgsless model not being available in \madgraph). Also, different gauges have been checked for \whizard\ and \CalcHep. In all comparisons, excellent agreement within the Monte Carlo errors was achieved. The detailed comparison including examples of the comparison tables can be found in~\cite{Christensen:2010wz}. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \subsection{Examples for the \whizard-/\FeynRules\ interface} Here, we will use the Standard Model, the MSSM and the Three-Site Higgsless Model as prime examples to explain the usage of the interface. Those are the models that have been used in the validation of the interface in~\cite{Christensen:2010wz}. The examples are constructed to show the application of the different options of the interface and to serve as a starting point for the generation of the user's own \whizard\ versions of other \FeynRules\ models. \subsubsection{\whizard-\FeynRules\ example: Standard Model}\label{sec:usageSM} To start off, we will create {\sc Whizard} 2 versions of the Standard Model as implemented in \FeynRules\ for different gauge choices. \paragraph{SM: Unitarity Gauge} In order to invoke \FeynRules, we change to the corresponding directory and load the program in \Mathematica\ via \begin{code} $FeynRulesPath = SetDirectory[""]; < WOFeynman]; \end{code} The modified gauge is reflected in the output of the interface \begin{code} Short model name is "fr_standard_model" Gauge: Feynman Generating code for WHIZARD / O'Mega version 2.0.3 Maximum number of couplings per FORTRAN module: 500 Extensive lorentz structure checks disabled. \end{code} The summary of the vertex identification now takes the following form \begin{code} processed a total of 163 vertices, kept 139 of them and threw away 24, 24 of which contained ghosts. \end{code} Again, this line tells us that there were no problems --- the only discarded interactions involved the ghost sector which is irrelevant for the tree-level part of \whizard. For a tree-level calculation, the only difference between the different gauges from the perspective of the interface are the gauge boson propagators and the Goldstone boson masses. Therefore, the interface can automatically convert a model in Feynman gauge to a model in $R_\xi$ gauge. To this end, the call to the interface must be changed to \begin{code} WriteWOOutput[LSM, WOGauge -> WORxi, WOAutoGauge -> True]; \end{code} The \verb?WOAutoGauge? argument instructs the interface to automatically \begin{enumerate} \item Introduce a symbol for the gauge parameter $\xi$ into the list of external parameters \item Generate the Goldstone boson masses from those of the associated gauge bosons (ignoring the values provided by \FeynRules) \end{enumerate} The modified setup is again reflected in the interface output \begin{code} Short model name is "fr_standard_model" Gauge: Rxi Gauge symbol: "Rxi" Generating code for WHIZARD / O'Mega version 2.0.3 Maximum number of couplings per FORTRAN module: 500 Extensive lorentz structure checks disabled. \end{code} Note the default choice \verb?Rxi? for the name of the $\xi$ parameter -- this can be modified via the option \verb?WOGaugeParameter?. While the \verb?WOAutoGauge? feature allows to generate $R_\xi$ gauged models from models implemented in Feynman gauge, it is of course also possible to use models genuinely implemented in $R_\xi$ gauge by setting this parameter to \verb?False?. Also, note that the choice of gauge only affects the propagators of massive fields. Massless gauge bosons are always treated in Feynman gauge. \paragraph{Compilation and usage} In order to compile and use the freshly generated model files, change to the output directory which can be determined from the interface output (in this example, it is \verb?fr_standard_model-WO?). Assuming that \whizard\ is available in the binary search path, compilation and installation proceeds as described above by executing \begin{code} ./configure && make && make install \end{code} The model is now ready and can be used similarly to the builtin \whizard\ models. For example, a minimal \whizard\ input file for calculating the $e^+e^- \longrightarrow W^+W^-$ scattering cross section in the freshly generated model would look like \begin{code} model = fr_standard_model process test = "e+", "e-" -> "W+", "W-" sqrts = 500 GeV integrate (test) \end{code} %%%%% \subsubsection{\whizard/\FeynRules\ example: MSSM} In this Section, we illustrate the usage of the interface between {\sc FeynRules} and {\sc Whizard} in the context of the MSSM. All the parameters of the model are then ordered in Les Houches blocks and counters following the SUSY Les Houches Accord (SLHA) \cite{Skands:2003cj,AguilarSaavedra:2005pw,Allanach:2008qq} (cf. also Sec.~\ref{sec:slha}). After having downloaded the model from the \FeynRules\ website, we store it in a new directory, labelled \verb"MSSM", of the model library of the local installation of \FeynRules. The model can then be loaded in \Mathematica\ as in the case of the SM example above \begin{code} $FeynRulesPath = SetDirectory[""]; <True" option of both interface commands \verb"FeynmanRules" and \verb"WriteWOOutput". The Feynman rules of the MSSM are then computed within the \Mathematica\ notebook by \begin{code} rules = FeynmanRules[lag, Exclude4Scalars->True, FlavorExpand->True]; \end{code} where \verb'lag' is the variable containing the Lagrangian. By default, all the parameters of the model are set to the value of \ttt{1}. A complete parameter \ttt{{\em }.dat} file must therefore be loaded. Such a parameter file can be downloaded from the \FeynRules\ website or created by hand by the user, and loaded into \FeynRules\ as \begin{code} ReadLHAFile[Input -> ".dat"]; \end{code} This command does not reduce the size of the model output by removing vertices with vanishing couplings. However, if desired, this task could be done with the \ttt{LoadRestriction} command (see Ref.\ \cite{Fuks:2012im} for details). The vertices are exported to \whizard\ by the command \begin{code} WriteWOOutput[Input -> rules]; \end{code} Note that the numerical values of the parameters of the model can be modified directly from \whizard, without having to generate a second time the \whizard\ model files from \FeynRules. A \sindarin\ script is created by the interface with the help of the instruction \begin{code} WriteWOExtParams["parameters.sin"]; \end{code} and can be further modified according to the needs of the user. \subsubsection{\whizard-\FeynRules\ example: Three-Site Higgsless Model} The Three-Site Higgsless model or Minimal Higgsless model (MHM) has been implemented into \ttt{LanHEP}~\cite{He:2007ge}, \FeynRules\ and independently into \whizard~\cite{Speckner:2010zi}, and the collider phenomenology has been studied by making use of these implementations \cite{He:2007ge,Ohl:2010zf,Speckner:2010zi}. Furthermore, the independent implementations in \FeynRules\ and directly into {\sc Whizard} have been compared and found to agree~\cite{Christensen:2010wz}. After the discovery of a Higgs boson at the LHC in 2012, such a model is not in good agreement with experimental data any more. Here, we simply use it as a guinea pig to describe the handling of a model with non-renormalizable interactions with the \FeynRules\ interface, and discuss how to generate \whizard\ model files for it. The model has been implemented in Feynman gauge as well as unitarity gauge and contains the variable \verb|FeynmanGauge| which can be set to \verb|True| or \verb|False|. When set to \verb|True|, the option \verb|WOGauge-> WOFeynman| must be used, as explained in~\cite{Christensen:2010wz}. $R_\xi$ gauge can also be accomplished with this model by use of the options \verb|WOGauge -> WORxi| and \verb?WOAutoGauge -> True?. Since this model makes use of a nonlinear sigma field of the form \begin{equation} \Sigma = 1 + i\pi - \frac{1}{2}\pi^2+\cdots \end{equation} many higher dimensional operators are included in the model which are not currently not supported by \whizard. Even for a future release of \whizard\ containing general Lorentz structures in interaction vertices, the user would be forced to expand the series only up to a certain order. Although \whizard\ can reject these vertices and print a warning message to the user, it is preferable to remove the vertices right away in the interface by the option \verb|MaxCanonicalDimension->4|. This is passed to the command \verb|FeynmanRules| and restricts the Feynman rules to those of dimension four and smaller\footnote{\ttt{MaxCanonicalDimension} is an option of the \ttt{FeynmanRules} function rather than of the interface, itself. In fact, the interface accepts all the options of {\tt FeynmanRules} and simply passes them on to the latter.}. As the use of different gauges was already illustrated in the SM example, we discuss the model only in Feynman gauge here. We load \FeynRules: \begin{code} $FeynRulesPath = SetDirectory[""]; <"]; LoadModel["3-Site-particles.fr", "3-Site-parameters.fr", "3-Site-lagrangian.fr"]; FeynmanGauge = True; \end{code} where \verb|| is the path to the directory where the MHM model files are stored and where the output of the \whizard\ interface will be written. The \whizard\ interface is then initiated: \begin{code} WriteWOOutput[LGauge, LGold, LGhost, LFermion, LGoldLeptons, LGoldQuarks, MaxCanonicalDimension->4, WOGauge->WOFeynman, WOModelName->"fr_mhm"]; \end{code} where we have also made use of the option \verb|WOModelName| to change the name of the model as seen by \whizard. As in the case of the SM, the interface begins by writing a short informational message: \begin{code} Short model name is "fr_mhm" Gauge: Feynman Generating code for WHIZARD / O'Mega version 2.0.3 Automagically assigning Goldstone boson masses... Maximum number of couplings per FORTRAN module: 500 Extensive lorentz structure checks disabled. \end{code} After calculating the Feynman rules and processing the vertices, the interface gives a summary: \begin{code} processed a total of 922 vertices, kept 633 of them and threw away 289, 289 of which contained ghosts. \end{code} showing that no vertices were missed. The files are stored in the directory \verb|fr_mhm| and are ready to be installed and used with \whizard. %%%%%%%%%%%%%%% \section{New physics models via the \UFO\ file format} \label{sec:ufo} In this section, we describe how to use the {\em Universal FeynRules Output} (\UFO, \cite{Degrande:2011ua}) format for physics models inside \whizard. Please refer the manuals of e.g.~\FeynRules\ manual for details on how to generate a \UFO\ file for your favorite physics model. \UFO\ files are a collection of \ttt{Python} scripts that encode the particles, the couplings, the Lorentz structures, the decays, as well as parameters, vertices and propagators of the corresponding model. They reside in a directory of the exact name of the model they have been created from. If the user wants to generate events for processes from a physics model from a \UFO\ file, then this directory of scripts generated by \FeynRules\ is immediately available if it is a subdirectory of the working directory of \whizard. The directory name will be taken as the model name. (The \UFO-model file name must not start with a non-letter character, i.e. especially not a number. In case such a file name wants to be used at all costs, the model name in the \sindarin\ script has to put in quotation marks, but this is not guaranteed to always work.) Then, a \UFO\ model named, e.g., \ttt{test\_model} is accessed by an extra \ttt{ufo} tag in the model assignment: \begin{Code} model = test_model (ufo) \end{Code} If desired, \whizard\ can access a directory of \UFO\ files elsewhere on the file system. For instance, if \FeynRules\ output resides in the subdirectory \ttt{MyMdl} of \ttt{/home/users/john/ufo}, \whizard\ can use the model named \ttt{MyMdl} as follows \begin{Code} model = MyMdl (ufo ('/home/users/john/my_ufo_models')) \end{Code} that is, the \sindarin\ keyword \ttt{ufo} can take an argument. Note however, that the latter approach can backfire --- in case just the working directory is packed and archived for future reference. %%%%%%%%%%%%%%% \clearpage %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \appendix %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \chapter{\sindarin\ Reference} In the \sindarin\ language, there are certain pre-defined constructors or commands that cannot be used in different context by the user, which are e.g. \ttt{alias}, \ttt{beams}, \ttt{integrate}, \ttt{simulate} etc. A complete list will be given below. Also units are fixed, like \ttt{degree}, \ttt{eV}, \ttt{keV}, \ttt{MeV}, \ttt{GeV}, and \ttt{TeV}. Again, these tags are locked and not user-redefinable. Their functionality will be listed in detail below, too. Furthermore, a variable with a preceding question mark, ?, is a logical, while a preceding dollar, \$, denotes a character string variable. Also, a lot of unary and binary operators exist, \ttt{+ - $\backslash$ , = : => < > <= >= \^ \; () [] \{\} } \url{==}, as well as quotation marks, ". Note that the different parentheses and brackets fulfill different purposes, which will be explained below. Comments in a line can either be marked by a hash, \#, or an exclamation mark, !. \section{Commands and Operators} We begin the \sindarin\ reference with all commands, operators, functions and constructors. The list of variables (which can be set to change behavior of \whizard) can be found in the next section. \begin{itemize} \item \ttt{+} \newline 1) Arithmetic operator for addition of integers, reals and complex numbers. Example: \ttt{real mm = mH + mZ} (cf. also \ttt{-}, \ttt{*}, \ttt{/}, \ttt{\^{}}). 2) It also adds different particles for inclusive process containers: \ttt{process foo = e1, E1 => (e2, E2) + (e3, E3)}. 3) It also serves as a shorthand notation for the concatenation of ($\to$) \ttt{combine} operations on particles/subevents, e.g. \ttt{cuts = any 170 GeV < M < 180 GeV [b + lepton + invisible]}. %%%%% \item \ttt{-} \newline Arithmetic operator for subtraction of integers, reals and complex numbers. Example: \ttt{real foo = 3.1 - 5.7} (cf. also \ttt{+}, \ttt{*}, \ttt{/}, \ttt{\^{}}). %%%%% \item \ttt{/} \newline Arithmetic operator for division of integers, reals and complex numbers. Example: \ttt{scale = mH / 2} (cf. also \ttt{+}, \ttt{*}, \ttt{-}, \ttt{\^{}}). %%%%% \item \ttt{*} \newline Arithmetic operator for multiplication of integers, reals and complex numbers. Example: \ttt{complex z = 2 * I} (cf. also \ttt{+}, \ttt{/}, \ttt{-}, \ttt{\^{}}). %%%%% \item \ttt{\^{}} \newline Arithmetic operator for exponentiation of integers, reals and complex numbers. Example: \ttt{real z = x\^{}2 + y\^{}2} (cf. also \ttt{+}, \ttt{/}, \ttt{-}, \ttt{\^{}}). %%%%% \item \ttt{<} \newline Arithmetic comparator between values that checks for ordering of two values: \ttt{{\em } < {\em }} tests whether \ttt{{\em val1}} is smaller than \ttt{{\em val2}}. Allowed for integer and real values. Note that this is an exact comparison if \ttt{tolerance} is set to zero. For a finite value of \ttt{tolerance} it is a ``fuzzy'' comparison. (cf. also \ttt{tolerance}, \ttt{<>}, \ttt{==}, \ttt{>}, \ttt{>=}, \ttt{<=}) %%%%% \item \ttt{>} \newline Arithmetic comparator between values that checks for ordering of two values: \ttt{{\em } > {\em }} tests whether \ttt{{\em val1}} is larger than \ttt{{\em val2}}. Allowed for integer and real values. Note that this is an exact comparison if \ttt{tolerance} is set to zero. For a finite value of \ttt{tolerance} it is a ``fuzzy'' comparison. (cf. also \ttt{tolerance}, \ttt{<>}, \ttt{==}, \ttt{>}, \ttt{>=}, \ttt{<=}) %%%%% \item \ttt{<=} \newline Arithmetic comparator between values that checks for ordering of two values: \ttt{{\em } <= {\em }} tests whether \ttt{{\em val1}} is smaller than or equal \ttt{{\em val2}}. Allowed for integer and real values. Note that this is an exact comparison if \ttt{tolerance} is set to zero. For a finite value of \ttt{tolerance} it is a ``fuzzy'' comparison. (cf. also \ttt{tolerance}, \ttt{<>}, \ttt{==}, \ttt{>}, \ttt{<}, \ttt{>=}) %%%%% \item \ttt{>=} \newline Arithmetic comparator between values that checks for ordering of two values: \ttt{{\em } >= {\em }} tests whether \ttt{{\em val1}} is larger than or equal \ttt{{\em val2}}. Allowed for integer and real values. Note that this is an exact comparison if \ttt{tolerance} is set to zero. For a finite value of \ttt{tolerance} it is a ``fuzzy'' comparison. (cf. also \ttt{tolerance}, \ttt{<>}, \ttt{==}, \ttt{>}, \ttt{<}, \ttt{>=}) %%%%% \item \ttt{==} \newline Arithmetic comparator between values that checks for identity of two values: \ttt{{\em } == {\em }}. Allowed for integer and real values. Note that this is an exact comparison if \ttt{tolerance} is set to zero. For a finite value of \ttt{tolerance} it is a ``fuzzy'' comparison. (cf. also \ttt{tolerance}, \ttt{<>}, \ttt{>}, \ttt{<}, \ttt{>=}, \ttt{<=}) %%%%% \item \ttt{<>} \newline Arithmetic comparator between values that checks for two values being unequal: \ttt{{\em } <> {\em }}. Allowed for integer and real values. Note that this is an exact comparison if \ttt{tolerance} is set to zero. For a finite value of \ttt{tolerance} it is a ``fuzzy'' comparison. (cf. also \ttt{tolerance}, \ttt{==}, \ttt{>}, \ttt{<}, \ttt{>=}, \ttt{<=}) %%%%% \item \ttt{!} \newline The exclamation mark tells \sindarin\ that everything that follows in that line should be treated as a comment. It is the same as ($\to$) \ttt{\#}. %%%%% \item \ttt{\#} \newline The hash tells \sindarin\ that everything that follows in that line should be treated as a comment. It is the same as ($\to$) \ttt{!}. %%%%% \item \ttt{\&} \newline Concatenates two or more particle lists/subevents and hence acts in the same way as the subevent function ($\to$) \ttt{join}: \ttt{let @visible = [photon] \& [colored] \& [lepton] in ...}. (cf. also \ttt{join}, \ttt{combine}, \ttt{collect}, \ttt{extract}, \ttt{sort}). %%%%% \item \ttt{\$} \newline Constructor at the beginning of a variable name, \ttt{\${\em }}, that specifies a string variable. %%%%% \item \ttt{@} \newline Constructor at the beginning of a variable name, \ttt{@{\em }}, that specifies a subevent variable, e.g. \ttt{let @W\_candidates = combine ["mu-", "numubar"] in ...}. %%%%% \item \ttt{=} \newline Binary constructor to appoint values to commands, e.g. \ttt{{\em } = {\em }} or \newline \ttt{{\em } {\em } = {\em }}. %%%%% \item \ttt{\%} \newline Constructor that gives the percentage of a number, so in principle multiplies a real number by \ttt{0.01}. Example: \ttt{1.23 \%} is equal to \ttt{0.0123}. %%%%% \item \ttt{:} \newline Separator in alias expressions for particles, e.g. \ttt{alias neutrino = n1:n2:n3:N1:N2:N3}. (cf. also \ttt{alias}) %%%%% \item \ttt{;} \newline Concatenation operator for logical expressions: \ttt{{\em lexpr1} ; {\em lexpr2}}. Evaluates \ttt{{\em lexpr1}} and throws the result away, then evaluates \ttt{{\em lexpr2}} and returns that result. Used in analysis expressions. (cf. also \ttt{analysis}, \ttt{record}) %%%%% \item \ttt{/+} \newline Incrementor for ($\to$) \ttt{scan} ranges, that increments additively, \ttt{scan {\em } = ({\em } => {\em } /+ {\em })}. E.g. \ttt{scan int i = (1 => 5 /+ 2)} scans over the values \ttt{1}, \ttt{3}, \ttt{5}. For real ranges, it divides the interval between upper and lower bound into as many intervals as the incrementor provides, e.g. \ttt{scan real r = (1 => 1.5 /+ 0.2)} runs over \ttt{1.0}, \ttt{1.333}, \ttt{1.667}, \ttt{1.5}. %%%%% \item \ttt{/+/} \newline Incrementor for ($\to$) \ttt{scan} ranges, that increments additively, but the number after the incrementor is the number of steps, not the step size: \ttt{scan {\em } = ({\em } => {\em } /+/ {\em })}. It is only available for real scan ranges, and divides the interval \ttt{{\em } - {\em }} into \ttt{{\em }} steps, e.g. \ttt{scan real r = (1 => 1.5 /+/ 3)} runs over \ttt{1.0}, \ttt{1.25}, \ttt{1.5}. %%%%% \item \ttt{/-} \newline Incrementor for ($\to$) \ttt{scan} ranges, that increments subtractively, \ttt{scan {\em } {\em } = ({\em } => {\em } /- {\em })}. E.g. \ttt{scan int i = (9 => 0 /+ 3)} scans over the values \ttt{9}, \ttt{6}, \ttt{3}, \ttt{0}. For real ranges, it divides the interval between upper and lower bound into as many intervals as the incrementor provides, e.g. \ttt{scan real r = (1 => 0.5 /- 0.2)} runs over \ttt{1.0}, \ttt{0.833}, \ttt{0.667}, \ttt{0.5}. %%%%% \item \ttt{/*} \newline Incrementor for ($\to$) \ttt{scan} ranges, that increments multiplicatively, \ttt{scan {\em } {\em } = ({\em } => {\em } /* {\em })}. E.g. \ttt{scan int i = (1 => 4 /* 2)} scans over the values \ttt{1}, \ttt{2}, \ttt{4}. For real ranges, it divides the interval between upper and lower bound into as many intervals as the incrementor provides, e.g. \ttt{scan real r = (1 => 5 /* 2)} runs over \ttt{1.0}, \ttt{2.236} (i.e. $\sqrt{5}$), \ttt{5.0}. %%%%% \item \ttt{/*/} \newline Incrementor for ($\to$) \ttt{scan} ranges, that increments multiplicatively, but the number after the incrementor is the number of steps, not the step size: \ttt{scan {\em } {\em } = ({\em } => {\em } /*/ {\em })}. It is only available for real scan ranges, and divides the interval \ttt{{\em } - {\em }} into \ttt{{\em }} steps, e.g. \ttt{scan real r = (1 => 9 /*/ 4)} runs over \ttt{1.000}, \ttt{2.080}, \ttt{4.327}, \ttt{9.000}. %%%%% \item \ttt{//} \newline Incrementor for ($\to$) \ttt{scan} ranges, that increments by division, \ttt{scan {\em } {\em } = ({\em } => {\em } // {\em })}. E.g. \ttt{scan int i = (13 => 0 // 3)} scans over the values \ttt{13}, \ttt{4}, \ttt{1}, \ttt{0}. For real ranges, it divides the interval between upper and lower bound into as many intervals as the incrementor provides, e.g. \ttt{scan real r = (5 => 1 // 2)} runs over \ttt{5.0}, \ttt{2.236} (i.e. $\sqrt{5}$), \ttt{1.0}. %%%%% \item \ttt{=>} \newline Binary operator that is used in several different contexts: 1) in process declarations between the particles specifying the initial and final state, e.g. \ttt{process {\em } = {\em }, {\em } => {\em }, ....}; 2) for the specification of beams when structure functions are applied to the beam particles, e.g. \ttt{beams = p, p => pdf\_builtin}; 3) for the specification of the scan range in the \ttt{scan {\em } {\em } = ({\em } => {\em } {\em })} (cf. also \ttt{process}, \ttt{beams}, \ttt{scan}) %%%%% \item \ttt{\%d} \newline Format specifier in analogy to the \ttt{C} language for the print out on screen by the ($\to$) \ttt{printf} or into strings by the ($\to$) \ttt{sprintf} command. It is used for decimal integer numbers, e.g. \ttt{printf "one = \%d" (i)}. The difference between \ttt{\%i} and \ttt{\%d} does not play a role here. (cf. also \ttt{printf}, \ttt{sprintf}, \ttt{\%i}, \ttt{\%e}, \ttt{\%f}, \ttt{\%g}, \ttt{\%E}, \ttt{\%F}, \ttt{\%G}, \ttt{\%s}) %%%%% \item \ttt{\%e} \newline Format specifier in analogy to the \ttt{C} language for the print out on screen by the ($\to$) \ttt{printf} or into strings by the ($\to$) \ttt{sprintf} command. It is used for floating-point numbers in standard form \ttt{[-]d.ddd e[+/-]ddd}. Usage e.g. \ttt{printf "pi = \%e" (PI)}. (cf. also \ttt{printf}, \ttt{sprintf}, \ttt{\%d}, \ttt{\%i}, \ttt{\%f}, \ttt{\%g}, \ttt{\%E}, \ttt{\%F}, \ttt{\%G}, \ttt{\%s}) %%%%% \item \ttt{\%E} \newline Same as ($\to$) \ttt{\%e}, but using upper-case letters. (cf. also \ttt{printf}, \ttt{sprintf}, \ttt{\%d}, \ttt{\%i}, \ttt{\%e}, \ttt{\%f}, \ttt{\%g}, \ttt{\%F}, \ttt{\%G}, \ttt{\%s}) %%%%% \item \ttt{\%f} \newline Format specifier in analogy to the \ttt{C} language for the print out on screen by the ($\to$) \ttt{printf} or into strings by the ($\to$) \ttt{sprintf} command. It is used for floating-point numbers in fixed-point form. Usage e.g. \ttt{printf "pi = \%f" (PI)}. (cf. also \ttt{printf}, \ttt{sprintf}, \ttt{\%d}, \ttt{\%i}, \ttt{\%e}, \ttt{\%g}, \ttt{\%E}, \ttt{\%F}, \ttt{\%G}, \ttt{\%s}) %%%%% \item \ttt{\%F} \newline Same as ($\to$) \ttt{\%f}, but using upper-case letters. (cf. also \ttt{printf}, \ttt{sprintf}, \ttt{\%d}, \ttt{\%i}, \ttt{\%e}, \ttt{\%f}, \ttt{\%g}, \ttt{\%E}, \ttt{\%G}, \ttt{\%s}) %%%%% \item \ttt{\%g} \newline Format specifier in analogy to the \ttt{C} language for the print out on screen by the ($\to$) \ttt{printf} or into strings by the ($\to$) \ttt{sprintf} command. It is used for floating-point numbers in normal or exponential notation, whichever is more approriate. Usage e.g. \ttt{printf "pi = \%g" (PI)}. (cf. also \ttt{printf}, \ttt{sprintf}, \ttt{\%d}, \ttt{\%i}, \ttt{\%e}, \ttt{\%f}, \ttt{\%E}, \ttt{\%F}, \ttt{\%G}, \ttt{\%s}) %%%%% \item \ttt{\%G} \newline Same as ($\to$) \ttt{\%g}, but using upper-case letters. (cf. also \ttt{printf}, \ttt{sprintf}, \ttt{\%d}, \ttt{\%i}, \ttt{\%e}, \ttt{\%f}, \ttt{\%g}, \ttt{\%E}, \ttt{\%F}, \ttt{\%s}) %%%%% \item \ttt{\%i} \newline Format specifier in analogy to the \ttt{C} language for the print out on screen by the ($\to$) \ttt{printf} or into strings by the ($\to$) \ttt{sprintf} command. It is used for integer numbers, e.g. \ttt{printf "one = \%i" (i)}. The difference between \ttt{\%i} and \ttt{\%d} does not play a role here. (cf. \ttt{printf}, \ttt{sprintf}, \ttt{\%d}, \ttt{\%e}, \ttt{\%f}, \ttt{\%g}, \ttt{\%E}, \ttt{\%F}, \ttt{\%G}, \ttt{\%s}) %%%%% \item \ttt{\%s} \newline Format specifier in analogy to the \ttt{C} language for the print out on screen by the ($\to$) \ttt{printf} or into strings by the ($\to$) \ttt{sprintf} command. It is used for logical or string variables e.g. \ttt{printf "foo = \%s" (\$method)}. (cf. \ttt{printf}, \ttt{sprintf}, \ttt{\%d}, \ttt{\%i}, \ttt{\%e}, \ttt{\%f}, \ttt{\%g}, \ttt{\%E}, \ttt{\%F}, \ttt{\%G}) %%%%% \item \ttt{abarn} \newline Physical unit, stating that a number is in attobarns ($10^{-18}$ barn). (cf. also \ttt{nbarn}, \ttt{fbarn}, \ttt{pbarn}) %%%%% \item \ttt{abs} \newline Numerical function that takes the absolute value of its argument: \ttt{abs ({\em })} yields \ttt{|{\em }|}. (cf. also \ttt{conjg}, \ttt{sgn}, \ttt{mod}, \ttt{modulo}) %%%%% \item \ttt{acos} \newline Numerical function \ttt{asin ({\em })} that calculates the arccosine trigonometric function (inverse of \ttt{cos}) of real and complex numerical numbers or variables. (cf. also \ttt{sin}, \ttt{cos}, \ttt{tan}, \ttt{asin}, \ttt{atan}) %%%%% \item \ttt{alias} \newline This allows to define a collective expression for a class of particles, e.g. to define a generic expression for leptons, neutrinos or a jet as \ttt{alias lepton = e1:e2:e3:E1:E2:E3}, \ttt{alias neutrino = n1:n2:n3:N1:N2:N3}, and \ttt{alias jet = u:d:s:c:U:D:S:C:g}, respectively. %%%%% \item \ttt{all} \newline \ttt{all} is a function that works on a logical expression and a list, \ttt{all {\em } [{\em }]}, and returns \ttt{true} if and only if \ttt{log\_expr} is fulfilled for {\em all} entries in \ttt{list}, and \ttt{false} otherwise. Examples: \ttt{all Pt > 100 GeV [lepton]} checks whether all leptons are harder than 100 GeV, \ttt{all Dist > 2 [u:U, d:D]} checks whether all pairs of corresponding quarks are separated in $R$ space by more than 2. Logical expressions with \ttt{all} can be logically combined with \ttt{and} and \ttt{or}. (cf. also \ttt{any}, \ttt{and}, \ttt{no}, and \ttt{or}) %%%%% \item \ttt{alt\_setup} \newline This command allows to specify alternative setups for a process/list of processes, \ttt{alt\_setup = \{ {\em } \} [, \{ {\em } \} , ...]}. An alternative setup can be a resetting of a coupling constant, or different cuts etc. It can be particularly used in a ($\to$) \ttt{rescan} procedure. %%%%% \item \ttt{analysis} \newline This command, \ttt{analysis = {\em }}, allows to define an analysis as a logical expression, with a syntax similar to the ($\to$) \ttt{cuts} or ($\to$) \ttt{selection} command. Note that a ($\to$) formally is a logical expression. %%%%% \item \ttt{and} \newline This is the standard two-place logical connective that has the value true if both of its operands are true, otherwise a value of false. It is applied to logical values, e.g. cut expressions. (cf. also \ttt{all}, \ttt{no}, \ttt{or}). %%%%% \item \ttt{any} \newline \ttt{any} is a function that works on a logical expression and a list, \ttt{any {\em } [{\em }]}, and returns \ttt{true} if \ttt{log\_expr} is fulfilled for any entry in \ttt{list}, and \ttt{false} otherwise. Examples: \ttt{any PDG == 13 [lepton]} checks whether any lepton is a muon, \ttt{any E > 2 * mW [jet]} checks whether any jet has an energy of twice the $W$ mass. Logical expressions with \ttt{any} can be logically combined with \ttt{and} and \ttt{or}. (cf. also \ttt{all}, \ttt{and}, \ttt{no}, and \ttt{or}) %%%%% \item \ttt{as} \newline cf. \ttt{compile} %%%%% \item \ttt{ascii} \newline Specifier for the \ttt{sample\_format} command to demand the generation of the standard \whizard\ verbose/debug ASCII event files. (cf. also \ttt{\$sample}, \ttt{\$sample\_normalization}, \ttt{sample\_format}) %%%%% \item \ttt{asin} \newline Numerical function \ttt{asin ({\em })} that calculates the arcsine trigonometric function (inverse of \ttt{sin}) of real and complex numerical numbers or variables. (cf. also \ttt{sin}, \ttt{cos}, \ttt{tan}, \ttt{acos}, \ttt{atan}) %%%%% \item \ttt{atan} \newline Numerical function \ttt{atan ({\em })} that calculates the arctangent trigonometric function (inverse of \ttt{tan}) of real and complex numerical numbers or variables. (cf. also \ttt{sin}, \ttt{cos}, \ttt{tan}, \ttt{asin}, \ttt{acos}) %%%%% \item \ttt{athena} \newline Specifier for the \ttt{sample\_format} command to demand the generation of the ATHENA variant for HEPEVT ASCII event files. (cf. also \ttt{\$sample}, \ttt{\$sample\_normalization}, \ttt{sample\_format}) %%%%% \item \ttt{beam} \newline Constructor that specifies a particle (in a subevent) as beam particle. It is used in cuts, analyses or selections, e.g. \ttt{cuts = all Theta > 20 degree [beam lepton, lepton]}. (cf. also \ttt{incoming}, \ttt{outgoing}, \ttt{cuts}, \ttt{analysis}, \ttt{selection}, \ttt{record}) %%%%% \item \ttt{beam\_events} \newline Beam structure specifier to read in lepton collider beamstrahlung's spectra from external files as pairs of energy fractions: \ttt{beams: e1, E1 => beam\_events}. Note that this is a pair spectrum that has to be applied to both beams simultaneously. (cf. also \ttt{beams}, \ttt{\$beam\_events\_file}, \ttt{?beam\_events\_warn\_eof}) %%%%% \item \ttt{beams} \newline This specifies the contents and structure of the beams: \ttt{beams = {\em }, {\em } [ => {\em } ....]}. If this command is absent in the input file, \whizard\ automatically takes the two incoming partons (or one for decays) of the corresponding process as beam particles, and no structure functions are applied. Protons and antiprotons as beam particles are predefined as \ttt{p} and \ttt{pbar}, respectively. A structure function, like \ttt{pdf\_builtin}, \ttt{ISR}, \ttt{EPA} and so on are switched on as e.g. \ttt{beams = p, p => lhapdf}. Structure functions can be specified for one of the two beam particles only, of the structure function is not a spectrum. (cf. also \ttt{beams\_momentum}, \ttt{beams\_theta}, \ttt{beams\_phi}, \ttt{beams\_pol\_density}, \ttt{beams\_pol\_fraction}, \ttt{beam\_events}, \ttt{circe1}, \ttt{circe2}, \ttt{energy\_scan}, \ttt{epa}, \ttt{ewa}, \ttt{isr}, \ttt{lhapdf}, \ttt{pdf\_builtin}). %%%%% \item \ttt{beams\_momentum} \newline Command to set the momenta (or energies) for the two beams of a scattering process: \ttt{beams\_momentum = {\em }, {\em }} to allow for asymmetric beam setups (e.g. HERA: \ttt{beams\_momentum = 27.5 GeV, 920 GeV}). Two arguments must be present for a scattering process, but the command can be used with one argument to integrate and simulate a decay of a moving particle. (cf. also \ttt{beams}, \ttt{beams\_theta}, \ttt{beams\_phi}, \ttt{beams\_pol\_density}, \ttt{beams\_pol\_fraction}) %%%%% \item \ttt{beams\_phi} \newline Same as ($\to$) \ttt{beams\_theta}, but to allow for a non-vanishing beam azimuth angle, too. (cf. also \ttt{beams}, \ttt{beams\_theta}, \ttt{beams\_momentum}, \ttt{beams\_pol\_density}, \ttt{beams\_pol\_fraction}) %%%%% \item \ttt{beams\_pol\_density} \newline This command allows to specify the initial state for polarized beams by the syntax: \ttt{beams\_pol\_density = @({\em }), @({\em })}. Two polarization specifiers are mandatory for scattering, while one can be used for decays from polarized probes. The specifier \ttt{{\em }} can be empty (no polarization), has one entry (for a definite helicity/spin orientation), or ranges of entries of a spin density matrix. The command can be used globally, or as a local argument of the \ttt{integrate} command. For detailed information, see Sec.~\ref{sec:initialpolarization}. It is also possible to use variables as placeholders in the specifiers. Note that polarization is assumed to be complete, for partial polarization use ($\to$) \ttt{beams\_pol\_fraction}. (cf. also \ttt{beams}, \ttt{beams\_theta}, \ttt{beams\_phi}, \ttt{beams\_momentum}, \ttt{beams\_pol\_fraction}) %%%%% \item \ttt{beams\_pol\_fraction} \newline This command allows to specify the amount of polarization when using polarized beams ($\to$ \ttt{beams\_pol\_density}). The syntax is: \ttt{beams\_pol\_fraction = {\em }, {\em }}. Two fractions must be present for scatterings, being real numbers between \ttt{0} and \ttt{1}. A specification with percentage is also possible, e.g. \ttt{beams\_pol\_fraction = 80\%, 40\%}. (cf. also \ttt{beams}, \ttt{beams\_theta}, \ttt{beams\_phi}, \ttt{beams\_momentum}, \ttt{beams\_pol\_density}) %%%%% \item \ttt{beams\_theta} \newline Command to set a crossing angle (with respect to the $z$ axis) for one or both of the beams of a scattering process: \ttt{beams\_theta = {\em }, {\em }} to allow for asymmetric beam setups (e.g. \ttt{beams\_angle = 0, 10 degree}). Two arguments must be present for a scattering process, but the command can be used with one argument to integrate and simulate a decay of a moving particle. (cf. also \ttt{beams}, \ttt{beams\_phi}, \ttt{beams\_momentum}, \ttt{beams\_pol\_density}, \ttt{beams\_pol\_fraction}) %%%%% \item \ttt{by} \newline Constructor that replaces the default sorting criterion (according to PDG codes) of the ($\to$) \ttt{sort} function on particle lists/subevents by one given by a unary or binary particle observable: \ttt{sort by {\em } [{\em } [, {\em }] ]}. (cf. also \ttt{sort}, \ttt{extract}, \ttt{join}, \ttt{collect}, \ttt{combine}, \ttt{+}) %%%%% \item \ttt{ceiling} \newline This is a function \ttt{ceiling ({\em })} that gives the least integer greater than or equal to \ttt{{\em }}, e.g. \ttt{int i = ceiling (4.56789)} gives \ttt{i = 5}. (cf. also \ttt{int}, \ttt{nint}, \ttt{floor}) %%%%% \item \ttt{circe1} \newline Beam structure specifier for the \circeone\ structure function for beamstrahlung at a linear lepton collider: \ttt{beams = e1, E1 => circe1}. Note that this is a pair spectrum, so the specifier acts for both beams simultaneously. (cf. also \ttt{beams}, \ttt{?circe1\_photons}, \ttt{?circe1\_photon2}, \ttt{circe1\_sqrts}, \ttt{?circe1\_generate}, \ttt{?circe1\_map}, \ttt{circe1\_eps}, \newline \ttt{circe1\_mapping\_slope}, \ttt{circe1\_ver}, \ttt{circe1\_rev}, \ttt{\$circe1\_acc}, \ttt{circe1\_chat}) %%%%% \item \ttt{circe2} \newline Beam structure specifier for the lepton-collider structure function for photon spectra, \circetwo: \ttt{beams = A, A => circe2}. Note that this is a pair spectrum, an application to only one beam is not possible. (cf. also \ttt{beams}, \ttt{?circe2\_polarized}, \ttt{\$circe2\_file}, \ttt{\$circe2\_design}) %%%%% \item \ttt{clear} \newline This command allows to clear a variable set before: \ttt{clear ({\em })} resets the variable \ttt{{\em }} which could be the \ttt{beams}, the \ttt{unstable} settings, \ttt{sqrts}, any kind of \ttt{cuts} or \ttt{scale} expressions, any user-set variable etc. The syntax of the command is completely analogous to ($\to$) \ttt{show}. %%%%% \item \ttt{close\_out} \newline With the command, \ttt{close\_out ("{\em })} user-defined information like data or ($\to$) \ttt{printf} statements can be written out to a user-defined file. The command closes an I/O stream to an external file \ttt{{\em }}. (cf. also \ttt{open\_out}, \ttt{\$out\_file}, \ttt{printf}) %%%%% \item \ttt{cluster} \newline Command that allows to cluster all particles in a subevent to a set of jets: \ttt{cluster [{\em}]}. It also to cluster particles subject to a certain boolean condition, \ttt{cluster if {\em} [{\em}]}. At the moment only available if the \fastjet\ package is linked. (cf. also \ttt{jet\_r}, \ttt{combine}, \ttt{jet\_algorithm}, \ttt{kt\_algorithm}, \newline \ttt{cambridge\_[for\_passive\_]algorithm}, \ttt{antikt\_algorithm}, \ttt{plugin\_algorithm}, \newline \ttt{genkt\_[for\_passive\_]algorithm}, \ttt{ee\_kt\_algorithm}, \ttt{ee\_genkt\_algorithm}, \ttt{?keep\_flavors\_when\_clustering}) %%%%% \item \ttt{collect} \newline The \ttt{collect [{\em }]} operation collects all particles in the list \ttt{{\em }} into a one-entry subevent with a four-momentum of the sum of all four-momenta of non-overlapping particles in \ttt{{\em }}. (cf. also \ttt{combine}, \ttt{select}, \ttt{extract}, \ttt{sort}) %%%%% \item \ttt{complex} \newline Defines a complex variable. The syntax is e.g. \ttt{complex x = 2 + 3 * I}. (cf.~also \ttt{int}, \ttt{real}) %%%%% \item \ttt{combine} \newline The \ttt{combine [{\em }, {\em }]} operation makes a particle list whose entries are the result of adding (the momenta of) each pair of particles in the two input lists \ttt{list1}, {list2}. For example, \ttt{combine [incoming lepton, lepton]} constructs all mutual pairings of an incoming lepton with an outgoing lepton (an alias for the leptons has to be defined, of course). (cf. also \ttt{collect}, \ttt{select}, \ttt{extract}, \ttt{sort}, \ttt{+}) %%%%% \item \ttt{compile} \newline The \ttt{compile ()} command has no arguments (the parentheses can also been left out: /\ttt{compile ()}. The command is optional, it invokes the compilation of the process(es) (i.e. the matrix element file(s)) to be compiled as a shared library. This shared object file has the standard name \ttt{default\_lib.so} and resides in the \ttt{.libs} subdirectory of the corresponding user workspace. If the user has defined a different library name \ttt{lib\_name} with the \ttt{library} command, then WHIZARD compiles this as the shared object \ttt{.libs/lib\_name.so}. (This allows to split process classes and to avoid too large libraries.) Another possibility is to use the command \ttt{compile as "static\_name"}. This will compile and link the process library in a static way and create the static executable \ttt{static\_name} in the user workspace. (cf. also \ttt{library}) %%%%% \item \ttt{compile\_analysis} \newline The \ttt{compile\_analysis} statement does the same as the \ttt{write\_analysis} command, namely to tell \whizard\ to write the analysis setup by the user for the \sindarin\ input file under consideration. If no \ttt{\$out\_file} is provided, the histogram tables/plot data etc. are written to the default file \ttt{whizard\_analysis.dat}. In addition to \ttt{write\_analysis}, \ttt{compile\_analysis} also invokes the \whizard\ \LaTeX routines for producing postscript or PDF output of the data (unless the flag $\rightarrow$ \ttt{?analysis\_file\_only} is set to \ttt{true}). (cf. also \ttt{\$out\_file}, \ttt{write\_analysis}, \ttt{?analysis\_file\_only}) %%%%% \item \ttt{conjg} \newline Numerical function that takes the complex conjugate of its argument: \ttt{conjg ({\em })} yields \ttt{{\em }$^\ast$}. (cf. also \ttt{abs}, \ttt{sgn}, \ttt{mod}, \ttt{modulo}) %%%%% \item \ttt{cos} \newline Numerical function \ttt{cos ({\em })} that calculates the cosine trigonometric function of real and complex numerical numbers or variables. (cf. also \ttt{sin}, \ttt{tan}, \ttt{asin}, \ttt{acos}, \ttt{atan}) %%%%% \item \ttt{cosh} \newline Numerical function \ttt{cosh ({\em })} that calculates the hyperbolic cosine function of real and complex numerical numbers or variables. Note that its inverse function is part of the \ttt{Fortran2008} status and hence not realized. (cf. also \ttt{sinh}, \ttt{tanh}) %%%%% \item \ttt{count} \newline Subevent function that counts the number of particles or particle pairs in a subevent: \ttt{count [{\em } [, {\em }]]}. This can also be a counting subject to a condition: \ttt{count if {\em } [{\em } [, {\em }]]}. %%%%% \item \ttt{cuts} \newline This command defines the cuts to be applied to certain processes. The syntax is: \ttt{cuts = {\em } {\em } [{\em }]}, where the cut expression must be initialized with a logical classifier \ttt{log\_class} like \ttt{all}, \ttt{any}, \ttt{no}. The logical expression \ttt{log\_expr} contains the cut to be evaluated. Note that this need not only be a kinematical cut expression like \ttt{E > 10 GeV} or \ttt{5 degree < Theta < 175 degree}, but can also be some sort of trigger expression or event selection. Whether the expression is evaluated on particles or pairs of particles depends on whether the discriminating variable is unary or binary, \ttt{Dist} being obviously binary, \ttt{Pt} being unary. Note that some variables are both unary and binary, e.g. the invariant mass $M$. Cut expressions can be connected by the logical connectives \ttt{and} and \ttt{or}. The \ttt{cuts} statement acts on all subsequent process integrations and analyses until a new \ttt{cuts} statement appears. (cf. also \ttt{all}, \ttt{any}, \ttt{Dist}, \ttt{E}, \ttt{M}, \ttt{no}, \ttt{Pt}). %%%%% \item \ttt{debug} \newline Specifier for the \ttt{sample\_format} command to demand the generation of the very verbose \whizard\ ASCII event file format intended for debugging. (cf. also \ttt{\$sample}, \ttt{sample\_format}, \ttt{\$sample\_normalization}) %%%%% \item \ttt{degree} \newline Expression specifying the physical unit of degree for angular variables, e.g. the cut expression function \ttt{Theta}. (if no unit is specified for angular variables, radians are used; cf. \ttt{rad}, \ttt{mrad}). %%%% \item \ttt{Dist} \newline Binary observable specifier, that gives the $\eta$-$\phi$- (pseudorapidity-azimuth) distance $R = \sqrt{(\Delta \eta)^2 + (\Delta\phi)^2}$ between the momenta of the two particles: \ttt{eval Dist [jet, jet]}. (cf. also \ttt{eval}, \ttt{cuts}, \ttt{selection}, \ttt{Theta}, \ttt{Eta}, \ttt{Phi}) %%%%% \item \ttt{dump} \newline Specifier for the \ttt{sample\_format} command to demand the generation of the intrinsic \whizard\ event record format (output of the \ttt{particle\_t} type container). (cf. also \ttt{\$sample}, \ttt{sample\_format}, \ttt{\$sample\_normalization} %%%%% \item \ttt{E} \newline Unary (binary) observable specifier for the energy of a single (two) particle(s), e.g. \ttt{eval E ["W+"]}, \ttt{all E > 200 GeV [b, B]}. (cf. \ttt{eval}, \ttt{cuts}, \ttt{selection}) %%%%% \item \ttt{else} \label{sindarin_else}\newline Constructor for providing an alternative in a conditional clause: \ttt{if {\em } then {\em } else {\em } endif}. (cf. also \ttt{if}, \ttt{elsif}, \ttt{endif}, \ttt{then}). %%%%% \item \ttt{elsif} \newline Constructor for concatenating more than one conditional clause with each other: \ttt{if {\em } then {\em } elsif {\em } then {\em } \ldots endif}. (cf. also \ttt{if}, \ttt{else}, \ttt{endif}, \ttt{then}). %%%%% \item \ttt{endif} \newline Mandatory constructor to conclude a conditional clause: \ttt{if {\em } then \ldots endif}. (cf. also \ttt{if}, \ttt{else}, \ttt{elsif}, \ttt{then}). %%%%% \item \ttt{energy\_scan} \newline Beam structure specifier for the energy scan structure function: \ttt{beams = e1, E1 => energy\_scan}. This pair spectrum that has to be applied to both beams simultaneously can be used to scan over a range of collider energies without using the \ttt{scan} command. (cf. also \ttt{beams}, \ttt{scan}, \ttt{?energy\_scan\_normalize}) %%%%% \item \ttt{epa} \newline Beam structure specifier for the equivalent-photon approximation (EPA), i.e the Weizs\"acker-Williams structure function: e.g. \ttt{beams = e1, E1 => epa} (applied to both beams), or e.g. \ttt{beams = e1, u => epa, none} (applied to only one beam). (cf. also \ttt{beams}, \ttt{epa\_alpha}, \ttt{epa\_x\_min}, \ttt{epa\_mass}, \ttt{epa\_q\_max}, \ttt{epa\_q\_min}, \ttt{?epa\_recoil}, \ttt{?epa\_keep\_energy}) %%%%% \item \ttt{Eta} \newline Unary and also binary observable specifier, that as a unary observable gives the pseudorapidity of a particle momentum. The pseudorapidity is given by $\eta = - \log \left[ \tan (\theta/2) \right]$, where $\theta$ is the angle with the beam direction. As a binary observable, it gives the pseudorapidity difference between the momenta of two particles, where $\theta$ is the enclosed angle: \ttt{eval Eta [e1]}, \ttt{all abs (Eta) < 3.5 [jet, jet]}. (cf. also \ttt{eval}, \ttt{cuts}, \ttt{selection}, \ttt{Rap}, \ttt{abs}) %%%%% \item \ttt{eV} \newline Physical unit, stating that the corresponding number is in electron volt. (cf. also \ttt{keV}, \ttt{meV}, \ttt{MeV}, \ttt{GeV}, \ttt{TeV}) %%%%% \item \ttt{eval} \newline Evaluator that tells \whizard\ to evaluate the following expr: \ttt{eval {\em }}. Examples are: \ttt{eval Rap [e1]}, \ttt{eval M / 1 GeV [combine [q,Q]]} etc. (cf. also \ttt{cuts}, \ttt{selection}, \ttt{record}) %%%%% \item \ttt{ewa} \newline Beam structure specifier for the equivalent-photon approximation (EWA): e.g. \ttt{beams = e1, E1 => ewa} (applied to both beams), or e.g. \ttt{beams = e1, u => ewa, none} (applied to only one beam). (cf. also \ttt{beams}, \ttt{ewa\_x\_min}, \ttt{ewa\_pt\_max}, \ttt{ewa\_mass}, \ttt{?ewa\_keep\_energy}, \ttt{?ewa\_recoil}) %%%%% \item \ttt{exec} \newline Constructor \ttt{exec ("{\em }")} that demands WHIZARD to execute/run the command \ttt{cmd\_name}. For this to work that specific command must be present either in the path of the operating system or as a command in the user workspace. %%%%% \item \ttt{exit} \newline Command to finish the \whizard\ run (and not execute any further code beyond the appearance of \ttt{exit} in the \sindarin\ file. The command (which is the same as $\to$ \ttt{quit}) allows for an argument, \ttt{exit ({\em })}, where the expression can be executed, e.g. a screen message or an exit code. %%%%% \item \ttt{exp} \newline Numerical function \ttt{exp ({\em })} that calculates the exponential of real and complex numerical numbers or variables. (cf. also \ttt{sqrt}, \ttt{log}, \ttt{log10}) %%%%% \item \ttt{expect} \newline The binary function \ttt{expect} compares two numerical expressions whether they fulfill a certain ordering condition or are equal up to a specific uncertainty or tolerance which can bet set by the specifier \ttt{tolerance}, i.e. in principle it checks whether a logical expression is true. The \ttt{expect} function does actually not just check a value for correctness, but also records its result. If failures are present when the program terminates, the exit code is nonzero. The syntax is \ttt{expect ({\em } {\em } {\em })}, where \ttt{{\em }} and \ttt{{\em }} are two numerical values (or corresponding variables) and \ttt{{\em }} is one of the following logical comparators: \ttt{<}, \ttt{>}, \ttt{<=}, \ttt{>=}, \ttt{==}, \ttt{<>}. (cf. also \ttt{<}, \ttt{>}, \ttt{<=}, \ttt{>=}, \ttt{==}, \ttt{<>}, \ttt{tolerance}). %%%%% \item \ttt{extract} \newline Subevent function that either extracts the first element of a particle list/subevent: \ttt{extract [ {\em }]}, or the element at position \ttt{} of the particle list: \ttt{extract {\em index } [ {\em }]}. Negative index values count from the end of the list. (cf. also \ttt{sort}, \ttt{combine}, \ttt{collect}, \ttt{+}, \ttt{index}) %%%%% \item \ttt{factorization\_scale} \newline This is a command, \ttt{factorization\_scale = {\em }}, that sets the factorization scale of a process or list of processes. It overwrites a possible scale set by the ($\to$) \ttt{scale} command. \ttt{{\em }} can be any kinematic expression that leads to a result of momentum dimension one, e.g. \ttt{100 GeV}, \ttt{eval Pt [e1]}. (cf. also \ttt{renormalization\_scale}). %%%%% \item \ttt{false} \newline Constructor stating that a logical expression or variable is false, e.g. \ttt{?{\em } = false}. (cf. also \ttt{true}). %%%%% \item \ttt{fbarn} \newline Physical unit, stating that a number is in femtobarns ($10^{-15}$ barn). (cf. also \ttt{nbarn}, \ttt{abarn}, \ttt{pbarn}) %%%%% \item \ttt{floor} \newline This is a function \ttt{floor ({\em })} that gives the greatest integer less than or equal to \ttt{{\em }}, e.g. \ttt{int i = floor (4.56789)} gives \ttt{i = 4}. (cf. also \ttt{int}, \ttt{nint}, \ttt{ceiling}) %%%%% \item \ttt{gaussian} \newline Beam structure specifier that imposes a Gaussian energy distribution, separately for each beam. The $\sigma$ values are set by \ttt{gaussian\_spread1} and \ttt{gaussian\_spread2}, respectively. %%%%% \item \ttt{GeV} \newline Physical unit, energies in $10^9$ electron volt. This is the default energy unit of WHIZARD. (cf. also \ttt{eV}, \ttt{keV}, \ttt{MeV}, \ttt{meV}, \ttt{TeV}) %%%%% \item \ttt{graph} \newline This command defines the necessary information regarding producing a graph of a function in \whizard's internal graphical \gamelan\ output. The syntax is: \ttt{graph {\em } \{ {\em } \}}. The record with name \ttt{{\em }} has to be defined, either before or after the graph definition. Possible optional arguments of the \ttt{graph} command are the minimal and maximal values of the axes (\ttt{x\_min}, \ttt{x\_max}, \ttt{y\_min}, \ttt{y\_max}). (cf. \ttt{plot}, \ttt{histogram}, \ttt{record}) %%%%% \item \ttt{Hel} \newline Unary observable specifier that allows to specify the helicity of a particle, e.g. \ttt{all Hel == -1 [e1]} in a selection. (cf. also \ttt{eval}, \ttt{cuts}, \ttt{selection}) %%%%% \item \ttt{hepevt} \newline Specifier for the \ttt{sample\_format} command to demand the generation of HEPEVT ASCII event files. (cf. also \ttt{\$sample}, \ttt{sample\_format}) %%%%% \item \ttt{hepevt\_verb} \newline Specifier for the \ttt{sample\_format} command to demand the generation of the extended or verbose version of HEPEVT ASCII event files. (cf. also \ttt{\$sample}, \ttt{sample\_format}) %%%%% \item \ttt{hepmc} \newline Specifier for the \ttt{sample\_format} command to demand the generation of HepMC ASCII event files. Note that this is only available if the HepMC package is installed and correctly linked. (cf. also \ttt{\$sample}, \ttt{sample\_format}, \ttt{?hepmc\_output\_cross\_section}) %%%%% \item \ttt{histogram} \newline This command defines the necessary information regarding plotting data as a histogram, in the form of: \ttt{histogram {\em } \{ {\em } \}}. The record with name \ttt{{\em }} has to be defined, either before or after the histogram definition. Possible optional arguments of the \ttt{histogram} command are the minimal and maximal values of the axes (\ttt{x\_min}, \ttt{x\_max}, \ttt{y\_min}, \ttt{y\_max}). (cf. \ttt{graph}, \ttt{plot}, \ttt{record}) %%%%% \item \ttt{if} \newline Conditional clause with the construction \ttt{if {\em } then {\em } [else {\em } \ldots] endif}. Note that there must be an \ttt{endif} statement. For more complicated expressions it is better to use expressions in parentheses: \ttt{if ({\em }) then \{{\em }\} else \{{\em }\} endif}. Examples are a selection of up quarks over down quarks depending on a logical variable: \ttt{if ?ok then u else d}, or the setting of an integer variable depending on the rapidity of some particle: \ttt{if (eta > 0) then \{ a = +1\} else \{ a = -1\}}. (cf. also \ttt{elsif}, \ttt{endif}, \ttt{then}) %%%%% \item \ttt{in} \newline Second part of the constructor to let a variable be local to an expression. It has the syntax \ttt{let {\em } = {\em } in {\em }}. E.g. \ttt{let int a = 3 in let int b = 4 in {\em }} (cf. also \ttt{let}) %%%%% \item \ttt{include} \newline The \ttt{include} statement, \ttt{include ("file.sin")} allows to include external \sindarin\ files \ttt{file.sin} into the main WHIZARD input file. A standard example is the inclusion of the standard cut file \ttt{default\_cuts.sin}. %%%%% \item \ttt{incoming} \newline Constructor that specifies particles (or subevents) as incoming. It is used in cuts, analyses or selections, e.g. \ttt{cuts = all Theta > 20 degree [incoming lepton, lepton]}. (cf. also \ttt{beam}, \ttt{outgoing}, \ttt{cuts}, \ttt{analysis}, \ttt{selection}, \ttt{record}) %%%%% \item \ttt{index} \newline Specifies the position of the element of a particle to be extracted by the subevent function ($\to$) \ttt{extract}: \ttt{extract {\em index } [ {\em }]}. Negative index values count from the end of the list. (cf. also \ttt{extract}, \ttt{sort}, \ttt{combine}, \ttt{collect}, \ttt{+}) %%%%% \item \ttt{int} \newline 1) This is a constructor to specify integer constants in the input file. Strictly speaking, it is a unary function setting the value \ttt{int\_val} of the integer variable \ttt{int\_var}: \ttt{int {\em } = {\em }}. Note that is mandatory for all user-defined variables. (cf. also \ttt{real} and \ttt{complex}) 2) It is a function \ttt{int ({\em })} that converts real and complex numbers (here their real parts) into integers. (cf. also \ttt{nint}, \ttt{floor}, \ttt{ceiling}) %%%%% \item \ttt{integrate} \newline The \ttt{integrate ({\em }) \{ {\em } \}} command invokes the integration (phase-space generation and Monte-Carlo sampling) of the process \ttt{proc\_name} (which can also be a list of processes) with the integration options \ttt{{\em }}. Possible options are (1) via \ttt{\$integration\_method = "{\em }"} the integration method (the default being VAMP), (2) the number of iterations and calls per integration during the Monte-Carlo phase-space integration via the \ttt{iterations} specifier; (3) goal for the accuracy, error or relative error (\ttt{accuracy\_goal}, \ttt{error\_goal}, \ttt{relative\_error\_goal}). (4) Invoking only phase space generation (\ttt{?phs\_only = true}), (5) making test calls of the matrix element. (cf. also \ttt{iterations}, \ttt{accuracy\_goal}, \ttt{error\_goal}, \ttt{relative\_error\_goal}, \ttt{error\_threshold}) %%%%% \item \ttt{isr} \newline Beam structure specifier for the lepton-collider/QED initial-state radiation (ISR) structure function: e.g. \ttt{beams = e1, E1 => isr} (applied to both beams), or e.g. \ttt{beams = e1, u => isr, none} (applied to only one beam). (cf. also \ttt{beams}, \ttt{isr\_alpha}, \ttt{isr\_q\_max}, \ttt{isr\_mass}, \ttt{isr\_order}, \ttt{?isr\_recoil}, \ttt{?isr\_keep\_energy}) %%%%% \item \ttt{iterations} \qquad (default: internal heuristics) \newline Option to set the number of iterations and calls per iteration during the Monte-Carlo phase-space integration process. The syntax is \ttt{iterations = {\em }:{\em }}. Note that this can be also a list, separated by colons, which breaks up the integration process into passes of the specified number of integrations and calls each. It works for all integration methods. For VAMP, there is the additional option to specify whether grids and channel weights should be adapted during iterations (\ttt{"g"}, \ttt{"w"}, \ttt{"gw"} for both, or \ttt{""} for no adaptation). (cf. also \ttt{integrate}, \ttt{accuracy\_goal}, \ttt{error\_goal}, \ttt{relative\_error\_goal}, \ttt{error\_threshold}). %%%%% \item \ttt{join} \newline Subevent function that concatenates two particle lists/subevents if there is no overlap: \ttt{join [{\em }, {\em }]}. The joining of the two lists can also be made depending on a condition: \ttt{join if {\em } [{\em }, {\em }]}. (cf. also \ttt{\&}, \ttt{collect}, \ttt{combine}, \ttt{extract}, \ttt{sort}, \ttt{+}) %%%%% \item \ttt{keV} \newline Physical unit, energies in $10^3$ electron volt. (cf. also \ttt{eV}, \ttt{meV}, \ttt{MeV}, \ttt{GeV}, \ttt{TeV}) %%%%% \item \ttt{kT} \newline Binary particle observable that represents a jet $k_T$ clustering measure: \ttt{kT [j1, j2]} gives the following kinematic expression: $2 \min(E_{j1}^2, E_{j2}^2) / Q^2 \times (1 - \cos\theta_{j1,j2})$. At the moment, $Q^2 = 1$. %%%%% \item \ttt{let} \newline This allows to let a variable be local to an expression. It has the syntax \ttt{let {\em } = {\em } in {\em }}. E.g. \ttt{let int a = 3 in let int b = 4 in {\em }} (cf. also \ttt{in}) %%%%% \item \ttt{lha} \newline Specifier for the \ttt{sample\_format} command to demand the generation of the \whizard\ version 1 style (deprecated) LHA ASCII event format files. (cf. also \ttt{\$sample}, \newline \ttt{sample\_format}) %%%%% \item \ttt{lhapdf} \newline This is a beams specifier to demand calling \lhapdf\ parton densities as structure functions to integrate processes in hadron collisions. Note that this only works if the external \lhapdf\ library is present and correctly linked. (cf. \ttt{beams}, \ttt{\$lhapdf\_dir}, \ttt{\$lhapdf\_file}, \ttt{lhapdf\_photon}, \ttt{\$lhapdf\_photon\_file}, \ttt{lhapdf\_member}, \ttt{lhapdf\_photon\_scheme}) %%%%% \item \ttt{lhapdf\_photon} \newline This is a beams specifier to demand calling \lhapdf\ parton densities as structure functions to integrate processes in hadron collisions with a photon as initializer of the hard scattering process. Note that this only works if the external \lhapdf\ library is present and correctly linked. (cf. \ttt{beams}, \ttt{lhapdf}, \ttt{\$lhapdf\_dir}, \ttt{\$lhapdf\_file}, \ttt{\$lhapdf\_photon\_file}, \ttt{lhapdf\_member}, \ttt{lhapdf\_photon\_scheme}) %%%%% \item \ttt{lhef} \newline Specifier for the \ttt{sample\_format} command to demand the generation of the Les Houches Accord (LHEF) event format files, with XML headers. There are several different versions of this format, which can be selected via the \ttt{\$lhef\_version} specifier (cf. also \ttt{\$sample}, \ttt{sample\_format}, \ttt{\$lhef\_version}, \ttt{\$lhef\_extension}, \ttt{?lhef\_write\_sqme\_prc}, \newline \ttt{?lhef\_write\_sqme\_ref}, \ttt{?lhef\_write\_sqme\_alt}) %%%%% \item \ttt{library} \newline The command \ttt{library = "{\em }"} allows to specify a separate shared object library archive \ttt{lib\_name.so}, not using the standard library \ttt{default\_lib.so}. Those libraries (when using shared libraries) are located in the \ttt{.libs} subdirectory of the user workspace. Specifying a separate library is useful for splitting up large lists of processes, or to restrict a larger number of different loaded model files to one specific process library. (cf. also \ttt{compile}, \ttt{\$library\_name}) %%%%% \item \ttt{log} \newline Numerical function \ttt{log ({\em })} that calculates the natural logarithm of real and complex numerical numbers or variables. (cf. also \ttt{sqrt}, \ttt{exp}, \ttt{log10}) %%%%% \item \ttt{log10} \newline Numerical function \ttt{log10 ({\em })} that calculates the base 10 logarithm of real and complex numerical numbers or variables. (cf. also \ttt{sqrt}, \ttt{exp}, \ttt{log}) %%%%% \item \ttt{long} \newline Specifier for the \ttt{sample\_format} command to demand the generation of the long variant of HEPEVT ASCII event files. (cf. also \ttt{\$sample}, \ttt{sample\_format}) %%%%% \item \ttt{M} \newline Unary (binary) observable specifier for the (signed) mass of a single (two) particle(s), e.g. \ttt{eval M [e1]}, \ttt{any M = 91 GeV [e2, E2]}. (cf. \ttt{eval}, \ttt{cuts}, \ttt{selection}) %%%%% \item \ttt{M2} \newline Unary (binary) observable specifier for the mass squared of a single (two) particle(s), e.g. \ttt{eval M2 [e1]}, \ttt{all M2 > 2*mZ [e2, E2]}. (cf. \ttt{eval}, \ttt{cuts}, \ttt{selection}) %%%%% \item \ttt{max} \newline Numerical function with two arguments \ttt{max ({\em }, {\em })} that gives the maximum of the two arguments: $\max (var1, var2)$. It can act on all combinations of integer and real variables. Example: \ttt{real heavier\_mass = max (mZ, mH)}. (cf. also \ttt{min}) %%%%% \item \ttt{meV} \newline Physical unit, stating that the corresponding number is in $10^{-3}$ electron volt. (cf. also \ttt{eV}, \ttt{keV}, \ttt{MeV}, \ttt{GeV}, \ttt{TeV}) %%%%% \item \ttt{MeV} \newline Physical unit, energies in $10^6$ electron volt. (cf. also \ttt{eV}, \ttt{keV}, \ttt{meV}, \ttt{GeV}, \ttt{TeV}) %%%%% \item \ttt{min} \newline Numerical function with two arguments \ttt{min ({\em }, {\em })} that gives the minimum of the two arguments: $\min (var1, var2)$. It can act on all combinations of integer and real variables. Example: \ttt{real lighter\_mass = min (mZ, mH)}. (cf. also \ttt{max}) %%%%% \item \ttt{mod} \newline Numerical function for integer and real numbers \ttt{mod (x, y)} that computes the remainder of the division of \ttt{x} by \ttt{y} (which must not be zero). (cf. also \ttt{abs}, \ttt{conjg}, \ttt{sgn}, \ttt{modulo}) %%%%% \item \ttt{model} \qquad (default: \ttt{SM}) \newline With this specifier, \ttt{model = {\em }}, one sets the hard interaction physics model for the processes defined after this model specification. The list of available models can be found in Table \ref{tab:models}. Note that the model specification can appear arbitrarily often in a \sindarin\ input file, e.g. for compiling and running processes defined in different physics models. (cf. also \ttt{\$model\_name}) %%%%% \item \ttt{modulo} \newline Numerical function for integer and real numbers \ttt{modulo (x, y)} that computes the value of $x$ modulo $y$. (cf. also \ttt{abs}, \ttt{conjg}, \ttt{sgn}, \ttt{mod}) %%%%% \item \ttt{mokka} \newline Specifier for the \ttt{sample\_format} command to demand the generation of the MOKKA variant for HEPEVT ASCII event files. (cf. also \ttt{\$sample}, \ttt{sample\_format}) %%%%% \item \ttt{mrad} \newline Expression specifying the physical unit of milliradians for angular variables. This default in \whizard\ is \ttt{rad}. (cf. \ttt{degree}, \ttt{rad}). %%%%% \item \ttt{nbarn} \newline Physical unit, stating that a number is in nanobarns ($10^{-9}$ barn). (cf. also \ttt{abarn}, \ttt{fbarn}, \ttt{pbarn}) %%%%% \item \ttt{n\_in} \newline Integer variable that accesses the number of incoming particles of a process. It can be used in cuts or in an analysis. (cf. also \ttt{sqrts\_hat}, \ttt{cuts}, \ttt{record}, \ttt{n\_out}, \ttt{n\_tot}) %%%%% \item \ttt{Nacl} \newline Unary observable specifier that returns the total number of open anticolor lines of a particle or subevent (i.e., composite particle). Defined only if \ttt{?colorize\_subevt} is true.. (cf. also \ttt{Ncol}, \ttt{?colorize\_subevt}) %%%%% \item \ttt{Ncol} \newline Unary observable specifier that returns the total number of open color lines of a particle or subevent (i.e., composite particle). Defined only if \ttt{?colorize\_subevt} is true.. (cf. also \ttt{Nacl}, \ttt{?colorize\_subevt}) %%%%% \item \ttt{nint} \newline This is a function \ttt{nint ({\em })} that converts real numbers into the closest integer, e.g. \ttt{int i = nint (4.56789)} gives \ttt{i = 5}. (cf. also \ttt{int}, \ttt{floor}, \ttt{ceiling}) %%%%% \item \ttt{no} \newline \ttt{no} is a function that works on a logical expression and a list, \ttt{no {\em } [{\em }]}, and returns \ttt{true} if and only if \ttt{log\_expr} is fulfilled for {\em none} of the entries in \ttt{list}, and \ttt{false} otherwise. Examples: \ttt{no Pt < 100 GeV [lepton]} checks whether no lepton is softer than 100 GeV. It is the logical opposite of the function \ttt{all}. Logical expressions with \ttt{no} can be logically combined with \ttt{and} and \ttt{or}. (cf. also \ttt{all}, \ttt{any}, \ttt{and}, and \ttt{or}) %%%%% \item \ttt{none} \newline Beams specifier that can used to explicitly {\em not} apply a structure function to a beam, e.g. in HERA physics: \ttt{beams = e1, P => none, pdf\_builtin}. (cf. also \ttt{beams}) %%%%% \item \ttt{not} \newline This is the standard logical negation that converts true into false and vice versa. It is applied to logical values, e.g. cut expressions. (cf. also \ttt{and}, \ttt{or}). %%%%% \item \ttt{n\_out} \newline Integer variable that accesses the number of outgoing particles of a process. It can be used in cuts or in an analysis. (cf. also \ttt{sqrts\_hat}, \ttt{cuts}, \ttt{record}, \ttt{n\_in}, \ttt{n\_tot}) %%%%% \item \ttt{n\_tot} \newline Integer variable that accesses the total number of particles (incoming plus outgoing) of a process. It can be used in cuts or in an analysis. (cf. also \ttt{sqrts\_hat}, \ttt{cuts}, \ttt{record}, \ttt{n\_in}, \ttt{n\_out}) %%%%% \item \ttt{observable} \newline With this, \ttt{observable = {\em }}, the user is able to define a variable specifier \ttt{obs\_spec} for observables. These can be reused in the analysis, e.g. as a \ttt{record}, as functions of the fundamental kinematical variables of the processes. (cf. \ttt{analysis}, \ttt{record}) %%%%% \item \ttt{open\_out} \newline With the command, \ttt{open\_out ("{\em })} user-defined information like data or ($\to$) \ttt{printf} statements can be written out to a user-defined file. The command opens an I/O stream to an external file \ttt{{\em }}. (cf. also \ttt{close\_out}, \ttt{\$out\_file}, \ttt{printf}) %%%%% \item \ttt{or} \newline This is the standard two-place logical connective that has the value true if one of its operands is true, otherwise a value of false. It is applied to logical values, e.g. cut expressions. (cf. also \ttt{and}, \ttt{not}). %%%%% \item \ttt{outgoing} \newline Constructor that specifies particles (or subevents) as outgoing. It is used in cuts, analyses or selections, e.g. \ttt{cuts = all Theta > 20 degree [incoming lepton, outgoing lepton]}. Note that the \ttt{outgoing} keyword is redundant and included only for completeness: \ttt{outgoing lepton} has the same meaning as \ttt{lepton}. (cf. also \ttt{beam}, \ttt{incoming}, \ttt{cuts}, \ttt{analysis}, \ttt{selection}, \ttt{record}) %%%%% \item \ttt{P} \newline Unary (binary) observable specifier for the spatial momentum $\sqrt{\vec{p}^2}$ of a single (two) particle(s), e.g. \ttt{eval P ["W+"]}, \ttt{all P > 200 GeV [b, B]}. (cf. \ttt{eval}, \ttt{cuts}, \ttt{selection}) %%%%% \item \ttt{pbarn} \newline Physical unit, stating that a number is in picobarns ($10^{-12}$ barn). (cf. also \ttt{abarn}, \ttt{fbarn}, \ttt{nbarn}) %%%%% \item \ttt{pdf\_builtin} \newline This is a beams specifier for \whizard's internal PDF structure functions to integrate processes in hadron collisions. (cf. \ttt{beams}, \ttt{pdf\_builtin\_photon}, \ttt{\$pdf\_builtin\_file}) %%%%% \item \ttt{pdf\_builtin\_photon} \newline This is a beams specifier for \whizard's internal PDF structure functions to integrate processes in hadron collisions with a photon as initializer of the hard scattering process. (cf. \ttt{beams}, \ttt{\$pdf\_builtin\_file}) %%%%% \item \ttt{PDG} \newline Unary observable specifier that allows to specify the PDG code of a particle, e.g. \ttt{eval PDG [e1]}, giving \ttt{11}. (cf. also \ttt{eval}, \ttt{cuts}, \ttt{selection}) %%%%% \item \ttt{Phi} \newline Unary and also binary observable specifier, that as a unary observable gives the azimuthal angle of a particle's momentum in the detector frame (beam into $+z$ direction). As a binary observable, it gives the azimuthal difference between the momenta of two particles: \ttt{eval Phi [e1]}, \ttt{all Phi > Pi [jet, jet]}. (cf. also \ttt{eval}, \ttt{cuts}, \ttt{selection}, \ttt{Theta}) %%%%% \item \ttt{photon\_isolation} \newline Logical function \ttt{photon\_isolation if {\em } [{\em } , {\em }]} that cuts out event where the photons in \ttt{{\em }} do not fulfill the condition \ttt{{\em }} and are not isolated from hadronic (and electromagnetic) activity, i.e. the photon fragmentation. (cf. also \ttt{cluster}, \ttt{collect}, \ttt{combine}, \ttt{extract}, \ttt{select}, \ttt{sort}, \ttt{+}) %%%%% \item \ttt{Pl} \newline Unary (binary) observable specifier for the longitudinal momentum ($p_z$ in the c.m. frame) of a single (two) particle(s), e.g. \ttt{eval Pl ["W+"]}, \ttt{all Pl > 200 GeV [b, B]}. (cf. \ttt{eval}, \ttt{cuts}, \ttt{selection}) %%%%% \item \ttt{plot} \newline This command defines the necessary information regarding plotting data as a graph, in the form of: \ttt{plot {\em } \{ {\em } \}}. The record with name \ttt{{\em }} has to be defined, either before or after the plot definition. Possible optional arguments of the \ttt{plot} command are the minimal and maximal values of the axes (\ttt{x\_min}, \ttt{x\_max}, \ttt{y\_min}, \ttt{y\_max}). (cf. \ttt{graph}, \ttt{histogram}, \ttt{record}) %%%%% \item \ttt{polarized} \newline Constructor to instruct \whizard\ to retain polarization of the corresponding particles in the generated events: \ttt{polarized {\em } [, {\em } , ...]}. (cf. also \ttt{unpolarized}, \ttt{simulate}, \ttt{?polarized\_events}) %%%%% \item \ttt{printf} \newline Command that allows to print data as screen messages, into logfiles or into user-defined output files: \ttt{printf "{\em }"}. There exist format specifiers, very similar to the \ttt{C} command \ttt{printf}, e.g. \ttt{printf "\%i" (123)}. (cf. also \ttt{open\_out}, \ttt{close\_out}, \ttt{\$out\_file}, \ttt{?out\_advance}, \ttt{sprintf}, \ttt{\%d}, \ttt{\%i}, \ttt{\%e}, \ttt{\%f}, \ttt{\%g}, \ttt{\%E}, \ttt{\%F}, \ttt{\%G}, \ttt{\%s}) %%%%% \item \ttt{process} \newline Allows to set a hard interaction process, either for a decay process with name \ttt{{\em }} as \ttt{process {\em } = {\em } => {\em }, {\em }, ...}, or for a scattering process with name \ttt{{\em } = {\em }, {\em } => {\em }, {\em }, ...}. Note that there can be arbitrarily many processes to be defined in a \sindarin\ input file. There are two options for particle/process sums: flavor sums: \ttt{{\em }:{\em }:...}, where all masses have to be identical, and inclusive sums, \ttt{{\em } + {\em } + ...}. The latter can be done on the level of individual particles, or sums over whole final states. Here, masses can differ, and terms will be translated into different process components. The \ttt{process} command also allows for optional arguments, e.g. to specify a numerical identifier (cf. \ttt{process\_num\_id}), the method how to generate the code for the matrix element(s): \ttt{\$method}, possible methods are either with the \oMega\ matrix element generator, using template matrix elements with different normalizations, or completely internal matrix element; for \oMega\ matrix elements there is also the possibility to specify possible restrictions (cf. \ttt{\$restrictions}). %%%%% \item \ttt{Pt} \newline Unary (binary) observable specifier for the transverse momentum ($\sqrt{p_x^2 + p_y^2}$ in the c.m. frame) of a single (two) particle(s), e.g. \ttt{eval Pt ["W+"]}, \ttt{all Pt > 200 GeV [b, B]}. (cf. \ttt{eval}, \ttt{cuts}, \ttt{selection}) %%%%% \item \ttt{Px} \newline Unary (binary) observable specifier for the $x$-component of the momentum of a single (two) particle(s), e.g. \ttt{eval Px ["W+"]}, \ttt{all Px > 200 GeV [b, B]}. (cf. \ttt{eval}, \ttt{cuts}, \ttt{selection}) %%%%% \item \ttt{Py} \newline Unary (binary) observable specifier for the $y$-component of the momentum of a single (two) particle(s), e.g. \ttt{eval Py ["W+"]}, \ttt{all Py > 200 GeV [b, B]}. (cf. \ttt{eval}, \ttt{cuts}, \ttt{selection}) %%%%% \item \ttt{Pz} \newline Unary (binary) observable specifier for the $z$-component of the momentum of a single (two) particle(s), e.g. \ttt{eval Pz ["W+"]}, \ttt{all Pz > 200 GeV [b, B]}. (cf. \ttt{eval}, \ttt{cuts}, \ttt{selection}) %%%%% \item \ttt{quit} \newline Command to finish the \whizard\ run (and not execute any further code beyond the appearance of \ttt{quit} in the \sindarin\ file. The command (which is the same as $\to$ \ttt{exit}) allows for an argument, \ttt{quit ({\em })}, where the expression can be executed, e.g. a screen message or an quit code. %%%%% \item \ttt{rad} \newline Expression specifying the physical unit of radians for angular variables. This is the default in \whizard. (cf. \ttt{degree}, \ttt{mrad}). %%%%% \item \ttt{Rap} \newline Unary and also binary observable specifier, that as a unary observable gives the rapidity of a particle momentum. The rapidity is given by $y = \frac12 \log \left[ (E + p_z)/(E-p_z) \right]$. As a binary observable, it gives the rapidity difference between the momenta of two particles: \ttt{eval Rap [e1]}, \ttt{all abs (Rap) < 3.5 [jet, jet]}. (cf. also \ttt{eval}, \ttt{cuts}, \ttt{selection}, \ttt{Eta}, \ttt{abs}) %%%%% \item \ttt{read\_slha} \newline Tells \whizard\ to read in an input file in the SUSY Les Houches accord (SLHA), as \ttt{read\_slha ("slha\_file.slha")}. Note that the files for the use in \whizard\ should have the suffix \ttt{.slha}. (cf. also \ttt{write\_slha}, \ttt{?slha\_read\_decays}, \ttt{?slha\_read\_input}, \ttt{?slha\_read\_spectrum}) %%%%% \item \ttt{real} \newline This is a constructor to specify real constants in the input file. Strictly speaking, it is a unary function setting the value \ttt{real\_val} of the real variable \ttt{real\_var}: \ttt{real {\em } = {\em }}. (cf. also \ttt{int} and \ttt{complex}) %%%%% \item \ttt{real\_epsilon}\\ Predefined real; the relative uncertainty intrinsic to the floating point type of the \fortran\ compiler with which \whizard\ has been built. %%%%% \item \ttt{real\_precision}\\ Predefined integer; the decimal precision of the floating point type of the \fortran\ compiler with which \whizard\ has been built. %%%%% \item \ttt{real\_range}\\ Predefined integer; the decimal range of the floating point type of the \fortran\ compiler with which \whizard\ has been built. %%%%% \item \ttt{real\_tiny}\\ Predefined real; the smallest number which can be represented by the floating point type of the \fortran\ compiler with which \whizard\ has been built. %%%%% \item \ttt{record} \newline The \ttt{record} constructor provides an internal data structure in \sindarin\ input files. Its syntax is in general \ttt{record {\em } ({\em })}. The \ttt{{\em }} could be the definition of a tuple of points for a histogram or an \ttt{eval} constructor that tells \whizard\ e.g. by which rule to calculate an observable to be stored in the record \ttt{record\_name}. Example: \ttt{record h (12)} is a record for a histogram defined under the name \ttt{h} with the single data point (bin) at value 12; \ttt{record rap1 (eval Rap [e1])} defines a record with name \ttt{rap1} which has an evaluator to calculate the rapidity (predefined \whizard\ function) of an outgoing electron. (cf. also \ttt{eval}, \ttt{histogram}, \ttt{plot}) %%%%% \item \ttt{renormalization\_scale} \newline This is a command, \ttt{renormalization\_scale = {\em }}, that sets the renormalization scale of a process or list of processes. It overwrites a possible scale set by the ($\to$) \ttt{scale} command. \ttt{{\em }} can be any kinematic expression that leads to a result of momentum dimension one, e.g. \ttt{100 GeV}, \ttt{eval Pt [e1]}. (cf. also \ttt{factorization\_scale}). %%%%% \item \ttt{rescan} \newline This command allows to rescan event samples with modified model parameter, beam structure etc. to recalculate (analysis) observables, e.g.: \newline \ttt{rescan "{\em }" ({\em }) \{ {\em }\}}. \newline \ttt{"{\em }"} is the name of the event file and \ttt{{\em }} is the process whose (existing) event file of arbitrary size that is to be rescanned. Several flags allow to reconstruct the beams ($\to$ \ttt{?recover\_beams}), to reuse only the hard process but rebuild the full events ($\to$ \ttt{?update\_event}), to recalculate the matrix element ($\to$ \ttt{?update\_sqme}) or to recalculate the individual event weight ($\to$ \ttt{?update\_weight}). Further rescan options are redefining model parameter input, or defining a completely new alternative setup ($\to$ \ttt{alt\_setup}) (cf. also \ttt{\$rescan\_input\_format}) %%%%% \item \ttt{results} \newline Only used in the combination \ttt{show (results)}. Forces \whizard\ to print out a results summary for the integrated processes. (cf. also \ttt{show}) %%%%% \item \ttt{reweight} \newline The \ttt{reweight = {\em }} command allows to give for a process or list of processes an alternative weight, given by any kind of scalar expression \ttt{{\em }}, e.g. \ttt{reweight = 0.2} or \ttt{reweight = (eval M2 [e1, E1]) / (eval M2 [e2, E2])}. (cf. also \ttt{alt\_setup}, \ttt{weight}, \ttt{rescan}) %%%%% \item \ttt{sample\_format} \newline Variable that allows the user to specify additional event formats beyond the \whizard\ native binary event format. Its syntax is \ttt{sample\_format = {\em }}, where \ttt{{\em }} can be any of the following specifiers: \ttt{hepevt}, \ttt{hepevt\_verb}, \ttt{ascii}, \ttt{athena}, \ttt{debug}, \ttt{long}, \ttt{short}, \ttt{hepmc}, \ttt{lhef}, \ttt{lha}, \ttt{lha\_verb}, \ttt{stdhep}, \ttt{stdhep\_up}. (cf. also \ttt{\$sample}, \ttt{simulate}, \ttt{hepevt}, \ttt{ascii}, \ttt{athena}, \ttt{debug}, \ttt{long}, \ttt{short}, \ttt{hepmc}, \ttt{lhef}, \ttt{lha}, \ttt{stdhep}, \ttt{stdhep\_up}, \newline \ttt{\$sample\_normalization}, \ttt{?sample\_pacify}, \ttt{sample\_max\_tries}, \ttt{sample\_split\_n\_evt}, \ttt{sample\_split\_n\_kbytes}) %%%%% \item \ttt{scale} \newline This is a command, \ttt{scale = {\em }}, that sets the kinematic scale of a process or list of processes. Unless overwritten explicitly by ($\to$) \ttt{factorization\_scale} and/or ($\to$) \ttt{renormalization\_scale} it sets both scales. \ttt{{\em }} can be any kinematic expression that leads to a result of momentum dimension one, e.g. \ttt{scale = 100 GeV}, \ttt{scale = eval Pt [e1]}. %%%%% \item \ttt{scan} \newline Constructor to perform loops over variables or scan over processes in the integration procedure. The syntax is \ttt{scan {\em } {\em } ({\em } or {\em } => {\em } /{\em } {\em }) \{ {\em } \}}. The variable \ttt{var} can be specified if it is not a real, e.g. an integer. \ttt{var\_name} is the name of the variable which is also allowed to be a predefined one like \ttt{seed}. For the scan, one can either specify an explicit list of values \ttt{value list}, or use an initial and final value and a rule to increment. The \ttt{scan\_cmd} can either be just a \ttt{show} to print out the scanned variable or the integration of a process. Examples are: \ttt{scan seed (32 => 1 // 2) \{ show (seed\_value) \} }, which runs the seed down in steps 32, 16, 8, 4, 2, 1 (division by two). \ttt{scan mW (75 GeV, 80 GeV => 82 GeV /+ 0.5 GeV, 83 GeV => 90 GeV /* 1.2) \{ show (sw) \} } scans over the $W$ mass for the values 75, 80, 80.5, 81, 81.5, 82, 83 GeV, namely one discrete value, steps by adding 0.5 GeV, and increase by 20 \% (the latter having no effect as it already exceeds the final value). It prints out the corresponding value of the effective mixing angle which is defined as a dependent variable in the model input file(s). \ttt{scan sqrts (500 GeV => 600 GeV /+ 10 GeV) \{ integrate (proc) \} } integrates the process \ttt{proc} in eleven increasing 10 GeV steps in center-of-mass energy from 500 to 600 GeV. (cf. also \ttt{/+}, \ttt{/+/}, \ttt{/-}, \ttt{/*}, \ttt{/*/}, \ttt{//}) %%%%% \item \ttt{select} \newline Subevent function \ttt{select if {\em } [{\em } [ , {\em }]]} that selects all particles in \ttt{{\em }} that satisfy the condition \ttt{{\em }}. The second particle list \ttt{{\em }} is for conditions that depend on binary observables. (cf. also \ttt{collect}, \ttt{combine}, \ttt{extract}, \ttt{sort}, \ttt{+}) %%%%% \item \ttt{select\_b\_jet} \newline Subevent function \ttt{select if {\em } [{\em } [ , {\em }]]} that selects all particles in \ttt{{\em }} that are $b$ jets and satisfy the condition \ttt{{\em }}. The second particle list \ttt{{\em }} is for conditions that depend on binary observables. (cf. also \ttt{cluster}, \ttt{collect}, \ttt{combine}, \ttt{extract}, \ttt{select}, \ttt{sort}, \ttt{+}) %%%%% \item \ttt{select\_c\_jet} \newline Subevent function \ttt{select if {\em } [{\em } [ , {\em }]]} that selects all particles in \ttt{{\em }} that are $c$ jets (but {\em not} $b$ jets) and satisfy the condition \ttt{{\em }}. The second particle list \ttt{{\em }} is for conditions that depend on binary observables. (cf. also \ttt{cluster}, \ttt{collect}, \ttt{combine}, \ttt{extract}, \ttt{select}, \ttt{sort}, \ttt{+}) %%%%% \item \ttt{select\_light\_jet} \newline Subevent function \ttt{select if {\em } [{\em } [ , {\em }]]} that selects all particles in \ttt{{\em }} that are light(-flavor) jets and satisfy the condition \ttt{{\em }}. The second particle list \ttt{{\em }} is for conditions that depend on binary observables. (cf. also \ttt{cluster}, \ttt{collect}, \ttt{combine}, \ttt{extract}, \ttt{select}, \ttt{sort}, \ttt{+}) %%%%% \item \ttt{select\_non\_b\_jet} \newline Subevent function \ttt{select if {\em } [{\em } [ , {\em }]]} that selects all particles in \ttt{{\em }} that are {\em not} $b$ jets ($c$ and light jets) and satisfy the condition \ttt{{\em }}. The second particle list \ttt{{\em }} is for conditions that depend on binary observables. (cf. also \ttt{cluster}, \ttt{collect}, \ttt{combine}, \ttt{extract}, \ttt{select}, \ttt{sort}, \ttt{+}) %%%%% \item \ttt{selection} \newline Command that allows to select particular final states in an analysis selection, \ttt{selection = {\em }}. The term \ttt{log\_expr} can be any kind of logical expression. The syntax matches exactly the one of the ($\to$) \ttt{cuts} command. E.g. \ttt{selection = any PDG == 13} is an electron selection in a lepton sample. %%%%% \item \ttt{sgn} \newline Numerical function for integer and real numbers that gives the sign of its argument: \ttt{sgn ({\em })} yields $+1$ if \ttt{{\em }} is positive or zero, and $-1$ otherwise. (cf. also \ttt{abs}, \ttt{conjg}, \ttt{mod}, \ttt{modulo}) %%%%% \item \ttt{short} \newline Specifier for the \ttt{sample\_format} command to demand the generation of the short variant of HEPEVT ASCII event files. (cf. also \ttt{\$sample}, \ttt{sample\_format}) %%%%% \item \ttt{show} \newline This is a unary function that is operating on specific constructors in order to print them out in the \whizard\ screen output as well as the log file \ttt{whizard.log}. Examples are \ttt{show({\em })} to issue a specific parameter from a model or a constant defined in a \sindarin\ input file, \ttt{show(integral({\em }))}, \ttt{show(library)}, \ttt{show(results)}, or \ttt{show({\em })} for any arbitrary variable. Further possibilities are \ttt{show(real)}, \ttt{show(string)}, \ttt{show(logical)} etc. to allow to show all defined real, string, logical etc. variables, respectively. (cf. also \ttt{library}, \ttt{results}) %%%%% \item \ttt{simulate} \newline This command invokes the generation of events for the process \ttt{proc} by means of \ttt{simulate ({\em })}. Optional arguments: \ttt{\$sample}, \ttt{sample\_format}, \ttt{checkpoint} (cf. also \ttt{integrate}, \ttt{luminosity}, \ttt{n\_events}, \ttt{\$sample}, \ttt{sample\_format}, \ttt{checkpoint}, \ttt{?unweighted}, \ttt{safety\_factor}, \ttt{?negative\_weights}, \ttt{sample\_max\_tries}, \ttt{sample\_split\_n\_evt}, \ttt{sample\_split\_n\_kbytes}) %%%%% \item \ttt{sin} \newline Numerical function \ttt{sin ({\em })} that calculates the sine trigonometric function of real and complex numerical numbers or variables. (cf. also \ttt{cos}, \ttt{tan}, \ttt{asin}, \ttt{acos}, \ttt{atan}) %%%%% \item \ttt{sinh} \newline Numerical function \ttt{sinh ({\em })} that calculates the hyperbolic sine function of real and complex numerical numbers or variables. Note that its inverse function is part of the \ttt{Fortran2008} status and hence not realized. (cf. also \ttt{cosh}, \ttt{tanh}) %%%%% \item \ttt{sort} \newline Subevent function that allows to sort a particle list/subevent either by increasing PDG code: \ttt{sort [{\em }]} (particles first, then antiparticles). Alternatively, it can sort according to a unary or binary particle observable (in that case there is a second particle list, where the first particle is taken as a reference): \ttt{sort by {\em } [{\em } [, {\em }]]}. (cf. also \ttt{extract}, \ttt{combine}, \ttt{collect}, \ttt{join}, \ttt{by}, \ttt{+}) %%%%% \item \ttt{sprintf} \newline Command that allows to print data into a string variable: \ttt{sprintf "{\em }"}. There exist format specifiers, very similar to the \ttt{C} command \ttt{sprintf}, e.g. \ttt{sprintf "\%i" (123)}. (cf. \ttt{printf}, \ttt{\%d}, \ttt{\%i}, \ttt{\%e}, \ttt{\%f}, \ttt{\%g}, \ttt{\%E}, \ttt{\%F}, \ttt{\%G}, \ttt{\%s}) %%%%% \item \ttt{sqrt} \newline Numerical function \ttt{sqrt ({\em })} that calculates the square root of real and complex numerical numbers or variables. (cf. also \ttt{exp}, \ttt{log}, \ttt{log10}) %%%%% \item \ttt{sqrts\_hat} \newline Real variable that accesses the partonic energy of a hard-scattering process. It can be used in cuts or in an analysis, e.g. \ttt{cuts = sqrts\_hat > {\em } [ {\em } ]}. The physical unit can be one of the following \ttt{eV}, \ttt{keV}, \ttt{MeV}, \ttt{GeV}, and \ttt{TeV}. (cf. also \ttt{sqrts}, \ttt{cuts}, \ttt{record}) %%%%% \item \ttt{stable} \newline This constructor allows particles in the final states of processes in decay cascade set-up to be set as stable, and not letting them decay. The syntax is \ttt{stable {\em }} (cf. also \ttt{unstable}) %%%%% \item \ttt{stdhep} \newline Specifier for the \ttt{sample\_format} command to demand the generation of binary StdHEP event files based on the HEPEVT common block. (cf. also \ttt{\$sample}, \ttt{sample\_format}) %%%%% \item \ttt{stdhep\_up} \newline Specifier for the \ttt{sample\_format} command to demand the generation of binary StdHEP event files based on the HEPRUP/HEPEUP common blocks. (cf. also \ttt{\$sample}, \ttt{sample\_format}) %%%%% \item \ttt{tan} \newline Numerical function \ttt{tan ({\em })} that calculates the tangent trigonometric function of real and complex numerical numbers or variables. (cf. also \ttt{sin}, \ttt{cos}, \ttt{asin}, \ttt{acos}, \ttt{atan}) %%%%% \item \ttt{tanh} \newline Numerical function \ttt{tanh ({\em })} that calculates the hyperbolic tangent function of real and complex numerical numbers or variables. Note that its inverse function is part of the \ttt{Fortran2008} status and hence not realized. (cf. also \ttt{cosh}, \ttt{sinh}) %%%%% \item \ttt{TeV} \newline Physical unit, for energies in $10^{12}$ electron volt. (cf. also \ttt{eV}, \ttt{keV}, \ttt{MeV}, \ttt{meV}, \ttt{GeV}) %%%% \item \ttt{then} \newline Mandatory phrase in a conditional clause: \ttt{if {\em } then {\em } \ldots endif}. (cf. also \ttt{if}, \ttt{else}, \ttt{elsif}, \ttt{endif}). %%%%% \item \ttt{Theta} \newline Unary and also binary observable specifier, that as a unary observable gives the angle between a particle's momentum and the beam axis ($+z$ direction). As a binary observable, it gives the angle enclosed between the momenta of the two particles: \ttt{eval Theta [e1]}, \ttt{all Theta > 30 degrees [jet, jet]}. (cf. also \ttt{eval}, \ttt{cuts}, \ttt{selection}, \ttt{Phi}, \ttt{Theta\_star}) %%%%% \item \ttt{Theta\_star} \newline Binary observable specifier, that gives the polar angle enclosed between the momenta of the two particles in the rest frame of the mother particle (momentum sum of the two particle): \ttt{eval Theta\_star [jet, jet]}. (cf. also \ttt{eval}, \ttt{cuts}, \ttt{selection}, \ttt{Theta}) %%%%% \item \ttt{true} \newline Constructor stating that a logical expression or variable is true, e.g. \ttt{?{\em } = true}. (cf. also \ttt{false}). %%%%% \item \ttt{unpolarized} \newline Constructor to force \whizard\ to discard polarization of the corresponding particles in the generated events: \ttt{unpolarized {\em } [, {\em } , ...]}. (cf. also \ttt{polarized}, \ttt{simulate}, \ttt{?polarized\_events}) %%%%% \item \ttt{unstable} \newline This constructor allows to let final state particles of the hard interaction undergo a subsequent (cascade) decay (in the on-shell approximation). For this the user has to define the list of desired \begin{figure} \begin{Verbatim}[frame=single] process zee = Z => e1, E1 process zuu = Z => u, U process zz = e1, E1 => Z, Z compile integrate (zee) { iterations = 1:100 } integrate (zuu) { iterations = 1:100 } sqrts = 500 GeV integrate (zz) { iterations = 3:5000, 2:5000 } unstable Z (zee, zuu) \end{Verbatim} \caption{\label{fig:ex_unstable} \sindarin\ input file for unstable particles and inclusive decays.} \end{figure} decay channels as \ttt{unstable {\em } ({\em }, {\em }, ....)}, where \ttt{mother} is the mother particle, and the argument is a list of decay channels. Note that -- unless the \ttt{?auto\_decays = true} flag has been set -- these decay channels have to be provided by the user as in the example in Fig. \ref{fig:ex_unstable}. First, the $Z$ decays to electrons and up quarks are generated, then $ZZ$ production at a 500 GeV ILC is called, and then both $Z$s are decayed according to the probability distribution of the two generated decay matrix elements. This obviously allows also for inclusive decays. (cf. also \ttt{stable}, \ttt{?auto\_decays}) %%%%% \item \ttt{weight} \newline This is a command, \ttt{weight = {\em }}, that allows to specify a weight for a process or list of processes. \ttt{{\em }} can be any expression that leads to a scalar result, e.g. \ttt{weight = 0.2}, \ttt{weight = eval Pt [jet]}. (cf. also \ttt{rescan}, \ttt{alt\_setup}, \ttt{reweight}) %%%%% \item \ttt{write\_analysis} \newline The \ttt{write\_analysis} statement tells \whizard\ to write the analysis setup by the user for the \sindarin\ input file under consideration. If no \ttt{\$out\_file} is provided, the histogram tables/plot data etc. are written to the default file \ttt{whizard\_analysis.dat}. Note that the related command \ttt{compile\_analysis} does the same as \ttt{write\_analysis} but in addition invokes the \whizard\ \LaTeX routines for producing postscript or PDF output of the data. (cf. also \ttt{\$out\_file}, \ttt{compile\_analysis}) %%%%% \item \ttt{write\_slha} \newline Demands \whizard\ to write out a file in the SUSY Les Houches accord (SLHA) format. (cf. also \ttt{read\_slha}, \ttt{?slha\_read\_decays}, \ttt{?slha\_read\_input}, \ttt{?slha\_read\_spectrum}) %%%%% \end{itemize} \section{Variables} \subsection{Rebuild Variables} \begin{itemize} \item \ttt{?rebuild\_events} \qquad (default: \ttt{false}) \newline This logical variable, if set \ttt{true} triggers \whizard\ to newly create an event sample, even if nothing seems to have changed, including the MD5 checksum. This can be used when manually manipulating some settings. (cf also \ttt{?rebuild\_grids}, \ttt{?rebuild\_library}, \ttt{?rebuild\_phase\_space}) %%%%% \item \ttt{?rebuild\_grids} \qquad (default: \ttt{false}) \newline The logical variable \ttt{?rebuild\_grids} forces \whizard\ to newly create the VAMP grids when using VAMP as an integration method, even if they are already present. (cf. also \ttt{?rebuild\_events}, \ttt{?rebuild\_library}, \ttt{?rebuild\_phase\_space}) %%%%% \item \ttt{?rebuild\_library} \qquad (default: \ttt{false}) \newline The logical variable \ttt{?rebuild\_library = true/false} specifies whether the library(-ies) for the matrix element code for processes is re-generated (incl. possible Makefiles etc.) by the corresponding ME method (e.g. if the process has been changed, but not its name). This can also be set as a command-line option \ttt{whizard --rebuild}. The default is \ttt{false}, i.e. code is never re-generated if it is present and the MD5 checksum is valid. (cf. also \ttt{?recompile\_library}, \ttt{?rebuild\_grids}, \ttt{?rebuild\_phase\_space}) %%%%% \item \ttt{?rebuild\_phase\_space} \qquad (default: \ttt{false}) \newline This logical variable, if set \ttt{true}, triggers recreation of the phase space file by \whizard\. (cf. also \ttt{?rebuild\_events}, \ttt{?rebuild\_grids}, \ttt{?rebuild\_library}) %%%%% \item \ttt{?recompile\_library} \qquad (default: \ttt{false}) \newline The logical variable \ttt{?recompile\_library = true/false} specifies whether the library(-ies) for the matrix element code for processes is re-compiled (e.g. if the process code has been manually modified by the user). This can also be set as a command-line option \ttt{whizard --recompile}. The default is \ttt{false}, i.e. code is never re-compiled if its corresponding object file is present. (cf. also \ttt{?rebuild\_library}) %%%%% \end{itemize} \subsection{Standard Variables} \begin{itemize} \input{variables} \end{itemize} %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \clearpage \section*{Acknowledgements} We would like to thank E.~Boos, R.~Chierici, K.~Desch, M.~Kobel, F.~Krauss, P.M.~Manakos, N.~Meyer, K.~M\"onig, H.~Reuter, T.~Robens, S.~Rosati, J.~Schumacher, M.~Schumacher, and C.~Schwinn who contributed to \whizard\ by their suggestions, bits of codes and valuable remarks and/or used several versions of the program for real-life applications and thus helped a lot in debugging and improving the code. Special thanks go to A.~Vaught and J.~Weill for their continuos efforts on improving the g95 and gfortran compilers, respectively. %\end{fmffile} %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%% References %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %\baselineskip15pt \begin{thebibliography}{19} \bibitem{PYTHIA} T.~Sj\"ostrand, Comput.\ Phys.\ Commun.\ \textbf{82} (1994) 74. \bibitem{comphep} A.~Pukhov, \emph{et al.}, Preprint INP MSU 98-41/542, \ttt{hep-ph/9908288}. \bibitem{madgraph} T.~Stelzer and W.F.~Long, Comput.\ Phys.\ Commun.\ \textbf{81} (1994) 357. \bibitem{omega} T.~Ohl, \emph{Proceedings of the Seventh International Workshop on Advanced Computing and Analysis Technics in Physics Research}, ACAT 2000, Fermilab, October 2000, IKDA-2000-30, \ttt{hep-ph/0011243}; M.~Moretti, Th.~Ohl, and J.~Reuter, LC-TOOL-2001-040 \bibitem{VAMP} T.~Ohl, {\em Vegas revisited: Adaptive Monte Carlo integration beyond factorization}, Comput.\ Phys.\ Commun.\ {\bf 120}, 13 (1999) [arXiv:hep-ph/9806432]. %%CITATION = CPHCB,120,13;%% \bibitem{CIRCE} T.~Ohl, {\em CIRCE version 1.0: Beam spectra for simulating linear collider physics}, Comput.\ Phys.\ Commun.\ {\bf 101}, 269 (1997) [arXiv:hep-ph/9607454]. %%CITATION = CPHCB,101,269;%% %\cite{Gribov:1972rt} \bibitem{Gribov:1972rt} V.~N.~Gribov and L.~N.~Lipatov, {\em e+ e- pair annihilation and deep inelastic e p scattering in perturbation theory}, Sov.\ J.\ Nucl.\ Phys.\ {\bf 15}, 675 (1972) [Yad.\ Fiz.\ {\bf 15}, 1218 (1972)]. %%CITATION = SJNCA,15,675;%% %\cite{Kuraev:1985hb} \bibitem{Kuraev:1985hb} E.~A.~Kuraev and V.~S.~Fadin, {\em On Radiative Corrections to e+ e- Single Photon Annihilation at High-Energy}, Sov.\ J.\ Nucl.\ Phys.\ {\bf 41}, 466 (1985) [Yad.\ Fiz.\ {\bf 41}, 733 (1985)]. %%CITATION = SJNCA,41,466;%% %\cite{Skrzypek:1990qs} \bibitem{Skrzypek:1990qs} M.~Skrzypek and S.~Jadach, {\em Exact and approximate solutions for the electron nonsinglet structure function in QED}, Z.\ Phys.\ C {\bf 49}, 577 (1991). %%CITATION = ZEPYA,C49,577;%% %\cite{Schulte:1998au} \bibitem{Schulte:1998au} D.~Schulte, {\em Beam-beam simulations with Guinea-Pig}, eConf C {\bf 980914}, 127 (1998). %%CITATION = ECONF,C980914,127;%% %\cite{Schulte:1999tx} \bibitem{Schulte:1999tx} D.~Schulte, {\em Beam-beam simulations with GUINEA-PIG}, CERN-PS-99-014-LP. %%CITATION = CERN-PS-99-014-LP;%% %\cite{Schulte:2007zz} \bibitem{Schulte:2007zz} D.~Schulte, M.~Alabau, P.~Bambade, O.~Dadoun, G.~Le Meur, C.~Rimbault and F.~Touze, {\em GUINEA PIG++ : An Upgraded Version of the Linear Collider Beam Beam Interaction Simulation Code GUINEA PIG}, Conf.\ Proc.\ C {\bf 070625}, 2728 (2007). %%CITATION = CONFP,C070625,2728;%% %\cite{Behnke:2013xla} \bibitem{Behnke:2013xla} T.~Behnke, J.~E.~Brau, B.~Foster, J.~Fuster, M.~Harrison, J.~M.~Paterson, M.~Peskin and M.~Stanitzki {\it et al.}, {\em The International Linear Collider Technical Design Report - Volume 1: Executive Summary}, arXiv:1306.6327 [physics.acc-ph]. %%CITATION = ARXIV:1306.6327;%% %\cite{Baer:2013cma} \bibitem{Baer:2013cma} H.~Baer, T.~Barklow, K.~Fujii, Y.~Gao, A.~Hoang, S.~Kanemura, J.~List and H.~E.~Logan {\it et al.}, {\em The International Linear Collider Technical Design Report - Volume 2: Physics}, arXiv:1306.6352 [hep-ph]. %%CITATION = ARXIV:1306.6352;%% %\cite{Adolphsen:2013jya} \bibitem{Adolphsen:2013jya} C.~Adolphsen, M.~Barone, B.~Barish, K.~Buesser, P.~Burrows, J.~Carwardine, J.~Clark and H\'{e}l\`{e}n.~M.~Durand {\it et al.}, {\em The International Linear Collider Technical Design Report - Volume 3.I: Accelerator \& in the Technical Design Phase}, arXiv:1306.6353 [physics.acc-ph]. %%CITATION = ARXIV:1306.6353;%% %\cite{Adolphsen:2013kya} \bibitem{Adolphsen:2013kya} C.~Adolphsen, M.~Barone, B.~Barish, K.~Buesser, P.~Burrows, J.~Carwardine, J.~Clark and H\'{e}l\`{e}n.~M.~Durand {\it et al.}, {\em The International Linear Collider Technical Design Report - Volume 3.II: Accelerator Baseline Design}, arXiv:1306.6328 [physics.acc-ph]. %%CITATION = ARXIV:1306.6328;%% %\cite{Behnke:2013lya} \bibitem{Behnke:2013lya} T.~Behnke, J.~E.~Brau, P.~N.~Burrows, J.~Fuster, M.~Peskin, M.~Stanitzki, Y.~Sugimoto and S.~Yamada {\it et al.}, %``The International Linear Collider Technical Design Report - Volume 4: Detectors,'' arXiv:1306.6329 [physics.ins-det]. %%CITATION = ARXIV:1306.6329;%% %\cite{Aicheler:2012bya} \bibitem{Aicheler:2012bya} M.~Aicheler, P.~Burrows, M.~Draper, T.~Garvey, P.~Lebrun, K.~Peach and N.~Phinney {\it et al.}, {\em A Multi-TeV Linear Collider Based on CLIC Technology : CLIC Conceptual Design Report}, CERN-2012-007. %%CITATION = CERN-2012-007;%% %\cite{Lebrun:2012hj} \bibitem{Lebrun:2012hj} P.~Lebrun, L.~Linssen, A.~Lucaci-Timoce, D.~Schulte, F.~Simon, S.~Stapnes, N.~Toge and H.~Weerts {\it et al.}, {\em The CLIC Programme: Towards a Staged e+e- Linear Collider Exploring the Terascale : CLIC Conceptual Design Report}, arXiv:1209.2543 [physics.ins-det]. %%CITATION = ARXIV:1209.2543;%% %\cite{Linssen:2012hp} \bibitem{Linssen:2012hp} L.~Linssen, A.~Miyamoto, M.~Stanitzki and H.~Weerts, {\em Physics and Detectors at CLIC: CLIC Conceptual Design Report}, arXiv:1202.5940 [physics.ins-det]. %%CITATION = ARXIV:1202.5940;%% %\cite{vonWeizsacker:1934sx} \bibitem{vonWeizsacker:1934sx} C.~F.~von Weizs\"acker, {\em Radiation emitted in collisions of very fast electrons}, Z.\ Phys.\ {\bf 88}, 612 (1934). %%CITATION = ZEPYA,88,612;%% %\cite{Williams:1934ad} \bibitem{Williams:1934ad} E.~J.~Williams, {\em Nature of the high-energy particles of penetrating radiation and status of ionization and radiation formulae}, Phys.\ Rev.\ {\bf 45}, 729 (1934). %%CITATION = PHRVA,45,729;%% %\cite{Budnev:1974de} \bibitem{Budnev:1974de} V.~M.~Budnev, I.~F.~Ginzburg, G.~V.~Meledin and V.~G.~Serbo, {\em The Two photon particle production mechanism. Physical problems. Applications. Equivalent photon approximation}, Phys.\ Rept.\ {\bf 15} (1974) 181. %%CITATION = PRPLC,15,181;%% %\cite{Ginzburg:1981vm} \bibitem{Ginzburg:1981vm} I.~F.~Ginzburg, G.~L.~Kotkin, V.~G.~Serbo and V.~I.~Telnov, {\em Colliding gamma e and gamma gamma Beams Based on the Single Pass Accelerators (of Vlepp Type)}, Nucl.\ Instrum.\ Meth.\ {\bf 205}, 47 (1983). %%CITATION = NUIMA,205,47;%% %\cite{Telnov:1989sd} \bibitem{Telnov:1989sd} V.~I.~Telnov, {\em Problems of Obtaining $\gamma \gamma$ and $\gamma \epsilon$ Colliding Beams at Linear Colliders}, Nucl.\ Instrum.\ Meth.\ A {\bf 294}, 72 (1990). %%CITATION = NUIMA,A294,72;%% %\cite{Telnov:1995hc} \bibitem{Telnov:1995hc} V.~I.~Telnov, {\em Principles of photon colliders}, Nucl.\ Instrum.\ Meth.\ A {\bf 355}, 3 (1995). %%CITATION = NUIMA,A355,3;%% %\cite{AguilarSaavedra:2001rg} \bibitem{AguilarSaavedra:2001rg} J.~A.~Aguilar-Saavedra {\it et al.} [ECFA/DESY LC Physics Working Group Collaboration], {\em TESLA: The Superconducting electron positron linear collider with an integrated x-ray laser laboratory. Technical design report. Part 3. Physics at an e+ e- linear collider}, hep-ph/0106315. %%CITATION = HEP-PH/0106315;%% %\cite{Richard:2001qm} \bibitem{Richard:2001qm} F.~Richard, J.~R.~Schneider, D.~Trines and A.~Wagner, {\em TESLA, The Superconducting Electron Positron Linear Collider with an Integrated X-ray Laser Laboratory, Technical Design Report Part 1 : Executive Summary}, hep-ph/0106314. %%CITATION = HEP-PH/0106314;%% %\cite{Sudakov:1954sw} \bibitem{Sudakov:1954sw} V.~V.~Sudakov, %``Vertex parts at very high-energies in quantum electrodynamics,'' Sov.\ Phys.\ JETP {\bf 3}, 65 (1956) [Zh.\ Eksp.\ Teor.\ Fiz.\ {\bf 30}, 87 (1956)]. %%CITATION = SPHJA,3,65;%% \cite{Sjostrand:1985xi} \bibitem{Sjostrand:1985xi} T.~Sjostrand, %``A Model for Initial State Parton Showers,'' Phys.\ Lett.\ {\bf 157B}, 321 (1985). doi:10.1016/0370-2693(85)90674-4 %%CITATION = doi:10.1016/0370-2693(85)90674-4;%% %\cite{Sjostrand:2006za} \bibitem{Sjostrand:2006za} T.~Sjostrand, S.~Mrenna and P.~Z.~Skands, %``PYTHIA 6.4 Physics and Manual,'' JHEP {\bf 0605}, 026 (2006) doi:10.1088/1126-6708/2006/05/026 [hep-ph/0603175]. %%CITATION = doi:10.1088/1126-6708/2006/05/026;%% %\cite{Ohl:1998jn} \bibitem{Ohl:1998jn} T.~Ohl, {\em Vegas revisited: Adaptive Monte Carlo integration beyond factorization}, Comput.\ Phys.\ Commun.\ {\bf 120}, 13 (1999) [hep-ph/9806432]. %%CITATION = HEP-PH/9806432;%% %\cite{Lepage:1980dq} \bibitem{Lepage:1980dq} G.~P.~Lepage, %``Vegas: An Adaptive Multidimensional Integration Program,'' CLNS-80/447. %%CITATION = CLNS-80/447;%% \bibitem{HDECAY} A.~Djouadi, J.~Kalinowski, M.~Spira, Comput.\ Phys.\ Commun.\ \textbf{108} (1998) 56-74. %\cite{Beyer:2006hx} \bibitem{Beyer:2006hx} M.~Beyer, W.~Kilian, P.~Krstono\v{s}ic, K.~M\"onig, J.~Reuter, E.~Schmidt and H.~Schr\"oder, {\em Determination of New Electroweak Parameters at the ILC - Sensitivity to New Physics}, Eur.\ Phys.\ J.\ C {\bf 48}, 353 (2006) [hep-ph/0604048]. %%CITATION = HEP-PH/0604048;%% %\cite{Alboteanu:2008my} \bibitem{Alboteanu:2008my} A.~Alboteanu, W.~Kilian and J.~Reuter, {\em Resonances and Unitarity in Weak Boson Scattering at the LHC}, JHEP {\bf 0811}, 010 (2008) [arXiv:0806.4145 [hep-ph]]. %%CITATION = ARXIV:0806.4145;%% %\cite{Binoth:2010xt} \bibitem{Binoth:2010xt} T.~Binoth {\it et al.}, %``A Proposal for a standard interface between Monte Carlo tools and one-loop programs,'' Comput.\ Phys.\ Commun.\ {\bf 181}, 1612 (2010) doi:10.1016/j.cpc.2010.05.016 [arXiv:1001.1307 [hep-ph]]. %%CITATION = doi:10.1016/j.cpc.2010.05.016;%% %\cite{Alioli:2013nda} \bibitem{Alioli:2013nda} S.~Alioli {\it et al.}, %``Update of the Binoth Les Houches Accord for a standard interface %between Monte Carlo tools and one-loop programs,'' Comput.\ Phys.\ Commun.\ {\bf 185}, 560 (2014) doi:10.1016/j.cpc.2013.10.020 [arXiv:1308.3462 [hep-ph]]. %%CITATION = doi:10.1016/j.cpc.2013.10.020;%% %\cite{Speckner:2010zi} \bibitem{Speckner:2010zi} C.~Speckner, {\em LHC Phenomenology of the Three-Site Higgsless Model}, PhD thesis, arXiv:1011.1851 [hep-ph]. %%CITATION = ARXIV:1011.1851;%% %\cite{Chivukula:2006cg} \bibitem{Chivukula:2006cg} R.~S.~Chivukula, B.~Coleppa, S.~Di Chiara, E.~H.~Simmons, H.~-J.~He, M.~Kurachi and M.~Tanabashi, {\em A Three Site Higgsless Model}, Phys.\ Rev.\ D {\bf 74}, 075011 (2006) [hep-ph/0607124]. %%CITATION = HEP-PH/0607124;%% %\cite{Chivukula:2005xm} \bibitem{Chivukula:2005xm} R.~S.~Chivukula, E.~H.~Simmons, H.~-J.~He, M.~Kurachi and M.~Tanabashi, {\em Ideal fermion delocalization in Higgsless models}, Phys.\ Rev.\ D {\bf 72}, 015008 (2005) [hep-ph/0504114]. %%CITATION = HEP-PH/0504114;%% %\cite{Ohl:2008ri} \bibitem{Ohl:2008ri} T.~Ohl and C.~Speckner, {\em Production of Almost Fermiophobic Gauge Bosons in the Minimal Higgsless Model at the LHC}, Phys.\ Rev.\ D {\bf 78}, 095008 (2008) [arXiv:0809.0023 [hep-ph]]. %%CITATION = ARXIV:0809.0023;%% %\cite{Ohl:2002jp} \bibitem{Ohl:2002jp} T.~Ohl and J.~Reuter, {\em Clockwork SUSY: Supersymmetric Ward and Slavnov-Taylor identities at work in Green's functions and scattering amplitudes}, Eur.\ Phys.\ J.\ C {\bf 30}, 525 (2003) [hep-th/0212224]. %%CITATION = HEP-TH/0212224;%% %\cite{Reuter:2009ex} \bibitem{Reuter:2009ex} J.~Reuter and F.~Braam, {\em The NMSSM implementation in WHIZARD}, AIP Conf.\ Proc.\ {\bf 1200}, 470 (2010) [arXiv:0909.3059 [hep-ph]]. %%CITATION = ARXIV:0909.3059;%% %\cite{Kalinowski:2008fk} \bibitem{Kalinowski:2008fk} J.~Kalinowski, W.~Kilian, J.~Reuter, T.~Robens and K.~Rolbiecki, {\em Pinning down the Invisible Sneutrino}, JHEP {\bf 0810}, 090 (2008) [arXiv:0809.3997 [hep-ph]]. %%CITATION = ARXIV:0809.3997;%% %\cite{Robens:2008sa} \bibitem{Robens:2008sa} T.~Robens, J.~Kalinowski, K.~Rolbiecki, W.~Kilian and J.~Reuter, {\em (N)LO Simulation of Chargino Production and Decay}, Acta Phys.\ Polon.\ B {\bf 39}, 1705 (2008) [arXiv:0803.4161 [hep-ph]]. %%CITATION = ARXIV:0803.4161;%% %\cite{Kilian:2004pp} \bibitem{Kilian:2004pp} W.~Kilian, D.~Rainwater and J.~Reuter, {\em Pseudo-axions in little Higgs models}, Phys.\ Rev.\ D {\bf 71}, 015008 (2005) [hep-ph/0411213]. %%CITATION = HEP-PH/0411213;%% %\cite{Kilian:2006eh} \bibitem{Kilian:2006eh} W.~Kilian, D.~Rainwater and J.~Reuter, {\em Distinguishing little-Higgs product and simple group models at the LHC and ILC}, Phys.\ Rev.\ D {\bf 74}, 095003 (2006) [Erratum-ibid.\ D {\bf 74}, 099905 (2006)] [hep-ph/0609119]. %%CITATION = HEP-PH/0609119;%% %\cite{Ohl:2004tn} \bibitem{Ohl:2004tn} T.~Ohl and J.~Reuter, {\em Testing the noncommutative standard model at a future photon collider}, Phys.\ Rev.\ D {\bf 70}, 076007 (2004) [hep-ph/0406098]. %%CITATION = HEP-PH/0406098;%% %\cite{Ohl:2010zf} \bibitem{Ohl:2010zf} T.~Ohl and C.~Speckner, {\em The Noncommutative Standard Model and Polarization in Charged Gauge Boson Production at the LHC}, Phys.\ Rev.\ D {\bf 82}, 116011 (2010) [arXiv:1008.4710 [hep-ph]]. %%CITATION = ARXIV:1008.4710;%% \bibitem{LesHouches} E.~Boos {\it et al.}, {\em Generic user process interface for event generators}, arXiv:hep-ph/0109068. %%CITATION = HEP-PH/0109068;%% \bibitem{Skands:2003cj} P.~Z.~Skands {\it et al.}, {\em SUSY Les Houches Accord: Interfacing SUSY Spectrum Calculators, Decay Packages, and Event Generators}, JHEP {\bf 0407}, 036 (2004) [arXiv:hep-ph/0311123]. %%CITATION = JHEPA,0407,036;%% %\cite{AguilarSaavedra:2005pw} \bibitem{AguilarSaavedra:2005pw} J.~A.~Aguilar-Saavedra, A.~Ali, B.~C.~Allanach, R.~L.~Arnowitt, H.~A.~Baer, J.~A.~Bagger, C.~Balazs and V.~D.~Barger {\it et al.}, {\em Supersymmetry parameter analysis: SPA convention and project}, Eur.\ Phys.\ J.\ C {\bf 46}, 43 (2006) [hep-ph/0511344]. %%CITATION = HEP-PH/0511344;%% %\cite{Allanach:2008qq} \bibitem{Allanach:2008qq} B.~C.~Allanach, C.~Balazs, G.~Belanger, M.~Bernhardt, F.~Boudjema, D.~Choudhury, K.~Desch and U.~Ellwanger {\it et al.}, %``SUSY Les Houches Accord 2,'' Comput.\ Phys.\ Commun.\ {\bf 180}, 8 (2009) [arXiv:0801.0045 [hep-ph]]. %%CITATION = ARXIV:0801.0045;%% \bibitem{LHEF} J.~Alwall {\it et al.}, {\em A standard format for Les Houches event files}, Comput.\ Phys.\ Commun.\ {\bf 176}, 300 (2007) [arXiv:hep-ph/0609017]. %%CITATION = CPHCB,176,300;%% \bibitem{Hagiwara:2005wg} K.~Hagiwara {\it et al.}, {\em Supersymmetry simulations with off-shell effects for LHC and ILC}, Phys.\ Rev.\ D {\bf 73}, 055005 (2006) [arXiv:hep-ph/0512260]. %%CITATION = PHRVA,D73,055005;%% \bibitem{Allanach:2002nj} B.~C.~Allanach {\it et al.}, {\em The Snowmass points and slopes: Benchmarks for SUSY searches}, in {\it Proc. of the APS/DPF/DPB Summer Study on the Future of Particle Physics (Snowmass 2001) } ed. N.~Graf, Eur.\ Phys.\ J.\ C {\bf 25} (2002) 113 [eConf {\bf C010630} (2001) P125] [arXiv:hep-ph/0202233]. %%CITATION = HEP-PH 0202233;%% \bibitem{PeskinSchroeder} M.E. Peskin, D.V.Schroeder, {\em An Introduction to Quantum Field Theory}, Addison-Wesley Publishing Co., 1995. \bibitem{stdhep} L.~Garren, {\em StdHep, Monte Carlo Standardization at FNAL}, Fermilab CS-doc-903, \url{http://cd-docdb.fnal.gov/cgi-bin/ShowDocument?docid=903} %\cite{Frixione:1998jh} \bibitem{Frixione:1998jh} S.~Frixione, %``Isolated photons in perturbative QCD,'' Phys.\ Lett.\ B {\bf 429}, 369 (1998) doi:10.1016/S0370-2693(98)00454-7 [hep-ph/9801442]. %%CITATION = doi:10.1016/S0370-2693(98)00454-7;%% \bibitem{LHAPDF} W.~Giele {\it et al.}, {\em The QCD / SM working group: Summary report}, arXiv:hep-ph/0204316; %%CITATION = HEP-PH/0204316;%% M.~R.~Whalley, D.~Bourilkov and R.~C.~Group, {\em The Les Houches Accord PDFs (LHAPDF) and Lhaglue}, arXiv:hep-ph/0508110; %%CITATION = HEP-PH/0508110;%% D.~Bourilkov, R.~C.~Group and M.~R.~Whalley, {\em LHAPDF: PDF use from the Tevatron to the LHC}, arXiv:hep-ph/0605240. %%CITATION = HEP-PH/0605240;%% \bibitem{HepMC} M.~Dobbs and J.~B.~Hansen, {\em The HepMC C++ Monte Carlo event record for High Energy Physics}, Comput.\ Phys.\ Commun.\ {\bf 134}, 41 (2001). %%CITATION = CPHCB,134,41;%% %\cite{Boos:2004kh} \bibitem{Boos:2004kh} E.~Boos {\it et al.} [CompHEP Collaboration], %``CompHEP 4.4: Automatic computations from Lagrangians to events,'' Nucl.\ Instrum.\ Meth.\ A {\bf 534}, 250 (2004) [hep-ph/0403113]. %%CITATION = HEP-PH/0403113;%% %493 citations counted in INSPIRE as of 12 May 2014 % Parton distributions %\cite{Pumplin:2002vw} \bibitem{Pumplin:2002vw} J.~Pumplin, D.~R.~Stump, J.~Huston {\it et al.}, {\em New generation of parton distributions with uncertainties from global QCD analysis}, JHEP {\bf 0207}, 012 (2002). [hep-ph/0201195]. %\cite{Martin:2004dh} \bibitem{Martin:2004dh} A.~D.~Martin, R.~G.~Roberts, W.~J.~Stirling {\it et al.}, {\em Parton distributions incorporating QED contributions}, Eur.\ Phys.\ J.\ {\bf C39}, 155-161 (2005). [hep-ph/0411040]. %\cite{Martin:2009iq} \bibitem{Martin:2009iq} A.~D.~Martin, W.~J.~Stirling, R.~S.~Thorne {\it et al.}, {\em Parton distributions for the LHC}, Eur.\ Phys.\ J.\ {\bf C63}, 189-285 (2009). [arXiv:0901.0002 [hep-ph]]. %\cite{Lai:2010vv} \bibitem{Lai:2010vv} H.~L.~Lai, M.~Guzzi, J.~Huston, Z.~Li, P.~M.~Nadolsky, J.~Pumplin and C.~P.~Yuan, {\em New parton distributions for collider physics}, Phys.\ Rev.\ D {\bf 82}, 074024 (2010) [arXiv:1007.2241 [hep-ph]]. %%CITATION = PHRVA,D82,074024;%% %\cite{Owens:2012bv} \bibitem{Owens:2012bv} J.~F.~Owens, A.~Accardi and W.~Melnitchouk, {\em Global parton distributions with nuclear and finite-$Q^2$ corrections}, Phys.\ Rev.\ D {\bf 87}, no. 9, 094012 (2013) [arXiv:1212.1702 [hep-ph]]. %%CITATION = ARXIV:1212.1702;%% %\cite{Accardi:2016qay} \bibitem{Accardi:2016qay} A.~Accardi, L.~T.~Brady, W.~Melnitchouk, J.~F.~Owens and N.~Sato, %``Constraints on large-$x$ parton distributions from new weak boson production and deep-inelastic scattering data,'' arXiv:1602.03154 [hep-ph]. %%CITATION = ARXIV:1602.03154;%% %\cite{Harland-Lang:2014zoa} \bibitem{Harland-Lang:2014zoa} L.~A.~Harland-Lang, A.~D.~Martin, P.~Motylinski and R.~S.~Thorne, %``Parton distributions in the LHC era: MMHT 2014 PDFs,'' arXiv:1412.3989 [hep-ph]. %%CITATION = ARXIV:1412.3989;%% %\cite{Dulat:2015mca} \bibitem{Dulat:2015mca} S.~Dulat {\it et al.}, %``The CT14 Global Analysis of Quantum Chromodynamics,'' arXiv:1506.07443 [hep-ph]. %%CITATION = ARXIV:1506.07443;%% %\cite{Salam:2008qg} \bibitem{Salam:2008qg} G.~P.~Salam and J.~Rojo, {\em A Higher Order Perturbative Parton Evolution Toolkit (HOPPET)}, Comput.\ Phys.\ Commun.\ {\bf 180}, 120 (2009) [arXiv:0804.3755 [hep-ph]]. %%CITATION = ARXIV:0804.3755;%% %\cite{Kilian:2011ka} \bibitem{Kilian:2011ka} W.~Kilian, J.~Reuter, S.~Schmidt and D.~Wiesler, {\em An Analytic Initial-State Parton Shower}, JHEP {\bf 1204} (2012) 013 [arXiv:1112.1039 [hep-ph]]. %%CITATION = ARXIV:1112.1039;%% %\cite{Staub:2008uz} \bibitem{Staub:2008uz} F.~Staub, {\em Sarah}, arXiv:0806.0538 [hep-ph]. %%CITATION = ARXIV:0806.0538;%% %\cite{Staub:2009bi} \bibitem{Staub:2009bi} F.~Staub, {\em From Superpotential to Model Files for FeynArts and CalcHep/CompHep}, Comput.\ Phys.\ Commun.\ {\bf 181}, 1077 (2010) [arXiv:0909.2863 [hep-ph]]. %%CITATION = ARXIV:0909.2863;%% %\cite{Staub:2010jh} \bibitem{Staub:2010jh} F.~Staub, {\em Automatic Calculation of supersymmetric Renormalization Group Equations and Self Energies}, Comput.\ Phys.\ Commun.\ {\bf 182}, 808 (2011) [arXiv:1002.0840 [hep-ph]]. %%CITATION = ARXIV:1002.0840;%% %\cite{Staub:2012pb} \bibitem{Staub:2012pb} F.~Staub, {\em SARAH 3.2: Dirac Gauginos, UFO output, and more}, Computer Physics Communications {\bf 184}, pp. 1792 (2013) [Comput.\ Phys.\ Commun.\ {\bf 184}, 1792 (2013)] [arXiv:1207.0906 [hep-ph]]. %%CITATION = ARXIV:1207.0906;%% %\cite{Staub:2013tta} \bibitem{Staub:2013tta} F.~Staub, {\em SARAH 4: A tool for (not only SUSY) model builders}, Comput.\ Phys.\ Commun.\ {\bf 185}, 1773 (2014) [arXiv:1309.7223 [hep-ph]]. %%CITATION = ARXIV:1309.7223;%% \bibitem{mathematica} \Mathematica\ is a registered trademark of Wolfram Research, Inc., Champain, IL, USA. %\cite{Porod:2003um} \bibitem{Porod:2003um} W.~Porod, {\em SPheno, a program for calculating supersymmetric spectra, SUSY particle decays and SUSY particle production at e+ e- colliders}, Comput.\ Phys.\ Commun.\ {\bf 153}, 275 (2003) [hep-ph/0301101]. %%CITATION = HEP-PH/0301101;%% %\cite{Porod:2011nf} \bibitem{Porod:2011nf} W.~Porod and F.~Staub, {\em SPheno 3.1: Extensions including flavour, CP-phases and models beyond the MSSM}, Comput.\ Phys.\ Commun.\ {\bf 183}, 2458 (2012) [arXiv:1104.1573 [hep-ph]]. %%CITATION = ARXIV:1104.1573;%% %\cite{Staub:2011dp} \bibitem{Staub:2011dp} F.~Staub, T.~Ohl, W.~Porod and C.~Speckner, %``A Tool Box for Implementing Supersymmetric Models,'' Comput.\ Phys.\ Commun.\ {\bf 183}, 2165 (2012) [arXiv:1109.5147 [hep-ph]]. %%CITATION = ARXIV:1109.5147;%% %%%%% FeynRules %%%%% %\cite{Christensen:2008py} \bibitem{Christensen:2008py} N.~D.~Christensen and C.~Duhr, {\em FeynRules - Feynman rules made easy}, Comput.\ Phys.\ Commun.\ {\bf 180}, 1614 (2009) [arXiv:0806.4194 [hep-ph]]. %%CITATION = ARXIV:0806.4194;%% %\cite{Christensen:2009jx} \bibitem{Christensen:2009jx} N.~D.~Christensen, P.~de Aquino, C.~Degrande, C.~Duhr, B.~Fuks, M.~Herquet, F.~Maltoni and S.~Schumann, {\em A Comprehensive approach to new physics simulations}, Eur.\ Phys.\ J.\ C {\bf 71}, 1541 (2011) [arXiv:0906.2474 [hep-ph]]. %%CITATION = ARXIV:0906.2474;%% %\cite{Duhr:2011se} \bibitem{Duhr:2011se} C.~Duhr and B.~Fuks, %``A superspace module for the FeynRules package,'' Comput.\ Phys.\ Commun.\ {\bf 182}, 2404 (2011) [arXiv:1102.4191 [hep-ph]]. %%CITATION = ARXIV:1102.4191;%% %\cite{Christensen:2010wz} \bibitem{Christensen:2010wz} N.~D.~Christensen, C.~Duhr, B.~Fuks, J.~Reuter and C.~Speckner, {\em Introducing an interface between WHIZARD and FeynRules}, Eur.\ Phys.\ J.\ C {\bf 72}, 1990 (2012) [arXiv:1010.3251 [hep-ph]]. %%CITATION = ARXIV:1010.3251;%% %\cite{Degrande:2011ua} \bibitem{Degrande:2011ua} C.~Degrande, C.~Duhr, B.~Fuks, D.~Grellscheid, O.~Mattelaer and T.~Reiter, %``UFO - The Universal FeynRules Output,'' Comput.\ Phys.\ Commun.\ {\bf 183}, 1201 (2012) doi:10.1016/j.cpc.2012.01.022 [arXiv:1108.2040 [hep-ph]]. %%CITATION = doi:10.1016/j.cpc.2012.01.022;%% %\cite{Han:1998sg} \bibitem{Han:1998sg} T.~Han, J.~D.~Lykken and R.~-J.~Zhang, {\em On Kaluza-Klein states from large extra dimensions}, Phys.\ Rev.\ D {\bf 59}, 105006 (1999) [hep-ph/9811350]. %%CITATION = HEP-PH/9811350;%% %\cite{Fuks:2012im} \bibitem{Fuks:2012im} B.~Fuks, {\em Beyond the Minimal Supersymmetric Standard Model: from theory to phenomenology}, Int.\ J.\ Mod.\ Phys.\ A {\bf 27}, 1230007 (2012) [arXiv:1202.4769 [hep-ph]]. %%CITATION = ARXIV:1202.4769;%% %\cite{He:2007ge} \bibitem{He:2007ge} H.~-J.~He, Y.~-P.~Kuang, Y.~-H.~Qi, B.~Zhang, A.~Belyaev, R.~S.~Chivukula, N.~D.~Christensen and A.~Pukhov {\it et al.}, {\em CERN LHC Signatures of New Gauge Bosons in Minimal Higgsless Model}, Phys.\ Rev.\ D {\bf 78}, 031701 (2008) [arXiv:0708.2588 [hep-ph]]. %%CITATION = ARXIV:0708.2588;%% %%%%% WHIZARD NLO %%%%% %\cite{Kilian:2006cj} \bibitem{Kilian:2006cj} W.~Kilian, J.~Reuter and T.~Robens, {\em NLO Event Generation for Chargino Production at the ILC}, Eur.\ Phys.\ J.\ C {\bf 48}, 389 (2006) [hep-ph/0607127]. %%CITATION = HEP-PH/0607127;%% %\cite{Binoth:2010ra} \bibitem{Binoth:2010ra} J.~R.~Andersen {\it et al.} [SM and NLO Multileg Working Group Collaboration], {\em Les Houches 2009: The SM and NLO Multileg Working Group: Summary report}, arXiv:1003.1241 [hep-ph]. %%CITATION = ARXIV:1003.1241;%% %\cite{Butterworth:2010ym} \bibitem{Butterworth:2010ym} J.~M.~Butterworth, A.~Arbey, L.~Basso, S.~Belov, A.~Bharucha, F.~Braam, A.~Buckley and M.~Campanelli {\it et al.}, {\em Les Houches 2009: The Tools and Monte Carlo working group Summary Report}, arXiv:1003.1643 [hep-ph], arXiv:1003.1643 [hep-ph]. %%CITATION = ARXIV:1003.1643;%% %\cite{Binoth:2009rv} \bibitem{Binoth:2009rv} T.~Binoth, N.~Greiner, A.~Guffanti, J.~Reuter, J.-P.~.Guillet and T.~Reiter, {\em Next-to-leading order QCD corrections to pp --> b anti-b b anti-b + X at the LHC: the quark induced case}, Phys.\ Lett.\ B {\bf 685}, 293 (2010) [arXiv:0910.4379 [hep-ph]]. %%CITATION = ARXIV:0910.4379;%% %\cite{Greiner:2011mp} \bibitem{Greiner:2011mp} N.~Greiner, A.~Guffanti, T.~Reiter and J.~Reuter, {\em NLO QCD corrections to the production of two bottom-antibottom pairs at the LHC} Phys.\ Rev.\ Lett.\ {\bf 107}, 102002 (2011) [arXiv:1105.3624 [hep-ph]]. %% CITATION = ARXIV:1105.3624;%% %\cite{L_Ecuyer:2002} \bibitem{L_Ecuyer:2002} P.~L\'{e}Ecuyer, R.~Simard, E.~J.~Chen, and W.~D.~Kelton, {\em An Object-Oriented Random-Number Package with Many Long Streams and Substreams}, Operations Research, vol. 50, no. 6, pp. 1073-1075, Dec. 2002. %\cite{Platzer:2013esa} \bibitem{Platzer:2013esa} S.~Pl\"atzer, {\em RAMBO on diet}, [arXiv:1308.2922 [hep-ph]]. %% CITATION = ARXIV:1308.2922;%% %\cite{Kleiss:1991rn} \bibitem{Kleiss:1991rn} R.~Kleiss and W.~J.~Stirling, {\em Massive multiplicities and Monte Carlo}, Nucl.\ Phys.\ B {\bf 385}, 413 (1992). doi:10.1016/0550-3213(92)90107-M %%CITATION = doi:10.1016/0550-3213(92)90107-M;%% %\cite{Kleiss:1985gy} \bibitem{Kleiss:1985gy} R.~Kleiss, W.~J.~Stirling and S.~D.~Ellis, {\em A New Monte Carlo Treatment of Multiparticle Phase Space at High-energies}, Comput.\ Phys.\ Commun.\ {\bf 40} (1986) 359. doi:10.1016/0010-4655(86)90119-0 %% CITATION = doi:10.1016/0010-4655(86)90119-0;%% \end{thebibliography} \end{document}