Page MenuHomeHEPForge

No OneTemporary

This file is larger than 256 KB, so syntax highlighting was skipped.
Index: trunk/src/physics/physics.nw
===================================================================
--- trunk/src/physics/physics.nw (revision 8188)
+++ trunk/src/physics/physics.nw (revision 8189)
@@ -1,5311 +1,5316 @@
% -*- ess-noweb-default-code-mode: f90-mode; noweb-default-code-mode: f90-mode; -*-
% WHIZARD code as NOWEB source: physics and such
\chapter{Physics}
\includemodulegraph{physics}
Here we collect definitions and functions that we need for (particle)
physics in general, to make them available for the more specific needs
of WHIZARD.
\begin{description}
\item[physics\_defs]
Physical constants.
\item[c\_particles]
A simple data type for particles which is C compatible.
\item[lorentz]
Define three-vectors, four-vectors and Lorentz
transformations and common operations for them.
\item[sm\_physics]
Here, running functions are stored for special kinematical setup like
running coupling constants, Catani-Seymour dipoles, or Sudakov factors.
\item[sm\_qcd]
Definitions and methods for dealing with the running QCD coupling.
\item[shower\_algorithms]
Algorithms typically used in Parton Showers as well as in their
matching to NLO computations, e.g. with the POWHEG method.
\end{description}
\clearpage
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
\section{Physics Constants}
There is also the generic [[constants]] module. The constants listed
here are more specific for particle physics.
<<[[physics_defs.f90]]>>=
<<File header>>
module physics_defs
<<Use kinds>>
<<Use strings>>
use constants, only: one, two, three
<<Standard module head>>
<<Physics defs: public parameters>>
<<Physics defs: public>>
<<Physics defs: interfaces>>
contains
<<Physics defs: procedures>>
end module physics_defs
@ %def physics_defs
@
\subsection{Units}
Conversion from energy units to cross-section units.
<<Physics defs: public parameters>>=
real(default), parameter, public :: &
conv = 0.38937966e12_default
@
+Conversion from millimeter to nanoseconds for lifetimes.
+<<Physics defs: public parameters>>=
+ real(default), parameter, public :: &
+ ns_per_mm = 1.e6_default / 299792458._default
+@
Rescaling factor.
<<Physics defs: public parameters>>=
real(default), parameter, public :: &
pb_per_fb = 1.e-3_default
@
String for the default energy and cross-section units.
<<Physics defs: public parameters>>=
character(*), parameter, public :: &
energy_unit = "GeV"
character(*), parameter, public :: &
cross_section_unit = "fb"
@
\subsection{SM and QCD constants}
<<Physics defs: public parameters>>=
real(default), parameter, public :: &
NC = three, &
CF = (NC**2 - one) / two / NC, &
CA = NC, &
TR = one / two
@
\subsection{Parameter Reference values}
These are used exclusively in the context of
running QCD parameters. In other contexts, we rely on the uniform
parameter set as provided by the model definition, modifiable by the
user.
<<Physics defs: public parameters>>=
real(default), public, parameter :: MZ_REF = 91.188_default
real(default), public, parameter :: ALPHA_QCD_MZ_REF = 0.1178_default
real(default), public, parameter :: LAMBDA_QCD_REF = 200.e-3_default
@ %def alpha_s_mz_ref mz_ref lambda_qcd_ref
@
\subsection{Particle codes}
Let us define a few particle codes independent of the model.
We need an UNDEFINED value:
<<Physics defs: public parameters>>=
integer, parameter, public :: UNDEFINED = 0
@ %def UNDEFINED
@ SM fermions:
<<Physics defs: public parameters>>=
integer, parameter, public :: ELECTRON = 11
integer, parameter, public :: ELECTRON_NEUTRINO = 12
integer, parameter, public :: MUON = 13
integer, parameter, public :: MUON_NEUTRINO = 14
integer, parameter, public :: TAU = 15
integer, parameter, public :: TAU_NEUTRINO = 16
@ %def ELECTRON MUON TAU
@ Gauge bosons:
<<Physics defs: public parameters>>=
integer, parameter, public :: GLUON = 21
integer, parameter, public :: PHOTON = 22
integer, parameter, public :: Z_BOSON = 23
integer, parameter, public :: W_BOSON = 24
@ %def GLUON PHOTON Z_BOSON W_BOSON
@ Light mesons:
<<Physics defs: public parameters>>=
integer, parameter, public :: PION = 111
integer, parameter, public :: PIPLUS = 211
integer, parameter, public :: PIMINUS = - PIPLUS
@ %def PION PIPLUS PIMINUS
@ Di-Quarks:
<<Physics defs: public parameters>>=
integer, parameter, public :: UD0 = 2101
integer, parameter, public :: UD1 = 2103
integer, parameter, public :: UU1 = 2203
@ %def UD0 UD1 UU1
@ Mesons:
<<Physics defs: public parameters>>=
integer, parameter, public :: K0L = 130
integer, parameter, public :: K0S = 310
integer, parameter, public :: K0 = 311
integer, parameter, public :: KPLUS = 321
integer, parameter, public :: DPLUS = 411
integer, parameter, public :: D0 = 421
integer, parameter, public :: B0 = 511
integer, parameter, public :: BPLUS = 521
@ %def K0L K0S K0 KPLUS DPLUS D0 B0 BPLUS
@ Light baryons:
<<Physics defs: public parameters>>=
integer, parameter, public :: PROTON = 2212
integer, parameter, public :: NEUTRON = 2112
integer, parameter, public :: DELTAPLUSPLUS = 2224
integer, parameter, public :: DELTAPLUS = 2214
integer, parameter, public :: DELTA0 = 2114
integer, parameter, public :: DELTAMINUS = 1114
@ %def PROTON NEUTRON DELTAPLUSPLUS DELTAPLUS DELTA0 DELTAMINUS
@ Strange baryons:
<<Physics defs: public parameters>>=
integer, parameter, public :: SIGMAPLUS = 3222
integer, parameter, public :: SIGMA0 = 3212
integer, parameter, public :: SIGMAMINUS = 3112
@ %def SIGMAPLUS SIGMA0 SIGMAMINUS
@ Charmed baryons:
<<Physics defs: public parameters>>=
integer, parameter, public :: SIGMACPLUSPLUS = 4222
integer, parameter, public :: SIGMACPLUS = 4212
integer, parameter, public :: SIGMAC0 = 4112
@ %def SIGMACPLUSPLUS SIGMACPLUS SIGMAC0
@ Bottom baryons:
<<Physics defs: public parameters>>=
integer, parameter, public :: SIGMAB0 = 5212
integer, parameter, public :: SIGMABPLUS = 5222
@ %def SIGMAB0 SIGMABPLUS
@ 81-100 are reserved for internal codes. Hadron and beam remnants:
<<Physics defs: public parameters>>=
integer, parameter, public :: BEAM_REMNANT = 9999
integer, parameter, public :: HADRON_REMNANT = 90
integer, parameter, public :: HADRON_REMNANT_SINGLET = 91
integer, parameter, public :: HADRON_REMNANT_TRIPLET = 92
integer, parameter, public :: HADRON_REMNANT_OCTET = 93
@ %def BEAM_REMNANT HADRON_REMNANT
@ %def HADRON_REMNANT_SINGLET HADRON_REMNANT_TRIPLET HADRON_REMNANT_OCTET
@
Further particle codes for internal use:
<<Physics defs: public parameters>>=
integer, parameter, public :: INTERNAL = 94
integer, parameter, public :: INVALID = 97
integer, parameter, public :: COMPOSITE = 99
@ %def INTERNAL INVALID COMPOSITE
@
\subsection{Spin codes}
Somewhat redundant, but for better readability we define named
constants for spin types. If the mass is nonzero, this is equal to
the number of degrees of freedom.
<<Physics defs: public parameters>>=
integer, parameter, public:: UNKNOWN = 0
integer, parameter, public :: SCALAR = 1, SPINOR = 2, VECTOR = 3, &
VECTORSPINOR = 4, TENSOR = 5
@ %def UNKNOWN SCALAR SPINOR VECTOR VECTORSPINOR TENSOR
@ Isospin types and charge types are counted in an analogous way,
where charge type 1 is charge 0, 2 is charge 1/3, and so on. Zero
always means unknown. Note that charge and isospin types have an
explicit sign.
Color types are defined as the dimension of the representation.
\subsection{NLO status codes}
Used to specify whether a [[term_instance_t]] of a
[[process_instance_t]] is associated with a Born, real-subtracted,
virtual-subtracted or subtraction-dummy matrix element.
<<Physics defs: public parameters>>=
integer, parameter, public :: BORN = 0
integer, parameter, public :: NLO_REAL = 1
integer, parameter, public :: NLO_VIRTUAL = 2
integer, parameter, public :: NLO_MISMATCH = 3
integer, parameter, public :: NLO_DGLAP = 4
integer, parameter, public :: NLO_SUBTRACTION = 5
integer, parameter, public :: NLO_FULL = 6
integer, parameter, public :: GKS = 7
integer, parameter, public :: COMPONENT_UNDEFINED = 99
@ % def BORN, NLO_REAL, NLO_VIRTUAL, NLO_SUBTRACTION, GKS
@ [[NLO_FULL]] is not strictly a component status code but having it is
convenient.
We define the number of additional subtractions for beam-involved NLO calculations.
Each subtraction refers to a rescaling of one of two beams.
<<Physics defs: public parameters>>=
integer, parameter, public :: n_beam_structure_int = 4
integer, parameter, public :: n_beam_gluon_offset = 2
@ %def n_beam_structure_int
@
<<Physics defs: public>>=
public :: component_status
<<Physics defs: interfaces>>=
interface component_status
module procedure component_status_of_string
module procedure component_status_to_string
end interface
<<Physics defs: procedures>>=
elemental function component_status_of_string (string) result (i)
integer :: i
type(string_t), intent(in) :: string
select case (char(string))
case ("born")
i = BORN
case ("real")
i = NLO_REAL
case ("virtual")
i = NLO_VIRTUAL
case ("mismatch")
i = NLO_MISMATCH
case ("dglap")
i = NLO_DGLAP
case ("subtraction")
i = NLO_SUBTRACTION
case ("full")
i = NLO_FULL
case ("GKS")
i = GKS
case default
i = COMPONENT_UNDEFINED
end select
end function component_status_of_string
elemental function component_status_to_string (i) result (string)
type(string_t) :: string
integer, intent(in) :: i
select case (i)
case (BORN)
string = "born"
case (NLO_REAL)
string = "real"
case (NLO_VIRTUAL)
string = "virtual"
case (NLO_MISMATCH)
string = "mismatch"
case (NLO_DGLAP)
string = "dglap"
case (NLO_SUBTRACTION)
string = "subtraction"
case (NLO_FULL)
string = "full"
case (GKS)
string = "GKS"
case default
string = "undefined"
end select
end function component_status_to_string
@ %def component_status
@
<<Physics defs: public>>=
public :: is_nlo_component
<<Physics defs: procedures>>=
elemental function is_nlo_component (comp) result (is_nlo)
logical :: is_nlo
integer, intent(in) :: comp
select case (comp)
case (BORN : GKS)
is_nlo = .true.
case default
is_nlo = .false.
end select
end function is_nlo_component
@ %def is_nlo_component
@
<<Physics defs: public>>=
public :: is_subtraction_component
<<Physics defs: procedures>>=
function is_subtraction_component (emitter, nlo_type) result (is_subtraction)
logical :: is_subtraction
integer, intent(in) :: emitter, nlo_type
is_subtraction = nlo_type == NLO_REAL .and. emitter < 0
end function is_subtraction_component
@ %def is_subtraction_component
@
\subsection{Threshold}
Some commonly used variables for the threshold computation
<<Physics defs: public parameters>>=
integer, parameter, public :: THR_POS_WP = 3
integer, parameter, public :: THR_POS_WM = 4
integer, parameter, public :: THR_POS_B = 5
integer, parameter, public :: THR_POS_BBAR = 6
integer, parameter, public :: THR_POS_GLUON = 7
integer, parameter, public :: THR_EMITTER_OFFSET = 4
integer, parameter, public :: NO_FACTORIZATION = 0
integer, parameter, public :: FACTORIZATION_THRESHOLD = 1
integer, dimension(2), parameter, public :: ass_quark = [5, 6]
integer, dimension(2), parameter, public :: ass_boson = [3, 4]
integer, parameter, public :: PROC_MODE_UNDEFINED = 0
integer, parameter, public :: PROC_MODE_TT = 1
integer, parameter, public :: PROC_MODE_WBWB = 2
@
@
<<Physics defs: public>>=
public :: thr_leg
<<Physics defs: procedures>>=
function thr_leg (emitter) result (leg)
integer :: leg
integer, intent(in) :: emitter
leg = emitter - THR_EMITTER_OFFSET
end function thr_leg
@ %def thr_leg
@
\clearpage
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
\section{C-compatible Particle Type}
For easy communication with C code, we introduce a simple C-compatible
type for particles. The components are either default C integers or
default C doubles.
The [[c_prt]] type is transparent, and its contents should be regarded
as part of the interface.
<<[[c_particles.f90]]>>=
<<File header>>
module c_particles
use, intrinsic :: iso_c_binding !NODEP!
use io_units
use format_defs, only: FMT_14, FMT_19
<<Standard module head>>
<<C Particles: public>>
<<C Particles: types>>
contains
<<C Particles: procedures>>
end module c_particles
@ %def c_particles
@
<<C Particles: public>>=
public :: c_prt_t
<<C Particles: types>>=
type, bind(C) :: c_prt_t
integer(c_int) :: type = 0
integer(c_int) :: pdg = 0
integer(c_int) :: polarized = 0
integer(c_int) :: h = 0
real(c_double) :: pe = 0
real(c_double) :: px = 0
real(c_double) :: py = 0
real(c_double) :: pz = 0
real(c_double) :: p2 = 0
end type c_prt_t
@ %def c_prt_t
@ This is for debugging only, there is no C binding. It is a
simplified version of [[prt_write]].
<<C Particles: public>>=
public :: c_prt_write
<<C Particles: procedures>>=
subroutine c_prt_write (prt, unit)
type(c_prt_t), intent(in) :: prt
integer, intent(in), optional :: unit
integer :: u
u = given_output_unit (unit); if (u < 0) return
write (u, "(1x,A)", advance="no") "prt("
write (u, "(I0,':')", advance="no") prt%type
if (prt%polarized /= 0) then
write (u, "(I0,'/',I0,'|')", advance="no") prt%pdg, prt%h
else
write (u, "(I0,'|')", advance="no") prt%pdg
end if
write (u, "(" // FMT_14 // ",';'," // FMT_14 // ",','," // &
FMT_14 // ",','," // FMT_14 // ")", advance="no") &
prt%pe, prt%px, prt%py, prt%pz
write (u, "('|'," // FMT_19 // ")", advance="no") prt%p2
write (u, "(A)") ")"
end subroutine c_prt_write
@ %def c_prt_write
@
\clearpage
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
\section{Lorentz algebra}
Define Lorentz vectors, three-vectors, boosts, and some functions to
manipulate them.
To make maximum use of this, all functions, if possible, are declared
elemental (or pure, if this is not possible).
<<[[lorentz.f90]]>>=
<<File header>>
module lorentz
<<Use kinds with double>>
use numeric_utils
use io_units
use constants, only: pi, twopi, degree, zero, one, two, eps0, tiny_07
use format_defs, only: FMT_11, FMT_13, FMT_15, FMT_19
use format_utils, only: pac_fmt
use diagnostics
use c_particles
<<Standard module head>>
<<Lorentz: public>>
<<Lorentz: public operators>>
<<Lorentz: public functions>>
<<Lorentz: types>>
<<Lorentz: parameters>>
<<Lorentz: interfaces>>
contains
<<Lorentz: procedures>>
end module lorentz
@ %def lorentz
@
\subsection{Three-vectors}
First of all, let us introduce three-vectors in a trivial way. The
functions and overloaded elementary operations clearly are too much
overhead, but we like to keep the interface for three-vectors and
four-vectors exactly parallel. By the way, we might attach a label to
a vector by extending the type definition later.
<<Lorentz: public>>=
public :: vector3_t
<<Lorentz: types>>=
type :: vector3_t
real(default), dimension(3) :: p
end type vector3_t
@ %def vector3_t
@ Output a vector
<<Lorentz: public>>=
public :: vector3_write
<<Lorentz: procedures>>=
subroutine vector3_write (p, unit, testflag)
type(vector3_t), intent(in) :: p
integer, intent(in), optional :: unit
logical, intent(in), optional :: testflag
character(len=7) :: fmt
integer :: u
u = given_output_unit (unit); if (u < 0) return
call pac_fmt (fmt, FMT_19, FMT_15, testflag)
write(u, "(1x,A,3(1x," // fmt // "))") 'P = ', p%p
end subroutine vector3_write
@ %def vector3_write
@ This is a three-vector with zero components
<<Lorentz: public>>=
public :: vector3_null
<<Lorentz: parameters>>=
type(vector3_t), parameter :: vector3_null = &
vector3_t ([ zero, zero, zero ])
@ %def vector3_null
@ Canonical three-vector:
<<Lorentz: public>>=
public :: vector3_canonical
<<Lorentz: procedures>>=
elemental function vector3_canonical (k) result (p)
type(vector3_t) :: p
integer, intent(in) :: k
p = vector3_null
p%p(k) = 1
end function vector3_canonical
@ %def vector3_canonical
@ A moving particle ($k$-axis, or arbitrary axis). Note that the
function for the generic momentum cannot be elemental.
<<Lorentz: public>>=
public :: vector3_moving
<<Lorentz: interfaces>>=
interface vector3_moving
module procedure vector3_moving_canonical
module procedure vector3_moving_generic
end interface
<<Lorentz: procedures>>=
elemental function vector3_moving_canonical (p, k) result(q)
type(vector3_t) :: q
real(default), intent(in) :: p
integer, intent(in) :: k
q = vector3_null
q%p(k) = p
end function vector3_moving_canonical
pure function vector3_moving_generic (p) result(q)
real(default), dimension(3), intent(in) :: p
type(vector3_t) :: q
q%p = p
end function vector3_moving_generic
@ %def vector3_moving
@ Equality and inequality
<<Lorentz: public operators>>=
public :: operator(==), operator(/=)
<<Lorentz: interfaces>>=
interface operator(==)
module procedure vector3_eq
end interface
interface operator(/=)
module procedure vector3_neq
end interface
<<Lorentz: procedures>>=
elemental function vector3_eq (p, q) result (r)
logical :: r
type(vector3_t), intent(in) :: p,q
r = all (abs (p%p - q%p) < eps0)
end function vector3_eq
elemental function vector3_neq (p, q) result (r)
logical :: r
type(vector3_t), intent(in) :: p,q
r = any (abs(p%p - q%p) > eps0)
end function vector3_neq
@ %def == /=
@ Define addition and subtraction
<<Lorentz: public operators>>=
public :: operator(+), operator(-)
<<Lorentz: interfaces>>=
interface operator(+)
module procedure add_vector3
end interface
interface operator(-)
module procedure sub_vector3
end interface
<<Lorentz: procedures>>=
elemental function add_vector3 (p, q) result (r)
type(vector3_t) :: r
type(vector3_t), intent(in) :: p,q
r%p = p%p + q%p
end function add_vector3
elemental function sub_vector3 (p, q) result (r)
type(vector3_t) :: r
type(vector3_t), intent(in) :: p,q
r%p = p%p - q%p
end function sub_vector3
@ %def + -
@ The multiplication sign is overloaded with scalar multiplication;
similarly division:
<<Lorentz: public operators>>=
public :: operator(*), operator(/)
<<Lorentz: interfaces>>=
interface operator(*)
module procedure prod_integer_vector3, prod_vector3_integer
module procedure prod_real_vector3, prod_vector3_real
end interface
interface operator(/)
module procedure div_vector3_real, div_vector3_integer
end interface
<<Lorentz: procedures>>=
elemental function prod_real_vector3 (s, p) result (q)
type(vector3_t) :: q
real(default), intent(in) :: s
type(vector3_t), intent(in) :: p
q%p = s * p%p
end function prod_real_vector3
elemental function prod_vector3_real (p, s) result (q)
type(vector3_t) :: q
real(default), intent(in) :: s
type(vector3_t), intent(in) :: p
q%p = s * p%p
end function prod_vector3_real
elemental function div_vector3_real (p, s) result (q)
type(vector3_t) :: q
real(default), intent(in) :: s
type(vector3_t), intent(in) :: p
q%p = p%p/s
end function div_vector3_real
elemental function prod_integer_vector3 (s, p) result (q)
type(vector3_t) :: q
integer, intent(in) :: s
type(vector3_t), intent(in) :: p
q%p = s * p%p
end function prod_integer_vector3
elemental function prod_vector3_integer (p, s) result (q)
type(vector3_t) :: q
integer, intent(in) :: s
type(vector3_t), intent(in) :: p
q%p = s * p%p
end function prod_vector3_integer
elemental function div_vector3_integer (p, s) result (q)
type(vector3_t) :: q
integer, intent(in) :: s
type(vector3_t), intent(in) :: p
q%p = p%p/s
end function div_vector3_integer
@ %def * /
@ The multiplication sign can also indicate scalar products:
<<Lorentz: interfaces>>=
interface operator(*)
module procedure prod_vector3
end interface
<<Lorentz: procedures>>=
elemental function prod_vector3 (p, q) result (s)
real(default) :: s
type(vector3_t), intent(in) :: p,q
s = dot_product (p%p, q%p)
end function prod_vector3
@ %def *
<<Lorentz: public functions>>=
public :: cross_product
<<Lorentz: interfaces>>=
interface cross_product
module procedure vector3_cross_product
end interface
<<Lorentz: procedures>>=
elemental function vector3_cross_product (p, q) result (r)
type(vector3_t) :: r
type(vector3_t), intent(in) :: p,q
integer :: i
do i=1,3
r%p(i) = dot_product (p%p, matmul(epsilon_three(i,:,:), q%p))
end do
end function vector3_cross_product
@ %def cross_product
@ Exponentiation is defined only for integer powers. Odd powers mean
take the square root; so [[p**1]] is the length of [[p]].
<<Lorentz: public operators>>=
public :: operator(**)
<<Lorentz: interfaces>>=
interface operator(**)
module procedure power_vector3
end interface
<<Lorentz: procedures>>=
elemental function power_vector3 (p, e) result (s)
real(default) :: s
type(vector3_t), intent(in) :: p
integer, intent(in) :: e
s = dot_product (p%p, p%p)
if (e/=2) then
if (mod(e,2)==0) then
s = s**(e/2)
else
s = sqrt(s)**e
end if
end if
end function power_vector3
@ %def **
@ Finally, we need a negation.
<<Lorentz: interfaces>>=
interface operator(-)
module procedure negate_vector3
end interface
<<Lorentz: procedures>>=
elemental function negate_vector3 (p) result (q)
type(vector3_t) :: q
type(vector3_t), intent(in) :: p
integer :: i
do i = 1, 3
if (abs (p%p(i)) < eps0) then
q%p(i) = 0
else
q%p(i) = -p%p(i)
end if
end do
end function negate_vector3
@ %def -
@ The sum function can be useful:
<<Lorentz: public functions>>=
public :: sum
<<Lorentz: interfaces>>=
interface sum
module procedure sum_vector3
end interface
@ %def sum
@
<<Lorentz: public>>=
public :: vector3_set_component
<<Lorentz: procedures>>=
subroutine vector3_set_component (p, i, value)
type(vector3_t), intent(inout) :: p
integer, intent(in) :: i
real(default), intent(in) :: value
p%p(i) = value
end subroutine vector3_set_component
@ %def vector3_set_component
@
<<Lorentz: procedures>>=
pure function sum_vector3 (p) result (q)
type(vector3_t) :: q
type(vector3_t), dimension(:), intent(in) :: p
integer :: i
do i=1, 3
q%p(i) = sum (p%p(i))
end do
end function sum_vector3
@ %def sum
@ Any component:
<<Lorentz: public>>=
public :: vector3_get_component
@ %def component
<<Lorentz: procedures>>=
elemental function vector3_get_component (p, k) result (c)
type(vector3_t), intent(in) :: p
integer, intent(in) :: k
real(default) :: c
c = p%p(k)
end function vector3_get_component
@ %def vector3_get_component
@ Extract all components. This is not elemental.
<<Lorentz: public>>=
public :: vector3_get_components
<<Lorentz: procedures>>=
pure function vector3_get_components (p) result (a)
type(vector3_t), intent(in) :: p
real(default), dimension(3) :: a
a = p%p
end function vector3_get_components
@ %def vector3_get_components
@ This function returns the direction of a three-vector, i.e., a
normalized three-vector. If the vector is null, we return a null vector.
<<Lorentz: public functions>>=
public :: direction
<<Lorentz: interfaces>>=
interface direction
module procedure vector3_get_direction
end interface
<<Lorentz: procedures>>=
elemental function vector3_get_direction (p) result (q)
type(vector3_t) :: q
type(vector3_t), intent(in) :: p
real(default) :: pp
pp = p**1
if (pp > eps0) then
q%p = p%p / pp
else
q%p = 0
end if
end function vector3_get_direction
@ %def direction
@
\subsection{Four-vectors}
In four-vectors the zero-component needs special treatment, therefore
we do not use the standard operations. Sure, we pay for the extra
layer of abstraction by losing efficiency; so we have to assume that
the time-critical applications do not involve four-vector operations.
<<Lorentz: public>>=
public :: vector4_t
<<Lorentz: types>>=
type :: vector4_t
real(default), dimension(0:3) :: p = &
[zero, zero, zero, zero]
contains
<<Lorentz: vector4: TBP>>
end type vector4_t
@ %def vector4_t
@ Output a vector
<<Lorentz: public>>=
public :: vector4_write
<<Lorentz: vector4: TBP>>=
procedure :: write => vector4_write
<<Lorentz: procedures>>=
subroutine vector4_write &
(p, unit, show_mass, testflag, compressed, ultra)
class(vector4_t), intent(in) :: p
integer, intent(in), optional :: unit
logical, intent(in), optional :: show_mass, testflag, compressed, ultra
logical :: comp, sm, tf, extreme
integer :: u
character(len=7) :: fmt
real(default) :: m
comp = .false.; if (present (compressed)) comp = compressed
sm = .false.; if (present (show_mass)) sm = show_mass
tf = .false.; if (present (testflag)) tf = testflag
extreme = .false.; if (present (ultra)) extreme = ultra
if (extreme) then
call pac_fmt (fmt, FMT_19, FMT_11, testflag)
else
call pac_fmt (fmt, FMT_19, FMT_13, testflag)
end if
u = given_output_unit (unit); if (u < 0) return
if (comp) then
write (u, "(4(F12.3,1X))", advance="no") p%p(0:3)
else
write (u, "(1x,A,1x," // fmt // ")") 'E = ', p%p(0)
write (u, "(1x,A,3(1x," // fmt // "))") 'P = ', p%p(1:)
if (sm) then
m = p**1
if (tf) call pacify (m, tolerance = 1E-6_default)
write (u, "(1x,A,1x," // fmt // ")") 'M = ', m
end if
end if
end subroutine vector4_write
@ %def vector4_write
@ Binary I/O
<<Lorentz: public>>=
public :: vector4_write_raw
public :: vector4_read_raw
<<Lorentz: procedures>>=
subroutine vector4_write_raw (p, u)
type(vector4_t), intent(in) :: p
integer, intent(in) :: u
write (u) p%p
end subroutine vector4_write_raw
subroutine vector4_read_raw (p, u, iostat)
type(vector4_t), intent(out) :: p
integer, intent(in) :: u
integer, intent(out), optional :: iostat
read (u, iostat=iostat) p%p
end subroutine vector4_read_raw
@ %def vector4_write_raw vector4_read_raw
@ This is a four-vector with zero components
<<Lorentz: public>>=
public :: vector4_null
<<Lorentz: parameters>>=
type(vector4_t), parameter :: vector4_null = &
vector4_t ([ zero, zero, zero, zero ])
@ %def vector4_null
@ Canonical four-vector:
<<Lorentz: public>>=
public :: vector4_canonical
<<Lorentz: procedures>>=
elemental function vector4_canonical (k) result (p)
type(vector4_t) :: p
integer, intent(in) :: k
p = vector4_null
p%p(k) = 1
end function vector4_canonical
@ %def vector4_canonical
@ A particle at rest:
<<Lorentz: public>>=
public :: vector4_at_rest
<<Lorentz: procedures>>=
elemental function vector4_at_rest (m) result (p)
type(vector4_t) :: p
real(default), intent(in) :: m
p = vector4_t ([ m, zero, zero, zero ])
end function vector4_at_rest
@ %def vector4_at_rest
@ A moving particle ($k$-axis, or arbitrary axis)
<<Lorentz: public>>=
public :: vector4_moving
<<Lorentz: interfaces>>=
interface vector4_moving
module procedure vector4_moving_canonical
module procedure vector4_moving_generic
end interface
<<Lorentz: procedures>>=
elemental function vector4_moving_canonical (E, p, k) result (q)
type(vector4_t) :: q
real(default), intent(in) :: E, p
integer, intent(in) :: k
q = vector4_at_rest(E)
q%p(k) = p
end function vector4_moving_canonical
elemental function vector4_moving_generic (E, p) result (q)
type(vector4_t) :: q
real(default), intent(in) :: E
type(vector3_t), intent(in) :: p
q%p(0) = E
q%p(1:) = p%p
end function vector4_moving_generic
@ %def vector4_moving
@ Equality and inequality
<<Lorentz: interfaces>>=
interface operator(==)
module procedure vector4_eq
end interface
interface operator(/=)
module procedure vector4_neq
end interface
<<Lorentz: procedures>>=
elemental function vector4_eq (p, q) result (r)
logical :: r
type(vector4_t), intent(in) :: p,q
r = all (abs (p%p - q%p) < eps0)
end function vector4_eq
elemental function vector4_neq (p, q) result (r)
logical :: r
type(vector4_t), intent(in) :: p,q
r = any (abs (p%p - q%p) > eps0)
end function vector4_neq
@ %def == /=
@ Addition and subtraction:
<<Lorentz: interfaces>>=
interface operator(+)
module procedure add_vector4
end interface
interface operator(-)
module procedure sub_vector4
end interface
<<Lorentz: procedures>>=
elemental function add_vector4 (p,q) result (r)
type(vector4_t) :: r
type(vector4_t), intent(in) :: p,q
r%p = p%p + q%p
end function add_vector4
elemental function sub_vector4 (p,q) result (r)
type(vector4_t) :: r
type(vector4_t), intent(in) :: p,q
r%p = p%p - q%p
end function sub_vector4
@ %def + -
@ We also need scalar multiplication and division:
<<Lorentz: interfaces>>=
interface operator(*)
module procedure prod_real_vector4, prod_vector4_real
module procedure prod_integer_vector4, prod_vector4_integer
end interface
interface operator(/)
module procedure div_vector4_real
module procedure div_vector4_integer
end interface
<<Lorentz: procedures>>=
elemental function prod_real_vector4 (s, p) result (q)
type(vector4_t) :: q
real(default), intent(in) :: s
type(vector4_t), intent(in) :: p
q%p = s * p%p
end function prod_real_vector4
elemental function prod_vector4_real (p, s) result (q)
type(vector4_t) :: q
real(default), intent(in) :: s
type(vector4_t), intent(in) :: p
q%p = s * p%p
end function prod_vector4_real
elemental function div_vector4_real (p, s) result (q)
type(vector4_t) :: q
real(default), intent(in) :: s
type(vector4_t), intent(in) :: p
q%p = p%p/s
end function div_vector4_real
elemental function prod_integer_vector4 (s, p) result (q)
type(vector4_t) :: q
integer, intent(in) :: s
type(vector4_t), intent(in) :: p
q%p = s * p%p
end function prod_integer_vector4
elemental function prod_vector4_integer (p, s) result (q)
type(vector4_t) :: q
integer, intent(in) :: s
type(vector4_t), intent(in) :: p
q%p = s * p%p
end function prod_vector4_integer
elemental function div_vector4_integer (p, s) result (q)
type(vector4_t) :: q
integer, intent(in) :: s
type(vector4_t), intent(in) :: p
q%p = p%p/s
end function div_vector4_integer
@ %def * /
@ Scalar products and squares in the Minkowski sense:
<<Lorentz: interfaces>>=
interface operator(*)
module procedure prod_vector4
end interface
interface operator(**)
module procedure power_vector4
end interface
<<Lorentz: procedures>>=
elemental function prod_vector4 (p, q) result (s)
real(default) :: s
type(vector4_t), intent(in) :: p,q
s = p%p(0)*q%p(0) - dot_product(p%p(1:), q%p(1:))
end function prod_vector4
@ %def *
@ The power operation for four-vectors is signed, i.e., [[p**1]] is
positive for timelike and negative for spacelike vectors. Note that
[[(p**1)**2]] is not necessarily equal to [[p**2]].
<<Lorentz: procedures>>=
elemental function power_vector4 (p, e) result (s)
real(default) :: s
type(vector4_t), intent(in) :: p
integer, intent(in) :: e
s = p * p
if (e /= 2) then
if (mod(e, 2) == 0) then
s = s**(e / 2)
else if (s >= 0) then
s = sqrt(s)**e
else
s = -(sqrt(abs(s))**e)
end if
end if
end function power_vector4
@ %def **
@ Finally, we introduce a negation
<<Lorentz: interfaces>>=
interface operator(-)
module procedure negate_vector4
end interface
<<Lorentz: procedures>>=
elemental function negate_vector4 (p) result (q)
type(vector4_t) :: q
type(vector4_t), intent(in) :: p
integer :: i
do i = 0, 3
if (abs (p%p(i)) < eps0) then
q%p(i) = 0
else
q%p(i) = -p%p(i)
end if
end do
end function negate_vector4
@ %def -
@ The sum function can be useful:
<<Lorentz: interfaces>>=
interface sum
module procedure sum_vector4, sum_vector4_mask
end interface
@ %def sum
@
<<Lorentz: procedures>>=
pure function sum_vector4 (p) result (q)
type(vector4_t) :: q
type(vector4_t), dimension(:), intent(in) :: p
integer :: i
do i = 0, 3
q%p(i) = sum (p%p(i))
end do
end function sum_vector4
pure function sum_vector4_mask (p, mask) result (q)
type(vector4_t) :: q
type(vector4_t), dimension(:), intent(in) :: p
logical, dimension(:), intent(in) :: mask
integer :: i
do i = 0, 3
q%p(i) = sum (p%p(i), mask=mask)
end do
end function sum_vector4_mask
@ %def sum
@
\subsection{Conversions}
Manually set a component of the four-vector:
<<Lorentz: public>>=
public :: vector4_set_component
<<Lorentz: procedures>>=
subroutine vector4_set_component (p, k, c)
type(vector4_t), intent(inout) :: p
integer, intent(in) :: k
real(default), intent(in) :: c
p%p(k) = c
end subroutine vector4_set_component
@ %def vector4_get_component
Any component:
<<Lorentz: public>>=
public :: vector4_get_component
<<Lorentz: procedures>>=
elemental function vector4_get_component (p, k) result (c)
real(default) :: c
type(vector4_t), intent(in) :: p
integer, intent(in) :: k
c = p%p(k)
end function vector4_get_component
@ %def vector4_get_component
@ Extract all components. This is not elemental.
<<Lorentz: public>>=
public :: vector4_get_components
<<Lorentz: procedures>>=
pure function vector4_get_components (p) result (a)
real(default), dimension(0:3) :: a
type(vector4_t), intent(in) :: p
a = p%p
end function vector4_get_components
@ %def vector4_get_components
@ This function returns the space part of a four-vector, such that we
can apply three-vector operations on it:
<<Lorentz: public functions>>=
public :: space_part
<<Lorentz: interfaces>>=
interface space_part
module procedure vector4_get_space_part
end interface
<<Lorentz: procedures>>=
elemental function vector4_get_space_part (p) result (q)
type(vector3_t) :: q
type(vector4_t), intent(in) :: p
q%p = p%p(1:)
end function vector4_get_space_part
@ %def space_part
@ This function returns the direction of a four-vector, i.e., a
normalized three-vector. If the four-vector has zero space part, we
return a null vector.
<<Lorentz: interfaces>>=
interface direction
module procedure vector4_get_direction
end interface
<<Lorentz: procedures>>=
elemental function vector4_get_direction (p) result (q)
type(vector3_t) :: q
type(vector4_t), intent(in) :: p
real(default) :: qq
q%p = p%p(1:)
qq = q**1
if (abs(qq) > eps0) then
q%p = q%p / qq
else
q%p = 0
end if
end function vector4_get_direction
@ %def direction
@ Change the sign of the spatial part of a four-vector
<<Lorentz: public>>=
public :: vector4_invert_direction
<<Lorentz: procedures>>=
elemental subroutine vector4_invert_direction (p)
type(vector4_t), intent(inout) :: p
p%p(1:3) = -p%p(1:3)
end subroutine vector4_invert_direction
@ %def vector4_invert_direction
@ This function returns the four-vector as an ordinary array. A
second version for an array of four-vectors.
<<Lorentz: public>>=
public :: assignment (=)
<<Lorentz: interfaces>>=
interface assignment (=)
module procedure array_from_vector4_1, array_from_vector4_2, &
array_from_vector3_1, array_from_vector3_2, &
vector4_from_array, vector3_from_array
end interface
<<Lorentz: procedures>>=
pure subroutine array_from_vector4_1 (a, p)
real(default), dimension(:), intent(out) :: a
type(vector4_t), intent(in) :: p
a = p%p
end subroutine array_from_vector4_1
pure subroutine array_from_vector4_2 (a, p)
type(vector4_t), dimension(:), intent(in) :: p
real(default), dimension(:,:), intent(out) :: a
integer :: i
forall (i=1:size(p))
a(:,i) = p(i)%p
end forall
end subroutine array_from_vector4_2
pure subroutine array_from_vector3_1 (a, p)
real(default), dimension(:), intent(out) :: a
type(vector3_t), intent(in) :: p
a = p%p
end subroutine array_from_vector3_1
pure subroutine array_from_vector3_2 (a, p)
type(vector3_t), dimension(:), intent(in) :: p
real(default), dimension(:,:), intent(out) :: a
integer :: i
forall (i=1:size(p))
a(:,i) = p(i)%p
end forall
end subroutine array_from_vector3_2
pure subroutine vector4_from_array (p, a)
type(vector4_t), intent(out) :: p
real(default), dimension(:), intent(in) :: a
p%p(0:3) = a
end subroutine vector4_from_array
pure subroutine vector3_from_array (p, a)
type(vector3_t), intent(out) :: p
real(default), dimension(:), intent(in) :: a
p%p(1:3) = a
end subroutine vector3_from_array
@ %def array_from_vector4 array_from_vector3
@
<<Lorentz: public>>=
public :: vector4
<<Lorentz: procedures>>=
pure function vector4 (a) result (p)
type(vector4_t) :: p
real(default), intent(in), dimension(4) :: a
p%p = a
end function vector4
@ %def vector4
@
<<Lorentz: vector4: TBP>>=
procedure :: to_pythia6 => vector4_to_pythia6
<<Lorentz: procedures>>=
pure function vector4_to_pythia6 (vector4, m) result (p)
real(double), dimension(1:5) :: p
class(vector4_t), intent(in) :: vector4
real(default), intent(in), optional :: m
p(1:3) = vector4%p(1:3)
p(4) = vector4%p(0)
if (present (m)) then
p(5) = m
else
p(5) = vector4 ** 1
end if
end function vector4_to_pythia6
@ %def vector4_to_pythia6
@ Transform the momentum of a [[c_prt]] object into a four-vector and
vice versa:
<<Lorentz: interfaces>>=
interface assignment (=)
module procedure vector4_from_c_prt, c_prt_from_vector4
end interface
<<Lorentz: procedures>>=
pure subroutine vector4_from_c_prt (p, c_prt)
type(vector4_t), intent(out) :: p
type(c_prt_t), intent(in) :: c_prt
p%p(0) = c_prt%pe
p%p(1) = c_prt%px
p%p(2) = c_prt%py
p%p(3) = c_prt%pz
end subroutine vector4_from_c_prt
pure subroutine c_prt_from_vector4 (c_prt, p)
type(c_prt_t), intent(out) :: c_prt
type(vector4_t), intent(in) :: p
c_prt%pe = p%p(0)
c_prt%px = p%p(1)
c_prt%py = p%p(2)
c_prt%pz = p%p(3)
c_prt%p2 = p ** 2
end subroutine c_prt_from_vector4
@ %def vector4_from_c_prt c_prt_from_vector4
@ Initialize a [[c_prt_t]] object with the components of a four-vector
as its kinematical entries. Compute the invariant mass, or use the
optional mass-squared value instead.
<<Lorentz: public>>=
public :: vector4_to_c_prt
<<Lorentz: procedures>>=
elemental function vector4_to_c_prt (p, p2) result (c_prt)
type(c_prt_t) :: c_prt
type(vector4_t), intent(in) :: p
real(default), intent(in), optional :: p2
c_prt%pe = p%p(0)
c_prt%px = p%p(1)
c_prt%py = p%p(2)
c_prt%pz = p%p(3)
if (present (p2)) then
c_prt%p2 = p2
else
c_prt%p2 = p ** 2
end if
end function vector4_to_c_prt
@ %def vector4_to_c_prt
@
<<Lorentz: public>>=
public :: phs_point_t
<<Lorentz: types>>=
type :: phs_point_t
type(vector4_t), dimension(:), allocatable :: p
integer :: n_momenta = 0
contains
<<Lorentz: phs point: TBP>>
end type phs_point_t
@ %def phs_point_t
@
<<Lorentz: interfaces>>=
interface operator(==)
module procedure phs_point_eq
end interface
<<Lorentz: procedures>>=
elemental function phs_point_eq (phs_point_1, phs_point_2) result (eq)
logical :: eq
type(phs_point_t), intent(in) :: phs_point_1, phs_point_2
eq = all (phs_point_1%p == phs_point_2%p)
end function phs_point_eq
@ %def phs_point_eq
@
<<Lorentz: interfaces>>=
interface operator(*)
module procedure prod_LT_phs_point
end interface
<<Lorentz: procedures>>=
elemental function prod_LT_phs_point (L, phs_point) result (phs_point_LT)
type(phs_point_t) :: phs_point_LT
type(lorentz_transformation_t), intent(in) :: L
type(phs_point_t), intent(in) :: phs_point
phs_point_LT = size (phs_point%p)
phs_point_LT%p = L * phs_point%p
end function prod_LT_phs_point
@ %def prod_LT_phs_point
@
<<Lorentz: interfaces>>=
interface assignment(=)
module procedure phs_point_from_n, phs_point_from_vector4, &
phs_point_from_phs_point
end interface
<<Lorentz: procedures>>=
pure subroutine phs_point_from_n (phs_point, n_particles)
type(phs_point_t), intent(out) :: phs_point
integer, intent(in) :: n_particles
allocate (phs_point%p (n_particles))
phs_point%n_momenta = n_particles
phs_point%p = vector4_null
end subroutine phs_point_from_n
@ %def phs_point_init_from_n
@
<<Lorentz: phs point: TBP>>=
<<Lorentz: procedures>>=
pure subroutine phs_point_from_vector4 (phs_point, p)
type(phs_point_t), intent(out) :: phs_point
type(vector4_t), intent(in), dimension(:) :: p
phs_point%n_momenta = size (p)
allocate (phs_point%p (phs_point%n_momenta), source = p)
end subroutine phs_point_from_vector4
@ %def phs_point_init_from_p
@
<<Lorentz: procedures>>=
pure subroutine phs_point_from_phs_point (phs_point, phs_point_in)
type(phs_point_t), intent(out) :: phs_point
type(phs_point_t), intent(in) :: phs_point_in
phs_point%n_momenta = phs_point_in%n_momenta
allocate (phs_point%p (phs_point%n_momenta))
phs_point%p = phs_point_in%p
end subroutine phs_point_from_phs_point
@ %def phs_point_from_phs_point
@
<<Lorentz: phs point: TBP>>=
procedure :: get_sqrts_in => phs_point_get_sqrts_in
<<Lorentz: procedures>>=
function phs_point_get_sqrts_in (phs_point, n_in) result (msq)
real(default) :: msq
class(phs_point_t), intent(in) :: phs_point
integer, intent(in) :: n_in
msq = (sum (phs_point%p(1:n_in)))**2
end function phs_point_get_sqrts_in
@ %def phs_point_get_sqrts_in
@
<<Lorentz: phs point: TBP>>=
procedure :: final => phs_point_final
<<Lorentz: procedures>>=
subroutine phs_point_final (phs_point)
class(phs_point_t), intent(inout) :: phs_point
deallocate (phs_point%p)
phs_point%n_momenta = 0
end subroutine phs_point_final
@ %def phs_point_final
@
<<Lorentz: phs point: TBP>>=
procedure :: write => phs_point_write
<<Lorentz: procedures>>=
subroutine phs_point_write (phs_point, unit, show_mass, testflag, &
check_conservation, ultra, n_in)
class(phs_point_t), intent(in) :: phs_point
integer, intent(in), optional :: unit
logical, intent(in), optional :: show_mass
logical, intent(in), optional :: testflag, ultra
logical, intent(in), optional :: check_conservation
integer, intent(in), optional :: n_in
call vector4_write_set (phs_point%p, unit = unit, show_mass = show_mass, &
testflag = testflag, check_conservation = check_conservation, &
ultra = ultra, n_in = n_in)
end subroutine phs_point_write
@ %def phs_point_write
@
<<Lorentz: phs point: TBP>>=
procedure :: get_x => phs_point_get_x
<<Lorentz: procedures>>=
function phs_point_get_x (phs_point, E_beam) result (x)
real(default), dimension(2) :: x
class(phs_point_t), intent(in) :: phs_point
real(default), intent(in) :: E_beam
x = phs_point%p(1:2)%p(0) / E_beam
end function phs_point_get_x
@ %def phs_point_get_x
@
\subsection{Angles}
Return the angles in a canonical system. The angle $\phi$ is defined
between $0\leq\phi<2\pi$. In degenerate cases, return zero.
<<Lorentz: public functions>>=
public :: azimuthal_angle
<<Lorentz: interfaces>>=
interface azimuthal_angle
module procedure vector3_azimuthal_angle
module procedure vector4_azimuthal_angle
end interface
<<Lorentz: procedures>>=
elemental function vector3_azimuthal_angle (p) result (phi)
real(default) :: phi
type(vector3_t), intent(in) :: p
if (any (abs (p%p(1:2)) > 0)) then
phi = atan2(p%p(2), p%p(1))
if (phi < 0) phi = phi + twopi
else
phi = 0
end if
end function vector3_azimuthal_angle
elemental function vector4_azimuthal_angle (p) result (phi)
real(default) :: phi
type(vector4_t), intent(in) :: p
phi = vector3_azimuthal_angle (space_part (p))
end function vector4_azimuthal_angle
@ %def azimuthal_angle
@ Azimuthal angle in degrees
<<Lorentz: public functions>>=
public :: azimuthal_angle_deg
<<Lorentz: interfaces>>=
interface azimuthal_angle_deg
module procedure vector3_azimuthal_angle_deg
module procedure vector4_azimuthal_angle_deg
end interface
<<Lorentz: procedures>>=
elemental function vector3_azimuthal_angle_deg (p) result (phi)
real(default) :: phi
type(vector3_t), intent(in) :: p
phi = vector3_azimuthal_angle (p) / degree
end function vector3_azimuthal_angle_deg
elemental function vector4_azimuthal_angle_deg (p) result (phi)
real(default) :: phi
type(vector4_t), intent(in) :: p
phi = vector4_azimuthal_angle (p) / degree
end function vector4_azimuthal_angle_deg
@ %def azimuthal_angle_deg
@ The azimuthal distance of two vectors. This is the difference of
the azimuthal angles, but cannot be larger than $\pi$: The result is
between $-\pi<\Delta\phi\leq\pi$.
<<Lorentz: public functions>>=
public :: azimuthal_distance
<<Lorentz: interfaces>>=
interface azimuthal_distance
module procedure vector3_azimuthal_distance
module procedure vector4_azimuthal_distance
end interface
<<Lorentz: procedures>>=
elemental function vector3_azimuthal_distance (p, q) result (dphi)
real(default) :: dphi
type(vector3_t), intent(in) :: p,q
dphi = vector3_azimuthal_angle (q) - vector3_azimuthal_angle (p)
if (dphi <= -pi) then
dphi = dphi + twopi
else if (dphi > pi) then
dphi = dphi - twopi
end if
end function vector3_azimuthal_distance
elemental function vector4_azimuthal_distance (p, q) result (dphi)
real(default) :: dphi
type(vector4_t), intent(in) :: p,q
dphi = vector3_azimuthal_distance &
(space_part (p), space_part (q))
end function vector4_azimuthal_distance
@ %def azimuthal_distance
@ The same in degrees:
<<Lorentz: public functions>>=
public :: azimuthal_distance_deg
<<Lorentz: interfaces>>=
interface azimuthal_distance_deg
module procedure vector3_azimuthal_distance_deg
module procedure vector4_azimuthal_distance_deg
end interface
<<Lorentz: procedures>>=
elemental function vector3_azimuthal_distance_deg (p, q) result (dphi)
real(default) :: dphi
type(vector3_t), intent(in) :: p,q
dphi = vector3_azimuthal_distance (p, q) / degree
end function vector3_azimuthal_distance_deg
elemental function vector4_azimuthal_distance_deg (p, q) result (dphi)
real(default) :: dphi
type(vector4_t), intent(in) :: p,q
dphi = vector4_azimuthal_distance (p, q) / degree
end function vector4_azimuthal_distance_deg
@ %def azimuthal_distance_deg
@ The polar angle is defined $0\leq\theta\leq\pi$. Note that
[[ATAN2]] has the reversed order of arguments: [[ATAN2(Y,X)]]. Here,
$x$ is the 3-component while $y$ is the transverse momentum which is
always nonnegative. Therefore, the result is nonnegative as well.
<<Lorentz: public functions>>=
public :: polar_angle
<<Lorentz: interfaces>>=
interface polar_angle
module procedure polar_angle_vector3
module procedure polar_angle_vector4
end interface
<<Lorentz: procedures>>=
elemental function polar_angle_vector3 (p) result (theta)
real(default) :: theta
type(vector3_t), intent(in) :: p
if (any (abs (p%p) > 0)) then
theta = atan2 (sqrt(p%p(1)**2 + p%p(2)**2), p%p(3))
else
theta = 0
end if
end function polar_angle_vector3
elemental function polar_angle_vector4 (p) result (theta)
real(default) :: theta
type(vector4_t), intent(in) :: p
theta = polar_angle (space_part (p))
end function polar_angle_vector4
@ %def polar_angle
@ This is the cosine of the polar angle: $-1\leq\cos\theta\leq 1$.
<<Lorentz: public functions>>=
public :: polar_angle_ct
<<Lorentz: interfaces>>=
interface polar_angle_ct
module procedure polar_angle_ct_vector3
module procedure polar_angle_ct_vector4
end interface
<<Lorentz: procedures>>=
elemental function polar_angle_ct_vector3 (p) result (ct)
real(default) :: ct
type(vector3_t), intent(in) :: p
if (any (abs (p%p) > 0)) then
ct = p%p(3) / p**1
else
ct = 1
end if
end function polar_angle_ct_vector3
elemental function polar_angle_ct_vector4 (p) result (ct)
real(default) :: ct
type(vector4_t), intent(in) :: p
ct = polar_angle_ct (space_part (p))
end function polar_angle_ct_vector4
@ %def polar_angle_ct
@ The polar angle in degrees.
<<Lorentz: public functions>>=
public :: polar_angle_deg
<<Lorentz: interfaces>>=
interface polar_angle_deg
module procedure polar_angle_deg_vector3
module procedure polar_angle_deg_vector4
end interface
<<Lorentz: procedures>>=
elemental function polar_angle_deg_vector3 (p) result (theta)
real(default) :: theta
type(vector3_t), intent(in) :: p
theta = polar_angle (p) / degree
end function polar_angle_deg_vector3
elemental function polar_angle_deg_vector4 (p) result (theta)
real(default) :: theta
type(vector4_t), intent(in) :: p
theta = polar_angle (p) / degree
end function polar_angle_deg_vector4
@ %def polar_angle_deg
@ This is the angle enclosed between two three-momenta. If one of the
momenta is zero, we return an angle of zero. The range of the result
is $0\leq\theta\leq\pi$. If there is only one argument, take the
positive $z$ axis as reference.
<<Lorentz: public functions>>=
public :: enclosed_angle
<<Lorentz: interfaces>>=
interface enclosed_angle
module procedure enclosed_angle_vector3
module procedure enclosed_angle_vector4
end interface
<<Lorentz: procedures>>=
elemental function enclosed_angle_vector3 (p, q) result (theta)
real(default) :: theta
type(vector3_t), intent(in) :: p, q
theta = acos (enclosed_angle_ct (p, q))
end function enclosed_angle_vector3
elemental function enclosed_angle_vector4 (p, q) result (theta)
real(default) :: theta
type(vector4_t), intent(in) :: p, q
theta = enclosed_angle (space_part (p), space_part (q))
end function enclosed_angle_vector4
@ %def enclosed_angle
@ The cosine of the enclosed angle.
<<Lorentz: public functions>>=
public :: enclosed_angle_ct
<<Lorentz: interfaces>>=
interface enclosed_angle_ct
module procedure enclosed_angle_ct_vector3
module procedure enclosed_angle_ct_vector4
end interface
<<Lorentz: procedures>>=
elemental function enclosed_angle_ct_vector3 (p, q) result (ct)
real(default) :: ct
type(vector3_t), intent(in) :: p, q
if (any (abs (p%p) > 0) .and. any (abs (q%p) > 0)) then
ct = p*q / (p**1 * q**1)
if (ct>1) then
ct = 1
else if (ct<-1) then
ct = -1
end if
else
ct = 1
end if
end function enclosed_angle_ct_vector3
elemental function enclosed_angle_ct_vector4 (p, q) result (ct)
real(default) :: ct
type(vector4_t), intent(in) :: p, q
ct = enclosed_angle_ct (space_part (p), space_part (q))
end function enclosed_angle_ct_vector4
@ %def enclosed_angle_ct
@ The enclosed angle in degrees.
<<Lorentz: public functions>>=
public :: enclosed_angle_deg
<<Lorentz: interfaces>>=
interface enclosed_angle_deg
module procedure enclosed_angle_deg_vector3
module procedure enclosed_angle_deg_vector4
end interface
<<Lorentz: procedures>>=
elemental function enclosed_angle_deg_vector3 (p, q) result (theta)
real(default) :: theta
type(vector3_t), intent(in) :: p, q
theta = enclosed_angle (p, q) / degree
end function enclosed_angle_deg_vector3
elemental function enclosed_angle_deg_vector4 (p, q) result (theta)
real(default) :: theta
type(vector4_t), intent(in) :: p, q
theta = enclosed_angle (p, q) / degree
end function enclosed_angle_deg_vector4
@ %def enclosed_angle
@ The polar angle of the first momentum w.r.t.\ the second momentum,
evaluated in the rest frame of the second momentum. If the second
four-momentum is not timelike, return zero.
<<Lorentz: public functions>>=
public :: enclosed_angle_rest_frame
public :: enclosed_angle_ct_rest_frame
public :: enclosed_angle_deg_rest_frame
<<Lorentz: interfaces>>=
interface enclosed_angle_rest_frame
module procedure enclosed_angle_rest_frame_vector4
end interface
interface enclosed_angle_ct_rest_frame
module procedure enclosed_angle_ct_rest_frame_vector4
end interface
interface enclosed_angle_deg_rest_frame
module procedure enclosed_angle_deg_rest_frame_vector4
end interface
<<Lorentz: procedures>>=
elemental function enclosed_angle_rest_frame_vector4 (p, q) result (theta)
type(vector4_t), intent(in) :: p, q
real(default) :: theta
theta = acos (enclosed_angle_ct_rest_frame (p, q))
end function enclosed_angle_rest_frame_vector4
elemental function enclosed_angle_ct_rest_frame_vector4 (p, q) result (ct)
type(vector4_t), intent(in) :: p, q
real(default) :: ct
if (invariant_mass(q) > 0) then
ct = enclosed_angle_ct ( &
space_part (boost(-q, invariant_mass (q)) * p), &
space_part (q))
else
ct = 1
end if
end function enclosed_angle_ct_rest_frame_vector4
elemental function enclosed_angle_deg_rest_frame_vector4 (p, q) &
result (theta)
type(vector4_t), intent(in) :: p, q
real(default) :: theta
theta = enclosed_angle_rest_frame (p, q) / degree
end function enclosed_angle_deg_rest_frame_vector4
@ %def enclosed_angle_rest_frame
@ %def enclosed_angle_ct_rest_frame
@ %def enclosed_angle_deg_rest_frame
@
\subsection{More kinematical functions (some redundant)}
The scalar transverse momentum (assuming the $z$ axis is longitudinal)
<<Lorentz: public functions>>=
public :: transverse_part
<<Lorentz: interfaces>>=
interface transverse_part
module procedure transverse_part_vector4_beam_axis
module procedure transverse_part_vector4_vector4
end interface
<<Lorentz: procedures>>=
elemental function transverse_part_vector4_beam_axis (p) result (pT)
real(default) :: pT
type(vector4_t), intent(in) :: p
pT = sqrt(p%p(1)**2 + p%p(2)**2)
end function transverse_part_vector4_beam_axis
elemental function transverse_part_vector4_vector4 (p1, p2) result (pT)
real(default) :: pT
type(vector4_t), intent(in) :: p1, p2
real(default) :: p1_norm, p2_norm, p1p2, pT2
p1_norm = space_part_norm(p1)**2
p2_norm = space_part_norm(p2)**2
! p1p2 = p1%p(1:3)*p2%p(1:3)
p1p2 = vector4_get_space_part(p1) * vector4_get_space_part(p2)
pT2 = (p1_norm*p2_norm - p1p2)/p1_norm
pT = sqrt (pT2)
end function transverse_part_vector4_vector4
@ %def transverse_part
@ The scalar longitudinal momentum (assuming the $z$ axis is
longitudinal). Identical to [[momentum_z_component]].
<<Lorentz: public functions>>=
public :: longitudinal_part
<<Lorentz: interfaces>>=
interface longitudinal_part
module procedure longitudinal_part_vector4
end interface
<<Lorentz: procedures>>=
elemental function longitudinal_part_vector4 (p) result (pL)
real(default) :: pL
type(vector4_t), intent(in) :: p
pL = p%p(3)
end function longitudinal_part_vector4
@ %def longitudinal_part
@ Absolute value of three-momentum
<<Lorentz: public functions>>=
public :: space_part_norm
<<Lorentz: interfaces>>=
interface space_part_norm
module procedure space_part_norm_vector4
end interface
<<Lorentz: procedures>>=
elemental function space_part_norm_vector4 (p) result (p3)
real(default) :: p3
type(vector4_t), intent(in) :: p
p3 = sqrt (p%p(1)**2 + p%p(2)**2 + p%p(3)**2)
end function space_part_norm_vector4
@ %def momentum
@ The energy (the zeroth component)
<<Lorentz: public functions>>=
public :: energy
<<Lorentz: interfaces>>=
interface energy
module procedure energy_vector4
module procedure energy_vector3
module procedure energy_real
end interface
<<Lorentz: procedures>>=
elemental function energy_vector4 (p) result (E)
real(default) :: E
type(vector4_t), intent(in) :: p
E = p%p(0)
end function energy_vector4
@ Alternative: The energy corresponding to a given momentum and mass.
If the mass is omitted, it is zero
<<Lorentz: procedures>>=
elemental function energy_vector3 (p, mass) result (E)
real(default) :: E
type(vector3_t), intent(in) :: p
real(default), intent(in), optional :: mass
if (present (mass)) then
E = sqrt (p**2 + mass**2)
else
E = p**1
end if
end function energy_vector3
elemental function energy_real (p, mass) result (E)
real(default) :: E
real(default), intent(in) :: p
real(default), intent(in), optional :: mass
if (present (mass)) then
E = sqrt (p**2 + mass**2)
else
E = abs (p)
end if
end function energy_real
@ %def energy
@ The invariant mass of four-momenta. Zero for lightlike, negative for
spacelike momenta.
<<Lorentz: public functions>>=
public :: invariant_mass
<<Lorentz: interfaces>>=
interface invariant_mass
module procedure invariant_mass_vector4
end interface
<<Lorentz: procedures>>=
elemental function invariant_mass_vector4 (p) result (m)
real(default) :: m
type(vector4_t), intent(in) :: p
real(default) :: msq
msq = p*p
if (msq >= 0) then
m = sqrt (msq)
else
m = - sqrt (abs (msq))
end if
end function invariant_mass_vector4
@ %def invariant_mass
@ The invariant mass squared. Zero for lightlike, negative for
spacelike momenta.
<<Lorentz: public functions>>=
public :: invariant_mass_squared
<<Lorentz: interfaces>>=
interface invariant_mass_squared
module procedure invariant_mass_squared_vector4
end interface
<<Lorentz: procedures>>=
elemental function invariant_mass_squared_vector4 (p) result (msq)
real(default) :: msq
type(vector4_t), intent(in) :: p
msq = p*p
end function invariant_mass_squared_vector4
@ %def invariant_mass_squared
@ The transverse mass. If the mass squared is negative, this value
also is negative.
<<Lorentz: public functions>>=
public :: transverse_mass
<<Lorentz: interfaces>>=
interface transverse_mass
module procedure transverse_mass_vector4
end interface
<<Lorentz: procedures>>=
elemental function transverse_mass_vector4 (p) result (m)
real(default) :: m
type(vector4_t), intent(in) :: p
real(default) :: msq
msq = p%p(0)**2 - p%p(1)**2 - p%p(2)**2
if (msq >= 0) then
m = sqrt (msq)
else
m = - sqrt (abs (msq))
end if
end function transverse_mass_vector4
@ %def transverse_mass
@ The rapidity (defined if particle is massive or $p_\perp>0$)
<<Lorentz: public functions>>=
public :: rapidity
<<Lorentz: interfaces>>=
interface rapidity
module procedure rapidity_vector4
end interface
<<Lorentz: procedures>>=
elemental function rapidity_vector4 (p) result (y)
real(default) :: y
type(vector4_t), intent(in) :: p
y = .5 * log( (energy (p) + longitudinal_part (p)) &
& /(energy (p) - longitudinal_part (p)))
end function rapidity_vector4
@ %def rapidity
@ The pseudorapidity (defined if $p_\perp>0$)
<<Lorentz: public functions>>=
public :: pseudorapidity
<<Lorentz: interfaces>>=
interface pseudorapidity
module procedure pseudorapidity_vector4
end interface
<<Lorentz: procedures>>=
elemental function pseudorapidity_vector4 (p) result (eta)
real(default) :: eta
type(vector4_t), intent(in) :: p
eta = -log( tan (.5 * polar_angle (p)))
end function pseudorapidity_vector4
@ %def pseudorapidity
@ The rapidity distance (defined if both $p_\perp>0$)
<<Lorentz: public functions>>=
public :: rapidity_distance
<<Lorentz: interfaces>>=
interface rapidity_distance
module procedure rapidity_distance_vector4
end interface
<<Lorentz: procedures>>=
elemental function rapidity_distance_vector4 (p, q) result (dy)
type(vector4_t), intent(in) :: p, q
real(default) :: dy
dy = rapidity (q) - rapidity (p)
end function rapidity_distance_vector4
@ %def rapidity_distance
@ The pseudorapidity distance (defined if both $p_\perp>0$)
<<Lorentz: public functions>>=
public :: pseudorapidity_distance
<<Lorentz: interfaces>>=
interface pseudorapidity_distance
module procedure pseudorapidity_distance_vector4
end interface
<<Lorentz: procedures>>=
elemental function pseudorapidity_distance_vector4 (p, q) result (deta)
real(default) :: deta
type(vector4_t), intent(in) :: p, q
deta = pseudorapidity (q) - pseudorapidity (p)
end function pseudorapidity_distance_vector4
@ %def pseudorapidity_distance
@ The distance on the $\eta-\phi$ cylinder:
<<Lorentz: public functions>>=
public :: eta_phi_distance
<<Lorentz: interfaces>>=
interface eta_phi_distance
module procedure eta_phi_distance_vector4
end interface
<<Lorentz: procedures>>=
elemental function eta_phi_distance_vector4 (p, q) result (dr)
type(vector4_t), intent(in) :: p, q
real(default) :: dr
dr = sqrt ( &
pseudorapidity_distance (p, q)**2 &
+ azimuthal_distance (p, q)**2)
end function eta_phi_distance_vector4
@ %def eta_phi_distance
@
\subsection{Lorentz transformations}
<<Lorentz: public>>=
public :: lorentz_transformation_t
<<Lorentz: types>>=
type :: lorentz_transformation_t
private
real(default), dimension(0:3, 0:3) :: L
contains
<<Lorentz: lorentz transformation: TBP>>
end type lorentz_transformation_t
@ %def lorentz_transformation_t
@ Output:
<<Lorentz: public>>=
public :: lorentz_transformation_write
<<Lorentz: lorentz transformation: TBP>>=
procedure :: write => lorentz_transformation_write
<<Lorentz: procedures>>=
subroutine lorentz_transformation_write (L, unit, testflag, ultra)
class(lorentz_transformation_t), intent(in) :: L
integer, intent(in), optional :: unit
logical, intent(in), optional :: testflag, ultra
integer :: u, i
logical :: ult
character(len=7) :: fmt
ult = .false.; if (present (ultra)) ult = ultra
if (ult) then
call pac_fmt (fmt, FMT_19, FMT_11, ultra)
else
call pac_fmt (fmt, FMT_19, FMT_13, testflag)
end if
u = given_output_unit (unit); if (u < 0) return
write (u, "(1x,A,3(1x," // fmt // "))") "L00 = ", L%L(0,0)
write (u, "(1x,A,3(1x," // fmt // "))") "L0j = ", L%L(0,1:3)
do i = 1, 3
write (u, "(1x,A,I0,A,3(1x," // fmt // "))") &
"L", i, "0 = ", L%L(i,0)
write (u, "(1x,A,I0,A,3(1x," // fmt // "))") &
"L", i, "j = ", L%L(i,1:3)
end do
end subroutine lorentz_transformation_write
@ %def lorentz_transformation_write
@ Extract all components:
<<Lorentz: public>>=
public :: lorentz_transformation_get_components
<<Lorentz: procedures>>=
pure function lorentz_transformation_get_components (L) result (a)
type(lorentz_transformation_t), intent(in) :: L
real(default), dimension(0:3,0:3) :: a
a = L%L
end function lorentz_transformation_get_components
@ %def lorentz_transformation_get_components
@
\subsection{Functions of Lorentz transformations}
For the inverse, we make use of the fact that
$\Lambda^{\mu\nu}\Lambda_{\mu\rho}=\delta^\nu_\rho$. So, lowering the
indices and transposing is sufficient.
<<Lorentz: public functions>>=
public :: inverse
<<Lorentz: interfaces>>=
interface inverse
module procedure lorentz_transformation_inverse
end interface
<<Lorentz: procedures>>=
elemental function lorentz_transformation_inverse (L) result (IL)
type(lorentz_transformation_t) :: IL
type(lorentz_transformation_t), intent(in) :: L
IL%L(0,0) = L%L(0,0)
IL%L(0,1:) = -L%L(1:,0)
IL%L(1:,0) = -L%L(0,1:)
IL%L(1:,1:) = transpose(L%L(1:,1:))
end function lorentz_transformation_inverse
@ %def lorentz_transformation_inverse
@ %def inverse
@
\subsection{Invariants}
These are used below. The first array index is varying fastest in
[[FORTRAN]]; therefore the extra minus in the odd-rank tensor
epsilon.
<<Lorentz: parameters>>=
integer, dimension(3,3), parameter :: delta_three = &
& reshape( source = [ 1,0,0, 0,1,0, 0,0,1 ], &
& shape = [3,3] )
integer, dimension(3,3,3), parameter :: epsilon_three = &
& reshape( source = [ 0, 0,0, 0,0,-1, 0,1,0, &
& 0, 0,1, 0,0, 0, -1,0,0, &
& 0,-1,0, 1,0, 0, 0,0,0 ],&
& shape = [3,3,3] )
@ %def delta_three epsilon_three
@ This could be of some use:
<<Lorentz: public>>=
public :: identity
<<Lorentz: parameters>>=
type(lorentz_transformation_t), parameter :: &
& identity = &
& lorentz_transformation_t ( &
& reshape( source = [ one, zero, zero, zero, &
& zero, one, zero, zero, &
& zero, zero, one, zero, &
& zero, zero, zero, one ],&
& shape = [4,4] ) )
@ %def identity
<<Lorentz: public>>=
public :: space_reflection
<<Lorentz: parameters>>=
type(lorentz_transformation_t), parameter :: &
& space_reflection = &
& lorentz_transformation_t ( &
& reshape( source = [ one, zero, zero, zero, &
& zero,-one, zero, zero, &
& zero, zero,-one, zero, &
& zero, zero, zero,-one ],&
& shape = [4,4] ) )
@ %def space_reflection
@ Builds a unit vector orthogal to the input vector in the xy-plane.
<<Lorentz: public functions>>=
public :: create_orthogonal
<<Lorentz: procedures>>=
function create_orthogonal (p_in) result (p_out)
type(vector3_t), intent(in) :: p_in
type(vector3_t) :: p_out
real(default) :: ab
ab = sqrt (p_in%p(1)**2 + p_in%p(2)**2)
if (abs (ab) < eps0) then
p_out%p(1) = 1
p_out%p(2) = 0
p_out%p(3) = 0
else
p_out%p(1) = p_in%p(2)
p_out%p(2) = -p_in%p(1)
p_out%p(3) = 0
p_out = p_out / ab
end if
end function create_orthogonal
@ %def create_orthogonal
@
<<Lorentz: public functions>>=
public :: create_unit_vector
<<Lorentz: procedures>>=
function create_unit_vector (p_in) result (p_out)
type(vector4_t), intent(in) :: p_in
type(vector3_t) :: p_out
p_out%p = p_in%p(1:3) / space_part_norm (p_in)
end function create_unit_vector
@ %def create_unit_vector
@
<<Lorentz: public functions>>=
public :: normalize
<<Lorentz: procedures>>=
function normalize(p) result (p_norm)
type(vector3_t) :: p_norm
type(vector3_t), intent(in) :: p
real(default) :: abs
abs = sqrt (p%p(1)**2 + p%p(2)**2 + p%p(3)**2)
p_norm = p / abs
end function normalize
@ %def normalize
@ Computes the invariant mass of the momenta sum given by the indices in
[[i_res_born]] and the optional argument [[i_emitter]].
<<Lorentz: public>>=
public :: compute_resonance_mass
<<Lorentz: procedures>>=
pure function compute_resonance_mass (p, i_res_born, i_gluon) result (m)
real(default) :: m
type(vector4_t), intent(in), dimension(:) :: p
integer, intent(in), dimension(:) :: i_res_born
integer, intent(in), optional :: i_gluon
type(vector4_t) :: p_res
p_res = get_resonance_momentum (p, i_res_born, i_gluon)
m = p_res**1
end function compute_resonance_mass
@ %def compute_resonance_mass
@
<<Lorentz: public>>=
public :: get_resonance_momentum
<<Lorentz: procedures>>=
pure function get_resonance_momentum (p, i_res_born, i_gluon) result (p_res)
type(vector4_t) :: p_res
type(vector4_t), intent(in), dimension(:) :: p
integer, intent(in), dimension(:) :: i_res_born
integer, intent(in), optional :: i_gluon
integer :: i
p_res = vector4_null
do i = 1, size (i_res_born)
p_res = p_res + p (i_res_born(i))
end do
if (present (i_gluon)) p_res = p_res + p (i_gluon)
end function get_resonance_momentum
@ %def get_resonance_momentum
@
<<Lorentz: public>>=
public :: create_two_particle_decay
<<Lorentz: procedures>>=
function create_two_particle_decay (s, p1, p2) result (p_rest)
type(vector4_t), dimension(3) :: p_rest
real(default), intent(in) :: s
type(vector4_t), intent(in) :: p1, p2
real(default) :: m1_sq, m2_sq
real(default) :: E1, E2, p
m1_sq = p1**2; m2_sq = p2**2
p = sqrt (lambda (s, m1_sq, m2_sq)) / (two * sqrt (s))
E1 = sqrt (m1_sq + p**2); E2 = sqrt (m2_sq + p**2)
p_rest(1)%p = [sqrt (s), zero, zero, zero]
p_rest(2)%p(0) = E1
p_rest(2)%p(1:3) = p * p1%p(1:3) / space_part_norm (p1)
p_rest(3)%p(0) = E2; p_rest(3)%p(1:3) = -p_rest(2)%p(1:3)
end function create_two_particle_decay
@ %def create_two_particle_decay
@ This function creates a phase-space point for a $1 \to 3$ decay in
the decaying particle's rest frame. There are three rest frames for
this system, corresponding to $s$-, $t$,- and $u$-channel momentum
exchange, also referred to as Gottfried-Jackson frames. Below, we choose
the momentum with index 1 to be aligned along the $z$-axis. We then
have
\begin{align*}
s_1 &= \left(p_1 + p_2\right)^2, \\
s_2 &= \left(p_2 + p_3\right)^2, \\
s_3 &= \left(p_1 + p_3\right)^2, \\
s_1 + s_2 + s_3 &= s + m_1^2 + m_2^2 + m_3^2.
\end{align*}
From these we can construct
\begin{align*}
E_1^{R23} = \frac{s - s_2 - m_1^2}{2\sqrt{s_2}} &\quad P_1^{R23} = \frac{\lambda^{1/2}(s, s_2, m_1^2)}{2\sqrt{s_2}},\\
E_2^{R23} = \frac{s_2 + m_2^2 - m_3^2}{2\sqrt{s_2}} &\quad P_2^{R23} = \frac{\lambda^{1/2}(s_2, m_2^2, m_3^2)}{2\sqrt{s_2}},\\
E_3^{R23} = \frac{s_2 + m_3^2 - m_2^2}{2\sqrt{s_2}} &\quad P_3^{R23} = P_2^{R23},
\end{align*}
where $R23$ denotes the Gottfried-Jackson frame of our choice. Finally, the scattering angle $\theta_{12}^{R23}$ between
momentum $1$ and $2$ can be determined to be
\begin{equation*}
\cos\theta_{12}^{R23} = \frac{(s - s_2 - m_1^2)(s_2 + m_2^2 - m_3^2) + 2s_2 (m_1^2 + m_2^2 - s_1)}
{\lambda^{1/2}(s, s_2, m_1^2) \lambda^{1/2}(s_2, m_2^2, m_3^2)}
\end{equation*}
<<Lorentz: public>>=
public :: create_three_particle_decay
<<Lorentz: procedures>>=
function create_three_particle_decay (p1, p2, p3) result (p_rest)
type(vector4_t), dimension(4) :: p_rest
type(vector4_t), intent(in) :: p1, p2, p3
real(default) :: E1, E2, E3
real(default) :: pr1, pr2, pr3
real(default) :: s, s1, s2, s3
real(default) :: m1_sq, m2_sq, m3_sq
real(default) :: cos_theta_12
type(vector3_t) :: v3_unit
type(lorentz_transformation_t) :: rot
m1_sq = p1**2
m2_sq = p2**2
m3_sq = p3**2
s1 = (p1 + p2)**2
s2 = (p2 + p3)**2
s3 = (p3 + p1)**2
s = s1 + s2 + s3 - m1_sq - m2_sq - m3_sq
E1 = (s - s2 - m1_sq) / (two * sqrt (s2))
E2 = (s2 + m2_sq - m3_sq) / (two * sqrt (s2))
E3 = (s2 + m3_sq - m2_sq) / (two * sqrt (s2))
pr1 = sqrt (lambda (s, s2, m1_sq)) / (two * sqrt (s2))
pr2 = sqrt (lambda (s2, m2_sq, m3_sq)) / (two * sqrt(s2))
pr3 = pr2
cos_theta_12 = ((s - s2 - m1_sq) * (s2 + m2_sq - m3_sq) + two * s2 * (m1_sq + m2_sq - s1)) / &
sqrt (lambda (s, s2, m1_sq) * lambda (s2, m2_sq, m3_sq))
v3_unit%p = [zero, zero, one]
p_rest(1)%p(0) = E1
p_rest(1)%p(1:3) = v3_unit%p * pr1
p_rest(2)%p(0) = E2
p_rest(2)%p(1:3) = v3_unit%p * pr2
p_rest(3)%p(0) = E3
p_rest(3)%p(1:3) = v3_unit%p * pr3
p_rest(4)%p(0) = (s + s2 - m1_sq) / (2 * sqrt (s2))
p_rest(4)%p(1:3) = - p_rest(1)%p(1:3)
rot = rotation (cos_theta_12, sqrt (one - cos_theta_12**2), 2)
p_rest(2) = rot * p_rest(2)
p_rest(3)%p(1:3) = - p_rest(2)%p(1:3)
end function create_three_particle_decay
@ %def create_three_particle_decay
@
<<Lorentz: public>>=
public :: evaluate_one_to_two_splitting_special
<<Lorentz: interfaces>>=
abstract interface
subroutine evaluate_one_to_two_splitting_special (p_origin, &
p1_in, p2_in, p1_out, p2_out, msq_in, jac)
import
type(vector4_t), intent(in) :: p_origin
type(vector4_t), intent(in) :: p1_in, p2_in
type(vector4_t), intent(inout) :: p1_out, p2_out
real(default), intent(in), optional :: msq_in
real(default), intent(inout), optional :: jac
end subroutine evaluate_one_to_two_splitting_special
end interface
@ %def evaluate_one_to_two_splitting_special
@
<<Lorentz: public>>=
public :: generate_on_shell_decay
<<Lorentz: procedures>>=
recursive subroutine generate_on_shell_decay (p_dec, &
p_in, p_out, i_real, msq_in, jac, evaluate_special)
type(vector4_t), intent(in) :: p_dec
type(vector4_t), intent(in), dimension(:) :: p_in
type(vector4_t), intent(inout), dimension(:) :: p_out
integer, intent(in) :: i_real
real(default), intent(in), optional :: msq_in
real(default), intent(inout), optional :: jac
procedure(evaluate_one_to_two_splitting_special), intent(in), &
pointer, optional :: evaluate_special
type(vector4_t) :: p_dec_new
integer :: n_recoil
n_recoil = size (p_in) - 1
if (n_recoil > 1) then
if (present (evaluate_special)) then
call evaluate_special (p_dec, p_in(1), sum (p_in (2 : n_recoil + 1)), &
p_out(i_real), p_dec_new)
call generate_on_shell_decay (p_dec_new, p_in (2 : ), p_out, &
i_real + 1, msq_in, jac, evaluate_special)
else
call evaluate_one_to_two_splitting (p_dec, p_in(1), &
sum (p_in (2 : n_recoil + 1)), p_out(i_real), p_dec_new, msq_in, jac)
call generate_on_shell_decay (p_dec_new, p_in (2 : ), p_out, &
i_real + 1, msq_in, jac)
end if
else
call evaluate_one_to_two_splitting (p_dec, p_in(1), p_in(2), &
p_out(i_real), p_out(i_real + 1), msq_in, jac)
end if
end subroutine generate_on_shell_decay
subroutine evaluate_one_to_two_splitting (p_origin, &
p1_in, p2_in, p1_out, p2_out, msq_in, jac)
type(vector4_t), intent(in) :: p_origin
type(vector4_t), intent(in) :: p1_in, p2_in
type(vector4_t), intent(inout) :: p1_out, p2_out
real(default), intent(in), optional :: msq_in
real(default), intent(inout), optional :: jac
type(lorentz_transformation_t) :: L
type(vector4_t) :: p1_rest, p2_rest
real(default) :: m, msq, msq1, msq2
real(default) :: E1, E2, p
real(default) :: lda, rlda_soft
call get_rest_frame (p1_in, p2_in, p1_rest, p2_rest)
msq = p_origin**2; m = sqrt(msq)
msq1 = p1_in**2; msq2 = p2_in**2
lda = lambda (msq, msq1, msq2)
if (lda < zero) then
print *, 'Encountered lambda < 0 in 1 -> 2 splitting! '
print *, 'lda: ', lda
print *, 'm: ', m, 'msq: ', msq
print *, 'm1: ', sqrt (msq1), 'msq1: ', msq1
print *, 'm2: ', sqrt (msq2), 'msq2: ', msq2
stop
end if
p = sqrt (lda) / (two * m)
E1 = sqrt (msq1 + p**2)
E2 = sqrt (msq2 + p**2)
p1_out = shift_momentum (p1_rest, E1, p)
p2_out = shift_momentum (p2_rest, E2, p)
L = boost (p_origin, p_origin**1)
p1_out = L * p1_out
p2_out = L * p2_out
if (present (jac) .and. present (msq_in)) then
jac = jac * sqrt(lda) / msq
rlda_soft = sqrt (lambda (msq_in, msq1, msq2))
!!! We have to undo the Jacobian which has already been
!!! supplied by the Born phase space.
jac = jac * msq_in / rlda_soft
end if
contains
subroutine get_rest_frame (p1_in, p2_in, p1_out, p2_out)
type(vector4_t), intent(in) :: p1_in, p2_in
type(vector4_t), intent(out) :: p1_out, p2_out
type(lorentz_transformation_t) :: L
L = inverse (boost (p1_in + p2_in, (p1_in + p2_in)**1))
p1_out = L * p1_in; p2_out = L * p2_in
end subroutine get_rest_frame
function shift_momentum (p_in, E, p) result (p_out)
type(vector4_t) :: p_out
type(vector4_t), intent(in) :: p_in
real(default), intent(in) :: E, p
type(vector3_t) :: vec
vec = p_in%p(1:3) / space_part_norm (p_in)
p_out = vector4_moving (E, p * vec)
end function shift_momentum
end subroutine evaluate_one_to_two_splitting
@ %def generate_on_shell_decay
@
\subsection{Boosts}
We build Lorentz transformations from boosts and rotations. In both
cases we can supply a three-vector which defines the axis and (hyperbolic)
angle. For a boost, this is the vector $\vec\beta=\vec p/E$,
such that a particle at rest with mass $m$ is boosted to a particle
with three-vector $\vec p$. Here, we have
\begin{equation}
\beta = \tanh\chi = p/E, \qquad
\gamma = \cosh\chi = E/m, \qquad
\beta\gamma = \sinh\chi = p/m
\end{equation}
<<Lorentz: public functions>>=
public :: boost
<<Lorentz: interfaces>>=
interface boost
module procedure boost_from_rest_frame
module procedure boost_from_rest_frame_vector3
module procedure boost_generic
module procedure boost_canonical
end interface
@ %def boost
@ In the first form, the argument is some four-momentum, the space
part of which determines a direction, and the associated mass (which
is not checked against the four-momentum). The boost vector
$\gamma\vec\beta$ is then given by $\vec p/m$. This boosts from the
rest frame of a particle to the current frame. To be explicit, if
$\vec p$ is the momentum of a particle and $m$ its mass, $L(\vec p/m)$
is the transformation that turns $(m;\vec 0)$ into $(E;\vec p)$.
Conversely, the inverse transformation boosts a vector \emph{into} the
rest frame of a particle, in particular $(E;\vec p)$ into $(m;\vec
0)$.
<<Lorentz: procedures>>=
elemental function boost_from_rest_frame (p, m) result (L)
type(lorentz_transformation_t) :: L
type(vector4_t), intent(in) :: p
real(default), intent(in) :: m
L = boost_from_rest_frame_vector3 (space_part (p), m)
end function boost_from_rest_frame
elemental function boost_from_rest_frame_vector3 (p, m) result (L)
type(lorentz_transformation_t) :: L
type(vector3_t), intent(in) :: p
real(default), intent(in) :: m
type(vector3_t) :: beta_gamma
real(default) :: bg2, g, c
integer :: i,j
if (m > eps0) then
beta_gamma = p / m
bg2 = beta_gamma**2
else
bg2 = 0
L = identity
return
end if
if (bg2 > eps0) then
g = sqrt(1 + bg2); c = (g-1)/bg2
else
g = one + bg2 / two
c = one / two
end if
L%L(0,0) = g
L%L(0,1:) = beta_gamma%p
L%L(1:,0) = L%L(0,1:)
do i=1,3
do j=1,3
L%L(i,j) = delta_three(i,j) + c*beta_gamma%p(i)*beta_gamma%p(j)
end do
end do
end function boost_from_rest_frame_vector3
@ %def boost_from_rest_frame
@ A canonical boost is a boost along one of the coordinate axes, which
we may supply as an integer argument. Here, $\gamma\beta$ is scalar.
<<Lorentz: procedures>>=
elemental function boost_canonical (beta_gamma, k) result (L)
type(lorentz_transformation_t) :: L
real(default), intent(in) :: beta_gamma
integer, intent(in) :: k
real(default) :: g
g = sqrt(1 + beta_gamma**2)
L = identity
L%L(0,0) = g
L%L(0,k) = beta_gamma
L%L(k,0) = L%L(0,k)
L%L(k,k) = L%L(0,0)
end function boost_canonical
@ %def boost_canonical
@ Instead of a canonical axis, we can supply an arbitrary axis which
need not be normalized. If it is zero, return the unit matrix.
<<Lorentz: procedures>>=
elemental function boost_generic (beta_gamma, axis) result (L)
type(lorentz_transformation_t) :: L
real(default), intent(in) :: beta_gamma
type(vector3_t), intent(in) :: axis
if (any (abs (axis%p) > 0)) then
L = boost_from_rest_frame_vector3 (beta_gamma * axis, axis**1)
else
L = identity
end if
end function boost_generic
@ %def boost_generic
@
\subsection{Rotations}
For a rotation, the vector defines the rotation axis, and its length
the rotation angle.
<<Lorentz: public functions>>=
public :: rotation
<<Lorentz: interfaces>>=
interface rotation
module procedure rotation_generic
module procedure rotation_canonical
module procedure rotation_generic_cs
module procedure rotation_canonical_cs
end interface
@ %def rotation
@ If $\cos\phi$ and $\sin\phi$ is already known, we do not have to
calculate them. Of course, the user has to ensure that
$\cos^2\phi+\sin^2\phi=1$, and that the given axis [[n]] is normalized to
one. In the second form, the length of [[axis]] is the rotation
angle.
<<Lorentz: procedures>>=
elemental function rotation_generic_cs (cp, sp, axis) result (R)
type(lorentz_transformation_t) :: R
real(default), intent(in) :: cp, sp
type(vector3_t), intent(in) :: axis
integer :: i,j
R = identity
do i=1,3
do j=1,3
R%L(i,j) = cp*delta_three(i,j) + (1-cp)*axis%p(i)*axis%p(j) &
& - sp*dot_product(epsilon_three(i,j,:), axis%p)
end do
end do
end function rotation_generic_cs
elemental function rotation_generic (axis) result (R)
type(lorentz_transformation_t) :: R
type(vector3_t), intent(in) :: axis
real(default) :: phi
if (any (abs(axis%p) > 0)) then
phi = abs(axis**1)
R = rotation_generic_cs (cos(phi), sin(phi), axis/phi)
else
R = identity
end if
end function rotation_generic
@ %def rotation_generic_cs rotation_generic
@ Alternatively, give just the angle and label the coordinate axis by
an integer.
<<Lorentz: procedures>>=
elemental function rotation_canonical_cs (cp, sp, k) result (R)
type(lorentz_transformation_t) :: R
real(default), intent(in) :: cp, sp
integer, intent(in) :: k
integer :: i,j
R = identity
do i=1,3
do j=1,3
R%L(i,j) = -sp*epsilon_three(i,j,k)
end do
R%L(i,i) = cp
end do
R%L(k,k) = 1
end function rotation_canonical_cs
elemental function rotation_canonical (phi, k) result (R)
type(lorentz_transformation_t) :: R
real(default), intent(in) :: phi
integer, intent(in) :: k
R = rotation_canonical_cs(cos(phi), sin(phi), k)
end function rotation_canonical
@ %def rotation_canonical_cs rotation_canonical
@
This is viewed as a method for the first argument (three-vector):
Reconstruct the rotation that rotates it into the second three-vector.
<<Lorentz: public functions>>=
public :: rotation_to_2nd
<<Lorentz: interfaces>>=
interface rotation_to_2nd
module procedure rotation_to_2nd_generic
module procedure rotation_to_2nd_canonical
end interface
<<Lorentz: procedures>>=
elemental function rotation_to_2nd_generic (p, q) result (R)
type(lorentz_transformation_t) :: R
type(vector3_t), intent(in) :: p, q
type(vector3_t) :: a, b, ab
real(default) :: ct, st
if (any (abs (p%p) > 0) .and. any (abs (q%p) > 0)) then
a = direction (p)
b = direction (q)
ab = cross_product(a,b)
ct = a * b; st = ab**1
if (abs(st) > eps0) then
R = rotation_generic_cs (ct, st, ab / st)
else if (ct < 0) then
R = space_reflection
else
R = identity
end if
else
R = identity
end if
end function rotation_to_2nd_generic
@ %def rotation_to_2nd_generic
@
The same for a canonical axis: The function returns the transformation that
rotates the $k$-axis into the direction of $p$.
<<Lorentz: procedures>>=
elemental function rotation_to_2nd_canonical (k, p) result (R)
type(lorentz_transformation_t) :: R
integer, intent(in) :: k
type(vector3_t), intent(in) :: p
type(vector3_t) :: b, ab
real(default) :: ct, st
integer :: i, j
if (any (abs (p%p) > 0)) then
b = direction (p)
ab%p = 0
do i = 1, 3
do j = 1, 3
ab%p(j) = ab%p(j) + b%p(i) * epsilon_three(i,j,k)
end do
end do
ct = b%p(k); st = ab**1
if (abs(st) > eps0) then
R = rotation_generic_cs (ct, st, ab / st)
else if (ct < 0) then
R = space_reflection
else
R = identity
end if
else
R = identity
end if
end function rotation_to_2nd_canonical
@ %def rotation_to_2nd_canonical
@
\subsection{Composite Lorentz transformations}
This function returns the transformation that, given a pair of vectors
$p_{1,2}$, (a) boosts from the rest frame of the c.m. system (with
invariant mass $m$) into the lab frame where $p_i$ are defined, and
(b) turns the given axis (or the canonical vectors $\pm
e_k$) in the rest frame into the directions of $p_{1,2}$ in the lab frame.
Note that the energy components are not used; for a
consistent result one should have $(p_1+p_2)^2 = m^2$.
<<Lorentz: public functions>>=
public :: transformation
<<Lorentz: interfaces>>=
interface transformation
module procedure transformation_rec_generic
module procedure transformation_rec_canonical
end interface
@ %def transformation
<<Lorentz: procedures>>=
elemental function transformation_rec_generic (axis, p1, p2, m) result (L)
type(vector3_t), intent(in) :: axis
type(vector4_t), intent(in) :: p1, p2
real(default), intent(in) :: m
type(lorentz_transformation_t) :: L
L = boost (p1 + p2, m)
L = L * rotation_to_2nd (axis, space_part (inverse (L) * p1))
end function transformation_rec_generic
elemental function transformation_rec_canonical (k, p1, p2, m) result (L)
integer, intent(in) :: k
type(vector4_t), intent(in) :: p1, p2
real(default), intent(in) :: m
type(lorentz_transformation_t) :: L
L = boost (p1 + p2, m)
L = L * rotation_to_2nd (k, space_part (inverse (L) * p1))
end function transformation_rec_canonical
@ %def transformation_rec_generic transformation_rec_canonical
@
\subsection{Applying Lorentz transformations}
Multiplying vectors and Lorentz transformations is straightforward.
<<Lorentz: interfaces>>=
interface operator(*)
module procedure prod_LT_vector4
module procedure prod_LT_LT
module procedure prod_vector4_LT
end interface
<<Lorentz: procedures>>=
elemental function prod_LT_vector4 (L, p) result (np)
type(vector4_t) :: np
type(lorentz_transformation_t), intent(in) :: L
type(vector4_t), intent(in) :: p
np%p = matmul (L%L, p%p)
end function prod_LT_vector4
elemental function prod_LT_LT (L1, L2) result (NL)
type(lorentz_transformation_t) :: NL
type(lorentz_transformation_t), intent(in) :: L1,L2
NL%L = matmul (L1%L, L2%L)
end function prod_LT_LT
elemental function prod_vector4_LT (p, L) result (np)
type(vector4_t) :: np
type(vector4_t), intent(in) :: p
type(lorentz_transformation_t), intent(in) :: L
np%p = matmul (p%p, L%L)
end function prod_vector4_LT
@ %def *
@
\subsection{Special Lorentz transformations}
These routines have their application in the generation and extraction
of angles in the phase-space sampling routine. Since this part of the
program is time-critical, we calculate the composition of
transformations directly instead of multiplying rotations and boosts.
This Lorentz transformation is the composition of a rotation by $\phi$
around the $3$ axis, a rotation by $\theta$ around the $2$ axis, and a
boost along the $3$ axis:
\begin{equation}
L = B_3(\beta\gamma)\,R_2(\theta)\,R_3(\phi)
\end{equation}
Instead of the angles we provide sine and cosine.
<<Lorentz: public functions>>=
public :: LT_compose_r3_r2_b3
<<Lorentz: procedures>>=
elemental function LT_compose_r3_r2_b3 &
(cp, sp, ct, st, beta_gamma) result (L)
type(lorentz_transformation_t) :: L
real(default), intent(in) :: cp, sp, ct, st, beta_gamma
real(default) :: gamma
if (abs(beta_gamma) < eps0) then
L%L(0,0) = 1
L%L(1:,0) = 0
L%L(0,1:) = 0
L%L(1,1:) = [ ct*cp, -ct*sp, st ]
L%L(2,1:) = [ sp, cp, zero ]
L%L(3,1:) = [ -st*cp, st*sp, ct ]
else
gamma = sqrt(1 + beta_gamma**2)
L%L(0,0) = gamma
L%L(1,0) = 0
L%L(2,0) = 0
L%L(3,0) = beta_gamma
L%L(0,1:) = beta_gamma * [ -st*cp, st*sp, ct ]
L%L(1,1:) = [ ct*cp, -ct*sp, st ]
L%L(2,1:) = [ sp, cp, zero ]
L%L(3,1:) = gamma * [ -st*cp, st*sp, ct ]
end if
end function LT_compose_r3_r2_b3
@ %def LT_compose_r3_r2_b3
@ Different ordering:
\begin{equation}
L = B_3(\beta\gamma)\,R_3(\phi)\,R_2(\theta)
\end{equation}
<<Lorentz: public functions>>=
public :: LT_compose_r2_r3_b3
<<Lorentz: procedures>>=
elemental function LT_compose_r2_r3_b3 &
(ct, st, cp, sp, beta_gamma) result (L)
type(lorentz_transformation_t) :: L
real(default), intent(in) :: ct, st, cp, sp, beta_gamma
real(default) :: gamma
if (abs(beta_gamma) < eps0) then
L%L(0,0) = 1
L%L(1:,0) = 0
L%L(0,1:) = 0
L%L(1,1:) = [ ct*cp, -sp, st*cp ]
L%L(2,1:) = [ ct*sp, cp, st*sp ]
L%L(3,1:) = [ -st , zero, ct ]
else
gamma = sqrt(1 + beta_gamma**2)
L%L(0,0) = gamma
L%L(1,0) = 0
L%L(2,0) = 0
L%L(3,0) = beta_gamma
L%L(0,1:) = beta_gamma * [ -st , zero, ct ]
L%L(1,1:) = [ ct*cp, -sp, st*cp ]
L%L(2,1:) = [ ct*sp, cp, st*sp ]
L%L(3,1:) = gamma * [ -st , zero, ct ]
end if
end function LT_compose_r2_r3_b3
@ %def LT_compose_r2_r3_b3
@ This function returns the previous Lorentz transformation applied to
an arbitrary four-momentum and extracts the space part of the result:
\begin{equation}
\vec n = [B_3(\beta\gamma)\,R_2(\theta)\,R_3(\phi)\,p]_{\rm space\ part}
\end{equation}
The second variant applies if there is no rotation
<<Lorentz: public functions>>=
public :: axis_from_p_r3_r2_b3, axis_from_p_b3
<<Lorentz: procedures>>=
elemental function axis_from_p_r3_r2_b3 &
(p, cp, sp, ct, st, beta_gamma) result (n)
type(vector3_t) :: n
type(vector4_t), intent(in) :: p
real(default), intent(in) :: cp, sp, ct, st, beta_gamma
real(default) :: gamma, px, py
px = cp * p%p(1) - sp * p%p(2)
py = sp * p%p(1) + cp * p%p(2)
n%p(1) = ct * px + st * p%p(3)
n%p(2) = py
n%p(3) = -st * px + ct * p%p(3)
if (abs(beta_gamma) > eps0) then
gamma = sqrt(1 + beta_gamma**2)
n%p(3) = n%p(3) * gamma + p%p(0) * beta_gamma
end if
end function axis_from_p_r3_r2_b3
elemental function axis_from_p_b3 (p, beta_gamma) result (n)
type(vector3_t) :: n
type(vector4_t), intent(in) :: p
real(default), intent(in) :: beta_gamma
real(default) :: gamma
n%p = p%p(1:3)
if (abs(beta_gamma) > eps0) then
gamma = sqrt(1 + beta_gamma**2)
n%p(3) = n%p(3) * gamma + p%p(0) * beta_gamma
end if
end function axis_from_p_b3
@ %def axis_from_p_r3_r2_b3 axis_from_p_b3
@
\subsection{Special functions}
The K\"all\'en function, mostly used for the phase space.
This is equivalent to $\lambda(x,y,z)=x^2+y^2+z^2-2xy-2xz-2yz$.
<<Lorentz: public functions>>=
public :: lambda
<<Lorentz: procedures>>=
elemental function lambda (m1sq, m2sq, m3sq)
real(default) :: lambda
real(default), intent(in) :: m1sq, m2sq, m3sq
lambda = (m1sq - m2sq - m3sq)**2 - 4*m2sq*m3sq
end function lambda
@ %def lambda
@ Return a pair of head-to-head colliding momenta, given the collider
energy, particle masses, and optionally the momentum of the
c.m. system.
<<Lorentz: public functions>>=
public :: colliding_momenta
<<Lorentz: procedures>>=
function colliding_momenta (sqrts, m, p_cm) result (p)
type(vector4_t), dimension(2) :: p
real(default), intent(in) :: sqrts
real(default), dimension(2), intent(in), optional :: m
real(default), intent(in), optional :: p_cm
real(default), dimension(2) :: dmsq
real(default) :: ch, sh
real(default), dimension(2) :: E0, p0
integer, dimension(2), parameter :: sgn = [1, -1]
if (abs(sqrts) < eps0) then
call msg_fatal (" Colliding beams: sqrts is zero (please set sqrts)")
p = vector4_null; return
else if (sqrts <= 0) then
call msg_fatal (" Colliding beams: sqrts is negative")
p = vector4_null; return
end if
if (present (m)) then
dmsq = sgn * (m(1)**2-m(2)**2)
E0 = (sqrts + dmsq/sqrts) / 2
if (any (E0 < m)) then
call msg_fatal &
(" Colliding beams: beam energy is less than particle mass")
p = vector4_null; return
end if
p0 = sgn * sqrt (E0**2 - m**2)
else
E0 = sqrts / 2
p0 = sgn * E0
end if
if (present (p_cm)) then
sh = p_cm / sqrts
ch = sqrt (1 + sh**2)
p = vector4_moving (E0 * ch + p0 * sh, E0 * sh + p0 * ch, 3)
else
p = vector4_moving (E0, p0, 3)
end if
end function colliding_momenta
@ %def colliding_momenta
@ This subroutine is for the purpose of numerical checks and
comparisons. The idea is to set a number to zero if it is numerically
equivalent with zero. The equivalence is established by comparing
with a [[tolerance]] argument. We implement this for vectors and
transformations.
<<Lorentz: public functions>>=
public :: pacify
<<Lorentz: interfaces>>=
interface pacify
module procedure pacify_vector3
module procedure pacify_vector4
module procedure pacify_LT
end interface pacify
<<Lorentz: procedures>>=
elemental subroutine pacify_vector3 (p, tolerance)
type(vector3_t), intent(inout) :: p
real(default), intent(in) :: tolerance
where (abs (p%p) < tolerance) p%p = zero
end subroutine pacify_vector3
elemental subroutine pacify_vector4 (p, tolerance)
type(vector4_t), intent(inout) :: p
real(default), intent(in) :: tolerance
where (abs (p%p) < tolerance) p%p = zero
end subroutine pacify_vector4
elemental subroutine pacify_LT (LT, tolerance)
type(lorentz_transformation_t), intent(inout) :: LT
real(default), intent(in) :: tolerance
where (abs (LT%L) < tolerance) LT%L = zero
end subroutine pacify_LT
@ %def pacify
@
<<Lorentz: public>>=
public :: vector_set_reshuffle
<<Lorentz: procedures>>=
subroutine vector_set_reshuffle (p1, list, p2)
type(vector4_t), intent(in), dimension(:), allocatable :: p1
integer, intent(in), dimension(:), allocatable :: list
type(vector4_t), intent(out), dimension(:), allocatable :: p2
integer :: n, n_p
n_p = size (p1)
if (size (list) /= n_p) return
allocate (p2 (n_p))
do n = 1, n_p
p2(n) = p1(list(n))
end do
end subroutine vector_set_reshuffle
@ %def vector_set_reshuffle
@
<<Lorentz: public>>=
public :: vector_set_is_cms
<<Lorentz: procedures>>=
function vector_set_is_cms (p, n_in) result (is_cms)
logical :: is_cms
type(vector4_t), intent(in), dimension(:) :: p
integer, intent(in) :: n_in
integer :: i
type(vector4_t) :: p_sum
p_sum%p = 0._default
do i = 1, n_in
p_sum = p_sum + p(i)
end do
is_cms = all (abs (p_sum%p(1:3)) < tiny_07)
end function vector_set_is_cms
@ %def vector_set_is_cms
@
<<Lorentz: public>>=
public :: vector_set_is_lab
<<Lorentz: procedures>>=
function vector_set_is_lab (p, n_in) result (is_lab)
logical :: is_lab
type(vector4_t), intent(in), dimension(:) :: p
integer, intent(in) :: n_in
is_lab = .not. vector_set_is_cms (p, n_in)
end function vector_set_is_lab
@ %def vector_set_is_lab
@
<<Lorentz: public>>=
public :: vector4_write_set
<<Lorentz: procedures>>=
subroutine vector4_write_set (p, unit, show_mass, testflag, &
check_conservation, ultra, n_in)
type(vector4_t), intent(in), dimension(:) :: p
integer, intent(in), optional :: unit
logical, intent(in), optional :: show_mass
logical, intent(in), optional :: testflag, ultra
logical, intent(in), optional :: check_conservation
integer, intent(in), optional :: n_in
logical :: extreme
integer :: i, j
real(default), dimension(0:3) :: p_tot
character(len=7) :: fmt
integer :: u
logical :: yorn, is_test
integer :: n
extreme = .false.; if (present (ultra)) extreme = ultra
is_test = .false.; if (present (testflag)) is_test = testflag
u = given_output_unit (unit); if (u < 0) return
n = 2; if (present (n_in)) n = n_in
p_tot = 0
yorn = .false.; if (present (check_conservation)) yorn = check_conservation
do i = 1, size (p)
if (yorn .and. i > n) then
forall (j=0:3) p_tot(j) = p_tot(j) - p(i)%p(j)
else
forall (j=0:3) p_tot(j) = p_tot(j) + p(i)%p(j)
end if
call vector4_write (p(i), u, show_mass=show_mass, &
testflag=testflag, ultra=ultra)
end do
if (extreme) then
call pac_fmt (fmt, FMT_19, FMT_11, testflag)
else
call pac_fmt (fmt, FMT_19, FMT_15, testflag)
end if
if (is_test) call pacify (p_tot, 1.E-9_default)
if (.not. is_test) then
write (u, "(A5)") 'Total: '
write (u, "(1x,A,1x," // fmt // ")") "E = ", p_tot(0)
write (u, "(1x,A,3(1x," // fmt // "))") "P = ", p_tot(1:)
end if
end subroutine vector4_write_set
@ %def vector4_write_set
@
<<Lorentz: public>>=
public :: vector4_check_momentum_conservation
<<Lorentz: procedures>>=
subroutine vector4_check_momentum_conservation (p, n_in, unit, &
abs_smallness, rel_smallness, verbose)
type(vector4_t), dimension(:), intent(in) :: p
integer, intent(in) :: n_in
integer, intent(in), optional :: unit
real(default), intent(in), optional :: abs_smallness, rel_smallness
logical, intent(in), optional :: verbose
integer :: u, i
type(vector4_t) :: psum_in, psum_out
logical, dimension(0:3) :: p_diff
logical :: verb
u = given_output_unit (unit); if (u < 0) return
verb = .false.; if (present (verbose)) verb = verbose
psum_in = vector4_null
do i = 1, n_in
psum_in = psum_in + p(i)
end do
psum_out = vector4_null
do i = n_in + 1, size (p)
psum_out = psum_out + p(i)
end do
!!! !!! !!! Workaround for gfortran-4.8.4 bug
do i = 0, 3
p_diff(i) = vanishes (psum_in%p(i) - psum_out%p(i), &
abs_smallness = abs_smallness, rel_smallness = rel_smallness)
end do
if (.not. all (p_diff)) then
call msg_warning ("Momentum conservation: FAIL", unit = u)
if (verb) then
write (u, "(A)") "Incoming:"
call vector4_write (psum_in, u)
write (u, "(A)") "Outgoing:"
call vector4_write (psum_out, u)
end if
else
if (verb) then
write (u, "(A)") "Momentum conservation: CHECK"
end if
end if
end subroutine vector4_check_momentum_conservation
@ %def vector4_check_momentum_conservation
@ This computes the quantities
\begin{align*}
\langle ij \rangle &= \sqrt{|S_{ij}|} e^{i\phi_{ij}},
[ij] &= \sqrt{|S_{ij}|} e^{\i\tilde{\phi}_{ij}},
\end{align*}
with $S_{ij} = \left(p_i + p_j\right)^2$. The phase space factor
$\phi_{ij}$ is determined by
\begin{align*}
\cos\phi_{ij} &= \frac{p_i^1p_j^+ - p_j^1p_i^+}{\sqrt{p_i^+p_j^+S_{ij}}},
\sin\phi_{ij} &= \frac{p_i^2p_j^+ - p_j^2p_i^+}{\sqrt{p_i^+p_j^+S_{ij}}}.
\end{align*}
After $\langle ij \rangle$ has been computed according to these
formulae, $[ij]$ can be obtained by using the relation $S_{ij} =
\langle ij \rangle [ji]$ and taking into account that $[ij] =
-[ji]$. Thus, a minus-sign has to be applied.
<<Lorentz: public>>=
public :: spinor_product
<<Lorentz: procedures>>=
subroutine spinor_product (p1, p2, prod1, prod2)
type(vector4_t), intent(in) :: p1, p2
complex(default), intent(out) :: prod1, prod2
real(default) :: sij
complex(default) :: phase
real(default) :: pp_1, pp_2
pp_1 = p1%p(0) + p1%p(3)
pp_2 = p2%p(0) + p2%p(3)
sij = (p1+p2)**2
phase = cmplx ((p1%p(1)*pp_2 - p2%p(1)*pp_1)/sqrt (sij*pp_1*pp_2), &
(p1%p(2)*pp_2 - p2%p(2)*pp_1)/sqrt (sij*pp_1*pp_2), &
default)
!!! <ij>
prod1 = sqrt (sij) * phase
!!! [ij]
if (abs(prod1) > 0) then
prod2 = - sij / prod1
else
prod2 = 0
end if
end subroutine spinor_product
@ %def spinor_product
@
\clearpage
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
\section{Special Physics functions}
Here, we declare functions that are specific for the Standard Model,
including QCD: fixed and running $\alpha_s$, Catani-Seymour
dipole terms, loop functions, etc.
To make maximum use of this, all functions, if possible, are declared
elemental (or pure, if this is not possible).
<<[[sm_physics.f90]]>>=
<<File header>>
module sm_physics
<<Use kinds>>
use io_units
use constants
use numeric_utils
use diagnostics
use physics_defs
use lorentz
<<Standard module head>>
<<SM physics: public>>
<<SM physics: parameters>>
contains
<<SM physics: procedures>>
end module sm_physics
@ %def sm_physics
@
\subsection{Running $\alpha_s$}
@ Then we define the coefficients of the beta function of QCD (as a
reference cf. the Particle Data Group), where $n_f$ is the number of
active flavors in two different schemes:
\begin{align}
\beta_0 &=\; 11 - \frac23 n_f \\
\beta_1 &=\; 51 - \frac{19}{3} n_f \\
\beta_2 &=\; 2857 - \frac{5033}{9} n_f + \frac{325}{27} n_f^2
\end{align}
\begin{align}
b_0 &=\; \frac{1}{12 \pi} \left( 11 C_A - 2 n_f \right) \\
b_1 &=\; \frac{1}{24 \pi^2} \left( 17 C_A^2 - 5 C_A n_f - 3 C_F n_f \right) \\
b_2 &=\; \frac{1}{(4\pi)^3} \biggl( \frac{2857}{54} C_A^3 -
\frac{1415}{54} * C_A^2 n_f - \frac{205}{18} C_A C_F n_f + C_F^2 n_f
+ \frac{79}{54} C_A n_f**2 + \frac{11}{9} C_F n_f**2 \biggr)
\end{align}
<<SM physics: public>>=
public :: beta0, beta1, beta2, coeff_b0, coeff_b1, coeff_b2
<<SM physics: procedures>>=
pure function beta0 (nf)
real(default), intent(in) :: nf
real(default) :: beta0
beta0 = 11.0_default - two/three * nf
end function beta0
pure function beta1 (nf)
real(default), intent(in) :: nf
real(default) :: beta1
beta1 = 51.0_default - 19.0_default/three * nf
end function beta1
pure function beta2 (nf)
real(default), intent(in) :: nf
real(default) :: beta2
beta2 = 2857.0_default - 5033.0_default / 9.0_default * &
nf + 325.0_default/27.0_default * nf**2
end function beta2
pure function coeff_b0 (nf)
real(default), intent(in) :: nf
real(default) :: coeff_b0
coeff_b0 = (11.0_default * CA - two * nf) / (12.0_default * pi)
end function coeff_b0
pure function coeff_b1 (nf)
real(default), intent(in) :: nf
real(default) :: coeff_b1
coeff_b1 = (17.0_default * CA**2 - five * CA * nf - three * CF * nf) / &
(24.0_default * pi**2)
end function coeff_b1
pure function coeff_b2 (nf)
real(default), intent(in) :: nf
real(default) :: coeff_b2
coeff_b2 = (2857.0_default/54.0_default * CA**3 - &
1415.0_default/54.0_default * &
CA**2 * nf - 205.0_default/18.0_default * CA*CF*nf &
+ 79.0_default/54.0_default * CA*nf**2 + &
11.0_default/9.0_default * CF * nf**2) / (four*pi)**3
end function coeff_b2
@ %def beta0 beta1 beta2
@ %def coeff_b0 coeff_b1 coeff_b2
@ There should be two versions of running $\alpha_s$, one which takes
the scale and $\Lambda_{\text{QCD}}$ as input, and one which takes the
scale and e.g. $\alpha_s(m_Z)$ as input. Here, we take the one which
takes the QCD scale and scale as inputs from the PDG book.
<<SM physics: public>>=
public :: running_as, running_as_lam
<<SM physics: procedures>>=
pure function running_as (scale, al_mz, mz, order, nf) result (ascale)
real(default), intent(in) :: scale
real(default), intent(in), optional :: al_mz, nf, mz
integer, intent(in), optional :: order
integer :: ord
real(default) :: az, m_z, as_log, n_f, b0, b1, b2, ascale
real(default) :: as0, as1
if (present (mz)) then
m_z = mz
else
m_z = MZ_REF
end if
if (present (order)) then
ord = order
else
ord = 0
end if
if (present (al_mz)) then
az = al_mz
else
az = ALPHA_QCD_MZ_REF
end if
if (present (nf)) then
n_f = nf
else
n_f = 5
end if
b0 = coeff_b0 (n_f)
b1 = coeff_b1 (n_f)
b2 = coeff_b2 (n_f)
as_log = one + b0 * az * log(scale**2/m_z**2)
as0 = az / as_log
as1 = as0 - as0**2 * b1/b0 * log(as_log)
select case (ord)
case (0)
ascale = as0
case (1)
ascale = as1
case (2)
ascale = as1 + as0**3 * (b1**2/b0**2 * ((log(as_log))**2 - &
log(as_log) + as_log - one) - b2/b0 * (as_log - one))
case default
ascale = as0
end select
end function running_as
pure function running_as_lam (nf, scale, lambda, order) result (ascale)
real(default), intent(in) :: nf, scale
real(default), intent(in), optional :: lambda
integer, intent(in), optional :: order
real(default) :: lambda_qcd
real(default) :: as0, as1, logmul, b0, b1, b2, ascale
integer :: ord
if (present (lambda)) then
lambda_qcd = lambda
else
lambda_qcd = LAMBDA_QCD_REF
end if
if (present (order)) then
ord = order
else
ord = 0
end if
b0 = beta0(nf)
logmul = log(scale**2/lambda_qcd**2)
as0 = four*pi / b0 / logmul
if (ord > 0) then
b1 = beta1(nf)
as1 = as0 * (one - two* b1 / b0**2 * log(logmul) / logmul)
end if
select case (ord)
case (0)
ascale = as0
case (1)
ascale = as1
case (2)
b2 = beta2(nf)
ascale = as1 + as0 * four * b1**2/b0**4/logmul**2 * &
((log(logmul) - 0.5_default)**2 + &
b2*b0/8.0_default/b1**2 - five/four)
case default
ascale = as0
end select
end function running_as_lam
@ %def running_as
@ %def running_as_lam
@
\subsection{Catani-Seymour Parameters}
These are fundamental constants of the Catani-Seymour dipole formalism.
Since the corresponding parameters for the gluon case depend on the
number of flavors which is treated as an argument, there we do have
functions and not parameters.
\begin{equation}
\gamma_q = \gamma_{\bar q} = \frac{3}{2} C_F \qquad \gamma_g =
\frac{11}{6} C_A - \frac{2}{3} T_R N_f
\end{equation}
\begin{equation}
K_q = K_{\bar q} = \left( \frac{7}{2} - \frac{\pi^2}{6} \right) C_F \qquad
K_g = \left( \frac{67}{18} - \frac{\pi^2}{6} \right) C_A -
\frac{10}{9} T_R N_f
\end{equation}
<<SM physics: parameters>>=
real(kind=default), parameter, public :: gamma_q = three/two * CF, &
k_q = (7.0_default/two - pi**2/6.0_default) * CF
@ %def gamma_q
@
<<SM physics: public>>=
public :: gamma_g, k_g
<<SM physics: procedures>>=
elemental function gamma_g (nf) result (gg)
real(kind=default), intent(in) :: nf
real(kind=default) :: gg
gg = 11.0_default/6.0_default * CA - two/three * TR * nf
end function gamma_g
elemental function k_g (nf) result (kg)
real(kind=default), intent(in) :: nf
real(kind=default) :: kg
kg = (67.0_default/18.0_default - pi**2/6.0_default) * CA - &
10.0_default/9.0_default * TR * nf
end function k_g
@ %def gamma_g
@ %def k_g
@
\subsection{Mathematical Functions}
The dilogarithm. This simplified version is bound to double
precision, and restricted to argument values less or equal to unity,
so we do not need complex algebra. The wrapper converts it to default
precision (which is, of course, a no-op if double=default).
The routine calculates the dilogarithm through mapping on the area
where there is a quickly convergent series (adapted from an F77
routine by Hans Kuijf, 1988): Map $x$ such that $x$ is not in the
neighbourhood of $1$. Note that $|z|=-\ln(1-x)$ is always smaller
than $1.10$, but $\frac{1.10^{19}}{19!}{\rm Bernoulli}_{19}=2.7\times
10^{-15}$.
<<SM physics: public>>=
public :: Li2
<<SM physics: procedures>>=
elemental function Li2 (x)
use kinds, only: double
real(default), intent(in) :: x
real(default) :: Li2
Li2 = real( Li2_double (real(x, kind=double)), kind=default)
end function Li2
@ %def: Li2
@
<<SM physics: procedures>>=
elemental function Li2_double (x) result (Li2)
use kinds, only: double
real(kind=double), intent(in) :: x
real(kind=double) :: Li2
real(kind=double), parameter :: pi2_6 = pi**2/6
if (abs(1-x) < tiny_07) then
Li2 = pi2_6
else if (abs(1-x) < 0.5_double) then
Li2 = pi2_6 - log(1-x) * log(x) - Li2_restricted (1-x)
else if (abs(x) > 1.d0) then
! Li2 = 0
! call msg_bug (" Dilogarithm called outside of defined range.")
!!! Reactivate Dilogarithm identity
Li2 = -pi2_6 - 0.5_default * log(-x) * log(-x) - Li2_restricted (1/x)
else
Li2 = Li2_restricted (x)
end if
contains
elemental function Li2_restricted (x) result (Li2)
real(kind=double), intent(in) :: x
real(kind=double) :: Li2
real(kind=double) :: tmp, z, z2
z = - log (1-x)
z2 = z**2
! Horner's rule for the powers z^3 through z^19
tmp = 43867._double/798._double
tmp = tmp * z2 /342._double - 3617._double/510._double
tmp = tmp * z2 /272._double + 7._double/6._double
tmp = tmp * z2 /210._double - 691._double/2730._double
tmp = tmp * z2 /156._double + 5._double/66._double
tmp = tmp * z2 /110._double - 1._double/30._double
tmp = tmp * z2 / 72._double + 1._double/42._double
tmp = tmp * z2 / 42._double - 1._double/30._double
tmp = tmp * z2 / 20._double + 1._double/6._double
! The first three terms of the power series
Li2 = z2 * z * tmp / 6._double - 0.25_double * z2 + z
end function Li2_restricted
end function Li2_double
@ %def Li2_double
@
\subsection{Loop Integrals}
These functions appear in the calculation of the effective one-loop coupling of
a (pseudo)scalar to a vector boson pair.
<<SM physics: public>>=
public :: faux
<<SM physics: procedures>>=
elemental function faux (x) result (y)
real(default), intent(in) :: x
complex(default) :: y
if (1 <= x) then
y = asin(sqrt(1/x))**2
else
y = - 1/4.0_default * (log((1 + sqrt(1 - x))/ &
(1 - sqrt(1 - x))) - cmplx (0.0_default, pi, kind=default))**2
end if
end function faux
@ %def faux
@
<<SM physics: public>>=
public :: fonehalf
<<SM physics: procedures>>=
elemental function fonehalf (x) result (y)
real(default), intent(in) :: x
complex(default) :: y
if (abs(x) < eps0) then
y = 0
else
y = - 2.0_default * x * (1 + (1 - x) * faux(x))
end if
end function fonehalf
@ %def fonehalf
@
<<SM physics: public>>=
public :: fonehalf_pseudo
<<SM physics: procedures>>=
function fonehalf_pseudo (x) result (y)
real(default), intent(in) :: x
complex(default) :: y
if (abs(x) < eps0) then
y = 0
else
y = - 2.0_default * x * faux(x)
end if
end function fonehalf_pseudo
@ %def fonehalf_pseudo
@
<<SM physics: public>>=
public :: fone
<<SM physics: procedures>>=
elemental function fone (x) result (y)
real(default), intent(in) :: x
complex(default) :: y
if (abs(x) < eps0) then
y = 2.0_default
else
y = 2.0_default + 3.0_default * x + &
3.0_default * x * (2.0_default - x) * &
faux(x)
end if
end function fone
@ %def fone
@
<<SM physics: public>>=
public :: gaux
<<SM physics: procedures>>=
elemental function gaux (x) result (y)
real(default), intent(in) :: x
complex(default) :: y
if (1 <= x) then
y = sqrt(x - 1) * asin(sqrt(1/x))
else
y = sqrt(1 - x) * (log((1 + sqrt(1 - x)) / &
(1 - sqrt(1 - x))) - &
cmplx (0.0_default, pi, kind=default)) / 2.0_default
end if
end function gaux
@ %def gaux
@
<<SM physics: public>>=
public :: tri_i1
<<SM physics: procedures>>=
elemental function tri_i1 (a,b) result (y)
real(default), intent(in) :: a,b
complex(default) :: y
if (a < eps0 .or. b < eps0) then
y = 0
else
y = a*b/2.0_default/(a-b) + a**2 * b**2/2.0_default/(a-b)**2 * &
(faux(a) - faux(b)) + &
a**2 * b/(a-b)**2 * (gaux(a) - gaux(b))
end if
end function tri_i1
@ %def tri_i1
@
<<SM physics: public>>=
public :: tri_i2
<<SM physics: procedures>>=
elemental function tri_i2 (a,b) result (y)
real(default), intent(in) :: a,b
complex(default) :: y
if (a < eps0 .or. b < eps0) then
y = 0
else
y = - a * b / 2.0_default / (a-b) * (faux(a) - faux(b))
end if
end function tri_i2
@ %def tri_i2
@
\subsection{More on $\alpha_s$}
These functions are for the running of the strong coupling constants,
$\alpha_s$.
<<SM physics: public>>=
public :: run_b0
<<SM physics: procedures>>=
elemental function run_b0 (nf) result (bnull)
integer, intent(in) :: nf
real(default) :: bnull
bnull = 33.0_default - 2.0_default * nf
end function run_b0
@ %def run_b0
@
<<SM physics: public>>=
public :: run_b1
<<SM physics: procedures>>=
elemental function run_b1 (nf) result (bone)
integer, intent(in) :: nf
real(default) :: bone
bone = 6.0_default * (153.0_default - 19.0_default * nf)/run_b0(nf)**2
end function run_b1
@ %def run_b1
@
<<SM physics: public>>=
public :: run_aa
<<SM physics: procedures>>=
elemental function run_aa (nf) result (aaa)
integer, intent(in) :: nf
real(default) :: aaa
aaa = 12.0_default * PI / run_b0(nf)
end function run_aa
@ %def run_aa
@
<<SM physics: pubic functions>>=
public :: run_bb
<<SM physics: procedures>>=
elemental function run_bb (nf) result (bbb)
integer, intent(in) :: nf
real(default) :: bbb
bbb = run_b1(nf) / run_aa(nf)
end function run_bb
@ %def run_bb
@
\subsection{Functions for Catani-Seymour dipoles}
For the automated Catani-Seymour dipole subtraction, we need the
following functions.
<<SM physics: public>>=
public :: ff_dipole
<<SM physics: procedures>>=
pure subroutine ff_dipole (v_ijk,y_ijk,p_ij,pp_k,p_i,p_j,p_k)
type(vector4_t), intent(in) :: p_i, p_j, p_k
type(vector4_t), intent(out) :: p_ij, pp_k
real(kind=default), intent(out) :: y_ijk
real(kind=default) :: z_i
real(kind=default), intent(out) :: v_ijk
z_i = (p_i*p_k) / ((p_k*p_j) + (p_k*p_i))
y_ijk = (p_i*p_j) / ((p_i*p_j) + (p_i*p_k) + (p_j*p_k))
p_ij = p_i + p_j - y_ijk/(1.0_default - y_ijk) * p_k
pp_k = (1.0/(1.0_default - y_ijk)) * p_k
!!! We don't multiply by alpha_s right here:
v_ijk = 8.0_default * PI * CF * &
(2.0 / (1.0 - z_i*(1.0 - y_ijk)) - (1.0 + z_i))
end subroutine ff_dipole
@ %def ff_dipole
@
<<SM physics: public>>=
public :: fi_dipole
<<SM physics: procedures>>=
pure subroutine fi_dipole (v_ija,x_ija,p_ij,pp_a,p_i,p_j,p_a)
type(vector4_t), intent(in) :: p_i, p_j, p_a
type(vector4_t), intent(out) :: p_ij, pp_a
real(kind=default), intent(out) :: x_ija
real(kind=default) :: z_i
real(kind=default), intent(out) :: v_ija
z_i = (p_i*p_a) / ((p_a*p_j) + (p_a*p_i))
x_ija = ((p_i*p_a) + (p_j*p_a) - (p_i*p_j)) &
/ ((p_i*p_a) + (p_j*p_a))
p_ij = p_i + p_j - (1.0_default - x_ija) * p_a
pp_a = x_ija * p_a
!!! We don't not multiply by alpha_s right here:
v_ija = 8.0_default * PI * CF * &
(2.0 / (1.0 - z_i + (1.0 - x_ija)) - (1.0 + z_i)) / x_ija
end subroutine fi_dipole
@ %def fi_dipole
@
<<SM physics: public>>=
public :: if_dipole
<<SM physics: procedures>>=
pure subroutine if_dipole (v_kja,u_j,p_aj,pp_k,p_k,p_j,p_a)
type(vector4_t), intent(in) :: p_k, p_j, p_a
type(vector4_t), intent(out) :: p_aj, pp_k
real(kind=default), intent(out) :: u_j
real(kind=default) :: x_kja
real(kind=default), intent(out) :: v_kja
u_j = (p_a*p_j) / ((p_a*p_j) + (p_a*p_k))
x_kja = ((p_a*p_k) + (p_a*p_j) - (p_j*p_k)) &
/ ((p_a*p_j) + (p_a*p_k))
p_aj = x_kja * p_a
pp_k = p_k + p_j - (1.0_default - x_kja) * p_a
v_kja = 8.0_default * PI * CF * &
(2.0 / (1.0 - x_kja + u_j) - (1.0 + x_kja)) / x_kja
end subroutine if_dipole
@ %def if_dipole
@ This function depends on a variable number of final state particles
whose kinematics all get changed by the initial-initial dipole insertion.
<<SM physics: public>>=
public :: ii_dipole
<<SM physics: procedures>>=
pure subroutine ii_dipole (v_jab,v_j,p_in,p_out,flag_1or2)
type(vector4_t), dimension(:), intent(in) :: p_in
type(vector4_t), dimension(size(p_in)-1), intent(out) :: p_out
logical, intent(in) :: flag_1or2
real(kind=default), intent(out) :: v_j
real(kind=default), intent(out) :: v_jab
type(vector4_t) :: p_a, p_b, p_j
type(vector4_t) :: k, kk
type(vector4_t) :: p_aj
real(kind=default) :: x_jab
integer :: i
!!! flag_1or2 decides whether this a 12 or 21 dipole
if (flag_1or2) then
p_a = p_in(1)
p_b = p_in(2)
else
p_b = p_in(1)
p_a = p_in(2)
end if
!!! We assume that the unresolved particle has always the last
!!! momentum
p_j = p_in(size(p_in))
x_jab = ((p_a*p_b) - (p_a*p_j) - (p_b*p_j)) / (p_a*p_b)
v_j = (p_a*p_j) / (p_a * p_b)
p_aj = x_jab * p_a
k = p_a + p_b - p_j
kk = p_aj + p_b
do i = 3, size(p_in)-1
p_out(i) = p_in(i) - 2.0*((k+kk)*p_in(i))/((k+kk)*(k+kk)) * (k+kk) + &
(2.0 * (k*p_in(i)) / (k*k)) * kk
end do
if (flag_1or2) then
p_out(1) = p_aj
p_out(2) = p_b
else
p_out(1) = p_b
p_out(2) = p_aj
end if
v_jab = 8.0_default * PI * CF * &
(2.0 / (1.0 - x_jab) - (1.0 + x_jab)) / x_jab
end subroutine ii_dipole
@ %def ii_dipole
@
\subsection{Distributions for integrated dipoles and such}
Note that the following formulae are only meaningful for
$0 \leq x \leq 1$.
The Dirac delta distribution, modified for Monte-Carlo sampling,
centered at $x=1-\frac{\epsilon}{2}$:
<<SM physics: public>>=
public :: delta
<<SM physics: procedures>>=
elemental function delta (x,eps) result (z)
real(kind=default), intent(in) :: x, eps
real(kind=default) :: z
if (x > one - eps) then
z = one / eps
else
z = 0
end if
end function delta
@ %def delta
@ The $+$-distribution, $P_+(x) = \left( \frac{1}{1-x}\right)_+$, for
the regularization of soft-collinear singularities. The constant part
for the Monte-Carlo sampling is the integral over the splitting
function divided by the weight for the WHIZARD numerical integration
over the interval.
<<SM physics: public>>=
public :: plus_distr
<<SM physics: procedures>>=
elemental function plus_distr (x,eps) result (plusd)
real(kind=default), intent(in) :: x, eps
real(kind=default) :: plusd
if (x > one - eps) then
plusd = log(eps) / eps
else
plusd = one / (one - x)
end if
end function plus_distr
@ %def plus_distr
@ The splitting function in $D=4$ dimensions, regularized as
$+$-distributions if necessary:
\begin{align}
P^{qq} (x) = P^{\bar q\bar q} (x) &= \; C_F \cdot \left( \frac{1 +
x^2}{1-x} \right)_+ \\
P^{qg} (x) = P^{\bar q g} (x) &= \; C_F \cdot \frac{1 + (1-x)^2}{x}\\
P^{gq} (x) = P^{g \bar q} (x) &= \; T_R \cdot \left[ x^2 + (1-x)^2
\right] \\
P^{gg} (x) &= \; 2 C_A \biggl[ \left( \frac{1}{1-x} \right)_+ +
\frac{1-x}{x} - 1 + x(1-x) \biggl] \notag{}\\
&\quad + \delta(1-x) \left( \frac{11}{6} C_A -
\frac{2}{3} N_f T_R \right)
\end{align}
Since the number of flavors summed over in the gluon splitting
function might depend on the physics case under consideration, it is
implemented as an input variable.
<<SM physics: public>>=
public :: pqq
<<SM physics: procedures>>=
elemental function pqq (x,eps) result (pqqx)
real(kind=default), intent(in) :: x, eps
real(kind=default) :: pqqx
if (x > (1.0_default - eps)) then
pqqx = (eps - one) / two + two * log(eps) / eps - &
three * (eps - one) / eps / two
else
pqqx = (one + x**2) / (one - x)
end if
pqqx = CF * pqqx
end function pqq
@ %def pqq
@
<<SM physics: public>>=
public :: pgq
<<SM physics: procedures>>=
elemental function pgq (x) result (pgqx)
real(kind=default), intent(in) :: x
real(kind=default) :: pgqx
pgqx = TR * (x**2 + (one - x)**2)
end function pgq
@ %def pgq
@
<<SM physics: public>>=
public :: pqg
<<SM physics: procedures>>=
elemental function pqg (x) result (pqgx)
real(kind=default), intent(in) :: x
real(kind=default) :: pqgx
pqgx = CF * (one + (one - x)**2) / x
end function pqg
@ %def pqg
@
<<SM physics: public>>=
public :: pgg
<<SM physics: procedures>>=
elemental function pgg (x, nf, eps) result (pggx)
real(kind=default), intent(in) :: x, nf, eps
real(kind=default) :: pggx
pggx = two * CA * ( plus_distr (x, eps) + (one-x)/x - one + &
x*(one-x)) + delta (x, eps) * gamma_g(nf)
end function pgg
@ %def pgg
@ For the $qq$ and $gg$ cases, there exist ``regularized'' versions of
the splitting functions:
\begin{align}
P^{qq}_{\text{reg}} (x) &= - C_F \cdot (1 + x) \\
P^{gg}_{\text{reg}} (x) &= 2 C_A \left[ \frac{1-x}{x} - 1 + x(1-x) \right]
\end{align}
<<SM physics: public>>=
public :: pqq_reg
<<SM physics: procedures>>=
elemental function pqq_reg (x) result (pqqregx)
real(kind=default), intent(in) :: x
real(kind=default) :: pqqregx
pqqregx = - CF * (one + x)
end function pqq_reg
@ %def pqq_reg
@
<<SM physics: public>>=
public :: pgg_reg
<<SM physics: procedures>>=
elemental function pgg_reg (x) result (pggregx)
real(kind=default), intent(in) :: x
real(kind=default) :: pggregx
pggregx = two * CA * ((one - x)/x - one + x*(one - x))
end function pgg_reg
@ %def pgg_reg
@ Here, we collect the expressions needed for integrated
Catani-Seymour dipoles, and the so-called flavor kernels. We always
distinguish between the ``ordinary'' Catani-Seymour version, and the
one including a phase-space slicing parameter, $\alpha$.
The standard flavor kernels $\overline{K}^{ab}$ are:
\begin{align}
\overline{K}^{qg} (x) = \overline{K}^{\bar q g} (x) & = \;
P^{qg} (x) \log ((1-x)/x) + CF \times x \\
%%%
\overline{K}^{gq} (x) = \overline{K}^{g \bar q} (x) & = \;
P^{gq} (x) \log ((1-x)/x) + TR \times 2x(1-x) \\
%%%
\overline{K}^{qq} &=\; C_F \biggl[ \left( \frac{2}{1-x} \log
\frac{1-x}{x} \right)_+ - (1+x) \log ((1-x)/x) +
(1-x) \biggr] \notag{}\\
&\quad - (5 - \pi^2) \cdot C_F \cdot \delta(1-x) \\
%%%
\overline{K}^{gg} &=\; 2 C_A \biggl[ \left( \frac{1}{1-x} \log
\frac{1-x}{x} \right)_+ + \left( \frac{1-x}{x} - 1 + x(1-x)
\right) \log((1-x)/x) \biggr] \notag{}\\
&\quad - \delta(1-x) \biggl[ \left(
\frac{50}{9} - \pi^2 \right) C_A - \frac{16}{9} T_R N_f \biggr]
\end{align}
<<SM physics: public>>=
public :: kbarqg
<<SM physics: procedures>>=
function kbarqg (x) result (kbarqgx)
real(kind=default), intent(in) :: x
real(kind=default) :: kbarqgx
kbarqgx = pqg(x) * log((one-x)/x) + CF * x
end function kbarqg
@ %def kbarqg
@
<<SM physics: public>>=
public :: kbargq
<<SM physics: procedures>>=
function kbargq (x) result (kbargqx)
real(kind=default), intent(in) :: x
real(kind=default) :: kbargqx
kbargqx = pgq(x) * log((one-x)/x) + two * TR * x * (one - x)
end function kbargq
@ %def kbarqg
@
<<SM physics: public>>=
public :: kbarqq
<<SM physics: procedures>>=
function kbarqq (x,eps) result (kbarqqx)
real(kind=default), intent(in) :: x, eps
real(kind=default) :: kbarqqx
kbarqqx = CF*(log_plus_distr(x,eps) - (one+x) * log((one-x)/x) + (one - &
x) - (five - pi**2) * delta(x,eps))
end function kbarqq
@ %def kbarqq
@
<<SM physics: public>>=
public :: kbargg
<<SM physics: procedures>>=
function kbargg (x,eps,nf) result (kbarggx)
real(kind=default), intent(in) :: x, eps, nf
real(kind=default) :: kbarggx
kbarggx = CA * (log_plus_distr(x,eps) + two * ((one-x)/x - one + &
x*(one-x) * log((1-x)/x))) - delta(x,eps) * &
((50.0_default/9.0_default - pi**2) * CA - &
16.0_default/9.0_default * TR * nf)
end function kbargg
@ %def kbargg
@ The $\tilde{K}$ are used when two identified hadrons participate:
\begin{equation}
\tilde{K}^{ab} (x) = P^{ab}_{\text{reg}} (x) \cdot \log (1-x) +
\delta^{ab} \mathbf{T}_a^2 \biggl[ \left( \frac{2}{1-x} \log (1-x)
\right)_+ - \frac{\pi^2}{3} \delta(1-x) \biggr]
\end{equation}
<<SM physics: public>>=
public :: ktildeqq
<<SM physics: procedures>>=
function ktildeqq (x,eps) result (ktildeqqx)
real(kind=default), intent(in) :: x, eps
real(kind=default) :: ktildeqqx
ktildeqqx = pqq_reg (x) * log(one-x) + CF * ( - log2_plus_distr (x,eps) &
- pi**2/three * delta(x,eps))
end function ktildeqq
@ %def ktildeqq
@
<<SM physics: public>>=
public :: ktildeqg
<<SM physics: procedures>>=
function ktildeqg (x,eps) result (ktildeqgx)
real(kind=default), intent(in) :: x, eps
real(kind=default) :: ktildeqgx
ktildeqgx = pqg (x) * log(one-x)
end function ktildeqg
@ %def ktildeqg
@
<<SM physics: public>>=
public :: ktildegq
<<SM physics: procedures>>=
function ktildegq (x,eps) result (ktildegqx)
real(kind=default), intent(in) :: x, eps
real(kind=default) :: ktildegqx
ktildegqx = pgq (x) * log(one-x)
end function ktildegq
@ %def ktildeqg
@
<<SM physics: public>>=
public :: ktildegg
<<SM physics: procedures>>=
function ktildegg (x,eps) result (ktildeggx)
real(kind=default), intent(in) :: x, eps
real(kind=default) :: ktildeggx
ktildeggx = pgg_reg (x) * log(one-x) + CA * ( - &
log2_plus_distr (x,eps) - pi**2/three * delta(x,eps))
end function ktildegg
@ %def ktildegg
@ The insertion operator might not be necessary for a GOLEM interface
but is demanded by the Les Houches NLO accord. It is a
three-dimensional array, where the index always gives the inverse
power of the DREG expansion parameter, $\epsilon$.
<<SM physics: public>>=
public :: insert_q
<<SM physics: procedures>>=
pure function insert_q ()
real(kind=default), dimension(0:2) :: insert_q
insert_q(0) = gamma_q + k_q - pi**2/three * CF
insert_q(1) = gamma_q
insert_q(2) = CF
end function insert_q
@ %def insert_q
@
<<SM physics: public>>=
public :: insert_g
<<SM physics: procedures>>=
pure function insert_g (nf)
real(kind=default), intent(in) :: nf
real(kind=default), dimension(0:2) :: insert_g
insert_g(0) = gamma_g (nf) + k_g (nf) - pi**2/three * CA
insert_g(1) = gamma_g (nf)
insert_g(2) = CA
end function insert_g
@ %def insert_g
@ For better convergence, one can exclude regions of phase space with
a slicing parameter from the dipole subtraction procedure. First of
all, the $K$ functions get modified:
\begin{equation}
K_i (\alpha) = K_i - \mathbf{T}_i^2 \log^2 \alpha + \gamma_i (
\alpha - 1 - \log\alpha)
\end{equation}
<<SM physics: public>>=
public :: k_q_al, k_g_al
<<SM physics: procedures>>=
pure function k_q_al (alpha)
real(kind=default), intent(in) :: alpha
real(kind=default) :: k_q_al
k_q_al = k_q - CF * (log(alpha))**2 + gamma_q * &
(alpha - one - log(alpha))
end function k_q_al
pure function k_g_al (alpha, nf)
real(kind=default), intent(in) :: alpha, nf
real(kind=default) :: k_g_al
k_g_al = k_g (nf) - CA * (log(alpha))**2 + gamma_g (nf) * &
(alpha - one - log(alpha))
end function k_g_al
@ %def k_q_al
@ %def k_g_al
@ The $+$-distribution, but with a phase-space slicing parameter,
$\alpha$, $P_{1-\alpha}(x) = \left( \frac{1}{1-x}
\right)_{1-x}$. Since we need the fatal error message here, this
function cannot be elemental.
<<SM physics: public>>=
public :: plus_distr_al
<<SM physics: procedures>>=
function plus_distr_al (x,alpha,eps) result (plusd_al)
real(kind=default), intent(in) :: x, eps, alpha
real(kind=default) :: plusd_al
if ((one - alpha) >= (one - eps)) then
plusd_al = zero
call msg_fatal ('sm_physics, plus_distr_al: alpha and epsilon chosen wrongly')
elseif (x < (1.0_default - alpha)) then
plusd_al = 0
else if (x > (1.0_default - eps)) then
plusd_al = log(eps/alpha)/eps
else
plusd_al = one/(one-x)
end if
end function plus_distr_al
@ %def plus_distr_al
@ Introducing phase-space slicing parameters, these standard flavor
kernels $\overline{K}^{ab}$ become:
\begin{align}
\overline{K}^{qg}_\alpha (x) = \overline{K}^{\bar q g}_\alpha (x) & = \;
P^{qg} (x) \log (\alpha (1-x)/x) + C_F \times x \\
%%%
\overline{K}^{gq}_\alpha (x) = \overline{K}^{g \bar q}_\alpha (x) & = \;
P^{gq} (x) \log (\alpha (1-x)/x) + T_R \times 2x(1-x) \\
%%%
\overline{K}^{qq}_\alpha &=
C_F (1 - x) + P^{qq}_{\text{reg}} (x) \log \frac{\alpha(1-x)}{x}
\notag{}\\ &\quad
+ C_F \delta (1 - x) \log^2 \alpha
+ C_F \left( \frac{2}{1-x} \log \frac{1-x}{x} \right)_+ \notag{}\\
&\quad
- \left( \gamma_q + K_q(\alpha) - \frac56 \pi^2 C_F \right) \cdot
\delta(1-x) \; C_F \Bigl[ + \frac{2}{1-x} \log \left(
\frac{\alpha (2-x)}{1+\alpha-x} \right)
- \theta(1 - \alpha - x) \cdot \left( \frac{2}{1-x} \log
\frac{2-x}{1-x} \right) \Bigr] \\
%%%
\overline{K}^{gg}_\alpha &=\;
P^{gg}_{\text{reg}} (x) \log \frac{\alpha(1-x)}{x}
+ C_A \delta (1 - x) \log^2 \alpha \notag{}\\
&\quad
+ C_A \left( \frac{2}{1-x} \log \frac{1-x}{x} \right)_+
- \left( \gamma_g + K_g(\alpha) - \frac56 \pi^2 C_A \right) \cdot
\delta(1-x) \; C_A \Bigl[ + \frac{2}{1-x} \log \left(
\frac{\alpha (2-x)}{1+\alpha-x} \right)
- \theta(1 - \alpha - x) \cdot \left( \frac{2}{1-x} \log
\frac{2-x}{1-x} \right) \Bigr]
\end{align}
<<SM physics: public>>=
public :: kbarqg_al
<<SM physics: procedures>>=
function kbarqg_al (x,alpha,eps) result (kbarqgx)
real(kind=default), intent(in) :: x, alpha, eps
real(kind=default) :: kbarqgx
kbarqgx = pqg (x) * log(alpha*(one-x)/x) + CF * x
end function kbarqg_al
@ %def kbarqg_al
@
<<SM physics: public>>=
public :: kbargq_al
<<SM physics: procedures>>=
function kbargq_al (x,alpha,eps) result (kbargqx)
real(kind=default), intent(in) :: x, alpha, eps
real(kind=default) :: kbargqx
kbargqx = pgq (x) * log(alpha*(one-x)/x) + two * TR * x * (one-x)
end function kbargq_al
@ %def kbargq_al
@
<<SM physics: public>>=
public :: kbarqq_al
<<SM physics: procedures>>=
function kbarqq_al (x,alpha,eps) result (kbarqqx)
real(kind=default), intent(in) :: x, alpha, eps
real(kind=default) :: kbarqqx
kbarqqx = CF * (one - x) + pqq_reg(x) * log(alpha*(one-x)/x) &
+ CF * log_plus_distr(x,eps) &
- (gamma_q + k_q_al(alpha) - CF * &
five/6.0_default * pi**2 - CF * (log(alpha))**2) * &
delta(x,eps) + &
CF * two/(one -x)*log(alpha*(two-x)/(one+alpha-x))
if (x < (one-alpha)) then
kbarqqx = kbarqqx - CF * two/(one-x) * log((two-x)/(one-x))
end if
end function kbarqq_al
@ %def kbarqq_al
<<SM physics: public>>=
public :: kbargg_al
<<SM physics: procedures>>=
function kbargg_al (x,alpha,eps,nf) result (kbarggx)
real(kind=default), intent(in) :: x, alpha, eps, nf
real(kind=default) :: kbarggx
kbarggx = pgg_reg(x) * log(alpha*(one-x)/x) &
+ CA * log_plus_distr(x,eps) &
- (gamma_g(nf) + k_g_al(alpha,nf) - CA * &
five/6.0_default * pi**2 - CA * (log(alpha))**2) * &
delta(x,eps) + &
CA * two/(one -x)*log(alpha*(two-x)/(one+alpha-x))
if (x < (one-alpha)) then
kbarggx = kbarggx - CA * two/(one-x) * log((two-x)/(one-x))
end if
end function kbargg_al
@ %def kbargg_al
@ The $\tilde{K}$ flavor kernels in the presence of a phase-space slicing
parameter, are:
\begin{equation}
\tilde{K}^{ab} (x,\alpha) = P^{qq, \text{reg}} (x)
\log\frac{1-x}{\alpha} + ..........
\end{equation}
<<SM physics: public>>=
public :: ktildeqq_al
<<SM physics: procedures>>=
function ktildeqq_al (x,alpha,eps) result (ktildeqqx)
real(kind=default), intent(in) :: x, eps, alpha
real(kind=default) :: ktildeqqx
ktildeqqx = pqq_reg(x) * log((one-x)/alpha) + CF*( &
- log2_plus_distr_al(x,alpha,eps) - Pi**2/three * delta(x,eps) &
+ (one+x**2)/(one-x) * log(min(one,(alpha/(one-x)))) &
+ two/(one-x) * log((one+alpha-x)/alpha))
if (x > (one-alpha)) then
ktildeqqx = ktildeqqx - CF*two/(one-x)*log(two-x)
end if
end function ktildeqq_al
@ %def ktildeqq_al
@ This is a logarithmic $+$-distribution, $\left(
\frac{\log((1-x)/x)}{1-x} \right)_+$. For the sampling, we need the
integral over this function over the incomplete sampling interval
$[0,1-\epsilon]$, which is $\log^2(x) + 2 Li_2(x) -
\frac{\pi^2}{3}$. As this function is negative definite for $\epsilon
> 0.1816$, we take a hard upper limit for that sampling parameter,
irrespective of the fact what the user chooses.
<<SM physics: public>>=
public :: log_plus_distr
<<SM physics: procedures>>=
function log_plus_distr (x,eps) result (lpd)
real(kind=default), intent(in) :: x, eps
real(kind=default) :: lpd, eps2
eps2 = min (eps, 0.1816_default)
if (x > (1.0_default - eps2)) then
lpd = ((log(eps2))**2 + two*Li2(eps2) - pi**2/three)/eps2
else
lpd = two*log((one-x)/x)/(one-x)
end if
end function log_plus_distr
@ %def log_plus_distr
@ Logarithmic $+$-distribution, $2 \left( \frac{\log(1/(1-x))}{1-x} \right)_+$.
<<SM physics: public>>=
public :: log2_plus_distr
<<SM physics: procedures>>=
function log2_plus_distr (x,eps) result (lpd)
real(kind=default), intent(in) :: x, eps
real(kind=default) :: lpd
if (x > (1.0_default - eps)) then
lpd = - (log(eps))**2/eps
else
lpd = two*log(one/(one-x))/(one-x)
end if
end function log2_plus_distr
@ %def log2_plus_distr
@ Logarithmic $+$-distribution with phase-space slicing parameter, $2
\left( \frac{\log(1/(1-x))}{1-x} \right)_{1-\alpha}$.
<<SM physics: public>>=
public :: log2_plus_distr_al
<<SM physics: procedures>>=
function log2_plus_distr_al (x,alpha,eps) result (lpd_al)
real(kind=default), intent(in) :: x, eps, alpha
real(kind=default) :: lpd_al
if ((one - alpha) >= (one - eps)) then
lpd_al = zero
call msg_fatal ('alpha and epsilon chosen wrongly')
elseif (x < (one - alpha)) then
lpd_al = 0
elseif (x > (1.0_default - eps)) then
lpd_al = - ((log(eps))**2 - (log(alpha))**2)/eps
else
lpd_al = two*log(one/(one-x))/(one-x)
end if
end function log2_plus_distr_al
@ %def log2_plus_distr_al
@
\subsection{Splitting Functions}
@ Analogue to the regularized distributions of the last subsection, we
give here the unregularized splitting functions, relevant for the parton
shower algorithm. We can use this unregularized version since there will
be a cut-off $\epsilon$ that ensures that $\{z,1-z\}>\epsilon(t)$. This
cut-off seperates resolvable from unresolvable emissions.
[[p_xxx]] are the kernels that are summed over helicity:
<<SM physics: public>>=
public :: p_qqg
public :: p_gqq
public :: p_ggg
@ $q\to q g$
<<SM physics: procedures>>=
elemental function p_qqg (z) result (P)
real(default), intent(in) :: z
real(default) :: P
P = CF * (one + z**2) / (one - z)
end function p_qqg
@ $g\to q \bar{q}$
<<SM physics: procedures>>=
elemental function p_gqq (z) result (P)
real(default), intent(in) :: z
real(default) :: P
P = TR * (z**2 + (one - z)**2)
end function p_gqq
@ $g\to g g$
<<SM physics: procedures>>=
elemental function p_ggg (z) result (P)
real(default), intent(in) :: z
real(default) :: P
P = NC * ((one - z) / z + z / (one - z) + z * (one - z))
end function p_ggg
@ %def p_qqg p_gqq p_ggg
@ Analytically integrated splitting kernels:
<<SM physics: public>>=
public :: integral_over_p_qqg
public :: integral_over_p_gqq
public :: integral_over_p_ggg
<<SM physics: procedures>>=
pure function integral_over_p_qqg (zmin, zmax) result (integral)
real(default), intent(in) :: zmin, zmax
real(default) :: integral
integral = (two / three) * (- zmax**2 + zmin**2 - &
two * (zmax - zmin) + four * log((one - zmin) / (one - zmax)))
end function integral_over_p_qqg
pure function integral_over_p_gqq (zmin, zmax) result (integral)
real(default), intent(in) :: zmin, zmax
real(default) :: integral
integral = 0.5_default * ((two / three) * &
(zmax**3 - zmin**3) - (zmax**2 - zmin**2) + (zmax - zmin))
end function integral_over_p_gqq
pure function integral_over_p_ggg (zmin, zmax) result (integral)
real(default), intent(in) :: zmin, zmax
real(default) :: integral
integral = three * ((log(zmax) - two * zmax - &
log(one - zmax) + zmax**2 / two - zmax**3 / three) - &
(log(zmin) - zmin - zmin - log(one - zmin) + zmin**2 &
/ two - zmin**3 / three) )
end function integral_over_p_ggg
@ %def integral_over_p_gqq integral_over_p_ggg integral_over_p_qqg
@ We can also use (massless) helicity dependent splitting functions:
<<SM physics: public>>=
public :: p_qqg_pol
@ $q_a\to q_b g_c$, the helicity of the quark is not changed by gluon
emission and the gluon is preferably polarized in the branching plane
($l_c=1$):
<<SM physics: procedures>>=
elemental function p_qqg_pol (z, l_a, l_b, l_c) result (P)
real(default), intent(in) :: z
integer, intent(in) :: l_a, l_b, l_c
real(default) :: P
if (l_a /= l_b) then
P = zero
return
end if
if (l_c == -1) then
P = one - z
else
P = (one + z)**2 / (one - z)
end if
P = P * CF
end function p_qqg_pol
@
\subsection{Top width}
In order to produce sensible results, the widths have to be recomputed
for each parameter and order.
We start with the LO-expression for the top width given by the decay
$t\,\to\,W^+,b$, cf. [[doi:10.1016/0550-3213(91)90530-B]]:\\
The analytic formula given there is
\begin{equation*}
\Gamma = \frac{G_F m_t^2}{16\sqrt{2}\pi}
\left[\mathcal{F}_0(\varepsilon, \xi^{-1/2}) -
\frac{2\alpha_s}{3\pi} \mathcal{F}_1 (\varepsilon, \xi^{-1/2})\right],
\end{equation*}
with
\begin{align*}
\mathcal{F}_0 &= \frac{\sqrt{\lambda}}{2} f_0, \\
f_0 &= 4\left[(1-\varepsilon^2)^2 + w^2(1+\varepsilon^2) - 2w^4\right], \\
\lambda = 1 + w^4 + \varepsilon^4 - 2(w^2 + \varepsilon^2 + w^2\varepsilon^2).
\end{align*}
Defining
\begin{equation*}
u_q = \frac{1 + \varepsilon^2 - w^2 - \lambda^{1/2}}{1 +
\varepsilon^2 - w^2 + \lambda^{1/2}}
\end{equation*}
and
\begin{equation*}
u_w = \frac{1 - \varepsilon^2 + w^2 - \lambda^{1/2}}{1 -
\varepsilon^2 + w^2 + \lambda^{1/2}}
\end{equation*}
the factor $\mathcal{F}_1$ can be expressed as
\begin{align*}
\mathcal{F}_1 = \frac{1}{2}f_0(1+\varepsilon^2-w^2)
& \left[\pi^2 + 2Li_2(u_w) - 2Li_2(1-u_w) - 4Li_2(u_q) \right. \\
& -4Li_2(u_q u_w) + \log\left(\frac{1-u_q}{w^2}\right)\log(1-u_q)
- \log^2(1-u_q u_w) \\
& \left.+\frac{1}{4}\log^2\left(\frac{w^2}{u_w}\right) - \log(u_w)
\log\left[\frac{(1-u_q u_w)^2}{1-u_q}\right]
-2\log(u_q)\log\left[(1-u_q)(1-u_q u_w)\right]\right] \\
& -\sqrt{\lambda}f_0(2\log(w) + 3\log(\varepsilon) - 2\log{\lambda}) \\
& +4(1-\varepsilon^2)\left[(1-\varepsilon^2)^2 +
w^2(1+\varepsilon^2) - 4w^4\right]\log(u_w) \\
& \left[(3 - \varepsilon^2 + 11\varepsilon^4 - \varepsilon^6)
+ w^2(6 - 12\varepsilon^2 +2\varepsilon^4) - w^4(21 +
5\varepsilon^2) + 12w^6\right] \log(u_q) \\
& 6\sqrt{\lambda} (1-\varepsilon^2) (1 + \varepsilon^2 - w^2)
\log(\varepsilon)
+ \sqrt{\lambda}\left[-5 + 22\varepsilon^2 - 5\varepsilon^4 -
9w^2(1+\varepsilon^2) + 6w^4\right].
\end{align*}
@
<<SM physics: public>>=
public :: top_width_sm_lo
<<SM physics: procedures>>=
elemental function top_width_sm_lo (alpha, sinthw, vtb, mtop, mw, mb) &
result (gamma)
real(default) :: gamma
real(default), intent(in) :: alpha, sinthw, vtb, mtop, mw, mb
real(default) :: kappa
kappa = sqrt ((mtop**2 - (mw + mb)**2) * (mtop**2 - (mw - mb)**2))
gamma = alpha / four * mtop / (two * sinthw**2) * &
vtb**2 * kappa / mtop**2 * &
((mtop**2 + mb**2) / (two * mtop**2) + &
(mtop**2 - mb**2)**2 / (two * mtop**2 * mw**2) - &
mw**2 / mtop**2)
end function top_width_sm_lo
@ %def top_width_sm_lo
@
<<SM physics: public>>=
public :: g_mu_from_alpha
<<SM physics: procedures>>=
elemental function g_mu_from_alpha (alpha, mw, sinthw) result (g_mu)
real(default) :: g_mu
real(default), intent(in) :: alpha, mw, sinthw
g_mu = pi * alpha / sqrt(two) / mw**2 / sinthw**2
end function g_mu_from_alpha
@ %def g_mu_from_alpha
@
<<SM physics: public>>=
public :: alpha_from_g_mu
<<SM physics: procedures>>=
elemental function alpha_from_g_mu (g_mu, mw, sinthw) result (alpha)
real(default) :: alpha
real(default), intent(in) :: g_mu, mw, sinthw
alpha = g_mu * sqrt(two) / pi * mw**2 * sinthw**2
end function alpha_from_g_mu
@ %def alpha_from_g_mu
@ Cf. (3.3)-(3.7) in [[1207.5018]].
<<SM physics: public>>=
public :: top_width_sm_qcd_nlo_massless_b
<<SM physics: procedures>>=
elemental function top_width_sm_qcd_nlo_massless_b &
(alpha, sinthw, vtb, mtop, mw, alphas) result (gamma)
real(default) :: gamma
real(default), intent(in) :: alpha, sinthw, vtb, mtop, mw, alphas
real(default) :: prefac, g_mu, w2
g_mu = g_mu_from_alpha (alpha, mw, sinthw)
prefac = g_mu * mtop**3 * vtb**2 / (16 * sqrt(two) * pi)
w2 = mw**2 / mtop**2
gamma = prefac * (f0 (w2) - (two * alphas) / (3 * Pi) * f1 (w2))
end function top_width_sm_qcd_nlo_massless_b
@ %def top_width_sm_qcd_nlo_massless_b
@
<<SM physics: public>>=
public :: f0
<<SM physics: procedures>>=
elemental function f0 (w2) result (f)
real(default) :: f
real(default), intent(in) :: w2
f = two * (one - w2)**2 * (1 + 2 * w2)
end function f0
@ %def f0
@
<<SM physics: public>>=
public :: f1
<<SM physics: procedures>>=
elemental function f1 (w2) result (f)
real(default) :: f
real(default), intent(in) :: w2
f = f0 (w2) * (pi**2 + two * Li2 (w2) - two * Li2 (one - w2)) &
+ four * w2 * (one - w2 - two * w2**2) * log (w2) &
+ two * (one - w2)**2 * (five + four * w2) * log (one - w2) &
- (one - w2) * (five + 9 * w2 - 6 * w2**2)
end function f1
@ %def f1
@ Basically, the same as above but with $m_b$ dependence,
cf. Jezabek / Kuehn 1989.
<<SM physics: public>>=
public :: top_width_sm_qcd_nlo_jk
<<SM physics: procedures>>=
elemental function top_width_sm_qcd_nlo_jk &
(alpha, sinthw, vtb, mtop, mw, mb, alphas) result (gamma)
real(default) :: gamma
real(default), intent(in) :: alpha, sinthw, vtb, mtop, mw, mb, alphas
real(default) :: prefac, g_mu, eps2, i_xi
g_mu = g_mu_from_alpha (alpha, mw, sinthw)
prefac = g_mu * mtop**3 * vtb**2 / (16 * sqrt(two) * pi)
eps2 = (mb / mtop)**2
i_xi = (mw / mtop)**2
gamma = prefac * (ff0 (eps2, i_xi) - &
(two * alphas) / (3 * Pi) * ff1 (eps2, i_xi))
end function top_width_sm_qcd_nlo_jk
@ %def top_width_sm_qcd_nlo_jk
@ Same as above, $m_b > 0$, with the slightly different implementation
(2.6) of arXiv:1204.1513v1 by Campbell and Ellis.
<<SM physics: public>>=
public :: top_width_sm_qcd_nlo_ce
<<SM physics: procedures>>=
elemental function top_width_sm_qcd_nlo_ce &
(alpha, sinthw, vtb, mtop, mw, mb, alpha_s) result (gamma)
real(default) :: gamma
real(default), intent(in) :: alpha, sinthw, vtb, mtop, mw, mb, alpha_s
real(default) :: pm, pp, p0, p3
real(default) :: yw, yp
real(default) :: W0, Wp, Wm, w2
real(default) :: beta2
real(default) :: f
real(default) :: g_mu, gamma0
beta2 = (mb / mtop)**2
w2 = (mw / mtop)**2
p0 = (one - w2 + beta2) / two
p3 = sqrt (lambda (one, w2, beta2)) / two
pp = p0 + p3
pm = p0 - p3
W0 = (one + w2 - beta2) / two
Wp = W0 + p3
Wm = W0 - p3
yp = log (pp / pm) / two
yw = log (Wp / Wm) / two
f = (one - beta2)**2 + w2 * (one + beta2) - two * w2**2
g_mu = g_mu_from_alpha (alpha, mw, sinthw)
gamma0 = g_mu * mtop**3 * vtb**2 / (8 * pi * sqrt(two))
gamma = gamma0 * alpha_s / twopi * CF * &
(8 * f * p0 * (Li2(one - pm) - Li2(one - pp) - two * Li2(one - pm / pp) &
+ yp * log((four * p3**2) / (pp**2 * Wp)) + yw * log (pp)) &
+ four * (one - beta2) * ((one - beta2)**2 + w2 * (one + beta2) - four * w2**2) * yw &
+ (3 - beta2 + 11 * beta2**2 - beta2**3 + w2 * (6 - 12 * beta2 + two * beta2**2) &
- w2**2 * (21 + 5 * beta2) + 12 * w2**3) * yp &
+ 8 * f * p3 * log (sqrt(w2) / (four * p3**2)) &
+ 6 * (one - four * beta2 + 3 * beta2**2 + w2 * (3 + beta2) - four * w2**2) * p3 * log(sqrt(beta2)) &
+ (5 - 22 * beta2 + 5 * beta2**2 + 9 * w2 * (one + beta2) - 6 * w2**2) * p3)
end function top_width_sm_qcd_nlo_ce
@ %def top_width_sm_qcd_nlo_ce
@
<<SM physics: public>>=
public :: ff0
<<SM physics: procedures>>=
elemental function ff0 (eps2, w2) result (f)
real(default) :: f
real(default), intent(in) :: eps2, w2
f = one / two * sqrt(ff_lambda (eps2, w2)) * ff_f0 (eps2, w2)
end function ff0
@ %def ff0
@
<<SM physics: public>>=
public :: ff_f0
<<SM physics: procedures>>=
elemental function ff_f0 (eps2, w2) result (f)
real(default) :: f
real(default), intent(in) :: eps2, w2
f = four * ((1 - eps2)**2 + w2 * (1 + eps2) - 2 * w2**2)
end function ff_f0
@ %def ff_f0
@
<<SM physics: public>>=
public :: ff_lambda
<<SM physics: procedures>>=
elemental function ff_lambda (eps2, w2) result (l)
real(default) :: l
real(default), intent(in) :: eps2, w2
l = one + w2**2 + eps2**2 - two * (w2 + eps2 + w2 * eps2)
end function ff_lambda
@ %def ff_lambda
@
<<SM physics: public>>=
public :: ff1
<<SM physics: procedures>>=
elemental function ff1 (eps2, w2) result (f)
real(default) :: f
real(default), intent(in) :: eps2, w2
real(default) :: uq, uw, sq_lam, fff
sq_lam = sqrt (ff_lambda (eps2, w2))
fff = ff_f0 (eps2, w2)
uw = (one - eps2 + w2 - sq_lam) / &
(one - eps2 + w2 + sq_lam)
uq = (one + eps2 - w2 - sq_lam) / &
(one + eps2 - w2 + sq_lam)
f = one / two * fff * (one + eps2 - w2) * &
(pi**2 + two * Li2 (uw) - two * Li2 (one - uw) - four * Li2 (uq) &
- four * Li2 (uq * uw) + log ((one - uq) / w2) * log (one - uq) &
- log (one - uq * uw)**2 + one / four * log (w2 / uw)**2 &
- log (uw) * log ((one - uq * uw)**2 / (one - uq)) &
- two * log (uq) * log ((one - uq) * (one - uq * uw))) &
- sq_lam * fff * (two * log (sqrt (w2)) &
+ three * log (sqrt (eps2)) - two * log (sq_lam**2)) &
+ four * (one - eps2) * ((one - eps2)**2 + w2 * (one + eps2) &
- four * w2**2) * log (uw) &
+ (three - eps2 + 11 * eps2**2 - eps2**3 + w2 * &
(6 - 12 * eps2 + 2 * eps2**2) - w2**2 * (21 + five * eps2) &
+ 12 * w2**3) * log (uq) &
+ 6 * sq_lam * (one - eps2) * &
(one + eps2 - w2) * log (sqrt (eps2)) &
+ sq_lam * (- five + 22 * eps2 - five * eps2**2 - 9 * w2 * &
(one + eps2) + 6 * w2**2)
end function ff1
@ %def ff1
\subsection{Unit tests}
Test module, followed by the corresponding implementation module.
<<[[sm_physics_ut.f90]]>>=
<<File header>>
module sm_physics_ut
use unit_tests
use sm_physics_uti
<<Standard module head>>
<<SM physics: public test>>
contains
<<SM physics: test driver>>
end module sm_physics_ut
@ %def sm_physics_ut
@
<<[[sm_physics_uti.f90]]>>=
<<File header>>
module sm_physics_uti
<<Use kinds>>
use numeric_utils
use format_defs, only: FMT_15
use constants
use sm_physics
<<Standard module head>>
<<SM physics: test declarations>>
contains
<<SM physics: tests>>
end module sm_physics_uti
@ %def sm_physics_ut
@ API: driver for the unit tests below.
<<SM physics: public test>>=
public :: sm_physics_test
<<SM physics: test driver>>=
subroutine sm_physics_test (u, results)
integer, intent(in) :: u
type(test_results_t), intent(inout) :: results
<<SM physics: execute tests>>
end subroutine sm_physics_test
@ %def sm_physics_test
@
\subsubsection{Splitting functions}
<<SM physics: execute tests>>=
call test (sm_physics_1, "sm_physics_1", &
"Splitting functions", &
u, results)
<<SM physics: test declarations>>=
public :: sm_physics_1
<<SM physics: tests>>=
subroutine sm_physics_1 (u)
integer, intent(in) :: u
real(default) :: z = 0.75_default
write (u, "(A)") "* Test output: sm_physics_1"
write (u, "(A)") "* Purpose: check analytic properties"
write (u, "(A)")
write (u, "(A)") "* Splitting functions:"
write (u, "(A)")
call assert (u, vanishes (p_qqg_pol (z, +1, -1, +1)), "+-+")
call assert (u, vanishes (p_qqg_pol (z, +1, -1, -1)), "+--")
call assert (u, vanishes (p_qqg_pol (z, -1, +1, +1)), "-++")
call assert (u, vanishes (p_qqg_pol (z, -1, +1, -1)), "-+-")
!call assert (u, nearly_equal ( &
!p_qqg_pol (z, +1, +1, -1) + p_qqg_pol (z, +1, +1, +1), &
!p_qqg (z)), "pol sum")
write (u, "(A)")
write (u, "(A)") "* Test output end: sm_physics_1"
end subroutine sm_physics_1
@ %def sm_physics_1
@
\subsubsection{Top width}
<<SM physics: execute tests>>=
call test(sm_physics_2, "sm_physics_2", &
"Top width", u, results)
<<SM physics: test declarations>>=
public :: sm_physics_2
<<SM physics: tests>>=
subroutine sm_physics_2 (u)
integer, intent(in) :: u
real(default) :: mtop, mw, mz, mb, g_mu, sinthw, alpha, vtb, gamma0
real(default) :: w2, alphas, alphas_mz, gamma1
write (u, "(A)") "* Test output: sm_physics_2"
write (u, "(A)") "* Purpose: Check different top width computations"
write (u, "(A)")
write (u, "(A)") "* Values from [[1207.5018]] (massless b)"
mtop = 172.0
mw = 80.399
mz = 91.1876
mb = zero
mb = 0.00001
g_mu = 1.16637E-5
sinthw = sqrt(one - mw**2 / mz**2)
alpha = alpha_from_g_mu (g_mu, mw, sinthw)
vtb = one
w2 = mw**2 / mtop**2
write (u, "(A)") "* Check Li2 implementation"
call assert_equal (u, Li2(w2), 0.2317566263959552_default, &
"Li2(w2)", rel_smallness=1.0E-6_default)
call assert_equal (u, Li2(one - w2), 1.038200378935867_default, &
"Li2(one - w2)", rel_smallness=1.0E-6_default)
write (u, "(A)") "* Check LO Width"
gamma0 = top_width_sm_lo (alpha, sinthw, vtb, mtop, mw, mb)
call assert_equal (u, gamma0, 1.4655_default, &
"top_width_sm_lo", rel_smallness=1.0E-5_default)
alphas = zero
gamma0 = top_width_sm_qcd_nlo_massless_b &
(alpha, sinthw, vtb, mtop, mw, alphas)
call assert_equal (u, gamma0, 1.4655_default, &
"top_width_sm_qcd_nlo_massless_b", rel_smallness=1.0E-5_default)
gamma0 = top_width_sm_qcd_nlo_jk &
(alpha, sinthw, vtb, mtop, mw, mb, alphas)
call assert_equal (u, gamma0, 1.4655_default, &
"top_width_sm_qcd_nlo", rel_smallness=1.0E-5_default)
write (u, "(A)") "* Check NLO Width"
alphas_mz = 0.1202 ! MSTW2008 NLO fit
alphas = running_as (mtop, alphas_mz, mz, 1, 5.0_default)
gamma1 = top_width_sm_qcd_nlo_massless_b &
(alpha, sinthw, vtb, mtop, mw, alphas)
call assert_equal (u, gamma1, 1.3376_default, rel_smallness=1.0E-4_default)
gamma1 = top_width_sm_qcd_nlo_jk &
(alpha, sinthw, vtb, mtop, mw, mb, alphas)
! It would be nice to get one more significant digit but the
! expression is numerically rather unstable for mb -> 0
call assert_equal (u, gamma1, 1.3376_default, rel_smallness=1.0E-3_default)
write (u, "(A)") "* Values from threshold validation (massive b)"
alpha = one / 125.924
! ee = 0.315901
! cw = 0.881903
! v = 240.024
mtop = 172.0 ! This is the value for M1S !!!
mb = 4.2
sinthw = 0.47143
mz = 91.188
mw = 80.419
call assert_equal (u, sqrt(one - mw**2 / mz**2), sinthw, &
"sinthw", rel_smallness=1.0E-6_default)
write (u, "(A)") "* Check LO Width"
gamma0 = top_width_sm_lo (alpha, sinthw, vtb, mtop, mw, mb)
call assert_equal (u, gamma0, 1.5386446_default, &
"gamma0", rel_smallness=1.0E-7_default)
alphas = zero
gamma0 = top_width_sm_qcd_nlo_jk &
(alpha, sinthw, vtb, mtop, mw, mb, alphas)
call assert_equal (u, gamma0, 1.5386446_default, &
"gamma0", rel_smallness=1.0E-7_default)
write (u, "(A)") "* Check NLO Width"
alphas_mz = 0.118 !(Z pole, NLL running to mu_h)
alphas = running_as (mtop, alphas_mz, mz, 1, 5.0_default)
write (u, "(A," // FMT_15 // ")") "* alphas = ", alphas
gamma1 = top_width_sm_qcd_nlo_jk &
(alpha, sinthw, vtb, mtop, mw, mb, alphas)
write (u, "(A," // FMT_15 // ")") "* Gamma1 = ", gamma1
mb = zero
gamma1 = top_width_sm_qcd_nlo_massless_b &
(alpha, sinthw, vtb, mtop, mw, alphas)
alphas = running_as (mtop, alphas_mz, mz, 1, 5.0_default)
write (u, "(A," // FMT_15 // ")") "* Gamma1(mb=0) = ", gamma1
write (u, "(A)")
write (u, "(A)") "* Test output end: sm_physics_2"
end subroutine sm_physics_2
@ %def sm_physics_2
@
\clearpage
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
\section{QCD Coupling}
We provide various distinct implementations of the QCD coupling. In
this module, we define an abstract data type and three
implementations: fixed, running with $\alpha_s(M_Z)$ as input, and
running with $\Lambda_{\text{QCD}}$ as input. We use the functions
defined above in the module [[sm_physics]] but provide a common
interface. Later modules may define additional implementations.
<<[[sm_qcd.f90]]>>=
<<File header>>
module sm_qcd
<<Use kinds>>
use io_units
use format_defs, only: FMT_12
use numeric_utils
use diagnostics
use md5
use physics_defs
use sm_physics
<<Standard module head>>
<<SM qcd: public>>
<<SM qcd: types>>
<<SM qcd: interfaces>>
contains
<<SM qcd: procedures>>
end module sm_qcd
@ %def sm_qcd
@
\subsection{Coupling: Abstract Data Type}
This is the abstract version of the QCD coupling implementation.
<<SM qcd: public>>=
public :: alpha_qcd_t
<<SM qcd: types>>=
type, abstract :: alpha_qcd_t
contains
<<SM qcd: alpha qcd: TBP>>
end type alpha_qcd_t
@ %def alpha_qcd_t
@ There must be an output routine.
<<SM qcd: alpha qcd: TBP>>=
procedure (alpha_qcd_write), deferred :: write
<<SM qcd: interfaces>>=
abstract interface
subroutine alpha_qcd_write (object, unit)
import
class(alpha_qcd_t), intent(in) :: object
integer, intent(in), optional :: unit
end subroutine alpha_qcd_write
end interface
@ %def alpha_qcd_write
@ This method computes the running coupling, given a certain scale. All
parameters (reference value, order of the approximation, etc.) must be
set before calling this.
<<SM qcd: alpha qcd: TBP>>=
procedure (alpha_qcd_get), deferred :: get
<<SM qcd: interfaces>>=
abstract interface
function alpha_qcd_get (alpha_qcd, scale) result (alpha)
import
class(alpha_qcd_t), intent(in) :: alpha_qcd
real(default), intent(in) :: scale
real(default) :: alpha
end function alpha_qcd_get
end interface
@ %def alpha_qcd_get
@
\subsection{Fixed Coupling}
In this version, the $\alpha_s$ value is fixed, the [[scale]] argument
of the [[get]] method is ignored. There is only one parameter, the
value. By default, this is the value at $M_Z$.
<<SM qcd: public>>=
public :: alpha_qcd_fixed_t
<<SM qcd: types>>=
type, extends (alpha_qcd_t) :: alpha_qcd_fixed_t
real(default) :: val = ALPHA_QCD_MZ_REF
contains
<<SM qcd: alpha qcd fixed: TBP>>
end type alpha_qcd_fixed_t
@ %def alpha_qcd_fixed_t
@ Output.
<<SM qcd: alpha qcd fixed: TBP>>=
procedure :: write => alpha_qcd_fixed_write
<<SM qcd: procedures>>=
subroutine alpha_qcd_fixed_write (object, unit)
class(alpha_qcd_fixed_t), intent(in) :: object
integer, intent(in), optional :: unit
integer :: u
u = given_output_unit (unit); if (u < 0) return
write (u, "(3x,A)") "QCD parameters (fixed coupling):"
write (u, "(5x,A," // FMT_12 // ")") "alpha = ", object%val
end subroutine alpha_qcd_fixed_write
@ %def alpha_qcd_fixed_write
@ Calculation: the scale is ignored in this case.
<<SM qcd: alpha qcd fixed: TBP>>=
procedure :: get => alpha_qcd_fixed_get
<<SM qcd: procedures>>=
function alpha_qcd_fixed_get (alpha_qcd, scale) result (alpha)
class(alpha_qcd_fixed_t), intent(in) :: alpha_qcd
real(default), intent(in) :: scale
real(default) :: alpha
alpha = alpha_qcd%val
end function alpha_qcd_fixed_get
@ %def alpha_qcd_fixed_get
@
\subsection{Running Coupling}
In this version, the $\alpha_s$ value runs relative to the value at a
given reference scale. There are two parameters: the value of this
scale (default: $M_Z$), the value of $\alpha_s$ at this scale, and the
number of effective flavors. Furthermore, we have the order of the
approximation.
<<SM qcd: public>>=
public :: alpha_qcd_from_scale_t
<<SM qcd: types>>=
type, extends (alpha_qcd_t) :: alpha_qcd_from_scale_t
real(default) :: mu_ref = MZ_REF
real(default) :: ref = ALPHA_QCD_MZ_REF
integer :: order = 0
integer :: nf = 5
contains
<<SM qcd: alpha qcd from scale: TBP>>
end type alpha_qcd_from_scale_t
@ %def alpha_qcd_from_scale_t
@ Output.
<<SM qcd: alpha qcd from scale: TBP>>=
procedure :: write => alpha_qcd_from_scale_write
<<SM qcd: procedures>>=
subroutine alpha_qcd_from_scale_write (object, unit)
class(alpha_qcd_from_scale_t), intent(in) :: object
integer, intent(in), optional :: unit
integer :: u
u = given_output_unit (unit); if (u < 0) return
write (u, "(3x,A)") "QCD parameters (running coupling):"
write (u, "(5x,A," // FMT_12 // ")") "Scale mu = ", object%mu_ref
write (u, "(5x,A," // FMT_12 // ")") "alpha(mu) = ", object%ref
write (u, "(5x,A,I0)") "LL order = ", object%order
write (u, "(5x,A,I0)") "N(flv) = ", object%nf
end subroutine alpha_qcd_from_scale_write
@ %def alpha_qcd_from_scale_write
@ Calculation: here, we call the function for running $\alpha_s$ that
was defined in [[sm_physics]] above. The function does not take into
account thresholds, so the number of flavors should be the correct one
for the chosen scale. Normally, this should be the $Z$ boson mass.
<<SM qcd: alpha qcd from scale: TBP>>=
procedure :: get => alpha_qcd_from_scale_get
<<SM qcd: procedures>>=
function alpha_qcd_from_scale_get (alpha_qcd, scale) result (alpha)
class(alpha_qcd_from_scale_t), intent(in) :: alpha_qcd
real(default), intent(in) :: scale
real(default) :: alpha
alpha = running_as (scale, &
alpha_qcd%ref, alpha_qcd%mu_ref, alpha_qcd%order, &
real (alpha_qcd%nf, kind=default))
end function alpha_qcd_from_scale_get
@ %def alpha_qcd_from_scale_get
@
\subsection{Running Coupling, determined by $\Lambda_{\text{QCD}}$}
In this version, the input are the value $\Lambda_{\text{QCD}}$ and
the order of the approximation.
<<SM qcd: public>>=
public :: alpha_qcd_from_lambda_t
<<SM qcd: types>>=
type, extends (alpha_qcd_t) :: alpha_qcd_from_lambda_t
real(default) :: lambda = LAMBDA_QCD_REF
integer :: order = 0
integer :: nf = 5
contains
<<SM qcd: alpha qcd from lambda: TBP>>
end type alpha_qcd_from_lambda_t
@ %def alpha_qcd_from_lambda_t
@ Output.
<<SM qcd: alpha qcd from lambda: TBP>>=
procedure :: write => alpha_qcd_from_lambda_write
<<SM qcd: procedures>>=
subroutine alpha_qcd_from_lambda_write (object, unit)
class(alpha_qcd_from_lambda_t), intent(in) :: object
integer, intent(in), optional :: unit
integer :: u
u = given_output_unit (unit); if (u < 0) return
write (u, "(3x,A)") "QCD parameters (Lambda_QCD as input):"
write (u, "(5x,A," // FMT_12 // ")") "Lambda_QCD = ", object%lambda
write (u, "(5x,A,I0)") "LL order = ", object%order
write (u, "(5x,A,I0)") "N(flv) = ", object%nf
end subroutine alpha_qcd_from_lambda_write
@ %def alpha_qcd_from_lambda_write
@ Calculation: here, we call the second function for running $\alpha_s$ that
was defined in [[sm_physics]] above. The $\Lambda$ value should be
the one that is appropriate for the chosen number of effective
flavors. Again, thresholds are not incorporated.
<<SM qcd: alpha qcd from lambda: TBP>>=
procedure :: get => alpha_qcd_from_lambda_get
<<SM qcd: procedures>>=
function alpha_qcd_from_lambda_get (alpha_qcd, scale) result (alpha)
class(alpha_qcd_from_lambda_t), intent(in) :: alpha_qcd
real(default), intent(in) :: scale
real(default) :: alpha
alpha = running_as_lam (real (alpha_qcd%nf, kind=default), scale, &
alpha_qcd%lambda, alpha_qcd%order)
end function alpha_qcd_from_lambda_get
@ %def alpha_qcd_from_lambda_get
@
\subsection{Wrapper type}
We could get along with a polymorphic QCD type, but a monomorphic wrapper type
with a polymorphic component is easier to handle and probably safer
(w.r.t.\ compiler bugs). However, we keep the object transparent, so we can
set the type-specific parameters directly (by a [[dispatch]] routine).
TODO: The [[n_f]] parameter is a later addition which is not printed
nor used in the MD5 sum. The default $-1$ indicates that it has not
been set. We may change this behavior for a more consistent handling of
the $n_f$ parameter (cf.\ [[alphas_nf]]) within WHIZARD. This would
affect various MD5 sums in tests.
<<SM qcd: public>>=
public :: qcd_t
<<SM qcd: types>>=
type :: qcd_t
class(alpha_qcd_t), allocatable :: alpha
character(32) :: md5sum = ""
integer :: n_f = -1
contains
<<SM qcd: qcd: TBP>>
end type qcd_t
@ %def qcd_t
@ Output. We first print the polymorphic [[alpha]] which contains a headline,
then any extra components.
<<SM qcd: qcd: TBP>>=
procedure :: write => qcd_write
<<SM qcd: procedures>>=
subroutine qcd_write (qcd, unit, show_md5sum)
class(qcd_t), intent(in) :: qcd
integer, intent(in), optional :: unit
logical, intent(in), optional :: show_md5sum
logical :: show_md5
integer :: u
u = given_output_unit (unit); if (u < 0) return
show_md5 = .true.; if (present (show_md5sum)) show_md5 = show_md5sum
if (allocated (qcd%alpha)) then
call qcd%alpha%write (u)
else
write (u, "(3x,A)") "QCD parameters (coupling undefined)"
end if
if (show_md5 .and. qcd%md5sum /= "") &
write (u, "(5x,A,A,A)") "md5sum = '", qcd%md5sum, "'"
end subroutine qcd_write
@ %def qcd_write
@ Compute an MD5 sum for the [[alpha_s]] setup. This is
done by writing them to a temporary file, using a standard format.
<<SM qcd: qcd: TBP>>=
procedure :: compute_alphas_md5sum => qcd_compute_alphas_md5sum
<<SM qcd: procedures>>=
subroutine qcd_compute_alphas_md5sum (qcd)
class(qcd_t), intent(inout) :: qcd
integer :: unit
if (allocated (qcd%alpha)) then
unit = free_unit ()
open (unit, status="scratch", action="readwrite")
call qcd%alpha%write (unit)
rewind (unit)
qcd%md5sum = md5sum (unit)
close (unit)
end if
end subroutine qcd_compute_alphas_md5sum
@ %def qcd_compute_alphas_md5sum
@
@ Retrieve the MD5 sum of the qcd setup.
<<SM qcd: qcd: TBP>>=
procedure :: get_md5sum => qcd_get_md5sum
<<SM qcd: procedures>>=
function qcd_get_md5sum (qcd) result (md5sum)
character(32) :: md5sum
class(qcd_t), intent(inout) :: qcd
md5sum = qcd%md5sum
end function qcd_get_md5sum
@ %def qcd_get_md5sum
@
\subsection{Unit tests}
Test module, followed by the corresponding implementation module.
<<[[sm_qcd_ut.f90]]>>=
<<File header>>
module sm_qcd_ut
use unit_tests
use sm_qcd_uti
<<Standard module head>>
<<SM qcd: public test>>
contains
<<SM qcd: test driver>>
end module sm_qcd_ut
@ %def sm_qcd_ut
@
<<[[sm_qcd_uti.f90]]>>=
<<File header>>
module sm_qcd_uti
<<Use kinds>>
use physics_defs, only: MZ_REF
use sm_qcd
<<Standard module head>>
<<SM qcd: test declarations>>
contains
<<SM qcd: tests>>
end module sm_qcd_uti
@ %def sm_qcd_ut
@ API: driver for the unit tests below.
<<SM qcd: public test>>=
public :: sm_qcd_test
<<SM qcd: test driver>>=
subroutine sm_qcd_test (u, results)
integer, intent(in) :: u
type(test_results_t), intent(inout) :: results
<<SM qcd: execute tests>>
end subroutine sm_qcd_test
@ %def sm_qcd_test
@
\subsubsection{QCD Coupling}
We check two different implementations of the abstract QCD coupling.
<<SM qcd: execute tests>>=
call test (sm_qcd_1, "sm_qcd_1", &
"running alpha_s", &
u, results)
<<SM qcd: test declarations>>=
public :: sm_qcd_1
<<SM qcd: tests>>=
subroutine sm_qcd_1 (u)
integer, intent(in) :: u
type(qcd_t) :: qcd
write (u, "(A)") "* Test output: sm_qcd_1"
write (u, "(A)") "* Purpose: compute running alpha_s"
write (u, "(A)")
write (u, "(A)") "* Fixed:"
write (u, "(A)")
allocate (alpha_qcd_fixed_t :: qcd%alpha)
call qcd%compute_alphas_md5sum ()
call qcd%write (u)
write (u, *)
write (u, "(1x,A,F10.7)") "alpha_s (mz) =", &
qcd%alpha%get (MZ_REF)
write (u, "(1x,A,F10.7)") "alpha_s (1 TeV) =", &
qcd%alpha%get (1000._default)
write (u, *)
deallocate (qcd%alpha)
write (u, "(A)") "* Running from MZ (LO):"
write (u, "(A)")
allocate (alpha_qcd_from_scale_t :: qcd%alpha)
call qcd%compute_alphas_md5sum ()
call qcd%write (u)
write (u, *)
write (u, "(1x,A,F10.7)") "alpha_s (mz) =", &
qcd%alpha%get (MZ_REF)
write (u, "(1x,A,F10.7)") "alpha_s (1 TeV) =", &
qcd%alpha%get (1000._default)
write (u, *)
write (u, "(A)") "* Running from MZ (NLO):"
write (u, "(A)")
select type (alpha => qcd%alpha)
type is (alpha_qcd_from_scale_t)
alpha%order = 1
end select
call qcd%compute_alphas_md5sum ()
call qcd%write (u)
write (u, *)
write (u, "(1x,A,F10.7)") "alpha_s (mz) =", &
qcd%alpha%get (MZ_REF)
write (u, "(1x,A,F10.7)") "alpha_s (1 TeV) =", &
qcd%alpha%get (1000._default)
write (u, *)
write (u, "(A)") "* Running from MZ (NNLO):"
write (u, "(A)")
select type (alpha => qcd%alpha)
type is (alpha_qcd_from_scale_t)
alpha%order = 2
end select
call qcd%compute_alphas_md5sum ()
call qcd%write (u)
write (u, *)
write (u, "(1x,A,F10.7)") "alpha_s (mz) =", &
qcd%alpha%get (MZ_REF)
write (u, "(1x,A,F10.7)") "alpha_s (1 TeV) =", &
qcd%alpha%get (1000._default)
write (u, *)
deallocate (qcd%alpha)
write (u, "(A)") "* Running from Lambda_QCD (LO):"
write (u, "(A)")
allocate (alpha_qcd_from_lambda_t :: qcd%alpha)
call qcd%compute_alphas_md5sum ()
call qcd%write (u)
write (u, *)
write (u, "(1x,A,F10.7)") "alpha_s (mz) =", &
qcd%alpha%get (MZ_REF)
write (u, "(1x,A,F10.7)") "alpha_s (1 TeV) =", &
qcd%alpha%get (1000._default)
write (u, *)
write (u, "(A)") "* Running from Lambda_QCD (NLO):"
write (u, "(A)")
select type (alpha => qcd%alpha)
type is (alpha_qcd_from_lambda_t)
alpha%order = 1
end select
call qcd%compute_alphas_md5sum ()
call qcd%write (u)
write (u, *)
write (u, "(1x,A,F10.7)") "alpha_s (mz) =", &
qcd%alpha%get (MZ_REF)
write (u, "(1x,A,F10.7)") "alpha_s (1 TeV) =", &
qcd%alpha%get (1000._default)
write (u, *)
write (u, "(A)") "* Running from Lambda_QCD (NNLO):"
write (u, "(A)")
select type (alpha => qcd%alpha)
type is (alpha_qcd_from_lambda_t)
alpha%order = 2
end select
call qcd%compute_alphas_md5sum ()
call qcd%write (u)
write (u, *)
write (u, "(1x,A,F10.7)") "alpha_s (mz) =", &
qcd%alpha%get (MZ_REF)
write (u, "(1x,A,F10.7)") "alpha_s (1 TeV) =", &
qcd%alpha%get (1000._default)
write (u, "(A)")
write (u, "(A)") "* Test output end: sm_qcd_1"
end subroutine sm_qcd_1
@ %def sm_qcd_1
@
\clearpage
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
\section{Shower algorithms}
<<[[shower_algorithms.f90]]>>=
<<File header>>
module shower_algorithms
<<Use kinds>>
use diagnostics
use constants
<<Standard module head>>
<<shower algorithms: public>>
<<shower algorithms: interfaces>>
contains
<<shower algorithms: procedures>>
<<shower algorithms: tests>>
end module shower_algorithms
@ %def shower_algorithms
@ We want to generate emission variables [[x]]$\in\mathds{R}^d$
proportional to
\begin{align}
&\quad f(x)\; \Delta(f, h(x)) \quad\text{with}\\
\Delta(f, H) &= \exp\left\{-\int\text{d}^d x'f(x') \Theta(h(x') -
H)\right\}
\end{align}
The [[true_function]] $f$ is however too complicated and we are only
able to generate [[x]] according to the [[overestimator]] $F$. This
algorithm is described in Appendix B of 0709.2092 and is proven e.g.~in
1211.7204 and hep-ph/0606275. Intuitively speaking, we overestimate the
emission probability and can therefore set [[scale_max = scale]] if the
emission is rejected.
<<shower algorithms: procedures>>=
subroutine generate_vetoed (x, overestimator, true_function, &
sudakov, inverse_sudakov, scale_min)
real(default), dimension(:), intent(out) :: x
!class(rng_t), intent(inout) :: rng
procedure(XXX_function), pointer, intent(in) :: overestimator, true_function
procedure(sudakov_p), pointer, intent(in) :: sudakov, inverse_sudakov
real(default), intent(in) :: scale_min
real(default) :: random, scale_max, scale
scale_max = inverse_sudakov (one)
do while (scale_max > scale_min)
!call rng%generate (random)
scale = inverse_sudakov (random * sudakov (scale_max))
call generate_on_hypersphere (x, overestimator, scale)
!call rng%generate (random)
if (random < true_function (x) / overestimator (x)) then
return !!! accept x
end if
scale_max = scale
end do
end subroutine generate_vetoed
@ %def generate_vetoed
@
<<shower algorithms: procedures>>=
subroutine generate_on_hypersphere (x, overestimator, scale)
real(default), dimension(:), intent(out) :: x
procedure(XXX_function), pointer, intent(in) :: overestimator
real(default), intent(in) :: scale
call msg_bug ("generate_on_hypersphere: not implemented")
end subroutine generate_on_hypersphere
@ %def generate_on_hypersphere
@
<<shower algorithms: interfaces>>=
interface
pure function XXX_function (x)
import
real(default) :: XXX_function
real(default), dimension(:), intent(in) :: x
end function XXX_function
end interface
interface
pure function sudakov_p (x)
import
real(default) :: sudakov_p
real(default), intent(in) :: x
end function sudakov_p
end interface
@
\subsection{Unit tests}
(Currently unused.)
<<XXX shower algorithms: public>>=
public :: shower_algorithms_test
<<XXX shower algorithms: tests>>=
subroutine shower_algorithms_test (u, results)
integer, intent(in) :: u
type(test_results_t), intent(inout) :: results
<<shower algorithms: execute tests>>
end subroutine shower_algorithms_test
@ %def shower_algorithms_test
@
\subsubsection{Splitting functions}
<<XXX shower algorithms: execute tests>>=
call test (shower_algorithms_1, "shower_algorithms_1", &
"veto technique", &
u, results)
<<XXX shower algorithms: tests>>=
subroutine shower_algorithms_1 (u)
integer, intent(in) :: u
write (u, "(A)") "* Test output: shower_algorithms_1"
write (u, "(A)") "* Purpose: check veto technique"
write (u, "(A)")
write (u, "(A)") "* Splitting functions:"
write (u, "(A)")
!call assert (u, vanishes (p_qqg_pol (z, +1, -1, +1)))
!call assert (u, nearly_equal ( &
!p_qqg_pol (z, +1, +1, -1) + p_qqg_pol (z, +1, +1, +1),
!p_qqg (z))
write (u, "(A)")
write (u, "(A)") "* Test output end: shower_algorithms_1"
end subroutine shower_algorithms_1
@ %def shower_algorithms_1
Index: trunk/src/lcio/LCIOWrap.cpp
===================================================================
--- trunk/src/lcio/LCIOWrap.cpp (revision 8188)
+++ trunk/src/lcio/LCIOWrap.cpp (revision 8189)
@@ -1,557 +1,557 @@
//////////////////////////////////////////////////////////////////////////
// Interface for building LCIO events
//////////////////////////////////////////////////////////////////////////
#include<stdio.h>
#include<string>
#include<iostream>
#include<fstream>
#include "lcio.h"
#include "IO/LCWriter.h"
#include "IO/LCReader.h"
#include "EVENT/LCIO.h"
#include "EVENT/MCParticle.h"
#include "IMPL/LCEventImpl.h"
#include "IMPL/LCRunHeaderImpl.h"
#include "IMPL/LCCollectionVec.h"
#include "IMPL/MCParticleImpl.h"
#include "IMPL/LCTOOLS.h"
#include "UTIL/LCTime.h"
using namespace std;
using namespace lcio;
using namespace IMPL;
using namespace EVENT;
// Tell the caller that this is the true LCIO library
extern "C" bool lcio_available() {
return true;
}
//////////////////////////////////////////////////////////////////////////
// LCEventImpl functions
// The run number at the moment is set to the process ID. We add the process
// ID in addition as an event variable.
extern "C" LCEventImpl* new_lcio_event ( int proc_id, int event_id, int run_id ) {
LCEventImpl* evt = new LCEventImpl();
evt->setRunNumber ( run_id );
evt->parameters().setValue("Run ID", run_id );
evt->parameters().setValue("ProcessID", proc_id );
evt->setEventNumber ( event_id );
evt->parameters().setValue("Event Number", event_id );
LCTime now;
evt->setTimeStamp ( now.timeStamp() );
return evt;
}
extern "C" void lcio_event_delete( LCEventImpl* evt) {
delete evt;
}
extern "C" void lcio_set_weight( LCEventImpl* evt, double wgt ) {
evt->setWeight ( wgt );
}
extern "C" void lcio_set_alpha_qcd ( LCEventImpl* evt, double alphas ) {
float alpha_qcd = alphas;
evt->parameters().setValue ( "alphaQCD", alpha_qcd );
}
extern "C" void lcio_set_scale ( LCEventImpl* evt, double scale ) {
float scale_f = scale;
evt->parameters().setValue ( "scale", scale_f );
}
extern "C" void lcio_set_sqrts ( LCEventImpl* evt, double sqrts ) {
float sqrts_f = sqrts;
evt->parameters().setValue ( "Energy", sqrts_f );
}
extern "C" void lcio_set_xsec ( LCEventImpl* evt, double xsec, double xsec_err ) {
float xsec_f = xsec;
float xsec_err_f = xsec_err;
evt->parameters().setValue ( "crossSection", xsec_f );
evt->parameters().setValue ( "crossSectionError", xsec_err_f );
}
extern "C" void lcio_set_beam ( LCEventImpl* evt, int pdg, int beam ) {
if (beam == 1){
evt->parameters().setValue ( "beamPDG0", pdg );
}
else if (beam == 2){
evt->parameters().setValue ( "beamPDG1", pdg );
}
}
extern "C" void lcio_set_pol ( LCEventImpl* evt, double pol1, double pol2 ) {
float pol1_f = pol1;
float pol2_f = pol2;
evt->parameters().setValue ( "Pol0", pol1_f );
evt->parameters().setValue ( "Pol1", pol2_f );
}
extern "C" void lcio_set_beam_file ( LCEventImpl* evt, char* file ) {
evt->parameters().setValue ( "BeamSpectrum", file );
}
extern "C" void lcio_set_process_name ( LCEventImpl* evt, char* name ) {
evt->parameters().setValue ( "processName", name );
}
extern "C" LCEvent* read_lcio_event ( LCReader* lcRdr) {
LCEvent* evt;
if ((evt = lcRdr->readNextEvent ()) != 0) {
return evt;
}
else
{
return NULL;
}
}
// dump the event to the screen
extern "C" void dump_lcio_event ( LCEvent* evt) {
LCTOOLS::dumpEventDetailed ( evt );
}
extern "C" int lcio_event_get_event_number (LCEvent* evt) {
return evt->getEventNumber();
}
extern "C" int lcio_event_signal_process_id (LCEvent* evt) {
return evt->getParameters().getIntVal("ProcessID");
}
extern "C" int lcio_event_get_n_particles (LCEvent* evt) {
LCCollection* col = evt->getCollection( LCIO::MCPARTICLE );
int n = col->getNumberOfElements();
return n;
}
extern "C" double lcio_event_get_alpha_qcd (LCEvent* evt) {
double alphas;
return alphas = evt->parameters().getFloatVal( "alphaQCD" );
}
extern "C" double lcio_event_get_scale (LCEvent* evt) {
double scale;
return scale = evt->parameters().getFloatVal( "scale" );
}
// Write parameters in LCIO event in ASCII form to a stream
extern "C" std::ostream& printParameters
( const EVENT::LCParameters& params, std::ofstream &out){
StringVec intKeys ;
int nIntParameters = params.getIntKeys( intKeys ).size() ;
for(int i=0; i< nIntParameters ; i++ ){
IntVec intVec ;
params.getIntVals( intKeys[i], intVec ) ;
int nInt = intVec.size() ;
out << " parameter " << intKeys[i] << " [int]: " ;
if( nInt == 0 ){
out << " [empty] " << std::endl ;
}
for(int j=0; j< nInt ; j++ ){
out << intVec[j] << ", " ;
}
out << endl ;
}
StringVec floatKeys ;
int nFloatParameters = params.getFloatKeys( floatKeys ).size() ;
for(int i=0; i< nFloatParameters ; i++ ){
FloatVec floatVec ;
params.getFloatVals( floatKeys[i], floatVec ) ;
int nFloat = floatVec.size() ;
out << " parameter " << floatKeys[i] << " [float]: " ;
if( nFloat == 0 ){
out << " [empty] " << std::endl ;
}
for(int j=0; j< nFloat ; j++ ){
out << floatVec[j] << ", " ;
}
out << endl ;
}
StringVec stringKeys ;
int nStringParameters = params.getStringKeys( stringKeys ).size() ;
for(int i=0; i< nStringParameters ; i++ ){
StringVec stringVec ;
params.getStringVals( stringKeys[i], stringVec ) ;
int nString = stringVec.size() ;
out << " parameter " << stringKeys[i] << " [string]: " ;
if( nString == 0 ){
out << " [empty] " << std::endl ;
}
for(int j=0; j< nString ; j++ ){
out << stringVec[j] << ", " ;
}
out << endl ;
}
return out;
}
// Write MCParticles as ASCII to stream
extern "C" std::ostream& printMCParticles
(const EVENT::LCCollection* col, std::ofstream &out) {
out << endl
<< "--------------- " << "print out of " << LCIO::MCPARTICLE
<< " collection " << "--------------- " << endl ;
out << endl
<< " flag: 0x" << hex << col->getFlag() << dec << endl ;
printParameters( col->getParameters(), out ) ;
int nParticles = col->getNumberOfElements() ;
out << " " << LCTOOLS::getSimulatorStatusString() << std::endl ;
// fill map with particle pointers and collection indices
typedef std::map< MCParticle*, int > PointerToIndexMap ;
PointerToIndexMap p2i_map ;
for( int k=0; k<nParticles; k++){
MCParticle* part = static_cast<MCParticle*>( col->getElementAt( k ) ) ;
p2i_map[ part ] = k ;
}
out << endl
<< "[ id ]index| PDG | px, py, pz | energy |gen|[simstat ]| vertex x, y , z | endpoint x, y , z | mass | charge | spin | colorflow | [parents] - [daughters]"
<< endl
<< endl ;
// loop over collection - preserve order
for( int index = 0 ; index < nParticles ; index++){
char buff[215];
MCParticle* part = static_cast<MCParticle*>( col->getElementAt( index ) ) ;
sprintf(buff, "[%8.8d]%5d|%10d|% 1.2e,% 1.2e,% 1.2e|% 1.2e| %1d |%s|% 1.2e,% 1.2e,% 1.2e|% 1.2e,% 1.2e,% 1.2e|% 1.2e|% 1.2e|% 1.2e,% 1.2e,% 1.2e| (%d, %d) | [",
part->id(), index, part->getPDG(),
part->getMomentum()[0], part->getMomentum()[1],
part->getMomentum()[2], part->getEnergy(),
part->getGeneratorStatus(),
LCTOOLS::getSimulatorStatusString( part ).c_str(),
part->getVertex()[0], part->getVertex()[1], part->getVertex()[2],
part->getEndpoint()[0], part->getEndpoint()[1],
part->getEndpoint()[2], part->getMass(), part->getCharge(),
part->getSpin()[0], part->getSpin()[1], part->getSpin()[2],
part->getColorFlow()[0], part->getColorFlow()[1] );
out << buff;
for(unsigned int k=0;k<part->getParents().size();k++){
if(k>0) out << "," ;
out << p2i_map[ part->getParents()[k] ] ;
}
out << "] - [" ;
for(unsigned int k=0;k<part->getDaughters().size();k++){
if(k>0) out << "," ;
out << p2i_map[ part->getDaughters()[k] ] ;
}
out << "] " << endl ;
}
out << endl
<< "-------------------------------------------------------------------------------- "
<< endl ;
return out;
}
// Write LCIO event to ASCII file
extern "C" void lcio_event_to_file ( LCEvent* evt, char* filename ) {
ofstream myfile;
myfile.open ( filename );
myfile << endl
<< "=========================================" << endl;
myfile << " - Event : " << evt->getEventNumber() << endl;
myfile << " - run: " << evt->getRunNumber() << endl;
myfile << " - timestamp " << evt->getTimeStamp() << endl;
myfile << " - weight " << evt->getWeight() << endl;
myfile << "=========================================" << endl;
LCTime evtTime( evt->getTimeStamp() ) ;
myfile << " date: " << evtTime.getDateString() << endl ;
myfile << " detector : " << evt->getDetectorName() << endl ;
myfile << " event parameters: " << endl ;
printParameters (evt->getParameters(), myfile );
const std::vector< std::string >* strVec = evt->getCollectionNames() ;
// loop over all collections:
std::vector< std::string >::const_iterator name ;
for( name = strVec->begin() ; name != strVec->end() ; name++){
LCCollection* col = evt->getCollection( *name ) ;
myfile << endl
<< " collection name : " << *name
<< endl
<< " parameters: " << endl ;
// call the detailed print functions depending on type name
if( evt->getCollection( *name )->getTypeName() == LCIO::MCPARTICLE ){
if( col->getTypeName() != LCIO::MCPARTICLE ){
myfile << " collection not of type " << LCIO::MCPARTICLE << endl ;
return ;
}
printMCParticles (col, myfile);
}
myfile.close();
}
}
// add collection to LCIO event
extern "C" void lcio_event_add_collection
( LCEventImpl* evt, LCCollectionVec* mcVec ) {
evt->addCollection( mcVec, LCIO::MCPARTICLE );
}
extern "C" MCParticle* lcio_event_particle_k ( LCEventImpl* evt, int k ) {
LCCollection* col = evt->getCollection( LCIO::MCPARTICLE );
MCParticle* mcp = static_cast<MCParticle*>(col->getElementAt ( k ));
return mcp;
}
// returns the index of the parent / daughter with incoming index
extern "C" int lcio_event_parent_k
( LCEventImpl* evt, int num_part, int k_parent) {
LCCollection* col = evt->getCollection( LCIO::MCPARTICLE );
int nParticles = col->getNumberOfElements() ;
std::vector<int> p_parents[nParticles];
typedef std::map< MCParticle*, int > PointerToIndexMap ;
PointerToIndexMap p2i_map ;
for( int k=0; k<nParticles; k++){
MCParticle* part = static_cast<MCParticle*>( col->getElementAt ( k ) );
p2i_map[ part ] = k;
}
for( int index = 0; index < nParticles ; index++){
MCParticle* part = static_cast<MCParticle*>( col->getElementAt ( index ) );
for(unsigned int k =0;k<part->getParents().size();k++){
p_parents[index].push_back( p2i_map[ part -> getParents()[k] ]) ;
}
}
return p_parents[num_part-1][k_parent-1] + 1;
}
extern "C" int lcio_event_daughter_k
( LCEventImpl* evt, int num_part, int k_daughter) {
LCCollection* col = evt->getCollection( LCIO::MCPARTICLE );
int nParticles = col->getNumberOfElements() ;
std::vector<int> p_daughters[nParticles];
typedef std::map< MCParticle*, int > PointerToIndexMap ;
PointerToIndexMap p2i_map ;
for( int k=0; k<nParticles; k++){
MCParticle* part = static_cast<MCParticle*>( col->getElementAt ( k ) );
p2i_map[ part ] = k;
}
for( int index = 0; index < nParticles ; index++){
MCParticle* part = static_cast<MCParticle*>( col->getElementAt ( index ) );
for(unsigned int k =0;k<part->getDaughters().size();k++){
p_daughters[index].push_back( p2i_map[ part -> getDaughters()[k] ]) ;
}
}
return p_daughters[num_part-1][k_daughter-1] + 1;
}
//////////////////////////////////////////////////////////////////////////
// MCParticle and LCCollectionVec functions
extern "C" LCCollectionVec* new_lccollection() {
LCCollectionVec* mcVec = new LCCollectionVec(LCIO::MCPARTICLE);
return mcVec;
}
extern "C" void add_particle_to_collection
(MCParticleImpl* mcp, LCCollectionVec* mcVec) {
mcVec->push_back( mcp );
}
extern "C" MCParticleImpl* new_lcio_particle
(double px, double py, double pz, int pdg, double mass, double charge, int status) {
MCParticleImpl* mcp = new MCParticleImpl() ;
double p[3] = { px, py, pz };
mcp->setPDG ( pdg );
mcp->setMomentum ( p );
mcp->setMass ( mass );
mcp->setCharge ( charge );
mcp->setGeneratorStatus ( status );
mcp->setCreatedInSimulation (false);
return mcp;
}
extern "C" MCParticleImpl* lcio_set_color_flow
(MCParticleImpl* mcp, int cflow1, int cflow2) {
int cflow[2] = { cflow1, cflow2 };
mcp->setColorFlow ( cflow );
return mcp;
}
extern "C" MCParticleImpl* lcio_particle_set_spin
(MCParticleImpl* mcp, const double spin1, const double spin2, const double spin3) {
float spin1_fl = spin1;
float spin2_fl = spin2;
float spin3_fl = spin3;
float spin[3] = { spin1_fl, spin2_fl, spin3_fl };
mcp->setSpin( spin );
return mcp;
}
extern "C" MCParticleImpl* lcio_particle_set_time
(MCParticleImpl* mcp, const double t) {
mcp->setTime( t );
return mcp;
}
extern "C" MCParticleImpl* lcio_particle_set_vertex
(MCParticleImpl* mcp, const double vx, const double vy, const double vz) {
double vtx[3] = { vx, vy, vz };
mcp->setVertex( vtx );
return mcp;
}
extern "C" void lcio_particle_add_parent
( MCParticleImpl* daughter , MCParticleImpl* parent) {
daughter->addParent( parent );
}
extern "C" int lcio_particle_get_generator_status ( MCParticleImpl* mcp) {
return mcp->getGeneratorStatus();
}
extern "C" int lcio_particle_get_pdg_code ( MCParticleImpl* mcp) {
return mcp->getPDG();
}
extern "C" int lcio_particle_flow ( MCParticleImpl* mcp, int col_index ) {
return mcp->getColorFlow()[ col_index ];
}
extern "C" double lcio_polarization_degree ( MCParticleImpl* mcp) {
return mcp->getSpin()[ 0 ];
}
extern "C" double lcio_polarization_theta ( MCParticleImpl* mcp) {
return mcp->getSpin()[ 1 ];
}
extern "C" double lcio_polarization_phi ( MCParticleImpl* mcp) {
return mcp->getSpin()[ 2 ];
}
extern "C" double lcio_three_momentum ( MCParticleImpl* mcp, int p_index ) {
return mcp->getMomentum()[ p_index ];
}
extern "C" double lcio_energy ( MCParticleImpl* mcp ) {
return mcp->getEnergy();
}
extern "C" double lcio_mass ( MCParticleImpl* mcp ) {
return mcp->getMass();
}
extern "C" int lcio_n_parents ( MCParticleImpl* mcp) {
return mcp->getParents().size();
}
extern "C" int lcio_n_daughters ( MCParticleImpl* mcp) {
return mcp->getDaughters().size();
}
extern "C" double lcio_vtx_x (MCParticleImpl* mcp) {
return mcp->getVertex()[0];
}
extern "C" double lcio_vtx_y (MCParticleImpl* mcp) {
return mcp->getVertex()[1];
}
extern "C" double lcio_vtx_z (MCParticleImpl* mcp) {
return mcp->getVertex()[2];
}
-extern "C" double lcio_prt_time (MCParticleImpl* mcp) {
+extern "C" float lcio_prt_time (MCParticleImpl* mcp) {
return mcp->getTime();
}
//////////////////////////////////////////////////////////////////////////
// LCWriter functions
extern "C" LCWriter* open_lcio_writer_new
( char* filename, int complevel ) {
LCWriter* lcWrt = LCFactory::getInstance()->createLCWriter();
lcWrt->setCompressionLevel (complevel);
lcWrt->open( filename, LCIO::WRITE_NEW );
return lcWrt;
}
extern "C" LCWriter* open_lcio_writer_append
( char* filename ) {
LCWriter* lcWrt = LCFactory::getInstance()->createLCWriter();
lcWrt->open( filename, LCIO::WRITE_APPEND );
return lcWrt;
}
// write the event
extern "C" LCWriter* lcio_write_event
( LCWriter* lcWrt, LCEventImpl* evt) {
lcWrt->writeEvent( evt );
return lcWrt;
}
// destructor
extern "C" void lcio_writer_delete ( LCWriter* lcWrt ) {
lcWrt->close();
delete lcWrt;
}
//////////////////////////////////////////////////////////////////////////
// LCReader functions
extern "C" LCReader* open_lcio_reader ( char* filename) {
LCReader* lcRdr = LCFactory::getInstance()->createLCReader();
lcRdr->open ( filename );
return lcRdr;
}
extern "C" LCReader* open_lcio_reader_direct_access ( char* filename) {
LCReader* lcRdr = LCFactory::getInstance()->createLCReader(LCReader::directAccess);
lcRdr->open ( filename );
return lcRdr;
}
extern "C" int lcio_get_n_runs ( LCReader* lcRdr ) {
return lcRdr->getNumberOfRuns();
}
extern "C" int lcio_get_n_events ( LCReader* lcRdr ) {
return lcRdr->getNumberOfEvents();
}
extern "C" void lcio_reader_delete ( LCReader* lcRdr ) {
lcRdr->close();
}
//////////////////////////////////////////////////////////////////////////
// LCRunHeader functions
// We set the process ID equal to the run number, and at it also as an
// explicit parameter.
extern "C" LCRunHeaderImpl* new_lcio_run_header( int rn ) {
LCRunHeaderImpl* runHdr = new LCRunHeaderImpl;
runHdr->setRunNumber (rn);
return runHdr;
}
extern "C" void run_header_set_simstring
(LCRunHeaderImpl* runHdr, char* simstring) {
runHdr->parameters().setValue ( "SimulationProgram", simstring );
}
extern "C" bool read_run_header ( LCReader* lcRdr , LCRunHeader* runHdr ) {
return ((runHdr = lcRdr->readNextRunHeader ()) != 0);
}
extern "C" void dump_run_header ( LCRunHeaderImpl* runHdr ) {
LCTOOLS::dumpRunHeader( runHdr );
}
extern "C" void write_run_header
(LCWriter* lcWrt, const LCRunHeaderImpl* runHdr) {
lcWrt->writeRunHeader (runHdr);
}
Index: trunk/src/lcio/LCIOWrap_dummy.f90
===================================================================
--- trunk/src/lcio/LCIOWrap_dummy.f90 (revision 8188)
+++ trunk/src/lcio/LCIOWrap_dummy.f90 (revision 8189)
@@ -1,694 +1,689 @@
! WHIZARD <<Version>> <<Date>>
!
! Copyright (C) 1999-2018 by
! Wolfgang Kilian <kilian@physik.uni-siegen.de>
! Thorsten Ohl <ohl@physik.uni-wuerzburg.de>
! Juergen Reuter <juergen.reuter@desy.de>
+!
! with contributions from
-! Fabian Bach <fabian.bach@t-online.de>
-! Bijan Chokoufe <bijan.chokoufe@desy.de>
-! Christian Speckner <cnspeckn@googlemail.com>
-! Marco Sekulla <marco.sekulla@kit.edu>
-! Christian Weiss <christian.weiss@desy.de>
-! Felix Braam, Sebastian Schmidt,
-! Hans-Werner Boschmann, Daniel Wiesler
+! cf. main AUTHORS file
!
! WHIZARD is free software; you can redistribute it and/or modify it
! under the terms of the GNU General Public License as published by
! the Free Software Foundation; either version 2, or (at your option)
! any later version.
!
! WHIZARD is distributed in the hope that it will be useful, but
! WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with this program; if not, write to the Free Software
! Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!! Dummy interface for non-existent LCIO library
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!! Tell the caller that this is not the true LCIO library
logical(c_bool) function lcio_available () bind(C)
use iso_c_binding
lcio_available = .false.
end function lcio_available
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!! LCEventImpl functions
! extern "C" void* new_lcio_event( int proc_id, int event_id ) {}
type(c_ptr) function new_lcio_event (proc_id, event_id, run_id) bind(C)
use iso_c_binding
integer(c_int), value :: proc_id, event_id, run_id
new_lcio_event = c_null_ptr
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function new_lcio_event
! extern "C" void lcio_set_weight( LCEventImpl* evt, double wgt )
subroutine lcio_set_weight (evt_obj, weight) bind(C)
use iso_c_binding
type(c_ptr), value :: evt_obj
real(c_double), value :: weight
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end subroutine lcio_set_weight
! extern "C" void lcio_set_alpha_qcd ( LCEventImpl* evt, double alphas )
subroutine lcio_set_alpha_qcd (evt_obj, alphas) bind(C)
use iso_c_binding
type(c_ptr), value :: evt_obj
real(c_double), value :: alphas
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end subroutine lcio_set_alpha_qcd
! extern "C" void lcio_set_scale ( LCEventImpl* evt, double scale )
subroutine lcio_set_scale (evt_obj, scale) bind(C)
use iso_c_binding
type(c_ptr), value :: evt_obj
real(c_double), value :: scale
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end subroutine lcio_set_scale
! extern "C" void lcio_set_sqrts ( LCEventImpl* evt, double sqrts )
subroutine lcio_set_sqrts (evt_obj, sqrts) bind(C)
use iso_c_binding
type(c_ptr), value :: evt_obj
real(c_double), value :: sqrts
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end subroutine lcio_set_sqrts
! extern "C" void lcio_set_xsec ( LCEventImpl* evt, double xsec, double xsec_err )
subroutine lcio_set_xsec (evt_obj, xsec, xsec_err) bind(C)
use iso_c_binding
type(c_ptr), value :: evt_obj
real(c_double), value :: xsec, xsec_err
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end subroutine lcio_set_xsec
! extern "C" void lcio_set_beam ( LCEventImpl* evt, int pdg, int beam )
subroutine lcio_set_beam (evt_obj, pdg, beam) bind(C)
use iso_c_binding
type(c_ptr), value :: evt_obj
integer(c_int), value :: pdg, beam
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end subroutine lcio_set_beam
! extern "C" void lcio_set_pol ( LCEventImpl* evt, double pol1, double pol2 )
subroutine lcio_set_pol (evt_obj, pol1, pol2) bind(C)
use iso_c_binding
type(c_ptr), value :: evt_obj
real(c_double), value :: pol1, pol2
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end subroutine lcio_set_pol
! extern "C" void lcio_set_beam_file ( LCEventImpl* evt, char* file ) {
subroutine lcio_set_beam_file (evt_obj, file) bind(C)
use iso_c_binding
type(c_ptr), value :: evt_obj
character(len=1, kind=c_char), dimension(*), intent(in) :: file
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end subroutine lcio_set_beam_file
! extern "C" void lcio_set_process_name ( LCEventImpl* evt, char* name ) {
subroutine lcio_set_process_name (evt_obj, name) bind(C)
use iso_c_binding
type(c_ptr), value :: evt_obj
character(len=1, kind=c_char), dimension(*), intent(in) :: name
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end subroutine lcio_set_process_name
! extern "C" void lcio_event_delete( void* evt) {}
subroutine lcio_event_delete (evt_obj) bind(C)
use iso_c_binding
type(c_ptr), value :: evt_obj
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end subroutine lcio_event_delete
! extern "C" LCEvent* read_lcio_event ( LCReader* lcRdr )
type (c_ptr) function read_lcio_event (io_obj) bind(C)
use iso_c_binding
type(c_ptr), value :: io_obj
read_lcio_event = c_null_ptr
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function read_lcio_event
! extern "C" void dump_lcio_event ( LCEventImpl* evt )
subroutine dump_lcio_event (evt_obj) bind(C)
use iso_c_binding
type(c_ptr), value :: evt_obj
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end subroutine dump_lcio_event
! extern "C" int lcio_get_event_number (LCEvent* evt)
integer(c_int) function lcio_event_get_event_number (evt_obj) bind(C)
use iso_c_binding
type(c_ptr), value :: evt_obj
lcio_event_get_event_number = 0
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function lcio_event_get_event_number
! extern "C" int lcio_event_signal_process_id (LCEvent* evt)
integer(c_int) function lcio_event_signal_process_id (evt_obj) bind(C)
use iso_c_binding
type(c_ptr), value :: evt_obj
lcio_event_signal_process_id = 0
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function lcio_event_signal_process_id
! extern "C" int lcio_event_get_n_particles (LCEvent* evt)
integer(c_int) function lcio_event_get_n_particles (evt_obj) bind(C)
use iso_c_binding
type(c_ptr), value :: evt_obj
lcio_event_get_n_particles = 0
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function lcio_event_get_n_particles
! extern "C" double lcio_event_get_alpha_qcd (LCEvent* evt)
real(c_double) function lcio_event_get_alpha_qcd (evt_obj) bind(C)
use iso_c_binding
type(c_ptr), value :: evt_obj
lcio_event_get_alpha_qcd = 0._c_double
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function lcio_event_get_alpha_qcd
! extern "C" double lcio_event_get_scale (LCEvent* evt)
real(c_double) function lcio_event_get_scale (evt_obj) bind(C)
use iso_c_binding
type(c_ptr), value :: evt_obj
lcio_event_get_scale = 0._c_double
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function lcio_event_get_scale
! extern "C" void lcio_event_to_file ( LCEvent* evt, char* filename )
subroutine lcio_event_to_file (evt_obj, filename) bind(C)
use iso_c_binding
type(c_ptr), value :: evt_obj
character(c_char), dimension(*), intent(in) :: filename
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end subroutine lcio_event_to_file
! extern "C" void lcio_event_add_collection ( LCEventImpl* evt, LCCollectionVec* mcVec )
subroutine lcio_event_add_collection (evt_obj, lccoll_obj) bind(C)
use iso_c_binding
type(c_ptr), value :: evt_obj, lccoll_obj
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end subroutine lcio_event_add_collection
! extern "C" MCParticleImpl* lcio_event_particle_k ( LCEventImpl* evt, int k )
type(c_ptr) function lcio_event_particle_k (evt_obj, k) bind(C)
use iso_c_binding
type(c_ptr), value :: evt_obj
integer(c_int), value :: k
lcio_event_particle_k = c_null_ptr
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function lcio_event_particle_k
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!! MCParticleImpl and LCCollectionVec functions
! extern "C" LCCollectionVec* new_lccollection()
type(c_ptr) function new_lccollection () bind(C)
use iso_c_binding
new_lccollection = c_null_ptr
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function new_lccollection
! extern "C" void add_particle_to_collection (MCParticleImpl* mcp, LCCollectionVec* mcVec)
subroutine add_particle_to_collection (prt_obj, lccoll_obj) bind(C)
use iso_c_binding
type(c_ptr), value :: prt_obj, lccoll_obj
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end subroutine add_particle_to_collection
! extern "C" MCParticleImpl* new_lcio_particle(void* momentum, int pdg_id, int status)
type(c_ptr) function new_lcio_particle &
(px, py, pz, pdg_id, mass, charge, status) bind(C)
use iso_c_binding
integer(c_int), value :: pdg_id, status
real(c_double), value :: px, py, pz, mass, charge
new_lcio_particle = c_null_ptr
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function new_lcio_particle
! extern "C" void lcio_particle_add_parent
subroutine lcio_particle_add_parent (io_obj1, io_obj2) bind(C)
use iso_c_binding
type(c_ptr), value :: io_obj1, io_obj2
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end subroutine lcio_particle_add_parent
! extern "C" MCParticleImpl* lcio_set_color_flow
subroutine lcio_set_color_flow (prt_obj, cflow1, cflow2) bind(C)
use iso_c_binding
type(c_ptr), value :: prt_obj
integer(c_int), value :: cflow1, cflow2
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end subroutine lcio_set_color_flow
! extern "C" MCParticleImpl* lcio_particle_set_spin
! (MCParticleImpl* mcp, int s1, int s2, int s3)
subroutine lcio_particle_set_spin (prt_obj, s1, s2, s3) bind(C)
use iso_c_binding
type(c_ptr), value :: prt_obj
real(c_double), value :: s1, s2, s3
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end subroutine lcio_particle_set_spin
! extern "C" MCParticleImpl* lcio_particle_set_time
subroutine lcio_particle_set_time (prt_obj, t) bind(C)
use iso_c_binding
type(c_ptr), value :: prt_obj
real(c_double), value :: t
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end subroutine lcio_particle_set_time
! extern "C" MCParticleImpl* lcio_particle_set_vertex
! (MCParticleImpl* mcp, const double vx, const double vy, const double vz)
subroutine lcio_particle_set_vertex (prt_obj, vx, vy, vz) bind(C)
use iso_c_binding
type(c_ptr), value :: prt_obj
real(c_double), value :: vx, vy, vz
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end subroutine lcio_particle_set_vertex
! extern "C" double lcio_polarization_degree ( MCParticleImpl* mcp)
real(c_double) function lcio_polarization_degree (prt_obj) bind(C)
use iso_c_binding
type(c_ptr), value :: prt_obj
lcio_polarization_degree = 0._c_double
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function lcio_polarization_degree
! extern "C" double lcio_polarization_theta ( MCParticleImpl* mcp)
real(c_double) function lcio_polarization_theta (prt_obj) bind(C)
use iso_c_binding
type(c_ptr), value :: prt_obj
lcio_polarization_theta = 0._c_double
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function lcio_polarization_theta
! extern "C" double lcio_polarization_phi ( MCParticleImpl* mcp)
real(c_double) function lcio_polarization_phi (prt_obj) bind(C)
use iso_c_binding
type(c_ptr), value :: prt_obj
lcio_polarization_phi = 0._c_double
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function lcio_polarization_phi
! extern "C" const int* lcio_particle_flow
integer(c_int) function lcio_particle_flow (evt_obj, col_index) bind(C)
use iso_c_binding
type(c_ptr), value :: evt_obj
integer(c_int) :: col_index
lcio_particle_flow = 0_c_int
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function lcio_particle_flow
! extern "C" int lcio_particle_get_generator_status ( MCParticleImpl* mcp)
integer(c_int) function lcio_particle_get_generator_status (prt_obj) bind(C)
use iso_c_binding
type(c_ptr), value :: prt_obj
lcio_particle_get_generator_status = 0_c_int
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function lcio_particle_get_generator_status
! extern "C" int lcio_particle_get_pdg_code ( MCParticleImpl* mcp)
integer(c_int) function lcio_particle_get_pdg_code (prt_obj) bind(C)
use iso_c_binding
type(c_ptr), value :: prt_obj
lcio_particle_get_pdg_code = 0_c_int
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function lcio_particle_get_pdg_code
! extern "C" double lcio_three_momentum ( MCParticleImpl* mcp, int p_index ) {
real(c_double) function lcio_three_momentum (prt_obj, p_index) bind (C)
use iso_c_binding
type(c_ptr), value :: prt_obj
integer(c_int), value :: p_index
lcio_three_momentum = 0
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function lcio_three_momentum
! extern "C" double lcio_energy ( MCParticleImpl* mcp) {
real(c_double) function lcio_energy (prt_obj) bind (C)
use iso_c_binding
type(c_ptr), value :: prt_obj
lcio_energy = 0
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function lcio_energy
! extern "C" double lcio_mass ( MCParticleImpl* mcp) {
real(c_double) function lcio_mass (prt_obj) bind (C)
use iso_c_binding
type(c_ptr), value :: prt_obj
lcio_mass = 0
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function lcio_mass
! extern "C" int lcio_n_parents ( MCParticleImpl* mcp)
integer(c_int) function lcio_n_parents (prt_obj) bind (C)
use iso_c_binding
type(c_ptr), value :: prt_obj
lcio_n_parents = 0_c_int
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function lcio_n_parents
! extern "C" int lcio_n_daughters ( MCParticleImpl* mcp)
integer(c_int) function lcio_n_daughters (prt_obj) bind (C)
use iso_c_binding
type(c_ptr), value :: prt_obj
lcio_n_daughters = 0_c_int
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function lcio_n_daughters
! extern "C" double lcio_vtx_x (MCParticleImpl* mcp)
real(c_double) function lcio_vtx_x (prt_obj) bind (C)
use iso_c_binding
type(c_ptr), value :: prt_obj
lcio_vtx_x = 0
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function lcio_vtx_x
! extern "C" double lcio_vtx_y (MCParticleImpl* mcp)
real(c_double) function lcio_vtx_y (prt_obj) bind (C)
use iso_c_binding
type(c_ptr), value :: prt_obj
lcio_vtx_y = 0
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function lcio_vtx_y
! extern "C" double lcio_vtx_z (MCParticleImpl* mcp)
real(c_double) function lcio_vtx_z (prt_obj) bind (C)
use iso_c_binding
type(c_ptr), value :: prt_obj
lcio_vtx_z = 0
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function lcio_vtx_z
! extern "C" double lcio_prt_time (MCParticleImpl* mcp) {
-real(c_double) function lcio_prt_time (prt_obj) bind(C)
+real(c_float) function lcio_prt_time (prt_obj) bind(C)
use iso_c_binding
type(c_ptr), value :: prt_obj
lcio_prt_time = 0
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function lcio_prt_time
! extern "C" int lcio_event_daughter_k ( LCEventImpl* evt, int num_part, int k_daughter)
integer(c_int) function lcio_event_daughter_k &
(evt_obj, num_part, k_daughter) bind(C)
use iso_c_binding
type(c_ptr), value :: evt_obj
integer(c_int), value :: num_part, k_daughter
lcio_event_daughter_k = 0_c_int
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function lcio_event_daughter_k
! extern "C" int lcio_event_parent_k ( LCEventImpl* evt, int num_part, int k_parent)
integer(c_int) function lcio_event_parent_k &
(evt_obj, num_part, k_parent) bind(C)
use iso_c_binding
type(c_ptr), value :: evt_obj
integer(c_int), value :: num_part, k_parent
lcio_event_parent_k = 0_c_int
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function lcio_event_parent_k
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!! LCWriter functions
! extern "C" LCWriter* open_lcio_writer_new
type (c_ptr) function open_lcio_writer_new (filename, complevel) bind(C)
use iso_c_binding
character(c_char), dimension(*), intent(in) :: filename
integer(c_int), value :: complevel
open_lcio_writer_new = c_null_ptr
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function open_lcio_writer_new
! extern "C" LCWriter* lcio_writer_delete
subroutine lcio_writer_delete (io_obj) bind(C)
use iso_c_binding
type(c_ptr), value :: io_obj
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end subroutine lcio_writer_delete
! extern "C" LCWriter* lcio_write_event
subroutine lcio_write_event (io_obj, evt_obj) bind(C)
use iso_c_binding
type(c_ptr), value :: io_obj, evt_obj
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end subroutine lcio_write_event
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!! LCReader functions
! extern "C" LCReader* open_lcio_reader ()
type(c_ptr) function open_lcio_reader (filename) bind(C)
use iso_c_binding
character(c_char), dimension(*), intent(in) :: filename
open_lcio_reader = c_null_ptr
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function open_lcio_reader
! extern "C" LCReader* open_lcio_reader ()
type(c_ptr) function open_lcio_reader_direct_access (filename) bind(C)
use iso_c_binding
character(c_char), dimension(*), intent(in) :: filename
open_lcio_reader_direct_access = c_null_ptr
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function open_lcio_reader_direct_access
! extern "C" void lcio_get_n_runs ( LCReader* lcRdr )
integer(c_int) function lcio_get_n_runs (io_obj) bind(C)
use iso_c_binding
type(c_ptr), value :: io_obj
lcio_get_n_runs = 0_c_int
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function lcio_get_n_runs
! extern "C" void lcio_get_n_events ( LCReader* lcRdr )
integer(c_int) function lcio_get_n_events (io_obj) bind(C)
use iso_c_binding
type(c_ptr), value :: io_obj
lcio_get_n_events = 0_c_int
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function lcio_get_n_events
! extern "C" void lcio_reader_delete ( LCReader* lcRdr )
subroutine lcio_reader_delete (io_obj) bind(C)
use iso_c_binding
type(c_ptr), value :: io_obj
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end subroutine lcio_reader_delete
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!! LCRunHeader functions
! extern "C" LCRunHeaderImpl* new_lcio_run_header( int run_id ) {
type(c_ptr) function new_lcio_run_header (run_id) bind(C)
use iso_c_binding
integer(c_int), value :: run_id
new_lcio_run_header = c_null_ptr
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end function new_lcio_run_header
! extern "C" void run_header_set_simstring (LCRunHeaderImpl* runHdr, char* simstring)
subroutine run_header_set_simstring (runhdr_obj, simstring) bind(C)
use iso_c_binding
type(c_ptr), value :: runhdr_obj
character(c_char), dimension(*), intent(in) :: simstring
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end subroutine run_header_set_simstring
! extern "C" void dump_run_header ( LCRunHeaderImpl* runHdr )
subroutine dump_run_header (runhdr_obj) bind(C)
use iso_c_binding
type(c_ptr), value :: runhdr_obj
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end subroutine dump_run_header
! extern "C" void write_run_header (LCWriter* lcWrt, const LCRunHeaderImpl* runHdr)
subroutine write_run_header (lcwrt_obj, runhdr_obj) bind(C)
use iso_c_binding
type(c_ptr), value :: lcwrt_obj, runhdr_obj
write (0, "(A)") "***********************************************************"
write (0, "(A)") "*** LCIO: Error: library not linked, WHIZARD terminates ***"
write (0, "(A)") "***********************************************************"
stop
end subroutine write_run_header
Index: trunk/src/events/events.nw
===================================================================
--- trunk/src/events/events.nw (revision 8188)
+++ trunk/src/events/events.nw (revision 8189)
@@ -1,16364 +1,16371 @@
%% -*- ess-noweb-default-code-mode: f90-mode; noweb-default-code-mode: f90-mode; -*-
% WHIZARD code as NOWEB source: event handling objects
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
\chapter{Generic Event Handling}
\includemodulegraph{events}
Event records allow the MC to communicate with the outside world. The
event record should exhibit the observable contents of a physical
event. We should be able to read and write events. The actual
implementation of the event need not be defined yet, for that purpose.
We have the following basic modules:
\begin{description}
\item[event\_base]
Abstract base type for event records. The base type contains a
reference to a [[particle_set_t]] object as the event core, and it
holds some data that we should always expect, such as the squared
matrix element and event weight.
\item[eio\_data]
Transparent container for the metadata of an event sample.
\item[eio\_base]
Abstract base type for event-record input and output. The
implementations of this base type represent specific event I/O
formats.
\end{description}
These are the implementation modules:
\begin{description}
\item[eio\_checkpoints]
Auxiliary output format. The only purpose is to provide screen
diagnostics during event output.
\item[eio\_callback]
Auxiliary output format. The only purpose is to execute a callback
procedure, so we have a hook for external access during event output.
\item[eio\_weights]
Print some event summary data, no details. The main use if for
testing purposes.
\item[eio\_dump]
Dump the contents of WHIZARD's [[particle_set]] internal record,
using the [[write]] method of that record as-is. The main use if for
testing purposes.
\item[hep\_common]
Implements traditional HEP common blocks that are (still) used by
some of the event I/O formats below.
\item[hepmc\_interface]
Access particle objects of the HepMC package. Functional only if this
package is linked.
\item[lcio\_interface]
Access objects of the LCIO package. Functional only if this
package is linked.
\item[hep\_events]
Interface between the event record and the common blocks.
\item[eio\_ascii]
Collection of event output formats that write ASCII files.
\item[eio\_lhef]
LHEF for input and output.
\item[eio\_stdhep]
Support for the StdHEP format (binary, machine-independent).
\item[eio\_hepmc]
Support for the HepMC format (C++).
\item[eio\_lcio]
Support for the LCIO format (C++).
\end{description}
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
\section{Generic Event Handling}
We introduce events first in form of an abstract type, together with
some utilities. Abstract events can be used by other modules, in
particular event I/O, without introducing an explicit dependency on
the event implementation.
<<[[event_base.f90]]>>=
<<File header>>
module event_base
<<Use kinds>>
use kinds, only: i64
<<Use strings>>
use io_units
use string_utils, only: lower_case
use diagnostics
use model_data
use particles
<<Standard module head>>
<<Event base: public>>
<<Event base: parameters>>
<<Event base: types>>
<<Event base: interfaces>>
contains
<<Event base: procedures>>
end module event_base
@ %def event_base
@
\subsection{generic event type}
<<Event base: public>>=
public :: generic_event_t
<<Event base: types>>=
type, abstract :: generic_event_t
!private
logical :: particle_set_is_valid = .false.
type(particle_set_t), pointer :: particle_set => null ()
logical :: sqme_ref_known = .false.
real(default) :: sqme_ref = 0
logical :: sqme_prc_known = .false.
real(default) :: sqme_prc = 0
logical :: weight_ref_known = .false.
real(default) :: weight_ref = 0
logical :: weight_prc_known = .false.
real(default) :: weight_prc = 0
logical :: excess_prc_known = .false.
real(default) :: excess_prc = 0
integer :: n_alt = 0
logical :: sqme_alt_known = .false.
real(default), dimension(:), allocatable :: sqme_alt
logical :: weight_alt_known = .false.
real(default), dimension(:), allocatable :: weight_alt
contains
<<Event base: generic event: TBP>>
end type generic_event_t
@ %def generic_event_t
@
\subsection{Initialization}
This determines the number of alternate weights and sqme values.
<<Event base: generic event: TBP>>=
procedure :: base_init => generic_event_init
<<Event base: procedures>>=
subroutine generic_event_init (event, n_alt)
class(generic_event_t), intent(out) :: event
integer, intent(in) :: n_alt
event%n_alt = n_alt
allocate (event%sqme_alt (n_alt))
allocate (event%weight_alt (n_alt))
end subroutine generic_event_init
@ %def generic_event_init
@
\subsection{Access particle set}
The particle set is the core of the event. We allow access to it via
a pointer, and we maintain the information whether the particle set
is valid, i.e., has been filled with meaningful data.
<<Event base: generic event: TBP>>=
procedure :: has_valid_particle_set => generic_event_has_valid_particle_set
procedure :: accept_particle_set => generic_event_accept_particle_set
procedure :: discard_particle_set => generic_event_discard_particle_set
<<Event base: procedures>>=
function generic_event_has_valid_particle_set (event) result (flag)
class(generic_event_t), intent(in) :: event
logical :: flag
flag = event%particle_set_is_valid
end function generic_event_has_valid_particle_set
subroutine generic_event_accept_particle_set (event)
class(generic_event_t), intent(inout) :: event
event%particle_set_is_valid = .true.
end subroutine generic_event_accept_particle_set
subroutine generic_event_discard_particle_set (event)
class(generic_event_t), intent(inout) :: event
event%particle_set_is_valid = .false.
end subroutine generic_event_discard_particle_set
@ %def generic_event_has_valid_particle_set
@ %def generic_event_accept_particle_set
@ %def generic_event_discard_particle_set
@
These procedures deal with the particle set directly. Return the pointer:
<<Event base: generic event: TBP>>=
procedure :: get_particle_set_ptr => generic_event_get_particle_set_ptr
<<Event base: procedures>>=
function generic_event_get_particle_set_ptr (event) result (ptr)
class(generic_event_t), intent(in) :: event
type(particle_set_t), pointer :: ptr
ptr => event%particle_set
end function generic_event_get_particle_set_ptr
@ %def generic_event_get_particle_set_ptr
@
Let it point to some existing particle set:
<<Event base: generic event: TBP>>=
procedure :: link_particle_set => generic_event_link_particle_set
<<Event base: procedures>>=
subroutine generic_event_link_particle_set (event, particle_set)
class(generic_event_t), intent(inout) :: event
type(particle_set_t), intent(in), target :: particle_set
event%particle_set => particle_set
call event%accept_particle_set ()
end subroutine generic_event_link_particle_set
@ %def generic_event_link_particle_set
@
\subsection{Access sqme and weight}
There are several incarnations: the current value, a reference value,
alternate values.
<<Event base: generic event: TBP>>=
procedure :: sqme_prc_is_known => generic_event_sqme_prc_is_known
procedure :: sqme_ref_is_known => generic_event_sqme_ref_is_known
procedure :: sqme_alt_is_known => generic_event_sqme_alt_is_known
procedure :: weight_prc_is_known => generic_event_weight_prc_is_known
procedure :: weight_ref_is_known => generic_event_weight_ref_is_known
procedure :: weight_alt_is_known => generic_event_weight_alt_is_known
procedure :: excess_prc_is_known => generic_event_excess_prc_is_known
<<Event base: procedures>>=
function generic_event_sqme_prc_is_known (event) result (flag)
class(generic_event_t), intent(in) :: event
logical :: flag
flag = event%sqme_prc_known
end function generic_event_sqme_prc_is_known
function generic_event_sqme_ref_is_known (event) result (flag)
class(generic_event_t), intent(in) :: event
logical :: flag
flag = event%sqme_ref_known
end function generic_event_sqme_ref_is_known
function generic_event_sqme_alt_is_known (event) result (flag)
class(generic_event_t), intent(in) :: event
logical :: flag
flag = event%sqme_alt_known
end function generic_event_sqme_alt_is_known
function generic_event_weight_prc_is_known (event) result (flag)
class(generic_event_t), intent(in) :: event
logical :: flag
flag = event%weight_prc_known
end function generic_event_weight_prc_is_known
function generic_event_weight_ref_is_known (event) result (flag)
class(generic_event_t), intent(in) :: event
logical :: flag
flag = event%weight_ref_known
end function generic_event_weight_ref_is_known
function generic_event_weight_alt_is_known (event) result (flag)
class(generic_event_t), intent(in) :: event
logical :: flag
flag = event%weight_alt_known
end function generic_event_weight_alt_is_known
function generic_event_excess_prc_is_known (event) result (flag)
class(generic_event_t), intent(in) :: event
logical :: flag
flag = event%excess_prc_known
end function generic_event_excess_prc_is_known
@ %def generic_event_sqme_prc_is_known
@ %def generic_event_sqme_ref_is_known
@ %def generic_event_sqme_alt_is_known
@ %def generic_event_weight_prc_is_known
@ %def generic_event_weight_ref_is_known
@ %def generic_event_weight_alt_is_known
@ %def generic_event_excess_prc_is_known
@
<<Event base: generic event: TBP>>=
procedure :: get_n_alt => generic_event_get_n_alt
<<Event base: procedures>>=
function generic_event_get_n_alt (event) result (n)
class(generic_event_t), intent(in) :: event
integer :: n
n = event%n_alt
end function generic_event_get_n_alt
@ %def generic_event_get_n_alt
@
<<Event base: generic event: TBP>>=
procedure :: get_sqme_prc => generic_event_get_sqme_prc
procedure :: get_sqme_ref => generic_event_get_sqme_ref
generic :: get_sqme_alt => &
generic_event_get_sqme_alt_0, generic_event_get_sqme_alt_1
procedure :: generic_event_get_sqme_alt_0
procedure :: generic_event_get_sqme_alt_1
procedure :: get_weight_prc => generic_event_get_weight_prc
procedure :: get_weight_ref => generic_event_get_weight_ref
generic :: get_weight_alt => &
generic_event_get_weight_alt_0, generic_event_get_weight_alt_1
procedure :: generic_event_get_weight_alt_0
procedure :: generic_event_get_weight_alt_1
procedure :: get_excess_prc => generic_event_get_excess_prc
<<Event base: procedures>>=
function generic_event_get_sqme_prc (event) result (sqme)
class(generic_event_t), intent(in) :: event
real(default) :: sqme
if (event%sqme_prc_known) then
sqme = event%sqme_prc
else
sqme = 0
end if
end function generic_event_get_sqme_prc
function generic_event_get_sqme_ref (event) result (sqme)
class(generic_event_t), intent(in) :: event
real(default) :: sqme
if (event%sqme_ref_known) then
sqme = event%sqme_ref
else
sqme = 0
end if
end function generic_event_get_sqme_ref
function generic_event_get_sqme_alt_0 (event, i) result (sqme)
class(generic_event_t), intent(in) :: event
integer, intent(in) :: i
real(default) :: sqme
if (event%sqme_alt_known) then
sqme = event%sqme_alt(i)
else
sqme = 0
end if
end function generic_event_get_sqme_alt_0
function generic_event_get_sqme_alt_1 (event) result (sqme)
class(generic_event_t), intent(in) :: event
real(default), dimension(event%n_alt) :: sqme
sqme = event%sqme_alt
end function generic_event_get_sqme_alt_1
function generic_event_get_weight_prc (event) result (weight)
class(generic_event_t), intent(in) :: event
real(default) :: weight
if (event%weight_prc_known) then
weight = event%weight_prc
else
weight = 0
end if
end function generic_event_get_weight_prc
function generic_event_get_weight_ref (event) result (weight)
class(generic_event_t), intent(in) :: event
real(default) :: weight
if (event%weight_ref_known) then
weight = event%weight_ref
else
weight = 0
end if
end function generic_event_get_weight_ref
function generic_event_get_weight_alt_0 (event, i) result (weight)
class(generic_event_t), intent(in) :: event
integer, intent(in) :: i
real(default) :: weight
if (event%weight_alt_known) then
weight = event%weight_alt(i)
else
weight = 0
end if
end function generic_event_get_weight_alt_0
function generic_event_get_weight_alt_1 (event) result (weight)
class(generic_event_t), intent(in) :: event
real(default), dimension(event%n_alt) :: weight
weight = event%weight_alt
end function generic_event_get_weight_alt_1
function generic_event_get_excess_prc (event) result (excess)
class(generic_event_t), intent(in) :: event
real(default) :: excess
if (event%excess_prc_known) then
excess = event%excess_prc
else
excess = 0
end if
end function generic_event_get_excess_prc
@ %def generic_event_get_sqme_prc
@ %def generic_event_get_sqme_ref
@ %def generic_event_get_sqme_alt
@ %def generic_event_get_weight_prc
@ %def generic_event_get_weight_ref
@ %def generic_event_get_weight_alt
@ %def generic_event_get_excess_prc
@
<<Event base: generic event: TBP>>=
procedure :: set_sqme_prc => generic_event_set_sqme_prc
procedure :: set_sqme_ref => generic_event_set_sqme_ref
procedure :: set_sqme_alt => generic_event_set_sqme_alt
procedure :: set_weight_prc => generic_event_set_weight_prc
procedure :: set_weight_ref => generic_event_set_weight_ref
procedure :: set_weight_alt => generic_event_set_weight_alt
procedure :: set_excess_prc => generic_event_set_excess_prc
<<Event base: procedures>>=
subroutine generic_event_set_sqme_prc (event, sqme)
class(generic_event_t), intent(inout) :: event
real(default), intent(in) :: sqme
event%sqme_prc = sqme
event%sqme_prc_known = .true.
end subroutine generic_event_set_sqme_prc
subroutine generic_event_set_sqme_ref (event, sqme)
class(generic_event_t), intent(inout) :: event
real(default), intent(in) :: sqme
event%sqme_ref = sqme
event%sqme_ref_known = .true.
end subroutine generic_event_set_sqme_ref
subroutine generic_event_set_sqme_alt (event, sqme)
class(generic_event_t), intent(inout) :: event
real(default), dimension(:), intent(in) :: sqme
event%sqme_alt = sqme
event%sqme_alt_known = .true.
end subroutine generic_event_set_sqme_alt
subroutine generic_event_set_weight_prc (event, weight)
class(generic_event_t), intent(inout) :: event
real(default), intent(in) :: weight
event%weight_prc = weight
event%weight_prc_known = .true.
end subroutine generic_event_set_weight_prc
subroutine generic_event_set_weight_ref (event, weight)
class(generic_event_t), intent(inout) :: event
real(default), intent(in) :: weight
event%weight_ref = weight
event%weight_ref_known = .true.
end subroutine generic_event_set_weight_ref
subroutine generic_event_set_weight_alt (event, weight)
class(generic_event_t), intent(inout) :: event
real(default), dimension(:), intent(in) :: weight
event%weight_alt = weight
event%weight_alt_known = .true.
end subroutine generic_event_set_weight_alt
subroutine generic_event_set_excess_prc (event, excess)
class(generic_event_t), intent(inout) :: event
real(default), intent(in) :: excess
event%excess_prc = excess
event%excess_prc_known = .true.
end subroutine generic_event_set_excess_prc
@ %def generic_event_set_sqme_prc
@ %def generic_event_set_sqme_ref
@ %def generic_event_set_sqme_alt
@ %def generic_event_set_weight_prc
@ %def generic_event_set_weight_ref
@ %def generic_event_set_weight_alt
@ %def generic_event_set_excess_prc
@
Set the appropriate entry directly.
<<Event base: generic event: TBP>>=
procedure :: set => generic_event_set
<<Event base: procedures>>=
subroutine generic_event_set (event, &
weight_ref, weight_prc, weight_alt, &
excess_prc, &
sqme_ref, sqme_prc, sqme_alt)
class(generic_event_t), intent(inout) :: event
real(default), intent(in), optional :: weight_ref, weight_prc
real(default), intent(in), optional :: sqme_ref, sqme_prc
real(default), dimension(:), intent(in), optional :: sqme_alt, weight_alt
real(default), intent(in), optional :: excess_prc
if (present (sqme_prc)) then
call event%set_sqme_prc (sqme_prc)
end if
if (present (sqme_ref)) then
call event%set_sqme_ref (sqme_ref)
end if
if (present (sqme_alt)) then
call event%set_sqme_alt (sqme_alt)
end if
if (present (weight_prc)) then
call event%set_weight_prc (weight_prc)
end if
if (present (weight_ref)) then
call event%set_weight_ref (weight_ref)
end if
if (present (weight_alt)) then
call event%set_weight_alt (weight_alt)
end if
if (present (excess_prc)) then
call event%set_excess_prc (excess_prc)
end if
end subroutine generic_event_set
@ %def generic_event_set
@
\subsection{Pure Virtual Methods}
These procedures can only implemented in the concrete implementation.
Output (verbose, depending on parameters).
<<Event base: generic event: TBP>>=
procedure (generic_event_write), deferred :: write
<<Event base: interfaces>>=
abstract interface
subroutine generic_event_write (object, unit, &
show_process, show_transforms, &
show_decay, verbose, testflag)
import
class(generic_event_t), intent(in) :: object
integer, intent(in), optional :: unit
logical, intent(in), optional :: show_process
logical, intent(in), optional :: show_transforms
logical, intent(in), optional :: show_decay
logical, intent(in), optional :: verbose
logical, intent(in), optional :: testflag
end subroutine generic_event_write
end interface
@ %def generic_event_write
@
Generate an event, based on a selector index [[i_mci]], and optionally on an
extra set of random numbers [[r]]. For the main bunch of random numbers that
the generator needs, the event object should contain its own generator.
<<Event base: generic event: TBP>>=
procedure (generic_event_generate), deferred :: generate
<<Event base: interfaces>>=
abstract interface
subroutine generic_event_generate (event, i_mci, r, i_nlo)
import
class(generic_event_t), intent(inout) :: event
integer, intent(in) :: i_mci
real(default), dimension(:), intent(in), optional :: r
integer, intent(in), optional :: i_nlo
end subroutine generic_event_generate
end interface
@ %def event_generate
@
Alternative : inject a particle set that is supposed to represent the hard
process.
How this determines the event, is dependent on the event structure,
therefore this is a deferred method.
<<Event base: generic event: TBP>>=
procedure (generic_event_set_hard_particle_set), deferred :: &
set_hard_particle_set
<<Event base: interfaces>>=
abstract interface
subroutine generic_event_set_hard_particle_set (event, particle_set)
import
class(generic_event_t), intent(inout) :: event
type(particle_set_t), intent(in) :: particle_set
end subroutine generic_event_set_hard_particle_set
end interface
@ %def generic_event_set_hard_particle_set
@ Event index handlers.
<<Event base: generic event: TBP>>=
procedure (generic_event_set_index), deferred :: set_index
procedure (generic_event_handler), deferred :: reset_index
procedure (generic_event_increment_index), deferred :: increment_index
@
<<Event base: interfaces>>=
abstract interface
subroutine generic_event_set_index (event, index)
import
class(generic_event_t), intent(inout) :: event
integer, intent(in) :: index
end subroutine generic_event_set_index
end interface
abstract interface
subroutine generic_event_handler (event)
import
class(generic_event_t), intent(inout) :: event
end subroutine generic_event_handler
end interface
abstract interface
subroutine generic_event_increment_index (event, offset)
import
class(generic_event_t), intent(inout) :: event
integer, intent(in), optional :: offset
end subroutine generic_event_increment_index
end interface
@ %def generic_event_set_index
@ %def generic_event_increment_index
@ %def generic_event_handler
@ Evaluate any expressions associated with the event. No argument needed.
<<Event base: generic event: TBP>>=
procedure (generic_event_handler), deferred :: evaluate_expressions
@
Select internal parameters
<<Event base: generic event: TBP>>=
procedure (generic_event_select), deferred :: select
<<Event base: interfaces>>=
abstract interface
subroutine generic_event_select (event, i_mci, i_term, channel)
import
class(generic_event_t), intent(inout) :: event
integer, intent(in) :: i_mci, i_term, channel
end subroutine generic_event_select
end interface
@ %def generic_event_select
@ Return a pointer to the model for the currently active process.
<<Event base: generic event: TBP>>=
procedure (generic_event_get_model_ptr), deferred :: get_model_ptr
<<Event base: interfaces>>=
abstract interface
function generic_event_get_model_ptr (event) result (model)
import
class(generic_event_t), intent(in) :: event
class(model_data_t), pointer :: model
end function generic_event_get_model_ptr
end interface
@ %def generic_event_get_model_ptr
@ Return data used by external event formats.
<<Event base: generic event: TBP>>=
procedure (generic_event_has_index), deferred :: has_index
procedure (generic_event_get_index), deferred :: get_index
procedure (generic_event_get_fac_scale), deferred :: get_fac_scale
procedure (generic_event_get_alpha_s), deferred :: get_alpha_s
procedure (generic_event_get_sqrts), deferred :: get_sqrts
procedure (generic_event_get_polarization), deferred :: get_polarization
procedure (generic_event_get_beam_file), deferred :: get_beam_file
procedure (generic_event_get_process_name), deferred :: &
get_process_name
<<Event base: interfaces>>=
abstract interface
function generic_event_has_index (event) result (flag)
import
class(generic_event_t), intent(in) :: event
logical :: flag
end function generic_event_has_index
end interface
abstract interface
function generic_event_get_index (event) result (index)
import
class(generic_event_t), intent(in) :: event
integer :: index
end function generic_event_get_index
end interface
abstract interface
function generic_event_get_fac_scale (event) result (fac_scale)
import
class(generic_event_t), intent(in) :: event
real(default) :: fac_scale
end function generic_event_get_fac_scale
end interface
abstract interface
function generic_event_get_alpha_s (event) result (alpha_s)
import
class(generic_event_t), intent(in) :: event
real(default) :: alpha_s
end function generic_event_get_alpha_s
end interface
abstract interface
function generic_event_get_sqrts (event) result (sqrts)
import
class(generic_event_t), intent(in) :: event
real(default) :: sqrts
end function generic_event_get_sqrts
end interface
abstract interface
function generic_event_get_polarization (event) result (pol)
import
class(generic_event_t), intent(in) :: event
real(default), dimension(2) :: pol
end function generic_event_get_polarization
end interface
abstract interface
function generic_event_get_beam_file (event) result (file)
import
class(generic_event_t), intent(in) :: event
type(string_t) :: file
end function generic_event_get_beam_file
end interface
abstract interface
function generic_event_get_process_name (event) result (name)
import
class(generic_event_t), intent(in) :: event
type(string_t) :: name
end function generic_event_get_process_name
end interface
@ %def generic_event_get_index
@ %def generic_event_get_fac_scale
@ %def generic_event_get_alpha_s
@ %def generic_event_get_sqrts
@ %def generic_event_get_polarization
@ %def generic_event_get_beam_file
@ %def generic_event_get_process_name
@ Set data used by external event formats.
<<Event base: generic event: TBP>>=
procedure (generic_event_set_alpha_qcd_forced), deferred :: &
set_alpha_qcd_forced
procedure (generic_event_set_scale_forced), deferred :: &
set_scale_forced
<<Event base: interfaces>>=
abstract interface
subroutine generic_event_set_alpha_qcd_forced (event, alpha_qcd)
import
class(generic_event_t), intent(inout) :: event
real(default), intent(in) :: alpha_qcd
end subroutine generic_event_set_alpha_qcd_forced
end interface
abstract interface
subroutine generic_event_set_scale_forced (event, scale)
import
class(generic_event_t), intent(inout) :: event
real(default), intent(in) :: scale
end subroutine generic_event_set_scale_forced
end interface
@ %def generic_event_set_alpha_qcd_forced
@ %def generic_event_set_scale_forced
@
\subsection{Utilities}
Applying this, current event contents are marked as incomplete but
are not deleted. In particular, the initialization is kept.
<<Event base: generic event: TBP>>=
procedure :: reset_contents => generic_event_reset_contents
procedure :: base_reset_contents => generic_event_reset_contents
<<Event base: procedures>>=
subroutine generic_event_reset_contents (event)
class(generic_event_t), intent(inout) :: event
call event%discard_particle_set ()
event%sqme_ref_known = .false.
event%sqme_prc_known = .false.
event%sqme_alt_known = .false.
event%weight_ref_known = .false.
event%weight_prc_known = .false.
event%weight_alt_known = .false.
event%excess_prc_known = .false.
end subroutine generic_event_reset_contents
@ %def generic_event_reset_contents
@ Pacify particle set.
<<Event base: generic event: TBP>>=
procedure :: pacify_particle_set => generic_event_pacify_particle_set
<<Event base: procedures>>=
subroutine generic_event_pacify_particle_set (event)
class(generic_event_t), intent(inout) :: event
if (event%has_valid_particle_set ()) call pacify (event%particle_set)
end subroutine generic_event_pacify_particle_set
@ %def generic_event_pacify_particle_set
@
\subsection{Event normalization}
The parameters for event normalization. For unweighted events,
[[NORM_UNIT]] is intended as default, while for weighted events, it is
[[NORM_SIGMA]].
Note: the unit test for this is in [[eio_data_2]] below.
<<Event base: parameters>>=
integer, parameter, public :: NORM_UNDEFINED = 0
integer, parameter, public :: NORM_UNIT = 1
integer, parameter, public :: NORM_N_EVT = 2
integer, parameter, public :: NORM_SIGMA = 3
integer, parameter, public :: NORM_S_N = 4
@ %def NORM_UNDEFINED NORM_UNIT NORM_N_EVT NORM_SIGMA NORM_S_N
@ These functions translate between the user representation and the
internal one.
<<Event base: public>>=
public :: event_normalization_mode
public :: event_normalization_string
<<Event base: procedures>>=
function event_normalization_mode (string, unweighted) result (mode)
integer :: mode
type(string_t), intent(in) :: string
logical, intent(in) :: unweighted
select case (lower_case (char (string)))
case ("auto")
if (unweighted) then
mode = NORM_UNIT
else
mode = NORM_SIGMA
end if
case ("1")
mode = NORM_UNIT
case ("1/n")
mode = NORM_N_EVT
case ("sigma")
mode = NORM_SIGMA
case ("sigma/n")
mode = NORM_S_N
case default
call msg_fatal ("Event normalization: unknown value '" &
// char (string) // "'")
end select
end function event_normalization_mode
function event_normalization_string (norm_mode) result (string)
integer, intent(in) :: norm_mode
type(string_t) :: string
select case (norm_mode)
case (NORM_UNDEFINED); string = "[undefined]"
case (NORM_UNIT); string = "'1'"
case (NORM_N_EVT); string = "'1/n'"
case (NORM_SIGMA); string = "'sigma'"
case (NORM_S_N); string = "'sigma/n'"
case default; string = "???"
end select
end function event_normalization_string
@ %def event_normalization_mode
@ %def event_normalization_string
@ We place this here as a generic helper, so we can update event
weights whenever we need, not just in connection with an event sample
data object.
<<Event base: public>>=
public :: event_normalization_update
<<Event base: procedures>>=
subroutine event_normalization_update (weight, sigma, n, mode_new, mode_old)
real(default), intent(inout) :: weight
real(default), intent(in) :: sigma
integer, intent(in) :: n
integer, intent(in) :: mode_new, mode_old
if (mode_new /= mode_old) then
if (sigma > 0 .and. n > 0) then
weight = weight / factor (mode_old) * factor (mode_new)
else
call msg_fatal ("Event normalization update: null sample")
end if
end if
contains
function factor (mode)
real(default) :: factor
integer, intent(in) :: mode
select case (mode)
case (NORM_UNIT); factor = 1._default
case (NORM_N_EVT); factor = 1._default / n
case (NORM_SIGMA); factor = sigma
case (NORM_S_N); factor = sigma / n
case default
call msg_fatal ("Event normalization update: undefined mode")
end select
end function factor
end subroutine event_normalization_update
@ %def event_normalization_update
@
\subsection{Callback container}
This derived type contains a callback procedure that can
be executed during event I/O. The callback procedure is given the
event object (with class [[generic_event]]) and an event index.
This is a simple wrapper. The object is abstract, so the the actual
procedure is introduced by overriding the deferred one. We use the
PASS attribute, so we may supplement runtime data in the callback object
if desired.
<<Event base: public>>=
public :: event_callback_t
<<Event base: types>>=
type, abstract :: event_callback_t
private
contains
procedure(event_callback_write), deferred :: write
procedure(event_callback_proc), deferred :: proc
end type event_callback_t
@ %def event_callback_t
@ Identify the callback procedure in output
<<Event base: interfaces>>=
abstract interface
subroutine event_callback_write (event_callback, unit)
import
class(event_callback_t), intent(in) :: event_callback
integer, intent(in), optional :: unit
end subroutine event_callback_write
end interface
@ %def event_callback_write
@ This is the procedure interface.
<<Event base: interfaces>>=
abstract interface
subroutine event_callback_proc (event_callback, i, event)
import
class(event_callback_t), intent(in) :: event_callback
integer(i64), intent(in) :: i
class(generic_event_t), intent(in) :: event
end subroutine event_callback_proc
end interface
@ %def event_callback_proc
@ A dummy implementation for testing and fallback.
<<Event base: public>>=
public :: event_callback_nop_t
<<Event base: types>>=
type, extends (event_callback_t) :: event_callback_nop_t
private
contains
procedure :: write => event_callback_nop_write
procedure :: proc => event_callback_nop
end type event_callback_nop_t
@ %def event_callback_t
<<Event base: procedures>>=
subroutine event_callback_nop_write (event_callback, unit)
class(event_callback_nop_t), intent(in) :: event_callback
integer, intent(in), optional :: unit
integer :: u
u = given_output_unit (unit)
write (u, "(1x,A)") "NOP"
end subroutine event_callback_nop_write
subroutine event_callback_nop (event_callback, i, event)
class(event_callback_nop_t), intent(in) :: event_callback
integer(i64), intent(in) :: i
class(generic_event_t), intent(in) :: event
end subroutine event_callback_nop
@ %def event_callback_nop_write
@ %def event_callback_nop
@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
\section{Event Sample Data}
We define a simple and transparent container for (meta)data that are
associated with an event sample.
<<[[eio_data.f90]]>>=
<<File header>>
module eio_data
<<Use kinds>>
<<Use strings>>
use io_units
use numeric_utils
use diagnostics
use event_base
<<Standard module head>>
<<EIO data: public>>
<<EIO data: types>>
contains
<<EIO data: procedures>>
end module eio_data
@ %def eio_data
@
\subsection{Event Sample Data}
These are data that apply to an event sample as a whole. They are
given in an easily portable form (no fancy structure) and are used for
initializing event formats.
There are two MD5 sums here. [[md5sum_proc]] depends only on the
definition of the contributing processes. A sample with matching
checksum can be rescanned with modified model parameters, beam
structure etc, to recalculate observables. [[md5sum_config]] includes
all relevant data. Rescanning a sample with matching checksum will
produce identical observables. (A third checksum might be added which
depends on the event sample itself. This is not needed, so far.)
If alternate weights are part of the event sample ([[n_alt]] nonzero),
there is a configuration MD5 sum for each of them.
<<EIO data: public>>=
public :: event_sample_data_t
<<EIO data: types>>=
type :: event_sample_data_t
character(32) :: md5sum_prc = ""
character(32) :: md5sum_cfg = ""
logical :: unweighted = .true.
logical :: negative_weights = .false.
integer :: norm_mode = NORM_UNDEFINED
integer :: n_beam = 0
integer, dimension(2) :: pdg_beam = 0
real(default), dimension(2) :: energy_beam = 0
integer :: n_proc = 0
integer :: n_evt = 0
integer :: nlo_multiplier = 1
integer :: split_n_evt = 0
integer :: split_n_kbytes = 0
integer :: split_index = 0
real(default) :: total_cross_section = 0
integer, dimension(:), allocatable :: proc_num_id
integer :: n_alt = 0
character(32), dimension(:), allocatable :: md5sum_alt
real(default), dimension(:), allocatable :: cross_section
real(default), dimension(:), allocatable :: error
contains
<<EIO data: event sample data: TBP>>
end type event_sample_data_t
@ %def event_sample_data_t
@ Initialize: allocate for the number of processes
<<EIO data: event sample data: TBP>>=
procedure :: init => event_sample_data_init
<<EIO data: procedures>>=
subroutine event_sample_data_init (data, n_proc, n_alt)
class(event_sample_data_t), intent(out) :: data
integer, intent(in) :: n_proc
integer, intent(in), optional :: n_alt
data%n_proc = n_proc
allocate (data%proc_num_id (n_proc), source = 0)
allocate (data%cross_section (n_proc), source = 0._default)
allocate (data%error (n_proc), source = 0._default)
if (present (n_alt)) then
data%n_alt = n_alt
allocate (data%md5sum_alt (n_alt))
data%md5sum_alt = ""
end if
end subroutine event_sample_data_init
@ %def event_sample_data_init
@ Output.
<<EIO data: event sample data: TBP>>=
procedure :: write => event_sample_data_write
<<EIO data: procedures>>=
subroutine event_sample_data_write (data, unit)
class(event_sample_data_t), intent(in) :: data
integer, intent(in), optional :: unit
integer :: u, i
u = given_output_unit (unit)
write (u, "(1x,A)") "Event sample properties:"
write (u, "(3x,A,A,A)") "MD5 sum (proc) = '", data%md5sum_prc, "'"
write (u, "(3x,A,A,A)") "MD5 sum (config) = '", data%md5sum_cfg, "'"
write (u, "(3x,A,L1)") "unweighted = ", data%unweighted
write (u, "(3x,A,L1)") "negative weights = ", data%negative_weights
write (u, "(3x,A,A)") "normalization = ", &
char (event_normalization_string (data%norm_mode))
write (u, "(3x,A,I0)") "number of beams = ", data%n_beam
write (u, "(5x,A,2(1x,I19))") "PDG = ", &
data%pdg_beam(:data%n_beam)
write (u, "(5x,A,2(1x,ES19.12))") "Energy = ", &
data%energy_beam(:data%n_beam)
if (data%n_evt > 0) then
write (u, "(3x,A,I0)") "number of events = ", data%n_evt
end if
if (.not. vanishes (data%total_cross_section)) then
write (u, "(3x,A,ES19.12)") "total cross sec. = ", &
data%total_cross_section
end if
write (u, "(3x,A,I0)") "num of processes = ", data%n_proc
do i = 1, data%n_proc
write (u, "(3x,A,I0)") "Process #", data%proc_num_id (i)
select case (data%n_beam)
case (1)
write (u, "(5x,A,ES19.12)") "Width = ", data%cross_section(i)
case (2)
write (u, "(5x,A,ES19.12)") "CSec = ", data%cross_section(i)
end select
write (u, "(5x,A,ES19.12)") "Error = ", data%error(i)
end do
if (data%n_alt > 0) then
write (u, "(3x,A,I0)") "num of alt wgt = ", data%n_alt
do i = 1, data%n_alt
write (u, "(5x,A,A,A,1x,I0)") "MD5 sum (cfg) = '", &
data%md5sum_alt(i), "'", i
end do
end if
end subroutine event_sample_data_write
@ %def event_sample_data_write
@
\subsection{Unit tests}
Test module, followed by the corresponding implementation module.
<<[[eio_data_ut.f90]]>>=
<<File header>>
module eio_data_ut
use unit_tests
use eio_data_uti
<<Standard module head>>
<<EIO data: public test>>
contains
<<EIO data: test driver>>
end module eio_data_ut
@ %def eio_data_ut
@
<<[[eio_data_uti.f90]]>>=
<<File header>>
module eio_data_uti
<<Use kinds>>
<<Use strings>>
use event_base
use eio_data
<<Standard module head>>
<<EIO data: test declarations>>
contains
<<EIO data: tests>>
end module eio_data_uti
@ %def eio_data_ut
@ API: driver for the unit tests below.
<<EIO data: public test>>=
public :: eio_data_test
<<EIO data: test driver>>=
subroutine eio_data_test (u, results)
integer, intent(in) :: u
type(test_results_t), intent(inout) :: results
<<EIO data: execute tests>>
end subroutine eio_data_test
@ %def eio_data_test
@
\subsubsection{Event Sample Data}
Print the contents of a sample data block.
<<EIO data: execute tests>>=
call test (eio_data_1, "eio_data_1", &
"event sample data", &
u, results)
<<EIO data: test declarations>>=
public :: eio_data_1
<<EIO data: tests>>=
subroutine eio_data_1 (u)
integer, intent(in) :: u
type(event_sample_data_t) :: data
write (u, "(A)") "* Test output: eio_data_1"
write (u, "(A)") "* Purpose: display event sample data"
write (u, "(A)")
write (u, "(A)") "* Decay process, one component"
write (u, "(A)")
call data%init (1, 1)
data%n_beam = 1
data%pdg_beam(1) = 25
data%energy_beam(1) = 125
data%norm_mode = NORM_UNIT
data%proc_num_id = [42]
data%cross_section = [1.23e-4_default]
data%error = 5e-6_default
data%md5sum_prc = "abcdefghijklmnopabcdefghijklmnop"
data%md5sum_cfg = "12345678901234561234567890123456"
data%md5sum_alt(1) = "uuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuu"
call data%write (u)
write (u, "(A)")
write (u, "(A)") "* Scattering process, two components"
write (u, "(A)")
call data%init (2)
data%n_beam = 2
data%pdg_beam = [2212, -2212]
data%energy_beam = [8._default, 10._default]
data%norm_mode = NORM_SIGMA
data%proc_num_id = [12, 34]
data%cross_section = [100._default, 88._default]
data%error = [1._default, 0.1_default]
call data%write (u)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_data_1"
end subroutine eio_data_1
@ %def eio_data_1
@
\subsubsection{Event Normalization}
Check the functions for translating modes and updating weights.
<<EIO data: execute tests>>=
call test (eio_data_2, "eio_data_2", &
"event normalization", &
u, results)
<<EIO data: test declarations>>=
public :: eio_data_2
<<EIO data: tests>>=
subroutine eio_data_2 (u)
integer, intent(in) :: u
type(string_t) :: s
logical :: unweighted
real(default) :: w, w0, sigma
integer :: n
write (u, "(A)") "* Test output: eio_data_2"
write (u, "(A)") "* Purpose: handle event normalization"
write (u, "(A)")
write (u, "(A)") "* Normalization strings"
write (u, "(A)")
s = "auto"
unweighted = .true.
write (u, "(1x,A,1x,L1,1x,A)") char (s), unweighted, &
char (event_normalization_string &
(event_normalization_mode (s, unweighted)))
s = "AUTO"
unweighted = .false.
write (u, "(1x,A,1x,L1,1x,A)") char (s), unweighted, &
char (event_normalization_string &
(event_normalization_mode (s, unweighted)))
unweighted = .true.
s = "1"
write (u, "(2(1x,A))") char (s), char (event_normalization_string &
(event_normalization_mode (s, unweighted)))
s = "1/n"
write (u, "(2(1x,A))") char (s), char (event_normalization_string &
(event_normalization_mode (s, unweighted)))
s = "Sigma"
write (u, "(2(1x,A))") char (s), char (event_normalization_string &
(event_normalization_mode (s, unweighted)))
s = "sigma/N"
write (u, "(2(1x,A))") char (s), char (event_normalization_string &
(event_normalization_mode (s, unweighted)))
write (u, "(A)")
write (u, "(A)") "* Normalization update"
write (u, "(A)")
sigma = 5
n = 2
w0 = 1
w = w0
call event_normalization_update (w, sigma, n, NORM_UNIT, NORM_UNIT)
write (u, "(2(F6.3))") w0, w
w = w0
call event_normalization_update (w, sigma, n, NORM_N_EVT, NORM_UNIT)
write (u, "(2(F6.3))") w0, w
w = w0
call event_normalization_update (w, sigma, n, NORM_SIGMA, NORM_UNIT)
write (u, "(2(F6.3))") w0, w
w = w0
call event_normalization_update (w, sigma, n, NORM_S_N, NORM_UNIT)
write (u, "(2(F6.3))") w0, w
write (u, *)
w0 = 0.5
w = w0
call event_normalization_update (w, sigma, n, NORM_UNIT, NORM_N_EVT)
write (u, "(2(F6.3))") w0, w
w = w0
call event_normalization_update (w, sigma, n, NORM_N_EVT, NORM_N_EVT)
write (u, "(2(F6.3))") w0, w
w = w0
call event_normalization_update (w, sigma, n, NORM_SIGMA, NORM_N_EVT)
write (u, "(2(F6.3))") w0, w
w = w0
call event_normalization_update (w, sigma, n, NORM_S_N, NORM_N_EVT)
write (u, "(2(F6.3))") w0, w
write (u, *)
w0 = 5.0
w = w0
call event_normalization_update (w, sigma, n, NORM_UNIT, NORM_SIGMA)
write (u, "(2(F6.3))") w0, w
w = w0
call event_normalization_update (w, sigma, n, NORM_N_EVT, NORM_SIGMA)
write (u, "(2(F6.3))") w0, w
w = w0
call event_normalization_update (w, sigma, n, NORM_SIGMA, NORM_SIGMA)
write (u, "(2(F6.3))") w0, w
w = w0
call event_normalization_update (w, sigma, n, NORM_S_N, NORM_SIGMA)
write (u, "(2(F6.3))") w0, w
write (u, *)
w0 = 2.5
w = w0
call event_normalization_update (w, sigma, n, NORM_UNIT, NORM_S_N)
write (u, "(2(F6.3))") w0, w
w = w0
call event_normalization_update (w, sigma, n, NORM_N_EVT, NORM_S_N)
write (u, "(2(F6.3))") w0, w
w = w0
call event_normalization_update (w, sigma, n, NORM_SIGMA, NORM_S_N)
write (u, "(2(F6.3))") w0, w
w = w0
call event_normalization_update (w, sigma, n, NORM_S_N, NORM_S_N)
write (u, "(2(F6.3))") w0, w
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_data_2"
end subroutine eio_data_2
@ %def eio_data_2
@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
\section{Abstract I/O Handler}
This module defines an abstract object for event I/O and the
associated methods.
There are [[output]] and [[input]] methods which
write or read a single event from/to the I/O stream, respectively.
The I/O stream itself may be a file, a common block, or an externally
linked structure, depending on the concrete implementation.
A [[write]] method prints the current content of the
implementation-dependent event record in human-readable form.
The [[init_in]]/[[init_out]] and [[final]] prepare
and finalize the I/O stream, respectively. There is also a
[[switch_inout]] method which turns an input stream into an output
stream where events can be appended.
Optionally, output files can be split in chunks of well-defined size. The
[[split_out]] method takes care of this.
<<[[eio_base.f90]]>>=
<<File header>>
module eio_base
use kinds, only: i64
<<Use strings>>
use io_units
use diagnostics
use model_data
use event_base
use eio_data
<<Standard module head>>
<<EIO base: public>>
<<EIO base: types>>
<<EIO base: interfaces>>
contains
<<EIO base: procedures>>
end module eio_base
@ %def eio_base
@
\subsection{Type}
We can assume that most implementations will need the file extension as a
fixed string and, if they support file splitting, the current file index.
The fallback model is useful for implementations that are able to read
unknown files which may contain hadrons etc., not in the current
hard-interaction model.
<<EIO base: public>>=
public :: eio_t
<<EIO base: types>>=
type, abstract :: eio_t
type(string_t) :: sample
type(string_t) :: extension
type(string_t) :: filename
logical :: has_file = .false.
logical :: split = .false.
integer :: split_n_evt = 0
integer :: split_n_kbytes = 0
integer :: split_index = 0
integer :: split_count = 0
class(model_data_t), pointer :: fallback_model => null ()
contains
<<EIO base: eio: TBP>>
end type eio_t
@ %def eio_t
@ Write to screen. If possible, this should display the contents of the
current event, i.e., the last one that was written or read.
<<EIO base: eio: TBP>>=
procedure (eio_write), deferred :: write
<<EIO base: interfaces>>=
abstract interface
subroutine eio_write (object, unit)
import
class(eio_t), intent(in) :: object
integer, intent(in), optional :: unit
end subroutine eio_write
end interface
@ %def eio_write
@ Finalize. This should write/read footer data and close input/output
channels.
<<EIO base: eio: TBP>>=
procedure (eio_final), deferred :: final
<<EIO base: interfaces>>=
abstract interface
subroutine eio_final (object)
import
class(eio_t), intent(inout) :: object
end subroutine eio_final
end interface
@ %def eio_final
@ Determine splitting parameters from the event sample data.
<<EIO base: eio: TBP>>=
procedure :: set_splitting => eio_set_splitting
<<EIO base: procedures>>=
subroutine eio_set_splitting (eio, data)
class(eio_t), intent(inout) :: eio
type(event_sample_data_t), intent(in) :: data
eio%split = data%split_n_evt > 0 .or. data%split_n_kbytes > 0
if (eio%split) then
eio%split_n_evt = data%split_n_evt
eio%split_n_kbytes = data%split_n_kbytes
eio%split_index = data%split_index
eio%split_count = 0
end if
end subroutine eio_set_splitting
@ %def eio_set_splitting
@ Update the byte count and check if it has increased. We use integer
division to determine the number of [[n_kbytes]] blocks that are in
the event file.
<<EIO base: eio: TBP>>=
procedure :: update_split_count => eio_update_split_count
<<EIO base: procedures>>=
subroutine eio_update_split_count (eio, increased)
class(eio_t), intent(inout) :: eio
logical, intent(out) :: increased
integer :: split_count_old
if (eio%split_n_kbytes > 0) then
split_count_old = eio%split_count
eio%split_count = eio%file_size_kbytes () / eio%split_n_kbytes
increased = eio%split_count > split_count_old
end if
end subroutine eio_update_split_count
@ %def eio_update_split_count
@ Generate a filename, taking a possible split index into account.
<<EIO base: eio: TBP>>=
procedure :: set_filename => eio_set_filename
<<EIO base: procedures>>=
subroutine eio_set_filename (eio)
class(eio_t), intent(inout) :: eio
character(32) :: buffer
if (eio%split) then
write (buffer, "(I0,'.')") eio%split_index
eio%filename = eio%sample // "." // trim (buffer) // eio%extension
eio%has_file = .true.
else
eio%filename = eio%sample // "." // eio%extension
eio%has_file = .true.
end if
end subroutine eio_set_filename
@ %def eio_set_filename
@ Set the fallback model.
<<EIO base: eio: TBP>>=
procedure :: set_fallback_model => eio_set_fallback_model
<<EIO base: procedures>>=
subroutine eio_set_fallback_model (eio, model)
class(eio_t), intent(inout) :: eio
class(model_data_t), intent(in), target :: model
eio%fallback_model => model
end subroutine eio_set_fallback_model
@ %def eio_set_fallback_model
@ Initialize for output. We provide process names. This should
open an event file if appropriate and write header data. Some methods
may require event sample data.
<<EIO base: eio: TBP>>=
procedure (eio_init_out), deferred :: init_out
<<EIO base: interfaces>>=
abstract interface
subroutine eio_init_out (eio, sample, data, success, extension)
import
class(eio_t), intent(inout) :: eio
type(string_t), intent(in) :: sample
type(event_sample_data_t), intent(in), optional :: data
logical, intent(out), optional :: success
type(string_t), intent(in), optional :: extension
end subroutine eio_init_out
end interface
@ %def eio_init_out
@ Initialize for input. We provide process names. This should open an event
file if appropriate and read header data. The [[md5sum]] can be used to check
the integrity of the configuration, it it provides a checksum to compare with.
In case the extension has changed the extension is also given as an argument.
The [[data]] argument is [[intent(inout)]]: we may read part of it and
keep other parts and/or check them against the data in the file.
<<EIO base: eio: TBP>>=
procedure (eio_init_in), deferred :: init_in
<<EIO base: interfaces>>=
abstract interface
subroutine eio_init_in (eio, sample, data, success, extension)
import
class(eio_t), intent(inout) :: eio
type(string_t), intent(in) :: sample
type(event_sample_data_t), intent(inout), optional :: data
logical, intent(out), optional :: success
type(string_t), intent(in), optional :: extension
end subroutine eio_init_in
end interface
@ %def eio_init_in
@ Re-initialize for output. This should change the status of any event file
from input to output and position it for appending new events.
<<EIO base: eio: TBP>>=
procedure (eio_switch_inout), deferred :: switch_inout
<<EIO base: interfaces>>=
abstract interface
subroutine eio_switch_inout (eio, success)
import
class(eio_t), intent(inout) :: eio
logical, intent(out), optional :: success
end subroutine eio_switch_inout
end interface
@ %def eio_switch_inout
@ This is similar: split the output, i.e., close the current file and open a
new one. The default implementation does nothing. For the feature to work,
an implementation must override this.
<<EIO base: eio: TBP>>=
procedure :: split_out => eio_split_out
<<EIO base: procedures>>=
subroutine eio_split_out (eio)
class(eio_t), intent(inout) :: eio
end subroutine eio_split_out
@ %def eio_split_out
@ Determine the file size in kilobytes. More exactly, determine the
size in units of 1024 storage units, as returned by the INQUIRE statement.
The implementation returns zero if there is no file. The
[[has_file]] flag is set by the [[set_filename]] method, so we can be
confident that the [[inquire]] call is meaningful. If this algorithm
doesn't apply for a particular format, we still can override the
procedure.
<<EIO base: eio: TBP>>=
procedure :: file_size_kbytes => eio_file_size_kbytes
<<EIO base: procedures>>=
function eio_file_size_kbytes (eio) result (kbytes)
class(eio_t), intent(in) :: eio
integer :: kbytes
integer(i64) :: bytes
if (eio%has_file) then
inquire (file = char (eio%filename), size = bytes)
if (bytes > 0) then
kbytes = bytes / 1024
else
kbytes = 0
end if
else
kbytes = 0
end if
end function eio_file_size_kbytes
@ %def eio_file_size_kbytes
@ Output an event. All data can be taken from the [[event]] record.
The index [[i_prc]] identifies the process among the processes that
are contained in the current sample. The [[reading]] flag, if present,
indicates that the event was read from file, not generated.
The [[passed]] flag tells us that this event has passed the selection
criteria. Depending on the event format, we may choose to skip events
that have not passed.
<<EIO base: eio: TBP>>=
procedure (eio_output), deferred :: output
<<EIO base: interfaces>>=
abstract interface
subroutine eio_output (eio, event, i_prc, reading, passed, pacify)
import
class(eio_t), intent(inout) :: eio
class(generic_event_t), intent(in), target :: event
integer, intent(in) :: i_prc
logical, intent(in), optional :: reading, passed, pacify
end subroutine eio_output
end interface
@ %def eio_output
@ Input an event. This should fill all event data that cannot be inferred
from the associated process.
The input is broken down into two parts. First we read the [[i_prc]]
index. So we know which process to expect in the subsequent event.
If we have reached end of file, we also will know.
Then, we read the event itself.
The parameter [[iostat]] is supposed to be set as the Fortran standard
requires, negative for EOF and positive for error.
<<EIO base: eio: TBP>>=
procedure (eio_input_i_prc), deferred :: input_i_prc
procedure (eio_input_event), deferred :: input_event
<<EIO base: interfaces>>=
abstract interface
subroutine eio_input_i_prc (eio, i_prc, iostat)
import
class(eio_t), intent(inout) :: eio
integer, intent(out) :: i_prc
integer, intent(out) :: iostat
end subroutine eio_input_i_prc
end interface
abstract interface
subroutine eio_input_event (eio, event, iostat)
import
class(eio_t), intent(inout) :: eio
class(generic_event_t), intent(inout), target :: event
integer, intent(out) :: iostat
end subroutine eio_input_event
end interface
@ %def eio_input
@
<<EIO base: eio: TBP>>=
procedure (eio_skip), deferred :: skip
<<EIO base: interfaces>>=
abstract interface
subroutine eio_skip (eio, iostat)
import
class(eio_t), intent(inout) :: eio
integer, intent(out) :: iostat
end subroutine eio_skip
end interface
@ %def eio_skip
@
\subsection{Unit tests}
Test module, followed by the corresponding implementation module.
<<[[eio_base_ut.f90]]>>=
<<File header>>
module eio_base_ut
use unit_tests
use eio_base_uti
<<Standard module head>>
<<EIO base: public test>>
<<EIO base: public test auxiliary>>
contains
<<EIO base: test driver>>
end module eio_base_ut
@ %def eio_base_ut
@
<<[[eio_base_uti.f90]]>>=
<<File header>>
module eio_base_uti
<<Use kinds>>
<<Use strings>>
use io_units
use lorentz
use model_data
use particles
use event_base
use eio_data
use eio_base
<<Standard module head>>
<<EIO base: public test auxiliary>>
<<EIO base: test declarations>>
<<EIO base: test types>>
<<EIO base: test variables>>
contains
<<EIO base: tests>>
<<EIO base: test auxiliary>>
end module eio_base_uti
@ %def eio_base_ut
@ API: driver for the unit tests below.
<<EIO base: public test>>=
public :: eio_base_test
<<EIO base: test driver>>=
subroutine eio_base_test (u, results)
integer, intent(in) :: u
type(test_results_t), intent(inout) :: results
<<EIO base: execute tests>>
end subroutine eio_base_test
@ %def eio_base_test
@ The caller has to provide procedures that prepare and cleanup the test
environment. They depend on modules that are not available here.
<<EIO base: test types>>=
abstract interface
subroutine eio_prepare_event (event, unweighted, n_alt)
import
class(generic_event_t), intent(inout), pointer :: event
logical, intent(in), optional :: unweighted
integer, intent(in), optional :: n_alt
end subroutine eio_prepare_event
end interface
abstract interface
subroutine eio_cleanup_event (event)
import
class(generic_event_t), intent(inout), pointer :: event
end subroutine eio_cleanup_event
end interface
@ We store pointers to the test-environment handlers as module variables.
This allows us to call them from the test routines themselves, which don't
allow for extra arguments.
<<EIO base: public test auxiliary>>=
public :: eio_prepare_test, eio_cleanup_test
<<EIO base: test types>>=
procedure(eio_prepare_event), pointer :: eio_prepare_test => null ()
procedure(eio_cleanup_event), pointer :: eio_cleanup_test => null ()
@ %def eio_prepare_test eio_cleanup_test
@ Similarly, for the fallback (hadron) model that some eio tests require:
<<EIO base: test types>>=
abstract interface
subroutine eio_prepare_model (model)
import
class(model_data_t), intent(inout), pointer :: model
end subroutine eio_prepare_model
end interface
abstract interface
subroutine eio_cleanup_model (model)
import
class(model_data_t), intent(inout), pointer :: model
end subroutine eio_cleanup_model
end interface
<<EIO base: public test auxiliary>>=
public :: eio_prepare_fallback_model, eio_cleanup_fallback_model
<<EIO base: test variables>>=
procedure(eio_prepare_model), pointer :: eio_prepare_fallback_model => null ()
procedure(eio_cleanup_model), pointer :: eio_cleanup_fallback_model => null ()
@ %def eio_prepare_fallback_model eio_cleanup_fallback_model
@
\subsubsection{Test type for event I/O}
The contents simulate the contents of an external file. We have the
[[sample]] string as the file name and the array of momenta
[[event_p]] as the list of events. The
second index is the event index. The [[event_i]] component is the pointer
to the current event, [[event_n]] is the total number of stored events.
<<EIO base: test types>>=
type, extends (eio_t) :: eio_test_t
integer :: event_n = 0
integer :: event_i = 0
integer :: i_prc = 0
type(vector4_t), dimension(:,:), allocatable :: event_p
contains
<<EIO base: eio test: TBP>>
end type eio_test_t
@ %def eio_test_t
@ Write to screen. Pretend that this is an actual event format.
<<EIO base: eio test: TBP>>=
procedure :: write => eio_test_write
<<EIO base: test auxiliary>>=
subroutine eio_test_write (object, unit)
class(eio_test_t), intent(in) :: object
integer, intent(in), optional :: unit
integer :: u, i
u = given_output_unit (unit)
write (u, "(1x,A)") "Test event stream"
if (object%event_i /= 0) then
write (u, "(1x,A,I0,A)") "Event #", object%event_i, ":"
do i = 1, size (object%event_p, 1)
call vector4_write (object%event_p(i, object%event_i), u)
end do
end if
end subroutine eio_test_write
@ %def eio_test_write
@ Finalizer. For the test case, we just reset the event count,
but keep the stored ``events''. For the real implementations, the events
would be stored on an external medium, so we would delete the object
contents.
<<EIO base: eio test: TBP>>=
procedure :: final => eio_test_final
<<EIO base: test auxiliary>>=
subroutine eio_test_final (object)
class(eio_test_t), intent(inout) :: object
object%event_i = 0
end subroutine eio_test_final
@ %def eio_test_final
@ Initialization: We store the process IDs and the energy from the beam-data
object. We also allocate the momenta (i.e., the simulated event record) for a
fixed maximum size of 10 events, 2 momenta each. There is only a single
process.
<<EIO base: eio test: TBP>>=
procedure :: init_out => eio_test_init_out
<<EIO base: test auxiliary>>=
subroutine eio_test_init_out (eio, sample, data, success, extension)
class(eio_test_t), intent(inout) :: eio
type(string_t), intent(in) :: sample
type(event_sample_data_t), intent(in), optional :: data
logical, intent(out), optional :: success
type(string_t), intent(in), optional :: extension
eio%sample = sample
eio%event_n = 0
eio%event_i = 0
allocate (eio%event_p (2, 10))
if (present (success)) success = .true.
end subroutine eio_test_init_out
@ %def eio_test_init_out
@ Initialization for input. Nothing to do for the test type.
<<EIO base: eio test: TBP>>=
procedure :: init_in => eio_test_init_in
<<EIO base: test auxiliary>>=
subroutine eio_test_init_in (eio, sample, data, success, extension)
class(eio_test_t), intent(inout) :: eio
type(string_t), intent(in) :: sample
type(event_sample_data_t), intent(inout), optional :: data
logical, intent(out), optional :: success
type(string_t), intent(in), optional :: extension
if (present (success)) success = .true.
end subroutine eio_test_init_in
@ %def eio_test_init_in
@ Switch from output to input. Again, nothing to do for the test type.
<<EIO base: eio test: TBP>>=
procedure :: switch_inout => eio_test_switch_inout
<<EIO base: test auxiliary>>=
subroutine eio_test_switch_inout (eio, success)
class(eio_test_t), intent(inout) :: eio
logical, intent(out), optional :: success
if (present (success)) success = .true.
end subroutine eio_test_switch_inout
@ %def eio_test_switch_inout
@ Output. Increment the event counter and store the momenta of the current
event.
<<EIO base: eio test: TBP>>=
procedure :: output => eio_test_output
<<EIO base: test auxiliary>>=
subroutine eio_test_output (eio, event, i_prc, reading, passed, pacify)
class(eio_test_t), intent(inout) :: eio
class(generic_event_t), intent(in), target :: event
logical, intent(in), optional :: reading, passed, pacify
integer, intent(in) :: i_prc
type(particle_set_t), pointer :: pset
type(particle_t) :: prt
eio%event_n = eio%event_n + 1
eio%event_i = eio%event_n
eio%i_prc = i_prc
pset => event%get_particle_set_ptr ()
prt = pset%get_particle (3)
eio%event_p(1, eio%event_i) = prt%get_momentum ()
prt = pset%get_particle (4)
eio%event_p(2, eio%event_i) = prt%get_momentum ()
end subroutine eio_test_output
@ %def eio_test_output
@ Input. Increment the event counter and retrieve the momenta of the current
event. For the test case, we do not actually modify the current event.
<<EIO base: eio test: TBP>>=
procedure :: input_i_prc => eio_test_input_i_prc
procedure :: input_event => eio_test_input_event
<<EIO base: test auxiliary>>=
subroutine eio_test_input_i_prc (eio, i_prc, iostat)
class(eio_test_t), intent(inout) :: eio
integer, intent(out) :: i_prc
integer, intent(out) :: iostat
i_prc = eio%i_prc
iostat = 0
end subroutine eio_test_input_i_prc
subroutine eio_test_input_event (eio, event, iostat)
class(eio_test_t), intent(inout) :: eio
class(generic_event_t), intent(inout), target :: event
integer, intent(out) :: iostat
eio%event_i = eio%event_i + 1
iostat = 0
end subroutine eio_test_input_event
@ %def eio_test_input_i_prc
@ %def eio_test_input_event
@
<<EIO base: eio test: TBP>>=
procedure :: skip => eio_test_skip
<<EIO base: test auxiliary>>=
subroutine eio_test_skip (eio, iostat)
class(eio_test_t), intent(inout) :: eio
integer, intent(out) :: iostat
iostat = 0
end subroutine eio_test_skip
@ %def eio_test_skip
@
\subsubsection{Test I/O methods}
<<EIO base: execute tests>>=
call test (eio_base_1, "eio_base_1", &
"read and write event contents", &
u, results)
<<EIO base: test declarations>>=
public :: eio_base_1
<<EIO base: tests>>=
subroutine eio_base_1 (u)
integer, intent(in) :: u
class(generic_event_t), pointer :: event
class(eio_t), allocatable :: eio
integer :: i_prc, iostat
type(string_t) :: sample
write (u, "(A)") "* Test output: eio_base_1"
write (u, "(A)") "* Purpose: generate and read/write an event"
write (u, "(A)")
write (u, "(A)") "* Initialize test process"
call eio_prepare_test (event, unweighted = .false.)
write (u, "(A)")
write (u, "(A)") "* Generate and write an event"
write (u, "(A)")
sample = "eio_test1"
allocate (eio_test_t :: eio)
call eio%init_out (sample)
call event%generate (1, [0._default, 0._default])
call eio%output (event, 42)
call eio%write (u)
call eio%final ()
write (u, "(A)")
write (u, "(A)") "* Re-read the event"
write (u, "(A)")
call eio%init_in (sample)
call eio%input_i_prc (i_prc, iostat)
call eio%input_event (event, iostat)
call eio%write (u)
write (u, "(A)")
write (u, "(1x,A,I0)") "i = ", i_prc
write (u, "(A)")
write (u, "(A)") "* Generate and append another event"
write (u, "(A)")
call eio%switch_inout ()
call event%generate (1, [0._default, 0._default])
call eio%output (event, 5)
call eio%write (u)
call eio%final ()
write (u, "(A)")
write (u, "(A)") "* Re-read both events"
write (u, "(A)")
call eio%init_in (sample)
call eio%input_i_prc (i_prc, iostat)
call eio%input_event (event, iostat)
call eio%input_i_prc (i_prc, iostat)
call eio%input_event (event, iostat)
call eio%write (u)
write (u, "(A)")
write (u, "(1x,A,I0)") "i = ", i_prc
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio%final ()
deallocate (eio)
call eio_cleanup_test (event)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_base_1"
end subroutine eio_base_1
@ %def eio_base_1
@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
\section{Direct Event Access}
As a convenient application of the base type, we construct an event
handler that allows us of setting and retrieving events just in the
same way as an file I/O format, but directly dealing with particle
data and momenta. This is an input and output format, but we do not
care about counting events.
<<[[eio_direct.f90]]>>=
<<File header>>
module eio_direct
<<Use kinds>>
<<Use strings>>
use io_units
use diagnostics
use cputime
use lorentz, only: vector4_t
use particles, only: particle_set_t
use model_data, only: model_data_t
use event_base
use eio_data
use eio_base
<<Standard module head>>
<<EIO direct: public>>
<<EIO direct: types>>
contains
<<EIO direct: procedures>>
end module eio_direct
@ %def eio_direct
@
\subsection{Type}
<<EIO direct: public>>=
public :: eio_direct_t
<<EIO direct: types>>=
type, extends (eio_t) :: eio_direct_t
private
logical :: i_evt_set = .false.
integer :: i_evt = 0
integer :: i_prc = 0
integer :: i_mci = 0
integer :: i_term = 0
integer :: channel = 0
logical :: passed_set = .false.
logical :: passed = .true.
type(particle_set_t) :: pset
contains
<<EIO direct: eio direct: TBP>>
end type eio_direct_t
@ %def eio_direct_t
@
\subsection{Common Methods}
Output.
<<EIO direct: eio direct: TBP>>=
procedure :: write => eio_direct_write
<<EIO direct: procedures>>=
subroutine eio_direct_write (object, unit)
class(eio_direct_t), intent(in) :: object
integer, intent(in), optional :: unit
integer :: u
u = given_output_unit (unit)
write (u, "(1x,A)") "Event direct access:"
if (object%i_evt_set) then
write (u, "(3x,A,1x,I0)") "i_evt =", object%i_evt
else
write (u, "(3x,A)") "i_evt = [undefined]"
end if
write (u, "(3x,A,1x,I0)") "i_prc =", object%i_prc
write (u, "(3x,A,1x,I0)") "i_mci =", object%i_prc
write (u, "(3x,A,1x,I0)") "i_term =", object%i_prc
write (u, "(3x,A,1x,I0)") "channel =", object%i_prc
if (object%passed_set) then
write (u, "(3x,A,1x,L1)") "passed =", object%passed
else
write (u, "(3x,A)") "passed = [N/A]"
end if
call object%pset%write (u)
end subroutine eio_direct_write
@ %def eio_direct_write
@ Finalizer: trivial.
<<EIO direct: eio direct: TBP>>=
procedure :: final => eio_direct_final
<<EIO direct: procedures>>=
subroutine eio_direct_final (object)
class(eio_direct_t), intent(inout) :: object
call object%pset%final ()
end subroutine eio_direct_final
@ %def eio_direct_final
@ Initialize for input and/or output, both are identical
<<EIO direct: eio direct: TBP>>=
procedure :: init_out => eio_direct_init_out
<<EIO direct: procedures>>=
subroutine eio_direct_init_out (eio, sample, data, success, extension)
class(eio_direct_t), intent(inout) :: eio
type(string_t), intent(in) :: sample
type(string_t), intent(in), optional :: extension
type(event_sample_data_t), intent(in), optional :: data
logical, intent(out), optional :: success
if (present (success)) success = .true.
end subroutine eio_direct_init_out
@ %def eio_direct_init_out
@
<<EIO direct: eio direct: TBP>>=
procedure :: init_in => eio_direct_init_in
<<EIO direct: procedures>>=
subroutine eio_direct_init_in (eio, sample, data, success, extension)
class(eio_direct_t), intent(inout) :: eio
type(string_t), intent(in) :: sample
type(string_t), intent(in), optional :: extension
type(event_sample_data_t), intent(inout), optional :: data
logical, intent(out), optional :: success
if (present (success)) success = .true.
end subroutine eio_direct_init_in
@ %def eio_direct_init_in
@ Switch from input to output: no-op
<<EIO direct: eio direct: TBP>>=
procedure :: switch_inout => eio_direct_switch_inout
<<EIO direct: procedures>>=
subroutine eio_direct_switch_inout (eio, success)
class(eio_direct_t), intent(inout) :: eio
logical, intent(out), optional :: success
if (present (success)) success = .true.
end subroutine eio_direct_switch_inout
@ %def eio_direct_switch_inout
@ Output: transfer event contents from the [[event]] object to the
[[eio]] object. Note that finalization of the particle set is not
(yet) automatic.
<<EIO direct: eio direct: TBP>>=
procedure :: output => eio_direct_output
<<EIO direct: procedures>>=
subroutine eio_direct_output (eio, event, i_prc, reading, passed, pacify)
class(eio_direct_t), intent(inout) :: eio
class(generic_event_t), intent(in), target :: event
integer, intent(in) :: i_prc
logical, intent(in), optional :: reading, passed, pacify
type(particle_set_t), pointer :: pset_ptr
call eio%pset%final ()
if (event%has_index ()) then
call eio%set_event_index (event%get_index ())
else
call eio%reset_event_index ()
end if
if (present (passed)) then
eio%passed = passed
eio%passed_set = .true.
else
eio%passed_set = .false.
end if
pset_ptr => event%get_particle_set_ptr ()
if (associated (pset_ptr)) then
eio%i_prc = i_prc
eio%pset = pset_ptr
end if
end subroutine eio_direct_output
@ %def eio_direct_output
@ Input: transfer event contents from the [[eio]] object to the
[[event]] object. The [[i_prc]] parameter has been stored inside the
[[eio]] record before.
<<EIO direct: eio direct: TBP>>=
procedure :: input_i_prc => eio_direct_input_i_prc
procedure :: input_event => eio_direct_input_event
<<EIO direct: procedures>>=
subroutine eio_direct_input_i_prc (eio, i_prc, iostat)
class(eio_direct_t), intent(inout) :: eio
integer, intent(out) :: i_prc
integer, intent(out) :: iostat
i_prc = eio%i_prc
iostat = 0
end subroutine eio_direct_input_i_prc
subroutine eio_direct_input_event (eio, event, iostat)
class(eio_direct_t), intent(inout) :: eio
class(generic_event_t), intent(inout), target :: event
integer, intent(out) :: iostat
call event%select (eio%i_mci, eio%i_term, eio%channel)
if (eio%has_event_index ()) then
call event%set_index (eio%get_event_index ())
else
call event%reset_index ()
end if
call event%set_hard_particle_set (eio%pset)
end subroutine eio_direct_input_event
@ %def eio_direct_input_i_prc
@ %def eio_direct_input_event
@ No-op.
<<EIO direct: eio direct: TBP>>=
procedure :: skip => eio_direct_skip
<<EIO direct: procedures>>=
subroutine eio_direct_skip (eio, iostat)
class(eio_direct_t), intent(inout) :: eio
integer, intent(out) :: iostat
iostat = 0
end subroutine eio_direct_skip
@ %def eio_direct_skip
@
\subsection{Retrieve individual contents}
<<EIO direct: eio direct: TBP>>=
procedure :: has_event_index => eio_direct_has_event_index
procedure :: get_event_index => eio_direct_get_event_index
procedure :: passed_known => eio_direct_passed_known
procedure :: has_passed => eio_direct_has_passed
procedure :: get_n_in => eio_direct_get_n_in
procedure :: get_n_out => eio_direct_get_n_out
procedure :: get_n_tot => eio_direct_get_n_tot
<<EIO direct: procedures>>=
function eio_direct_has_event_index (eio) result (flag)
class(eio_direct_t), intent(in) :: eio
logical :: flag
flag = eio%i_evt_set
end function eio_direct_has_event_index
function eio_direct_get_event_index (eio) result (index)
class(eio_direct_t), intent(in) :: eio
integer :: index
if (eio%has_event_index ()) then
index = eio%i_evt
else
index = 0
end if
end function eio_direct_get_event_index
function eio_direct_passed_known (eio) result (flag)
class(eio_direct_t), intent(in) :: eio
logical :: flag
flag = eio%passed_set
end function eio_direct_passed_known
function eio_direct_has_passed (eio) result (flag)
class(eio_direct_t), intent(in) :: eio
logical :: flag
if (eio%passed_known ()) then
flag = eio%passed
else
flag = .true.
end if
end function eio_direct_has_passed
function eio_direct_get_n_in (eio) result (n_in)
class(eio_direct_t), intent(in) :: eio
integer :: n_in
n_in = eio%pset%get_n_in ()
end function eio_direct_get_n_in
function eio_direct_get_n_out (eio) result (n_out)
class(eio_direct_t), intent(in) :: eio
integer :: n_out
n_out = eio%pset%get_n_out ()
end function eio_direct_get_n_out
function eio_direct_get_n_tot (eio) result (n_tot)
class(eio_direct_t), intent(in) :: eio
integer :: n_tot
n_tot = eio%pset%get_n_tot ()
end function eio_direct_get_n_tot
@ %def eio_direct_has_event_index
@ %def eio_direct_get_event_index
@ %def eio_direct_passed_known
@ %def eio_direct_has_passed
@ %def eio_direct_get_n_in
@ %def eio_direct_get_n_out
@ %def eio_direct_get_n_tot
@ All momenta as a single allocatable array.
<<EIO direct: eio direct: TBP>>=
procedure :: get_momentum_array => eio_direct_get_momentum_array
<<EIO direct: procedures>>=
subroutine eio_direct_get_momentum_array (eio, p)
class(eio_direct_t), intent(in) :: eio
type(vector4_t), dimension(:), allocatable, intent(out) :: p
integer :: n
n = eio%get_n_tot ()
allocate (p (n))
p(:) = eio%pset%get_momenta ()
end subroutine eio_direct_get_momentum_array
@ %def eio_direct_get_momentum_array
@
\subsection{Manual access}
Build the contained particle set from scratch.
<<EIO direct: eio direct: TBP>>=
procedure :: init_direct => eio_direct_init_direct
<<EIO direct: procedures>>=
subroutine eio_direct_init_direct &
(eio, n_beam, n_in, n_rem, n_vir, n_out, pdg, model)
class(eio_direct_t), intent(out) :: eio
integer, intent(in) :: n_beam
integer, intent(in) :: n_in
integer, intent(in) :: n_rem
integer, intent(in) :: n_vir
integer, intent(in) :: n_out
integer, dimension(:), intent(in) :: pdg
class(model_data_t), intent(in), target :: model
call eio%pset%init_direct (n_beam, n_in, n_rem, n_vir, n_out, pdg, model)
end subroutine eio_direct_init_direct
@ %def eio_direct_init_direct
@ Set/reset the event index, which is optional.
<<EIO direct: eio direct: TBP>>=
procedure :: set_event_index => eio_direct_set_event_index
procedure :: reset_event_index => eio_direct_reset_event_index
<<EIO direct: procedures>>=
subroutine eio_direct_set_event_index (eio, index)
class(eio_direct_t), intent(inout) :: eio
integer, intent(in) :: index
eio%i_evt = index
eio%i_evt_set = .true.
end subroutine eio_direct_set_event_index
subroutine eio_direct_reset_event_index (eio)
class(eio_direct_t), intent(inout) :: eio
eio%i_evt_set = .false.
end subroutine eio_direct_reset_event_index
@ %def eio_direct_set_event_index
@ %def eio_direct_reset_event_index
@ Set the selection indices. This is supposed to select the [[i_prc]],
[[i_mci]], [[i_term]], and [[channel]]
entries of the event where the momentum set has to be stored, respectively.
The selection indices determine the process, MCI set, calculation term, and
phase-space channel is to be used for recalculation. The index values must
not be zero, even if the do not apply.
<<EIO direct: eio direct: TBP>>=
procedure :: set_selection_indices => eio_direct_set_selection_indices
<<EIO direct: procedures>>=
subroutine eio_direct_set_selection_indices &
(eio, i_prc, i_mci, i_term, channel)
class(eio_direct_t), intent(inout) :: eio
integer, intent(in) :: i_prc
integer, intent(in) :: i_mci
integer, intent(in) :: i_term
integer, intent(in) :: channel
eio%i_prc = i_prc
eio%i_mci = i_mci
eio%i_term = i_term
eio%channel = channel
end subroutine eio_direct_set_selection_indices
@ %def eio_direct_set_i_prc
@ Set momentum (or momenta -- elemental).
<<EIO direct: eio direct: TBP>>=
generic :: set_momentum => set_momentum_single
generic :: set_momentum => set_momentum_all
procedure :: set_momentum_single => eio_direct_set_momentum_single
procedure :: set_momentum_all => eio_direct_set_momentum_all
<<EIO direct: procedures>>=
subroutine eio_direct_set_momentum_single (eio, i, p, p2, on_shell)
class(eio_direct_t), intent(inout) :: eio
integer, intent(in) :: i
type(vector4_t), intent(in) :: p
real(default), intent(in), optional :: p2
logical, intent(in), optional :: on_shell
call eio%pset%set_momentum (i, p, p2, on_shell)
end subroutine eio_direct_set_momentum_single
subroutine eio_direct_set_momentum_all (eio, p, p2, on_shell)
class(eio_direct_t), intent(inout) :: eio
type(vector4_t), dimension(:), intent(in) :: p
real(default), dimension(:), intent(in), optional :: p2
logical, intent(in), optional :: on_shell
call eio%pset%set_momentum (p, p2, on_shell)
end subroutine eio_direct_set_momentum_all
@ %def eio_direct_set_momentum
@
\subsection{Unit tests}
Test module, followed by the corresponding implementation module.
<<[[eio_direct_ut.f90]]>>=
<<File header>>
module eio_direct_ut
use unit_tests
use eio_direct_uti
<<Standard module head>>
<<EIO direct: public test>>
contains
<<EIO direct: test driver>>
end module eio_direct_ut
@ %def eio_direct_ut
@
<<[[eio_direct_uti.f90]]>>=
<<File header>>
module eio_direct_uti
<<Use kinds>>
<<Use strings>>
use lorentz, only: vector4_t
use model_data, only: model_data_t
use event_base
use eio_data
use eio_base
use eio_direct
use eio_base_ut, only: eio_prepare_test, eio_cleanup_test
<<Standard module head>>
<<EIO direct: test declarations>>
contains
<<EIO direct: tests>>
end module eio_direct_uti
@ %def eio_direct_ut
@ API: driver for the unit tests below.
<<EIO direct: public test>>=
public :: eio_direct_test
<<EIO direct: test driver>>=
subroutine eio_direct_test (u, results)
integer, intent(in) :: u
type(test_results_t), intent(inout) :: results
<<EIO direct: execute tests>>
end subroutine eio_direct_test
@ %def eio_direct_test
@
\subsubsection{Test I/O methods}
We test the implementation of all I/O methods.
<<EIO direct: execute tests>>=
call test (eio_direct_1, "eio_direct_1", &
"read and write event contents", &
u, results)
<<EIO direct: test declarations>>=
public :: eio_direct_1
<<EIO direct: tests>>=
subroutine eio_direct_1 (u)
integer, intent(in) :: u
class(generic_event_t), pointer :: event
class(eio_t), allocatable :: eio
type(event_sample_data_t) :: data
type(string_t) :: sample
type(vector4_t), dimension(:), allocatable :: p
class(model_data_t), pointer :: model
integer :: i, n_events, iostat, i_prc
write (u, "(A)") "* Test output: eio_direct_1"
write (u, "(A)") "* Purpose: generate and read/write an event"
write (u, "(A)")
write (u, "(A)") "* Initialize test process"
call eio_prepare_test (event, unweighted = .false.)
write (u, "(A)")
write (u, "(A)") "* Initial state"
write (u, "(A)")
allocate (eio_direct_t :: eio)
call eio%write (u)
write (u, "(A)")
write (u, "(A)") "* Extract an empty event"
write (u, "(A)")
call eio%output (event, 1)
call eio%write (u)
write (u, "(A)")
write (u, "(A)") "* Retrieve contents"
write (u, "(A)")
select type (eio)
class is (eio_direct_t)
if (eio%has_event_index ()) write (u, "(A,1x,I0)") "index =", eio%get_event_index ()
if (eio%passed_known ()) write (u, "(A,1x,L1)") "passed =", eio%has_passed ()
write (u, "(A,1x,I0)") "n_in =", eio%get_n_in ()
write (u, "(A,1x,I0)") "n_out =", eio%get_n_out ()
end select
write (u, "(A)")
write (u, "(A)") "* Generate and extract an event"
write (u, "(A)")
call event%generate (1, [0._default, 0._default])
call event%set_index (42)
model => event%get_model_ptr ()
sample = ""
call eio%init_out (sample)
call eio%output (event, 1, passed = .true.)
call eio%write (u)
write (u, "(A)")
write (u, "(A)") "* Retrieve contents"
write (u, "(A)")
select type (eio)
class is (eio_direct_t)
if (eio%has_event_index ()) write (u, "(A,1x,I0)") "index =", eio%get_event_index ()
if (eio%passed_known ()) write (u, "(A,1x,L1)") "passed =", eio%has_passed ()
write (u, "(A,1x,I0)") "n_in =", eio%get_n_in ()
write (u, "(A,1x,I0)") "n_out =", eio%get_n_out ()
end select
select type (eio)
class is (eio_direct_t)
call eio%get_momentum_array (p)
if (allocated (p)) then
write (u, "(A)") "p[3] ="
call p(3)%write (u)
end if
end select
write (u, "(A)")
write (u, "(A)") "* Re-create an eio event record: initialization"
write (u, "(A)")
call eio%final ()
select type (eio)
class is (eio_direct_t)
call eio%init_direct ( &
n_beam = 0, n_in = 2, n_rem = 0, n_vir = 0, n_out = 2, &
pdg = [25, 25, 25, 25], model = model)
call eio%set_event_index (42)
call eio%set_selection_indices (1, 1, 1, 1)
call eio%write (u)
end select
write (u, "(A)")
write (u, "(A)") "* Re-create an eio event record: &
&set momenta, interchanged"
write (u, "(A)")
select type (eio)
class is (eio_direct_t)
call eio%set_momentum (p([1,2,4,3]), on_shell=.true.)
call eio%write (u)
end select
write (u, "(A)")
write (u, "(A)") "* 'read' i_prc"
write (u, "(A)")
call eio%input_i_prc (i_prc, iostat)
write (u, "(1x,A,1x,I0)") "i_prc =", i_prc
write (u, "(1x,A,1x,I0)") "iostat =", iostat
write (u, "(A)")
write (u, "(A)") "* 'read' (fill) event"
write (u, "(A)")
call eio%input_event (event, iostat)
write (u, "(1x,A,1x,I0)") "iostat =", iostat
write (u, "(A)")
call event%write (u)
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio%final ()
deallocate (eio)
call eio_cleanup_test (event)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_direct_1"
end subroutine eio_direct_1
@ %def eio_direct_1
@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
\section{Event Generation Checkpoints}
This is an output-only format. Its only use is to write screen
messages every $n$ events, to inform the user about progress.
<<[[eio_checkpoints.f90]]>>=
<<File header>>
module eio_checkpoints
<<Use strings>>
use io_units
use diagnostics
use cputime
use event_base
use eio_data
use eio_base
<<Standard module head>>
<<EIO checkpoints: public>>
<<EIO checkpoints: parameters>>
<<EIO checkpoints: types>>
contains
<<EIO checkpoints: procedures>>
end module eio_checkpoints
@ %def eio_checkpoints
@
\subsection{Type}
<<EIO checkpoints: public>>=
public :: eio_checkpoints_t
<<EIO checkpoints: types>>=
type, extends (eio_t) :: eio_checkpoints_t
logical :: active = .false.
logical :: running = .false.
integer :: val = 0
integer :: n_events = 0
integer :: n_read = 0
integer :: i_evt = 0
logical :: blank = .false.
type(timer_t) :: timer
contains
<<EIO checkpoints: eio checkpoints: TBP>>
end type eio_checkpoints_t
@ %def eio_checkpoints_t
@
\subsection{Specific Methods}
Set parameters that are specifically used for checkpointing.
<<EIO checkpoints: eio checkpoints: TBP>>=
procedure :: set_parameters => eio_checkpoints_set_parameters
<<EIO checkpoints: procedures>>=
subroutine eio_checkpoints_set_parameters (eio, checkpoint, blank)
class(eio_checkpoints_t), intent(inout) :: eio
integer, intent(in) :: checkpoint
logical, intent(in), optional :: blank
eio%val = checkpoint
if (present (blank)) eio%blank = blank
end subroutine eio_checkpoints_set_parameters
@ %def eio_checkpoints_set_parameters
@
\subsection{Common Methods}
Output. This is not the actual event format, but a readable account
of the current status.
<<EIO checkpoints: eio checkpoints: TBP>>=
procedure :: write => eio_checkpoints_write
<<EIO checkpoints: procedures>>=
subroutine eio_checkpoints_write (object, unit)
class(eio_checkpoints_t), intent(in) :: object
integer, intent(in), optional :: unit
integer :: u
u = given_output_unit (unit)
if (object%active) then
write (u, "(1x,A)") "Event-sample checkpoints: active"
write (u, "(3x,A,I0)") "interval = ", object%val
write (u, "(3x,A,I0)") "n_events = ", object%n_events
write (u, "(3x,A,I0)") "n_read = ", object%n_read
write (u, "(3x,A,I0)") "n_current = ", object%i_evt
write (u, "(3x,A,L1)") "blanking = ", object%blank
call object%timer%write (u)
else
write (u, "(1x,A)") "Event-sample checkpoints: off"
end if
end subroutine eio_checkpoints_write
@ %def eio_checkpoints_write
@ Finalizer: trivial.
<<EIO checkpoints: eio checkpoints: TBP>>=
procedure :: final => eio_checkpoints_final
<<EIO checkpoints: procedures>>=
subroutine eio_checkpoints_final (object)
class(eio_checkpoints_t), intent(inout) :: object
object%active = .false.
end subroutine eio_checkpoints_final
@ %def eio_checkpoints_final
@ Activate checkpointing for event generation or writing.
<<EIO checkpoints: eio checkpoints: TBP>>=
procedure :: init_out => eio_checkpoints_init_out
<<EIO checkpoints: procedures>>=
subroutine eio_checkpoints_init_out (eio, sample, data, success, extension)
class(eio_checkpoints_t), intent(inout) :: eio
type(string_t), intent(in) :: sample
type(string_t), intent(in), optional :: extension
type(event_sample_data_t), intent(in), optional :: data
logical, intent(out), optional :: success
if (present (data)) then
if (eio%val > 0) then
eio%active = .true.
eio%i_evt = 0
eio%n_read = 0
eio%n_events = data%n_evt * data%nlo_multiplier
end if
end if
if (present (success)) success = .true.
end subroutine eio_checkpoints_init_out
@ %def eio_checkpoints_init_out
@ No checkpointing for event reading.
<<EIO checkpoints: eio checkpoints: TBP>>=
procedure :: init_in => eio_checkpoints_init_in
<<EIO checkpoints: procedures>>=
subroutine eio_checkpoints_init_in (eio, sample, data, success, extension)
class(eio_checkpoints_t), intent(inout) :: eio
type(string_t), intent(in) :: sample
type(string_t), intent(in), optional :: extension
type(event_sample_data_t), intent(inout), optional :: data
logical, intent(out), optional :: success
call msg_bug ("Event checkpoints: event input not supported")
if (present (success)) success = .false.
end subroutine eio_checkpoints_init_in
@ %def eio_checkpoints_init_in
@ Switch from input to output: also not supported.
<<EIO checkpoints: eio checkpoints: TBP>>=
procedure :: switch_inout => eio_checkpoints_switch_inout
<<EIO checkpoints: procedures>>=
subroutine eio_checkpoints_switch_inout (eio, success)
class(eio_checkpoints_t), intent(inout) :: eio
logical, intent(out), optional :: success
call msg_bug ("Event checkpoints: in-out switch not supported")
if (present (success)) success = .false.
end subroutine eio_checkpoints_switch_inout
@ %def eio_checkpoints_switch_inout
@ Checkpoints: display progress for the current event, if applicable.
<<EIO checkpoints: eio checkpoints: TBP>>=
procedure :: output => eio_checkpoints_output
<<EIO checkpoints: procedures>>=
subroutine eio_checkpoints_output (eio, event, i_prc, reading, passed, pacify)
class(eio_checkpoints_t), intent(inout) :: eio
class(generic_event_t), intent(in), target :: event
integer, intent(in) :: i_prc
logical, intent(in), optional :: reading, passed, pacify
logical :: rd
rd = .false.; if (present (reading)) rd = reading
if (eio%active) then
if (.not. eio%running) call eio%startup ()
if (eio%running) then
eio%i_evt = eio%i_evt + 1
if (rd) then
eio%n_read = eio%n_read + 1
else if (mod (eio%i_evt, eio%val) == 0) then
call eio%message (eio%blank)
end if
if (eio%i_evt == eio%n_events) call eio%shutdown ()
end if
end if
end subroutine eio_checkpoints_output
@ %def eio_checkpoints_output
@ When the first event is called, we have to initialize the screen output.
<<EIO checkpoints: eio checkpoints: TBP>>=
procedure :: startup => eio_checkpoints_startup
<<EIO checkpoints: procedures>>=
subroutine eio_checkpoints_startup (eio)
class(eio_checkpoints_t), intent(inout) :: eio
if (eio%active .and. eio%i_evt < eio%n_events) then
call msg_message ("")
call msg_message (checkpoint_bar)
call msg_message (checkpoint_head)
call msg_message (checkpoint_bar)
write (msg_buffer, checkpoint_fmt) 0., 0, eio%n_events - eio%i_evt, "???"
call msg_message ()
eio%running = .true.
call eio%timer%start ()
end if
end subroutine eio_checkpoints_startup
@ %def eio_checkpoints_startup
@ This message is printed at every checkpoint.
<<EIO checkpoints: eio checkpoints: TBP>>=
procedure :: message => eio_checkpoints_message
<<EIO checkpoints: procedures>>=
subroutine eio_checkpoints_message (eio, testflag)
class(eio_checkpoints_t), intent(inout) :: eio
logical, intent(in), optional :: testflag
real :: t
type(time_t) :: time_remaining
type(string_t) :: time_string
call eio%timer%stop ()
t = eio%timer
call eio%timer%restart ()
time_remaining = &
nint (t / (eio%i_evt - eio%n_read) * (eio%n_events - eio%i_evt))
time_string = time_remaining%to_string_ms (blank = testflag)
write (msg_buffer, checkpoint_fmt) &
100 * (eio%i_evt - eio%n_read) / real (eio%n_events - eio%n_read), &
eio%i_evt - eio%n_read, &
eio%n_events - eio%i_evt, &
char (time_string)
call msg_message ()
end subroutine eio_checkpoints_message
@ %def eio_checkpoints_message
@ When the last event is called, wrap up.
<<EIO checkpoints: eio checkpoints: TBP>>=
procedure :: shutdown => eio_checkpoints_shutdown
<<EIO checkpoints: procedures>>=
subroutine eio_checkpoints_shutdown (eio)
class(eio_checkpoints_t), intent(inout) :: eio
if (mod (eio%i_evt, eio%val) /= 0) then
write (msg_buffer, checkpoint_fmt) &
100., eio%i_evt - eio%n_read, 0, "0m:00s"
call msg_message ()
end if
call msg_message (checkpoint_bar)
call msg_message ("")
eio%running = .false.
end subroutine eio_checkpoints_shutdown
@ %def eio_checkpoints_shutdown
<<EIO checkpoints: eio checkpoints: TBP>>=
procedure :: input_i_prc => eio_checkpoints_input_i_prc
procedure :: input_event => eio_checkpoints_input_event
<<EIO checkpoints: procedures>>=
subroutine eio_checkpoints_input_i_prc (eio, i_prc, iostat)
class(eio_checkpoints_t), intent(inout) :: eio
integer, intent(out) :: i_prc
integer, intent(out) :: iostat
call msg_bug ("Event checkpoints: event input not supported")
i_prc = 0
iostat = 1
end subroutine eio_checkpoints_input_i_prc
subroutine eio_checkpoints_input_event (eio, event, iostat)
class(eio_checkpoints_t), intent(inout) :: eio
class(generic_event_t), intent(inout), target :: event
integer, intent(out) :: iostat
call msg_bug ("Event checkpoints: event input not supported")
iostat = 1
end subroutine eio_checkpoints_input_event
@ %def eio_checkpoints_input_i_prc
@ %def eio_checkpoints_input_event
@
<<EIO checkpoints: eio checkpoints: TBP>>=
procedure :: skip => eio_checkpoints_skip
<<EIO checkpoints: procedures>>=
subroutine eio_checkpoints_skip (eio, iostat)
class(eio_checkpoints_t), intent(inout) :: eio
integer, intent(out) :: iostat
iostat = 0
end subroutine eio_checkpoints_skip
@ %def eio_checkpoints_skip
@
\subsection{Message header}
<<EIO checkpoints: parameters>>=
character(*), parameter :: &
checkpoint_head = "| % complete | events generated | events remaining &
&| time remaining"
character(*), parameter :: &
checkpoint_bar = "|==================================================&
&=================|"
character(*), parameter :: &
checkpoint_fmt = "(' ',F5.1,T16,I9,T35,I9,T58,A)"
@ %def checkpoint_head
@ %def checkpoint_bar
@ %def checkpoint_fmt
@ %def checkpointing_t
@
\subsection{Unit tests}
Test module, followed by the corresponding implementation module.
<<[[eio_checkpoints_ut.f90]]>>=
<<File header>>
module eio_checkpoints_ut
use unit_tests
use eio_checkpoints_uti
<<Standard module head>>
<<EIO checkpoints: public test>>
contains
<<EIO checkpoints: test driver>>
end module eio_checkpoints_ut
@ %def eio_checkpoints_ut
@
<<[[eio_checkpoints_uti.f90]]>>=
<<File header>>
module eio_checkpoints_uti
<<Use kinds>>
<<Use strings>>
use event_base
use eio_data
use eio_base
use eio_checkpoints
use eio_base_ut, only: eio_prepare_test, eio_cleanup_test
<<Standard module head>>
<<EIO checkpoints: test declarations>>
contains
<<EIO checkpoints: tests>>
end module eio_checkpoints_uti
@ %def eio_checkpoints_ut
@ API: driver for the unit tests below.
<<EIO checkpoints: public test>>=
public :: eio_checkpoints_test
<<EIO checkpoints: test driver>>=
subroutine eio_checkpoints_test (u, results)
integer, intent(in) :: u
type(test_results_t), intent(inout) :: results
<<EIO checkpoints: execute tests>>
end subroutine eio_checkpoints_test
@ %def eio_checkpoints_test
@
\subsubsection{Test I/O methods}
We test the implementation of all I/O methods.
<<EIO checkpoints: execute tests>>=
call test (eio_checkpoints_1, "eio_checkpoints_1", &
"read and write event contents", &
u, results)
<<EIO checkpoints: test declarations>>=
public :: eio_checkpoints_1
<<EIO checkpoints: tests>>=
subroutine eio_checkpoints_1 (u)
integer, intent(in) :: u
class(generic_event_t), pointer :: event
class(eio_t), allocatable :: eio
type(event_sample_data_t) :: data
type(string_t) :: sample
integer :: i, n_events
write (u, "(A)") "* Test output: eio_checkpoints_1"
write (u, "(A)") "* Purpose: generate a number of events &
&with screen output"
write (u, "(A)")
write (u, "(A)") "* Initialize test process"
call eio_prepare_test (event)
write (u, "(A)")
write (u, "(A)") "* Generate events"
write (u, "(A)")
sample = "eio_checkpoints_1"
allocate (eio_checkpoints_t :: eio)
n_events = 10
call data%init (1, 0)
data%n_evt = n_events
select type (eio)
type is (eio_checkpoints_t)
call eio%set_parameters (checkpoint = 4)
end select
call eio%init_out (sample, data)
do i = 1, n_events
call event%generate (1, [0._default, 0._default])
call eio%output (event, i_prc = 0)
end do
write (u, "(A)") "* Checkpointing status"
write (u, "(A)")
call eio%write (u)
call eio%final ()
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio_cleanup_test (event)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_checkpoints_1"
end subroutine eio_checkpoints_1
@ %def eio_checkpoints_1
@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
\section{Event Generation Callback}
This is an output-only format. Its only use is to write screen
messages every $n$ events, to inform the user about progress.
<<[[eio_callback.f90]]>>=
<<File header>>
module eio_callback
use kinds, only: i64
<<Use strings>>
use io_units
use diagnostics
use cputime
use event_base
use eio_data
use eio_base
<<Standard module head>>
<<EIO callback: public>>
<<EIO callback: types>>
contains
<<EIO callback: procedures>>
end module eio_callback
@ %def eio_callback
@
\subsection{Type}
<<EIO callback: public>>=
public :: eio_callback_t
<<EIO callback: types>>=
type, extends (eio_t) :: eio_callback_t
class(event_callback_t), allocatable :: callback
integer(i64) :: i_evt = 0
integer :: i_interval = 0
integer :: n_interval = 0
! type(timer_t) :: timer
contains
<<EIO callback: eio callback: TBP>>
end type eio_callback_t
@ %def eio_callback_t
@
\subsection{Specific Methods}
Set parameters that are specifically used for callback: the procedure
and the number of events to wait until the procedure is called (again).
<<EIO callback: eio callback: TBP>>=
procedure :: set_parameters => eio_callback_set_parameters
<<EIO callback: procedures>>=
subroutine eio_callback_set_parameters (eio, callback, count_interval)
class(eio_callback_t), intent(inout) :: eio
class(event_callback_t), intent(in) :: callback
integer, intent(in) :: count_interval
allocate (eio%callback, source = callback)
eio%n_interval = count_interval
end subroutine eio_callback_set_parameters
@ %def eio_callback_set_parameters
@
\subsection{Common Methods}
Output. This is not the actual event format, but a readable account
of the current status.
<<EIO callback: eio callback: TBP>>=
procedure :: write => eio_callback_write
<<EIO callback: procedures>>=
subroutine eio_callback_write (object, unit)
class(eio_callback_t), intent(in) :: object
integer, intent(in), optional :: unit
integer :: u
u = given_output_unit (unit)
write (u, "(1x,A)") "Event-sample callback:"
write (u, "(3x,A,I0)") "interval = ", object%n_interval
write (u, "(3x,A,I0)") "evt count = ", object%i_evt
! call object%timer%write (u)
end subroutine eio_callback_write
@ %def eio_callback_write
@ Finalizer: trivial.
<<EIO callback: eio callback: TBP>>=
procedure :: final => eio_callback_final
<<EIO callback: procedures>>=
subroutine eio_callback_final (object)
class(eio_callback_t), intent(inout) :: object
end subroutine eio_callback_final
@ %def eio_callback_final
@ Activate checkpointing for event generation or writing.
<<EIO callback: eio callback: TBP>>=
procedure :: init_out => eio_callback_init_out
<<EIO callback: procedures>>=
subroutine eio_callback_init_out (eio, sample, data, success, extension)
class(eio_callback_t), intent(inout) :: eio
type(string_t), intent(in) :: sample
type(string_t), intent(in), optional :: extension
type(event_sample_data_t), intent(in), optional :: data
logical, intent(out), optional :: success
eio%i_evt = 0
eiO%i_interval = 0
if (present (success)) success = .true.
end subroutine eio_callback_init_out
@ %def eio_callback_init_out
@ No callback for event reading.
<<EIO callback: eio callback: TBP>>=
procedure :: init_in => eio_callback_init_in
<<EIO callback: procedures>>=
subroutine eio_callback_init_in (eio, sample, data, success, extension)
class(eio_callback_t), intent(inout) :: eio
type(string_t), intent(in) :: sample
type(string_t), intent(in), optional :: extension
type(event_sample_data_t), intent(inout), optional :: data
logical, intent(out), optional :: success
call msg_bug ("Event callback: event input not supported")
if (present (success)) success = .false.
end subroutine eio_callback_init_in
@ %def eio_callback_init_in
@ Switch from input to output: also not supported.
<<EIO callback: eio callback: TBP>>=
procedure :: switch_inout => eio_callback_switch_inout
<<EIO callback: procedures>>=
subroutine eio_callback_switch_inout (eio, success)
class(eio_callback_t), intent(inout) :: eio
logical, intent(out), optional :: success
call msg_bug ("Event callback: in-out switch not supported")
if (present (success)) success = .false.
end subroutine eio_callback_switch_inout
@ %def eio_callback_switch_inout
@ The actual callback. First increment counters, then call the
procedure if the counter hits the interval.
<<EIO callback: eio callback: TBP>>=
procedure :: output => eio_callback_output
<<EIO callback: procedures>>=
subroutine eio_callback_output (eio, event, i_prc, reading, passed, pacify)
class(eio_callback_t), intent(inout) :: eio
class(generic_event_t), intent(in), target :: event
integer, intent(in) :: i_prc
logical, intent(in), optional :: reading, passed, pacify
eio%i_evt = eio%i_evt + 1
if (eio%n_interval > 0) then
eio%i_interval = eio%i_interval + 1
if (eio%i_interval >= eio%n_interval) then
call eio%callback%proc (eio%i_evt, event)
eio%i_interval = 0
end if
end if
end subroutine eio_callback_output
@ %def eio_callback_output
@ No input.
<<EIO callback: eio callback: TBP>>=
procedure :: input_i_prc => eio_callback_input_i_prc
procedure :: input_event => eio_callback_input_event
<<EIO callback: procedures>>=
subroutine eio_callback_input_i_prc (eio, i_prc, iostat)
class(eio_callback_t), intent(inout) :: eio
integer, intent(out) :: i_prc
integer, intent(out) :: iostat
call msg_bug ("Event callback: event input not supported")
i_prc = 0
iostat = 1
end subroutine eio_callback_input_i_prc
subroutine eio_callback_input_event (eio, event, iostat)
class(eio_callback_t), intent(inout) :: eio
class(generic_event_t), intent(inout), target :: event
integer, intent(out) :: iostat
call msg_bug ("Event callback: event input not supported")
iostat = 1
end subroutine eio_callback_input_event
@ %def eio_callback_input_i_prc
@ %def eio_callback_input_event
@
<<EIO callback: eio callback: TBP>>=
procedure :: skip => eio_callback_skip
<<EIO callback: procedures>>=
subroutine eio_callback_skip (eio, iostat)
class(eio_callback_t), intent(inout) :: eio
integer, intent(out) :: iostat
iostat = 0
end subroutine eio_callback_skip
@ %def eio_callback_skip
@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
\section{Event Weight Output}
This is an output-only format. For each event, we print the indices
that identify process, process part (MCI group), and term. As
numerical information we print the squared matrix element (trace) and
the event weight.
<<[[eio_weights.f90]]>>=
<<File header>>
module eio_weights
<<Use kinds>>
<<Use strings>>
use io_units
use diagnostics
use event_base
use eio_data
use eio_base
<<Standard module head>>
<<EIO weights: public>>
<<EIO weights: types>>
contains
<<EIO weights: procedures>>
end module eio_weights
@ %def eio_weights
@
\subsection{Type}
<<EIO weights: public>>=
public :: eio_weights_t
<<EIO weights: types>>=
type, extends (eio_t) :: eio_weights_t
logical :: writing = .false.
integer :: unit = 0
logical :: pacify = .false.
contains
<<EIO weights: eio weights: TBP>>
end type eio_weights_t
@ %def eio_weights_t
@
\subsection{Specific Methods}
Set pacify flags.
<<EIO weights: eio weights: TBP>>=
procedure :: set_parameters => eio_weights_set_parameters
<<EIO weights: procedures>>=
subroutine eio_weights_set_parameters (eio, pacify)
class(eio_weights_t), intent(inout) :: eio
logical, intent(in), optional :: pacify
if (present (pacify)) eio%pacify = pacify
eio%extension = "weights.dat"
end subroutine eio_weights_set_parameters
@ %def eio_weights_set_parameters
@
\subsection{Common Methods}
@ Output. This is not the actual event format, but a readable account
of the current object status.
<<EIO weights: eio weights: TBP>>=
procedure :: write => eio_weights_write
<<EIO weights: procedures>>=
subroutine eio_weights_write (object, unit)
class(eio_weights_t), intent(in) :: object
integer, intent(in), optional :: unit
integer :: u
u = given_output_unit (unit)
write (u, "(1x,A)") "Weight stream:"
if (object%writing) then
write (u, "(3x,A,A)") "Writing to file = ", char (object%filename)
write (u, "(3x,A,L1)") "Reduced I/O prec. = ", object%pacify
else
write (u, "(3x,A)") "[closed]"
end if
end subroutine eio_weights_write
@ %def eio_weights_write
@ Finalizer: close any open file.
<<EIO weights: eio weights: TBP>>=
procedure :: final => eio_weights_final
<<EIO weights: procedures>>=
subroutine eio_weights_final (object)
class(eio_weights_t), intent(inout) :: object
if (object%writing) then
write (msg_buffer, "(A,A,A)") "Events: closing weight stream file '", &
char (object%filename), "'"
call msg_message ()
close (object%unit)
object%writing = .false.
end if
end subroutine eio_weights_final
@ %def eio_weights_final
@ Initialize event writing.
<<EIO weights: eio weights: TBP>>=
procedure :: init_out => eio_weights_init_out
<<EIO weights: procedures>>=
subroutine eio_weights_init_out (eio, sample, data, success, extension)
class(eio_weights_t), intent(inout) :: eio
type(string_t), intent(in) :: sample
type(string_t), intent(in), optional :: extension
type(event_sample_data_t), intent(in), optional :: data
logical, intent(out), optional :: success
if (present(extension)) then
eio%extension = extension
else
eio%extension = "weights.dat"
end if
eio%filename = sample // "." // eio%extension
eio%unit = free_unit ()
write (msg_buffer, "(A,A,A)") "Events: writing to weight stream file '", &
char (eio%filename), "'"
call msg_message ()
eio%writing = .true.
open (eio%unit, file = char (eio%filename), &
action = "write", status = "replace")
if (present (success)) success = .true.
end subroutine eio_weights_init_out
@ %def eio_weights_init_out
@ Initialize event reading.
<<EIO weights: eio weights: TBP>>=
procedure :: init_in => eio_weights_init_in
<<EIO weights: procedures>>=
subroutine eio_weights_init_in (eio, sample, data, success, extension)
class(eio_weights_t), intent(inout) :: eio
type(string_t), intent(in) :: sample
type(string_t), intent(in), optional :: extension
type(event_sample_data_t), intent(inout), optional :: data
logical, intent(out), optional :: success
call msg_bug ("Weight stream: event input not supported")
if (present (success)) success = .false.
end subroutine eio_weights_init_in
@ %def eio_weights_init_in
@ Switch from input to output: reopen the file for reading.
<<EIO weights: eio weights: TBP>>=
procedure :: switch_inout => eio_weights_switch_inout
<<EIO weights: procedures>>=
subroutine eio_weights_switch_inout (eio, success)
class(eio_weights_t), intent(inout) :: eio
logical, intent(out), optional :: success
call msg_bug ("Weight stream: in-out switch not supported")
if (present (success)) success = .false.
end subroutine eio_weights_switch_inout
@ %def eio_weights_switch_inout
@ Output an event. Write first the event indices, then weight and two
values of the squared matrix element: [[sqme_ref]] is the value stored
in the event record, and [[sqme_prc]] is the one stored in the process
instance. (They can differ: when recalculating, the former is read
from file and the latter is the result of the new calculation.)
For the alternative entries, the [[sqme]] value is always obtained by
a new calculation, and thus qualifies as [[sqme_prc]].
Don't write the file if the [[passed]] flag is set and false.
<<EIO weights: eio weights: TBP>>=
procedure :: output => eio_weights_output
<<EIO weights: procedures>>=
subroutine eio_weights_output (eio, event, i_prc, reading, passed, pacify)
class(eio_weights_t), intent(inout) :: eio
class(generic_event_t), intent(in), target :: event
integer, intent(in) :: i_prc
logical, intent(in), optional :: reading, passed, pacify
integer :: n_alt, i
real(default) :: weight, sqme_ref, sqme_prc
logical :: evt_pacify, evt_passed
evt_pacify = eio%pacify; if (present (pacify)) evt_pacify = pacify
evt_passed = .true.; if (present (passed)) evt_passed = passed
if (eio%writing) then
if (evt_passed) then
weight = event%get_weight_prc ()
sqme_ref = event%get_sqme_ref ()
sqme_prc = event%get_sqme_prc ()
n_alt = event%get_n_alt ()
1 format (I0,3(1x,ES17.10),3(1x,I0))
2 format (I0,3(1x,ES15.8),3(1x,I0))
if (evt_pacify) then
write (eio%unit, 2) 0, weight, sqme_prc, sqme_ref, &
i_prc
else
write (eio%unit, 1) 0, weight, sqme_prc, sqme_ref, &
i_prc
end if
do i = 1, n_alt
weight = event%get_weight_alt(i)
sqme_prc = event%get_sqme_alt(i)
if (evt_pacify) then
write (eio%unit, 2) i, weight, sqme_prc
else
write (eio%unit, 1) i, weight, sqme_prc
end if
end do
end if
else
call eio%write ()
call msg_fatal ("Weight stream file is not open for writing")
end if
end subroutine eio_weights_output
@ %def eio_weights_output
@ Input an event.
<<EIO weights: eio weights: TBP>>=
procedure :: input_i_prc => eio_weights_input_i_prc
procedure :: input_event => eio_weights_input_event
<<EIO weights: procedures>>=
subroutine eio_weights_input_i_prc (eio, i_prc, iostat)
class(eio_weights_t), intent(inout) :: eio
integer, intent(out) :: i_prc
integer, intent(out) :: iostat
call msg_bug ("Weight stream: event input not supported")
i_prc = 0
iostat = 1
end subroutine eio_weights_input_i_prc
subroutine eio_weights_input_event (eio, event, iostat)
class(eio_weights_t), intent(inout) :: eio
class(generic_event_t), intent(inout), target :: event
integer, intent(out) :: iostat
call msg_bug ("Weight stream: event input not supported")
iostat = 1
end subroutine eio_weights_input_event
@ %def eio_weights_input_i_prc
@ %def eio_weights_input_event
@
<<EIO weights: eio weights: TBP>>=
procedure :: skip => eio_weights_skip
<<EIO weights: procedures>>=
subroutine eio_weights_skip (eio, iostat)
class(eio_weights_t), intent(inout) :: eio
integer, intent(out) :: iostat
iostat = 0
end subroutine eio_weights_skip
@ %def eio_weights_skip
@
\subsection{Unit tests}
Test module, followed by the corresponding implementation module.
<<[[eio_weights_ut.f90]]>>=
<<File header>>
module eio_weights_ut
use unit_tests
use eio_weights_uti
<<Standard module head>>
<<EIO weights: public test>>
contains
<<EIO weights: test driver>>
end module eio_weights_ut
@ %def eio_weights_ut
@
<<[[eio_weights_uti.f90]]>>=
<<File header>>
module eio_weights_uti
<<Use kinds>>
<<Use strings>>
use io_units
use event_base
use eio_data
use eio_base
use eio_weights
use eio_base_ut, only: eio_prepare_test, eio_cleanup_test
<<Standard module head>>
<<EIO weights: test declarations>>
contains
<<EIO weights: tests>>
end module eio_weights_uti
@ %def eio_weights_ut
@ API: driver for the unit tests below.
<<EIO weights: public test>>=
public :: eio_weights_test
<<EIO weights: test driver>>=
subroutine eio_weights_test (u, results)
integer, intent(in) :: u
type(test_results_t), intent(inout) :: results
<<EIO weights: execute tests>>
end subroutine eio_weights_test
@ %def eio_weights_test
@
\subsubsection{Simple event}
We test the implementation of all I/O methods.
<<EIO weights: execute tests>>=
call test (eio_weights_1, "eio_weights_1", &
"read and write event contents", &
u, results)
<<EIO weights: test declarations>>=
public :: eio_weights_1
<<EIO weights: tests>>=
subroutine eio_weights_1 (u)
integer, intent(in) :: u
class(generic_event_t), pointer :: event
class(eio_t), allocatable :: eio
type(string_t) :: sample
integer :: u_file
character(80) :: buffer
write (u, "(A)") "* Test output: eio_weights_1"
write (u, "(A)") "* Purpose: generate an event and write weight to file"
write (u, "(A)")
write (u, "(A)") "* Initialize test process"
call eio_prepare_test (event, unweighted = .false.)
write (u, "(A)")
write (u, "(A)") "* Generate and write an event"
write (u, "(A)")
sample = "eio_weights_1"
allocate (eio_weights_t :: eio)
call eio%init_out (sample)
call event%generate (1, [0._default, 0._default])
call eio%output (event, i_prc = 42)
call eio%write (u)
call eio%final ()
write (u, "(A)")
write (u, "(A)") "* File contents: &
&(weight, sqme(evt), sqme(prc), i_prc)"
write (u, "(A)")
u_file = free_unit ()
open (u_file, file = "eio_weights_1.weights.dat", &
action = "read", status = "old")
read (u_file, "(A)") buffer
write (u, "(A)") trim (buffer)
close (u_file)
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio_cleanup_test (event)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_weights_1"
end subroutine eio_weights_1
@ %def eio_weights_1
@
\subsubsection{Multiple weights}
Event with several weight entries set.
<<EIO weights: execute tests>>=
call test (eio_weights_2, "eio_weights_2", &
"multiple weights", &
u, results)
<<EIO weights: test declarations>>=
public :: eio_weights_2
<<EIO weights: tests>>=
subroutine eio_weights_2 (u)
integer, intent(in) :: u
class(generic_event_t), pointer :: event
class(eio_t), allocatable :: eio
type(string_t) :: sample
integer :: u_file, i
character(80) :: buffer
write (u, "(A)") "* Test output: eio_weights_2"
write (u, "(A)") "* Purpose: generate an event and write weight to file"
write (u, "(A)")
write (u, "(A)") "* Initialize test process"
call eio_prepare_test (event, unweighted = .false., n_alt = 2)
write (u, "(A)")
write (u, "(A)") "* Generate and write an event"
write (u, "(A)")
sample = "eio_weights_2"
allocate (eio_weights_t :: eio)
call eio%init_out (sample)
select type (eio)
type is (eio_weights_t)
call eio%set_parameters (pacify = .true.)
end select
call event%generate (1, [0._default, 0._default])
call event%set (sqme_alt = [2._default, 3._default])
call event%set (weight_alt = &
[2 * event%get_weight_prc (), 3 * event%get_weight_prc ()])
call eio%output (event, i_prc = 42)
call eio%write (u)
call eio%final ()
write (u, "(A)")
write (u, "(A)") "* File contents: &
&(weight, sqme(evt), sqme(prc), i_prc)"
write (u, "(A)")
u_file = free_unit ()
open (u_file, file = "eio_weights_2.weights.dat", &
action = "read", status = "old")
do i = 1, 3
read (u_file, "(A)") buffer
write (u, "(A)") trim (buffer)
end do
close (u_file)
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio_cleanup_test (event)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_weights_2"
end subroutine eio_weights_2
@ %def eio_weights_2
@
\subsubsection{Multiple events}
Events with [[passed]] flag switched on/off.
<<EIO weights: execute tests>>=
call test (eio_weights_3, "eio_weights_3", &
"check passed-flag", &
u, results)
<<EIO weights: test declarations>>=
public :: eio_weights_3
<<EIO weights: tests>>=
subroutine eio_weights_3 (u)
integer, intent(in) :: u
class(generic_event_t), pointer :: event
class(eio_t), allocatable :: eio
type(string_t) :: sample
integer :: u_file, iostat
character(80) :: buffer
write (u, "(A)") "* Test output: eio_weights_3"
write (u, "(A)") "* Purpose: generate three events and write to file"
write (u, "(A)")
write (u, "(A)") "* Initialize test process"
call eio_prepare_test (event, unweighted = .false.)
write (u, "(A)")
write (u, "(A)") "* Generate and write events"
write (u, "(A)")
sample = "eio_weights_3"
allocate (eio_weights_t :: eio)
select type (eio)
type is (eio_weights_t)
call eio%set_parameters (pacify = .true.)
end select
call eio%init_out (sample)
call event%generate (1, [0._default, 0._default])
call eio%output (event, i_prc = 1)
call event%generate (1, [0.1_default, 0._default])
call eio%output (event, i_prc = 1, passed = .false.)
call event%generate (1, [0.2_default, 0._default])
call eio%output (event, i_prc = 1, passed = .true.)
call eio%write (u)
call eio%final ()
write (u, "(A)")
write (u, "(A)") "* File contents: &
&(weight, sqme(evt), sqme(prc), i_prc), should be just two entries"
write (u, "(A)")
u_file = free_unit ()
open (u_file, file = "eio_weights_3.weights.dat", &
action = "read", status = "old")
do
read (u_file, "(A)", iostat=iostat) buffer
if (iostat /= 0) exit
write (u, "(A)") trim (buffer)
end do
close (u_file)
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio_cleanup_test (event)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_weights_3"
end subroutine eio_weights_3
@ %def eio_weights_3
@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
\section{Event Dump Output}
This is an output-only format. We simply dump the contents of the
[[particle_set]], using the [[write]] method of that type. The
event-format options are the options of that procedure.
<<[[eio_dump.f90]]>>=
<<File header>>
module eio_dump
use, intrinsic :: iso_fortran_env, only: output_unit
use kinds, only: i64
<<Use strings>>
use format_utils, only: write_separator
use format_utils, only: pac_fmt
use format_defs, only: FMT_16, FMT_19
use io_units
use diagnostics
use event_base
use eio_data
use eio_base
<<Standard module head>>
<<EIO dump: public>>
<<EIO dump: types>>
contains
<<EIO dump: procedures>>
end module eio_dump
@ %def eio_dump
@
\subsection{Type}
<<EIO dump: public>>=
public :: eio_dump_t
<<EIO dump: types>>=
type, extends (eio_t) :: eio_dump_t
integer(i64) :: count = 0
integer :: unit = 0
logical :: writing = .false.
logical :: screen = .false.
logical :: pacify = .false.
logical :: weights = .false.
logical :: compressed = .false.
logical :: summary = .false.
contains
<<EIO dump: eio dump: TBP>>
end type eio_dump_t
@ %def eio_dump_t
@
\subsection{Specific Methods}
Set control parameters. We may provide a [[unit]] for input or output; this
will be taken if the sample file name is empty. In that case, the unit is
assumed to be open and will be kept open; no messages will be issued.
<<EIO dump: eio dump: TBP>>=
procedure :: set_parameters => eio_dump_set_parameters
<<EIO dump: procedures>>=
subroutine eio_dump_set_parameters (eio, extension, &
pacify, weights, compressed, summary, screen, unit)
class(eio_dump_t), intent(inout) :: eio
type(string_t), intent(in), optional :: extension
logical, intent(in), optional :: pacify
logical, intent(in), optional :: weights
logical, intent(in), optional :: compressed
logical, intent(in), optional :: summary
logical, intent(in), optional :: screen
integer, intent(in), optional :: unit
if (present (pacify)) eio%pacify = pacify
if (present (weights)) eio%weights = weights
if (present (compressed)) eio%compressed = compressed
if (present (summary)) eio%summary = summary
if (present (screen)) eio%screen = screen
if (present (unit)) eio%unit = unit
eio%extension = "pset.dat"
if (present (extension)) eio%extension = extension
end subroutine eio_dump_set_parameters
@ %def eio_dump_set_parameters
@
\subsection{Common Methods}
@ Output. This is not the actual event format, but a readable account
of the current object status.
<<EIO dump: eio dump: TBP>>=
procedure :: write => eio_dump_write
<<EIO dump: procedures>>=
subroutine eio_dump_write (object, unit)
class(eio_dump_t), intent(in) :: object
integer, intent(in), optional :: unit
integer :: u
u = given_output_unit (unit)
write (u, "(1x,A)") "Dump event stream:"
if (object%writing) then
write (u, "(3x,A,L1)") "Screen output = ", object%screen
write (u, "(3x,A,A,A)") "Writing to file = '", char (object%filename), "'"
write (u, "(3x,A,L1)") "Reduced I/O prec. = ", object%pacify
write (u, "(3x,A,L1)") "Show weights/sqme = ", object%weights
write (u, "(3x,A,L1)") "Compressed = ", object%compressed
write (u, "(3x,A,L1)") "Summary = ", object%summary
else
write (u, "(3x,A)") "[closed]"
end if
end subroutine eio_dump_write
@ %def eio_dump_write
@ Finalizer: close any open file.
<<EIO dump: eio dump: TBP>>=
procedure :: final => eio_dump_final
<<EIO dump: procedures>>=
subroutine eio_dump_final (object)
class(eio_dump_t), intent(inout) :: object
if (object%screen) then
write (msg_buffer, "(A,A,A)") "Events: display complete"
call msg_message ()
object%screen = .false.
end if
if (object%writing) then
if (object%filename /= "") then
write (msg_buffer, "(A,A,A)") "Events: closing event dump file '", &
char (object%filename), "'"
call msg_message ()
close (object%unit)
end if
object%writing = .false.
end if
end subroutine eio_dump_final
@ %def eio_dump_final
@ Initialize event writing.
<<EIO dump: eio dump: TBP>>=
procedure :: init_out => eio_dump_init_out
<<EIO dump: procedures>>=
subroutine eio_dump_init_out (eio, sample, data, success, extension)
class(eio_dump_t), intent(inout) :: eio
type(string_t), intent(in) :: sample
type(string_t), intent(in), optional :: extension
type(event_sample_data_t), intent(in), optional :: data
logical, intent(out), optional :: success
if (present(extension)) then
eio%extension = extension
else
eio%extension = "pset.dat"
end if
if (sample == "" .and. eio%unit /= 0) then
eio%filename = ""
eio%writing = .true.
else if (sample /= "") then
eio%filename = sample // "." // eio%extension
eio%unit = free_unit ()
write (msg_buffer, "(A,A,A)") "Events: writing to event dump file '", &
char (eio%filename), "'"
call msg_message ()
eio%writing = .true.
open (eio%unit, file = char (eio%filename), &
action = "write", status = "replace")
end if
if (eio%screen) then
write (msg_buffer, "(A,A,A)") "Events: display on standard output"
call msg_message ()
end if
eio%count = 0
if (present (success)) success = .true.
end subroutine eio_dump_init_out
@ %def eio_dump_init_out
@ Initialize event reading.
<<EIO dump: eio dump: TBP>>=
procedure :: init_in => eio_dump_init_in
<<EIO dump: procedures>>=
subroutine eio_dump_init_in (eio, sample, data, success, extension)
class(eio_dump_t), intent(inout) :: eio
type(string_t), intent(in) :: sample
type(string_t), intent(in), optional :: extension
type(event_sample_data_t), intent(inout), optional :: data
logical, intent(out), optional :: success
call msg_bug ("Event dump: event input not supported")
if (present (success)) success = .false.
end subroutine eio_dump_init_in
@ %def eio_dump_init_in
@ Switch from input to output: reopen the file for reading.
<<EIO dump: eio dump: TBP>>=
procedure :: switch_inout => eio_dump_switch_inout
<<EIO dump: procedures>>=
subroutine eio_dump_switch_inout (eio, success)
class(eio_dump_t), intent(inout) :: eio
logical, intent(out), optional :: success
call msg_bug ("Event dump: in-out switch not supported")
if (present (success)) success = .false.
end subroutine eio_dump_switch_inout
@ %def eio_dump_switch_inout
@ Output an event. Delegate the output call to the [[write]] method
of the current particle set, if valid. Output both to file (if defined)
and to screen (if requested).
<<EIO dump: eio dump: TBP>>=
procedure :: output => eio_dump_output
<<EIO dump: procedures>>=
subroutine eio_dump_output (eio, event, i_prc, reading, passed, pacify)
class(eio_dump_t), intent(inout) :: eio
class(generic_event_t), intent(in), target :: event
integer, intent(in) :: i_prc
logical, intent(in), optional :: reading, passed, pacify
character(len=7) :: fmt
eio%count = eio%count + 1
if (present (pacify)) then
call pac_fmt (fmt, FMT_19, FMT_16, pacify)
else
call pac_fmt (fmt, FMT_19, FMT_16, eio%pacify)
end if
if (eio%writing) call dump (eio%unit)
if (eio%screen) then
call dump (output_unit)
if (logfile_unit () > 0) call dump (logfile_unit ())
end if
contains
subroutine dump (u)
integer, intent(in) :: u
integer :: i
call write_separator (u, 2)
write (u, "(1x,A,I0)", advance="no") "Event"
if (event%has_index ()) then
write (u, "(1x,'#',I0)") event%get_index ()
else
write (u, *)
end if
call write_separator (u, 2)
write (u, "(1x,A,1x,I0)") "count =", eio%count
if (present (passed)) then
write (u, "(1x,A,1x,L1)") "passed =", passed
else
write (u, "(1x,A)") "passed = [N/A]"
end if
write (u, "(1x,A,1x,I0)") "prc id =", i_prc
if (eio%weights) then
call write_separator (u)
if (event%sqme_ref_known) then
write (u, "(1x,A," // fmt // ")") "sqme (ref) = ", &
event%sqme_ref
else
write (u, "(1x,A)") "sqme (ref) = [undefined]"
end if
if (event%sqme_prc_known) then
write (u, "(1x,A," // fmt // ")") "sqme (prc) = ", &
event%sqme_prc
else
write (u, "(1x,A)") "sqme (prc) = [undefined]"
end if
if (event%weight_ref_known) then
write (u, "(1x,A," // fmt // ")") "weight (ref) = ", &
event%weight_ref
else
write (u, "(1x,A)") "weight (ref) = [undefined]"
end if
if (event%weight_prc_known) then
write (u, "(1x,A," // fmt // ")") "weight (prc) = ", &
event%weight_prc
else
write (u, "(1x,A)") "weight (prc) = [undefined]"
end if
if (event%excess_prc_known) then
write (u, "(1x,A," // fmt // ")") "excess (prc) = ", &
event%excess_prc
else
write (u, "(1x,A)") "excess (prc) = [undefined]"
end if
do i = 1, event%n_alt
if (event%sqme_ref_known) then
write (u, "(1x,A,I0,A," // fmt // ")") "sqme (", i, ") = ",&
event%sqme_prc
else
write (u, "(1x,A,I0,A)") "sqme (", i, ") = [undefined]"
end if
if (event%weight_prc_known) then
write (u, "(1x,A,I0,A," // fmt // ")") "weight (", i, ") = ",&
event%weight_prc
else
write (u, "(1x,A,I0,A)") "weight (", i, ") = [undefined]"
end if
end do
end if
call write_separator (u)
if (event%particle_set_is_valid) then
call event%particle_set%write (unit = u, &
summary = eio%summary, compressed = eio%compressed, &
testflag = eio%pacify)
else
write (u, "(1x,A)") "Particle set: [invalid]"
end if
end subroutine dump
end subroutine eio_dump_output
@ %def eio_dump_output
@ Input an event.
<<EIO dump: eio dump: TBP>>=
procedure :: input_i_prc => eio_dump_input_i_prc
procedure :: input_event => eio_dump_input_event
<<EIO dump: procedures>>=
subroutine eio_dump_input_i_prc (eio, i_prc, iostat)
class(eio_dump_t), intent(inout) :: eio
integer, intent(out) :: i_prc
integer, intent(out) :: iostat
call msg_bug ("Dump stream: event input not supported")
i_prc = 0
iostat = 1
end subroutine eio_dump_input_i_prc
subroutine eio_dump_input_event (eio, event, iostat)
class(eio_dump_t), intent(inout) :: eio
class(generic_event_t), intent(inout), target :: event
integer, intent(out) :: iostat
call msg_bug ("Dump stream: event input not supported")
iostat = 1
end subroutine eio_dump_input_event
@ %def eio_dump_input_i_prc
@ %def eio_dump_input_event
@
<<EIO dump: eio dump: TBP>>=
procedure :: skip => eio_dump_skip
<<EIO dump: procedures>>=
subroutine eio_dump_skip (eio, iostat)
class(eio_dump_t), intent(inout) :: eio
integer, intent(out) :: iostat
iostat = 0
end subroutine eio_dump_skip
@ %def eio_dump_skip
@
\subsection{Unit tests}
Test module, followed by the corresponding implementation module.
<<[[eio_dump_ut.f90]]>>=
<<File header>>
module eio_dump_ut
use unit_tests
use eio_dump_uti
<<Standard module head>>
<<EIO dump: public test>>
contains
<<EIO dump: test driver>>
end module eio_dump_ut
@ %def eio_dump_ut
@
<<[[eio_dump_uti.f90]]>>=
<<File header>>
module eio_dump_uti
<<Use kinds>>
<<Use strings>>
use io_units
use event_base
use eio_data
use eio_base
use eio_dump
use eio_base_ut, only: eio_prepare_test, eio_cleanup_test
<<Standard module head>>
<<EIO dump: test declarations>>
contains
<<EIO dump: tests>>
end module eio_dump_uti
@ %def eio_dump_ut
@ API: driver for the unit tests below.
<<EIO dump: public test>>=
public :: eio_dump_test
<<EIO dump: test driver>>=
subroutine eio_dump_test (u, results)
integer, intent(in) :: u
type(test_results_t), intent(inout) :: results
<<EIO dump: execute tests>>
end subroutine eio_dump_test
@ %def eio_dump_test
@
\subsubsection{Test I/O methods}
We test the implementation of all I/O methods.
<<EIO dump: execute tests>>=
call test (eio_dump_1, "eio_dump_1", &
"write event contents", &
u, results)
<<EIO dump: test declarations>>=
public :: eio_dump_1
<<EIO dump: tests>>=
subroutine eio_dump_1 (u)
integer, intent(in) :: u
class(generic_event_t), pointer :: event
class(eio_t), allocatable :: eio
integer :: i_prc
integer :: u_file
write (u, "(A)") "* Test output: eio_dump_1"
write (u, "(A)") "* Purpose: generate events and write essentials to output"
write (u, "(A)")
write (u, "(A)") "* Initialize test process"
call eio_prepare_test (event, unweighted = .false.)
write (u, "(A)")
write (u, "(A)") "* Generate and write three events (two passed)"
write (u, "(A)")
allocate (eio_dump_t :: eio)
select type (eio)
type is (eio_dump_t)
call eio%set_parameters (unit = u, weights = .true., pacify = .true.)
end select
i_prc = 42
call eio%init_out (var_str (""))
call event%generate (1, [0._default, 0._default])
call eio%output (event, i_prc = i_prc)
call event%generate (1, [0.1_default, 0._default])
call event%set_index (99)
call eio%output (event, i_prc = i_prc, passed = .false.)
call event%generate (1, [0.2_default, 0._default])
call event%increment_index ()
call eio%output (event, i_prc = i_prc, passed = .true.)
write (u, "(A)")
write (u, "(A)") "* Contents of eio_dump object"
write (u, "(A)")
call eio%write (u)
write (u, "(A)")
write (u, "(A)") "* Cleanup"
select type (eio)
type is (eio_dump_t)
eio%writing = .false.
end select
call eio%final ()
call eio_cleanup_test (event)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_dump_1"
end subroutine eio_dump_1
@ %def eio_dump_1
@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
\section{ASCII File Formats}
Here, we implement several ASCII file formats. It is possible to
switch between them using flags.
<<[[eio_ascii.f90]]>>=
<<File header>>
module eio_ascii
<<Use strings>>
use io_units
use diagnostics
use event_base
use eio_data
use eio_base
use hep_common
use hep_events
<<Standard module head>>
<<EIO ascii: public>>
<<EIO ascii: types>>
contains
<<EIO ascii: procedures>>
end module eio_ascii
@ %def eio_ascii
@
\subsection{Type}
<<EIO ascii: public>>=
public :: eio_ascii_t
<<EIO ascii: types>>=
type, abstract, extends (eio_t) :: eio_ascii_t
logical :: writing = .false.
integer :: unit = 0
logical :: keep_beams = .false.
logical :: keep_remnants = .true.
logical :: ensure_order = .false.
contains
<<EIO ascii: eio ascii: TBP>>
end type eio_ascii_t
@ %def eio_ascii_t
@
<<EIO ascii: public>>=
public :: eio_ascii_ascii_t
<<EIO ascii: types>>=
type, extends (eio_ascii_t) :: eio_ascii_ascii_t
end type eio_ascii_ascii_t
@ %def eio_ascii_ascii_t
@
<<EIO ascii: public>>=
public :: eio_ascii_athena_t
<<EIO ascii: types>>=
type, extends (eio_ascii_t) :: eio_ascii_athena_t
end type eio_ascii_athena_t
@ %def eio_ascii_athena_t
@ The debug format has a few options that can be controlled by
Sindarin variables.
<<EIO ascii: public>>=
public :: eio_ascii_debug_t
<<EIO ascii: types>>=
type, extends (eio_ascii_t) :: eio_ascii_debug_t
logical :: show_process = .true.
logical :: show_transforms = .true.
logical :: show_decay = .true.
logical :: verbose = .true.
end type eio_ascii_debug_t
@ %def eio_ascii_debug_t
@
<<EIO ascii: public>>=
public :: eio_ascii_hepevt_t
<<EIO ascii: types>>=
type, extends (eio_ascii_t) :: eio_ascii_hepevt_t
end type eio_ascii_hepevt_t
@ %def eio_ascii_hepevt_t
@
<<EIO ascii: public>>=
public :: eio_ascii_hepevt_verb_t
<<EIO ascii: types>>=
type, extends (eio_ascii_t) :: eio_ascii_hepevt_verb_t
end type eio_ascii_hepevt_verb_t
@ %def eio_ascii_hepevt_verb_t
@
<<EIO ascii: public>>=
public :: eio_ascii_lha_t
<<EIO ascii: types>>=
type, extends (eio_ascii_t) :: eio_ascii_lha_t
end type eio_ascii_lha_t
@ %def eio_ascii_lha_t
@
<<EIO ascii: public>>=
public :: eio_ascii_lha_verb_t
<<EIO ascii: types>>=
type, extends (eio_ascii_t) :: eio_ascii_lha_verb_t
end type eio_ascii_lha_verb_t
@ %def eio_ascii_lha_verb_t
@
<<EIO ascii: public>>=
public :: eio_ascii_long_t
<<EIO ascii: types>>=
type, extends (eio_ascii_t) :: eio_ascii_long_t
end type eio_ascii_long_t
@ %def eio_ascii_long_t
@
<<EIO ascii: public>>=
public :: eio_ascii_mokka_t
<<EIO ascii: types>>=
type, extends (eio_ascii_t) :: eio_ascii_mokka_t
end type eio_ascii_mokka_t
@ %def eio_ascii_mokka_t
@
<<EIO ascii: public>>=
public :: eio_ascii_short_t
<<EIO ascii: types>>=
type, extends (eio_ascii_t) :: eio_ascii_short_t
end type eio_ascii_short_t
@ %def eio_ascii_short_t
@
\subsection{Specific Methods}
Set parameters that are specifically used with ASCII file formats. In
particular, this is the file extension.
<<EIO ascii: eio ascii: TBP>>=
procedure :: set_parameters => eio_ascii_set_parameters
<<EIO ascii: procedures>>=
subroutine eio_ascii_set_parameters (eio, &
keep_beams, keep_remnants, ensure_order, extension, &
show_process, show_transforms, show_decay, verbose)
class(eio_ascii_t), intent(inout) :: eio
logical, intent(in), optional :: keep_beams
logical, intent(in), optional :: keep_remnants
logical, intent(in), optional :: ensure_order
type(string_t), intent(in), optional :: extension
logical, intent(in), optional :: show_process, show_transforms, show_decay
logical, intent(in), optional :: verbose
if (present (keep_beams)) eio%keep_beams = keep_beams
if (present (keep_remnants)) eio%keep_remnants = keep_remnants
if (present (ensure_order)) eio%ensure_order = ensure_order
if (present (extension)) then
eio%extension = extension
else
select type (eio)
type is (eio_ascii_ascii_t)
eio%extension = "evt"
type is (eio_ascii_athena_t)
eio%extension = "athena.evt"
type is (eio_ascii_debug_t)
eio%extension = "debug"
type is (eio_ascii_hepevt_t)
eio%extension = "hepevt"
type is (eio_ascii_hepevt_verb_t)
eio%extension = "hepevt.verb"
type is (eio_ascii_lha_t)
eio%extension = "lha"
type is (eio_ascii_lha_verb_t)
eio%extension = "lha.verb"
type is (eio_ascii_long_t)
eio%extension = "long.evt"
type is (eio_ascii_mokka_t)
eio%extension = "mokka.evt"
type is (eio_ascii_short_t)
eio%extension = "short.evt"
end select
end if
select type (eio)
type is (eio_ascii_debug_t)
if (present (show_process)) eio%show_process = show_process
if (present (show_transforms)) eio%show_transforms = show_transforms
if (present (show_decay)) eio%show_decay = show_decay
if (present (verbose)) eio%verbose = verbose
end select
end subroutine eio_ascii_set_parameters
@ %def eio_ascii_set_parameters
@
\subsection{Common Methods}
Output. This is not the actual event format, but a readable account
of the current object status.
<<EIO ascii: eio ascii: TBP>>=
procedure :: write => eio_ascii_write
<<EIO ascii: procedures>>=
subroutine eio_ascii_write (object, unit)
class(eio_ascii_t), intent(in) :: object
integer, intent(in), optional :: unit
integer :: u
u = given_output_unit (unit)
select type (object)
type is (eio_ascii_ascii_t)
write (u, "(1x,A)") "ASCII event stream (default format):"
type is (eio_ascii_athena_t)
write (u, "(1x,A)") "ASCII event stream (ATHENA format):"
type is (eio_ascii_debug_t)
write (u, "(1x,A)") "ASCII event stream (Debugging format):"
type is (eio_ascii_hepevt_t)
write (u, "(1x,A)") "ASCII event stream (HEPEVT format):"
type is (eio_ascii_hepevt_verb_t)
write (u, "(1x,A)") "ASCII event stream (verbose HEPEVT format):"
type is (eio_ascii_lha_t)
write (u, "(1x,A)") "ASCII event stream (LHA format):"
type is (eio_ascii_lha_verb_t)
write (u, "(1x,A)") "ASCII event stream (verbose LHA format):"
type is (eio_ascii_long_t)
write (u, "(1x,A)") "ASCII event stream (long format):"
type is (eio_ascii_mokka_t)
write (u, "(1x,A)") "ASCII event stream (MOKKA format):"
type is (eio_ascii_short_t)
write (u, "(1x,A)") "ASCII event stream (short format):"
end select
if (object%writing) then
write (u, "(3x,A,A)") "Writing to file = ", char (object%filename)
else
write (u, "(3x,A)") "[closed]"
end if
write (u, "(3x,A,L1)") "Keep beams = ", object%keep_beams
write (u, "(3x,A,L1)") "Keep remnants = ", object%keep_remnants
select type (object)
type is (eio_ascii_debug_t)
write (u, "(3x,A,L1)") "Show process = ", object%show_process
write (u, "(3x,A,L1)") "Show transforms = ", object%show_transforms
write (u, "(3x,A,L1)") "Show decay tree = ", object%show_decay
write (u, "(3x,A,L1)") "Verbose output = ", object%verbose
end select
end subroutine eio_ascii_write
@ %def eio_ascii_write
@ Finalizer: close any open file.
<<EIO ascii: eio ascii: TBP>>=
procedure :: final => eio_ascii_final
<<EIO ascii: procedures>>=
subroutine eio_ascii_final (object)
class(eio_ascii_t), intent(inout) :: object
if (object%writing) then
write (msg_buffer, "(A,A,A)") "Events: closing ASCII file '", &
char (object%filename), "'"
call msg_message ()
close (object%unit)
object%writing = .false.
end if
end subroutine eio_ascii_final
@ %def eio_ascii_final
@ Initialize event writing.
Check weight normalization. This applies to all ASCII-type files that
use the HEPRUP common block. We can't allow normalization conventions
that are not covered by the HEPRUP definition.
<<EIO ascii: eio ascii: TBP>>=
procedure :: init_out => eio_ascii_init_out
<<EIO ascii: procedures>>=
subroutine eio_ascii_init_out (eio, sample, data, success, extension)
class(eio_ascii_t), intent(inout) :: eio
type(string_t), intent(in) :: sample
type(string_t), intent(in), optional :: extension
type(event_sample_data_t), intent(in), optional :: data
logical, intent(out), optional :: success
integer :: i
if (.not. present (data)) &
call msg_bug ("ASCII initialization: missing data")
if (data%n_beam /= 2) &
call msg_fatal ("ASCII: defined for scattering processes only")
eio%sample = sample
call eio%check_normalization (data)
call eio%set_splitting (data)
call eio%set_filename ()
eio%unit = free_unit ()
write (msg_buffer, "(A,A,A)") "Events: writing to ASCII file '", &
char (eio%filename), "'"
call msg_message ()
eio%writing = .true.
open (eio%unit, file = char (eio%filename), &
action = "write", status = "replace")
select type (eio)
type is (eio_ascii_lha_t)
call heprup_init &
(data%pdg_beam, &
data%energy_beam, &
n_processes = data%n_proc, &
unweighted = data%unweighted, &
negative_weights = data%negative_weights)
do i = 1, data%n_proc
call heprup_set_process_parameters (i = i, &
process_id = data%proc_num_id(i), &
cross_section = data%cross_section(i), &
error = data%error(i))
end do
call heprup_write_ascii (eio%unit)
type is (eio_ascii_lha_verb_t)
call heprup_init &
(data%pdg_beam, &
data%energy_beam, &
n_processes = data%n_proc, &
unweighted = data%unweighted, &
negative_weights = data%negative_weights)
do i = 1, data%n_proc
call heprup_set_process_parameters (i = i, &
process_id = data%proc_num_id(i), &
cross_section = data%cross_section(i), &
error = data%error(i))
end do
call heprup_write_verbose (eio%unit)
end select
if (present (success)) success = .true.
end subroutine eio_ascii_init_out
@ %def eio_ascii_init_out
@ Some event properties do not go well with some output formats. In
particular, many formats require unweighted events.
<<EIO ascii: eio ascii: TBP>>=
procedure :: check_normalization => eio_ascii_check_normalization
<<EIO ascii: procedures>>=
subroutine eio_ascii_check_normalization (eio, data)
class(eio_ascii_t), intent(in) :: eio
type(event_sample_data_t), intent(in) :: data
if (data%unweighted) then
else
select type (eio)
type is (eio_ascii_athena_t); call msg_fatal &
("Event output (Athena format): events must be unweighted.")
type is (eio_ascii_hepevt_t); call msg_fatal &
("Event output (HEPEVT format): events must be unweighted.")
type is (eio_ascii_hepevt_verb_t); call msg_fatal &
("Event output (HEPEVT format): events must be unweighted.")
end select
select case (data%norm_mode)
case (NORM_SIGMA)
case default
select type (eio)
type is (eio_ascii_lha_t)
call msg_fatal &
("Event output (LHA): normalization for weighted events &
&must be 'sigma'")
type is (eio_ascii_lha_verb_t)
call msg_fatal &
("Event output (LHA): normalization for weighted events &
&must be 'sigma'")
end select
end select
end if
end subroutine eio_ascii_check_normalization
@ %def check_normalization
@ Initialize event reading.
<<EIO ascii: eio ascii: TBP>>=
procedure :: init_in => eio_ascii_init_in
<<EIO ascii: procedures>>=
subroutine eio_ascii_init_in (eio, sample, data, success, extension)
class(eio_ascii_t), intent(inout) :: eio
type(string_t), intent(in) :: sample
type(string_t), intent(in), optional :: extension
type(event_sample_data_t), intent(inout), optional :: data
logical, intent(out), optional :: success
call msg_bug ("ASCII: event input not supported")
if (present (success)) success = .false.
end subroutine eio_ascii_init_in
@ %def eio_ascii_init_in
@ Switch from input to output: reopen the file for reading.
<<EIO ascii: eio ascii: TBP>>=
procedure :: switch_inout => eio_ascii_switch_inout
<<EIO ascii: procedures>>=
subroutine eio_ascii_switch_inout (eio, success)
class(eio_ascii_t), intent(inout) :: eio
logical, intent(out), optional :: success
call msg_bug ("ASCII: in-out switch not supported")
if (present (success)) success = .false.
end subroutine eio_ascii_switch_inout
@ %def eio_ascii_switch_inout
@ Split event file: increment the counter, close the current file, open a new
one. If the file needs a header, repeat it for the new file. (We assume that
the common block contents are still intact.)
<<EIO ascii: eio ascii: TBP>>=
procedure :: split_out => eio_ascii_split_out
<<EIO ascii: procedures>>=
subroutine eio_ascii_split_out (eio)
class(eio_ascii_t), intent(inout) :: eio
if (eio%split) then
eio%split_index = eio%split_index + 1
call eio%set_filename ()
write (msg_buffer, "(A,A,A)") "Events: writing to ASCII file '", &
char (eio%filename), "'"
call msg_message ()
close (eio%unit)
open (eio%unit, file = char (eio%filename), &
action = "write", status = "replace")
select type (eio)
type is (eio_ascii_lha_t)
call heprup_write_ascii (eio%unit)
type is (eio_ascii_lha_verb_t)
call heprup_write_verbose (eio%unit)
end select
end if
end subroutine eio_ascii_split_out
@ %def eio_ascii_split_out
@ Output an event. Write first the event indices, then weight and
squared matrix element, then the particle set.
Events that did not pass the selection are skipped. The exceptions are
the [[ascii]] and [[debug]] formats. These are the formats that
contain the [[passed]] flag in their output, and should be most useful
for debugging purposes.
<<EIO ascii: eio ascii: TBP>>=
procedure :: output => eio_ascii_output
<<EIO ascii: procedures>>=
subroutine eio_ascii_output (eio, event, i_prc, reading, passed, pacify)
class(eio_ascii_t), intent(inout) :: eio
class(generic_event_t), intent(in), target :: event
integer, intent(in) :: i_prc
logical, intent(in), optional :: reading, passed, pacify
if (present (passed)) then
if (.not. passed) then
select type (eio)
type is (eio_ascii_debug_t)
type is (eio_ascii_ascii_t)
class default
return
end select
end if
end if
if (eio%writing) then
select type (eio)
type is (eio_ascii_lha_t)
call hepeup_from_event (event, &
process_index = i_prc, &
keep_beams = eio%keep_beams, &
keep_remnants = eio%keep_remnants)
call hepeup_write_lha (eio%unit)
type is (eio_ascii_lha_verb_t)
call hepeup_from_event (event, &
process_index = i_prc, &
keep_beams = eio%keep_beams, &
keep_remnants = eio%keep_remnants)
call hepeup_write_verbose (eio%unit)
type is (eio_ascii_ascii_t)
call event%write (eio%unit, &
show_process = .false., &
show_transforms = .false., &
show_decay = .false., &
verbose = .false., testflag = pacify)
type is (eio_ascii_athena_t)
call hepevt_from_event (event, &
keep_beams = eio%keep_beams, &
keep_remnants = eio%keep_remnants, &
ensure_order = eio%ensure_order)
call hepevt_write_athena (eio%unit)
type is (eio_ascii_debug_t)
call event%write (eio%unit, &
show_process = eio%show_process, &
show_transforms = eio%show_transforms, &
show_decay = eio%show_decay, &
verbose = eio%verbose, &
testflag = pacify)
type is (eio_ascii_hepevt_t)
call hepevt_from_event (event, &
keep_beams = eio%keep_beams, &
keep_remnants = eio%keep_remnants, &
ensure_order = eio%ensure_order)
call hepevt_write_hepevt (eio%unit)
type is (eio_ascii_hepevt_verb_t)
call hepevt_from_event (event, &
keep_beams = eio%keep_beams, &
keep_remnants = eio%keep_remnants, &
ensure_order = eio%ensure_order)
call hepevt_write_verbose (eio%unit)
type is (eio_ascii_long_t)
call hepevt_from_event (event, &
keep_beams = eio%keep_beams, &
keep_remnants = eio%keep_remnants, &
ensure_order = eio%ensure_order)
call hepevt_write_ascii (eio%unit, .true.)
type is (eio_ascii_mokka_t)
call hepevt_from_event (event, &
keep_beams = eio%keep_beams, &
keep_remnants = eio%keep_remnants, &
ensure_order = eio%ensure_order)
call hepevt_write_mokka (eio%unit)
type is (eio_ascii_short_t)
call hepevt_from_event (event, &
keep_beams = eio%keep_beams, &
keep_remnants = eio%keep_remnants, &
ensure_order = eio%ensure_order)
call hepevt_write_ascii (eio%unit, .false.)
end select
else
call eio%write ()
call msg_fatal ("ASCII file is not open for writing")
end if
end subroutine eio_ascii_output
@ %def eio_ascii_output
@ Input an event.
<<EIO ascii: eio ascii: TBP>>=
procedure :: input_i_prc => eio_ascii_input_i_prc
procedure :: input_event => eio_ascii_input_event
<<EIO ascii: procedures>>=
subroutine eio_ascii_input_i_prc (eio, i_prc, iostat)
class(eio_ascii_t), intent(inout) :: eio
integer, intent(out) :: i_prc
integer, intent(out) :: iostat
call msg_bug ("ASCII: event input not supported")
i_prc = 0
iostat = 1
end subroutine eio_ascii_input_i_prc
subroutine eio_ascii_input_event (eio, event, iostat)
class(eio_ascii_t), intent(inout) :: eio
class(generic_event_t), intent(inout), target :: event
integer, intent(out) :: iostat
call msg_bug ("ASCII: event input not supported")
iostat = 1
end subroutine eio_ascii_input_event
@ %def eio_ascii_input_i_prc
@ %def eio_ascii_input_event
@
<<EIO ascii: eio ascii: TBP>>=
procedure :: skip => eio_ascii_skip
<<EIO ascii: procedures>>=
subroutine eio_ascii_skip (eio, iostat)
class(eio_ascii_t), intent(inout) :: eio
integer, intent(out) :: iostat
iostat = 0
end subroutine eio_ascii_skip
@ %def eio_asciii_skip
@
\subsection{Unit tests}
Test module, followed by the corresponding implementation module.
<<[[eio_ascii_ut.f90]]>>=
<<File header>>
module eio_ascii_ut
use unit_tests
use eio_ascii_uti
<<Standard module head>>
<<EIO ascii: public test>>
contains
<<EIO ascii: test driver>>
end module eio_ascii_ut
@ %def eio_ascii_ut
@
<<[[eio_ascii_uti.f90]]>>=
<<File header>>
module eio_ascii_uti
<<Use kinds>>
<<Use strings>>
use io_units
use model_data
use event_base
use eio_data
use eio_base
use eio_ascii
use eio_base_ut, only: eio_prepare_test, eio_cleanup_test
<<Standard module head>>
<<EIO ascii: test declarations>>
contains
<<EIO ascii: tests>>
end module eio_ascii_uti
@ %def eio_ascii_uti
@ API: driver for the unit tests below.
<<EIO ascii: public test>>=
public :: eio_ascii_test
<<EIO ascii: test driver>>=
subroutine eio_ascii_test (u, results)
integer, intent(in) :: u
type(test_results_t), intent(inout) :: results
<<EIO ascii: execute tests>>
end subroutine eio_ascii_test
@ %def eio_ascii_test
@
\subsubsection{Test I/O methods}
We test the implementation of all I/O methods, method [[ascii]]:
<<EIO ascii: execute tests>>=
call test (eio_ascii_1, "eio_ascii_1", &
"read and write event contents, format [ascii]", &
u, results)
<<EIO ascii: test declarations>>=
public :: eio_ascii_1
<<EIO ascii: tests>>=
subroutine eio_ascii_1 (u)
integer, intent(in) :: u
class(generic_event_t), pointer :: event
type(event_sample_data_t) :: data
class(eio_t), allocatable :: eio
type(string_t) :: sample
integer :: u_file, iostat
character(80) :: buffer
write (u, "(A)") "* Test output: eio_ascii_1"
write (u, "(A)") "* Purpose: generate an event in ASCII ascii format"
write (u, "(A)") "* and write weight to file"
write (u, "(A)")
write (u, "(A)") "* Initialize test process"
call eio_prepare_test (event, unweighted = .false.)
call data%init (1)
data%n_evt = 1
data%n_beam = 2
data%pdg_beam = 25
data%energy_beam = 500
data%proc_num_id = [42]
data%cross_section(1) = 100
data%error(1) = 1
data%total_cross_section = sum (data%cross_section)
write (u, "(A)")
write (u, "(A)") "* Generate and write an event"
write (u, "(A)")
sample = "eio_ascii_1"
allocate (eio_ascii_ascii_t :: eio)
select type (eio)
class is (eio_ascii_t); call eio%set_parameters ()
end select
call eio%init_out (sample, data)
call event%generate (1, [0._default, 0._default])
call event%set_index (42)
call event%evaluate_expressions ()
call eio%output (event, i_prc = 1)
call eio%write (u)
call eio%final ()
write (u, "(A)")
write (u, "(A)") "* File contents:"
write (u, "(A)")
u_file = free_unit ()
open (u_file, file = char (sample // ".evt"), &
action = "read", status = "old")
do
read (u_file, "(A)", iostat = iostat) buffer
if (buffer(1:21) == " <generator_version>") buffer = "[...]"
if (iostat /= 0) exit
write (u, "(A)") trim (buffer)
end do
close (u_file)
write (u, "(A)")
write (u, "(A)") "* Reset data"
write (u, "(A)")
deallocate (eio)
allocate (eio_ascii_ascii_t :: eio)
select type (eio)
type is (eio_ascii_ascii_t)
call eio%set_parameters (keep_beams = .true.)
end select
call eio%write (u)
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio_cleanup_test (event)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_ascii_1"
end subroutine eio_ascii_1
@ %def eio_ascii_1
@
We test the implementation of all I/O methods, method [[athena]]:
<<EIO ascii: execute tests>>=
call test (eio_ascii_2, "eio_ascii_2", &
"read and write event contents, format [athena]", &
u, results)
<<EIO ascii: test declarations>>=
public :: eio_ascii_2
<<EIO ascii: tests>>=
subroutine eio_ascii_2 (u)
integer, intent(in) :: u
class(generic_event_t), pointer :: event
type(event_sample_data_t) :: data
class(eio_t), allocatable :: eio
type(string_t) :: sample
integer :: u_file, iostat
character(80) :: buffer
write (u, "(A)") "* Test output: eio_ascii_2"
write (u, "(A)") "* Purpose: generate an event in ASCII athena format"
write (u, "(A)") "* and write weight to file"
write (u, "(A)")
write (u, "(A)") "* Initialize test process"
call eio_prepare_test (event, unweighted = .false.)
call data%init (1)
data%n_evt = 1
data%n_beam = 2
data%pdg_beam = 25
data%energy_beam = 500
data%proc_num_id = [42]
data%cross_section(1) = 100
data%error(1) = 1
data%total_cross_section = sum (data%cross_section)
write (u, "(A)")
write (u, "(A)") "* Generate and write an event"
write (u, "(A)")
sample = "eio_ascii_2"
allocate (eio_ascii_athena_t :: eio)
select type (eio)
class is (eio_ascii_t); call eio%set_parameters ()
end select
call eio%init_out (sample, data)
call event%generate (1, [0._default, 0._default])
call event%set_index (42)
call event%evaluate_expressions ()
call eio%output (event, i_prc = 1)
call eio%write (u)
call eio%final ()
write (u, "(A)")
write (u, "(A)") "* File contents:"
write (u, "(A)")
u_file = free_unit ()
open (u_file, file = char(sample // ".athena.evt"), &
action = "read", status = "old")
do
read (u_file, "(A)", iostat = iostat) buffer
if (buffer(1:21) == " <generator_version>") buffer = "[...]"
if (iostat /= 0) exit
write (u, "(A)") trim (buffer)
end do
close (u_file)
write (u, "(A)")
write (u, "(A)") "* Reset data"
write (u, "(A)")
deallocate (eio)
allocate (eio_ascii_athena_t :: eio)
select type (eio)
type is (eio_ascii_athena_t)
call eio%set_parameters (keep_beams = .true.)
end select
call eio%write (u)
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio_cleanup_test (event)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_ascii_2"
end subroutine eio_ascii_2
@ %def eio_ascii_2
@
We test the implementation of all I/O methods, method [[debug]]:
<<EIO ascii: execute tests>>=
call test (eio_ascii_3, "eio_ascii_3", &
"read and write event contents, format [debug]", &
u, results)
<<EIO ascii: test declarations>>=
public :: eio_ascii_3
<<EIO ascii: tests>>=
subroutine eio_ascii_3 (u)
integer, intent(in) :: u
class(generic_event_t), pointer :: event
type(event_sample_data_t) :: data
class(eio_t), allocatable :: eio
type(string_t) :: sample
integer :: u_file, iostat
character(80) :: buffer
write (u, "(A)") "* Test output: eio_ascii_3"
write (u, "(A)") "* Purpose: generate an event in ASCII debug format"
write (u, "(A)") "* and write weight to file"
write (u, "(A)")
write (u, "(A)") "* Initialize test process"
call eio_prepare_test (event, unweighted = .false.)
call data%init (1)
data%n_evt = 1
data%n_beam = 2
data%pdg_beam = 25
data%energy_beam = 500
data%proc_num_id = [42]
data%cross_section(1) = 100
data%error(1) = 1
data%total_cross_section = sum (data%cross_section)
write (u, "(A)")
write (u, "(A)") "* Generate and write an event"
write (u, "(A)")
sample = "eio_ascii_3"
allocate (eio_ascii_debug_t :: eio)
select type (eio)
class is (eio_ascii_t); call eio%set_parameters ()
end select
call eio%init_out (sample, data)
call event%generate (1, [0._default, 0._default])
call event%increment_index ()
call event%evaluate_expressions ()
call eio%output (event, i_prc = 1)
call eio%write (u)
call eio%final ()
write (u, "(A)")
write (u, "(A)") "* File contents:"
write (u, "(A)")
u_file = free_unit ()
open (u_file, file = char (sample // ".debug"), &
action = "read", status = "old")
do
read (u_file, "(A)", iostat = iostat) buffer
if (buffer(1:21) == " <generator_version>") buffer = "[...]"
if (iostat /= 0) exit
write (u, "(A)") trim (buffer)
end do
close (u_file)
write (u, "(A)")
write (u, "(A)") "* Reset data"
write (u, "(A)")
deallocate (eio)
allocate (eio_ascii_debug_t :: eio)
select type (eio)
type is (eio_ascii_debug_t)
call eio%set_parameters (keep_beams = .true.)
end select
call eio%write (u)
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio_cleanup_test (event)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_ascii_3"
end subroutine eio_ascii_3
@ %def eio_ascii_3
@
We test the implementation of all I/O methods, method [[hepevt]]:
<<EIO ascii: execute tests>>=
call test (eio_ascii_4, "eio_ascii_4", &
"read and write event contents, format [hepevt]", &
u, results)
<<EIO ascii: test declarations>>=
public :: eio_ascii_4
<<EIO ascii: tests>>=
subroutine eio_ascii_4 (u)
integer, intent(in) :: u
class(generic_event_t), pointer :: event
type(event_sample_data_t) :: data
class(eio_t), allocatable :: eio
type(string_t) :: sample
integer :: u_file, iostat
character(80) :: buffer
write (u, "(A)") "* Test output: eio_ascii_4"
write (u, "(A)") "* Purpose: generate an event in ASCII hepevt format"
write (u, "(A)") "* and write weight to file"
write (u, "(A)")
write (u, "(A)") "* Initialize test process"
call eio_prepare_test (event, unweighted = .false.)
call data%init (1)
data%n_evt = 1
data%n_beam = 2
data%pdg_beam = 25
data%energy_beam = 500
data%proc_num_id = [42]
data%cross_section(1) = 100
data%error(1) = 1
data%total_cross_section = sum (data%cross_section)
write (u, "(A)")
write (u, "(A)") "* Generate and write an event"
write (u, "(A)")
sample = "eio_ascii_4"
allocate (eio_ascii_hepevt_t :: eio)
select type (eio)
class is (eio_ascii_t); call eio%set_parameters ()
end select
call eio%init_out (sample, data)
call event%generate (1, [0._default, 0._default])
call event%increment_index ()
call event%evaluate_expressions ()
call eio%output (event, i_prc = 1)
call eio%write (u)
call eio%final ()
write (u, "(A)")
write (u, "(A)") "* File contents:"
write (u, "(A)")
u_file = free_unit ()
open (u_file, file = char (sample // ".hepevt"), &
action = "read", status = "old")
do
read (u_file, "(A)", iostat = iostat) buffer
if (buffer(1:21) == " <generator_version>") buffer = "[...]"
if (iostat /= 0) exit
write (u, "(A)") trim (buffer)
end do
close (u_file)
write (u, "(A)")
write (u, "(A)") "* Reset data"
write (u, "(A)")
deallocate (eio)
allocate (eio_ascii_hepevt_t :: eio)
select type (eio)
type is (eio_ascii_hepevt_t)
call eio%set_parameters (keep_beams = .true.)
end select
call eio%write (u)
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio_cleanup_test (event)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_ascii_4"
end subroutine eio_ascii_4
@ %def eio_ascii_4
@
We test the implementation of all I/O methods, method [[lha]] (old LHA):
<<EIO ascii: execute tests>>=
call test (eio_ascii_5, "eio_ascii_5", &
"read and write event contents, format [lha]", &
u, results)
<<EIO ascii: test declarations>>=
public :: eio_ascii_5
<<EIO ascii: tests>>=
subroutine eio_ascii_5 (u)
integer, intent(in) :: u
class(generic_event_t), pointer :: event
type(event_sample_data_t) :: data
class(eio_t), allocatable :: eio
type(string_t) :: sample
integer :: u_file, iostat
character(80) :: buffer
write (u, "(A)") "* Test output: eio_ascii_5"
write (u, "(A)") "* Purpose: generate an event in ASCII LHA format"
write (u, "(A)") "* and write weight to file"
write (u, "(A)")
write (u, "(A)") "* Initialize test process"
call eio_prepare_test (event, unweighted = .false.)
call data%init (1)
data%n_evt = 1
data%n_beam = 2
data%pdg_beam = 25
data%energy_beam = 500
data%proc_num_id = [42]
data%cross_section(1) = 100
data%error(1) = 1
data%total_cross_section = sum (data%cross_section)
write (u, "(A)")
write (u, "(A)") "* Generate and write an event"
write (u, "(A)")
sample = "eio_ascii_5"
allocate (eio_ascii_lha_t :: eio)
select type (eio)
class is (eio_ascii_t); call eio%set_parameters ()
end select
call eio%init_out (sample, data)
call event%generate (1, [0._default, 0._default])
call event%increment_index ()
call event%evaluate_expressions ()
call eio%output (event, i_prc = 1)
call eio%write (u)
call eio%final ()
write (u, "(A)")
write (u, "(A)") "* File contents:"
write (u, "(A)")
u_file = free_unit ()
open (u_file, file = char (sample // ".lha"), &
action = "read", status = "old")
do
read (u_file, "(A)", iostat = iostat) buffer
if (buffer(1:21) == " <generator_version>") buffer = "[...]"
if (iostat /= 0) exit
write (u, "(A)") trim (buffer)
end do
close (u_file)
write (u, "(A)")
write (u, "(A)") "* Reset data"
write (u, "(A)")
deallocate (eio)
allocate (eio_ascii_lha_t :: eio)
select type (eio)
type is (eio_ascii_lha_t)
call eio%set_parameters (keep_beams = .true.)
end select
call eio%write (u)
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio_cleanup_test (event)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_ascii_5"
end subroutine eio_ascii_5
@ %def eio_ascii_5
@
We test the implementation of all I/O methods, method [[long]]:
<<EIO ascii: execute tests>>=
call test (eio_ascii_6, "eio_ascii_6", &
"read and write event contents, format [long]", &
u, results)
<<EIO ascii: test declarations>>=
public :: eio_ascii_6
<<EIO ascii: tests>>=
subroutine eio_ascii_6 (u)
integer, intent(in) :: u
class(generic_event_t), pointer :: event
type(event_sample_data_t) :: data
class(eio_t), allocatable :: eio
type(string_t) :: sample
integer :: u_file, iostat
character(80) :: buffer
write (u, "(A)") "* Test output: eio_ascii_6"
write (u, "(A)") "* Purpose: generate an event in ASCII long format"
write (u, "(A)") "* and write weight to file"
write (u, "(A)")
write (u, "(A)") "* Initialize test process"
call eio_prepare_test (event, unweighted = .false.)
call data%init (1)
data%n_evt = 1
data%n_beam = 2
data%pdg_beam = 25
data%energy_beam = 500
data%proc_num_id = [42]
data%cross_section(1) = 100
data%error(1) = 1
data%total_cross_section = sum (data%cross_section)
write (u, "(A)")
write (u, "(A)") "* Generate and write an event"
write (u, "(A)")
sample = "eio_ascii_6"
allocate (eio_ascii_long_t :: eio)
select type (eio)
class is (eio_ascii_t); call eio%set_parameters ()
end select
call eio%init_out (sample, data)
call event%generate (1, [0._default, 0._default])
call event%increment_index ()
call event%evaluate_expressions ()
call eio%output (event, i_prc = 1)
call eio%write (u)
call eio%final ()
write (u, "(A)")
write (u, "(A)") "* File contents:"
write (u, "(A)")
u_file = free_unit ()
open (u_file, file = char (sample // ".long.evt"), &
action = "read", status = "old")
do
read (u_file, "(A)", iostat = iostat) buffer
if (buffer(1:21) == " <generator_version>") buffer = "[...]"
if (iostat /= 0) exit
write (u, "(A)") trim (buffer)
end do
close (u_file)
write (u, "(A)")
write (u, "(A)") "* Reset data"
write (u, "(A)")
deallocate (eio)
allocate (eio_ascii_long_t :: eio)
select type (eio)
type is (eio_ascii_long_t)
call eio%set_parameters (keep_beams = .true.)
end select
call eio%write (u)
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio_cleanup_test (event)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_ascii_6"
end subroutine eio_ascii_6
@ %def eio_ascii_6
@
We test the implementation of all I/O methods, method [[mokka]]:
<<EIO ascii: execute tests>>=
call test (eio_ascii_7, "eio_ascii_7", &
"read and write event contents, format [mokka]", &
u, results)
<<EIO ascii: test declarations>>=
public :: eio_ascii_7
<<EIO ascii: tests>>=
subroutine eio_ascii_7 (u)
integer, intent(in) :: u
class(generic_event_t), pointer :: event
type(event_sample_data_t) :: data
class(eio_t), allocatable :: eio
type(string_t) :: sample
integer :: u_file, iostat
character(80) :: buffer
write (u, "(A)") "* Test output: eio_ascii_7"
write (u, "(A)") "* Purpose: generate an event in ASCII mokka format"
write (u, "(A)") "* and write weight to file"
write (u, "(A)")
write (u, "(A)") "* Initialize test process"
call eio_prepare_test (event, unweighted = .false.)
call data%init (1)
data%n_evt = 1
data%n_beam = 2
data%pdg_beam = 25
data%energy_beam = 500
data%proc_num_id = [42]
data%cross_section(1) = 100
data%error(1) = 1
data%total_cross_section = sum (data%cross_section)
write (u, "(A)")
write (u, "(A)") "* Generate and write an event"
write (u, "(A)")
sample = "eio_ascii_7"
allocate (eio_ascii_mokka_t :: eio)
select type (eio)
class is (eio_ascii_t); call eio%set_parameters ()
end select
call eio%init_out (sample, data)
call event%generate (1, [0._default, 0._default])
call event%increment_index ()
call event%evaluate_expressions ()
call eio%output (event, i_prc = 1)
call eio%write (u)
call eio%final ()
write (u, "(A)")
write (u, "(A)") "* File contents:"
write (u, "(A)")
u_file = free_unit ()
open (u_file, file = char (sample // ".mokka.evt"), &
action = "read", status = "old")
do
read (u_file, "(A)", iostat = iostat) buffer
if (buffer(1:21) == " <generator_version>") buffer = "[...]"
if (iostat /= 0) exit
write (u, "(A)") trim (buffer)
end do
close (u_file)
write (u, "(A)")
write (u, "(A)") "* Reset data"
write (u, "(A)")
deallocate (eio)
allocate (eio_ascii_mokka_t :: eio)
select type (eio)
type is (eio_ascii_mokka_t)
call eio%set_parameters (keep_beams = .true.)
end select
call eio%write (u)
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio_cleanup_test (event)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_ascii_7"
end subroutine eio_ascii_7
@ %def eio_ascii_7
@
We test the implementation of all I/O methods, method [[short]]:
<<EIO ascii: execute tests>>=
call test (eio_ascii_8, "eio_ascii_8", &
"read and write event contents, format [short]", &
u, results)
<<EIO ascii: test declarations>>=
public :: eio_ascii_8
<<EIO ascii: tests>>=
subroutine eio_ascii_8 (u)
integer, intent(in) :: u
class(generic_event_t), pointer :: event
type(event_sample_data_t) :: data
class(eio_t), allocatable :: eio
type(string_t) :: sample
integer :: u_file, iostat
character(80) :: buffer
write (u, "(A)") "* Test output: eio_ascii_8"
write (u, "(A)") "* Purpose: generate an event in ASCII short format"
write (u, "(A)") "* and write weight to file"
write (u, "(A)")
write (u, "(A)") "* Initialize test process"
call eio_prepare_test (event, unweighted = .false.)
call data%init (1)
data%n_evt = 1
data%n_beam = 2
data%pdg_beam = 25
data%energy_beam = 500
data%proc_num_id = [42]
data%cross_section(1) = 100
data%error(1) = 1
data%total_cross_section = sum (data%cross_section)
write (u, "(A)")
write (u, "(A)") "* Generate and write an event"
write (u, "(A)")
sample = "eio_ascii_8"
allocate (eio_ascii_short_t :: eio)
select type (eio)
class is (eio_ascii_t); call eio%set_parameters ()
end select
call eio%init_out (sample, data)
call event%generate (1, [0._default, 0._default])
call event%increment_index ()
call event%evaluate_expressions ()
call eio%output (event, i_prc = 1)
call eio%write (u)
call eio%final ()
write (u, "(A)")
write (u, "(A)") "* File contents:"
write (u, "(A)")
u_file = free_unit ()
open (u_file, file = char (sample // ".short.evt"), &
action = "read", status = "old")
do
read (u_file, "(A)", iostat = iostat) buffer
if (buffer(1:21) == " <generator_version>") buffer = "[...]"
if (iostat /= 0) exit
write (u, "(A)") trim (buffer)
end do
close (u_file)
write (u, "(A)")
write (u, "(A)") "* Reset data"
write (u, "(A)")
deallocate (eio)
allocate (eio_ascii_short_t :: eio)
select type (eio)
type is (eio_ascii_short_t)
call eio%set_parameters (keep_beams = .true.)
end select
call eio%write (u)
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio_cleanup_test (event)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_ascii_8"
end subroutine eio_ascii_8
@ %def eio_ascii_8
@
We test the implementation of all I/O methods, method [[lha]] (old
LHA) in verbose version:
<<EIO ascii: execute tests>>=
call test (eio_ascii_9, "eio_ascii_9", &
"read and write event contents, format [lha_verb]", &
u, results)
<<EIO ascii: test declarations>>=
public :: eio_ascii_9
<<EIO ascii: tests>>=
subroutine eio_ascii_9 (u)
integer, intent(in) :: u
class(generic_event_t), pointer :: event
type(event_sample_data_t) :: data
class(eio_t), allocatable :: eio
type(string_t) :: sample
integer :: u_file, iostat
character(80) :: buffer
write (u, "(A)") "* Test output: eio_ascii_9"
write (u, "(A)") "* Purpose: generate an event in ASCII LHA verbose format"
write (u, "(A)") "* and write weight to file"
write (u, "(A)")
write (u, "(A)") "* Initialize test process"
call eio_prepare_test (event, unweighted = .false.)
call data%init (1)
data%n_evt = 1
data%n_beam = 2
data%pdg_beam = 25
data%energy_beam = 500
data%proc_num_id = [42]
data%cross_section(1) = 100
data%error(1) = 1
data%total_cross_section = sum (data%cross_section)
write (u, "(A)")
write (u, "(A)") "* Generate and write an event"
write (u, "(A)")
sample = "eio_ascii_9"
allocate (eio_ascii_lha_verb_t :: eio)
select type (eio)
class is (eio_ascii_t); call eio%set_parameters ()
end select
call eio%init_out (sample, data)
call event%generate (1, [0._default, 0._default])
call event%increment_index ()
call event%evaluate_expressions ()
call eio%output (event, i_prc = 1)
call eio%write (u)
call eio%final ()
write (u, "(A)")
write (u, "(A)") "* File contents:"
write (u, "(A)")
u_file = free_unit ()
open (u_file, file = char (sample // ".lha.verb"), &
action = "read", status = "old")
do
read (u_file, "(A)", iostat = iostat) buffer
if (buffer(1:21) == " <generator_version>") buffer = "[...]"
if (iostat /= 0) exit
write (u, "(A)") trim (buffer)
end do
close (u_file)
write (u, "(A)")
write (u, "(A)") "* Reset data"
write (u, "(A)")
deallocate (eio)
allocate (eio_ascii_lha_verb_t :: eio)
select type (eio)
type is (eio_ascii_lha_verb_t)
call eio%set_parameters (keep_beams = .true.)
end select
call eio%write (u)
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio_cleanup_test (event)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_ascii_9"
end subroutine eio_ascii_9
@ %def eio_ascii_9
@
We test the implementation of all I/O methods, method [[hepevt_verb]]:
<<EIO ascii: execute tests>>=
call test (eio_ascii_10, "eio_ascii_10", &
"read and write event contents, format [hepevt_verb]", &
u, results)
<<EIO ascii: test declarations>>=
public :: eio_ascii_10
<<EIO ascii: tests>>=
subroutine eio_ascii_10 (u)
integer, intent(in) :: u
class(generic_event_t), pointer :: event
type(event_sample_data_t) :: data
class(eio_t), allocatable :: eio
type(string_t) :: sample
integer :: u_file, iostat
character(80) :: buffer
write (u, "(A)") "* Test output: eio_ascii_10"
write (u, "(A)") "* Purpose: generate an event in ASCII hepevt verbose format"
write (u, "(A)") "* and write weight to file"
write (u, "(A)")
write (u, "(A)") "* Initialize test process"
call eio_prepare_test (event, unweighted = .false.)
call data%init (1)
data%n_evt = 1
data%n_beam = 2
data%pdg_beam = 25
data%energy_beam = 500
data%proc_num_id = [42]
data%cross_section(1) = 100
data%error(1) = 1
data%total_cross_section = sum (data%cross_section)
write (u, "(A)")
write (u, "(A)") "* Generate and write an event"
write (u, "(A)")
sample = "eio_ascii_10"
allocate (eio_ascii_hepevt_verb_t :: eio)
select type (eio)
class is (eio_ascii_t); call eio%set_parameters ()
end select
call eio%init_out (sample, data)
call event%generate (1, [0._default, 0._default])
call event%increment_index ()
call event%evaluate_expressions ()
call eio%output (event, i_prc = 1)
call eio%write (u)
call eio%final ()
write (u, "(A)")
write (u, "(A)") "* File contents:"
write (u, "(A)")
u_file = free_unit ()
open (u_file, file = char (sample // ".hepevt.verb"), &
action = "read", status = "old")
do
read (u_file, "(A)", iostat = iostat) buffer
if (buffer(1:21) == " <generator_version>") buffer = "[...]"
if (iostat /= 0) exit
write (u, "(A)") trim (buffer)
end do
close (u_file)
write (u, "(A)")
write (u, "(A)") "* Reset data"
write (u, "(A)")
deallocate (eio)
allocate (eio_ascii_hepevt_verb_t :: eio)
select type (eio)
type is (eio_ascii_hepevt_verb_t)
call eio%set_parameters (keep_beams = .true.)
end select
call eio%write (u)
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio_cleanup_test (event)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_ascii_10"
end subroutine eio_ascii_10
@ %def eio_ascii_10
@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
\section{HEP Common Blocks}
Long ago, to transfer data between programs one had to set up a common
block and link both programs as libraries to the main executable. The
HEP community standardizes several of those common blocks.
The modern way of data exchange uses data files with standard
formats. However, the LHEF standard data format derives from a common
block (actually, two).
\whizard\ used to support those common blocks, and LHEF was
implemented via writing/reading blocks. We still keep this
convention, but intend to eliminate common blocks (or any other static
storage) from the workflow in the future. This will gain flexibility
towards concurrent running of program images.
We encapsulate everything here in a module. The module holds the
variables which are part of the common block. To access the common
block variables, we just have to [[use]] this module. (They are
nevertheless in the common block, since external software may access
it in this way.)
Note: This code is taken essentially unchanged from \whizard\ 2.1 and
does not (yet) provide unit tests.
<<[[hep_common.f90]]>>=
<<File header>>
module hep_common
<<Use kinds>>
use kinds, only: double
use constants
<<Use strings>>
use io_units
use diagnostics
use numeric_utils
use physics_defs, only: HADRON_REMNANT
use physics_defs, only: HADRON_REMNANT_SINGLET
use physics_defs, only: HADRON_REMNANT_TRIPLET
use physics_defs, only: HADRON_REMNANT_OCTET
use xml
use lorentz
use flavors
use colors
use polarizations
use model_data
use particles
use subevents, only: PRT_BEAM, PRT_INCOMING, PRT_OUTGOING
use subevents, only: PRT_UNDEFINED
use subevents, only: PRT_VIRTUAL, PRT_RESONANT, PRT_BEAM_REMNANT
<<Standard module head>>
<<HEP common: public>>
<<HEP common: interfaces>>
<<HEP common: parameters>>
<<HEP common: variables>>
<<HEP common: common blocks>>
contains
<<HEP common: procedures>>
end module hep_common
@ %def hep_common
@
\subsection{Event characteristics}
The maximal number of particles in an event record.
<<HEP common: parameters>>=
integer, parameter, public :: MAXNUP = 500
@ %def MAXNUP
@ The number of particles in this event.
<<HEP common: variables>>=
integer, public :: NUP
@ %def NUP
@ The process ID for this event.
<<HEP common: variables>>=
integer, public :: IDPRUP
@ %def IDPRUP
@ The weight of this event ($\pm 1$ for unweighted events).
<<HEP common: variables>>=
double precision, public :: XWGTUP
@ %def XWGTUP
@ The factorization scale that is used for PDF calculation ($-1$ if
undefined).
<<HEP common: variables>>=
double precision, public :: SCALUP
@ %def SCALUP
@ The QED and QCD couplings $\alpha$ used for this event ($-1$ if
undefined).
<<HEP common: variables>>=
double precision, public :: AQEDUP
double precision, public :: AQCDUP
@ %def AQEDUP AQCDUP
@
\subsection{Particle characteristics}
The PDG code:
<<HEP common: variables>>=
integer, dimension(MAXNUP), public :: IDUP
@ %def IDUP
@ The status code. Incoming: $-1$, outgoing: $+1$. Intermediate
t-channel propagator: $-2$ (currently not used by WHIZARD).
Intermediate resonance whose mass should be preserved: $2$.
Intermediate resonance for documentation: $3$ (currently not used).
Beam particles: $-9$.
<<HEP common: variables>>=
integer, dimension(MAXNUP), public :: ISTUP
@ %def ISTUP
@ Index of first and last mother.
<<HEP common: variables>>=
integer, dimension(2,MAXNUP), public :: MOTHUP
@ %def MOTHUP
@ Color line index of the color and anticolor entry for the particle.
The standard recommends using large numbers; we start from MAXNUP+1.
<<HEP common: variables>>=
integer, dimension(2,MAXNUP), public :: ICOLUP
@ %def ICOLUP
@ Momentum, energy, and invariant mass: $(p_x,p_y,p_z,E,M)$. For
space-like particles, $M$ is the negative square root of the absolute
value of the invariant mass.
<<HEP common: variables>>=
double precision, dimension(5,MAXNUP), public :: PUP
@ %def PUP
@ Invariant lifetime (distance) from production to decay in mm.
<<HEP common: variables>>=
double precision, dimension(MAXNUP), public :: VTIMUP
@ %def VTIMUP
@ Cosine of the angle between the spin-vector and a particle and the
3-momentum of its mother, given in the lab frame. If
undefined/unpolarized: $9$.
<<HEP common: variables>>=
double precision, dimension(MAXNUP), public :: SPINUP
@ %def SPINUP
@
\subsection{The HEPRUP common block}
This common block is filled once per run.
\subsubsection{Run characteristics}
The maximal number of different processes.
<<HEP common: parameters>>=
integer, parameter, public :: MAXPUP = 100
@ %def MAXPUP
@ The beam PDG codes.
<<HEP common: variables>>=
integer, dimension(2), public :: IDBMUP
@ %def IDBMUP
@ The beam energies in GeV.
<<HEP common: variables>>=
double precision, dimension(2), public :: EBMUP
@ %def EBMUP
@ The PDF group and set for the two beams. (Undefined: use $-1$;
LHAPDF: use group = $0$).
<<HEP common: variables>>=
integer, dimension(2), public :: PDFGUP
integer, dimension(2), public :: PDFSUP
@ %def PDFGUP PDFSUP
@ The (re)weighting model. 1: events are weighted, the shower
generator (SHG) selects processes according to the maximum weight (in
pb) and unweights events. 2: events are weighted, the SHG selects
processes according to their cross section (in pb) and unweights
events. 3: events are unweighted and simply run through the SHG. 4:
events are weighted, and the SHG keeps the weight. Negative numbers:
negative weights are allowed (and are reweighted to $\pm 1$ by the
SHG, if allowed).
\whizard\ only supports modes 3 and 4, as the SHG is not given control
over process selection. This is consistent with writing events to
file, for offline showering.
<<HEP common: variables>>=
integer, public :: IDWTUP
@ %def IDWTUP
@ The number of different processes.
<<HEP common: variables>>=
integer, public :: NPRUP
@ %def NPRUP
@
\subsubsection{Process characteristics}
Cross section and error in pb. (Cross section is needed only for
$[[IDWTUP]] = 2$, so here both values are given for informational
purposes only.)
<<HEP common: variables>>=
double precision, dimension(MAXPUP), public :: XSECUP
double precision, dimension(MAXPUP), public :: XERRUP
@ %def XSECUP XERRUP
@ Maximum weight, i.e., the maximum value that [[XWGTUP]] can take.
Also unused for the supported weighting models. It is $\pm 1$ for
unweighted events.
<<HEP common: variables>>=
double precision, dimension(MAXPUP), public :: XMAXUP
@ %def XMAXUP
@ Internal ID of the selected process, matches [[IDPRUP]] below.
<<HEP common: variables>>=
integer, dimension(MAXPUP), public :: LPRUP
@ %def LPRUP
@
\subsubsection{The common block}
<<HEP common: common blocks>>=
common /HEPRUP/ &
IDBMUP, EBMUP, PDFGUP, PDFSUP, IDWTUP, NPRUP, &
XSECUP, XERRUP, XMAXUP, LPRUP
save /HEPRUP/
@ %def HEPRUP
@ Fill the run characteristics of the common block. The
initialization sets the beam properties, number of processes, and
weighting model.
<<HEP common: public>>=
public :: heprup_init
<<HEP common: procedures>>=
subroutine heprup_init &
(beam_pdg, beam_energy, n_processes, unweighted, negative_weights)
integer, dimension(2), intent(in) :: beam_pdg
real(default), dimension(2), intent(in) :: beam_energy
integer, intent(in) :: n_processes
logical, intent(in) :: unweighted
logical, intent(in) :: negative_weights
IDBMUP = beam_pdg
EBMUP = beam_energy
PDFGUP = -1
PDFSUP = -1
if (unweighted) then
IDWTUP = 3
else
IDWTUP = 4
end if
if (negative_weights) IDWTUP = - IDWTUP
NPRUP = n_processes
end subroutine heprup_init
@ %def heprup_init
The HEPRUP (event) common block is needed for the interface to the shower.
Filling of it is triggered by some output file formats. If these are not
present, the common block is filled with some dummy information. Be generous
with the number of processes in HEPRUP so that PYTHIA only rarely needs to be
reinitialized in case events with higher process ids are generated.
<<HEP common: public>>=
public :: assure_heprup
<<HEP common: procedures>>=
subroutine assure_heprup (pset)
type(particle_set_t), intent(in) :: pset
integer :: i, num_id
integer, parameter :: min_processes = 10
num_id = 1
if (LPRUP (num_id) /= 0) return
call heprup_init ( &
[pset%prt(1)%get_pdg (), pset%prt(2)%get_pdg ()] , &
[pset%prt(1)%p%p(0), pset%prt(2)%p%p(0)], &
num_id, .false., .false.)
do i = 1, (num_id / min_processes + 1) * min_processes
call heprup_set_process_parameters (i = i, process_id = &
i, cross_section = 1._default, error = 1._default)
end do
end subroutine assure_heprup
@ %def assure_heprup
@ Read in the LHE file opened in unit [[u]] and add the final
particles to the [[particle_set]], the outgoing particles of the existing
[[particle_set]] are compared to the particles that are read in. When
they are equal in flavor and momenta, they are erased and their
mother-daughter relations are transferred to the existing particles.
<<HEP common: public>>=
public :: combine_lhef_with_particle_set
<<HEP common: procedures>>=
subroutine combine_lhef_with_particle_set &
(particle_set, u, model_in, model_hadrons)
type(particle_set_t), intent(inout) :: particle_set
integer, intent(in) :: u
class(model_data_t), intent(in), target :: model_in
class(model_data_t), intent(in), target :: model_hadrons
type(flavor_t) :: flv
type(color_t) :: col
class(model_data_t), pointer :: model
type(particle_t), dimension(:), allocatable :: prt_tmp, prt
integer :: i, j
type(vector4_t) :: mom, d_mom
integer, PARAMETER :: MAXLEN=200
character(len=maxlen) :: string
integer :: ibeg, n_tot, n_entries
integer, dimension(:), allocatable :: relations, mothers, tbd
INTEGER :: NUP,IDPRUP,IDUP,ISTUP
real(kind=double) :: XWGTUP,SCALUP,AQEDUP,AQCDUP,VTIMUP,SPINUP
integer :: MOTHUP(1:2), ICOLUP(1:2)
real(kind=double) :: PUP(1:5)
real(kind=default) :: pup_dum(1:5)
character(len=5) :: buffer
character(len=6) :: strfmt
logical :: not_found
logical :: debug_lhef = .false.
STRFMT='(A000)'
WRITE (STRFMT(3:5),'(I3)') MAXLEN
if (debug_lhef) call particle_set%write ()
rewind (u)
do
read (u,*, END=501, ERR=502) STRING
IBEG = 0
do
if (signal_is_pending ()) return
IBEG = IBEG + 1
! Allow indentation.
IF (STRING (IBEG:IBEG) .EQ. ' ' .and. IBEG < MAXLEN-6) cycle
exit
end do
IF (string(IBEG:IBEG+6) /= '<event>' .and. &
string(IBEG:IBEG+6) /= '<event ') cycle
exit
end do
!!! Read first line of event info -> number of entries
read (u, *, END=503, ERR=504) NUP, IDPRUP, XWGTUP, SCALUP, AQEDUP, AQCDUP
n_tot = particle_set%get_n_tot ()
allocate (prt_tmp (1:n_tot+NUP))
allocate (relations (1:NUP), mothers (1:NUP), tbd(1:NUP))
do i = 1, n_tot
if (signal_is_pending ()) return
prt_tmp (i) = particle_set%get_particle (i)
end do
!!! transfer particles from lhef to particle_set
!!!...Read NUP subsequent lines with information on each particle.
n_entries = 1
mothers = 0
relations = 0
PARTICLE_LOOP: do I = 1, NUP
read (u,*, END=200, ERR=505) IDUP, ISTUP, MOTHUP(1), MOTHUP(2), &
ICOLUP(1), ICOLUP(2), (PUP (J),J=1,5), VTIMUP, SPINUP
if (model_in%test_field (IDUP)) then
model => model_in
else if (model_hadrons%test_field (IDUP)) then
model => model_hadrons
else
write (buffer, "(I5)") IDUP
call msg_error ("Parton " // buffer // &
" found neither in given model file nor in SM_hadrons")
return
end if
if (debug_lhef) then
print *, "IDUP, ISTUP, MOTHUP, PUP = ", IDUP, ISTUP, MOTHUP(1), &
MOTHUP(2), PUP
end if
call flv%init (IDUP, model)
if (IABS(IDUP) == 2212 .or. IABS(IDUP) == 2112) then
! PYTHIA sometimes sets color indices for protons and neutrons (?)
ICOLUP (1) = 0
ICOLUP (2) = 0
end if
call col%init_col_acl (ICOLUP (1), ICOLUP (2))
!!! Settings for unpolarized particles
! particle_set%prt (oldsize+i)%hel = ??
! particle_set%prt (oldsize+i)%pol = ??
if (MOTHUP(1) /= 0) then
mothers(i) = MOTHUP(1)
end if
pup_dum = PUP
if (pup_dum(4) < 1E-10_default) cycle
mom = vector4_moving (pup_dum (4), &
vector3_moving ([pup_dum (1), pup_dum (2), pup_dum (3)]))
not_found = .true.
SCAN_PARTICLES: do j = 1, n_tot
d_mom = prt_tmp(j)%get_momentum ()
if (all (nearly_equal &
(mom%p, d_mom%p, abs_smallness = 1.E-4_default)) .and. &
(prt_tmp(j)%get_pdg () == IDUP)) then
if (.not. prt_tmp(j)%get_status () == PRT_BEAM .or. &
.not. prt_tmp(j)%get_status () == PRT_BEAM_REMNANT) &
relations(i) = j
not_found = .false.
end if
end do SCAN_PARTICLES
if (not_found) then
if (debug_lhef) &
print *, "Not found: adding particle"
call prt_tmp(n_tot+n_entries)%set_flavor (flv)
call prt_tmp(n_tot+n_entries)%set_color (col)
call prt_tmp(n_tot+n_entries)%set_momentum (mom)
if (MOTHUP(1) /= 0) then
if (relations(MOTHUP(1)) /= 0) then
call prt_tmp(n_tot+n_entries)%set_parents &
([relations(MOTHUP(1))])
call prt_tmp(relations(MOTHUP(1)))%add_child (n_tot+n_entries)
if (prt_tmp(relations(MOTHUP(1)))%get_status () &
== PRT_OUTGOING) &
call prt_tmp(relations(MOTHUP(1)))%reset_status &
(PRT_VIRTUAL)
end if
end if
call prt_tmp(n_tot+n_entries)%set_status (PRT_OUTGOING)
if (debug_lhef) call prt_tmp(n_tot+n_entries)%write ()
n_entries = n_entries + 1
end if
end do PARTICLE_LOOP
do i = 1, n_tot
if (prt_tmp(i)%get_status () == PRT_OUTGOING .and. &
prt_tmp(i)%get_n_children () /= 0) then
call prt_tmp(i)%reset_status (PRT_VIRTUAL)
end if
end do
allocate (prt (1:n_tot+n_entries-1))
prt = prt_tmp (1:n_tot+n_entries-1)
! transfer to particle_set
call particle_set%replace (prt)
deallocate (prt, prt_tmp)
if (debug_lhef) then
call particle_set%write ()
print *, "combine_lhef_with_particle_set"
! stop
end if
200 continue
return
501 write(*,*) "READING LHEF failed 501"
return
502 write(*,*) "READING LHEF failed 502"
return
503 write(*,*) "READING LHEF failed 503"
return
504 write(*,*) "READING LHEF failed 504"
return
505 write(*,*) "READING LHEF failed 505"
return
end subroutine combine_lhef_with_particle_set
@ %def combine_lhef_with_particle_set
@
<<HEP common: public>>=
public :: w2p_write_lhef_event
<<HEP common: procedures>>=
subroutine w2p_write_lhef_event (unit)
integer, intent(in) :: unit
type(xml_tag_t), allocatable :: tag_lhef, tag_head, tag_init, &
tag_event, tag_gen_n, tag_gen_v
call msg_debug (D_EVENTS, "w2p_write_lhef_event")
allocate (tag_lhef, tag_head, tag_init, tag_event, &
tag_gen_n, tag_gen_v)
call tag_lhef%init (var_str ("LesHouchesEvents"), &
[xml_attribute (var_str ("version"), var_str ("1.0"))], .true.)
call tag_head%init (var_str ("header"), .true.)
call tag_init%init (var_str ("init"), .true.)
call tag_event%init (var_str ("event"), .true.)
call tag_gen_n%init (var_str ("generator_name"), .true.)
call tag_gen_v%init (var_str ("generator_version"), .true.)
call tag_lhef%write (unit); write (unit, *)
call tag_head%write (unit); write (unit, *)
write (unit, "(2x)", advance = "no")
call tag_gen_n%write (var_str ("WHIZARD"), unit)
write (unit, *)
write (unit, "(2x)", advance = "no")
call tag_gen_v%write (var_str ("<<Version>>"), unit)
write (unit, *)
call tag_head%close (unit); write (unit, *)
call tag_init%write (unit); write (unit, *)
call heprup_write_lhef (unit)
call tag_init%close (unit); write (unit, *)
call tag_event%write (unit); write (unit, *)
call hepeup_write_lhef (unit)
call tag_event%close (unit); write (unit, *)
call tag_lhef%close (unit); write (unit, *)
deallocate (tag_lhef, tag_head, tag_init, tag_event, &
tag_gen_n, tag_gen_v)
end subroutine w2p_write_lhef_event
@ %def w2p_write_lhef_event
@ Extract parameters from the common block. We leave it to the caller
to specify which parameters it actually needs.
[[PDFGUP]] and [[PDFSUP]] are not extracted. [[IDWTUP=1,2]] are not
supported by \whizard, but correspond to weighted events.
<<HEP common: public>>=
public :: heprup_get_run_parameters
<<HEP common: procedures>>=
subroutine heprup_get_run_parameters &
(beam_pdg, beam_energy, n_processes, unweighted, negative_weights)
integer, dimension(2), intent(out), optional :: beam_pdg
real(default), dimension(2), intent(out), optional :: beam_energy
integer, intent(out), optional :: n_processes
logical, intent(out), optional :: unweighted
logical, intent(out), optional :: negative_weights
if (present (beam_pdg)) beam_pdg = IDBMUP
if (present (beam_energy)) beam_energy = EBMUP
if (present (n_processes)) n_processes = NPRUP
if (present (unweighted)) then
select case (abs (IDWTUP))
case (3)
unweighted = .true.
case (4)
unweighted = .false.
case (1,2) !!! not supported by WHIZARD
unweighted = .false.
case default
call msg_fatal ("HEPRUP: unsupported IDWTUP value")
end select
end if
if (present (negative_weights)) then
negative_weights = IDWTUP < 0
end if
end subroutine heprup_get_run_parameters
@ %def heprup_get_run_parameters
@ Specify PDF set info. Since we support only LHAPDF, the group entry
is zero.
<<HEP common: public>>=
public :: heprup_set_lhapdf_id
<<HEP common: procedures>>=
subroutine heprup_set_lhapdf_id (i_beam, pdf_id)
integer, intent(in) :: i_beam, pdf_id
PDFGUP(i_beam) = 0
PDFSUP(i_beam) = pdf_id
end subroutine heprup_set_lhapdf_id
@ %def heprup_set_lhapdf_id
@ Fill the characteristics for a particular process. Only the process
ID is mandatory. Note that \whizard\ computes cross sections in fb,
so we have to rescale to pb. The maximum weight is meaningless for
unweighted events.
<<HEP common: public>>=
public :: heprup_set_process_parameters
<<HEP common: procedures>>=
subroutine heprup_set_process_parameters &
(i, process_id, cross_section, error, max_weight)
integer, intent(in) :: i, process_id
real(default), intent(in), optional :: cross_section, error, max_weight
real(default), parameter :: pb_per_fb = 1.e-3_default
LPRUP(i) = process_id
if (present (cross_section)) then
XSECUP(i) = cross_section * pb_per_fb
else
XSECUP(i) = 0
end if
if (present (error)) then
XERRUP(i) = error * pb_per_fb
else
XERRUP(i) = 0
end if
select case (IDWTUP)
case (3); XMAXUP(i) = 1
case (4)
if (present (max_weight)) then
XMAXUP(i) = max_weight * pb_per_fb
else
XMAXUP(i) = 0
end if
end select
end subroutine heprup_set_process_parameters
@ %def heprup_set_process_parameters
@ Extract the process parameters, as far as needed.
<<HEP common: public>>=
public :: heprup_get_process_parameters
<<HEP common: procedures>>=
subroutine heprup_get_process_parameters &
(i, process_id, cross_section, error, max_weight)
integer, intent(in) :: i
integer, intent(out), optional :: process_id
real(default), intent(out), optional :: cross_section, error, max_weight
real(default), parameter :: pb_per_fb = 1.e-3_default
if (present (process_id)) process_id = LPRUP(i)
if (present (cross_section)) then
cross_section = XSECUP(i) / pb_per_fb
end if
if (present (error)) then
error = XERRUP(i) / pb_per_fb
end if
if (present (max_weight)) then
select case (IDWTUP)
case (3)
max_weight = 1
case (4)
max_weight = XMAXUP(i) / pb_per_fb
case (1,2) !!! not supported by WHIZARD
max_weight = 0
case default
call msg_fatal ("HEPRUP: unsupported IDWTUP value")
end select
end if
end subroutine heprup_get_process_parameters
@ %def heprup_get_process_parameters
@
\subsection{Run parameter output (verbose)}
This is a verbose output of the HEPRUP block.
<<HEP common: public>>=
public :: heprup_write_verbose
<<HEP common: procedures>>=
subroutine heprup_write_verbose (unit)
integer, intent(in), optional :: unit
integer :: u, i
u = given_output_unit (unit); if (u < 0) return
write (u, "(A)") "HEPRUP Common Block"
write (u, "(3x,A6,' = ',I9,3x,1x,I9,3x,8x,A)") "IDBMUP", IDBMUP, &
"PDG code of beams"
write (u, "(3x,A6,' = ',G12.5,1x,G12.5,8x,A)") "EBMUP ", EBMUP, &
"Energy of beams in GeV"
write (u, "(3x,A6,' = ',I9,3x,1x,I9,3x,8x,A)") "PDFGUP", PDFGUP, &
"PDF author group [-1 = undefined]"
write (u, "(3x,A6,' = ',I9,3x,1x,I9,3x,8x,A)") "PDFSUP", PDFSUP, &
"PDF set ID [-1 = undefined]"
write (u, "(3x,A6,' = ',I9,3x,1x,9x,3x,8x,A)") "IDWTUP", IDWTUP, &
"LHA code for event weight mode"
write (u, "(3x,A6,' = ',I9,3x,1x,9x,3x,8x,A)") "NPRUP ", NPRUP, &
"Number of user subprocesses"
do i = 1, NPRUP
write (u, "(1x,A,I0)") "Subprocess #", i
write (u, "(3x,A6,' = ',ES12.5,1x,12x,8x,A)") "XSECUP", XSECUP(i), &
"Cross section in pb"
write (u, "(3x,A6,' = ',ES12.5,1x,12x,8x,A)") "XERRUP", XERRUP(i), &
"Cross section error in pb"
write (u, "(3x,A6,' = ',ES12.5,1x,12x,8x,A)") "XMAXUP", XMAXUP(i), &
"Maximum event weight (cf. IDWTUP)"
write (u, "(3x,A6,' = ',I9,3x,1x,12x,8x,A)") "LPRUP ", LPRUP(i), &
"Subprocess ID"
end do
end subroutine heprup_write_verbose
@ %def heprup_write_verbose
@
\subsection{Run parameter output (other formats)}
This routine writes the initialization block according to the LHEF
standard. It uses the current contents of the HEPRUP block.
<<HEP common: public>>=
public :: heprup_write_lhef
<<HEP common: procedures>>=
subroutine heprup_write_lhef (unit)
integer, intent(in), optional :: unit
integer :: u, i
u = given_output_unit (unit); if (u < 0) return
write (u, "(2(1x,I0),2(1x,ES17.10),6(1x,I0))") &
IDBMUP, EBMUP, PDFGUP, PDFSUP, IDWTUP, NPRUP
do i = 1, NPRUP
write (u, "(3(1x,ES17.10),1x,I0)") &
XSECUP(i), XERRUP(i), XMAXUP(i), LPRUP(i)
end do
end subroutine heprup_write_lhef
@ %def heprup_write_lhef
@
This routine is a complete dummy at the moment. It uses the current
contents of the HEPRUP block. At the end, it should depend on certain
input flags for the different ASCII event formats.
<<HEP common: public>>=
public :: heprup_write_ascii
<<HEP common: procedures>>=
subroutine heprup_write_ascii (unit)
integer, intent(in), optional :: unit
integer :: u, i
u = given_output_unit (unit); if (u < 0) return
write (u, "(2(1x,I0),2(1x,ES17.10),6(1x,I0))") &
IDBMUP, EBMUP, PDFGUP, PDFSUP, IDWTUP, NPRUP
do i = 1, NPRUP
write (u, "(3(1x,ES17.10),1x,I0)") &
XSECUP(i), XERRUP(i), XMAXUP(i), LPRUP(i)
end do
end subroutine heprup_write_ascii
@ %def heprup_write_ascii
@
\subsubsection{Run parameter input (LHEF)}
In a LHEF file, the parameters are written in correct order on
separate lines, but we should not count on the precise format.
List-directed input should just work.
<<HEP common: public>>=
public :: heprup_read_lhef
<<HEP common: procedures>>=
subroutine heprup_read_lhef (u)
integer, intent(in) :: u
integer :: i
read (u, *) &
IDBMUP, EBMUP, PDFGUP, PDFSUP, IDWTUP, NPRUP
do i = 1, NPRUP
read (u, *) &
XSECUP(i), XERRUP(i), XMAXUP(i), LPRUP(i)
end do
end subroutine heprup_read_lhef
@ %def heprup_read_lhef
@
\subsection{The HEPEUP common block}
<<HEP common: common blocks>>=
common /HEPEUP/ &
NUP, IDPRUP, XWGTUP, SCALUP, AQEDUP, AQCDUP, &
IDUP, ISTUP, MOTHUP, ICOLUP, PUP, VTIMUP, SPINUP
save /HEPEUP/
@ %def HEPEUP
@
\subsubsection{Initialization}
Fill the event characteristics of the common block. The
initialization sets only the number of particles and initializes the
rest with default values. The other routine sets the optional
parameters.
<<HEP common: public>>=
public :: hepeup_init
public :: hepeup_set_event_parameters
<<HEP common: procedures>>=
subroutine hepeup_init (n_tot)
integer, intent(in) :: n_tot
NUP = n_tot
IDPRUP = 0
XWGTUP = 1
SCALUP = -1
AQEDUP = -1
AQCDUP = -1
end subroutine hepeup_init
subroutine hepeup_set_event_parameters &
(proc_id, weight, scale, alpha_qed, alpha_qcd)
integer, intent(in), optional :: proc_id
real(default), intent(in), optional :: weight, scale, alpha_qed, alpha_qcd
if (present (proc_id)) IDPRUP = proc_id
if (present (weight)) XWGTUP = weight
if (present (scale)) SCALUP = scale
if (present (alpha_qed)) AQEDUP = alpha_qed
if (present (alpha_qcd)) AQCDUP = alpha_qcd
end subroutine hepeup_set_event_parameters
@ %def hepeup_init hepeup_set_event_parameters
@ Extract event information. The caller determines the parameters.
<<HEP common: public>>=
public :: hepeup_get_event_parameters
<<HEP common: procedures>>=
subroutine hepeup_get_event_parameters &
(proc_id, weight, scale, alpha_qed, alpha_qcd)
integer, intent(out), optional :: proc_id
real(default), intent(out), optional :: weight, scale, alpha_qed, alpha_qcd
if (present (proc_id)) proc_id = IDPRUP
if (present (weight)) weight = XWGTUP
if (present (scale)) scale = SCALUP
if (present (alpha_qed)) alpha_qed = AQEDUP
if (present (alpha_qcd)) alpha_qcd = AQCDUP
end subroutine hepeup_get_event_parameters
@ %def hepeup_get_event_parameters
@
\subsubsection{Particle data}
Below we need the particle status codes which are actually defined
in the [[subevents]] module.
Set the entry for a specific particle. All parameters are set with
the exception of lifetime and spin, where default values are stored.
<<HEP common: public>>=
public :: hepeup_set_particle
<<HEP common: procedures>>=
subroutine hepeup_set_particle (i, pdg, status, parent, col, p, m2)
integer, intent(in) :: i
integer, intent(in) :: pdg, status
integer, dimension(:), intent(in) :: parent
type(vector4_t), intent(in) :: p
integer, dimension(2), intent(in) :: col
real(default), intent(in) :: m2
if (i > MAXNUP) then
call msg_error (arr=[ &
var_str ("Too many particles in HEPEUP common block. " // &
"If this happened "), &
var_str ("during event output, your events will be " // &
"invalid; please consider "), &
var_str ("switching to a modern event format like HEPMC. " // &
"If you are not "), &
var_str ("using an old, HEPEUP based format and " // &
"nevertheless get this error,"), &
var_str ("please notify the WHIZARD developers,") ])
return
end if
IDUP(i) = pdg
select case (status)
case (PRT_BEAM); ISTUP(i) = -9
case (PRT_INCOMING); ISTUP(i) = -1
case (PRT_BEAM_REMNANT); ISTUP(i) = 3
case (PRT_OUTGOING); ISTUP(i) = 1
case (PRT_RESONANT); ISTUP(i) = 2
case (PRT_VIRTUAL); ISTUP(i) = 3
case default; ISTUP(i) = 0
end select
select case (size (parent))
case (0); MOTHUP(:,i) = 0
case (1); MOTHUP(1,i) = parent(1); MOTHUP(2,i) = 0
case default; MOTHUP(:,i) = [ parent(1), parent(size (parent)) ]
end select
if (col(1) > 0) then
ICOLUP(1,i) = 500 + col(1)
else
ICOLUP(1,i) = 0
end if
if (col(2) > 0) then
ICOLUP(2,i) = 500 + col(2)
else
ICOLUP(2,i) = 0
end if
PUP(1:3,i) = vector3_get_components (space_part (p))
PUP(4,i) = energy (p)
PUP(5,i) = sign (sqrt (abs (m2)), m2)
VTIMUP(i) = 0
SPINUP(i) = 9
end subroutine hepeup_set_particle
@ %def hepeup_set_particle
@ Set the lifetime, actually $c\tau$ measured im mm, where $\tau$ is
the invariant lifetime.
<<HEP common: public>>=
public :: hepeup_set_particle_lifetime
<<HEP common: procedures>>=
subroutine hepeup_set_particle_lifetime (i, lifetime)
integer, intent(in) :: i
real(default), intent(in) :: lifetime
VTIMUP(i) = lifetime
end subroutine hepeup_set_particle_lifetime
@ %def hepeup_set_particle_lifetime
@ Set the particle spin entry. We need the cosine of the angle of the
spin axis with respect to the three-momentum of the parent particle.
If the particle has a full polarization density matrix given, we need
the particle momentum and polarization as well as the mother-particle
momentum. The polarization is transformed into a spin vector (which
is sensible only for spin-1/2 or massless particles), which then is
transformed into the lab frame (by a rotation of the 3-axis to the
particle momentum axis). Finally, we compute the scalar product of
this vector with the mother-particle three-momentum.
This puts severe restrictions on the applicability of this definition,
and Lorentz invariance is lost. Unfortunately, the Les Houches Accord
requires this computation.
<<HEP common: public>>=
public :: hepeup_set_particle_spin
<<HEP common: interfaces>>=
interface hepeup_set_particle_spin
module procedure hepeup_set_particle_spin_pol
end interface
<<HEP common: procedures>>=
subroutine hepeup_set_particle_spin_pol (i, p, pol, p_mother)
integer, intent(in) :: i
type(vector4_t), intent(in) :: p
type(polarization_t), intent(in) :: pol
type(vector4_t), intent(in) :: p_mother
type(vector3_t) :: s3, p3
type(vector4_t) :: s4
s3 = vector3_moving (pol%get_axis ())
p3 = space_part (p)
s4 = rotation_to_2nd (3, p3) * vector4_moving (0._default, s3)
SPINUP(i) = enclosed_angle_ct (s4, p_mother)
end subroutine hepeup_set_particle_spin_pol
@ %def hepeup_set_particle_spin
@
Extract particle data. The caller decides which ones to retrieve.
Status codes: beam remnants share the status code with virtual particles.
However, for the purpose of WHIZARD we should identify them. We
use the PDG code for this.
<<HEP common: public>>=
public :: hepeup_get_particle
<<HEP common: procedures>>=
subroutine hepeup_get_particle (i, pdg, status, parent, col, p, m2)
integer, intent(in) :: i
integer, intent(out), optional :: pdg, status
integer, dimension(:), intent(out), optional :: parent
type(vector4_t), intent(out), optional :: p
integer, dimension(2), intent(out), optional :: col
real(default), dimension(5,MAXNUP) :: pup_def
real(default), intent(out), optional :: m2
if (present (pdg)) pdg = IDUP(i)
if (present (status)) then
select case (ISTUP(i))
case (-9); status = PRT_BEAM
case (-1); status = PRT_INCOMING
case (1); status = PRT_OUTGOING
case (2); status = PRT_RESONANT
case (3);
select case (abs (IDUP(i)))
case (HADRON_REMNANT, HADRON_REMNANT_SINGLET, &
HADRON_REMNANT_TRIPLET, HADRON_REMNANT_OCTET)
status = PRT_BEAM_REMNANT
case default
status = PRT_VIRTUAL
end select
case default
status = PRT_UNDEFINED
end select
end if
if (present (parent)) then
select case (size (parent))
case (0)
case (1); parent(1) = MOTHUP(1,i)
case (2); parent = MOTHUP(:,i)
end select
end if
if (present (col)) then
col = ICOLUP(:,i)
end if
if (present (p)) then
pup_def = PUP
p = vector4_moving (pup_def(4,i), vector3_moving (pup_def(1:3,i)))
end if
if (present (m2)) then
m2 = sign (PUP(5,i) ** 2, PUP(5,i))
end if
end subroutine hepeup_get_particle
@ %def hepeup_get_particle
@
\subsection{The HEPEVT and HEPEV4 common block}
For the LEP Monte Carlos, a standard common block has been proposed
in AKV89. We strongly recommend its use. (The description is an
abbreviated transcription of AKV89, Vol. 3, pp. 327-330).
[[NMXHEP]] is the maximum number of entries:
<<HEP common: variables>>=
integer, parameter :: NMXHEP = 4000
@ %def NMXHEP
@ [[NEVHEP]] is normally the event number, but may take special
values as follows:
0 the program does not keep track of event numbers.
-1 a special initialization record.
-2 a special final record.
<<HEP common: variables>>=
integer :: NEVHEP
@ %def NEVHEP
@ [[NHEP]] holds the number of entries for this event.
<<HEP common: variables>>=
integer, public :: NHEP
@ %def NHEP
@ The entry [[ISTHEP(N)]] gives the status code for the [[N]]th entry,
with the following semantics:
0 a null entry.
1 an existing entry, which has not decayed or fragmented.
2 a decayed or fragmented entry, which is retained for
event history information.
3 documentation line.
4- 10 reserved for future standards.
11-200 at the disposal of each model builder.
201- at the disposal of users.
<<HEP common: variables>>=
integer, dimension(NMXHEP), public :: ISTHEP
@ %def ISTHEP
@
The Particle Data Group has proposed standard particle codes,
which are to be stored in [[IDHEP(N)]].
<<HEP common: variables>>=
integer, dimension(NMXHEP), public :: IDHEP
@ %def IDHEP
@ [[JMOHEP(1,N)]] points to the mother of the [[N]]th entry, if any.
It is set to zero for initial entries.
[[JMOHEP(2,N)]] points to the second mother, if any.
<<HEP common: variables>>=
integer, dimension(2, NMXHEP), public :: JMOHEP
@ %def JMOHEP
@ [[JDAHEP(1,N)]] and [[JDAHEP(2,N)]] point to the first and last daughter
of the [[N]]th entry, if any. These are zero for entries which have not
yet decayed. The other daughters are stored in between these two.
<<HEP common: variables>>=
integer, dimension(2, NMXHEP), public :: JDAHEP
@ %def JDAHEP
@ In [[PHEP]] we store the momentum of the particle, more specifically
this means that [[PHEP(1,N)]], [[PHEP(2,N)]], and [[PHEP(3,N)]] contain the
momentum in the $x$, $y$, and $z$ direction (as defined by the machine
people), measured in GeV/c. [[PHEP(4,N)]] contains the energy in GeV
and [[PHEP(5,N)]] the mass in GeV$/c^2$. The latter may be negative for
spacelike partons.
<<HEP common: variables>>=
double precision, dimension(5, NMXHEP), public :: PHEP
@ %def PHEP
@ Finally [[VHEP]] is the place to store the position of the production
vertex. [[VHEP(1,N)]], [[VHEP(2,N)]], and [[VHEP(3,N)]] contain the $x$, $y$,
and $z$ coordinate (as defined by the machine people), measured in mm.
[[VHEP(4,N)]] contains the production time in mm/c.
<<HEP common: variables>>=
double precision, dimension(4, NMXHEP) :: VHEP
@ %def VHEP
@ As an amendment to the proposed standard common block HEPEVT, we
also have a polarisation common block HEPSPN, as described in
AKV89. [[SHEP(1,N)]], [[SHEP(2,N)]], and [[SHEP(3,N)]] give the $x$, $y$, and $z$
component of the spinvector $s$ of a fermion in the fermions restframe.
Furthermore, we add the polarization of the corresponding outgoing
particles:
<<HEP common: variables>>=
integer, dimension(NMXHEP) :: hepevt_pol
@ %def hepevt_pol
@
By this variable the identity of the current process is given, defined
via the LPRUP codes.
<<HEP common: variables>>=
integer, public :: idruplh
@ %def idruplh
This is the event weight, i.e. the cross section divided by the total
number of generated events for the output of the parton shower programs.
<<HEP common: variables>>=
double precision, public :: eventweightlh
@ %def eventweightlh
@ There are the values for the electromagnetic and the strong coupling
constants, $\alpha_{em}$ and $\alpha_s$.
<<HEP common: variables>>=
double precision, public :: alphaqedlh, alphaqcdlh
@ %def alphaqedlh, alphaqcdlh
@ This is the squared scale $Q$ of the event.
<<HEP common: variables>>=
double precision, dimension(10), public :: scalelh
@ %def scalelh
@ Finally, these variables contain the spin information and the
color/anticolor flow of the particles.
<<HEP common: variables>>=
double precision, dimension (3,NMXHEP), public :: spinlh
integer, dimension (2,NMXHEP), public :: icolorflowlh
@ %def spinlh icolorflowlh
By convention, [[SHEP(4,N)]] is always 1. All this is taken from StdHep
4.06 manual and written using Fortran90 conventions.
<<HEP common: common blocks>>=
common /HEPEVT/ &
NEVHEP, NHEP, ISTHEP, IDHEP, &
JMOHEP, JDAHEP, PHEP, VHEP
save /HEPEVT/
@ %def HEPEVT
@ Here we store HEPEVT parameters of the WHIZARD 1 realization which
are not part of the HEPEVT common block.
<<HEP common: variables>>=
integer :: hepevt_n_out, hepevt_n_remnants
@ %def hepevt_n_out, hepevt_n_remnants
@
<<HEP common: variables>>=
double precision :: hepevt_weight, hepevt_function_value
double precision :: hepevt_function_ratio
@ %def hepevt_weight hepevt_function_value
@ The HEPEV4 common block is an extension of the HEPEVT common block
to allow for partonic colored events, including especially the color
flow etc.
<<HEP common: common blocks>>=
common /HEPEV4/ &
eventweightlh, alphaqedlh, alphaqcdlh, scalelh, &
spinlh, icolorflowlh, idruplh
save /HEPEV4/
@ %def HEPEV4
@ Filling HEPEVT: If the event count is not provided, set [[NEVHEP]]
to zero. If the event count is [[-1]] or [[-2]], the record
corresponds to initialization and finalization, and the event is
irrelevant.
Note that the event count may be larger than $2^{31}$ (2 GEvents). In
that case, cut off the upper bits since [[NEVHEP]] is probably limited
to default integer.
For the HEPEV4 common block, it is unclear why the [[scalelh]] variable
is 10-dimensional. We choose to only set the first value of the array.
<<HEP common: public>>=
public :: hepevt_init
public :: hepevt_set_event_parameters
<<HEP common: procedures>>=
subroutine hepevt_init (n_tot, n_out)
integer, intent(in) :: n_tot, n_out
NHEP = n_tot
NEVHEP = 0
idruplh = 0
hepevt_n_out = n_out
hepevt_n_remnants = 0
hepevt_weight = 1
eventweightlh = 1
hepevt_function_value = 0
hepevt_function_ratio = 1
alphaqcdlh = -1
alphaqedlh = -1
scalelh = -1
end subroutine hepevt_init
subroutine hepevt_set_event_parameters &
(proc_id, weight, function_value, function_ratio, &
alpha_qcd, alpha_qed, scale, i_evt)
integer, intent(in), optional :: proc_id
integer, intent(in), optional :: i_evt
real(default), intent(in), optional :: weight, function_value, &
function_ratio, alpha_qcd, alpha_qed, scale
if (present (proc_id)) idruplh = proc_id
if (present (i_evt)) NEVHEP = i_evt
if (present (weight)) then
hepevt_weight = weight
eventweightlh = weight
end if
if (present (function_value)) hepevt_function_value = &
function_value
if (present (function_ratio)) hepevt_function_ratio = &
function_ratio
if (present (alpha_qcd)) alphaqcdlh = alpha_qcd
if (present (alpha_qed)) alphaqedlh = alpha_qed
if (present (scale)) scalelh(1) = scale
if (present (i_evt)) NEVHEP = i_evt
end subroutine hepevt_set_event_parameters
@ %def hepevt_init hepevt_set_event_parameters
@ Set the entry for a specific particle. All parameters are set with
the exception of lifetime and spin, where default values are stored.
<<HEP common: public>>=
public :: hepevt_set_particle
<<HEP common: procedures>>=
subroutine hepevt_set_particle &
(i, pdg, status, parent, child, p, m2, hel, vtx, &
col, pol_status, pol, fill_hepev4)
integer, intent(in) :: i
integer, intent(in) :: pdg, status
integer, dimension(:), intent(in) :: parent
integer, dimension(:), intent(in) :: child
logical, intent(in), optional :: fill_hepev4
type(vector4_t), intent(in) :: p
real(default), intent(in) :: m2
integer, dimension(2), intent(in) :: col
integer, intent(in) :: pol_status
integer, intent(in) :: hel
type(polarization_t), intent(in), optional :: pol
type(vector4_t), intent(in) :: vtx
logical :: hepev4
hepev4 = .false.; if (present (fill_hepev4)) hepev4 = fill_hepev4
IDHEP(i) = pdg
select case (status)
case (PRT_BEAM); ISTHEP(i) = 2
case (PRT_INCOMING); ISTHEP(i) = 2
case (PRT_OUTGOING); ISTHEP(i) = 1
case (PRT_VIRTUAL); ISTHEP(i) = 2
case (PRT_RESONANT); ISTHEP(i) = 2
case default; ISTHEP(i) = 0
end select
select case (size (parent))
case (0); JMOHEP(:,i) = 0
case (1); JMOHEP(1,i) = parent(1); JMOHEP(2,i) = 0
case default; JMOHEP(:,i) = [ parent(1), parent(size (parent)) ]
end select
select case (size (child))
case (0); JDAHEP(:,i) = 0
case (1); JDAHEP(:,i) = child(1)
case default; JDAHEP(:,i) = [ child(1), child(size (child)) ]
end select
PHEP(1:3,i) = vector3_get_components (space_part (p))
PHEP(4,i) = energy (p)
PHEP(5,i) = sign (sqrt (abs (m2)), m2)
VHEP(1:3,i) = vtx%p(1:3)
VHEP(4,i) = vtx%p(0)
hepevt_pol(i) = hel
if (hepev4) then
if (col(1) > 0) then
icolorflowlh(1,i) = 500 + col(1)
else
icolorflowlh(1,i) = 0
end if
if (col(2) > 0) then
icolorflowlh(2,i) = 500 + col(2)
else
icolorflowlh(2,i) = 0
end if
if (present (pol) .and. &
pol_status == PRT_GENERIC_POLARIZATION) then
if (pol%is_polarized ()) &
spinlh(:,i) = pol%get_axis ()
else
spinlh(:,i) = zero
spinlh(3,i) = hel
end if
end if
end subroutine hepevt_set_particle
@ %def hepevt_set_particle
@
\subsection{Event output}
This is a verbose output of the HEPEVT block.
<<HEP common: public>>=
public :: hepevt_write_verbose
<<HEP common: procedures>>=
subroutine hepevt_write_verbose (unit)
integer, intent(in), optional :: unit
integer :: u, i
u = given_output_unit (unit); if (u < 0) return
write (u, "(A)") "HEPEVT Common Block"
write (u, "(3x,A6,' = ',I9,3x,1x,20x,A)") "NEVHEP", NEVHEP, &
"Event number"
write (u, "(3x,A6,' = ',I9,3x,1x,20x,A)") "NHEP ", NHEP, &
"Number of particles in event"
do i = 1, NHEP
write (u, "(1x,A,I0)") "Particle #", i
write (u, "(3x,A6,' = ',I9,3x,1x,20x,A)", advance="no") &
"ISTHEP", ISTHEP(i), "Status code: "
select case (ISTHEP(i))
case ( 0); write (u, "(A)") "null entry"
case ( 1); write (u, "(A)") "outgoing"
case ( 2); write (u, "(A)") "decayed"
case ( 3); write (u, "(A)") "documentation"
case (4:10); write (u, "(A)") "[unspecified]"
case (11:200); write (u, "(A)") "[model-specific]"
case (201:); write (u, "(A)") "[user-defined]"
case default; write (u, "(A)") "[undefined]"
end select
write (u, "(3x,A6,' = ',I9,3x,1x,20x,A)") "IDHEP ", IDHEP(i), &
"PDG code of particle"
write (u, "(3x,A6,' = ',I9,3x,1x,I9,3x,8x,A)") "JMOHEP", JMOHEP(:,i), &
"Index of first/second mother"
write (u, "(3x,A6,' = ',I9,3x,1x,I9,3x,8x,A)") "JDAHEP", JDAHEP(:,i), &
"Index of first/last daughter"
write (u, "(3x,A6,' = ',ES12.5,1x,ES12.5,8x,A)") "PHEP12", &
PHEP(1:2,i), "Transversal momentum (x/y) in GeV"
write (u, "(3x,A6,' = ',ES12.5,1x,12x,8x,A)") "PHEP3 ", PHEP(3,i), &
"Longitudinal momentum (z) in GeV"
write (u, "(3x,A6,' = ',ES12.5,1x,12x,8x,A)") "PHEP4 ", PHEP(4,i), &
"Energy in GeV"
write (u, "(3x,A6,' = ',ES12.5,1x,12x,8x,A)") "PHEP5 ", PHEP(5,i), &
"Invariant mass in GeV"
write (u, "(3x,A6,' = ',ES12.5,1x,ES12.5,8x,A)") "VHEP12", VHEP(1:2,i), &
"Transversal displacement (xy) in mm"
write (u, "(3x,A6,' = ',ES12.5,1x,12x,8x,A)") "VHEP3 ", VHEP(3,i), &
"Longitudinal displacement (z) in mm"
write (u, "(3x,A6,' = ',ES12.5,1x,12x,8x,A)") "VHEP4 ", VHEP(4,i), &
"Production time in mm"
end do
end subroutine hepevt_write_verbose
@ %def hepevt_write_verbose
@
This is a verbose output of the HEPEUP block.
<<HEP common: public>>=
public :: hepeup_write_verbose
<<HEP common: procedures>>=
subroutine hepeup_write_verbose (unit)
integer, intent(in), optional :: unit
integer :: u, i
u = given_output_unit (unit); if (u < 0) return
write (u, "(A)") "HEPEUP Common Block"
write (u, "(3x,A6,' = ',I9,3x,1x,20x,A)") "NUP ", NUP, &
"Number of particles in event"
write (u, "(3x,A6,' = ',I9,3x,1x,20x,A)") "IDPRUP", IDPRUP, &
"Subprocess ID"
write (u, "(3x,A6,' = ',ES12.5,1x,20x,A)") "XWGTUP", XWGTUP, &
"Event weight"
write (u, "(3x,A6,' = ',ES12.5,1x,20x,A)") "SCALUP", SCALUP, &
"Event energy scale in GeV"
write (u, "(3x,A6,' = ',ES12.5,1x,20x,A)") "AQEDUP", AQEDUP, &
"QED coupling [-1 = undefined]"
write (u, "(3x,A6,' = ',ES12.5,1x,20x,A)") "AQCDUP", AQCDUP, &
"QCD coupling [-1 = undefined]"
do i = 1, NUP
write (u, "(1x,A,I0)") "Particle #", i
write (u, "(3x,A6,' = ',I9,3x,1x,20x,A)") "IDUP ", IDUP(i), &
"PDG code of particle"
write (u, "(3x,A6,' = ',I9,3x,1x,20x,A)", advance="no") &
"ISTUP ", ISTUP(i), "Status code: "
select case (ISTUP(i))
case (-1); write (u, "(A)") "incoming"
case ( 1); write (u, "(A)") "outgoing"
case (-2); write (u, "(A)") "spacelike"
case ( 2); write (u, "(A)") "resonance"
case ( 3); write (u, "(A)") "resonance (doc)"
case (-9); write (u, "(A)") "beam"
case default; write (u, "(A)") "[undefined]"
end select
write (u, "(3x,A6,' = ',I9,3x,1x,I9,3x,8x,A)") "MOTHUP", MOTHUP(:,i), &
"Index of first/last mother"
write (u, "(3x,A6,' = ',I9,3x,1x,I9,3x,8x,A)") "ICOLUP", ICOLUP(:,i), &
"Color/anticolor flow index"
write (u, "(3x,A6,' = ',ES12.5,1x,ES12.5,8x,A)") "PUP1/2", PUP(1:2,i), &
"Transversal momentum (x/y) in GeV"
write (u, "(3x,A6,' = ',ES12.5,1x,12x,8x,A)") "PUP3 ", PUP(3,i), &
"Longitudinal momentum (z) in GeV"
write (u, "(3x,A6,' = ',ES12.5,1x,12x,8x,A)") "PUP4 ", PUP(4,i), &
"Energy in GeV"
write (u, "(3x,A6,' = ',ES12.5,1x,12x,8x,A)") "PUP5 ", PUP(5,i), &
"Invariant mass in GeV"
write (u, "(3x,A6,' = ',ES12.5,1x,12x,8x,A)") "VTIMUP", VTIMUP(i), &
"Invariant lifetime in mm"
write (u, "(3x,A6,' = ',ES12.5,1x,12x,8x,A)") "SPINUP", SPINUP(i), &
"cos(spin angle) [9 = undefined]"
end do
end subroutine hepeup_write_verbose
@ %def hepeup_write_verbose
@
\subsection{Event output in various formats}
This routine writes event output according to the LHEF standard. It
uses the current contents of the HEPEUP block.
<<HEP common: public>>=
public :: hepeup_write_lhef
public :: hepeup_write_lha
<<HEP common: procedures>>=
subroutine hepeup_write_lhef (unit)
integer, intent(in), optional :: unit
integer :: u, i
u = given_output_unit (unit); if (u < 0) return
call msg_debug (D_EVENTS, "hepeup_write_lhef")
call msg_debug2 (D_EVENTS, "ID IST MOTH ICOL P VTIM SPIN")
write (u, "(2(1x,I0),4(1x,ES17.10))") &
NUP, IDPRUP, XWGTUP, SCALUP, AQEDUP, AQCDUP
do i = 1, NUP
write (u, "(6(1x,I0),7(1x,ES17.10))") &
IDUP(i), ISTUP(i), MOTHUP(:,i), ICOLUP(:,i), &
PUP(:,i), VTIMUP(i), SPINUP(i)
if (debug2_active (D_EVENTS)) then
write (msg_buffer, "(6(1x,I0),7(1x,ES17.10))") &
IDUP(i), ISTUP(i), MOTHUP(:,i), ICOLUP(:,i), &
PUP(:,i), VTIMUP(i), SPINUP(i)
call msg_message ()
end if
end do
end subroutine hepeup_write_lhef
subroutine hepeup_write_lha (unit)
integer, intent(in), optional :: unit
integer :: u, i
integer, dimension(MAXNUP) :: spin_up
spin_up = int(SPINUP)
u = given_output_unit (unit); if (u < 0) return
write (u, "(2(1x,I5),1x,ES17.10,3(1x,ES13.6))") &
NUP, IDPRUP, XWGTUP, SCALUP, AQEDUP, AQCDUP
write (u, "(500(1x,I5))") IDUP(:NUP)
write (u, "(500(1x,I5))") MOTHUP(1,:NUP)
write (u, "(500(1x,I5))") MOTHUP(2,:NUP)
write (u, "(500(1x,I5))") ICOLUP(1,:NUP)
write (u, "(500(1x,I5))") ICOLUP(2,:NUP)
write (u, "(500(1x,I5))") ISTUP(:NUP)
write (u, "(500(1x,I5))") spin_up(:NUP)
do i = 1, NUP
write (u, "(1x,I5,4(1x,ES17.10))") i, PUP([ 4,1,2,3 ], i)
end do
end subroutine hepeup_write_lha
@ %def hepeup_write_lhef hepeup_write_lha
@ This routine writes event output according to the HEPEVT standard. It
uses the current contents of the HEPEVT block and some additional
parameters according to the standard in WHIZARD 1. For the long ASCII
format, the value of the sample function (i.e. the product of squared
matrix element, structure functions and phase space factor is printed out).
The option of reweighting matrix elements with respect to some
reference cross section is not implemented in WHIZARD 2 for this event
format, therefore the second entry in the long ASCII format (the
function ratio) is always one. The ATHENA format is an implementation
of the HEPEVT format that is readable by the ATLAS ATHENA software
framework. It is very similar to the WHIZARD 1 HEPEVT format, except
that it contains an event counter, a particle counter inside the
event, and has the HEPEVT [[ISTHEP]] status before the PDG code. The
MOKKA format is a special ASCII format that contains the information
to be parsed to the MOKKA LC fast simulation software.
<<HEP common: public>>=
public :: hepevt_write_hepevt
public :: hepevt_write_ascii
public :: hepevt_write_athena
public :: hepevt_write_mokka
<<HEP common: procedures>>=
subroutine hepevt_write_hepevt (unit)
integer, intent(in), optional :: unit
integer :: u, i
u = given_output_unit (unit); if (u < 0) return
write (u, "(3(1x,I0),(1x,ES17.10))") &
NHEP, hepevt_n_out, hepevt_n_remnants, hepevt_weight
do i = 1, NHEP
write (u, "(7(1x,I0))") &
ISTHEP(i), IDHEP(i), JMOHEP(:,i), JDAHEP(:,i), hepevt_pol(i)
write (u, "(5(1x,ES17.10))") PHEP(:,i)
write (u, "(5(1x,ES17.10))") VHEP(:,i), 0.d0
end do
end subroutine hepevt_write_hepevt
subroutine hepevt_write_ascii (unit, long)
integer, intent(in), optional :: unit
logical, intent(in) :: long
integer :: u, i
u = given_output_unit (unit); if (u < 0) return
write (u, "(3(1x,I0),(1x,ES17.10))") &
NHEP, hepevt_n_out, hepevt_n_remnants, hepevt_weight
do i = 1, NHEP
if (ISTHEP(i) /= 1) cycle
write (u, "(2(1x,I0))") IDHEP(i), hepevt_pol(i)
write (u, "(5(1x,ES17.10))") PHEP(:,i)
end do
if (long) then
write (u, "(2(1x,ES17.10))") &
hepevt_function_value, hepevt_function_ratio
end if
end subroutine hepevt_write_ascii
subroutine hepevt_write_athena (unit)
integer, intent(in), optional :: unit
integer :: u, i, num_event
num_event = 0
u = given_output_unit (unit); if (u < 0) return
write (u, "(2(1x,I0))") NEVHEP, NHEP
do i = 1, NHEP
write (u, "(7(1x,I0))") &
i, ISTHEP(i), IDHEP(i), JMOHEP(:,i), JDAHEP(:,i)
write (u, "(5(1x,ES17.10))") PHEP(:,i)
write (u, "(5(1x,ES17.10))") VHEP(1:4,i)
end do
end subroutine hepevt_write_athena
subroutine hepevt_write_mokka (unit)
integer, intent(in), optional :: unit
integer :: u, i
u = given_output_unit (unit); if (u < 0) return
write (u, "(3(1x,I0),(1x,ES17.10))") &
NHEP, hepevt_n_out, hepevt_n_remnants, hepevt_weight
do i = 1, NHEP
write (u, "(4(1x,I0),4(1x,ES17.10))") &
ISTHEP(i), IDHEP(i), JDAHEP(1,i), JDAHEP(2,i), &
PHEP(1:3,i), PHEP(5,i)
end do
end subroutine hepevt_write_mokka
@ %def hepevt_write_hepevt hepevt_write_ascii
@ %def hepevt_write_athena
@
\subsection{Event input in various formats}
This routine writes event output according to the LHEF standard. It
uses the current contents of the HEPEUP block.
<<HEP common: public>>=
public :: hepeup_read_lhef
<<HEP common: procedures>>=
subroutine hepeup_read_lhef (u)
integer, intent(in) :: u
integer :: i
read (u, *) &
NUP, IDPRUP, XWGTUP, SCALUP, AQEDUP, AQCDUP
do i = 1, NUP
read (u, *) &
IDUP(i), ISTUP(i), MOTHUP(:,i), ICOLUP(:,i), &
PUP(:,i), VTIMUP(i), SPINUP(i)
end do
end subroutine hepeup_read_lhef
@ %def hepeup_read_lhef
@
\subsection{Data Transfer: particle sets}
The \whizard\ format for handling particle data in events is
[[particle_set_t]]. We have to interface this to the common blocks.
We first create a new particle set that contains only the particles
that are supported by the LHEF format. These are: beam, incoming,
resonant, outgoing. We drop particles with unknown, virtual or
beam-remnant status.
From this set we fill the common block. Event information such as
process ID and weight is not transferred here; this has to be done by
the caller. The spin information is set only if the particle has a
unique mother, and if its polarization is fully defined.
We use this routine also to hand over information to Pythia which lets
Tauola access SPINUP. Tauola expects in SPINUP the helicity and not the
LHA convention. We switch to this mode with [[tauola_convention]].
<<HEP common: public>>=
public :: hepeup_from_particle_set
<<HEP common: procedures>>=
subroutine hepeup_from_particle_set (pset_in, &
keep_beams, keep_remnants, tauola_convention)
type(particle_set_t), intent(in) :: pset_in
type(particle_set_t), target :: pset
logical, intent(in), optional :: keep_beams
logical, intent(in), optional :: keep_remnants
logical, intent(in), optional :: tauola_convention
integer :: i, n_parents, status, n_tot
integer, dimension(1) :: i_mother
logical :: kr, tc
kr = .true.; if (present (keep_remnants)) kr = keep_remnants
tc = .false.; if (present (tauola_convention)) tc = tauola_convention
call pset_in%filter_particles (pset, real_parents = .true. , &
keep_beams = keep_beams, keep_virtuals = .false.)
n_tot = pset%get_n_tot ()
call hepeup_init (n_tot)
do i = 1, n_tot
associate (prt => pset%prt(i))
status = prt%get_status ()
if (kr .and. status == PRT_BEAM_REMNANT &
.and. prt%get_n_children () == 0) &
status = PRT_OUTGOING
call hepeup_set_particle (i, &
prt%get_pdg (), &
status, &
prt%get_parents (), &
prt%get_color (), &
prt%get_momentum (), &
prt%get_p2 ())
n_parents = prt%get_n_parents ()
call hepeup_set_particle_lifetime (i, &
prt%get_lifetime ())
if (.not. tc) then
if (n_parents == 1) then
i_mother = prt%get_parents ()
select case (prt%get_polarization_status ())
case (PRT_GENERIC_POLARIZATION)
call hepeup_set_particle_spin (i, &
prt%get_momentum (), &
prt%get_polarization (), &
pset%prt(i_mother(1))%get_momentum ())
end select
end if
else
select case (prt%get_polarization_status ())
case (PRT_DEFINITE_HELICITY)
SPINUP(i) = prt%get_helicity()
end select
end if
end associate
end do
end subroutine hepeup_from_particle_set
@ %def hepeup_from_particle_set
@ Input. The particle set should be allocated properly, but we
replace the particle contents.
If there are no beam particles in the event, we try to reconstruct beam
particles and beam remnants. We assume for simplicity that the beam
particles, if any, are the first two particles. If they are absent, the first
two particles should be the incoming partons.
<<HEP common: public>>=
public :: hepeup_to_particle_set
<<HEP common: procedures>>=
subroutine hepeup_to_particle_set &
(particle_set, recover_beams, model, alt_model)
type(particle_set_t), intent(inout), target :: particle_set
logical, intent(in), optional :: recover_beams
class(model_data_t), intent(in), target :: model, alt_model
type(particle_t), dimension(:), allocatable :: prt
integer, dimension(2) :: parent
integer, dimension(:), allocatable :: child
integer :: i, j, k, pdg, status
type(flavor_t) :: flv
type(color_t) :: col
integer, dimension(2) :: c
type(vector4_t) :: p
real(default) :: p2
logical :: reconstruct
integer :: off
if (present (recover_beams)) then
reconstruct = recover_beams .and. .not. all (ISTUP(1:2) == PRT_BEAM)
else
reconstruct = .false.
end if
if (reconstruct) then
off = 4
else
off = 0
end if
allocate (prt (NUP + off), child (NUP + off))
do i = 1, NUP
k = i + off
call hepeup_get_particle (i, pdg, status, col = c, p = p, m2 = p2)
call flv%init (pdg, model, alt_model)
call prt(k)%set_flavor (flv)
call prt(k)%reset_status (status)
call col%init (c)
call prt(k)%set_color (col)
call prt(k)%set_momentum (p, p2)
where (MOTHUP(:,i) /= 0)
parent = MOTHUP(:,i) + off
elsewhere
parent = 0
end where
call prt(k)%set_parents (parent)
child = [(j, j = 1 + off, NUP + off)]
where (MOTHUP(1,:NUP) /= i .and. MOTHUP(2,:NUP) /= i) child = 0
call prt(k)%set_children (child)
end do
if (reconstruct) then
do k = 1, 2
call prt(k)%reset_status (PRT_BEAM)
call prt(k)%set_children ([k+2,k+4])
end do
do k = 3, 4
call prt(k)%reset_status (PRT_BEAM_REMNANT)
call prt(k)%set_parents ([k-2])
end do
do k = 5, 6
call prt(k)%set_parents ([k-4])
end do
end if
call particle_set%replace (prt)
end subroutine hepeup_to_particle_set
@ %def hepeup_to_particle_set
@
The HEPEVT common block is quite similar, but does contain less
information, e.g. no color flows (it was LEP time). The spin
information is set only if the particle has a unique mother, and if
its polarization is fully defined.
<<HEP common: public>>=
public :: hepevt_from_particle_set
<<HEP common: procedures>>=
subroutine hepevt_from_particle_set &
(particle_set, keep_beams, keep_remnants, ensure_order, fill_hepev4)
type(particle_set_t), intent(in) :: particle_set
type(particle_set_t), target :: pset_hepevt, pset_tmp
logical, intent(in), optional :: keep_beams
logical, intent(in), optional :: keep_remnants
logical, intent(in), optional :: ensure_order
logical, intent(in), optional :: fill_hepev4
integer :: i, status, n_tot
logical :: activate_remnants, ensure
activate_remnants = .true.
if (present (keep_remnants)) activate_remnants = keep_remnants
ensure = .false.
if (present (ensure_order)) ensure = ensure_order
call particle_set%filter_particles (pset_tmp, real_parents = .true., &
keep_virtuals = .false., keep_beams = keep_beams)
if (ensure) then
call pset_tmp%to_hepevt_form (pset_hepevt)
else
pset_hepevt = pset_tmp
end if
n_tot = pset_hepevt%get_n_tot ()
call hepevt_init (n_tot, pset_hepevt%get_n_out ())
do i = 1, n_tot
associate (prt => pset_hepevt%prt(i))
status = prt%get_status ()
if (activate_remnants &
.and. status == PRT_BEAM_REMNANT &
.and. prt%get_n_children () == 0) &
status = PRT_OUTGOING
select case (prt%get_polarization_status ())
case (PRT_GENERIC_POLARIZATION)
call hepevt_set_particle (i, &
prt%get_pdg (), status, &
prt%get_parents (), &
prt%get_children (), &
prt%get_momentum (), &
prt%get_p2 (), &
prt%get_helicity (), &
prt%get_vertex (), &
prt%get_color (), &
prt%get_polarization_status (), &
pol = prt%get_polarization (), &
fill_hepev4 = fill_hepev4)
case default
call hepevt_set_particle (i, &
prt%get_pdg (), status, &
prt%get_parents (), &
prt%get_children (), &
prt%get_momentum (), &
prt%get_p2 (), &
prt%get_helicity (), &
prt%get_vertex (), &
prt%get_color (), &
prt%get_polarization_status (), &
fill_hepev4 = fill_hepev4)
end select
end associate
end do
call pset_hepevt%final ()
end subroutine hepevt_from_particle_set
@ %def hepevt_from_particle_set
@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
\section{HepMC events}
This section provides the interface to the HepMC C++ library for handling
Monte-Carlo events.
Each C++ class of HepMC that we use is mirrored by a Fortran type,
which contains as its only component the C pointer to the C++ object.
Each C++ method of HepMC that we use has a C wrapper function. This
function takes a pointer to the host object as its first argument.
Further arguments are either C pointers, or in the case of simple
types (integer, real), interoperable C/Fortran objects.
The C wrapper functions have explicit interfaces in the Fortran
module. They are called by Fortran wrapper procedures. These are
treated as methods of the corresponding Fortran type.
<<[[hepmc_interface.f90]]>>=
<<File header>>
module hepmc_interface
use, intrinsic :: iso_c_binding !NODEP!
<<Use kinds>>
<<Use strings>>
use constants, only: PI
use lorentz
use flavors
use colors
use helicities
use polarizations
<<Standard module head>>
<<HepMC interface: public>>
<<HepMC interface: types>>
<<HepMC interface: parameters>>
<<HepMC interface: interfaces>>
contains
<<HepMC interface: procedures>>
end module hepmc_interface
@ %def hepmc_interface
@
\subsection{Interface check}
This function can be called in order to verify that we are using the
actual HepMC library, and not the dummy version.
<<HepMC interface: interfaces>>=
interface
logical(c_bool) function hepmc_available () bind(C)
import
end function hepmc_available
end interface
<<HepMC interface: public>>=
public :: hepmc_is_available
<<HepMC interface: procedures>>=
function hepmc_is_available () result (flag)
logical :: flag
flag = hepmc_available ()
end function hepmc_is_available
@ %def hepmc_is_available
@
\subsection{FourVector}
The C version of four-vectors is often transferred by value, and the
associated procedures are all inlined. The wrapper needs to transfer
by reference, so we create FourVector objects on the heap which have
to be deleted explicitly. The input is a [[vector4_t]] or
[[vector3_t]] object from the [[lorentz]] module.
<<HepMC interface: public>>=
public :: hepmc_four_vector_t
<<HepMC interface: types>>=
type :: hepmc_four_vector_t
private
type(c_ptr) :: obj
end type hepmc_four_vector_t
@ %def hepmc_four_vector_t
@ In the C constructor, the zero-component (fourth argument) is
optional; if missing, it is set to zero. The Fortran version has
initializer form and takes either a three-vector or a four-vector.
A further version extracts the four-vector from a HepMC particle
object.
<<HepMC interface: interfaces>>=
interface
type(c_ptr) function new_four_vector_xyz (x, y, z) bind(C)
import
real(c_double), value :: x, y, z
end function new_four_vector_xyz
end interface
interface
type(c_ptr) function new_four_vector_xyzt (x, y, z, t) bind(C)
import
real(c_double), value :: x, y, z, t
end function new_four_vector_xyzt
end interface
@ %def new_four_vector_xyz new_four_vector_xyzt
<<HepMC interface: public>>=
public :: hepmc_four_vector_init
<<HepMC interface: interfaces>>=
interface hepmc_four_vector_init
module procedure hepmc_four_vector_init_v4
module procedure hepmc_four_vector_init_v3
module procedure hepmc_four_vector_init_hepmc_prt
end interface
<<HepMC interface: procedures>>=
subroutine hepmc_four_vector_init_v4 (pp, p)
type(hepmc_four_vector_t), intent(out) :: pp
type(vector4_t), intent(in) :: p
real(default), dimension(0:3) :: pa
pa = vector4_get_components (p)
pp%obj = new_four_vector_xyzt &
(real (pa(1), c_double), &
real (pa(2), c_double), &
real (pa(3), c_double), &
real (pa(0), c_double))
end subroutine hepmc_four_vector_init_v4
subroutine hepmc_four_vector_init_v3 (pp, p)
type(hepmc_four_vector_t), intent(out) :: pp
type(vector3_t), intent(in) :: p
real(default), dimension(3) :: pa
pa = vector3_get_components (p)
pp%obj = new_four_vector_xyz &
(real (pa(1), c_double), &
real (pa(2), c_double), &
real (pa(3), c_double))
end subroutine hepmc_four_vector_init_v3
subroutine hepmc_four_vector_init_hepmc_prt (pp, prt)
type(hepmc_four_vector_t), intent(out) :: pp
type(hepmc_particle_t), intent(in) :: prt
pp%obj = gen_particle_momentum (prt%obj)
end subroutine hepmc_four_vector_init_hepmc_prt
@ %def hepmc_four_vector_init
@ Here, the destructor is explicitly needed.
<<HepMC interface: interfaces>>=
interface
subroutine four_vector_delete (p_obj) bind(C)
import
type(c_ptr), value :: p_obj
end subroutine four_vector_delete
end interface
@ %def four_vector_delete
<<HepMC interface: public>>=
public :: hepmc_four_vector_final
<<HepMC interface: procedures>>=
subroutine hepmc_four_vector_final (p)
type(hepmc_four_vector_t), intent(inout) :: p
call four_vector_delete (p%obj)
end subroutine hepmc_four_vector_final
@ %def hepmc_four_vector_final
@ Convert to a Lorentz vector.
<<HepMC interface: interfaces>>=
interface
function four_vector_px (p_obj) result (px) bind(C)
import
real(c_double) :: px
type(c_ptr), value :: p_obj
end function four_vector_px
end interface
interface
function four_vector_py (p_obj) result (py) bind(C)
import
real(c_double) :: py
type(c_ptr), value :: p_obj
end function four_vector_py
end interface
interface
function four_vector_pz (p_obj) result (pz) bind(C)
import
real(c_double) :: pz
type(c_ptr), value :: p_obj
end function four_vector_pz
end interface
interface
function four_vector_e (p_obj) result (e) bind(C)
import
real(c_double) :: e
type(c_ptr), value :: p_obj
end function four_vector_e
end interface
@ %def four_vector_px four_vector_py four_vector_pz four_vector_e
<<HepMC interface: public>>=
public :: hepmc_four_vector_to_vector4
<<HepMC interface: procedures>>=
subroutine hepmc_four_vector_to_vector4 (pp, p)
type(hepmc_four_vector_t), intent(in) :: pp
type(vector4_t), intent(out) :: p
real(default) :: E
real(default), dimension(3) :: p3
E = four_vector_e (pp%obj)
p3(1) = four_vector_px (pp%obj)
p3(2) = four_vector_py (pp%obj)
p3(3) = four_vector_pz (pp%obj)
p = vector4_moving (E, vector3_moving (p3))
end subroutine hepmc_four_vector_to_vector4
@ %def hepmc_four_vector_to_vector4
@
\subsection{Polarization}
Polarization objects are temporarily used for assigning particle
polarization. We add a flag [[polarized]]. If this is false, the
polarization is not set and should not be transferred to
[[hepmc_particle]] objects.
<<HepMC interface: public>>=
public :: hepmc_polarization_t
<<HepMC interface: types>>=
type :: hepmc_polarization_t
private
logical :: polarized = .false.
type(c_ptr) :: obj
end type hepmc_polarization_t
@ %def hepmc_polarization_t
@ Constructor. The C wrapper takes polar and azimuthal angle as
arguments. The Fortran version allows for either a complete
polarization density matrix, or for a definite (diagonal) helicity.
\emph{HepMC does not allow to specify the degree of polarization,
therefore we have to map it to either 0 or 1. We choose 0 for
polarization less than $0.5$ and 1 for polarization greater than
$0.5$. Even this simplification works only for spin-1/2 and for
massless particles; massive vector bosons cannot be treated this
way. In particular, zero helicity is always translated as
unpolarized.}
\emph{For massive vector bosons, we arbitrarily choose the convention
that the longitudinal (zero) helicity state is mapped to the theta
angle $\pi/2$. This works under the condition that helicity is
projected onto one of the basis states.}
<<HepMC interface: interfaces>>=
interface
type(c_ptr) function new_polarization (theta, phi) bind(C)
import
real(c_double), value :: theta, phi
end function new_polarization
end interface
@ %def new_polarization
<<HepMC interface: public>>=
public :: hepmc_polarization_init
<<HepMC interface: interfaces>>=
interface hepmc_polarization_init
module procedure hepmc_polarization_init_pol
module procedure hepmc_polarization_init_hel
module procedure hepmc_polarization_init_int
end interface
<<HepMC interface: procedures>>=
subroutine hepmc_polarization_init_pol (hpol, pol)
type(hepmc_polarization_t), intent(out) :: hpol
type(polarization_t), intent(in) :: pol
real(default) :: r, theta, phi
if (pol%is_polarized ()) then
call pol%to_angles (r, theta, phi)
if (r >= 0.5) then
hpol%polarized = .true.
hpol%obj = new_polarization &
(real (theta, c_double), real (phi, c_double))
end if
end if
end subroutine hepmc_polarization_init_pol
subroutine hepmc_polarization_init_hel (hpol, hel)
type(hepmc_polarization_t), intent(out) :: hpol
type(helicity_t), intent(in) :: hel
integer, dimension(2) :: h
if (hel%is_defined ()) then
h = hel%to_pair ()
select case (h(1))
case (1:)
hpol%polarized = .true.
hpol%obj = new_polarization (0._c_double, 0._c_double)
case (:-1)
hpol%polarized = .true.
hpol%obj = new_polarization (real (pi, c_double), 0._c_double)
case (0)
hpol%polarized = .true.
hpol%obj = new_polarization (real (pi/2, c_double), 0._c_double)
end select
end if
end subroutine hepmc_polarization_init_hel
subroutine hepmc_polarization_init_int (hpol, hel)
type(hepmc_polarization_t), intent(out) :: hpol
integer, intent(in) :: hel
select case (hel)
case (1:)
hpol%polarized = .true.
hpol%obj = new_polarization (0._c_double, 0._c_double)
case (:-1)
hpol%polarized = .true.
hpol%obj = new_polarization (real (pi, c_double), 0._c_double)
case (0)
hpol%polarized = .true.
hpol%obj = new_polarization (real (pi/2, c_double), 0._c_double)
end select
end subroutine hepmc_polarization_init_int
@ %def hepmc_polarization_init
@ Destructor. The C object is deallocated only if the [[polarized]]
flag is set.
<<HepMC interface: interfaces>>=
interface
subroutine polarization_delete (pol_obj) bind(C)
import
type(c_ptr), value :: pol_obj
end subroutine polarization_delete
end interface
@ %def polarization_delete
<<HepMC interface: public>>=
public :: hepmc_polarization_final
<<HepMC interface: procedures>>=
subroutine hepmc_polarization_final (hpol)
type(hepmc_polarization_t), intent(inout) :: hpol
if (hpol%polarized) call polarization_delete (hpol%obj)
end subroutine hepmc_polarization_final
@ %def hepmc_polarization_final
@ Recover polarization from HepMC polarization object (with the
abovementioned deficiencies).
<<HepMC interface: interfaces>>=
interface
function polarization_theta (pol_obj) result (theta) bind(C)
import
real(c_double) :: theta
type(c_ptr), value :: pol_obj
end function polarization_theta
end interface
interface
function polarization_phi (pol_obj) result (phi) bind(C)
import
real(c_double) :: phi
type(c_ptr), value :: pol_obj
end function polarization_phi
end interface
@ %def polarization_theta polarization_phi
<<HepMC interface: public>>=
public :: hepmc_polarization_to_pol
<<HepMC interface: procedures>>=
subroutine hepmc_polarization_to_pol (hpol, flv, pol)
type(hepmc_polarization_t), intent(in) :: hpol
type(flavor_t), intent(in) :: flv
type(polarization_t), intent(out) :: pol
real(default) :: theta, phi
theta = polarization_theta (hpol%obj)
phi = polarization_phi (hpol%obj)
call pol%init_angles (flv, 1._default, theta, phi)
end subroutine hepmc_polarization_to_pol
@ %def hepmc_polarization_to_pol
@ Recover helicity. Here, $\phi$ is ignored and only the sign of
$\cos\theta$ is relevant, mapped to positive/negative helicity.
<<HepMC interface: public>>=
public :: hepmc_polarization_to_hel
<<HepMC interface: procedures>>=
subroutine hepmc_polarization_to_hel (hpol, flv, hel)
type(hepmc_polarization_t), intent(in) :: hpol
type(flavor_t), intent(in) :: flv
type(helicity_t), intent(out) :: hel
real(default) :: theta
integer :: hmax
theta = polarization_theta (hpol%obj)
hmax = flv%get_spin_type () / 2
call hel%init (sign (hmax, nint (cos (theta))))
end subroutine hepmc_polarization_to_hel
@ %def hepmc_polarization_to_hel
@
\subsection{GenParticle}
Particle objects have the obvious meaning.
<<HepMC interface: public>>=
public :: hepmc_particle_t
<<HepMC interface: types>>=
type :: hepmc_particle_t
private
type(c_ptr) :: obj
end type hepmc_particle_t
@ %def hepmc_particle_t
@ Constructor. The C version takes a FourVector object, which in the
Fortran wrapper is created on the fly from a [[vector4]] Lorentz
vector.
No destructor is needed as long as all particles are entered into
vertex containers.
<<HepMC interface: interfaces>>=
interface
type(c_ptr) function new_gen_particle (prt_obj, pdg_id, status) bind(C)
import
type(c_ptr), value :: prt_obj
integer(c_int), value :: pdg_id, status
end function new_gen_particle
end interface
@ %def new_gen_particle
<<HepMC interface: public>>=
public :: hepmc_particle_init
<<HepMC interface: procedures>>=
subroutine hepmc_particle_init (prt, p, pdg, status)
type(hepmc_particle_t), intent(out) :: prt
type(vector4_t), intent(in) :: p
integer, intent(in) :: pdg, status
type(hepmc_four_vector_t) :: pp
call hepmc_four_vector_init (pp, p)
prt%obj = new_gen_particle (pp%obj, int (pdg, c_int), int (status, c_int))
call hepmc_four_vector_final (pp)
end subroutine hepmc_particle_init
@ %def hepmc_particle_init
@ Set the particle color flow.
<<HepMC interface: interfaces>>=
interface
subroutine gen_particle_set_flow (prt_obj, code_index, code) bind(C)
import
type(c_ptr), value :: prt_obj
integer(c_int), value :: code_index, code
end subroutine gen_particle_set_flow
end interface
@ %def gen_particle_set_flow
@ Set the particle color. Either from a [[color_t]] object or
directly from a pair of integers.
<<HepMC interface: interfaces>>=
interface hepmc_particle_set_color
module procedure hepmc_particle_set_color_col
module procedure hepmc_particle_set_color_int
end interface hepmc_particle_set_color
<<HepMC interface: public>>=
public :: hepmc_particle_set_color
<<HepMC interface: procedures>>=
subroutine hepmc_particle_set_color_col (prt, col)
type(hepmc_particle_t), intent(inout) :: prt
type(color_t), intent(in) :: col
integer(c_int) :: c
c = col%get_col ()
if (c /= 0) call gen_particle_set_flow (prt%obj, 1_c_int, c)
c = col%get_acl ()
if (c /= 0) call gen_particle_set_flow (prt%obj, 2_c_int, c)
end subroutine hepmc_particle_set_color_col
subroutine hepmc_particle_set_color_int (prt, col)
type(hepmc_particle_t), intent(inout) :: prt
integer, dimension(2), intent(in) :: col
integer(c_int) :: c
c = col(1)
if (c /= 0) call gen_particle_set_flow (prt%obj, 1_c_int, c)
c = col(2)
if (c /= 0) call gen_particle_set_flow (prt%obj, 2_c_int, c)
end subroutine hepmc_particle_set_color_int
@ %def hepmc_particle_set_color
@ Set the particle polarization. For the restrictions on particle
polarization in HepMC, see above [[hepmc_polarization_init]].
<<HepMC interface: interfaces>>=
interface
subroutine gen_particle_set_polarization (prt_obj, pol_obj) bind(C)
import
type(c_ptr), value :: prt_obj, pol_obj
end subroutine gen_particle_set_polarization
end interface
@ %def gen_particle_set_polarization
<<HepMC interface: public>>=
public :: hepmc_particle_set_polarization
<<HepMC interface: interfaces>>=
interface hepmc_particle_set_polarization
module procedure hepmc_particle_set_polarization_pol
module procedure hepmc_particle_set_polarization_hel
module procedure hepmc_particle_set_polarization_int
end interface
<<HepMC interface: procedures>>=
subroutine hepmc_particle_set_polarization_pol (prt, pol)
type(hepmc_particle_t), intent(inout) :: prt
type(polarization_t), intent(in) :: pol
type(hepmc_polarization_t) :: hpol
call hepmc_polarization_init (hpol, pol)
if (hpol%polarized) call gen_particle_set_polarization (prt%obj, hpol%obj)
call hepmc_polarization_final (hpol)
end subroutine hepmc_particle_set_polarization_pol
subroutine hepmc_particle_set_polarization_hel (prt, hel)
type(hepmc_particle_t), intent(inout) :: prt
type(helicity_t), intent(in) :: hel
type(hepmc_polarization_t) :: hpol
call hepmc_polarization_init (hpol, hel)
if (hpol%polarized) call gen_particle_set_polarization (prt%obj, hpol%obj)
call hepmc_polarization_final (hpol)
end subroutine hepmc_particle_set_polarization_hel
subroutine hepmc_particle_set_polarization_int (prt, hel)
type(hepmc_particle_t), intent(inout) :: prt
integer, intent(in) :: hel
type(hepmc_polarization_t) :: hpol
call hepmc_polarization_init (hpol, hel)
if (hpol%polarized) call gen_particle_set_polarization (prt%obj, hpol%obj)
call hepmc_polarization_final (hpol)
end subroutine hepmc_particle_set_polarization_int
@ %def hepmc_particle_set_polarization
@ Return the HepMC barcode (unique integer ID) of the particle.
<<HepMC interface: interfaces>>=
interface
function gen_particle_barcode (prt_obj) result (barcode) bind(C)
import
integer(c_int) :: barcode
type(c_ptr), value :: prt_obj
end function gen_particle_barcode
end interface
@ %def gen_particle_barcode
<<HepMC interface: public>>=
public :: hepmc_particle_get_barcode
<<HepMC interface: procedures>>=
function hepmc_particle_get_barcode (prt) result (barcode)
integer :: barcode
type(hepmc_particle_t), intent(in) :: prt
barcode = gen_particle_barcode (prt%obj)
end function hepmc_particle_get_barcode
@ %def hepmc_particle_get_barcode
@ Return the four-vector component of the particle object as a [[vector4_t]] Lorentz vector.
<<HepMC interface: interfaces>>=
interface
type(c_ptr) function gen_particle_momentum (prt_obj) bind(C)
import
type(c_ptr), value :: prt_obj
end function gen_particle_momentum
end interface
@ %def gen_particle_momentum
<<HepMC interface: public>>=
public :: hepmc_particle_get_momentum
<<HepMC interface: procedures>>=
function hepmc_particle_get_momentum (prt) result (p)
type(vector4_t) :: p
type(hepmc_particle_t), intent(in) :: prt
type(hepmc_four_vector_t) :: pp
call hepmc_four_vector_init (pp, prt)
call hepmc_four_vector_to_vector4 (pp, p)
call hepmc_four_vector_final (pp)
end function hepmc_particle_get_momentum
@ %def hepmc_particle_get_momentum
@ Return the invariant mass squared of the particle object. HepMC
stores the signed invariant mass (no squaring).
<<HepMC interface: interfaces>>=
interface
function gen_particle_generated_mass (prt_obj) result (mass) bind(C)
import
real(c_double) :: mass
type(c_ptr), value :: prt_obj
end function gen_particle_generated_mass
end interface
@ %def gen_particle_generated_mass
<<HepMC interface: public>>=
public :: hepmc_particle_get_mass_squared
<<HepMC interface: procedures>>=
function hepmc_particle_get_mass_squared (prt) result (m2)
real(default) :: m2
type(hepmc_particle_t), intent(in) :: prt
real(default) :: m
m = gen_particle_generated_mass (prt%obj)
m2 = sign (m**2, m)
end function hepmc_particle_get_mass_squared
@ %def hepmc_particle_get_mass_squared
@ Return the PDG ID:
<<HepMC interface: interfaces>>=
interface
function gen_particle_pdg_id (prt_obj) result (pdg_id) bind(C)
import
integer(c_int) :: pdg_id
type(c_ptr), value :: prt_obj
end function gen_particle_pdg_id
end interface
@ %def gen_particle_pdg_id
<<HepMC interface: public>>=
public :: hepmc_particle_get_pdg
<<HepMC interface: procedures>>=
function hepmc_particle_get_pdg (prt) result (pdg)
integer :: pdg
type(hepmc_particle_t), intent(in) :: prt
pdg = gen_particle_pdg_id (prt%obj)
end function hepmc_particle_get_pdg
@ %def hepmc_particle_get_pdg
@ Return the status code:
<<HepMC interface: interfaces>>=
interface
function gen_particle_status (prt_obj) result (status) bind(C)
import
integer(c_int) :: status
type(c_ptr), value :: prt_obj
end function gen_particle_status
end interface
@ %def gen_particle_status
<<HepMC interface: public>>=
public :: hepmc_particle_get_status
<<HepMC interface: procedures>>=
function hepmc_particle_get_status (prt) result (status)
integer :: status
type(hepmc_particle_t), intent(in) :: prt
status = gen_particle_status (prt%obj)
end function hepmc_particle_get_status
@ %def hepmc_particle_get_status
<<HepMC interface: interfaces>>=
interface
function gen_particle_is_beam (prt_obj) result (is_beam) bind(C)
import
logical(c_bool) :: is_beam
type(c_ptr), value :: prt_obj
end function gen_particle_is_beam
end interface
@ %def gen_particle_is_beam
@ Determine whether a particle is a beam particle.
<<HepMC interface: public>>=
public :: hepmc_particle_is_beam
<<HepMC interface: procedures>>=
function hepmc_particle_is_beam (prt) result (is_beam)
logical :: is_beam
type(hepmc_particle_t), intent(in) :: prt
is_beam = gen_particle_is_beam (prt%obj)
end function hepmc_particle_is_beam
@ %def hepmc_particle_is_beam
@ Return the production/decay vertex (as a pointer, no finalization
necessary).
<<HepMC interface: interfaces>>=
interface
type(c_ptr) function gen_particle_production_vertex (prt_obj) bind(C)
import
type(c_ptr), value :: prt_obj
end function gen_particle_production_vertex
end interface
interface
type(c_ptr) function gen_particle_end_vertex (prt_obj) bind(C)
import
type(c_ptr), value :: prt_obj
end function gen_particle_end_vertex
end interface
@ %def gen_particle_production_vertex gen_particle_end_vertex
<<HepMC interface: public>>=
public :: hepmc_particle_get_production_vertex
public :: hepmc_particle_get_decay_vertex
<<HepMC interface: procedures>>=
function hepmc_particle_get_production_vertex (prt) result (v)
type(hepmc_vertex_t) :: v
type(hepmc_particle_t), intent(in) :: prt
v%obj = gen_particle_production_vertex (prt%obj)
end function hepmc_particle_get_production_vertex
function hepmc_particle_get_decay_vertex (prt) result (v)
type(hepmc_vertex_t) :: v
type(hepmc_particle_t), intent(in) :: prt
v%obj = gen_particle_end_vertex (prt%obj)
end function hepmc_particle_get_decay_vertex
@ %def hepmc_particle_get_production_vertex hepmc_particle_get_decay_vertex
@ Return the number of parents/children.
<<HepMC interface: public>>=
public :: hepmc_particle_get_n_parents
public :: hepmc_particle_get_n_children
<<HepMC interface: procedures>>=
function hepmc_particle_get_n_parents (prt) result (n_parents)
integer :: n_parents
type(hepmc_particle_t), intent(in) :: prt
type(hepmc_vertex_t) :: v
v = hepmc_particle_get_production_vertex (prt)
if (hepmc_vertex_is_valid (v)) then
n_parents = hepmc_vertex_get_n_in (v)
else
n_parents = 0
end if
end function hepmc_particle_get_n_parents
function hepmc_particle_get_n_children (prt) result (n_children)
integer :: n_children
type(hepmc_particle_t), intent(in) :: prt
type(hepmc_vertex_t) :: v
v = hepmc_particle_get_decay_vertex (prt)
if (hepmc_vertex_is_valid (v)) then
n_children = hepmc_vertex_get_n_out (v)
else
n_children = 0
end if
end function hepmc_particle_get_n_children
@ %def hepmc_particle_get_n_parents
@ %def hepmc_particle_get_n_children
@ Convenience function: Return the array of parent particles for a
given HepMC particle. The contents are HepMC barcodes that still have
to be mapped to the particle indices.
<<HepMC interface: public>>=
public :: hepmc_particle_get_parent_barcodes
public :: hepmc_particle_get_child_barcodes
<<HepMC interface: procedures>>=
function hepmc_particle_get_parent_barcodes (prt) result (parent_barcode)
type(hepmc_particle_t), intent(in) :: prt
integer, dimension(:), allocatable :: parent_barcode
type(hepmc_vertex_t) :: v
type(hepmc_vertex_particle_in_iterator_t) :: it
integer :: i
v = hepmc_particle_get_production_vertex (prt)
if (hepmc_vertex_is_valid (v)) then
allocate (parent_barcode (hepmc_vertex_get_n_in (v)))
if (size (parent_barcode) /= 0) then
call hepmc_vertex_particle_in_iterator_init (it, v)
do i = 1, size (parent_barcode)
parent_barcode(i) = hepmc_particle_get_barcode &
(hepmc_vertex_particle_in_iterator_get (it))
call hepmc_vertex_particle_in_iterator_advance (it)
end do
call hepmc_vertex_particle_in_iterator_final (it)
end if
else
allocate (parent_barcode (0))
end if
end function hepmc_particle_get_parent_barcodes
function hepmc_particle_get_child_barcodes (prt) result (child_barcode)
type(hepmc_particle_t), intent(in) :: prt
integer, dimension(:), allocatable :: child_barcode
type(hepmc_vertex_t) :: v
type(hepmc_vertex_particle_out_iterator_t) :: it
integer :: i
v = hepmc_particle_get_decay_vertex (prt)
if (hepmc_vertex_is_valid (v)) then
allocate (child_barcode (hepmc_vertex_get_n_out (v)))
call hepmc_vertex_particle_out_iterator_init (it, v)
if (size (child_barcode) /= 0) then
do i = 1, size (child_barcode)
child_barcode(i) = hepmc_particle_get_barcode &
(hepmc_vertex_particle_out_iterator_get (it))
call hepmc_vertex_particle_out_iterator_advance (it)
end do
call hepmc_vertex_particle_out_iterator_final (it)
end if
else
allocate (child_barcode (0))
end if
end function hepmc_particle_get_child_barcodes
@ %def hepmc_particle_get_parent_barcodes hepmc_particle_get_child_barcodes
@ Return the polarization (assuming that the particle is completely
polarized). Note that the generated polarization object needs finalization.
<<HepMC interface: interfaces>>=
interface
type(c_ptr) function gen_particle_polarization (prt_obj) bind(C)
import
type(c_ptr), value :: prt_obj
end function gen_particle_polarization
end interface
@ %def gen_particle_polarization
<<HepMC interface: public>>=
public :: hepmc_particle_get_polarization
<<HepMC interface: procedures>>=
function hepmc_particle_get_polarization (prt) result (pol)
type(hepmc_polarization_t) :: pol
type(hepmc_particle_t), intent(in) :: prt
pol%obj = gen_particle_polarization (prt%obj)
end function hepmc_particle_get_polarization
@ %def hepmc_particle_get_polarization
@ Return the particle color as a two-dimensional array (color, anticolor).
<<HepMC interface: interfaces>>=
interface
function gen_particle_flow (prt_obj, code_index) result (code) bind(C)
import
integer(c_int) :: code
type(c_ptr), value :: prt_obj
integer(c_int), value :: code_index
end function gen_particle_flow
end interface
@ %def gen_particle_flow
<<HepMC interface: public>>=
public :: hepmc_particle_get_color
<<HepMC interface: procedures>>=
function hepmc_particle_get_color (prt) result (col)
integer, dimension(2) :: col
type(hepmc_particle_t), intent(in) :: prt
col(1) = gen_particle_flow (prt%obj, 1)
col(2) = - gen_particle_flow (prt%obj, 2)
end function hepmc_particle_get_color
@ %def hepmc_particle_get_color
@
<<HepMC interface: interfaces>>=
interface
function gen_vertex_pos_x (v_obj) result (x) bind(C)
import
type(c_ptr), value :: v_obj
real(c_double) :: x
end function gen_vertex_pos_x
end interface
interface
function gen_vertex_pos_y (v_obj) result (y) bind(C)
import
type(c_ptr), value :: v_obj
real(c_double) :: y
end function gen_vertex_pos_y
end interface
interface
function gen_vertex_pos_z (v_obj) result (z) bind(C)
import
type(c_ptr), value :: v_obj
real(c_double) :: z
end function gen_vertex_pos_z
end interface
interface
function gen_vertex_time (v_obj) result (t) bind(C)
import
type(c_ptr), value :: v_obj
real(c_double) :: t
end function gen_vertex_time
end interface
@
<<HepMC interface: public>>=
public :: hepmc_vertex_to_vertex
<<HepMC interface: procedures>>=
function hepmc_vertex_to_vertex (vtx) result (v)
type(hepmc_vertex_t), intent(in) :: vtx
type(vector4_t) :: v
real(default) :: t, vx, vy, vz
if (hepmc_vertex_is_valid (vtx)) then
t = gen_vertex_time (vtx%obj)
vx = gen_vertex_pos_x (vtx%obj)
vy = gen_vertex_pos_y (vtx%obj)
vz = gen_vertex_pos_z (vtx%obj)
v = vector4_moving (t, &
vector3_moving ([vx, vy, vz]))
end if
end function hepmc_vertex_to_vertex
@ %def hepmc_vertex_to_vertex
@
\subsection{GenVertex}
Vertices are made of particles (incoming and outgoing).
<<HepMC interface: public>>=
public :: hepmc_vertex_t
<<HepMC interface: types>>=
type :: hepmc_vertex_t
private
type(c_ptr) :: obj
end type hepmc_vertex_t
@ %def hepmc_vertex_t
@ Constructor. Two versions, one plain, one with the position in
space and time (measured in mm) as argument. The Fortran version has
initializer form, and the vertex position is an optional argument.
A destructor is unnecessary as long as all vertices are entered into
an event container.
<<HepMC interface: interfaces>>=
interface
type(c_ptr) function new_gen_vertex () bind(C)
import
end function new_gen_vertex
end interface
interface
type(c_ptr) function new_gen_vertex_pos (prt_obj) bind(C)
import
type(c_ptr), value :: prt_obj
end function new_gen_vertex_pos
end interface
@ %def new_gen_vertex new_gen_vertex_pos
<<HepMC interface: public>>=
public :: hepmc_vertex_init
<<HepMC interface: procedures>>=
subroutine hepmc_vertex_init (v, x)
type(hepmc_vertex_t), intent(out) :: v
type(vector4_t), intent(in), optional :: x
type(hepmc_four_vector_t) :: pos
if (present (x)) then
call hepmc_four_vector_init (pos, x)
v%obj = new_gen_vertex_pos (pos%obj)
call hepmc_four_vector_final (pos)
else
v%obj = new_gen_vertex ()
end if
end subroutine hepmc_vertex_init
@ %def hepmc_vertex_init
@ Return true if the vertex pointer is non-null:
<<HepMC interface: interfaces>>=
interface
function gen_vertex_is_valid (v_obj) result (flag) bind(C)
import
logical(c_bool) :: flag
type(c_ptr), value :: v_obj
end function gen_vertex_is_valid
end interface
@ %def gen_vertex_is_valid
<<HepMC interface: public>>=
public :: hepmc_vertex_is_valid
<<HepMC interface: procedures>>=
function hepmc_vertex_is_valid (v) result (flag)
logical :: flag
type(hepmc_vertex_t), intent(in) :: v
flag = gen_vertex_is_valid (v%obj)
end function hepmc_vertex_is_valid
@ %def hepmc_vertex_is_valid
@ Add a particle to a vertex, incoming or outgoing.
<<HepMC interface: interfaces>>=
interface
subroutine gen_vertex_add_particle_in (v_obj, prt_obj) bind(C)
import
type(c_ptr), value :: v_obj, prt_obj
end subroutine gen_vertex_add_particle_in
end interface
interface
subroutine gen_vertex_add_particle_out (v_obj, prt_obj) bind(C)
import
type(c_ptr), value :: v_obj, prt_obj
end subroutine gen_vertex_add_particle_out
end interface
<<HepMC interface: public>>=
public :: hepmc_vertex_add_particle_in
public :: hepmc_vertex_add_particle_out
@ %def gen_vertex_add_particle_in gen_vertex_add_particle_out
<<HepMC interface: procedures>>=
subroutine hepmc_vertex_add_particle_in (v, prt)
type(hepmc_vertex_t), intent(inout) :: v
type(hepmc_particle_t), intent(in) :: prt
call gen_vertex_add_particle_in (v%obj, prt%obj)
end subroutine hepmc_vertex_add_particle_in
subroutine hepmc_vertex_add_particle_out (v, prt)
type(hepmc_vertex_t), intent(inout) :: v
type(hepmc_particle_t), intent(in) :: prt
call gen_vertex_add_particle_out (v%obj, prt%obj)
end subroutine hepmc_vertex_add_particle_out
@ %def hepmc_vertex_add_particle_in hepmc_vertex_add_particle_out
@ Return the number of incoming/outgoing particles.
<<HepMC interface: interfaces>>=
interface
function gen_vertex_particles_in_size (v_obj) result (size) bind(C)
import
integer(c_int) :: size
type(c_ptr), value :: v_obj
end function gen_vertex_particles_in_size
end interface
interface
function gen_vertex_particles_out_size (v_obj) result (size) bind(C)
import
integer(c_int) :: size
type(c_ptr), value :: v_obj
end function gen_vertex_particles_out_size
end interface
@ %def gen_vertex_particles_in_size gen_vertex_particles_out_size
<<HepMC interface: public>>=
public :: hepmc_vertex_get_n_in
public :: hepmc_vertex_get_n_out
<<HepMC interface: procedures>>=
function hepmc_vertex_get_n_in (v) result (n_in)
integer :: n_in
type(hepmc_vertex_t), intent(in) :: v
n_in = gen_vertex_particles_in_size (v%obj)
end function hepmc_vertex_get_n_in
function hepmc_vertex_get_n_out (v) result (n_out)
integer :: n_out
type(hepmc_vertex_t), intent(in) :: v
n_out = gen_vertex_particles_out_size (v%obj)
end function hepmc_vertex_get_n_out
@ %def hepmc_vertex_n_in hepmc_vertex_n_out
@
\subsection{Vertex-particle-in iterator}
This iterator iterates over all incoming particles in an vertex. We store a
pointer to the vertex in addition to the iterator. This allows for
simple end checking.
The iterator is actually a constant iterator; it can only read.
<<HepMC interface: public>>=
public :: hepmc_vertex_particle_in_iterator_t
<<HepMC interface: types>>=
type :: hepmc_vertex_particle_in_iterator_t
private
type(c_ptr) :: obj
type(c_ptr) :: v_obj
end type hepmc_vertex_particle_in_iterator_t
@ %def hepmc_vertex_particle_in_iterator_t
@ Constructor. The iterator is initialized at the first particle in
the vertex.
<<HepMC interface: interfaces>>=
interface
type(c_ptr) function &
new_vertex_particles_in_const_iterator (v_obj) bind(C)
import
type(c_ptr), value :: v_obj
end function new_vertex_particles_in_const_iterator
end interface
@ %def new_vertex_particles_in_const_iterator
<<HepMC interface: public>>=
public :: hepmc_vertex_particle_in_iterator_init
<<HepMC interface: procedures>>=
subroutine hepmc_vertex_particle_in_iterator_init (it, v)
type(hepmc_vertex_particle_in_iterator_t), intent(out) :: it
type(hepmc_vertex_t), intent(in) :: v
it%obj = new_vertex_particles_in_const_iterator (v%obj)
it%v_obj = v%obj
end subroutine hepmc_vertex_particle_in_iterator_init
@ %def hepmc_vertex_particle_in_iterator_init
@ Destructor. Necessary because the iterator is allocated on the
heap.
<<HepMC interface: interfaces>>=
interface
subroutine vertex_particles_in_const_iterator_delete (it_obj) bind(C)
import
type(c_ptr), value :: it_obj
end subroutine vertex_particles_in_const_iterator_delete
end interface
@ %def vertex_particles_in_const_iterator_delete
<<HepMC interface: public>>=
public :: hepmc_vertex_particle_in_iterator_final
<<HepMC interface: procedures>>=
subroutine hepmc_vertex_particle_in_iterator_final (it)
type(hepmc_vertex_particle_in_iterator_t), intent(inout) :: it
call vertex_particles_in_const_iterator_delete (it%obj)
end subroutine hepmc_vertex_particle_in_iterator_final
@ %def hepmc_vertex_particle_in_iterator_final
@ Increment
<<HepMC interface: interfaces>>=
interface
subroutine vertex_particles_in_const_iterator_advance (it_obj) bind(C)
import
type(c_ptr), value :: it_obj
end subroutine vertex_particles_in_const_iterator_advance
end interface
@ %def vertex_particles_in_const_iterator_advance
<<HepMC interface: public>>=
public :: hepmc_vertex_particle_in_iterator_advance
<<HepMC interface: procedures>>=
subroutine hepmc_vertex_particle_in_iterator_advance (it)
type(hepmc_vertex_particle_in_iterator_t), intent(inout) :: it
call vertex_particles_in_const_iterator_advance (it%obj)
end subroutine hepmc_vertex_particle_in_iterator_advance
@ %def hepmc_vertex_particle_in_iterator_advance
@ Reset to the beginning
<<HepMC interface: interfaces>>=
interface
subroutine vertex_particles_in_const_iterator_reset &
(it_obj, v_obj) bind(C)
import
type(c_ptr), value :: it_obj, v_obj
end subroutine vertex_particles_in_const_iterator_reset
end interface
@ %def vertex_particles_in_const_iterator_reset
<<HepMC interface: public>>=
public :: hepmc_vertex_particle_in_iterator_reset
<<HepMC interface: procedures>>=
subroutine hepmc_vertex_particle_in_iterator_reset (it)
type(hepmc_vertex_particle_in_iterator_t), intent(inout) :: it
call vertex_particles_in_const_iterator_reset (it%obj, it%v_obj)
end subroutine hepmc_vertex_particle_in_iterator_reset
@ %def hepmc_vertex_particle_in_iterator_reset
@ Test: return true as long as we are not past the end.
<<HepMC interface: interfaces>>=
interface
function vertex_particles_in_const_iterator_is_valid &
(it_obj, v_obj) result (flag) bind(C)
import
logical(c_bool) :: flag
type(c_ptr), value :: it_obj, v_obj
end function vertex_particles_in_const_iterator_is_valid
end interface
@ %def vertex_particles_in_const_iterator_is_valid
<<HepMC interface: public>>=
public :: hepmc_vertex_particle_in_iterator_is_valid
<<HepMC interface: procedures>>=
function hepmc_vertex_particle_in_iterator_is_valid (it) result (flag)
logical :: flag
type(hepmc_vertex_particle_in_iterator_t), intent(in) :: it
flag = vertex_particles_in_const_iterator_is_valid (it%obj, it%v_obj)
end function hepmc_vertex_particle_in_iterator_is_valid
@ %def hepmc_vertex_particle_in_iterator_is_valid
@ Return the particle pointed to by the iterator. (The particle
object should not be finalized, since it contains merely a pointer to
the particle which is owned by the vertex.)
<<HepMC interface: interfaces>>=
interface
type(c_ptr) function &
vertex_particles_in_const_iterator_get (it_obj) bind(C)
import
type(c_ptr), value :: it_obj
end function vertex_particles_in_const_iterator_get
end interface
@ %def vertex_particles_in_const_iterator_get
<<HepMC interface: public>>=
public :: hepmc_vertex_particle_in_iterator_get
<<HepMC interface: procedures>>=
function hepmc_vertex_particle_in_iterator_get (it) result (prt)
type(hepmc_particle_t) :: prt
type(hepmc_vertex_particle_in_iterator_t), intent(in) :: it
prt%obj = vertex_particles_in_const_iterator_get (it%obj)
end function hepmc_vertex_particle_in_iterator_get
@ %def hepmc_vertex_particle_in_iterator_get
@
\subsection{Vertex-particle-out iterator}
This iterator iterates over all incoming particles in an vertex. We store a
pointer to the vertex in addition to the iterator. This allows for
simple end checking.
The iterator is actually a constant iterator; it can only read.
<<HepMC interface: public>>=
public :: hepmc_vertex_particle_out_iterator_t
<<HepMC interface: types>>=
type :: hepmc_vertex_particle_out_iterator_t
private
type(c_ptr) :: obj
type(c_ptr) :: v_obj
end type hepmc_vertex_particle_out_iterator_t
@ %def hepmc_vertex_particle_out_iterator_t
@ Constructor. The iterator is initialized at the first particle in
the vertex.
<<HepMC interface: interfaces>>=
interface
type(c_ptr) function &
new_vertex_particles_out_const_iterator (v_obj) bind(C)
import
type(c_ptr), value :: v_obj
end function new_vertex_particles_out_const_iterator
end interface
@ %def new_vertex_particles_out_const_iterator
<<HepMC interface: public>>=
public :: hepmc_vertex_particle_out_iterator_init
<<HepMC interface: procedures>>=
subroutine hepmc_vertex_particle_out_iterator_init (it, v)
type(hepmc_vertex_particle_out_iterator_t), intent(out) :: it
type(hepmc_vertex_t), intent(in) :: v
it%obj = new_vertex_particles_out_const_iterator (v%obj)
it%v_obj = v%obj
end subroutine hepmc_vertex_particle_out_iterator_init
@ %def hepmc_vertex_particle_out_iterator_init
@ Destructor. Necessary because the iterator is allocated on the
heap.
<<HepMC interface: interfaces>>=
interface
subroutine vertex_particles_out_const_iterator_delete (it_obj) bind(C)
import
type(c_ptr), value :: it_obj
end subroutine vertex_particles_out_const_iterator_delete
end interface
@ %def vertex_particles_out_const_iterator_delete
<<HepMC interface: public>>=
public :: hepmc_vertex_particle_out_iterator_final
<<HepMC interface: procedures>>=
subroutine hepmc_vertex_particle_out_iterator_final (it)
type(hepmc_vertex_particle_out_iterator_t), intent(inout) :: it
call vertex_particles_out_const_iterator_delete (it%obj)
end subroutine hepmc_vertex_particle_out_iterator_final
@ %def hepmc_vertex_particle_out_iterator_final
@ Increment
<<HepMC interface: interfaces>>=
interface
subroutine vertex_particles_out_const_iterator_advance (it_obj) bind(C)
import
type(c_ptr), value :: it_obj
end subroutine vertex_particles_out_const_iterator_advance
end interface
@ %def vertex_particles_out_const_iterator_advance
<<HepMC interface: public>>=
public :: hepmc_vertex_particle_out_iterator_advance
<<HepMC interface: procedures>>=
subroutine hepmc_vertex_particle_out_iterator_advance (it)
type(hepmc_vertex_particle_out_iterator_t), intent(inout) :: it
call vertex_particles_out_const_iterator_advance (it%obj)
end subroutine hepmc_vertex_particle_out_iterator_advance
@ %def hepmc_vertex_particle_out_iterator_advance
@ Reset to the beginning
<<HepMC interface: interfaces>>=
interface
subroutine vertex_particles_out_const_iterator_reset &
(it_obj, v_obj) bind(C)
import
type(c_ptr), value :: it_obj, v_obj
end subroutine vertex_particles_out_const_iterator_reset
end interface
@ %def vertex_particles_out_const_iterator_reset
<<HepMC interface: public>>=
public :: hepmc_vertex_particle_out_iterator_reset
<<HepMC interface: procedures>>=
subroutine hepmc_vertex_particle_out_iterator_reset (it)
type(hepmc_vertex_particle_out_iterator_t), intent(inout) :: it
call vertex_particles_out_const_iterator_reset (it%obj, it%v_obj)
end subroutine hepmc_vertex_particle_out_iterator_reset
@ %def hepmc_vertex_particle_out_iterator_reset
@ Test: return true as long as we are not past the end.
<<HepMC interface: interfaces>>=
interface
function vertex_particles_out_const_iterator_is_valid &
(it_obj, v_obj) result (flag) bind(C)
import
logical(c_bool) :: flag
type(c_ptr), value :: it_obj, v_obj
end function vertex_particles_out_const_iterator_is_valid
end interface
@ %def vertex_particles_out_const_iterator_is_valid
<<HepMC interface: public>>=
public :: hepmc_vertex_particle_out_iterator_is_valid
<<HepMC interface: procedures>>=
function hepmc_vertex_particle_out_iterator_is_valid (it) result (flag)
logical :: flag
type(hepmc_vertex_particle_out_iterator_t), intent(in) :: it
flag = vertex_particles_out_const_iterator_is_valid (it%obj, it%v_obj)
end function hepmc_vertex_particle_out_iterator_is_valid
@ %def hepmc_vertex_particle_out_iterator_is_valid
@ Return the particle pointed to by the iterator. (The particle
object should not be finalized, since it contains merely a pointer to
the particle which is owned by the vertex.)
<<HepMC interface: interfaces>>=
interface
type(c_ptr) function &
vertex_particles_out_const_iterator_get (it_obj) bind(C)
import
type(c_ptr), value :: it_obj
end function vertex_particles_out_const_iterator_get
end interface
@ %def vertex_particles_out_const_iterator_get
<<HepMC interface: public>>=
public :: hepmc_vertex_particle_out_iterator_get
<<HepMC interface: procedures>>=
function hepmc_vertex_particle_out_iterator_get (it) result (prt)
type(hepmc_particle_t) :: prt
type(hepmc_vertex_particle_out_iterator_t), intent(in) :: it
prt%obj = vertex_particles_out_const_iterator_get (it%obj)
end function hepmc_vertex_particle_out_iterator_get
@ %def hepmc_vertex_particle_out_iterator_get
@
\subsection{GenEvent}
The main object of HepMC is a GenEvent. The object is filled by
GenVertex objects, which in turn contain GenParticle objects.
<<HepMC interface: public>>=
public :: hepmc_event_t
<<HepMC interface: types>>=
type :: hepmc_event_t
private
type(c_ptr) :: obj
end type hepmc_event_t
@ %def hepmc_event_t
@ Constructor. Arguments are process ID (integer) and event ID
(integer).
The Fortran version has initializer form.
<<HepMC interface: interfaces>>=
interface
type(c_ptr) function new_gen_event (proc_id, event_id) bind(C)
import
integer(c_int), value :: proc_id, event_id
end function new_gen_event
end interface
@ %def new_gen_event
<<HepMC interface: public>>=
public :: hepmc_event_init
<<HepMC interface: procedures>>=
subroutine hepmc_event_init (evt, proc_id, event_id)
type(hepmc_event_t), intent(out) :: evt
integer, intent(in), optional :: proc_id, event_id
integer(c_int) :: pid, eid
pid = 0; if (present (proc_id)) pid = proc_id
eid = 0; if (present (event_id)) eid = event_id
evt%obj = new_gen_event (pid, eid)
end subroutine hepmc_event_init
@ %def hepmc_event_init
@ Destructor.
<<HepMC interface: interfaces>>=
interface
subroutine gen_event_delete (evt_obj) bind(C)
import
type(c_ptr), value :: evt_obj
end subroutine gen_event_delete
end interface
@ %def gen_event_delete
<<HepMC interface: public>>=
public :: hepmc_event_final
<<HepMC interface: procedures>>=
subroutine hepmc_event_final (evt)
type(hepmc_event_t), intent(inout) :: evt
call gen_event_delete (evt%obj)
end subroutine hepmc_event_final
@ %def hepmc_event_final
@ Screen output. Printing to file is possible in principle (using a
C++ output channel), by allowing an argument. Printing to an open
Fortran unit is obviously not possible.
<<HepMC interface: interfaces>>=
interface
subroutine gen_event_print (evt_obj) bind(C)
import
type(c_ptr), value :: evt_obj
end subroutine gen_event_print
end interface
@ %def gen_event_print
<<HepMC interface: public>>=
public :: hepmc_event_print
<<HepMC interface: procedures>>=
subroutine hepmc_event_print (evt)
type(hepmc_event_t), intent(in) :: evt
call gen_event_print (evt%obj)
end subroutine hepmc_event_print
@ %def hepmc_event_print
@ Get the event number.
<<HepMC interface: interfaces>>=
interface
integer(c_int) function gen_event_event_number (evt_obj) bind(C)
use iso_c_binding !NODEP!
type(c_ptr), value :: evt_obj
end function gen_event_event_number
end interface
@ %def gen_event_event_number
<<HepMC interface: public>>=
public :: hepmc_event_get_event_index
<<HepMC interface: procedures>>=
function hepmc_event_get_event_index (evt) result (i_proc)
integer :: i_proc
type(hepmc_event_t), intent(in) :: evt
i_proc = gen_event_event_number (evt%obj)
end function hepmc_event_get_event_index
@ %def hepmc_event_get_event_index
@ Set the numeric signal process ID
<<HepMC interface: interfaces>>=
interface
subroutine gen_event_set_signal_process_id (evt_obj, proc_id) bind(C)
import
type(c_ptr), value :: evt_obj
integer(c_int), value :: proc_id
end subroutine gen_event_set_signal_process_id
end interface
@ %def gen_event_set_signal_process_id
<<HepMC interface: public>>=
public :: hepmc_event_set_process_id
<<HepMC interface: procedures>>=
subroutine hepmc_event_set_process_id (evt, proc)
type(hepmc_event_t), intent(in) :: evt
integer, intent(in) :: proc
integer(c_int) :: i_proc
i_proc = proc
call gen_event_set_signal_process_id (evt%obj, i_proc)
end subroutine hepmc_event_set_process_id
@ %def hepmc_event_set_process_id
@ Get the numeric signal process ID
<<HepMC interface: interfaces>>=
interface
integer(c_int) function gen_event_signal_process_id (evt_obj) bind(C)
import
type(c_ptr), value :: evt_obj
end function gen_event_signal_process_id
end interface
@ %def gen_event_signal_process_id
<<HepMC interface: public>>=
public :: hepmc_event_get_process_id
<<HepMC interface: procedures>>=
function hepmc_event_get_process_id (evt) result (i_proc)
integer :: i_proc
type(hepmc_event_t), intent(in) :: evt
i_proc = gen_event_signal_process_id (evt%obj)
end function hepmc_event_get_process_id
@ %def hepmc_event_get_process_id
@ Set the event energy scale
<<HepMC interface: interfaces>>=
interface
subroutine gen_event_set_event_scale (evt_obj, scale) bind(C)
import
type(c_ptr), value :: evt_obj
real(c_double), value :: scale
end subroutine gen_event_set_event_scale
end interface
@ %def gen_event_set_event_scale
<<HepMC interface: public>>=
public :: hepmc_event_set_scale
<<HepMC interface: procedures>>=
subroutine hepmc_event_set_scale (evt, scale)
type(hepmc_event_t), intent(in) :: evt
real(default), intent(in) :: scale
real(c_double) :: cscale
cscale = scale
call gen_event_set_event_scale (evt%obj, cscale)
end subroutine hepmc_event_set_scale
@ %def hepmc_event_set_scale
@ Get the event energy scale
<<HepMC interface: interfaces>>=
interface
real(c_double) function gen_event_event_scale (evt_obj) bind(C)
import
type(c_ptr), value :: evt_obj
end function gen_event_event_scale
end interface
@ %def gen_event_event_scale
<<HepMC interface: public>>=
public :: hepmc_event_get_scale
<<HepMC interface: procedures>>=
function hepmc_event_get_scale (evt) result (scale)
real(default) :: scale
type(hepmc_event_t), intent(in) :: evt
scale = gen_event_event_scale (evt%obj)
end function hepmc_event_get_scale
@ %def hepmc_event_set_scale
@ Set the value of $\alpha_{\rm QCD}$.
<<HepMC interface: interfaces>>=
interface
subroutine gen_event_set_alpha_qcd (evt_obj, a) bind(C)
import
type(c_ptr), value :: evt_obj
real(c_double), value :: a
end subroutine gen_event_set_alpha_qcd
end interface
@ %def gen_event_set_alpha_qcd
<<HepMC interface: public>>=
public :: hepmc_event_set_alpha_qcd
<<HepMC interface: procedures>>=
subroutine hepmc_event_set_alpha_qcd (evt, alpha)
type(hepmc_event_t), intent(in) :: evt
real(default), intent(in) :: alpha
real(c_double) :: a
a = alpha
call gen_event_set_alpha_qcd (evt%obj, a)
end subroutine hepmc_event_set_alpha_qcd
@ %def hepmc_event_set_alpha_qcd
@ Get the value of $\alpha_{\rm QCD}$.
<<HepMC interface: interfaces>>=
interface
real(c_double) function gen_event_alpha_qcd (evt_obj) bind(C)
import
type(c_ptr), value :: evt_obj
end function gen_event_alpha_qcd
end interface
@ %def gen_event_get_alpha_qcd
<<HepMC interface: public>>=
public :: hepmc_event_get_alpha_qcd
<<HepMC interface: procedures>>=
function hepmc_event_get_alpha_qcd (evt) result (alpha)
real(default) :: alpha
type(hepmc_event_t), intent(in) :: evt
alpha = gen_event_alpha_qcd (evt%obj)
end function hepmc_event_get_alpha_qcd
@ %def hepmc_event_get_alpha_qcd
@ Set the value of $\alpha_{\rm QED}$.
<<HepMC interface: interfaces>>=
interface
subroutine gen_event_set_alpha_qed (evt_obj, a) bind(C)
import
type(c_ptr), value :: evt_obj
real(c_double), value :: a
end subroutine gen_event_set_alpha_qed
end interface
@ %def gen_event_set_alpha_qed
<<HepMC interface: public>>=
public :: hepmc_event_set_alpha_qed
<<HepMC interface: procedures>>=
subroutine hepmc_event_set_alpha_qed (evt, alpha)
type(hepmc_event_t), intent(in) :: evt
real(default), intent(in) :: alpha
real(c_double) :: a
a = alpha
call gen_event_set_alpha_qed (evt%obj, a)
end subroutine hepmc_event_set_alpha_qed
@ %def hepmc_event_set_alpha_qed
@ Get the value of $\alpha_{\rm QED}$.
<<HepMC interface: interfaces>>=
interface
real(c_double) function gen_event_alpha_qed (evt_obj) bind(C)
import
type(c_ptr), value :: evt_obj
end function gen_event_alpha_qed
end interface
@ %def gen_event_get_alpha_qed
<<HepMC interface: public>>=
public :: hepmc_event_get_alpha_qed
<<HepMC interface: procedures>>=
function hepmc_event_get_alpha_qed (evt) result (alpha)
real(default) :: alpha
type(hepmc_event_t), intent(in) :: evt
alpha = gen_event_alpha_qed (evt%obj)
end function hepmc_event_get_alpha_qed
@ %def hepmc_event_get_alpha_qed
@ Clear a weight value to the end of the weight container.
<<HepMC interface: interfaces>>=
interface
subroutine gen_event_clear_weights (evt_obj) bind(C)
use iso_c_binding !NODEP!
type(c_ptr), value :: evt_obj
end subroutine gen_event_clear_weights
end interface
@ %def gen_event_set_alpha_qed
@ The HepMC weights are measured in pb.
<<HepMC interface: parameters>>=
real(default), parameter :: pb_per_fb = 1.e-3_default
@ %def pb_per_fb
@
<<HepMC interface: public>>=
public :: hepmc_event_clear_weights
<<HepMC interface: procedures>>=
subroutine hepmc_event_clear_weights (evt)
type(hepmc_event_t), intent(in) :: evt
call gen_event_clear_weights (evt%obj)
end subroutine hepmc_event_clear_weights
@ %def hepmc_event_clear_weights
@ Add a weight value to the end of the weight container.
<<HepMC interface: interfaces>>=
interface
subroutine gen_event_add_weight (evt_obj, w) bind(C)
use iso_c_binding !NODEP!
type(c_ptr), value :: evt_obj
real(c_double), value :: w
end subroutine gen_event_add_weight
end interface
@ %def gen_event_add_weight
@
<<HepMC interface: public>>=
public :: hepmc_event_add_weight
<<HepMC interface: procedures>>=
subroutine hepmc_event_add_weight (evt, weight)
type(hepmc_event_t), intent(in) :: evt
real(default), intent(in) :: weight
real(c_double) :: w
w = weight * pb_per_fb
call gen_event_add_weight (evt%obj, w)
end subroutine hepmc_event_add_weight
@ %def hepmc_event_add_weight
@ Get the size of the weight container (the number of valid elements).
<<HepMC interface: interfaces>>=
interface
integer(c_int) function gen_event_weights_size (evt_obj) bind(C)
use iso_c_binding !NODEP!
type(c_ptr), value :: evt_obj
end function gen_event_weights_size
end interface
@ %def gen_event_get_weight
<<HepMC interface: public>>=
public :: hepmc_event_get_weights_size
<<HepMC interface: procedures>>=
function hepmc_event_get_weights_size (evt) result (n)
integer :: n
type(hepmc_event_t), intent(in) :: evt
n = gen_event_weights_size (evt%obj)
end function hepmc_event_get_weights_size
@ %def hepmc_event_get_weights_size
@ Get the value of the weight with index [[i]]. (Count from 1, while C counts
from zero.)
<<HepMC interface: interfaces>>=
interface
real(c_double) function gen_event_weight (evt_obj, i) bind(C)
use iso_c_binding !NODEP!
type(c_ptr), value :: evt_obj
integer(c_int), value :: i
end function gen_event_weight
end interface
@ %def gen_event_get_weight
<<HepMC interface: public>>=
public :: hepmc_event_get_weight
<<HepMC interface: procedures>>=
function hepmc_event_get_weight (evt, index) result (weight)
real(default) :: weight
type(hepmc_event_t), intent(in) :: evt
integer, intent(in) :: index
integer(c_int) :: i
i = index - 1
weight = gen_event_weight (evt%obj, i) / pb_per_fb
end function hepmc_event_get_weight
@ %def hepmc_event_get_weight
@ Add a vertex to the event container.
<<HepMC interface: interfaces>>=
interface
subroutine gen_event_add_vertex (evt_obj, v_obj) bind(C)
import
type(c_ptr), value :: evt_obj
type(c_ptr), value :: v_obj
end subroutine gen_event_add_vertex
end interface
@ %def gen_event_add_vertex
<<HepMC interface: public>>=
public :: hepmc_event_add_vertex
<<HepMC interface: procedures>>=
subroutine hepmc_event_add_vertex (evt, v)
type(hepmc_event_t), intent(inout) :: evt
type(hepmc_vertex_t), intent(in) :: v
call gen_event_add_vertex (evt%obj, v%obj)
end subroutine hepmc_event_add_vertex
@ %def hepmc_event_add_vertex
@ Mark a particular vertex as the signal process (hard interaction).
<<HepMC interface: interfaces>>=
interface
subroutine gen_event_set_signal_process_vertex (evt_obj, v_obj) bind(C)
import
type(c_ptr), value :: evt_obj
type(c_ptr), value :: v_obj
end subroutine gen_event_set_signal_process_vertex
end interface
@ %def gen_event_set_signal_process_vertex
<<HepMC interface: public>>=
public :: hepmc_event_set_signal_process_vertex
<<HepMC interface: procedures>>=
subroutine hepmc_event_set_signal_process_vertex (evt, v)
type(hepmc_event_t), intent(inout) :: evt
type(hepmc_vertex_t), intent(in) :: v
call gen_event_set_signal_process_vertex (evt%obj, v%obj)
end subroutine hepmc_event_set_signal_process_vertex
@ %def hepmc_event_set_signal_process_vertex
@ Return the the signal process (hard interaction).
<<HepMC interface: interfaces>>=
interface
function gen_event_get_signal_process_vertex (evt_obj) &
result (v_obj) bind(C)
import
type(c_ptr), value :: evt_obj
type(c_ptr) :: v_obj
end function gen_event_get_signal_process_vertex
end interface
@ %def gen_event_get_signal_process_vertex
<<HepMC interface: public>>=
public :: hepmc_event_get_signal_process_vertex
<<HepMC interface: procedures>>=
function hepmc_event_get_signal_process_vertex (evt) result (v)
type(hepmc_event_t), intent(in) :: evt
type(hepmc_vertex_t) :: v
v%obj = gen_event_get_signal_process_vertex (evt%obj)
end function hepmc_event_get_signal_process_vertex
@ %def hepmc_event_get_signal_process_vertex
@ Set the beam particles explicitly.
<<HepMC interface: public>>=
public :: hepmc_event_set_beam_particles
<<HepMC interface: procedures>>=
subroutine hepmc_event_set_beam_particles (evt, prt1, prt2)
type(hepmc_event_t), intent(inout) :: evt
type(hepmc_particle_t), intent(in) :: prt1, prt2
logical(c_bool) :: flag
flag = gen_event_set_beam_particles (evt%obj, prt1%obj, prt2%obj)
end subroutine hepmc_event_set_beam_particles
@ %def hepmc_event_set_beam_particles
@ The C function returns a boolean which we do not use.
<<HepMC interface: interfaces>>=
interface
logical(c_bool) function gen_event_set_beam_particles &
(evt_obj, prt1_obj, prt2_obj) bind(C)
import
type(c_ptr), value :: evt_obj, prt1_obj, prt2_obj
end function gen_event_set_beam_particles
end interface
@ %def gen_event_set_beam_particles
@ Set the cross section and error explicitly. Note that HepMC uses
pb, while WHIZARD uses fb.
<<HepMC interface: public>>=
public :: hepmc_event_set_cross_section
<<HepMC interface: procedures>>=
subroutine hepmc_event_set_cross_section (evt, xsec, xsec_err)
type(hepmc_event_t), intent(inout) :: evt
real(default), intent(in) :: xsec, xsec_err
call gen_event_set_cross_section &
(evt%obj, &
real (xsec * 1e-3_default, c_double), &
real (xsec_err * 1e-3_default, c_double))
end subroutine hepmc_event_set_cross_section
@ %def hepmc_event_set_cross_section
@ The C function returns a boolean which we do not use.
<<HepMC interface: interfaces>>=
interface
subroutine gen_event_set_cross_section (evt_obj, xs, xs_err) bind(C)
import
type(c_ptr), value :: evt_obj
real(c_double), value :: xs, xs_err
end subroutine gen_event_set_cross_section
end interface
@ %def gen_event_set_cross_section
@
\subsection{Event-particle iterator}
This iterator iterates over all particles in an event. We store a
pointer to the event in addition to the iterator. This allows for
simple end checking.
The iterator is actually a constant iterator; it can only read.
<<HepMC interface: public>>=
public :: hepmc_event_particle_iterator_t
<<HepMC interface: types>>=
type :: hepmc_event_particle_iterator_t
private
type(c_ptr) :: obj
type(c_ptr) :: evt_obj
end type hepmc_event_particle_iterator_t
@ %def hepmc_event_particle_iterator_t
@ Constructor. The iterator is initialized at the first particle in
the event.
<<HepMC interface: interfaces>>=
interface
type(c_ptr) function new_event_particle_const_iterator (evt_obj) bind(C)
import
type(c_ptr), value :: evt_obj
end function new_event_particle_const_iterator
end interface
@ %def new_event_particle_const_iterator
<<HepMC interface: public>>=
public :: hepmc_event_particle_iterator_init
<<HepMC interface: procedures>>=
subroutine hepmc_event_particle_iterator_init (it, evt)
type(hepmc_event_particle_iterator_t), intent(out) :: it
type(hepmc_event_t), intent(in) :: evt
it%obj = new_event_particle_const_iterator (evt%obj)
it%evt_obj = evt%obj
end subroutine hepmc_event_particle_iterator_init
@ %def hepmc_event_particle_iterator_init
@ Destructor. Necessary because the iterator is allocated on the
heap.
<<HepMC interface: interfaces>>=
interface
subroutine event_particle_const_iterator_delete (it_obj) bind(C)
import
type(c_ptr), value :: it_obj
end subroutine event_particle_const_iterator_delete
end interface
@ %def event_particle_const_iterator_delete
<<HepMC interface: public>>=
public :: hepmc_event_particle_iterator_final
<<HepMC interface: procedures>>=
subroutine hepmc_event_particle_iterator_final (it)
type(hepmc_event_particle_iterator_t), intent(inout) :: it
call event_particle_const_iterator_delete (it%obj)
end subroutine hepmc_event_particle_iterator_final
@ %def hepmc_event_particle_iterator_final
@ Increment
<<HepMC interface: interfaces>>=
interface
subroutine event_particle_const_iterator_advance (it_obj) bind(C)
import
type(c_ptr), value :: it_obj
end subroutine event_particle_const_iterator_advance
end interface
@ %def event_particle_const_iterator_advance
<<HepMC interface: public>>=
public :: hepmc_event_particle_iterator_advance
<<HepMC interface: procedures>>=
subroutine hepmc_event_particle_iterator_advance (it)
type(hepmc_event_particle_iterator_t), intent(inout) :: it
call event_particle_const_iterator_advance (it%obj)
end subroutine hepmc_event_particle_iterator_advance
@ %def hepmc_event_particle_iterator_advance
@ Reset to the beginning
<<HepMC interface: interfaces>>=
interface
subroutine event_particle_const_iterator_reset (it_obj, evt_obj) bind(C)
import
type(c_ptr), value :: it_obj, evt_obj
end subroutine event_particle_const_iterator_reset
end interface
@ %def event_particle_const_iterator_reset
<<HepMC interface: public>>=
public :: hepmc_event_particle_iterator_reset
<<HepMC interface: procedures>>=
subroutine hepmc_event_particle_iterator_reset (it)
type(hepmc_event_particle_iterator_t), intent(inout) :: it
call event_particle_const_iterator_reset (it%obj, it%evt_obj)
end subroutine hepmc_event_particle_iterator_reset
@ %def hepmc_event_particle_iterator_reset
@ Test: return true as long as we are not past the end.
<<HepMC interface: interfaces>>=
interface
function event_particle_const_iterator_is_valid &
(it_obj, evt_obj) result (flag) bind(C)
import
logical(c_bool) :: flag
type(c_ptr), value :: it_obj, evt_obj
end function event_particle_const_iterator_is_valid
end interface
@ %def event_particle_const_iterator_is_valid
<<HepMC interface: public>>=
public :: hepmc_event_particle_iterator_is_valid
<<HepMC interface: procedures>>=
function hepmc_event_particle_iterator_is_valid (it) result (flag)
logical :: flag
type(hepmc_event_particle_iterator_t), intent(in) :: it
flag = event_particle_const_iterator_is_valid (it%obj, it%evt_obj)
end function hepmc_event_particle_iterator_is_valid
@ %def hepmc_event_particle_iterator_is_valid
@ Return the particle pointed to by the iterator. (The particle
object should not be finalized, since it contains merely a pointer to
the particle which is owned by the vertex.)
<<HepMC interface: interfaces>>=
interface
type(c_ptr) function event_particle_const_iterator_get (it_obj) bind(C)
import
type(c_ptr), value :: it_obj
end function event_particle_const_iterator_get
end interface
@ %def event_particle_const_iterator_get
<<HepMC interface: public>>=
public :: hepmc_event_particle_iterator_get
<<HepMC interface: procedures>>=
function hepmc_event_particle_iterator_get (it) result (prt)
type(hepmc_particle_t) :: prt
type(hepmc_event_particle_iterator_t), intent(in) :: it
prt%obj = event_particle_const_iterator_get (it%obj)
end function hepmc_event_particle_iterator_get
@ %def hepmc_event_particle_iterator_get
@
\subsection{I/O streams}
There is a specific I/O stream type for handling the output of
GenEvent objects (i.e., Monte Carlo event samples) to file. Opening
the file is done by the constructor, closing by the destructor.
<<HepMC interface: public>>=
public :: hepmc_iostream_t
<<HepMC interface: types>>=
type :: hepmc_iostream_t
private
type(c_ptr) :: obj
end type hepmc_iostream_t
@ %def hepmc_iostream_t
@ Constructor for an output stream associated to a file.
<<HepMC interface: interfaces>>=
interface
type(c_ptr) function new_io_gen_event_out (filename) bind(C)
import
character(c_char), dimension(*), intent(in) :: filename
end function new_io_gen_event_out
end interface
@ %def new_io_gen_event
<<HepMC interface: public>>=
public :: hepmc_iostream_open_out
<<HepMC interface: procedures>>=
subroutine hepmc_iostream_open_out (iostream, filename)
type(hepmc_iostream_t), intent(out) :: iostream
type(string_t), intent(in) :: filename
iostream%obj = new_io_gen_event_out (char (filename) // c_null_char)
end subroutine hepmc_iostream_open_out
@ %def hepmc_iostream_open_out
@ Constructor for an input stream associated to a file.
<<HepMC interface: interfaces>>=
interface
type(c_ptr) function new_io_gen_event_in (filename) bind(C)
import
character(c_char), dimension(*), intent(in) :: filename
end function new_io_gen_event_in
end interface
@ %def new_io_gen_event
<<HepMC interface: public>>=
public :: hepmc_iostream_open_in
<<HepMC interface: procedures>>=
subroutine hepmc_iostream_open_in (iostream, filename)
type(hepmc_iostream_t), intent(out) :: iostream
type(string_t), intent(in) :: filename
iostream%obj = new_io_gen_event_in (char (filename) // c_null_char)
end subroutine hepmc_iostream_open_in
@ %def hepmc_iostream_open_in
@ Destructor:
<<HepMC interface: interfaces>>=
interface
subroutine io_gen_event_delete (io_obj) bind(C)
import
type(c_ptr), value :: io_obj
end subroutine io_gen_event_delete
end interface
@ %def io_gen_event_delete
<<HepMC interface: public>>=
public :: hepmc_iostream_close
<<HepMC interface: procedures>>=
subroutine hepmc_iostream_close (iostream)
type(hepmc_iostream_t), intent(inout) :: iostream
call io_gen_event_delete (iostream%obj)
end subroutine hepmc_iostream_close
@ %def hepmc_iostream_close
@ Write a single event to the I/O stream.
<<HepMC interface: interfaces>>=
interface
subroutine io_gen_event_write_event (io_obj, evt_obj) bind(C)
import
type(c_ptr), value :: io_obj, evt_obj
end subroutine io_gen_event_write_event
end interface
@ %def io_gen_event_write_event
<<HepMC interface: public>>=
public :: hepmc_iostream_write_event
<<HepMC interface: procedures>>=
subroutine hepmc_iostream_write_event (iostream, evt)
type(hepmc_iostream_t), intent(inout) :: iostream
type(hepmc_event_t), intent(in) :: evt
call io_gen_event_write_event (iostream%obj, evt%obj)
end subroutine hepmc_iostream_write_event
@ %def hepmc_iostream_write_event
@ Read a single event from the I/O stream. Return true if successful.
<<HepMC interface: interfaces>>=
interface
logical(c_bool) function io_gen_event_read_event (io_obj, evt_obj) bind(C)
import
type(c_ptr), value :: io_obj, evt_obj
end function io_gen_event_read_event
end interface
@ %def io_gen_event_read_event
<<HepMC interface: public>>=
public :: hepmc_iostream_read_event
<<HepMC interface: procedures>>=
subroutine hepmc_iostream_read_event (iostream, evt, ok)
type(hepmc_iostream_t), intent(inout) :: iostream
type(hepmc_event_t), intent(inout) :: evt
logical, intent(out) :: ok
ok = io_gen_event_read_event (iostream%obj, evt%obj)
end subroutine hepmc_iostream_read_event
@ %def hepmc_iostream_read_event
@
\subsection{Unit tests}
Test module, followed by the corresponding implementation module.
<<[[hepmc_interface_ut.f90]]>>=
<<File header>>
module hepmc_interface_ut
use unit_tests
use hepmc_interface_uti
<<Standard module head>>
<<HepMC interface: public test>>
contains
<<HepMC interface: test driver>>
end module hepmc_interface_ut
@ %def hepmc_interface_ut
@
<<[[hepmc_interface_uti.f90]]>>=
<<File header>>
module hepmc_interface_uti
<<Use kinds>>
<<Use strings>>
use io_units
use lorentz
use flavors
use colors
use polarizations
use hepmc_interface
<<Standard module head>>
<<HepMC interface: test declarations>>
contains
<<HepMC interface: tests>>
end module hepmc_interface_uti
@ %def hepmc_interface_ut
@ API: driver for the unit tests below.
<<HepMC interface: public test>>=
public :: hepmc_interface_test
<<HepMC interface: test driver>>=
subroutine hepmc_interface_test (u, results)
integer, intent(in) :: u
type(test_results_t), intent(inout) :: results
<<HepMC interface: execute tests>>
end subroutine hepmc_interface_test
@ %def hepmc_test
@
This test example is an abridged version from the build-from-scratch
example in the HepMC distribution. We create two vertices for $p\to
q$ PDF splitting, then a vertex for a $qq\to W^-g$ hard-interaction
process, and finally a vertex for $W^-\to qq$ decay. The setup is for
LHC kinematics.
Extending the original example, we set color flow for the incoming
quarks and polarization for the outgoing photon. For the latter, we
have to define a particle-data object for the photon, so a flavor
object can be correctly initialized.
<<HepMC interface: execute tests>>=
call test (hepmc_interface_1, "hepmc_interface_1", &
"check HepMC interface", &
u, results)
<<HepMC interface: test declarations>>=
public :: hepmc_interface_1
<<HepMC interface: tests>>=
subroutine hepmc_interface_1 (u)
use physics_defs, only: VECTOR
use model_data, only: field_data_t
integer, intent(in) :: u
integer :: u_file, iostat
type(hepmc_event_t) :: evt
type(hepmc_vertex_t) :: v1, v2, v3, v4
type(hepmc_particle_t) :: prt1, prt2, prt3, prt4, prt5, prt6, prt7, prt8
type(hepmc_iostream_t) :: iostream
type(flavor_t) :: flv
type(color_t) :: col
type(polarization_t) :: pol
type(field_data_t), target :: photon_data
character(80) :: buffer
write (u, "(A)") "* Test output: HepMC interface"
write (u, "(A)") "* Purpose: test HepMC interface"
write (u, "(A)")
write (u, "(A)") "* Initialization"
write (u, "(A)")
! Initialize a photon flavor object and some polarization
call photon_data%init (var_str ("PHOTON"), 22)
call photon_data%set (spin_type=VECTOR)
call photon_data%freeze ()
call flv%init (photon_data)
call pol%init_angles &
(flv, 0.6_default, 1._default, 0.5_default)
! Event initialization
call hepmc_event_init (evt, 20, 1)
write (u, "(A)") "* p -> q splitting"
write (u, "(A)")
! $p\to q$ splittings
call hepmc_vertex_init (v1)
call hepmc_event_add_vertex (evt, v1)
call hepmc_vertex_init (v2)
call hepmc_event_add_vertex (evt, v2)
call particle_init (prt1, &
0._default, 0._default, 7000._default, 7000._default, &
2212, 3)
call hepmc_vertex_add_particle_in (v1, prt1)
call particle_init (prt2, &
0._default, 0._default,-7000._default, 7000._default, &
2212, 3)
call hepmc_vertex_add_particle_in (v2, prt2)
call particle_init (prt3, &
.750_default, -1.569_default, 32.191_default, 32.238_default, &
1, 3)
call color_init_from_array (col, [501])
call hepmc_particle_set_color (prt3, col)
call hepmc_vertex_add_particle_out (v1, prt3)
call particle_init (prt4, &
-3.047_default, -19._default, -54.629_default, 57.920_default, &
-2, 3)
call color_init_from_array (col, [-501])
call hepmc_particle_set_color (prt4, col)
call hepmc_vertex_add_particle_out (v2, prt4)
write (u, "(A)") "* Hard interaction"
write (u, "(A)")
! Hard interaction
call hepmc_vertex_init (v3)
call hepmc_event_add_vertex (evt, v3)
call hepmc_vertex_add_particle_in (v3, prt3)
call hepmc_vertex_add_particle_in (v3, prt4)
call particle_init (prt6, &
-3.813_default, 0.113_default, -1.833_default, 4.233_default, &
22, 1)
call hepmc_particle_set_polarization (prt6, pol)
call hepmc_vertex_add_particle_out (v3, prt6)
call particle_init (prt5, &
1.517_default, -20.68_default, -20.605_default, 85.925_default, &
-24, 3)
call hepmc_vertex_add_particle_out (v3, prt5)
call hepmc_event_set_signal_process_vertex (evt, v3)
! $W^-$ decay
call vertex_init_pos (v4, &
0.12_default, -0.3_default, 0.05_default, 0.004_default)
call hepmc_event_add_vertex (evt, v4)
call hepmc_vertex_add_particle_in (v4, prt5)
call particle_init (prt7, &
-2.445_default, 28.816_default, 6.082_default, 29.552_default, &
1, 1)
call hepmc_vertex_add_particle_out (v4, prt7)
call particle_init (prt8, &
3.962_default, -49.498_default, -26.687_default, 56.373_default, &
-2, 1)
call hepmc_vertex_add_particle_out (v4, prt8)
! Event output
call hepmc_event_print (evt)
write (u, "(A)") "Writing to file 'hepmc_test.hepmc'"
write (u, "(A)")
call hepmc_iostream_open_out (iostream , var_str ("hepmc_test.hepmc"))
call hepmc_iostream_write_event (iostream, evt)
call hepmc_iostream_close (iostream)
write (u, "(A)") "Writing completed"
write (u, "(A)")
write (u, "(A)") "* File contents:"
write (u, "(A)")
u_file = free_unit ()
open (u_file, file = "hepmc_test.hepmc", &
action = "read", status = "old")
do
read (u_file, "(A)", iostat = iostat) buffer
if (buffer(1:14) == "HepMC::Version") buffer = "[...]"
if (iostat /= 0) exit
write (u, "(A)") trim (buffer)
end do
close (u_file)
write (u, "(A)")
write (u, "(A)") "* Cleanup"
write (u, "(A)")
! Wrapup
! call pol%final ()
call hepmc_event_final (evt)
write (u, "(A)")
write (u, "(A)") "* Test output end: hepmc_interface_1"
contains
subroutine vertex_init_pos (v, x, y, z, t)
type(hepmc_vertex_t), intent(out) :: v
real(default), intent(in) :: x, y, z, t
type(vector4_t) :: xx
xx = vector4_moving (t, vector3_moving ([x, y, z]))
call hepmc_vertex_init (v, xx)
end subroutine vertex_init_pos
subroutine particle_init (prt, px, py, pz, E, pdg, status)
type(hepmc_particle_t), intent(out) :: prt
real(default), intent(in) :: px, py, pz, E
integer, intent(in) :: pdg, status
type(vector4_t) :: p
p = vector4_moving (E, vector3_moving ([px, py, pz]))
call hepmc_particle_init (prt, p, pdg, status)
end subroutine particle_init
end subroutine hepmc_interface_1
@ %def hepmc_interface_1
@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
\section{LCIO events}
This section provides the interface to the LCIO C++ library for handling
Monte-Carlo events.
Each C++ class of LCIO that we use is mirrored by a Fortran type,
which contains as its only component the C pointer to the C++ object.
Each C++ method of LCIO that we use has a C wrapper function. This
function takes a pointer to the host object as its first argument.
Further arguments are either C pointers, or in the case of simple
types (integer, real), interoperable C/Fortran objects.
The C wrapper functions have explicit interfaces in the Fortran
module. They are called by Fortran wrapper procedures. These are
treated as methods of the corresponding Fortran type.
<<[[lcio_interface.f90]]>>=
<<File header>>
module lcio_interface
use, intrinsic :: iso_c_binding !NODEP!
<<Use kinds>>
<<Use strings>>
use constants, only: PI
+ use physics_defs, only: ns_per_mm
use diagnostics
use lorentz
use flavors
use colors
use helicities
use polarizations
<<Standard module head>>
<<LCIO interface: public>>
<<LCIO interface: types>>
<<LCIO interface: interfaces>>
contains
<<LCIO interface: procedures>>
end module lcio_interface
@ %def lcio_interface
@
\subsection{Interface check}
This function can be called in order to verify that we are using the
actual LCIO library, and not the dummy version.
<<LCIO interface: interfaces>>=
interface
logical(c_bool) function lcio_available () bind(C)
import
end function lcio_available
end interface
<<LCIO interface: public>>=
public :: lcio_is_available
<<LCIO interface: procedures>>=
function lcio_is_available () result (flag)
logical :: flag
flag = lcio_available ()
end function lcio_is_available
@ %def lcio_is_available
@
\subsection{LCIO Run Header}
This is a type for the run header of the LCIO file.
<<LCIO interface: public>>=
public :: lcio_run_header_t
<<LCIO interface: types>>=
type :: lcio_run_header_t
private
type(c_ptr) :: obj
end type lcio_run_header_t
@ %def lcio_run_header_t
The Fortran version has initializer form.
<<LCIO interface: interfaces>>=
interface
type(c_ptr) function new_lcio_run_header (proc_id) bind(C)
import
integer(c_int), value :: proc_id
end function new_lcio_run_header
end interface
@ %def new_lcio_run_header
<<LCIO interface: interfaces>>=
interface
subroutine run_header_set_simstring &
(runhdr_obj, simstring) bind(C)
import
type(c_ptr), value :: runhdr_obj
character(c_char), dimension(*), intent(in) :: simstring
end subroutine run_header_set_simstring
end interface
@ %def run_header_set_simstring
<<LCIO interface: public>>=
public :: lcio_run_header_init
<<LCIO interface: procedures>>=
subroutine lcio_run_header_init (runhdr, proc_id, run_id)
type(lcio_run_header_t), intent(out) :: runhdr
integer, intent(in), optional :: proc_id, run_id
integer(c_int) :: rid
rid = 0; if (present (run_id)) rid = run_id
runhdr%obj = new_lcio_run_header (rid)
call run_header_set_simstring (runhdr%obj, &
"WHIZARD version:" // "<<Version>>")
end subroutine lcio_run_header_init
@ %def lcio_run_header_init
@
<<LCIO interface: interfaces>>=
interface
subroutine write_run_header (lcwrt_obj, runhdr_obj) bind(C)
import
type(c_ptr), value :: lcwrt_obj
type(c_ptr), value :: runhdr_obj
end subroutine write_run_header
end interface
@ %def write_run_header
<<LCIO interface: public>>=
public :: lcio_run_header_write
<<LCIO interface: procedures>>=
subroutine lcio_run_header_write (wrt, hdr)
type(lcio_writer_t), intent(inout) :: wrt
type(lcio_run_header_t), intent(inout) :: hdr
call write_run_header (wrt%obj, hdr%obj)
end subroutine lcio_run_header_write
@ %def lcio_run_header_write
@
\subsection{LCIO Event and LC Collection}
The main object of LCIO is a LCEventImpl. The object is filled by
MCParticle objects, which are set as LCCollection.
<<LCIO interface: public>>=
public :: lccollection_t
<<LCIO interface: types>>=
type :: lccollection_t
private
type(c_ptr) :: obj
end type lccollection_t
@ %def lccollection_t
@ Initializer.
<<LCIO interface: interfaces>>=
interface
type(c_ptr) function new_lccollection () bind(C)
import
end function new_lccollection
end interface
@ %def new_lccollection
<<LCIO interface: public>>=
public :: lcio_event_t
<<LCIO interface: types>>=
type :: lcio_event_t
private
type(c_ptr) :: obj
type(lccollection_t) :: lccoll
end type lcio_event_t
@ %def lcio_event_t
@ Constructor. Arguments are process ID (integer) and event ID
(integer).
The Fortran version has initializer form.
<<LCIO interface: interfaces>>=
interface
type(c_ptr) function new_lcio_event (proc_id, event_id, run_id) bind(C)
import
integer(c_int), value :: proc_id, event_id, run_id
end function new_lcio_event
end interface
@ %def new_lcio_event
@
<<LCIO interface: public>>=
public :: lcio_event_init
<<LCIO interface: procedures>>=
subroutine lcio_event_init (evt, proc_id, event_id, run_id)
type(lcio_event_t), intent(out) :: evt
integer, intent(in), optional :: proc_id, event_id, run_id
integer(c_int) :: pid, eid, rid
pid = 0; if (present (proc_id)) pid = proc_id
eid = 0; if (present (event_id)) eid = event_id
rid = 0; if (present (run_id)) rid = run_id
evt%obj = new_lcio_event (pid, eid, rid)
evt%lccoll%obj = new_lccollection ()
end subroutine lcio_event_init
@ %def lcio_event_init
@ Destructor.
<<LCIO interface: interfaces>>=
interface
subroutine lcio_event_delete (evt_obj) bind(C)
import
type(c_ptr), value :: evt_obj
end subroutine lcio_event_delete
end interface
@ %def lcio_event_delete
@ Show event on screen.
<<LCIO interface: interfaces>>=
interface
subroutine dump_lcio_event (evt_obj) bind(C)
import
type(c_ptr), value :: evt_obj
end subroutine dump_lcio_event
end interface
@ %def dump_lcio_event
<<LCIO interface: public>>=
public :: show_lcio_event
<<LCIO interface: procedures>>=
subroutine show_lcio_event (evt)
type(lcio_event_t), intent(in) :: evt
if (c_associated (evt%obj)) then
call dump_lcio_event (evt%obj)
else
call msg_error ("LCIO event is not allocated.")
end if
end subroutine show_lcio_event
@ %def show_lcio_event
@ Put a single event to file.
<<LCIO interface: interfaces>>=
interface
subroutine lcio_event_to_file (evt_obj, filename) bind(C)
import
type(c_ptr), value :: evt_obj
character(c_char), dimension(*), intent(in) :: filename
end subroutine lcio_event_to_file
end interface
@ %def lcio_event_to_file
<<LCIO interface: public>>=
public :: write_lcio_event
<<LCIO interface: procedures>>=
subroutine write_lcio_event (evt, filename)
type(lcio_event_t), intent(in) :: evt
type(string_t), intent(in) :: filename
call lcio_event_to_file (evt%obj, char (filename) // c_null_char)
end subroutine write_lcio_event
@ %def write_lcio_event
@
<<LCIO interface: public>>=
public :: lcio_event_final
<<LCIO interface: procedures>>=
subroutine lcio_event_final (evt)
type(lcio_event_t), intent(inout) :: evt
call lcio_event_delete (evt%obj)
end subroutine lcio_event_final
@ %def lcio_event_final
@
<<LCIO interface: interfaces>>=
interface
subroutine lcio_set_weight (evt_obj, weight) bind(C)
import
type(c_ptr), value :: evt_obj
real(c_double), value :: weight
end subroutine lcio_set_weight
end interface
interface
subroutine lcio_set_alpha_qcd (evt_obj, alphas) bind(C)
import
type(c_ptr), value :: evt_obj
real(c_double), value :: alphas
end subroutine lcio_set_alpha_qcd
end interface
interface
subroutine lcio_set_scale (evt_obj, scale) bind(C)
import
type(c_ptr), value :: evt_obj
real(c_double), value :: scale
end subroutine lcio_set_scale
end interface
interface
subroutine lcio_set_sqrts (evt_obj, sqrts) bind(C)
import
type(c_ptr), value :: evt_obj
real(c_double), value :: sqrts
end subroutine lcio_set_sqrts
end interface
interface
subroutine lcio_set_xsec (evt_obj, xsec, xsec_err) bind(C)
import
type(c_ptr), value :: evt_obj
real(c_double), value :: xsec, xsec_err
end subroutine lcio_set_xsec
end interface
interface
subroutine lcio_set_beam (evt_obj, pdg, beam) bind(C)
import
type(c_ptr), value :: evt_obj
integer(c_int), value :: pdg, beam
end subroutine lcio_set_beam
end interface
interface
subroutine lcio_set_pol (evt_obj, pol1, pol2) bind(C)
import
type(c_ptr), value :: evt_obj
real(c_double), value :: pol1, pol2
end subroutine lcio_set_pol
end interface
interface
subroutine lcio_set_beam_file (evt_obj, file) bind(C)
import
type(c_ptr), value :: evt_obj
character(len=1, kind=c_char), dimension(*), intent(in) :: file
end subroutine lcio_set_beam_file
end interface
interface
subroutine lcio_set_process_name (evt_obj, name) bind(C)
import
type(c_ptr), value :: evt_obj
character(len=1, kind=c_char), dimension(*), intent(in) :: name
end subroutine lcio_set_process_name
end interface
@ %def lcio_set_weight lcio_set_alpha_qcd lcio_set_scale lcio_set_sqrts
@ %def lcio_set_xsec lcio_set_beam lcio_set_pol
@ %def lcio_set_beam_file lcio_set_process_name
@
<<LCIO interface: public>>=
public :: lcio_event_set_weight
<<LCIO interface: procedures>>=
subroutine lcio_event_set_weight (evt, weight)
type(lcio_event_t), intent(inout) :: evt
real(default), intent(in) :: weight
call lcio_set_weight (evt%obj, real (weight, c_double))
end subroutine lcio_event_set_weight
@ %def lcio_event_set_weight
@
<<LCIO interface: public>>=
public :: lcio_event_set_alpha_qcd
<<LCIO interface: procedures>>=
subroutine lcio_event_set_alpha_qcd (evt, alphas)
type(lcio_event_t), intent(inout) :: evt
real(default), intent(in) :: alphas
call lcio_set_alpha_qcd (evt%obj, real (alphas, c_double))
end subroutine lcio_event_set_alpha_qcd
@ %def lcio_event_set_alpha_qcd
@
<<LCIO interface: public>>=
public :: lcio_event_set_scale
<<LCIO interface: procedures>>=
subroutine lcio_event_set_scale (evt, scale)
type(lcio_event_t), intent(inout) :: evt
real(default), intent(in) :: scale
call lcio_set_scale (evt%obj, real (scale, c_double))
end subroutine lcio_event_set_scale
@ %def lcio_event_set_scale
@
<<LCIO interface: public>>=
public :: lcio_event_set_sqrts
<<LCIO interface: procedures>>=
subroutine lcio_event_set_sqrts (evt, sqrts)
type(lcio_event_t), intent(inout) :: evt
real(default), intent(in) :: sqrts
call lcio_set_sqrts (evt%obj, real (sqrts, c_double))
end subroutine lcio_event_set_sqrts
@ %def lcio_event_set_sqrts
@
<<LCIO interface: public>>=
public :: lcio_event_set_xsec
<<LCIO interface: procedures>>=
subroutine lcio_event_set_xsec (evt, xsec, xsec_err)
type(lcio_event_t), intent(inout) :: evt
real(default), intent(in) :: xsec, xsec_err
call lcio_set_xsec (evt%obj, &
real (xsec, c_double), real (xsec_err, c_double))
end subroutine lcio_event_set_xsec
@ %def lcio_event_set_xsec
@
<<LCIO interface: public>>=
public :: lcio_event_set_beam
<<LCIO interface: procedures>>=
subroutine lcio_event_set_beam (evt, pdg, beam)
type(lcio_event_t), intent(inout) :: evt
integer, intent(in) :: pdg, beam
call lcio_set_beam (evt%obj, &
int (pdg, c_int), int (beam, c_int))
end subroutine lcio_event_set_beam
@ %def lcio_event_set_beam
@
<<LCIO interface: public>>=
public :: lcio_event_set_polarization
<<LCIO interface: procedures>>=
subroutine lcio_event_set_polarization (evt, pol)
type(lcio_event_t), intent(inout) :: evt
real(default), intent(in), dimension(2) :: pol
call lcio_set_pol (evt%obj, &
real (pol(1), c_double), real (pol(2), c_double))
end subroutine lcio_event_set_polarization
@ %def lcio_event_set_polarization
@
<<LCIO interface: public>>=
public :: lcio_event_set_beam_file
<<LCIO interface: procedures>>=
subroutine lcio_event_set_beam_file (evt, file)
type(lcio_event_t), intent(inout) :: evt
type(string_t), intent(in) :: file
call lcio_set_beam_file (evt%obj, &
char (file) // c_null_char)
end subroutine lcio_event_set_beam_file
@ %def lcio_event_set_beam_file
@
<<LCIO interface: public>>=
public :: lcio_event_set_process_name
<<LCIO interface: procedures>>=
subroutine lcio_event_set_process_name (evt, name)
type(lcio_event_t), intent(inout) :: evt
type(string_t), intent(in) :: name
call lcio_set_process_name (evt%obj, &
char (name) // c_null_char)
end subroutine lcio_event_set_process_name
@ %def lcio_event_set_process_name
@
<<LCIO interface: interfaces>>=
interface
subroutine lcio_event_add_collection &
(evt_obj, lccoll_obj) bind(C)
import
type(c_ptr), value :: evt_obj, lccoll_obj
end subroutine lcio_event_add_collection
end interface
@ %def lcio_event_add_collection
<<LCIO interface: public>>=
public :: lcio_event_add_coll
<<LCIO interface: procedures>>=
subroutine lcio_event_add_coll (evt)
type(lcio_event_t), intent(inout) :: evt
call lcio_event_add_collection (evt%obj, &
evt%lccoll%obj)
end subroutine lcio_event_add_coll
@ %def lcio_event_add_coll
@
\subsection{LCIO Particle}
Particle objects have the obvious meaning.
<<LCIO interface: public>>=
public :: lcio_particle_t
<<LCIO interface: types>>=
type :: lcio_particle_t
private
type(c_ptr) :: obj
end type lcio_particle_t
@ %def lcio_particle_t
@ Constructor.
<<LCIO interface: interfaces>>=
interface
type(c_ptr) function new_lcio_particle &
(px, py, pz, pdg_id, mass, charge, status) bind(C)
import
integer(c_int), value :: pdg_id, status
real(c_double), value :: px, py, pz, mass, charge
end function new_lcio_particle
end interface
@ %def new_lcio_particle
@
<<LCIO interface: interfaces>>=
interface
subroutine add_particle_to_collection &
(prt_obj, lccoll_obj) bind(C)
import
type(c_ptr), value :: prt_obj, lccoll_obj
end subroutine add_particle_to_collection
end interface
@ %def add_particle_to_collection
<<LCIO interface: public>>=
public :: lcio_particle_add_to_evt_coll
<<LCIO interface: procedures>>=
subroutine lcio_particle_add_to_evt_coll &
(lprt, evt)
type(lcio_particle_t), intent(in) :: lprt
type(lcio_event_t), intent(inout) :: evt
call add_particle_to_collection (lprt%obj, evt%lccoll%obj)
end subroutine lcio_particle_add_to_evt_coll
@ %def lcio_particle_to_collection
@
<<LCIO interface: public>>=
public :: lcio_particle_init
<<LCIO interface: procedures>>=
subroutine lcio_particle_init (prt, p, pdg, charge, status)
type(lcio_particle_t), intent(out) :: prt
type(vector4_t), intent(in) :: p
real(default), intent(in) :: charge
real(default) :: mass
real(default) :: px, py, pz
integer, intent(in) :: pdg, status
px = vector4_get_component (p, 1)
py = vector4_get_component (p, 2)
pz = vector4_get_component (p, 3)
mass = p**1
prt%obj = new_lcio_particle (real (px, c_double), real (py, c_double), &
real (pz, c_double), int (pdg, c_int), &
real (mass, c_double), real (charge, c_double), int (status, c_int))
end subroutine lcio_particle_init
@ %def lcio_particle_init
@ Set the particle color flow.
<<LCIO interface: interfaces>>=
interface
subroutine lcio_set_color_flow (prt_obj, col1, col2) bind(C)
import
type(c_ptr), value :: prt_obj
integer(c_int), value :: col1, col2
end subroutine lcio_set_color_flow
end interface
@ %def lcio_set_color_flow
@ Set the particle color. Either from a [[color_t]] object or
directly from a pair of integers.
<<LCIO interface: interfaces>>=
interface lcio_particle_set_color
module procedure lcio_particle_set_color_col
module procedure lcio_particle_set_color_int
end interface lcio_particle_set_color
<<LCIO interface: public>>=
public :: lcio_particle_set_color
<<LCIO interface: procedures>>=
subroutine lcio_particle_set_color_col (prt, col)
type(lcio_particle_t), intent(inout) :: prt
type(color_t), intent(in) :: col
integer(c_int), dimension(2) :: c
c(1) = col%get_col ()
c(2) = col%get_acl ()
if (c(1) /= 0 .or. c(2) /= 0) then
call lcio_set_color_flow (prt%obj, c(1), c(2))
end if
end subroutine lcio_particle_set_color_col
subroutine lcio_particle_set_color_int (prt, col)
type(lcio_particle_t), intent(inout) :: prt
integer, dimension(2), intent(in) :: col
integer(c_int), dimension(2) :: c
c = col
if (c(1) /= 0 .or. c(2) /= 0) then
call lcio_set_color_flow (prt%obj, c(1), c(2))
end if
end subroutine lcio_particle_set_color_int
@ %def lcio_particle_set_color
@ Return the particle color as a two-dimensional array (color, anticolor).
<<LCIO interface: interfaces>>=
interface
integer(c_int) function lcio_particle_flow (prt_obj, col_index) bind(C)
use iso_c_binding !NODEP!
type(c_ptr), value :: prt_obj
integer(c_int), value :: col_index
end function lcio_particle_flow
end interface
@ %def lcio_particle_flow
<<LCIO interface: public>>=
public :: lcio_particle_get_flow
<<LCIO interface: procedures>>=
function lcio_particle_get_flow (prt) result (col)
integer, dimension(2) :: col
type(lcio_particle_t), intent(in) :: prt
col(1) = lcio_particle_flow (prt%obj, 0_c_int)
col(2) = - lcio_particle_flow (prt%obj, 1_c_int)
end function lcio_particle_get_flow
@ %def lcio_particle_get_flow
@ Return the four-momentum of a LCIO particle.
<<LCIO interface: interfaces>>=
interface
real(c_double) function lcio_three_momentum (prt_obj, p_index) bind(C)
use iso_c_binding !NODEP!
type(c_ptr), value :: prt_obj
integer(c_int), value :: p_index
end function lcio_three_momentum
end interface
@ %def lcio_three_momentum
<<LCIO interface: interfaces>>=
interface
real(c_double) function lcio_energy (prt_obj) bind(C)
import
type(c_ptr), intent(in), value :: prt_obj
end function lcio_energy
end interface
@ %def lcio_energy
<<LCIO interface: public>>=
public :: lcio_particle_get_momentum
<<LCIO interface: procedures>>=
function lcio_particle_get_momentum (prt) result (p)
type(vector4_t) :: p
type(lcio_particle_t), intent(in) :: prt
real(default) :: E, px, py, pz
E = lcio_energy (prt%obj)
px = lcio_three_momentum (prt%obj, 0_c_int)
py = lcio_three_momentum (prt%obj, 1_c_int)
pz = lcio_three_momentum (prt%obj, 2_c_int)
p = vector4_moving ( E, vector3_moving ([ px, py, pz ]))
end function lcio_particle_get_momentum
@ %def lcio_particle_get_momentum
@ Return the invariant mass squared of the particle object. LCIO
stores the signed invariant mass (no squaring).
<<LCIO interface: interfaces>>=
interface
function lcio_mass (prt_obj) result (mass) bind(C)
import
real(c_double) :: mass
type(c_ptr), value :: prt_obj
end function lcio_mass
end interface
@ %def lcio_mass
<<LCIO interface: public>>=
public :: lcio_particle_get_mass_squared
<<LCIO interface: procedures>>=
function lcio_particle_get_mass_squared (prt) result (m2)
real(default) :: m2
type(lcio_particle_t), intent(in) :: prt
real(default) :: m
m = lcio_mass (prt%obj)
m2 = sign (m**2, m)
end function lcio_particle_get_mass_squared
@ %def lcio_particle_get_mass_squared
@ Return vertex and production time of a LCIO particle.
<<LCIO interface: interfaces>>=
interface
real(c_double) function lcio_vtx_x (prt) bind(C)
import
type(c_ptr), value :: prt
end function lcio_vtx_x
end interface
interface
real(c_double) function lcio_vtx_y (prt) bind(C)
import
type(c_ptr), value :: prt
end function lcio_vtx_y
end interface
interface
real(c_double) function lcio_vtx_z (prt) bind(C)
import
type(c_ptr), value :: prt
end function lcio_vtx_z
end interface
interface
- real(c_double) function lcio_prt_time (prt) bind(C)
+ real(c_float) function lcio_prt_time (prt) bind(C)
import
type(c_ptr), value :: prt
end function lcio_prt_time
end interface
@
@
+(Decay) times in LCIO are in nanoseconds, so they need to get
+converted to mm for the internal format.
<<LCIO interface: public>>=
public :: lcio_particle_get_vertex
public :: lcio_particle_get_time
<<LCIO interface: procedures>>=
function lcio_particle_get_vertex (prt) result (vtx)
type(vector3_t) :: vtx
type(lcio_particle_t), intent(in) :: prt
real(default) :: vx, vy, vz
vx = lcio_vtx_x (prt%obj)
vy = lcio_vtx_y (prt%obj)
vz = lcio_vtx_z (prt%obj)
vtx = vector3_moving ([vx, vy, vz])
end function lcio_particle_get_vertex
function lcio_particle_get_time (prt) result (time)
real(default) :: time
type(lcio_particle_t), intent(in) :: prt
time = lcio_prt_time (prt%obj)
+ time = time / ns_per_mm
end function lcio_particle_get_time
@ %def lcio_particle_get_vertex lcio_particle_get_time
@
\subsection{Polarization}
For polarization there is a three-component float entry foreseen in the LCIO
format. Completely generic density matrices can in principle be attached to
events as float vectors added to [[LCCollection]] of the [[LCEvent]]. This is
not yet implemented currently. Here, we restrict ourselves to the same
implementation as in HepMC format: we use two entries as the polarization
angles, while the first entry gives the degree of polarization (something
not specified in the HepMC format).
\emph{For massive vector bosons, we arbitrarily choose the convention
that the longitudinal (zero) helicity state is mapped to the theta
angle $\pi/2$. This works under the condition that helicity is
projected onto one of the basis states.}
<<LCIO interface: interfaces>>=
interface
subroutine lcio_particle_set_spin (prt_obj, s1, s2, s3) bind(C)
import
type(c_ptr), value :: prt_obj
real(c_double), value :: s1, s2, s3
end subroutine lcio_particle_set_spin
end interface
@ %def lcio_particle_set_spin
@
<<LCIO interface: public>>=
public :: lcio_polarization_init
<<LCIO interface: interfaces>>=
interface lcio_polarization_init
module procedure lcio_polarization_init_pol
module procedure lcio_polarization_init_hel
module procedure lcio_polarization_init_int
end interface
<<LCIO interface: procedures>>=
subroutine lcio_polarization_init_pol (prt, pol)
type(lcio_particle_t), intent(inout) :: prt
type(polarization_t), intent(in) :: pol
real(default) :: r, theta, phi
if (pol%is_polarized ()) then
call pol%to_angles (r, theta, phi)
call lcio_particle_set_spin (prt%obj, &
real(r, c_double), real (theta, c_double), real (phi, c_double))
end if
end subroutine lcio_polarization_init_pol
subroutine lcio_polarization_init_hel (prt, hel)
type(lcio_particle_t), intent(inout) :: prt
type(helicity_t), intent(in) :: hel
integer, dimension(2) :: h
if (hel%is_defined ()) then
h = hel%to_pair ()
select case (h(1))
case (1:)
call lcio_particle_set_spin (prt%obj, 1._c_double, &
0._c_double, 0._c_double)
case (:-1)
call lcio_particle_set_spin (prt%obj, 1._c_double, &
real (pi, c_double), 0._c_double)
case (0)
call lcio_particle_set_spin (prt%obj, 1._c_double, &
real (pi/2, c_double), 0._c_double)
end select
end if
end subroutine lcio_polarization_init_hel
subroutine lcio_polarization_init_int (prt, hel)
type(lcio_particle_t), intent(inout) :: prt
integer, intent(in) :: hel
call lcio_particle_set_spin (prt%obj, 0._c_double, &
0._c_double, real (hel, c_double))
end subroutine lcio_polarization_init_int
@ %def lcio_polarization_init
@ Recover polarization from LCIO particle (with the
abovementioned deficiencies).
<<LCIO interface: interfaces>>=
interface
function lcio_polarization_degree (prt_obj) result (degree) bind(C)
import
real(c_double) :: degree
type(c_ptr), value :: prt_obj
end function lcio_polarization_degree
end interface
interface
function lcio_polarization_theta (prt_obj) result (theta) bind(C)
import
real(c_double) :: theta
type(c_ptr), value :: prt_obj
end function lcio_polarization_theta
end interface
interface
function lcio_polarization_phi (prt_obj) result (phi) bind(C)
import
real(c_double) :: phi
type(c_ptr), value :: prt_obj
end function lcio_polarization_phi
end interface
@ %def lcio_polarization_degree lcio_polarization_theta lcio_polarization_phi
<<LCIO interface: public>>=
public :: lcio_particle_to_pol
<<LCIO interface: procedures>>=
subroutine lcio_particle_to_pol (prt, flv, pol)
type(lcio_particle_t), intent(in) :: prt
type(flavor_t), intent(in) :: flv
type(polarization_t), intent(out) :: pol
real(default) :: degree, theta, phi
degree = lcio_polarization_degree (prt%obj)
theta = lcio_polarization_theta (prt%obj)
phi = lcio_polarization_phi (prt%obj)
call pol%init_angles (flv, degree, theta, phi)
end subroutine lcio_particle_to_pol
@ %def lcio_polarization_to_pol
@ Recover helicity. Here, $\phi$ and [[degree]] is ignored and only the sign of
$\cos\theta$ is relevant, mapped to positive/negative helicity.
<<LCIO interface: public>>=
public :: lcio_particle_to_hel
<<LCIO interface: procedures>>=
subroutine lcio_particle_to_hel (prt, flv, hel)
type(lcio_particle_t), intent(in) :: prt
type(flavor_t), intent(in) :: flv
type(helicity_t), intent(out) :: hel
real(default) :: theta
integer :: hmax
theta = lcio_polarization_theta (prt%obj)
hmax = flv%get_spin_type () / 2
call hel%init (sign (hmax, nint (cos (theta))))
end subroutine lcio_particle_to_hel
@ %def lcio_particle_to_hel
@ Set the vertex of a particle.
<<LCIO interface: interfaces>>=
interface
subroutine lcio_particle_set_vertex (prt_obj, vx, vy, vz) bind(C)
import
type(c_ptr), value :: prt_obj
real(c_double), value :: vx, vy, vz
end subroutine lcio_particle_set_vertex
end interface
interface
subroutine lcio_particle_set_time (prt_obj, t) bind(C)
import
type(c_ptr), value :: prt_obj
- real(c_double), value :: t
+ real(c_float), value :: t
end subroutine lcio_particle_set_time
end interface
@ %def lcio_particle_set_vertex lcio_particle_set_time
@
<<LCIO interface: public>>=
public :: lcio_particle_set_vtx
<<LCIO interface: procedures>>=
subroutine lcio_particle_set_vtx (prt, vtx)
type(lcio_particle_t), intent(inout) :: prt
type(vector3_t), intent(in) :: vtx
call lcio_particle_set_vertex (prt%obj, real(vtx%p(1), c_double), &
real(vtx%p(2), c_double), real(vtx%p(3), c_double))
end subroutine lcio_particle_set_vtx
@ %def lcio_particle_set_vtx
@
+Times in LCIO are in nanoseconds, not in mm, so need to be converted.
<<LCIO interface: public>>=
public :: lcio_particle_set_t
<<LCIO interface: procedures>>=
subroutine lcio_particle_set_t (prt, t)
type(lcio_particle_t), intent(inout) :: prt
real(default), intent(in) :: t
- call lcio_particle_set_time (prt%obj, real(t, c_double))
+ real(default) :: ns_from_t_mm
+ ns_from_t_mm = ns_per_mm * t
+ call lcio_particle_set_time (prt%obj, real(ns_from_t_mm, c_float))
end subroutine lcio_particle_set_t
@ %def lcio_particle_set_t
@
<<LCIO interface: interfaces>>=
interface
subroutine lcio_particle_add_parent (prt_obj1, prt_obj2) bind(C)
import
type(c_ptr), value :: prt_obj1, prt_obj2
end subroutine lcio_particle_add_parent
end interface
@ %def lcio_particle_add_parent
<<LCIO interface: public>>=
public :: lcio_particle_set_parent
<<LCIO interface: procedures>>=
subroutine lcio_particle_set_parent (daughter, parent)
type(lcio_particle_t), intent(inout) :: daughter, parent
call lcio_particle_add_parent (daughter%obj, parent%obj)
end subroutine lcio_particle_set_parent
@ %def lcio_particle_set_parent
@
<<LCIO interface: interfaces>>=
interface
integer(c_int) function lcio_particle_get_generator_status &
(prt_obj) bind(C)
import
type(c_ptr), value :: prt_obj
end function lcio_particle_get_generator_status
end interface
@ %def lcio_particle_get_generator_status
<<LCIO interface: public>>=
public :: lcio_particle_get_status
<<LCIO interface: procedures>>=
function lcio_particle_get_status (lptr) result (status)
integer :: status
type(lcio_particle_t), intent(in) :: lptr
status = lcio_particle_get_generator_status (lptr%obj)
end function lcio_particle_get_status
@ %def lcio_particle_get_status
@ Getting the PDG code.
<<LCIO interface: interfaces>>=
interface
integer(c_int) function lcio_particle_get_pdg_code (prt_obj) bind(C)
import
type(c_ptr), value :: prt_obj
end function lcio_particle_get_pdg_code
end interface
@ %def lcio_particle_get_pdg_code
@
<<LCIO interface: public>>=
public :: lcio_particle_get_pdg
<<LCIO interface: procedures>>=
function lcio_particle_get_pdg (lptr) result (pdg)
integer :: pdg
type(lcio_particle_t), intent(in) :: lptr
pdg = lcio_particle_get_pdg_code (lptr%obj)
end function lcio_particle_get_pdg
@ %def lcio_particle_get_pdg
@ Obtaining the number of parents and daughters of an LCIO particle.
<<LCIO interface: interfaces>>=
interface
integer(c_int) function lcio_n_parents (prt_obj) bind(C)
import
type(c_ptr), value :: prt_obj
end function lcio_n_parents
end interface
@ %def lcio_n_parents
@
<<LCIO interface: interfaces>>=
interface
integer(c_int) function lcio_n_daughters (prt_obj) bind(C)
import
type(c_ptr), value :: prt_obj
end function lcio_n_daughters
end interface
@ %def lcio_n_daughters
@
<<LCIO interface: public>>=
public :: lcio_particle_get_n_parents
<<LCIO interface: procedures>>=
function lcio_particle_get_n_parents (lptr) result (n_parents)
integer :: n_parents
type(lcio_particle_t), intent(in) :: lptr
n_parents = lcio_n_parents (lptr%obj)
end function lcio_particle_get_n_parents
@ %def lcio_particle_get_n_parents
@
<<LCIO interface: public>>=
public :: lcio_particle_get_n_children
<<LCIO interface: procedures>>=
function lcio_particle_get_n_children (lptr) result (n_children)
integer :: n_children
type(lcio_particle_t), intent(in) :: lptr
n_children = lcio_n_daughters (lptr%obj)
end function lcio_particle_get_n_children
@ %def lcio_particle_get_n_children
@ This provides access from the LCIO event [[lcio_event_t]] to the array entries
of the parent and daughter arrays of the LCIO particles.
<<LCIO interface: interfaces>>=
interface
integer(c_int) function lcio_event_parent_k &
(evt_obj, num_part, k_parent) bind (C)
use iso_c_binding !NODEP!
type(c_ptr), value :: evt_obj
integer(c_int), value :: num_part, k_parent
end function lcio_event_parent_k
end interface
@ %def lcio_event_parent_k
<<LCIO interface: interfaces>>=
interface
integer(c_int) function lcio_event_daughter_k &
(evt_obj, num_part, k_daughter) bind (C)
use iso_c_binding !NODEP!
type(c_ptr), value :: evt_obj
integer(c_int), value :: num_part, k_daughter
end function lcio_event_daughter_k
end interface
@ %def lcio_event_daughter_k
@
<<LCIO interface: public>>=
public :: lcio_get_n_parents
<<LCIO interface: procedures>>=
function lcio_get_n_parents (evt, num_part, k_parent) result (index_parent)
type(lcio_event_t), intent(in) :: evt
integer, intent(in) :: num_part, k_parent
integer :: index_parent
index_parent = lcio_event_parent_k (evt%obj, int (num_part, c_int), &
int (k_parent, c_int))
end function lcio_get_n_parents
@ %def lcio_get_n_parents
@
<<LCIO interface: public>>=
public :: lcio_get_n_children
<<LCIO interface: procedures>>=
function lcio_get_n_children (evt, num_part, k_daughter) result (index_daughter)
type(lcio_event_t), intent(in) :: evt
integer, intent(in) :: num_part, k_daughter
integer :: index_daughter
index_daughter = lcio_event_daughter_k (evt%obj, int (num_part, c_int), &
int (k_daughter, c_int))
end function lcio_get_n_children
@ %def lcio_get_n_children
@
\subsection{LCIO Writer type}
There is a specific LCIO Writer type for handling the output of
LCEventImpl objects (i.e., Monte Carlo event samples) to file. Opening
the file is done by the constructor, closing by the destructor.
<<LCIO interface: public>>=
public :: lcio_writer_t
<<LCIO interface: types>>=
type :: lcio_writer_t
private
type(c_ptr) :: obj
end type lcio_writer_t
@ %def lcio_writer_t
@ Constructor for an output associated to a file.
<<LCIO interface: interfaces>>=
interface
type(c_ptr) function open_lcio_writer_new (filename, complevel) bind(C)
import
character(c_char), dimension(*), intent(in) :: filename
integer(c_int), intent(in) :: complevel
end function open_lcio_writer_new
end interface
@ %def open_lcio_writer_now
<<LCIO interface: public>>=
public :: lcio_writer_open_out
<<LCIO interface: procedures>>=
subroutine lcio_writer_open_out (lcio_writer, filename)
type(lcio_writer_t), intent(out) :: lcio_writer
type(string_t), intent(in) :: filename
lcio_writer%obj = open_lcio_writer_new (char (filename) // &
c_null_char, 9_c_int)
end subroutine lcio_writer_open_out
@ %def lcio_writer_open_out
@ Destructor:
<<LCIO interface: interfaces>>=
interface
subroutine lcio_writer_delete (io_obj) bind(C)
import
type(c_ptr), value :: io_obj
end subroutine lcio_writer_delete
end interface
@ %def lcio_writer_delete
<<LCIO interface: public>>=
public :: lcio_writer_close
<<LCIO interface: procedures>>=
subroutine lcio_writer_close (lciowriter)
type(lcio_writer_t), intent(inout) :: lciowriter
call lcio_writer_delete (lciowriter%obj)
end subroutine lcio_writer_close
@ %def lcio_writer_close
@ Write a single event to the LCIO writer.
<<LCIO interface: interfaces>>=
interface
subroutine lcio_write_event (io_obj, evt_obj) bind(C)
import
type(c_ptr), value :: io_obj, evt_obj
end subroutine lcio_write_event
end interface
@ %def lcio_write_event
<<LCIO interface: public>>=
public :: lcio_event_write
<<LCIO interface: procedures>>=
subroutine lcio_event_write (wrt, evt)
type(lcio_writer_t), intent(inout) :: wrt
type(lcio_event_t), intent(in) :: evt
call lcio_write_event (wrt%obj, evt%obj)
end subroutine lcio_event_write
@ %def lcio_event_write
@
\subsection{LCIO Reader type}
There is a specific LCIO Reader type for handling the input of
LCEventImpl objects (i.e., Monte Carlo event samples) from file. Opening
the file is done by the constructor, closing by the destructor.
<<LCIO interface: public>>=
public :: lcio_reader_t
<<LCIO interface: types>>=
type :: lcio_reader_t
private
type(c_ptr) :: obj
end type lcio_reader_t
@ %def lcio_reader_t
@ Constructor for an output associated to a file.
<<LCIO interface: interfaces>>=
interface
type(c_ptr) function open_lcio_reader (filename) bind(C)
import
character(c_char), dimension(*), intent(in) :: filename
end function open_lcio_reader
end interface
@ %def open_lcio_reader
<<LCIO interface: public>>=
public :: lcio_open_file
<<LCIO interface: procedures>>=
subroutine lcio_open_file (lcio_reader, filename)
type(lcio_reader_t), intent(out) :: lcio_reader
type(string_t), intent(in) :: filename
lcio_reader%obj = open_lcio_reader (char (filename) // c_null_char)
end subroutine lcio_open_file
@ %def lcio_open_file
@ Destructor:
<<LCIO interface: interfaces>>=
interface
subroutine lcio_reader_delete (io_obj) bind(C)
import
type(c_ptr), value :: io_obj
end subroutine lcio_reader_delete
end interface
@ %def lcio_reader_delete
<<LCIO interface: public>>=
public :: lcio_reader_close
<<LCIO interface: procedures>>=
subroutine lcio_reader_close (lcioreader)
type(lcio_reader_t), intent(inout) :: lcioreader
call lcio_reader_delete (lcioreader%obj)
end subroutine lcio_reader_close
@ %def lcio_reader_close
@
@ Read a single event from the event file. Return true if successful.
<<LCIO interface: interfaces>>=
interface
type(c_ptr) function read_lcio_event (io_obj) bind(C)
import
type(c_ptr), value :: io_obj
end function read_lcio_event
end interface
@ %def read_lcio_event
<<LCIO interface: public>>=
public :: lcio_read_event
<<LCIO interface: procedures>>=
subroutine lcio_read_event (lcrdr, evt, ok)
type(lcio_reader_t), intent(inout) :: lcrdr
type(lcio_event_t), intent(out) :: evt
logical, intent(out) :: ok
evt%obj = read_lcio_event (lcrdr%obj)
ok = c_associated (evt%obj)
end subroutine lcio_read_event
@ %def lcio_read_event
@ Get the event index.
<<LCIO interface: interfaces>>=
interface
integer(c_int) function lcio_event_get_event_number (evt_obj) bind(C)
import
type(c_ptr), value :: evt_obj
end function lcio_event_get_event_number
end interface
@ %def lcio_event_get_event_number
<<LCIO interface: public>>=
public :: lcio_event_get_event_index
<<LCIO interface: procedures>>=
function lcio_event_get_event_index (evt) result (i_evt)
integer :: i_evt
type(lcio_event_t), intent(in) :: evt
i_evt = lcio_event_get_event_number (evt%obj)
end function lcio_event_get_event_index
@ %def lcio_event_get_event_index
@ Extract the process ID. This is stored (at the moment abusively) in the
RUN ID as well as in an additional event parameter.
<<LCIO interface: interfaces>>=
interface
integer(c_int) function lcio_event_signal_process_id (evt_obj) bind(C)
import
type(c_ptr), value :: evt_obj
end function lcio_event_signal_process_id
end interface
@ %def lcio_event_signal_process_id
<<LCIO interface: public>>=
public :: lcio_event_get_process_id
<<LCIO interface: procedures>>=
function lcio_event_get_process_id (evt) result (i_proc)
integer :: i_proc
type(lcio_event_t), intent(in) :: evt
i_proc = lcio_event_signal_process_id (evt%obj)
end function lcio_event_get_process_id
@ %def lcio_event_get_process_id
@ Number of particles in an LCIO event.
<<LCIO interface: interfaces>>=
interface
integer(c_int) function lcio_event_get_n_particles (evt_obj) bind(C)
import
type(c_ptr), value :: evt_obj
end function lcio_event_get_n_particles
end interface
@ %def lcio_event_get_n_particles
<<LCIO interface:>>=
@
<<LCIO interface: public>>=
public :: lcio_event_get_n_tot
<<LCIO interface: procedures>>=
function lcio_event_get_n_tot (evt) result (n_tot)
integer :: n_tot
type(lcio_event_t), intent(in) :: evt
n_tot = lcio_event_get_n_particles (evt%obj)
end function lcio_event_get_n_tot
@ %def lcio_event_get_n_tot
@ Extracting $\alpha_s$ and the scale.
<<LCIO interface: interfaces>>=
interface
function lcio_event_get_alpha_qcd (evt_obj) result (as) bind(C)
import
real(c_double) :: as
type(c_ptr), value :: evt_obj
end function lcio_event_get_alpha_qcd
end interface
interface
function lcio_event_get_scale (evt_obj) result (scale) bind(C)
import
real(c_double) :: scale
type(c_ptr), value :: evt_obj
end function lcio_event_get_scale
end interface
@ %def lcio_event_get_alpha_qcd lcio_event_get_scale
@
<<LCIO interface: public>>=
public :: lcio_event_get_alphas
<<LCIO interface: procedures>>=
function lcio_event_get_alphas (evt) result (as)
type(lcio_event_t), intent(in) :: evt
real(default) :: as
as = lcio_event_get_alpha_qcd (evt%obj)
end function lcio_event_get_alphas
@ %def lcio_event_get_alphas
@
<<LCIO interface: public>>=
public :: lcio_event_get_scaleval
<<LCIO interface: procedures>>=
function lcio_event_get_scaleval (evt) result (scale)
type(lcio_event_t), intent(in) :: evt
real(default) :: scale
scale = lcio_event_get_scale (evt%obj)
end function lcio_event_get_scaleval
@ %def lcio_event_get_scaleval
@ Extracting particles by index from an LCIO event.
<<LCIO interface: interfaces>>=
interface
type(c_ptr) function lcio_event_particle_k (evt_obj, k) bind(C)
import
type(c_ptr), value :: evt_obj
integer(c_int), value :: k
end function lcio_event_particle_k
end interface
@ %def lcio_event_particle_k
@
<<LCIO interface: public>>=
public :: lcio_event_get_particle
<<LCIO interface: procedures>>=
function lcio_event_get_particle (evt, n) result (prt)
type(lcio_event_t), intent(in) :: evt
integer, intent(in) :: n
type(lcio_particle_t) :: prt
prt%obj = lcio_event_particle_k (evt%obj, int (n, c_int))
end function lcio_event_get_particle
@ %def lcio_event_get_particle
@
\subsection{Unit tests}
Test module, followed by the corresponding implementation module.
<<[[lcio_interface_ut.f90]]>>=
<<File header>>
module lcio_interface_ut
use unit_tests
use lcio_interface_uti
<<Standard module head>>
<<LCIO interface: public test>>
contains
<<LCIO interface: test driver>>
end module lcio_interface_ut
@ %def lcio_interface_ut
@
<<[[lcio_interface_uti.f90]]>>=
<<File header>>
module lcio_interface_uti
<<Use kinds>>
<<Use strings>>
use io_units
use lorentz
use flavors
use colors
use polarizations
use lcio_interface
<<Standard module head>>
<<LCIO interface: test declarations>>
contains
<<LCIO interface: tests>>
end module lcio_interface_uti
@ %def lcio_interface_ut
@ API: driver for the unit tests below.
<<LCIO interface: public test>>=
public :: lcio_interface_test
<<LCIO interface: test driver>>=
subroutine lcio_interface_test (u, results)
integer, intent(in) :: u
type(test_results_t), intent(inout) :: results
<<LCIO interface: execute tests>>
end subroutine lcio_interface_test
@ %def lcio_interface_test
@
<<LCIO interface: execute tests>>=
call test (lcio_interface_1, "lcio_interface_1", &
"check LCIO interface", &
u, results)
<<LCIO interface: test declarations>>=
public :: lcio_interface_1
<<LCIO interface: tests>>=
subroutine lcio_interface_1 (u)
use physics_defs, only: VECTOR
use model_data, only: field_data_t
integer, intent(in) :: u
integer :: u_file, iostat
type(lcio_event_t) :: evt
type(lcio_particle_t) :: prt1, prt2, prt3, prt4, prt5, prt6, prt7, prt8
type(flavor_t) :: flv
type(color_t) :: col
type(polarization_t) :: pol
type(field_data_t), target :: photon_data
character(220) :: buffer
write (u, "(A)") "* Test output: LCIO interface"
write (u, "(A)") "* Purpose: test LCIO interface"
write (u, "(A)")
write (u, "(A)") "* Initialization"
write (u, "(A)")
! Initialize a photon flavor object and some polarization
call photon_data%init (var_str ("PHOTON"), 22)
call photon_data%set (spin_type=VECTOR)
call photon_data%freeze ()
call flv%init (photon_data)
call pol%init_angles &
(flv, 0.6_default, 1._default, 0.5_default)
! Event initialization
call lcio_event_init (evt, 20, 1, 42)
write (u, "(A)") "* p -> q splitting"
write (u, "(A)")
! $p\to q$ splittings
call particle_init (prt1, &
0._default, 0._default, 7000._default, 7000._default, &
2212, 1._default, 3)
call particle_init (prt2, &
0._default, 0._default,-7000._default, 7000._default, &
2212, 1._default, 3)
call particle_init (prt3, &
.750_default, -1.569_default, 32.191_default, 32.238_default, &
1, -1._default/3._default, 3)
call color_init_from_array (col, [501])
call lcio_particle_set_color (prt3, col)
call lcio_particle_set_parent (prt3, prt1)
call lcio_particle_set_parent (prt3, prt2)
call particle_init (prt4, &
-3.047_default, -19._default, -54.629_default, 57.920_default, &
-2, -2._default/3._default, 3)
call color_init_from_array (col, [-501])
call lcio_particle_set_color (prt4, col)
call lcio_particle_set_parent (prt4, prt1)
call lcio_particle_set_parent (prt4, prt2)
write (u, "(A)") "* Hard interaction"
write (u, "(A)")
! Hard interaction
call particle_init (prt6, &
-3.813_default, 0.113_default, -1.833_default, 4.233_default, &
22, 0._default, 1)
call lcio_polarization_init (prt6, pol)
call particle_init (prt5, &
1.517_default, -20.68_default, -20.605_default, 85.925_default, &
-24, -1._default, 3)
call lcio_particle_set_parent (prt5, prt3)
call lcio_particle_set_parent (prt5, prt4)
call lcio_particle_set_parent (prt6, prt3)
call lcio_particle_set_parent (prt6, prt4)
! $W^-$ decay
call particle_init (prt7, &
-2.445_default, 28.816_default, 6.082_default, 29.552_default, &
1, -1._default/3._default, 1)
call particle_init (prt8, &
3.962_default, -49.498_default, -26.687_default, 56.373_default, &
-2, -2._default/3._default, 1)
call lcio_particle_set_t (prt7, 0.12_default)
call lcio_particle_set_t (prt8, 0.12_default)
call lcio_particle_set_vtx &
(prt7, vector3_moving ([-0.3_default, 0.05_default, 0.004_default]))
call lcio_particle_set_vtx &
(prt8, vector3_moving ([-0.3_default, 0.05_default, 0.004_default]))
call lcio_particle_set_parent (prt7, prt5)
call lcio_particle_set_parent (prt8, prt5)
call lcio_particle_add_to_evt_coll (prt1, evt)
call lcio_particle_add_to_evt_coll (prt2, evt)
call lcio_particle_add_to_evt_coll (prt3, evt)
call lcio_particle_add_to_evt_coll (prt4, evt)
call lcio_particle_add_to_evt_coll (prt5, evt)
call lcio_particle_add_to_evt_coll (prt6, evt)
call lcio_particle_add_to_evt_coll (prt7, evt)
call lcio_particle_add_to_evt_coll (prt8, evt)
call lcio_event_add_coll (evt)
! Event output
write (u, "(A)") "Writing in ASCII form to file 'lcio_test.slcio'"
write (u, "(A)")
call write_lcio_event (evt, var_str ("lcio_test.slcio"))
write (u, "(A)") "Writing completed"
write (u, "(A)")
write (u, "(A)") "* File contents:"
write (u, "(A)")
u_file = free_unit ()
open (u_file, file = "lcio_test.slcio", &
action = "read", status = "old")
do
read (u_file, "(A)", iostat = iostat) buffer
if (trim (buffer) == "") cycle
if (buffer(1:12) == " - timestamp") buffer = "[...]"
if (buffer(1:6) == " date:") buffer = "[...]"
if (iostat /= 0) exit
write (u, "(A)") trim (buffer)
end do
close (u_file)
write (u, "(A)")
write (u, "(A)") "* Cleanup"
write (u, "(A)")
! Wrapup
! call pol%final ()
call lcio_event_final (evt)
write (u, "(A)")
write (u, "(A)") "* Test output end: lcio_interface_1"
contains
subroutine particle_init &
(prt, px, py, pz, E, pdg, charge, status)
type(lcio_particle_t), intent(out) :: prt
real(default), intent(in) :: px, py, pz, E, charge
integer, intent(in) :: pdg, status
type(vector4_t) :: p
p = vector4_moving (E, vector3_moving ([px, py, pz]))
call lcio_particle_init (prt, p, pdg, charge, status)
end subroutine particle_init
end subroutine lcio_interface_1
@ %def lcio_interface_1
@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
\section{HEP Common and Events}
This is a separate module that manages data exchange between the common blocks
and [[event_t]] objects. We separate this from the previous module in order
to avoid a circular module dependency. It also contains the functions
necessary for communication between [[hepmc_event_t]] and
[[event_t]] or [[lcio_event_t]] and [[event_t]] as well as
[[particle_set_t]] and [[particle_t]] objects.
<<[[hep_events.f90]]>>=
<<File header>>
module hep_events
<<Use kinds>>
<<Use strings>>
use diagnostics
use lorentz
use numeric_utils
use flavors
use colors
use helicities
use polarizations
use model_data
use subevents, only: PRT_BEAM, PRT_INCOMING, PRT_OUTGOING
use subevents, only: PRT_UNDEFINED
use subevents, only: PRT_VIRTUAL, PRT_RESONANT, PRT_BEAM_REMNANT
use particles
use hep_common
use hepmc_interface
use lcio_interface
use event_base
<<Standard module head>>
<<HEP events: public>>
contains
<<HEP events: procedures>>
end module hep_events
@ %def hep_events
@
\subsection{Data Transfer: events}
Fill the HEPEUP block, given a \whizard\ event object.
<<HEP events: public>>=
public :: hepeup_from_event
<<HEP events: procedures>>=
subroutine hepeup_from_event &
(event, keep_beams, keep_remnants, process_index)
class(generic_event_t), intent(in), target :: event
logical, intent(in), optional :: keep_beams
logical, intent(in), optional :: keep_remnants
integer, intent(in), optional :: process_index
type(particle_set_t), pointer :: particle_set
real(default) :: scale, alpha_qcd
if (event%has_valid_particle_set ()) then
particle_set => event%get_particle_set_ptr ()
call hepeup_from_particle_set (particle_set, keep_beams, keep_remnants)
if (present (process_index)) then
call hepeup_set_event_parameters (proc_id = process_index)
end if
scale = event%get_fac_scale ()
if (.not. vanishes (scale)) then
call hepeup_set_event_parameters (scale = scale)
end if
alpha_qcd = event%get_alpha_s ()
if (.not. vanishes (alpha_qcd)) then
call hepeup_set_event_parameters (alpha_qcd = alpha_qcd)
end if
if (event%weight_prc_is_known ()) then
call hepeup_set_event_parameters (weight = event%get_weight_prc ())
end if
else
call msg_bug ("HEPEUP: event incomplete")
end if
end subroutine hepeup_from_event
@ %def hepeup_from_event
@ Reverse.
Note: The current implementation sets the particle set of the hard
process and is therefore not useful if the event on file is dressed.
This should be reconsidered.
Note: setting of scale or alpha is not yet supported by the
[[event_t]] object. Ticket \#628.
<<HEP events: public>>=
public :: hepeup_to_event
<<HEP events: procedures>>=
subroutine hepeup_to_event &
(event, fallback_model, process_index, recover_beams, &
use_alpha_s, use_scale)
class(generic_event_t), intent(inout), target :: event
class(model_data_t), intent(in), target :: fallback_model
integer, intent(out), optional :: process_index
logical, intent(in), optional :: recover_beams
logical, intent(in), optional :: use_alpha_s
logical, intent(in), optional :: use_scale
class(model_data_t), pointer :: model
real(default) :: weight, scale, alpha_qcd
type(particle_set_t) :: particle_set
model => event%get_model_ptr ()
call hepeup_to_particle_set &
(particle_set, recover_beams, model, fallback_model)
call event%set_hard_particle_set (particle_set)
call particle_set%final ()
if (present (process_index)) then
call hepeup_get_event_parameters (proc_id = process_index)
end if
call hepeup_get_event_parameters (weight = weight, &
scale = scale, alpha_qcd = alpha_qcd)
call event%set_weight_ref (weight)
if (present (use_alpha_s)) then
if (use_alpha_s .and. alpha_qcd > 0) &
call event%set_alpha_qcd_forced (alpha_qcd)
end if
if (present (use_scale)) then
if (use_scale .and. scale > 0) &
call event%set_scale_forced (scale)
end if
end subroutine hepeup_to_event
@ %def hepeup_to_event
@ Fill the HEPEVT (event) common block.
The [[i_evt]] argument overrides the index stored in the [[event]] object.
<<HEP events: public>>=
public :: hepevt_from_event
<<HEP events: procedures>>=
subroutine hepevt_from_event &
(event, process_index, i_evt, keep_beams, keep_remnants, &
ensure_order, fill_hepev4)
class(generic_event_t), intent(in), target :: event
integer, intent(in), optional :: i_evt, process_index
logical, intent(in), optional :: keep_beams
logical, intent(in), optional :: keep_remnants
logical, intent(in), optional :: ensure_order
logical, intent(in), optional :: fill_hepev4
type(particle_set_t), pointer :: particle_set
real(default) :: alpha_qcd, scale
if (event%has_valid_particle_set ()) then
particle_set => event%get_particle_set_ptr ()
call hepevt_from_particle_set (particle_set, keep_beams, &
keep_remnants, ensure_order, fill_hepev4)
if (present (process_index)) then
call hepevt_set_event_parameters (proc_id = process_index)
end if
if (event%weight_prc_is_known ()) then
call hepevt_set_event_parameters (weight = event%get_weight_prc ())
end if
if (event%sqme_prc_is_known ()) then
call hepevt_set_event_parameters &
(function_value = event%get_sqme_prc ())
end if
scale = event%get_fac_scale ()
if (.not. vanishes (scale)) then
call hepevt_set_event_parameters (scale = scale)
end if
alpha_qcd = event%get_alpha_s ()
if (.not. vanishes (alpha_qcd)) then
call hepevt_set_event_parameters (alpha_qcd = alpha_qcd)
end if
if (present (i_evt)) then
call hepevt_set_event_parameters (i_evt = i_evt)
else if (event%has_index ()) then
call hepevt_set_event_parameters (i_evt = event%get_index ())
else
call hepevt_set_event_parameters (i_evt = 0)
end if
else
call msg_bug ("HEPEVT: event incomplete")
end if
end subroutine hepevt_from_event
@ %def hepevt_from_event
@
\subsubsection{HepMC format}
The master output function fills a HepMC GenEvent object that is
already initialized, but has no vertices in it.
We first set up the vertex lists and enter the vertices into the HepMC
event. Then, we assign first all incoming particles and then all
outgoing particles to their associated vertices. Particles which have
neither parent nor children entries (this should not happen) are
dropped.
Finally, we insert the beam particles. If there are none, use the incoming
particles instead.
@ Transform a particle into a [[hepmc_particle]] object, including
color and polarization. The HepMC status is equivalent to the HEPEVT
status, in particular: 0 = null entry, 1 = physical particle, 2 =
decayed/fragmented SM hadron, tau or muon, 3 = other unphysical particle
entry, 4 = incoming particles, 11 = intermediate resonance such as squarks.
The use of 11 for intermediate resonances is as done by HERWIG, see
http://herwig.hepforge.org/trac/wiki/FaQs.
<<HEP events: procedures>>=
subroutine particle_to_hepmc (prt, hprt)
type(particle_t), intent(in) :: prt
type(hepmc_particle_t), intent(out) :: hprt
integer :: hepmc_status
select case (prt%get_status ())
case (PRT_UNDEFINED)
hepmc_status = 0
case (PRT_OUTGOING)
hepmc_status = 1
case (PRT_BEAM)
hepmc_status = 4
case (PRT_RESONANT)
if (abs(prt%get_pdg()) == 13 .or. &
abs(prt%get_pdg()) == 15) then
hepmc_status = 2
else
hepmc_status = 11
end if
case default
hepmc_status = 3
end select
call hepmc_particle_init (hprt, &
prt%get_momentum (), prt%get_pdg (), &
hepmc_status)
call hepmc_particle_set_color (hprt, prt%get_color ())
select case (prt%get_polarization_status ())
case (PRT_DEFINITE_HELICITY)
call hepmc_particle_set_polarization (hprt, &
prt%get_helicity ())
case (PRT_GENERIC_POLARIZATION)
call hepmc_particle_set_polarization (hprt, &
prt%get_polarization ())
end select
end subroutine particle_to_hepmc
@ %def particle_to_hepmc
@
<<HEP events: public>>=
public :: hepmc_event_from_particle_set
<<HEP events: procedures>>=
subroutine hepmc_event_from_particle_set &
(evt, particle_set, cross_section, error)
type(hepmc_event_t), intent(inout) :: evt
type(particle_set_t), intent(in) :: particle_set
real(default), intent(in), optional :: cross_section, error
type(hepmc_vertex_t), dimension(:), allocatable :: v
type(hepmc_particle_t), dimension(:), allocatable :: hprt
type(hepmc_particle_t), dimension(2) :: hbeam
type(vector4_t), dimension(:), allocatable :: vtx
logical, dimension(:), allocatable :: is_beam
integer, dimension(:), allocatable :: v_from, v_to
integer :: n_vertices, n_tot, i
n_tot = particle_set%get_n_tot ()
allocate (v_from (n_tot), v_to (n_tot))
call particle_set%assign_vertices (v_from, v_to, n_vertices)
allocate (hprt (n_tot))
allocate (vtx (n_vertices))
vtx = vector4_null
do i = 1, n_tot
if (v_to(i) /= 0 .or. v_from(i) /= 0) then
call particle_to_hepmc (particle_set%prt(i), hprt(i))
if (v_to(i) /= 0) then
vtx(v_to(i)) = particle_set%prt(i)%get_vertex ()
end if
end if
end do
if (present (cross_section) .and. present(error)) &
call hepmc_event_set_cross_section (evt, cross_section, error)
allocate (v (n_vertices))
do i = 1, n_vertices
call hepmc_vertex_init (v(i), vtx(i))
call hepmc_event_add_vertex (evt, v(i))
end do
allocate (is_beam (n_tot))
is_beam = particle_set%prt(1:n_tot)%get_status () == PRT_BEAM
if (.not. any (is_beam)) then
is_beam = particle_set%prt(1:n_tot)%get_status () == PRT_INCOMING
end if
if (count (is_beam) == 2) then
hbeam = pack (hprt, is_beam)
call hepmc_event_set_beam_particles (evt, hbeam(1), hbeam(2))
end if
do i = 1, n_tot
if (v_to(i) /= 0) then
call hepmc_vertex_add_particle_in (v(v_to(i)), hprt(i))
end if
end do
do i = 1, n_tot
if (v_from(i) /= 0) then
call hepmc_vertex_add_particle_out (v(v_from(i)), hprt(i))
end if
end do
FIND_SIGNAL_PROCESS: do i = 1, n_tot
if (particle_set%prt(i)%get_status () == PRT_INCOMING) then
call hepmc_event_set_signal_process_vertex (evt, v(v_to(i)))
exit FIND_SIGNAL_PROCESS
end if
end do FIND_SIGNAL_PROCESS
end subroutine hepmc_event_from_particle_set
@ %def hepmc_event_from_particle_set
@ Initialize a particle from a HepMC particle object. The model is
necessary for making a fully qualified flavor component. We have the
additional flag [[polarized]] which tells whether the polarization
information should be interpreted or ignored, and the lookup array of
barcodes. Note that the lookup array is searched linearly, a possible
bottleneck for large particle arrays. If necessary, the barcode array
could be replaced by a hash table.
<<HEP events: procedures>>=
subroutine particle_from_hepmc_particle &
(prt, hprt, model, fallback_model, polarization, barcode)
type(particle_t), intent(out) :: prt
type(hepmc_particle_t), intent(in) :: hprt
type(model_data_t), intent(in), target :: model
type(model_data_t), intent(in), target :: fallback_model
type(hepmc_vertex_t) :: vtx
integer, intent(in) :: polarization
integer, dimension(:), intent(in) :: barcode
type(hepmc_polarization_t) :: hpol
type(flavor_t) :: flv
type(color_t) :: col
type(helicity_t) :: hel
type(polarization_t) :: pol
type(vector4_t) :: vertex
integer :: n_parents, n_children
integer, dimension(:), allocatable :: &
parent_barcode, child_barcode, parent, child
integer :: i
select case (hepmc_particle_get_status (hprt))
case (1); call prt%set_status (PRT_OUTGOING)
case (2); call prt%set_status (PRT_RESONANT)
case (3); call prt%set_status (PRT_VIRTUAL)
end select
if (hepmc_particle_is_beam (hprt)) call prt%set_status (PRT_BEAM)
call flv%init (hepmc_particle_get_pdg (hprt), model, fallback_model)
call col%init (hepmc_particle_get_color (hprt))
call prt%set_flavor (flv)
call prt%set_color (col)
call prt%set_polarization (polarization)
select case (polarization)
case (PRT_DEFINITE_HELICITY)
hpol = hepmc_particle_get_polarization (hprt)
call hepmc_polarization_to_hel (hpol, prt%get_flv (), hel)
call prt%set_helicity (hel)
call hepmc_polarization_final (hpol)
case (PRT_GENERIC_POLARIZATION)
hpol = hepmc_particle_get_polarization (hprt)
call hepmc_polarization_to_pol (hpol, prt%get_flv (), pol)
call prt%set_pol (pol)
call hepmc_polarization_final (hpol)
end select
call prt%set_momentum (hepmc_particle_get_momentum (hprt), &
hepmc_particle_get_mass_squared (hprt))
n_parents = hepmc_particle_get_n_parents (hprt)
n_children = hepmc_particle_get_n_children (hprt)
allocate (parent_barcode (n_parents), parent (n_parents))
allocate (child_barcode (n_children), child (n_children))
parent_barcode = hepmc_particle_get_parent_barcodes (hprt)
child_barcode = hepmc_particle_get_child_barcodes (hprt)
do i = 1, size (barcode)
where (parent_barcode == barcode(i)) parent = i
where (child_barcode == barcode(i)) child = i
end do
call prt%set_parents (parent)
call prt%set_children (child)
if (prt%get_status () == PRT_VIRTUAL .and. n_parents == 0) &
call prt%set_status (PRT_INCOMING)
vtx = hepmc_particle_get_decay_vertex (hprt)
if (hepmc_vertex_is_valid (vtx)) then
vertex = hepmc_vertex_to_vertex (vtx)
if (vertex /= vector4_null) call prt%set_vertex (vertex)
end if
end subroutine particle_from_hepmc_particle
@ %def particle_from_hepmc_particle
@ If a particle set is initialized from a HepMC event record, we have
to specify the treatment of polarization (unpolarized or density
matrix) which is common to all particles. Correlated polarization
information is not available.
There is some complication in reconstructing incoming particles and
beam remnants. First of all, they all will be tagged as virtual. We
then define an incoming particle as
<<HEP events: public>>=
public :: hepmc_event_to_particle_set
<<HEP events: procedures>>=
subroutine hepmc_event_to_particle_set &
(particle_set, evt, model, fallback_model, polarization)
type(particle_set_t), intent(inout), target :: particle_set
type(hepmc_event_t), intent(in) :: evt
class(model_data_t), intent(in), target :: model, fallback_model
integer, intent(in) :: polarization
type(hepmc_event_particle_iterator_t) :: it
type(hepmc_vertex_t) :: v
type(hepmc_vertex_particle_in_iterator_t) :: v_it
type(hepmc_particle_t) :: prt
integer, dimension(:), allocatable :: barcode
integer :: n_tot, i, bc
n_tot = 0
call hepmc_event_particle_iterator_init (it, evt)
do while (hepmc_event_particle_iterator_is_valid (it))
n_tot = n_tot + 1
call hepmc_event_particle_iterator_advance (it)
end do
allocate (barcode (n_tot))
call hepmc_event_particle_iterator_reset (it)
do i = 1, n_tot
barcode(i) = hepmc_particle_get_barcode &
(hepmc_event_particle_iterator_get (it))
call hepmc_event_particle_iterator_advance (it)
end do
allocate (particle_set%prt (n_tot))
call hepmc_event_particle_iterator_reset (it)
do i = 1, n_tot
prt = hepmc_event_particle_iterator_get (it)
call particle_from_hepmc_particle (particle_set%prt(i), &
prt, model, fallback_model, polarization, barcode)
call hepmc_event_particle_iterator_advance (it)
end do
call hepmc_event_particle_iterator_final (it)
v = hepmc_event_get_signal_process_vertex (evt)
if (hepmc_vertex_is_valid (v)) then
call hepmc_vertex_particle_in_iterator_init (v_it, v)
do while (hepmc_vertex_particle_in_iterator_is_valid (v_it))
prt = hepmc_vertex_particle_in_iterator_get (v_it)
bc = hepmc_particle_get_barcode &
(hepmc_vertex_particle_in_iterator_get (v_it))
do i = 1, size(barcode)
if (bc == barcode(i)) &
call particle_set%prt(i)%set_status (PRT_INCOMING)
end do
call hepmc_vertex_particle_in_iterator_advance (v_it)
end do
call hepmc_vertex_particle_in_iterator_final (v_it)
end if
do i = 1, n_tot
if (particle_set%prt(i)%get_status () == PRT_VIRTUAL &
.and. particle_set%prt(i)%get_n_children () == 0) &
call particle_set%prt(i)%set_status (PRT_OUTGOING)
end do
particle_set%n_tot = n_tot
particle_set%n_beam = &
count (particle_set%prt%get_status () == PRT_BEAM)
particle_set%n_in = &
count (particle_set%prt%get_status () == PRT_INCOMING)
particle_set%n_out = &
count (particle_set%prt%get_status () == PRT_OUTGOING)
particle_set%n_vir = &
particle_set%n_tot - particle_set%n_in - particle_set%n_out
end subroutine hepmc_event_to_particle_set
@ %def hepmc_event_to_particle_set
@ Fill a WHIZARD event from a HepMC event record. In HepMC the weights
are in a weight container. If the size of this container is larger than
one, it is ambiguous to assign the event a specific weight. For now we
only allow to read in unweighted events.
<<HEP events: public>>=
public :: hepmc_to_event
<<HEP events: procedures>>=
subroutine hepmc_to_event &
(event, hepmc_event, fallback_model, process_index, &
recover_beams, use_alpha_s, use_scale)
class(generic_event_t), intent(inout), target :: event
type(hepmc_event_t), intent(inout) :: hepmc_event
class(model_data_t), intent(in), target :: fallback_model
integer, intent(out), optional :: process_index
logical, intent(in), optional :: recover_beams
logical, intent(in), optional :: use_alpha_s
logical, intent(in), optional :: use_scale
class(model_data_t), pointer :: model
real(default) :: scale, alpha_qcd
type(particle_set_t) :: particle_set
model => event%get_model_ptr ()
call event%set_index (hepmc_event_get_event_index (hepmc_event))
call hepmc_event_to_particle_set (particle_set, &
hepmc_event, model, fallback_model, PRT_DEFINITE_HELICITY)
call event%set_hard_particle_set (particle_set)
call particle_set%final ()
call event%set_weight_ref (1._default)
alpha_qcd = hepmc_event_get_alpha_qcd (hepmc_event)
scale = hepmc_event_get_scale (hepmc_event)
if (present (use_alpha_s)) then
if (use_alpha_s .and. alpha_qcd > 0) &
call event%set_alpha_qcd_forced (alpha_qcd)
end if
if (present (use_scale)) then
if (use_scale .and. scale > 0) &
call event%set_scale_forced (scale)
end if
end subroutine hepmc_to_event
@ %def hepmc_to_event
@
\subsubsection{LCIO event format}
The master output function fills a LCIO event object that is
already initialized, but has no particles in it.
In contrast to HepMC in LCIO there are no vertices (except for tracker
and other detector specifications). So we assign first all incoming
particles and then all outgoing particles to LCIO particle types.
Particles which have neither parent nor children entries (this
should not happen) are dropped. Finally, we insert the beam particles.
If there are none, use the incoming particles instead.
Transform a particle into a [[lcio_particle]] object, including
color and polarization. The LCIO status is equivalent to the HepMC
status, in particular: 0 = null entry, 1 = physical particle, 2 =
decayed/fragmented SM hadron, tau or muon, 3 = other unphysical particle
entry, 4 = incoming particles, 11 = intermediate resonance such as squarks.
The use of 11 for intermediate resonances is as done by HERWIG, see
http://herwig.hepforge.org/trac/wiki/FaQs.
A beam-remnant particle (e.g., ISR photon) that has no children is
tagged as outgoing, otherwise unphysical.
<<HEP events: public>>=
public :: particle_to_lcio
<<HEP events: procedures>>=
subroutine particle_to_lcio (prt, lprt)
type(particle_t), intent(in) :: prt
type(lcio_particle_t), intent(out) :: lprt
integer :: lcio_status
type(vector4_t) :: vtx
select case (prt%get_status ())
case (PRT_UNDEFINED)
lcio_status = 0
case (PRT_OUTGOING)
lcio_status = 1
case (PRT_BEAM_REMNANT)
if (prt%get_n_children () == 0) then
lcio_status = 1
else
lcio_status = 3
end if
case (PRT_BEAM)
lcio_status = 4
case (PRT_RESONANT)
lcio_status = 2
case default
lcio_status = 3
end select
call lcio_particle_init (lprt, &
prt%get_momentum (), &
prt%get_pdg (), &
prt%flv%get_charge (), &
lcio_status)
call lcio_particle_set_color (lprt, prt%get_color ())
vtx = prt%get_vertex ()
call lcio_particle_set_vtx (lprt, space_part (vtx))
call lcio_particle_set_t (lprt, vtx%p(0))
select case (prt%get_polarization_status ())
case (PRT_DEFINITE_HELICITY)
call lcio_polarization_init (lprt, prt%get_helicity ())
case (PRT_GENERIC_POLARIZATION)
call lcio_polarization_init (lprt, prt%get_polarization ())
end select
end subroutine particle_to_lcio
@ %def particle_to_lcio
@
@ Initialize a particle from a LCIO particle object. The model is
necessary for making a fully qualified flavor component.
<<HEP events: public>>=
public :: particle_from_lcio_particle
<<HEP events: procedures>>=
subroutine particle_from_lcio_particle &
(prt, lprt, model, daughters, parents, polarization)
type(particle_t), intent(out) :: prt
type(lcio_particle_t), intent(in) :: lprt
type(model_data_t), intent(in), target :: model
integer, dimension(:), intent(in) :: daughters, parents
type(vector4_t) :: vtx4
type(flavor_t) :: flv
type(color_t) :: col
type(helicity_t) :: hel
type(polarization_t) :: pol
integer, intent(in) :: polarization
select case (lcio_particle_get_status (lprt))
case (1); call prt%set_status (PRT_OUTGOING)
case (2); call prt%set_status (PRT_RESONANT)
case (3); call prt%set_status (PRT_VIRTUAL)
end select
call flv%init (lcio_particle_get_pdg (lprt), model)
call col%init (lcio_particle_get_flow (lprt))
if (flv%is_beam_remnant ()) call prt%set_status (PRT_BEAM_REMNANT)
call prt%set_flavor (flv)
call prt%set_color (col)
call prt%set_polarization (polarization)
select case (polarization)
case (PRT_DEFINITE_HELICITY)
call lcio_particle_to_hel (lprt, prt%get_flv (), hel)
call prt%set_helicity (hel)
case (PRT_GENERIC_POLARIZATION)
call lcio_particle_to_pol (lprt, prt%get_flv (), pol)
call prt%set_pol (pol)
end select
call prt%set_momentum (lcio_particle_get_momentum (lprt), &
lcio_particle_get_mass_squared (lprt))
call prt%set_parents (parents)
call prt%set_children (daughters)
if (prt%get_status () == PRT_VIRTUAL .and. size(parents) == 0) &
call prt%set_status (PRT_INCOMING)
vtx4 = vector4_moving (lcio_particle_get_time (lprt), &
lcio_particle_get_vertex (lprt))
if (vtx4 /= vector4_null) call prt%set_vertex (vtx4)
end subroutine particle_from_lcio_particle
@ %def particle_from_lcio_particle
@
<<HEP events: public>>=
public :: lcio_event_from_particle_set
<<HEP events: procedures>>=
subroutine lcio_event_from_particle_set (evt, particle_set)
type(lcio_event_t), intent(inout) :: evt
type(particle_set_t), intent(in) :: particle_set
type(lcio_particle_t), dimension(:), allocatable :: lprt
type(particle_set_t), target :: pset_filtered
integer, dimension(:), allocatable :: parent
integer :: n_tot, i, j, n_beam, n_parents, type, beam_count
call particle_set%filter_particles ( pset_filtered, real_parents = .true. , &
keep_beams = .true. , keep_virtuals = .false.)
n_tot = pset_filtered%n_tot
n_beam = count (pset_filtered%prt%get_status () == PRT_BEAM)
if (n_beam == 0) then
type = PRT_INCOMING
else
type = PRT_BEAM
end if
beam_count = 0
allocate (lprt (n_tot))
do i = 1, n_tot
call particle_to_lcio (pset_filtered%prt(i), lprt(i))
n_parents = pset_filtered%prt(i)%get_n_parents ()
if (n_parents /= 0) then
allocate (parent (n_parents))
parent = pset_filtered%prt(i)%get_parents ()
do j = 1, n_parents
call lcio_particle_set_parent (lprt(i), lprt(parent(j)))
end do
deallocate (parent)
end if
if (pset_filtered%prt(i)%get_status () == type) then
beam_count = beam_count + 1
call lcio_event_set_beam &
(evt, pset_filtered%prt(i)%get_pdg (), beam_count)
end if
call lcio_particle_add_to_evt_coll (lprt(i), evt)
end do
call lcio_event_add_coll (evt)
end subroutine lcio_event_from_particle_set
@ %def lcio_event_from_particle_set
@ If a particle set is initialized from a LCIO event record, we have
to specify the treatment of polarization (unpolarized or density
matrix) which is common to all particles. Correlated polarization
information is not available.
<<HEP events: public>>=
public :: lcio_event_to_particle_set
<<HEP events: procedures>>=
subroutine lcio_event_to_particle_set &
(particle_set, evt, model, fallback_model, polarization)
type(particle_set_t), intent(inout), target :: particle_set
type(lcio_event_t), intent(in) :: evt
class(model_data_t), intent(in), target :: model, fallback_model
integer, intent(in) :: polarization
type(lcio_particle_t) :: prt
integer, dimension(:), allocatable :: parents, daughters
integer :: n_tot, i, j, n_parents, n_children
n_tot = lcio_event_get_n_tot (evt)
allocate (particle_set%prt (n_tot))
do i = 1, n_tot
prt = lcio_event_get_particle (evt, i-1)
n_parents = lcio_particle_get_n_parents (prt)
n_children = lcio_particle_get_n_children (prt)
allocate (daughters (n_children))
allocate (parents (n_parents))
if (n_children > 0) then
do j = 1, n_children
daughters(j) = lcio_get_n_children (evt,i,j)
end do
end if
if (n_parents > 0) then
do j = 1, n_parents
parents(j) = lcio_get_n_parents (evt,i,j)
end do
end if
call particle_from_lcio_particle (particle_set%prt(i), prt, model, &
daughters, parents, polarization)
deallocate (daughters, parents)
end do
do i = 1, n_tot
if (particle_set%prt(i)%get_status () == PRT_VIRTUAL) then
CHECK_BEAM: do j = 1, particle_set%prt(i)%get_n_parents ()
if (particle_set%prt(j)%get_status () == PRT_BEAM) &
call particle_set%prt(i)%set_status (PRT_INCOMING)
exit CHECK_BEAM
end do CHECK_BEAM
end if
end do
particle_set%n_tot = n_tot
particle_set%n_beam = &
count (particle_set%prt%get_status () == PRT_BEAM)
particle_set%n_in = &
count (particle_set%prt%get_status () == PRT_INCOMING)
particle_set%n_out = &
count (particle_set%prt%get_status () == PRT_OUTGOING)
particle_set%n_vir = &
particle_set%n_tot - particle_set%n_in - particle_set%n_out
end subroutine lcio_event_to_particle_set
@ %def lcio_event_to_particle_set
@
<<HEP events: public>>=
public :: lcio_to_event
<<HEP events: procedures>>=
subroutine lcio_to_event &
(event, lcio_event, fallback_model, process_index, recover_beams, &
use_alpha_s, use_scale)
class(generic_event_t), intent(inout), target :: event
type(lcio_event_t), intent(inout) :: lcio_event
class(model_data_t), intent(in), target :: fallback_model
integer, intent(out), optional :: process_index
logical, intent(in), optional :: recover_beams
logical, intent(in), optional :: use_alpha_s
logical, intent(in), optional :: use_scale
class(model_data_t), pointer :: model
real(default) :: scale, alpha_qcd
type(particle_set_t) :: particle_set
model => event%get_model_ptr ()
call lcio_event_to_particle_set (particle_set, &
lcio_event, model, fallback_model, PRT_DEFINITE_HELICITY)
call event%set_hard_particle_set (particle_set)
call particle_set%final ()
alpha_qcd = lcio_event_get_alphas (lcio_event)
scale = lcio_event_get_scaleval (lcio_event)
if (present (use_alpha_s)) then
if (use_alpha_s .and. alpha_qcd > 0) &
call event%set_alpha_qcd_forced (alpha_qcd)
end if
if (present (use_scale)) then
if (use_scale .and. scale > 0) &
call event%set_scale_forced (scale)
end if
end subroutine lcio_to_event
@ %def lcio_to_event
@
\subsection{Unit tests}
Test module, followed by the corresponding implementation module.
<<[[hep_events_ut.f90]]>>=
<<File header>>
module hep_events_ut
use unit_tests
use hepmc_interface, only: HEPMC_IS_AVAILABLE
use hep_events_uti
<<Standard module head>>
<<HEP events: public test>>
contains
<<HEP events: test driver>>
end module hep_events_ut
@ %def hep_events_ut
@
<<[[hep_events_uti.f90]]>>=
<<File header>>
module hep_events_uti
<<Use kinds>>
<<Use strings>>
use lorentz
use flavors
use colors
use helicities
use quantum_numbers
use state_matrices, only: FM_SELECT_HELICITY, FM_FACTOR_HELICITY
use interactions
use evaluators
use model_data
use particles
use subevents
use hepmc_interface
use hep_events
<<Standard module head>>
<<HEP events: test declarations>>
contains
<<HEP events: tests>>
end module hep_events_uti
@ %def hep_events_ut
@ API: driver for the unit tests below.
<<HEP events: public test>>=
public :: hep_events_test
<<HEP events: test driver>>=
subroutine hep_events_test (u, results)
integer, intent(in) :: u
type(test_results_t), intent(inout) :: results
<<HEP events: execute tests>>
end subroutine hep_events_test
@ %def particles_test
@ If [[HepMC]] is available, check the routines via [[HepMC]].
Set up a chain of production and decay and factorize the result into
particles. The process is $d\bar d \to Z \to q\bar q$.
<<HEP events: execute tests>>=
if (hepmc_is_available ()) then
call test (hep_events_1, "hep_events_1", &
"check HepMC event routines", &
u, results)
end if
<<HEP events: test declarations>>=
public :: hep_events_1
<<HEP events: tests>>=
subroutine hep_events_1 (u)
use os_interface
integer, intent(in) :: u
type(model_data_t), target :: model
type(flavor_t), dimension(3) :: flv
type(color_t), dimension(3) :: col
type(helicity_t), dimension(3) :: hel
type(quantum_numbers_t), dimension(3) :: qn
type(vector4_t), dimension(3) :: p
type(interaction_t), target :: int1, int2
type(quantum_numbers_mask_t) :: qn_mask_conn
type(evaluator_t), target :: eval
type(interaction_t), pointer :: int
type(particle_set_t) :: particle_set1, particle_set2
type(hepmc_event_t) :: hepmc_event
type(hepmc_iostream_t) :: iostream
real(default) :: cross_section, error, weight
logical :: ok
write (u, "(A)") "* Test output: HEP events"
write (u, "(A)") "* Purpose: test HepMC event routines"
write (u, "(A)")
write (u, "(A)") "* Reading model file"
call model%init_sm_test ()
write (u, "(A)")
write (u, "(A)") "* Initializing production process"
call int1%basic_init (2, 0, 1, set_relations=.true.)
call flv%init ([1, -1, 23], model)
call col%init_col_acl ([0, 0, 0], [0, 0, 0])
call hel(3)%init ( 1, 1)
call qn%init (flv, col, hel)
call int1%add_state (qn, value=(0.25_default, 0._default))
call hel(3)%init ( 1,-1)
call qn%init (flv, col, hel)
call int1%add_state (qn, value=(0._default, 0.25_default))
call hel(3)%init (-1, 1)
call qn%init (flv, col, hel)
call int1%add_state (qn, value=(0._default,-0.25_default))
call hel(3)%init (-1,-1)
call qn%init (flv, col, hel)
call int1%add_state (qn, value=(0.25_default, 0._default))
call hel(3)%init ( 0, 0)
call qn%init (flv, col, hel)
call int1%add_state (qn, value=(0.5_default, 0._default))
call int1%freeze ()
p(1) = vector4_moving (45._default, 45._default, 3)
p(2) = vector4_moving (45._default,-45._default, 3)
p(3) = p(1) + p(2)
call int1%set_momenta (p)
write (u, "(A)")
write (u, "(A)") "* Setup decay process"
call int2%basic_init (1, 0, 2, set_relations=.true.)
call flv%init ([23, 1, -1], model)
call col%init_col_acl ([0, 501, 0], [0, 0, 501])
call hel%init ([1, 1, 1], [1, 1, 1])
call qn%init (flv, col, hel)
call int2%add_state (qn, value=(1._default, 0._default))
call hel%init ([1, 1, 1], [-1,-1,-1])
call qn%init (flv, col, hel)
call int2%add_state (qn, value=(0._default, 0.1_default))
call hel%init ([-1,-1,-1], [1, 1, 1])
call qn%init (flv, col, hel)
call int2%add_state (qn, value=(0._default,-0.1_default))
call hel%init ([-1,-1,-1], [-1,-1,-1])
call qn%init (flv, col, hel)
call int2%add_state (qn, value=(1._default, 0._default))
call hel%init ([0, 1,-1], [0, 1,-1])
call qn%init (flv, col, hel)
call int2%add_state (qn, value=(4._default, 0._default))
call hel%init ([0,-1, 1], [0, 1,-1])
call qn%init (flv, col, hel)
call int2%add_state (qn, value=(2._default, 0._default))
call hel%init ([0, 1,-1], [0,-1, 1])
call qn%init (flv, col, hel)
call int2%add_state (qn, value=(2._default, 0._default))
call hel%init ([0,-1, 1], [0,-1, 1])
call qn%init (flv, col, hel)
call int2%add_state (qn, value=(4._default, 0._default))
call flv%init ([23, 2, -2], model)
call hel%init ([0, 1,-1], [0, 1,-1])
call qn%init (flv, col, hel)
call int2%add_state (qn, value=(0.5_default, 0._default))
call hel%init ([0,-1, 1], [0,-1, 1])
call qn%init (flv, col, hel)
call int2%add_state (qn, value=(0.5_default, 0._default))
call int2%freeze ()
p(2) = vector4_moving (45._default, 45._default, 2)
p(3) = vector4_moving (45._default,-45._default, 2)
call int2%set_momenta (p)
call int2%set_source_link (1, int1, 3)
call int1%basic_write (u)
call int2%basic_write (u)
write (u, "(A)")
write (u, "(A)") "* Concatenate production and decay"
call eval%init_product (int1, int2, qn_mask_conn, &
connections_are_resonant=.true.)
call eval%receive_momenta ()
call eval%evaluate ()
call eval%write (u)
write (u, "(A)")
write (u, "(A)") "* Factorize as subevent (complete, polarized)"
write (u, "(A)")
int => eval%interaction_t
call particle_set1%init &
(ok, int, int, FM_FACTOR_HELICITY, &
[0.2_default, 0.2_default], .false., .true.)
call particle_set1%write (u)
write (u, "(A)")
write (u, "(A)") "* Factorize as subevent (in/out only, selected helicity)"
write (u, "(A)")
int => eval%interaction_t
call particle_set2%init &
(ok, int, int, FM_SELECT_HELICITY, &
[0.9_default, 0.9_default], .false., .false.)
call particle_set2%write (u)
call particle_set2%final ()
write (u, "(A)")
write (u, "(A)") "* Factorize as subevent (complete, selected helicity)"
write (u, "(A)")
int => eval%interaction_t
call particle_set2%init &
(ok, int, int, FM_SELECT_HELICITY, &
[0.7_default, 0.7_default], .false., .true.)
call particle_set2%write (u)
write (u, "(A)")
write (u, "(A)") "* Transfer particle_set to HepMC, print, and output to"
write (u, "(A)") " hep_events.hepmc.dat"
write (u, "(A)")
cross_section = 42.0_default
error = 17.0_default
weight = 1.0_default
call hepmc_event_init (hepmc_event, 11, 127)
call hepmc_event_from_particle_set (hepmc_event, particle_set2, &
cross_section, error)
call hepmc_event_add_weight (hepmc_event, weight)
call hepmc_event_print (hepmc_event)
call hepmc_iostream_open_out &
(iostream , var_str ("hep_events.hepmc.dat"))
call hepmc_iostream_write_event (iostream, hepmc_event)
call hepmc_iostream_close (iostream)
write (u, "(A)")
write (u, "(A)") "* Recover from HepMC file"
write (u, "(A)")
call particle_set2%final ()
call hepmc_event_final (hepmc_event)
call hepmc_event_init (hepmc_event)
call hepmc_iostream_open_in &
(iostream , var_str ("hep_events.hepmc.dat"))
call hepmc_iostream_read_event (iostream, hepmc_event, ok)
call hepmc_iostream_close (iostream)
call hepmc_event_to_particle_set (particle_set2, &
hepmc_event, model, model, PRT_DEFINITE_HELICITY)
call particle_set2%write (u)
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call particle_set1%final ()
call particle_set2%final ()
call eval%final ()
call int1%final ()
call int2%final ()
call hepmc_event_final (hepmc_event)
call model%final ()
write (u, "(A)")
write (u, "(A)") "* Test output end: hep_events_1"
end subroutine hep_events_1
@
@ %def hep_events_1
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
\section{LHEF Input/Output}
The LHEF event record is standardized. It is an ASCII format. We try
our best at using it for both input and output.
<<[[eio_lhef.f90]]>>=
<<File header>>
module eio_lhef
<<Use kinds>>
<<Use strings>>
use io_units
use string_utils
use numeric_utils
use diagnostics
use os_interface
use xml
use event_base
use eio_data
use eio_base
use hep_common
use hep_events
<<Standard module head>>
<<EIO LHEF: public>>
<<EIO LHEF: types>>
contains
<<EIO LHEF: procedures>>
end module eio_lhef
@ %def eio_lhef
@
\subsection{Type}
With sufficient confidence that it will always be three characters, we
can store the version string with a default value.
<<EIO LHEF: public>>=
public :: eio_lhef_t
<<EIO LHEF: types>>=
type, extends (eio_t) :: eio_lhef_t
logical :: writing = .false.
logical :: reading = .false.
integer :: unit = 0
type(event_sample_data_t) :: data
type(cstream_t) :: cstream
character(3) :: version = "1.0"
logical :: keep_beams = .false.
logical :: keep_remnants = .true.
logical :: keep_virtuals = .false.
logical :: recover_beams = .true.
logical :: unweighted = .true.
logical :: write_sqme_ref = .false.
logical :: write_sqme_prc = .false.
logical :: write_sqme_alt = .false.
logical :: use_alphas_from_file = .false.
logical :: use_scale_from_file = .false.
integer :: n_alt = 0
integer, dimension(:), allocatable :: proc_num_id
integer :: i_weight_sqme = 0
type(xml_tag_t) :: tag_lhef, tag_head, tag_init, tag_event
type(xml_tag_t), allocatable :: tag_gen_n, tag_gen_v
type(xml_tag_t), allocatable :: tag_generator, tag_xsecinfo
type(xml_tag_t), allocatable :: tag_sqme_ref, tag_sqme_prc
type(xml_tag_t), dimension(:), allocatable :: tag_sqme_alt, tag_wgts_alt
type(xml_tag_t), allocatable :: tag_weight, tag_weightinfo, tag_weights
contains
<<EIO LHEF: eio lhef: TBP>>
end type eio_lhef_t
@ %def eio_lhef_t
@
\subsection{Specific Methods}
Set parameters that are specifically used with LHEF.
<<EIO LHEF: eio lhef: TBP>>=
procedure :: set_parameters => eio_lhef_set_parameters
<<EIO LHEF: procedures>>=
subroutine eio_lhef_set_parameters (eio, &
keep_beams, keep_remnants, recover_beams, &
use_alphas_from_file, use_scale_from_file, &
version, extension, write_sqme_ref, write_sqme_prc, write_sqme_alt)
class(eio_lhef_t), intent(inout) :: eio
logical, intent(in), optional :: keep_beams
logical, intent(in), optional :: keep_remnants
logical, intent(in), optional :: recover_beams
logical, intent(in), optional :: use_alphas_from_file
logical, intent(in), optional :: use_scale_from_file
character(*), intent(in), optional :: version
type(string_t), intent(in), optional :: extension
logical, intent(in), optional :: write_sqme_ref
logical, intent(in), optional :: write_sqme_prc
logical, intent(in), optional :: write_sqme_alt
if (present (keep_beams)) eio%keep_beams = keep_beams
if (present (keep_remnants)) eio%keep_remnants = keep_remnants
if (present (recover_beams)) eio%recover_beams = recover_beams
if (present (use_alphas_from_file)) &
eio%use_alphas_from_file = use_alphas_from_file
if (present (use_scale_from_file)) &
eio%use_scale_from_file = use_scale_from_file
if (present (version)) then
select case (version)
case ("1.0", "2.0", "3.0")
eio%version = version
case default
call msg_error ("LHEF version " // version &
// " is not supported. Inserting 2.0")
eio%version = "2.0"
end select
end if
if (present (extension)) then
eio%extension = extension
else
eio%extension = "lhe"
end if
if (present (write_sqme_ref)) eio%write_sqme_ref = write_sqme_ref
if (present (write_sqme_prc)) eio%write_sqme_prc = write_sqme_prc
if (present (write_sqme_alt)) eio%write_sqme_alt = write_sqme_alt
end subroutine eio_lhef_set_parameters
@ %def eio_lhef_set_parameters
@
\subsection{Common Methods}
Output. This is not the actual event format, but a readable account
of the current object status.
<<EIO LHEF: eio lhef: TBP>>=
procedure :: write => eio_lhef_write
<<EIO LHEF: procedures>>=
subroutine eio_lhef_write (object, unit)
class(eio_lhef_t), intent(in) :: object
integer, intent(in), optional :: unit
integer :: u, i
u = given_output_unit (unit)
write (u, "(1x,A)") "LHEF event stream:"
if (object%writing) then
write (u, "(3x,A,A)") "Writing to file = ", char (object%filename)
else if (object%reading) then
write (u, "(3x,A,A)") "Reading from file = ", char (object%filename)
else
write (u, "(3x,A)") "[closed]"
end if
write (u, "(3x,A,L1)") "Keep beams = ", object%keep_beams
write (u, "(3x,A,L1)") "Keep remnants = ", object%keep_remnants
write (u, "(3x,A,L1)") "Recover beams = ", object%recover_beams
write (u, "(3x,A,L1)") "Alpha_s from file = ", &
object%use_alphas_from_file
write (u, "(3x,A,L1)") "Scale from file = ", &
object%use_scale_from_file
write (u, "(3x,A,A)") "Version = ", object%version
write (u, "(3x,A,A,A)") "File extension = '", &
char (object%extension), "'"
if (allocated (object%proc_num_id)) then
write (u, "(3x,A)") "Numerical process IDs:"
do i = 1, size (object%proc_num_id)
write (u, "(5x,I0,': ',I0)") i, object%proc_num_id(i)
end do
end if
end subroutine eio_lhef_write
@ %def eio_lhef_write
@ Finalizer: close any open file.
<<EIO LHEF: eio lhef: TBP>>=
procedure :: final => eio_lhef_final
<<EIO LHEF: procedures>>=
subroutine eio_lhef_final (object)
class(eio_lhef_t), intent(inout) :: object
if (allocated (object%proc_num_id)) deallocate (object%proc_num_id)
if (object%writing) then
write (msg_buffer, "(A,A,A)") "Events: closing LHEF file '", &
char (object%filename), "'"
call msg_message ()
call object%write_footer ()
close (object%unit)
object%writing = .false.
else if (object%reading) then
write (msg_buffer, "(A,A,A)") "Events: closing LHEF file '", &
char (object%filename), "'"
call msg_message ()
call object%cstream%final ()
close (object%unit)
object%reading = .false.
end if
end subroutine eio_lhef_final
@ %def eio_lhef_final
@ Common initialization for input and output.
<<EIO LHEF: eio lhef: TBP>>=
procedure :: common_init => eio_lhef_common_init
<<EIO LHEF: procedures>>=
subroutine eio_lhef_common_init (eio, sample, data, extension)
class(eio_lhef_t), intent(inout) :: eio
type(string_t), intent(in) :: sample
type(string_t), intent(in), optional :: extension
type(event_sample_data_t), intent(in), optional :: data
if (.not. present (data)) &
call msg_bug ("LHEF initialization: missing data")
eio%data = data
if (data%n_beam /= 2) &
call msg_fatal ("LHEF: defined for scattering processes only")
eio%unweighted = data%unweighted
if (eio%unweighted) then
select case (data%norm_mode)
case (NORM_UNIT)
case default; call msg_fatal &
("LHEF: normalization for unweighted events must be '1'")
end select
else
select case (data%norm_mode)
case (NORM_SIGMA)
case default; call msg_fatal &
("LHEF: normalization for weighted events must be 'sigma'")
end select
end if
eio%n_alt = data%n_alt
eio%sample = sample
if (present (extension)) then
eio%extension = extension
end if
call eio%set_filename ()
eio%unit = free_unit ()
call eio%init_tags (data)
allocate (eio%proc_num_id (data%n_proc), source = data%proc_num_id)
end subroutine eio_lhef_common_init
@ %def eio_lhef_common_init
@ Initialize the tag objects. Some tags depend on the LHEF
version. In particular, the tags that in LHEF 2.0 identify
individual weights by name in each event block, in LHEF 3.0 are
replaced by info tags in the init block and a single \texttt{weights}
tag in the event block. The name attributes of those tags
are specific for \whizard.
<<EIO LHEF: eio lhef: TBP>>=
procedure :: init_tags => eio_lhef_init_tags
<<EIO LHEF: procedures>>=
subroutine eio_lhef_init_tags (eio, data)
class(eio_lhef_t), intent(inout) :: eio
type(event_sample_data_t), intent(in) :: data
real(default), parameter :: pb_per_fb = 1.e-3_default
integer :: i
call eio%tag_lhef%init ( &
var_str ("LesHouchesEvents"), &
[xml_attribute (var_str ("version"), var_str (eio%version))], &
.true.)
call eio%tag_head%init ( &
var_str ("header"), &
.true.)
call eio%tag_init%init ( &
var_str ("init"), &
.true.)
call eio%tag_event%init (var_str ("event"), &
.true.)
select case (eio%version)
case ("1.0")
allocate (eio%tag_gen_n)
call eio%tag_gen_n%init ( &
var_str ("generator_name"), &
.true.)
allocate (eio%tag_gen_v)
call eio%tag_gen_v%init ( &
var_str ("generator_version"), &
.true.)
end select
select case (eio%version)
case ("2.0", "3.0")
allocate (eio%tag_generator)
call eio%tag_generator%init ( &
var_str ("generator"), &
[xml_attribute (var_str ("version"), var_str ("<<Version>>"))], &
.true.)
allocate (eio%tag_xsecinfo)
call eio%tag_xsecinfo%init ( &
var_str ("xsecinfo"), &
[xml_attribute (var_str ("neve"), str (data%n_evt)), &
xml_attribute (var_str ("totxsec"), &
str (data%total_cross_section * pb_per_fb))])
end select
select case (eio%version)
case ("2.0")
allocate (eio%tag_weight)
call eio%tag_weight%init (var_str ("weight"), &
[xml_attribute (var_str ("name"))])
if (eio%write_sqme_ref) then
allocate (eio%tag_sqme_ref)
call eio%tag_sqme_ref%init (var_str ("weight"), &
[xml_attribute (var_str ("name"), var_str ("sqme_ref"))], &
.true.)
end if
if (eio%write_sqme_prc) then
allocate (eio%tag_sqme_prc)
call eio%tag_sqme_prc%init (var_str ("weight"), &
[xml_attribute (var_str ("name"), var_str ("sqme_prc"))], &
.true.)
end if
if (eio%n_alt > 0) then
if (eio%write_sqme_alt) then
allocate (eio%tag_sqme_alt (1))
call eio%tag_sqme_alt(1)%init (var_str ("weight"), &
[xml_attribute (var_str ("name"), var_str ("sqme_alt"))], &
.true.)
end if
allocate (eio%tag_wgts_alt (1))
call eio%tag_wgts_alt(1)%init (var_str ("weight"), &
[xml_attribute (var_str ("name"), var_str ("wgts_alt"))], &
.true.)
end if
case ("3.0")
if (eio%write_sqme_ref) then
allocate (eio%tag_sqme_ref)
call eio%tag_sqme_ref%init (var_str ("weightinfo"), &
[xml_attribute (var_str ("name"), var_str ("sqme_ref"))])
end if
if (eio%write_sqme_prc) then
allocate (eio%tag_sqme_prc)
call eio%tag_sqme_prc%init (var_str ("weightinfo"), &
[xml_attribute (var_str ("name"), var_str ("sqme_prc"))])
end if
if (eio%n_alt > 0) then
if (eio%write_sqme_alt) then
allocate (eio%tag_sqme_alt (eio%n_alt))
do i = 1, eio%n_alt
call eio%tag_sqme_alt(i)%init (var_str ("weightinfo"), &
[xml_attribute (var_str ("name"), &
var_str ("sqme_alt") // str (i))])
end do
end if
allocate (eio%tag_wgts_alt (eio%n_alt))
do i = 1, eio%n_alt
call eio%tag_wgts_alt(i)%init (var_str ("weightinfo"), &
[xml_attribute (var_str ("name"), &
var_str ("wgts_alt") // str (i))])
end do
end if
allocate (eio%tag_weightinfo)
call eio%tag_weightinfo%init (var_str ("weightinfo"), &
[xml_attribute (var_str ("name"))])
allocate (eio%tag_weights)
call eio%tag_weights%init (var_str ("weights"), .true.)
end select
end subroutine eio_lhef_init_tags
@ %def eio_lhef_init_tags
@ Initialize event writing.
<<EIO LHEF: eio lhef: TBP>>=
procedure :: init_out => eio_lhef_init_out
<<EIO LHEF: procedures>>=
subroutine eio_lhef_init_out (eio, sample, data, success, extension)
class(eio_lhef_t), intent(inout) :: eio
type(string_t), intent(in) :: sample
type(string_t), intent(in), optional :: extension
type(event_sample_data_t), intent(in), optional :: data
logical, intent(out), optional :: success
integer :: u, i
call eio%set_splitting (data)
call eio%common_init (sample, data, extension)
write (msg_buffer, "(A,A,A)") "Events: writing to LHEF file '", &
char (eio%filename), "'"
call msg_message ()
eio%writing = .true.
u = eio%unit
open (u, file = char (eio%filename), &
action = "write", status = "replace")
call eio%write_header ()
call heprup_init &
(data%pdg_beam, &
data%energy_beam, &
n_processes = data%n_proc, &
unweighted = data%unweighted, &
negative_weights = data%negative_weights)
do i = 1, data%n_proc
call heprup_set_process_parameters (i = i, &
process_id = data%proc_num_id(i), &
cross_section = data%cross_section(i), &
error = data%error(i))
end do
call eio%tag_init%write (u); write (u, *)
call heprup_write_lhef (u)
select case (eio%version)
case ("2.0"); call eio%write_init_20 (data)
case ("3.0"); call eio%write_init_30 (data)
end select
call eio%tag_init%close (u); write (u, *)
if (present (success)) success = .true.
end subroutine eio_lhef_init_out
@ %def eio_lhef_init_out
@ Initialize event reading. First read the LHEF tag and version, then
read the header and skip over its contents, then read the init block.
(We require the opening and closing tags of the init block to be placed
on separate lines without extra stuff.)
For input, we do not (yet?) support split event files.
<<EIO LHEF: eio lhef: TBP>>=
procedure :: init_in => eio_lhef_init_in
<<EIO LHEF: procedures>>=
subroutine eio_lhef_init_in (eio, sample, data, success, extension)
class(eio_lhef_t), intent(inout) :: eio
type(string_t), intent(in) :: sample
type(string_t), intent(in), optional :: extension
type(event_sample_data_t), intent(inout), optional :: data
logical, intent(out), optional :: success
logical :: exist, ok, closing
type(event_sample_data_t) :: data_file
type(string_t) :: string
integer :: u
eio%split = .false.
call eio%common_init (sample, data, extension)
write (msg_buffer, "(A,A,A)") "Events: reading from LHEF file '", &
char (eio%filename), "'"
call msg_message ()
inquire (file = char (eio%filename), exist = exist)
if (.not. exist) call msg_fatal ("Events: LHEF file not found.")
eio%reading = .true.
u = eio%unit
open (u, file = char (eio%filename), &
action = "read", status = "old")
call eio%cstream%init (u)
call eio%read_header ()
call eio%tag_init%read (eio%cstream, ok)
if (.not. ok) call err_init
select case (eio%version)
case ("1.0"); call eio%read_init_10 (data_file)
call eio%tag_init%read_content (eio%cstream, string, closing)
if (string /= "" .or. .not. closing) call err_init
case ("2.0"); call eio%read_init_20 (data_file)
case ("3.0"); call eio%read_init_30 (data_file)
end select
call eio%merge_data (data, data_file)
if (present (success)) success = .true.
contains
subroutine err_init
call msg_fatal ("LHEF: syntax error in init tag")
end subroutine err_init
end subroutine eio_lhef_init_in
@ %def eio_lhef_init_in
@ Merge event sample data: we can check the data in the file against
our assumptions and set or reset parameters.
<<EIO LHEF: eio lhef: TBP>>=
procedure :: merge_data => eio_merge_data
<<EIO LHEF: procedures>>=
subroutine eio_merge_data (eio, data, data_file)
class(eio_lhef_t), intent(inout) :: eio
type(event_sample_data_t), intent(inout) :: data
type(event_sample_data_t), intent(in) :: data_file
real, parameter :: tolerance = 1000 * epsilon (1._default)
if (data%unweighted .neqv. data_file%unweighted) call err_weights
if (data%negative_weights .neqv. data_file%negative_weights) &
call err_weights
if (data%norm_mode /= data_file%norm_mode) call err_norm
if (data%n_beam /= data_file%n_beam) call err_beams
if (any (data%pdg_beam /= data_file%pdg_beam)) call err_beams
if (any (abs ((data%energy_beam - data_file%energy_beam)) &
> (data%energy_beam + data_file%energy_beam) * tolerance)) &
call err_beams
if (data%n_proc /= data_file%n_proc) call err_proc
if (any (data%proc_num_id /= data_file%proc_num_id)) call err_proc
where (data%cross_section == 0)
data%cross_section = data_file%cross_section
data%error = data_file%error
end where
data%total_cross_section = sum (data%cross_section)
if (data_file%n_evt > 0) then
if (data%n_evt > 0 .and. data_file%n_evt /= data%n_evt) call err_n_evt
data%n_evt = data_file%n_evt
end if
contains
subroutine err_weights
call msg_fatal ("LHEF: mismatch in event weight properties")
end subroutine err_weights
subroutine err_norm
call msg_fatal ("LHEF: mismatch in event normalization")
end subroutine err_norm
subroutine err_beams
call msg_fatal ("LHEF: mismatch in beam properties")
end subroutine err_beams
subroutine err_proc
call msg_fatal ("LHEF: mismatch in process definitions")
end subroutine err_proc
subroutine err_n_evt
call msg_error ("LHEF: mismatch in specified number of events (ignored)")
end subroutine err_n_evt
end subroutine eio_merge_data
@ %def eio_merge_data
@ Switch from input to output: reopen the file for reading.
<<EIO LHEF: eio lhef: TBP>>=
procedure :: switch_inout => eio_lhef_switch_inout
<<EIO LHEF: procedures>>=
subroutine eio_lhef_switch_inout (eio, success)
class(eio_lhef_t), intent(inout) :: eio
logical, intent(out), optional :: success
call msg_bug ("LHEF: in-out switch not supported")
if (present (success)) success = .false.
end subroutine eio_lhef_switch_inout
@ %def eio_lhef_switch_inout
@ Split event file: increment the counter, close the current file, open a new
one. If the file needs a header, repeat it for the new file. (We assume that
the common block contents are still intact.)
<<EIO LHEF: eio lhef: TBP>>=
procedure :: split_out => eio_lhef_split_out
<<EIO LHEF: procedures>>=
subroutine eio_lhef_split_out (eio)
class(eio_lhef_t), intent(inout) :: eio
integer :: u
if (eio%split) then
eio%split_index = eio%split_index + 1
call eio%set_filename ()
write (msg_buffer, "(A,A,A)") "Events: writing to LHEF file '", &
char (eio%filename), "'"
call msg_message ()
call eio%write_footer ()
u = eio%unit
close (u)
open (u, file = char (eio%filename), &
action = "write", status = "replace")
call eio%write_header ()
call eio%tag_init%write (u); write (u, *)
call heprup_write_lhef (u)
select case (eio%version)
case ("2.0"); call eio%write_init_20 (eio%data)
case ("3.0"); call eio%write_init_30 (eio%data)
end select
call eio%tag_init%close (u); write (u, *)
end if
end subroutine eio_lhef_split_out
@ %def eio_lhef_split_out
@ Output an event. Write first the event indices, then weight and
squared matrix element, then the particle set.
<<EIO LHEF: eio lhef: TBP>>=
procedure :: output => eio_lhef_output
<<EIO LHEF: procedures>>=
subroutine eio_lhef_output (eio, event, i_prc, reading, passed, pacify)
class(eio_lhef_t), intent(inout) :: eio
class(generic_event_t), intent(in), target :: event
integer, intent(in) :: i_prc
logical, intent(in), optional :: reading, passed, pacify
integer :: u
u = given_output_unit (eio%unit); if (u < 0) return
if (present (passed)) then
if (.not. passed) return
end if
if (eio%writing) then
call hepeup_from_event (event, &
process_index = eio%proc_num_id (i_prc), &
keep_beams = eio%keep_beams, &
keep_remnants = eio%keep_remnants)
write (u, '(A)') "<event>"
call hepeup_write_lhef (eio%unit)
select case (eio%version)
case ("2.0"); call eio%write_event_20 (event)
case ("3.0"); call eio%write_event_30 (event)
end select
write (u, '(A)') "</event>"
else
call eio%write ()
call msg_fatal ("LHEF file is not open for writing")
end if
end subroutine eio_lhef_output
@ %def eio_lhef_output
@ Input an event. Upon input of [[i_prc]], we can just read in the
whole HEPEUP common block. These data are known to come first. The
[[i_prc]] value can be deduced from the IDPRUP value by a table
lookup.
Reading the common block bypasses the [[cstream]] which accesses the
input unit. This is consistent with the LHEF specification. After
the common-block data have been swallowed, we can resume reading from
stream.
We don't catch actual I/O errors. However, we return a negative value in
[[iostat]] if we reached the terminating [[</LesHouchesEvents>]] tag.
<<EIO LHEF: eio lhef: TBP>>=
procedure :: input_i_prc => eio_lhef_input_i_prc
<<EIO LHEF: procedures>>=
subroutine eio_lhef_input_i_prc (eio, i_prc, iostat)
class(eio_lhef_t), intent(inout) :: eio
integer, intent(out) :: i_prc
integer, intent(out) :: iostat
integer :: i, proc_num_id
type(string_t) :: s
logical :: ok
iostat = 0
call eio%tag_lhef%read_content (eio%cstream, s, ok)
if (ok) then
if (s == "") then
iostat = -1
else
call err_close
end if
return
else
call eio%cstream%revert_record (s)
end if
call eio%tag_event%read (eio%cstream, ok)
if (.not. ok) then
call err_evt1
return
end if
call hepeup_read_lhef (eio%unit)
call hepeup_get_event_parameters (proc_id = proc_num_id)
i_prc = 0
FIND_I_PRC: do i = 1, size (eio%proc_num_id)
if (eio%proc_num_id(i) == proc_num_id) then
i_prc = i
exit FIND_I_PRC
end if
end do FIND_I_PRC
if (i_prc == 0) call err_index
contains
subroutine err_close
call msg_error ("LHEF: reading events: syntax error in closing tag")
iostat = 1
end subroutine
subroutine err_evt1
call msg_error ("LHEF: reading events: invalid event tag, &
&aborting read")
iostat = 2
end subroutine err_evt1
subroutine err_index
call msg_error ("LHEF: reading events: undefined process ID " &
// char (str (proc_num_id)) // ", aborting read")
iostat = 3
end subroutine err_index
end subroutine eio_lhef_input_i_prc
@ %def eio_lhef_input_i_prc
@ Since we have already read the event information from file, this
input routine can transfer the common-block contents to the event
record. Also, we read any further information in the event record.
Since LHEF doesn't give this information, we must assume that the MCI
group, term, and channel can all be safely set to 1. This works if
there is only one MCI group and term. The channel doesn't matter for
the matrix element.
The event index is incremented, as if the event was generated. The
LHEF format does not support event indices.
<<EIO LHEF: eio lhef: TBP>>=
procedure :: input_event => eio_lhef_input_event
<<EIO LHEF: procedures>>=
subroutine eio_lhef_input_event (eio, event, iostat)
class(eio_lhef_t), intent(inout) :: eio
class(generic_event_t), intent(inout), target :: event
integer, intent(out) :: iostat
type(string_t) :: s
logical :: closing
iostat = 0
call event%reset_contents ()
call event%select (1, 1, 1)
call hepeup_to_event (event, eio%fallback_model, &
recover_beams = eio%recover_beams, &
use_alpha_s = eio%use_alphas_from_file, &
use_scale = eio%use_scale_from_file)
select case (eio%version)
case ("1.0")
call eio%tag_event%read_content (eio%cstream, s, closing = closing)
if (s /= "" .or. .not. closing) call err_evt2
case ("2.0"); call eio%read_event_20 (event)
case ("3.0"); call eio%read_event_30 (event)
end select
call event%increment_index ()
contains
subroutine err_evt2
call msg_error ("LHEF: reading events: syntax error in event record, &
&aborting read")
iostat = 2
end subroutine err_evt2
end subroutine eio_lhef_input_event
@ %def eio_lhef_input_event
@
<<EIO LHEF: eio lhef: TBP>>=
procedure :: skip => eio_lhef_skip
<<EIO LHEF: procedures>>=
subroutine eio_lhef_skip (eio, iostat)
class(eio_lhef_t), intent(inout) :: eio
integer, intent(out) :: iostat
if (eio%reading) then
read (eio%unit, iostat = iostat)
else
call eio%write ()
call msg_fatal ("Raw event file is not open for reading")
end if
end subroutine eio_lhef_skip
@ %def eio_lhef_skip
@
\subsection{Les Houches Event File: header/footer}
These two routines write the header and footer for the Les Houches
Event File format (LHEF).
The current version writes no information except for the generator
name and version (v.1.0 only).
<<EIO LHEF: eio lhef: TBP>>=
procedure :: write_header => eio_lhef_write_header
procedure :: write_footer => eio_lhef_write_footer
<<EIO LHEF: procedures>>=
subroutine eio_lhef_write_header (eio)
class(eio_lhef_t), intent(in) :: eio
integer :: u
u = given_output_unit (eio%unit); if (u < 0) return
call eio%tag_lhef%write (u); write (u, *)
call eio%tag_head%write (u); write (u, *)
select case (eio%version)
case ("1.0")
write (u, "(2x)", advance = "no")
call eio%tag_gen_n%write (var_str ("WHIZARD"), u)
write (u, *)
write (u, "(2x)", advance = "no")
call eio%tag_gen_v%write (var_str ("<<Version>>"), u)
write (u, *)
end select
call eio%tag_head%close (u); write (u, *)
end subroutine eio_lhef_write_header
subroutine eio_lhef_write_footer (eio)
class(eio_lhef_t), intent(in) :: eio
integer :: u
u = given_output_unit (eio%unit); if (u < 0) return
call eio%tag_lhef%close (u)
end subroutine eio_lhef_write_footer
@ %def eio_lhef_write_header eio_lhef_write_footer
@ Reading the header just means finding the tags and ignoring any
contents. When done, we should stand just after the header tag.
<<EIO LHEF: eio lhef: TBP>>=
procedure :: read_header => eio_lhef_read_header
<<EIO LHEF: procedures>>=
subroutine eio_lhef_read_header (eio)
class(eio_lhef_t), intent(inout) :: eio
logical :: success, closing
type(string_t) :: content
call eio%tag_lhef%read (eio%cstream, success)
if (.not. success .or. .not. eio%tag_lhef%has_content) call err_lhef
if (eio%tag_lhef%get_attribute (1) /= eio%version) call err_version
call eio%tag_head%read (eio%cstream, success)
if (.not. success) call err_header
if (eio%tag_head%has_content) then
SKIP_HEADER_CONTENT: do
call eio%tag_head%read_content (eio%cstream, content, closing)
if (closing) exit SKIP_HEADER_CONTENT
end do SKIP_HEADER_CONTENT
end if
contains
subroutine err_lhef
call msg_fatal ("LHEF: LesHouchesEvents tag absent or corrupted")
end subroutine err_lhef
subroutine err_header
call msg_fatal ("LHEF: header tag absent or corrupted")
end subroutine err_header
subroutine err_version
call msg_error ("LHEF: version mismatch: expected " &
// eio%version // ", found " &
// char (eio%tag_lhef%get_attribute (1)))
end subroutine err_version
end subroutine eio_lhef_read_header
@ %def eio_lhef_read_header
@
\subsection{Version-Specific Code: 1.0}
In version 1.0, the init tag contains just HEPRUP data. While a
[[cstream]] is connected to the input unit, we bypass it temporarily
for the purpose of reading the HEPRUP contents. This is consistent
with the LHEF standard.
This routine does not read the closing tag of the init block.
<<EIO LHEF: eio lhef: TBP>>=
procedure :: read_init_10 => eio_lhef_read_init_10
<<EIO LHEF: procedures>>=
subroutine eio_lhef_read_init_10 (eio, data)
class(eio_lhef_t), intent(in) :: eio
type(event_sample_data_t), intent(out) :: data
integer :: n_proc, i
call heprup_read_lhef (eio%unit)
call heprup_get_run_parameters (n_processes = n_proc)
call data%init (n_proc)
data%n_beam = 2
call heprup_get_run_parameters ( &
unweighted = data%unweighted, &
negative_weights = data%negative_weights, &
beam_pdg = data%pdg_beam, &
beam_energy = data%energy_beam)
if (data%unweighted) then
data%norm_mode = NORM_UNIT
else
data%norm_mode = NORM_SIGMA
end if
do i = 1, n_proc
call heprup_get_process_parameters (i, &
process_id = data%proc_num_id(i), &
cross_section = data%cross_section(i), &
error = data%error(i))
end do
end subroutine eio_lhef_read_init_10
@ %def eio_lhef_read_init_10
@
\subsection{Version-Specific Code: 2.0}
This is the init information for the 2.0 format, after the HEPRUP
data. We have the following tags:
\begin{itemize}
\item \texttt{generator} Generator name and version.
\item \texttt{xsecinfo} Cross section and weights data. We have the
total cross section and number of events (assuming that the event
file is intact), but information on minimum and maximum weights is
not available before the file is complete. We just write the
mandatory tags. (Note that the default values of the other tags
describe a uniform unit weight, but we can determine most values
only after the sample is complete.)
\item \texttt{cutsinfo} This optional tag is too specific to represent the
possibilities of WHIZARD, so we skip it.
\item \texttt{procinfo} This optional tag is useful for giving
details of NLO calculations. Skipped.
\item \texttt{mergetype} Optional, also not applicable.
\end{itemize}
<<EIO LHEF: eio lhef: TBP>>=
procedure :: write_init_20 => eio_lhef_write_init_20
<<EIO LHEF: procedures>>=
subroutine eio_lhef_write_init_20 (eio, data)
class(eio_lhef_t), intent(in) :: eio
type(event_sample_data_t), intent(in) :: data
integer :: u
u = eio%unit
call eio%tag_generator%write (u)
write (u, "(A)", advance="no") "WHIZARD"
call eio%tag_generator%close (u); write (u, *)
call eio%tag_xsecinfo%write (u); write (u, *)
end subroutine eio_lhef_write_init_20
@ %def eio_lhef_write_init_20
@ When reading the init block, we first call the 1.0 routine that
fills HEPRUP. Then we consider the possible tags. Only the
\texttt{generator} and \texttt{xsecinfo} tags are of interest. We
skip everything else except for the closing tag.
<<EIO LHEF: eio lhef: TBP>>=
procedure :: read_init_20 => eio_lhef_read_init_20
<<EIO LHEF: procedures>>=
subroutine eio_lhef_read_init_20 (eio, data)
class(eio_lhef_t), intent(inout) :: eio
type(event_sample_data_t), intent(out) :: data
real(default), parameter :: pb_per_fb = 1.e-3_default
type(string_t) :: content
logical :: found, closing
call eio_lhef_read_init_10 (eio, data)
SCAN_INIT_TAGS: do
call eio%tag_generator%read (eio%cstream, found)
if (found) then
if (.not. eio%tag_generator%has_content) call err_generator
call eio%tag_generator%read_content (eio%cstream, content, closing)
call msg_message ("LHEF: Event file has been generated by " &
// char (content) // " " &
// char (eio%tag_generator%get_attribute (1)))
cycle SCAN_INIT_TAGS
end if
call eio%tag_xsecinfo%read (eio%cstream, found)
if (found) then
if (eio%tag_xsecinfo%has_content) call err_xsecinfo
cycle SCAN_INIT_TAGS
end if
call eio%tag_init%read_content (eio%cstream, content, closing)
if (closing) then
if (content /= "") call err_init
exit SCAN_INIT_TAGS
end if
end do SCAN_INIT_TAGS
data%n_evt = &
read_ival (eio%tag_xsecinfo%get_attribute (1))
data%total_cross_section = &
read_rval (eio%tag_xsecinfo%get_attribute (2)) / pb_per_fb
contains
subroutine err_generator
call msg_fatal ("LHEF: invalid generator tag")
end subroutine err_generator
subroutine err_xsecinfo
call msg_fatal ("LHEF: invalid xsecinfo tag")
end subroutine err_xsecinfo
subroutine err_init
call msg_fatal ("LHEF: syntax error after init tag")
end subroutine err_init
end subroutine eio_lhef_read_init_20
@ %def eio_lhef_read_init_20
@ This is additional event-specific information for the 2.0 format,
after the HEPEUP data. We can specify weights, starting from the
master weight and adding alternative weights. The alternative weights
are collected in a common tag.
<<EIO LHEF: eio lhef: TBP>>=
procedure :: write_event_20 => eio_lhef_write_event_20
<<EIO LHEF: procedures>>=
subroutine eio_lhef_write_event_20 (eio, event)
class(eio_lhef_t), intent(in) :: eio
class(generic_event_t), intent(in) :: event
type(string_t) :: s
integer :: i, u
u = eio%unit
if (eio%write_sqme_ref) then
s = str (event%get_sqme_ref ())
call eio%tag_sqme_ref%write (s, u); write (u, *)
end if
if (eio%write_sqme_prc) then
s = str (event%get_sqme_prc ())
call eio%tag_sqme_prc%write (s, u); write (u, *)
end if
if (eio%n_alt > 0) then
if (eio%write_sqme_alt) then
s = str (event%get_sqme_alt(1))
do i = 2, eio%n_alt
s = s // " " // str (event%get_sqme_alt(i)); write (u, *)
end do
call eio%tag_sqme_alt(1)%write (s, u)
end if
s = str (event%get_weight_alt(1))
do i = 2, eio%n_alt
s = s // " " // str (event%get_weight_alt(i)); write (u, *)
end do
call eio%tag_wgts_alt(1)%write (s, u)
end if
end subroutine eio_lhef_write_event_20
@ %def eio_lhef_write_event_20
@ Read extra event data. If there is a weight entry labeled [[sqme_prc]], we
take this as the squared matrix-element value (the new
\emph{reference} value [[sqme_ref]]). Other tags, including
tags written by the above writer, are skipped.
<<EIO LHEF: eio lhef: TBP>>=
procedure :: read_event_20 => eio_lhef_read_event_20
<<EIO LHEF: procedures>>=
subroutine eio_lhef_read_event_20 (eio, event)
class(eio_lhef_t), intent(inout) :: eio
class(generic_event_t), intent(inout) :: event
type(string_t) :: content
logical :: found, closing
SCAN_EVENT_TAGS: do
call eio%tag_weight%read (eio%cstream, found)
if (found) then
if (.not. eio%tag_weight%has_content) call err_weight
call eio%tag_weight%read_content (eio%cstream, content, closing)
if (.not. closing) call err_weight
if (eio%tag_weight%get_attribute (1) == "sqme_prc") then
call event%set_sqme_ref (read_rval (content))
end if
cycle SCAN_EVENT_TAGS
end if
call eio%tag_event%read_content (eio%cstream, content, closing)
if (closing) then
if (content /= "") call err_event
exit SCAN_EVENT_TAGS
end if
end do SCAN_EVENT_TAGS
contains
subroutine err_weight
call msg_fatal ("LHEF: invalid weight tag in event record")
end subroutine err_weight
subroutine err_event
call msg_fatal ("LHEF: syntax error after event tag")
end subroutine err_event
end subroutine eio_lhef_read_event_20
@ %def eio_lhef_read_event_20
@
\subsection{Version-Specific Code: 3.0}
This is the init information for the 3.0 format, after the HEPRUP
data. We have the following tags:
\begin{itemize}
\item \texttt{generator} Generator name and version.
\item \texttt{xsecinfo} Cross section and weights data. We have the
total cross section and number of events (assuming that the event
file is intact), but information on minimum and maximum weights is
not available before the file is complete. We just write the
mandatory tags. (Note that the default values of the other tags
describe a uniform unit weight, but we can determine most values
only after the sample is complete.)
\item \texttt{cutsinfo} This optional tag is too specific to represent the
possibilities of WHIZARD, so we skip it.
\item \texttt{procinfo} This optional tag is useful for giving
details of NLO calculations. Skipped.
\item \texttt{weightinfo} Determine the meaning of optional weights, whose
values are given in the event record.
\end{itemize}
<<EIO LHEF: eio lhef: TBP>>=
procedure :: write_init_30 => eio_lhef_write_init_30
<<EIO LHEF: procedures>>=
subroutine eio_lhef_write_init_30 (eio, data)
class(eio_lhef_t), intent(in) :: eio
type(event_sample_data_t), intent(in) :: data
integer :: u, i
u = given_output_unit (eio%unit)
call eio%tag_generator%write (u)
write (u, "(A)", advance="no") "WHIZARD"
call eiO%tag_generator%close (u); write (u, *)
call eio%tag_xsecinfo%write (u); write (u, *)
if (eio%write_sqme_ref) then
call eio%tag_sqme_ref%write (u); write (u, *)
end if
if (eio%write_sqme_prc) then
call eio%tag_sqme_prc%write (u); write (u, *)
end if
if (eio%write_sqme_alt) then
do i = 1, eio%n_alt
call eio%tag_sqme_alt(i)%write (u); write (u, *)
end do
end if
do i = 1, eio%n_alt
call eio%tag_wgts_alt(i)%write (u); write (u, *)
end do
end subroutine eio_lhef_write_init_30
@ %def eio_lhef_write_init_30
@ When reading the init block, we first call the 1.0 routine that
fills HEPRUP. Then we consider the possible tags. Only the
\texttt{generator} and \texttt{xsecinfo} tags are of interest. We
skip everything else except for the closing tag.
<<EIO LHEF: eio lhef: TBP>>=
procedure :: read_init_30 => eio_lhef_read_init_30
<<EIO LHEF: procedures>>=
subroutine eio_lhef_read_init_30 (eio, data)
class(eio_lhef_t), intent(inout) :: eio
type(event_sample_data_t), intent(out) :: data
real(default), parameter :: pb_per_fb = 1.e-3_default
type(string_t) :: content
logical :: found, closing
integer :: n_weightinfo
call eio_lhef_read_init_10 (eio, data)
n_weightinfo = 0
eio%i_weight_sqme = 0
SCAN_INIT_TAGS: do
call eio%tag_generator%read (eio%cstream, found)
if (found) then
if (.not. eio%tag_generator%has_content) call err_generator
call eio%tag_generator%read_content (eio%cstream, content, closing)
call msg_message ("LHEF: Event file has been generated by " &
// char (content) // " " &
// char (eio%tag_generator%get_attribute (1)))
cycle SCAN_INIT_TAGS
end if
call eio%tag_xsecinfo%read (eio%cstream, found)
if (found) then
if (eio%tag_xsecinfo%has_content) call err_xsecinfo
cycle SCAN_INIT_TAGS
end if
call eio%tag_weightinfo%read (eio%cstream, found)
if (found) then
if (eio%tag_weightinfo%has_content) call err_xsecinfo
n_weightinfo = n_weightinfo + 1
if (eio%tag_weightinfo%get_attribute (1) == "sqme_prc") then
eio%i_weight_sqme = n_weightinfo
end if
cycle SCAN_INIT_TAGS
end if
call eio%tag_init%read_content (eio%cstream, content, closing)
if (closing) then
if (content /= "") call err_init
exit SCAN_INIT_TAGS
end if
end do SCAN_INIT_TAGS
data%n_evt = &
read_ival (eio%tag_xsecinfo%get_attribute (1))
data%total_cross_section = &
read_rval (eio%tag_xsecinfo%get_attribute (2)) / pb_per_fb
contains
subroutine err_generator
call msg_fatal ("LHEF: invalid generator tag")
end subroutine err_generator
subroutine err_xsecinfo
call msg_fatal ("LHEF: invalid xsecinfo tag")
end subroutine err_xsecinfo
subroutine err_init
call msg_fatal ("LHEF: syntax error after init tag")
end subroutine err_init
end subroutine eio_lhef_read_init_30
@ %def eio_lhef_read_init_30
@ This is additional event-specific information for the 3.0 format,
after the HEPEUP data. We can specify weights, starting from the
master weight and adding alternative weights. The weight tags are
already allocated, so we just have to transfer the weight values to
strings, assemble them and write them to file. All weights are
collected in a single tag.
Note: If efficiency turns out to be an issue, we may revert to
traditional character buffer writing. However, we need to know the
maximum length.
<<EIO LHEF: eio lhef: TBP>>=
procedure :: write_event_30 => eio_lhef_write_event_30
<<EIO LHEF: procedures>>=
subroutine eio_lhef_write_event_30 (eio, event)
class(eio_lhef_t), intent(in) :: eio
class(generic_event_t), intent(in) :: event
type(string_t) :: s
integer :: u, i
u = eio%unit
s = ""
if (eio%write_sqme_ref) then
s = s // str (event%get_sqme_ref ()) // " "
end if
if (eio%write_sqme_prc) then
s = s // str (event%get_sqme_prc ()) // " "
end if
if (eio%n_alt > 0) then
if (eio%write_sqme_alt) then
s = s // str (event%get_sqme_alt(1)) // " "
do i = 2, eio%n_alt
s = s // str (event%get_sqme_alt(i)) // " "
end do
end if
s = s // str (event%get_weight_alt(1)) // " "
do i = 2, eio%n_alt
s = s // str (event%get_weight_alt(i)) // " "
end do
end if
if (len_trim (s) > 0) then
call eio%tag_weights%write (trim (s), u); write (u, *)
end if
end subroutine eio_lhef_write_event_30
@ %def eio_lhef_write_event_30
@ Read extra event data. If there is a [[weights]] tag and if there
was a [[weightinfo]] entry labeled [[sqme_prc]], we extract the
corresponding entry from the weights string and store this as the
event's squared matrix-element value. Other tags, including
tags written by the above writer, are skipped.
<<EIO LHEF: eio lhef: TBP>>=
procedure :: read_event_30 => eio_lhef_read_event_30
<<EIO LHEF: procedures>>=
subroutine eio_lhef_read_event_30 (eio, event)
class(eio_lhef_t), intent(inout) :: eio
class(generic_event_t), intent(inout) :: event
type(string_t) :: content, string
logical :: found, closing
integer :: i
SCAN_EVENT_TAGS: do
call eio%tag_weights%read (eio%cstream, found)
if (found) then
if (.not. eio%tag_weights%has_content) call err_weights
call eio%tag_weights%read_content (eio%cstream, content, closing)
if (.not. closing) call err_weights
if (eio%i_weight_sqme > 0) then
SCAN_WEIGHTS: do i = 1, eio%i_weight_sqme
call split (content, string, " ")
content = adjustl (content)
if (i == eio%i_weight_sqme) then
call event%set_sqme_ref (read_rval (string))
exit SCAN_WEIGHTS
end if
end do SCAN_WEIGHTS
end if
cycle SCAN_EVENT_TAGS
end if
call eio%tag_event%read_content (eio%cstream, content, closing)
if (closing) then
if (content /= "") call err_event
exit SCAN_EVENT_TAGS
end if
end do SCAN_EVENT_TAGS
contains
subroutine err_weights
call msg_fatal ("LHEF: invalid weights tag in event record")
end subroutine err_weights
subroutine err_event
call msg_fatal ("LHEF: syntax error after event tag")
end subroutine err_event
end subroutine eio_lhef_read_event_30
@ %def eio_lhef_read_event_30
@
\subsection{Unit tests}
Test module, followed by the corresponding implementation module.
<<[[eio_lhef_ut.f90]]>>=
<<File header>>
module eio_lhef_ut
use unit_tests
use eio_lhef_uti
<<Standard module head>>
<<EIO LHEF: public test>>
contains
<<EIO LHEF: test driver>>
end module eio_lhef_ut
@ %def eio_lhef_ut
@
<<[[eio_lhef_uti.f90]]>>=
<<File header>>
module eio_lhef_uti
<<Use kinds>>
<<Use strings>>
use io_units
use model_data
use event_base
use eio_data
use eio_base
use eio_lhef
use eio_base_ut, only: eio_prepare_test, eio_cleanup_test
use eio_base_ut, only: eio_prepare_fallback_model, eio_cleanup_fallback_model
<<Standard module head>>
<<EIO LHEF: test declarations>>
contains
<<EIO LHEF: tests>>
end module eio_lhef_uti
@ %def eio_lhef_ut
@ API: driver for the unit tests below.
<<EIO LHEF: public test>>=
public :: eio_lhef_test
<<EIO LHEF: test driver>>=
subroutine eio_lhef_test (u, results)
integer, intent(in) :: u
type(test_results_t), intent(inout) :: results
<<EIO LHEF: execute tests>>
end subroutine eio_lhef_test
@ %def eio_lhef_test
@
\subsubsection{Version 1.0 Output}
We test the implementation of all I/O methods. We start with output
according to version 1.0.
<<EIO LHEF: execute tests>>=
call test (eio_lhef_1, "eio_lhef_1", &
"write version 1.0", &
u, results)
<<EIO LHEF: test declarations>>=
public :: eio_lhef_1
<<EIO LHEF: tests>>=
subroutine eio_lhef_1 (u)
integer, intent(in) :: u
class(generic_event_t), pointer :: event
type(event_sample_data_t) :: data
class(eio_t), allocatable :: eio
type(string_t) :: sample
integer :: u_file, iostat
character(80) :: buffer
write (u, "(A)") "* Test output: eio_lhef_1"
write (u, "(A)") "* Purpose: generate an event and write weight to file"
write (u, "(A)")
write (u, "(A)") "* Initialize test process"
call eio_prepare_test (event, unweighted = .false.)
call data%init (1)
data%n_evt = 1
data%n_beam = 2
data%unweighted = .true.
data%norm_mode = NORM_UNIT
data%pdg_beam = 25
data%energy_beam = 500
data%proc_num_id = [42]
data%cross_section(1) = 100
data%error(1) = 1
data%total_cross_section = sum (data%cross_section)
write (u, "(A)")
write (u, "(A)") "* Generate and write an event"
write (u, "(A)")
sample = "eio_lhef_1"
allocate (eio_lhef_t :: eio)
select type (eio)
type is (eio_lhef_t)
call eio%set_parameters ()
end select
call eio%init_out (sample, data)
call event%generate (1, [0._default, 0._default])
call eio%output (event, i_prc = 1)
call eio%write (u)
call eio%final ()
write (u, "(A)")
write (u, "(A)") "* File contents:"
write (u, "(A)")
u_file = free_unit ()
open (u_file, file = char (sample // "." // eio%extension), &
action = "read", status = "old")
do
read (u_file, "(A)", iostat = iostat) buffer
if (buffer(1:21) == " <generator_version>") buffer = "[...]"
if (iostat /= 0) exit
write (u, "(A)") trim (buffer)
end do
close (u_file)
write (u, "(A)")
write (u, "(A)") "* Reset data"
write (u, "(A)")
deallocate (eio)
allocate (eio_lhef_t :: eio)
select type (eio)
type is (eio_lhef_t)
call eio%set_parameters ()
end select
select type (eio)
type is (eio_lhef_t)
call eio%set_parameters (keep_beams = .true.)
end select
call eio%write (u)
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio_cleanup_test (event)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_lhef_1"
end subroutine eio_lhef_1
@ %def eio_lhef_1
@
\subsubsection{Version 2.0 Output}
Version 2.0 has added a lot of options to the LHEF format. We
implement some of them.
<<EIO LHEF: execute tests>>=
call test (eio_lhef_2, "eio_lhef_2", &
"write version 2.0", &
u, results)
<<EIO LHEF: test declarations>>=
public :: eio_lhef_2
<<EIO LHEF: tests>>=
subroutine eio_lhef_2 (u)
integer, intent(in) :: u
class(generic_event_t), pointer :: event
type(event_sample_data_t) :: data
class(eio_t), allocatable :: eio
type(string_t) :: sample
integer :: u_file, iostat
character(80) :: buffer
write (u, "(A)") "* Test output: eio_lhef_2"
write (u, "(A)") "* Purpose: generate an event and write weight to file"
write (u, "(A)")
write (u, "(A)") "* Initialize test process"
call eio_prepare_test (event, unweighted = .false.)
call data%init (1)
data%unweighted = .false.
data%norm_mode = NORM_SIGMA
data%n_evt = 1
data%n_beam = 2
data%pdg_beam = 25
data%energy_beam = 500
data%proc_num_id = [42]
data%cross_section(1) = 100
data%error(1) = 1
data%total_cross_section = sum (data%cross_section)
write (u, "(A)")
write (u, "(A)") "* Generate and write an event"
write (u, "(A)")
sample = "eio_lhef_2"
allocate (eio_lhef_t :: eio)
select type (eio)
type is (eio_lhef_t)
call eio%set_parameters (version = "2.0", write_sqme_prc = .true.)
end select
call eio%init_out (sample, data)
call event%generate (1, [0._default, 0._default])
call eio%output (event, i_prc = 1)
call eio%write (u)
call eio%final ()
write (u, "(A)")
write (u, "(A)") "* File contents:"
write (u, "(A)")
u_file = free_unit ()
open (u_file, file = char (sample // "." // eio%extension), &
action = "read", status = "old")
do
read (u_file, "(A)", iostat = iostat) buffer
if (buffer(1:10) == "<generator") buffer = "[...]"
if (iostat /= 0) exit
write (u, "(A)") trim (buffer)
end do
close (u_file)
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio_cleanup_test (event)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_lhef_2"
end subroutine eio_lhef_2
@ %def eio_lhef_2
@
\subsubsection{Version 3.0 Output}
Version 3.0 is an update which removes some tags (which we didn't use anyway)
and suggests a new treatment of weights.
<<EIO LHEF: execute tests>>=
call test (eio_lhef_3, "eio_lhef_3", &
"write version 3.0", &
u, results)
<<EIO LHEF: test declarations>>=
public :: eio_lhef_3
<<EIO LHEF: tests>>=
subroutine eio_lhef_3 (u)
integer, intent(in) :: u
class(generic_event_t), pointer :: event
type(event_sample_data_t) :: data
class(eio_t), allocatable :: eio
type(string_t) :: sample
integer :: u_file, iostat
character(80) :: buffer
write (u, "(A)") "* Test output: eio_lhef_3"
write (u, "(A)") "* Purpose: generate an event and write weight to file"
write (u, "(A)")
write (u, "(A)") "* Initialize test process"
call eio_prepare_test (event, unweighted = .false.)
call data%init (1)
data%unweighted = .false.
data%norm_mode = NORM_SIGMA
data%n_evt = 1
data%n_beam = 2
data%pdg_beam = 25
data%energy_beam = 500
data%proc_num_id = [42]
data%cross_section(1) = 100
data%error(1) = 1
data%total_cross_section = sum (data%cross_section)
write (u, "(A)")
write (u, "(A)") "* Generate and write an event"
write (u, "(A)")
sample = "eio_lhef_3"
allocate (eio_lhef_t :: eio)
select type (eio)
type is (eio_lhef_t)
call eio%set_parameters (version = "3.0", write_sqme_prc = .true.)
end select
call eio%init_out (sample, data)
call event%generate (1, [0._default, 0._default])
call eio%output (event, i_prc = 1)
call eio%write (u)
call eio%final ()
write (u, "(A)")
write (u, "(A)") "* File contents:"
write (u, "(A)")
u_file = free_unit ()
open (u_file, file = char (sample // ".lhe"), &
action = "read", status = "old")
do
read (u_file, "(A)", iostat = iostat) buffer
if (buffer(1:10) == "<generator") buffer = "[...]"
if (iostat /= 0) exit
write (u, "(A)") trim (buffer)
end do
close (u_file)
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio_cleanup_test (event)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_lhef_3"
end subroutine eio_lhef_3
@ %def eio_lhef_3
@
\subsubsection{Version 1.0 Input}
Check input of a version-1.0 conforming LHEF file.
<<EIO LHEF: execute tests>>=
call test (eio_lhef_4, "eio_lhef_4", &
"read version 1.0", &
u, results)
<<EIO LHEF: test declarations>>=
public :: eio_lhef_4
<<EIO LHEF: tests>>=
subroutine eio_lhef_4 (u)
integer, intent(in) :: u
class(model_data_t), pointer :: fallback_model
class(generic_event_t), pointer :: event
type(event_sample_data_t) :: data
class(eio_t), allocatable :: eio
type(string_t) :: sample
integer :: u_file, iostat, i_prc
write (u, "(A)") "* Test output: eio_lhef_4"
write (u, "(A)") "* Purpose: read a LHEF 1.0 file"
write (u, "(A)")
write (u, "(A)") "* Write a LHEF data file"
write (u, "(A)")
u_file = free_unit ()
sample = "eio_lhef_4"
open (u_file, file = char (sample // ".lhe"), &
status = "replace", action = "readwrite")
write (u_file, "(A)") '<LesHouchesEvents version="1.0">'
write (u_file, "(A)") '<header>'
write (u_file, "(A)") ' <arbitrary_tag opt="foo">content</arbitrary_tag>'
write (u_file, "(A)") ' Text'
write (u_file, "(A)") ' <another_tag />'
write (u_file, "(A)") '</header>'
write (u_file, "(A)") '<init>'
write (u_file, "(A)") ' 25 25 5.0000000000E+02 5.0000000000E+02 &
& -1 -1 -1 -1 3 1'
write (u_file, "(A)") ' 1.0000000000E-01 1.0000000000E-03 &
& 1.0000000000E+00 42'
write (u_file, "(A)") '</init>'
write (u_file, "(A)") '<event>'
write (u_file, "(A)") ' 4 42 3.0574068604E+08 1.0000000000E+03 &
& -1.0000000000E+00 -1.0000000000E+00'
write (u_file, "(A)") ' 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'
write (u_file, "(A)") ' 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'
write (u_file, "(A)") ' 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'
write (u_file, "(A)") ' 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'
write (u_file, "(A)") '</event>'
write (u_file, "(A)") '</LesHouchesEvents>'
close (u_file)
write (u, "(A)") "* Initialize test process"
write (u, "(A)")
call eio_prepare_fallback_model (fallback_model)
call eio_prepare_test (event, unweighted = .false.)
allocate (eio_lhef_t :: eio)
select type (eio)
type is (eio_lhef_t)
call eio%set_parameters (recover_beams = .false.)
end select
call eio%set_fallback_model (fallback_model)
call data%init (1)
data%n_beam = 2
data%unweighted = .true.
data%norm_mode = NORM_UNIT
data%pdg_beam = 25
data%energy_beam = 500
data%proc_num_id = [42]
call data%write (u)
write (u, *)
write (u, "(A)") "* Initialize and read header"
write (u, "(A)")
call eio%init_in (sample, data)
call eio%write (u)
write (u, *)
select type (eio)
type is (eio_lhef_t)
call eio%tag_lhef%write (u); write (u, *)
end select
write (u, *)
call data%write (u)
write (u, "(A)")
write (u, "(A)") "* Read event"
write (u, "(A)")
call eio%input_i_prc (i_prc, iostat)
select type (eio)
type is (eio_lhef_t)
write (u, "(A,I0,A,I0)") "Found process #", i_prc, &
" with ID = ", eio%proc_num_id(i_prc)
end select
call eio%input_event (event, iostat)
call event%write (u)
write (u, "(A)")
write (u, "(A)") "* Read closing"
write (u, "(A)")
call eio%input_i_prc (i_prc, iostat)
write (u, "(A,I0)") "iostat = ", iostat
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio%final ()
call eio_cleanup_test (event)
call eio_cleanup_fallback_model (fallback_model)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_lhef_4"
end subroutine eio_lhef_4
@ %def eio_lhef_4
@
\subsubsection{Version 2.0 Input}
Check input of a version-2.0 conforming LHEF file.
<<EIO LHEF: execute tests>>=
call test (eio_lhef_5, "eio_lhef_5", &
"read version 2.0", &
u, results)
<<EIO LHEF: test declarations>>=
public :: eio_lhef_5
<<EIO LHEF: tests>>=
subroutine eio_lhef_5 (u)
integer, intent(in) :: u
class(model_data_t), pointer :: fallback_model
class(generic_event_t), pointer :: event
type(event_sample_data_t) :: data
class(eio_t), allocatable :: eio
type(string_t) :: sample
integer :: u_file, iostat, i_prc
write (u, "(A)") "* Test output: eio_lhef_5"
write (u, "(A)") "* Purpose: read a LHEF 2.0 file"
write (u, "(A)")
write (u, "(A)") "* Write a LHEF data file"
write (u, "(A)")
u_file = free_unit ()
sample = "eio_lhef_5"
open (u_file, file = char (sample // ".lhe"), &
status = "replace", action = "readwrite")
write (u_file, "(A)") '<LesHouchesEvents version="2.0">'
write (u_file, "(A)") '<header>'
write (u_file, "(A)") '</header>'
write (u_file, "(A)") '<init>'
write (u_file, "(A)") ' 25 25 5.0000000000E+02 5.0000000000E+02 &
&-1 -1 -1 -1 4 1'
write (u_file, "(A)") ' 1.0000000000E-01 1.0000000000E-03 &
& 0.0000000000E+00 42'
write (u_file, "(A)") '<generator version="2.2.3">WHIZARD&
&</generator>'
write (u_file, "(A)") '<xsecinfo neve="1" totxsec="1.0000000000E-01" />'
write (u_file, "(A)") '</init>'
write (u_file, "(A)") '<event>'
write (u_file, "(A)") ' 4 42 3.0574068604E+08 1.0000000000E+03 &
&-1.0000000000E+00 -1.0000000000E+00'
write (u_file, "(A)") ' 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'
write (u_file, "(A)") ' 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'
write (u_file, "(A)") ' 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'
write (u_file, "(A)") ' 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'
write (u_file, "(A)") '<weight name="sqme_prc">1.0000000000E+00</weight>'
write (u_file, "(A)") '</event>'
write (u_file, "(A)") '</LesHouchesEvents>'
close (u_file)
write (u, "(A)") "* Initialize test process"
write (u, "(A)")
call eio_prepare_fallback_model (fallback_model)
call eio_prepare_test (event, unweighted = .false.)
allocate (eio_lhef_t :: eio)
select type (eio)
type is (eio_lhef_t)
call eio%set_parameters (version = "2.0", recover_beams = .false.)
end select
call eio%set_fallback_model (fallback_model)
call data%init (1)
data%unweighted = .false.
data%norm_mode = NORM_SIGMA
data%n_beam = 2
data%pdg_beam = 25
data%energy_beam = 500
data%proc_num_id = [42]
call data%write (u)
write (u, *)
write (u, "(A)") "* Initialize and read header"
write (u, "(A)")
call eio%init_in (sample, data)
call eio%write (u)
write (u, *)
select type (eio)
type is (eio_lhef_t)
call eio%tag_lhef%write (u); write (u, *)
end select
write (u, *)
call data%write (u)
write (u, "(A)")
write (u, "(A)") "* Read event"
write (u, "(A)")
call eio%input_i_prc (i_prc, iostat)
select type (eio)
type is (eio_lhef_t)
write (u, "(A,I0,A,I0)") "Found process #", i_prc, &
" with ID = ", eio%proc_num_id(i_prc)
end select
call eio%input_event (event, iostat)
call event%write (u)
write (u, "(A)")
write (u, "(A)") "* Read closing"
write (u, "(A)")
call eio%input_i_prc (i_prc, iostat)
write (u, "(A,I0)") "iostat = ", iostat
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio%final ()
call eio_cleanup_test (event)
call eio_cleanup_fallback_model (fallback_model)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_lhef_5"
end subroutine eio_lhef_5
@ %def eio_lhef_5
@
\subsubsection{Version 3.0 Input}
Check input of a version-3.0 conforming LHEF file.
<<EIO LHEF: execute tests>>=
call test (eio_lhef_6, "eio_lhef_6", &
"read version 3.0", &
u, results)
<<EIO LHEF: test declarations>>=
public :: eio_lhef_6
<<EIO LHEF: tests>>=
subroutine eio_lhef_6 (u)
integer, intent(in) :: u
class(model_data_t), pointer :: fallback_model
class(generic_event_t), pointer :: event
type(event_sample_data_t) :: data
class(eio_t), allocatable :: eio
type(string_t) :: sample
integer :: u_file, iostat, i_prc
write (u, "(A)") "* Test output: eio_lhef_6"
write (u, "(A)") "* Purpose: read a LHEF 3.0 file"
write (u, "(A)")
write (u, "(A)") "* Write a LHEF data file"
write (u, "(A)")
u_file = free_unit ()
sample = "eio_lhef_6"
open (u_file, file = char (sample // ".lhe"), &
status = "replace", action = "readwrite")
write (u_file, "(A)") '<LesHouchesEvents version="3.0">'
write (u_file, "(A)") '<header>'
write (u_file, "(A)") '</header>'
write (u_file, "(A)") '<init>'
write (u_file, "(A)") ' 25 25 5.0000000000E+02 5.0000000000E+02 &
&-1 -1 -1 -1 4 1'
write (u_file, "(A)") ' 1.0000000000E-01 1.0000000000E-03 &
& 0.0000000000E+00 42'
write (u_file, "(A)") '<generator version="2.2.3">WHIZARD&
&</generator>'
write (u_file, "(A)") '<xsecinfo neve="1" totxsec="1.0000000000E-01" />'
write (u_file, "(A)") '<weightinfo name="sqme_prc" />'
write (u_file, "(A)") '</init>'
write (u_file, "(A)") '<event>'
write (u_file, "(A)") ' 4 42 3.0574068604E+08 1.0000000000E+03 &
&-1.0000000000E+00 -1.0000000000E+00'
write (u_file, "(A)") ' 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'
write (u_file, "(A)") ' 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'
write (u_file, "(A)") ' 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'
write (u_file, "(A)") ' 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'
write (u_file, "(A)") '<weights>1.0000000000E+00</weights>'
write (u_file, "(A)") '</event>'
write (u_file, "(A)") '</LesHouchesEvents>'
close (u_file)
write (u, "(A)") "* Initialize test process"
write (u, "(A)")
call eio_prepare_fallback_model (fallback_model)
call eio_prepare_test (event, unweighted = .false.)
allocate (eio_lhef_t :: eio)
select type (eio)
type is (eio_lhef_t)
call eio%set_parameters (version = "3.0", recover_beams = .false.)
end select
call eio%set_fallback_model (fallback_model)
call data%init (1)
data%unweighted = .false.
data%norm_mode = NORM_SIGMA
data%n_beam = 2
data%pdg_beam = 25
data%energy_beam = 500
data%proc_num_id = [42]
call data%write (u)
write (u, *)
write (u, "(A)") "* Initialize and read header"
write (u, "(A)")
call eio%init_in (sample, data)
call eio%write (u)
write (u, *)
select type (eio)
type is (eio_lhef_t)
call eio%tag_lhef%write (u); write (u, *)
end select
write (u, *)
call data%write (u)
write (u, "(A)")
write (u, "(A)") "* Read event"
write (u, "(A)")
call eio%input_i_prc (i_prc, iostat)
select type (eio)
type is (eio_lhef_t)
write (u, "(A,I0,A,I0)") "Found process #", i_prc, &
" with ID = ", eio%proc_num_id(i_prc)
end select
call eio%input_event (event, iostat)
call event%write (u)
write (u, "(A)")
write (u, "(A)") "* Read closing"
write (u, "(A)")
call eio%input_i_prc (i_prc, iostat)
write (u, "(A,I0)") "iostat = ", iostat
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio%final ()
call eio_cleanup_test (event)
call eio_cleanup_fallback_model (fallback_model)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_lhef_6"
end subroutine eio_lhef_6
@ %def eio_lhef_6
@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
\section{STDHEP File Formats}
Here, we implement the two existing STDHEP file formats, one based on the
HEPRUP/HEPEUP common blocks, the other based on the HEPEVT common block.
The second one is actually the standard STDHEP format.
<<[[eio_stdhep.f90]]>>=
<<File header>>
module eio_stdhep
use kinds, only: i32, i64
<<Use strings>>
use io_units
use string_utils
use diagnostics
use event_base
use hep_common
use hep_events
use eio_data
use eio_base
<<Standard module head>>
<<EIO stdhep: public>>
<<EIO stdhep: types>>
<<EIO stdhep: variables>>
contains
<<EIO stdhep: procedures>>
end module eio_stdhep
@ %def eio_stdhep
@
\subsection{Type}
<<EIO stdhep: public>>=
public :: eio_stdhep_t
<<EIO stdhep: types>>=
type, abstract, extends (eio_t) :: eio_stdhep_t
logical :: writing = .false.
logical :: reading = .false.
integer :: unit = 0
logical :: keep_beams = .false.
logical :: keep_remnants = .true.
logical :: ensure_order = .false.
logical :: recover_beams = .false.
logical :: use_alphas_from_file = .false.
logical :: use_scale_from_file = .false.
integer, dimension(:), allocatable :: proc_num_id
integer(i64) :: n_events_expected = 0
contains
<<EIO stdhep: eio stdhep: TBP>>
end type eio_stdhep_t
@ %def eio_stdhep_t
@
<<EIO stdhep: public>>=
public :: eio_stdhep_hepevt_t
<<EIO stdhep: types>>=
type, extends (eio_stdhep_t) :: eio_stdhep_hepevt_t
end type eio_stdhep_hepevt_t
@ %def eio_stdhep_hepevt_t
@
<<EIO stdhep: public>>=
public :: eio_stdhep_hepeup_t
<<EIO stdhep: types>>=
type, extends (eio_stdhep_t) :: eio_stdhep_hepeup_t
end type eio_stdhep_hepeup_t
@ %def eio_stdhep_hepeup_t
@
<<EIO stdhep: public>>=
public :: eio_stdhep_hepev4_t
<<EIO stdhep: types>>=
type, extends (eio_stdhep_t) :: eio_stdhep_hepev4_t
end type eio_stdhep_hepev4_t
@ %def eio_stdhep_hepev4_t
@
\subsection{Specific Methods}
Set parameters that are specifically used with STDHEP file formats.
<<EIO stdhep: eio stdhep: TBP>>=
procedure :: set_parameters => eio_stdhep_set_parameters
<<EIO stdhep: procedures>>=
subroutine eio_stdhep_set_parameters (eio, &
keep_beams, keep_remnants, ensure_order, recover_beams, &
use_alphas_from_file, use_scale_from_file, extension)
class(eio_stdhep_t), intent(inout) :: eio
logical, intent(in), optional :: keep_beams
logical, intent(in), optional :: keep_remnants
logical, intent(in), optional :: ensure_order
logical, intent(in), optional :: recover_beams
logical, intent(in), optional :: use_alphas_from_file
logical, intent(in), optional :: use_scale_from_file
type(string_t), intent(in), optional :: extension
if (present (keep_beams)) eio%keep_beams = keep_beams
if (present (keep_remnants)) eio%keep_remnants = keep_remnants
if (present (ensure_order)) eio%ensure_order = ensure_order
if (present (recover_beams)) eio%recover_beams = recover_beams
if (present (use_alphas_from_file)) &
eio%use_alphas_from_file = use_alphas_from_file
if (present (use_scale_from_file)) &
eio%use_scale_from_file = use_scale_from_file
if (present (extension)) then
eio%extension = extension
else
select type (eio)
type is (eio_stdhep_hepevt_t)
eio%extension = "hep"
type is (eio_stdhep_hepev4_t)
eio%extension = "ev4.hep"
type is (eio_stdhep_hepeup_t)
eio%extension = "up.hep"
end select
end if
end subroutine eio_stdhep_set_parameters
@ %def eio_ascii_stdhep_parameters
@
\subsection{Common Methods}
Output. This is not the actual event format, but a readable account
of the current object status.
<<EIO stdhep: eio stdhep: TBP>>=
procedure :: write => eio_stdhep_write
<<EIO stdhep: procedures>>=
subroutine eio_stdhep_write (object, unit)
class(eio_stdhep_t), intent(in) :: object
integer, intent(in), optional :: unit
integer :: u, i
u = given_output_unit (unit)
write (u, "(1x,A)") "STDHEP event stream:"
if (object%writing) then
write (u, "(3x,A,A)") "Writing to file = ", char (object%filename)
else if (object%reading) then
write (u, "(3x,A,A)") "Reading from file = ", char (object%filename)
else
write (u, "(3x,A)") "[closed]"
end if
write (u, "(3x,A,L1)") "Keep beams = ", object%keep_beams
write (u, "(3x,A,L1)") "Keep remnants = ", object%keep_remnants
write (u, "(3x,A,L1)") "Recover beams = ", object%recover_beams
write (u, "(3x,A,L1)") "Alpha_s from file = ", &
object%use_alphas_from_file
write (u, "(3x,A,L1)") "Scale from file = ", &
object%use_scale_from_file
if (allocated (object%proc_num_id)) then
write (u, "(3x,A)") "Numerical process IDs:"
do i = 1, size (object%proc_num_id)
write (u, "(5x,I0,': ',I0)") i, object%proc_num_id(i)
end do
end if
end subroutine eio_stdhep_write
@ %def eio_stdhep_write
@ Finalizer: close any open file.
<<EIO stdhep: eio stdhep: TBP>>=
procedure :: final => eio_stdhep_final
<<EIO stdhep: procedures>>=
subroutine eio_stdhep_final (object)
class(eio_stdhep_t), intent(inout) :: object
if (allocated (object%proc_num_id)) deallocate (object%proc_num_id)
if (object%writing) then
write (msg_buffer, "(A,A,A)") "Events: closing STDHEP file '", &
char (object%filename), "'"
call msg_message ()
call stdhep_write (200)
call stdhep_end ()
object%writing = .false.
else if (object%reading) then
write (msg_buffer, "(A,A,A)") "Events: closing STDHEP file '", &
char (object%filename), "'"
call msg_message ()
object%reading = .false.
end if
end subroutine eio_stdhep_final
@ %def eio_stdhep_final
@ Common initialization for input and output.
<<EIO stdhep: eio stdhep: TBP>>=
procedure :: common_init => eio_stdhep_common_init
<<EIO stdhep: procedures>>=
subroutine eio_stdhep_common_init (eio, sample, data, extension)
class(eio_stdhep_t), intent(inout) :: eio
type(string_t), intent(in) :: sample
type(string_t), intent(in), optional :: extension
type(event_sample_data_t), intent(in), optional :: data
if (.not. present (data)) &
call msg_bug ("STDHEP initialization: missing data")
if (data%n_beam /= 2) &
call msg_fatal ("STDHEP: defined for scattering processes only")
if (present (extension)) then
eio%extension = extension
end if
eio%sample = sample
call eio%set_filename ()
eio%unit = free_unit ()
allocate (eio%proc_num_id (data%n_proc), source = data%proc_num_id)
end subroutine eio_stdhep_common_init
@ %def eio_stdhep_common_init
@ Split event file: increment the counter, close the current file, open a new
one. If the file needs a header, repeat it for the new file. (We assume that
the common block contents are still intact.)
<<EIO stdhep: eio stdhep: TBP>>=
procedure :: split_out => eio_stdhep_split_out
<<EIO stdhep: procedures>>=
subroutine eio_stdhep_split_out (eio)
class(eio_stdhep_t), intent(inout) :: eio
if (eio%split) then
eio%split_index = eio%split_index + 1
call eio%set_filename ()
write (msg_buffer, "(A,A,A)") "Events: writing to STDHEP file '", &
char (eio%filename), "'"
call msg_message ()
call stdhep_write (200)
call stdhep_end ()
select type (eio)
type is (eio_stdhep_hepeup_t)
call stdhep_init_out (char (eio%filename), &
"WHIZARD <<Version>>", eio%n_events_expected)
call stdhep_write (100)
call stdhep_write (STDHEP_HEPRUP)
type is (eio_stdhep_hepevt_t)
call stdhep_init_out (char (eio%filename), &
"WHIZARD <<Version>>", eio%n_events_expected)
call stdhep_write (100)
type is (eio_stdhep_hepev4_t)
call stdhep_init_out (char (eio%filename), &
"WHIZARD <<Version>>", eio%n_events_expected)
call stdhep_write (100)
end select
end if
end subroutine eio_stdhep_split_out
@ %def eio_stdhep_split_out
@ Initialize event writing.
<<EIO stdhep: eio stdhep: TBP>>=
procedure :: init_out => eio_stdhep_init_out
<<EIO stdhep: procedures>>=
subroutine eio_stdhep_init_out (eio, sample, data, success, extension)
class(eio_stdhep_t), intent(inout) :: eio
type(string_t), intent(in) :: sample
type(string_t), intent(in), optional :: extension
type(event_sample_data_t), intent(in), optional :: data
logical, intent(out), optional :: success
integer :: i
if (.not. present (data)) &
call msg_bug ("STDHEP initialization: missing data")
call eio%set_splitting (data)
call eio%common_init (sample, data, extension)
eio%n_events_expected = data%n_evt
write (msg_buffer, "(A,A,A)") "Events: writing to STDHEP file '", &
char (eio%filename), "'"
call msg_message ()
eio%writing = .true.
select type (eio)
type is (eio_stdhep_hepeup_t)
call heprup_init &
(data%pdg_beam, &
data%energy_beam, &
n_processes = data%n_proc, &
unweighted = data%unweighted, &
negative_weights = data%negative_weights)
do i = 1, data%n_proc
call heprup_set_process_parameters (i = i, &
process_id = data%proc_num_id(i), &
cross_section = data%cross_section(i), &
error = data%error(i))
end do
call stdhep_init_out (char (eio%filename), &
"WHIZARD <<Version>>", eio%n_events_expected)
call stdhep_write (100)
call stdhep_write (STDHEP_HEPRUP)
type is (eio_stdhep_hepevt_t)
call stdhep_init_out (char (eio%filename), &
"WHIZARD <<Version>>", eio%n_events_expected)
call stdhep_write (100)
type is (eio_stdhep_hepev4_t)
call stdhep_init_out (char (eio%filename), &
"WHIZARD <<Version>>", eio%n_events_expected)
call stdhep_write (100)
end select
if (present (success)) success = .true.
end subroutine eio_stdhep_init_out
@ %def eio_stdhep_init_out
@ Initialize event reading.
<<EIO stdhep: eio stdhep: TBP>>=
procedure :: init_in => eio_stdhep_init_in
<<EIO stdhep: procedures>>=
subroutine eio_stdhep_init_in (eio, sample, data, success, extension)
class(eio_stdhep_t), intent(inout) :: eio
type(string_t), intent(in) :: sample
type(string_t), intent(in), optional :: extension
type(event_sample_data_t), intent(inout), optional :: data
logical, intent(out), optional :: success
integer :: ilbl, lok
logical :: exist
call eio%common_init (sample, data, extension)
write (msg_buffer, "(A,A,A)") "Events: reading from STDHEP file '", &
char (eio%filename), "'"
call msg_message ()
inquire (file = char (eio%filename), exist = exist)
if (.not. exist) call msg_fatal ("Events: STDHEP file not found.")
eio%reading = .true.
call stdhep_init_in (char (eio%filename), eio%n_events_expected)
call stdhep_read (ilbl, lok)
if (lok /= 0) then
call stdhep_end ()
write (msg_buffer, "(A)") "Events: STDHEP file appears to" // &
" be empty."
call msg_message ()
end if
if (ilbl == 100) then
write (msg_buffer, "(A)") "Events: reading in STDHEP events"
call msg_message ()
end if
if (present (success)) success = .false.
end subroutine eio_stdhep_init_in
@ %def eio_stdhep_init_in
@ Switch from input to output: reopen the file for reading.
<<EIO stdhep: eio stdhep: TBP>>=
procedure :: switch_inout => eio_stdhep_switch_inout
<<EIO stdhep: procedures>>=
subroutine eio_stdhep_switch_inout (eio, success)
class(eio_stdhep_t), intent(inout) :: eio
logical, intent(out), optional :: success
call msg_bug ("STDHEP: in-out switch not supported")
if (present (success)) success = .false.
end subroutine eio_stdhep_switch_inout
@ %def eio_stdhep_switch_inout
@ Output an event. Write first the event indices, then weight and
squared matrix element, then the particle set.
<<EIO stdhep: eio stdhep: TBP>>=
procedure :: output => eio_stdhep_output
<<EIO stdhep: procedures>>=
subroutine eio_stdhep_output (eio, event, i_prc, reading, passed, pacify)
class(eio_stdhep_t), intent(inout) :: eio
class(generic_event_t), intent(in), target :: event
integer, intent(in) :: i_prc
logical, intent(in), optional :: reading, passed, pacify
if (present (passed)) then
if (.not. passed) return
end if
if (eio%writing) then
select type (eio)
type is (eio_stdhep_hepeup_t)
call hepeup_from_event (event, &
process_index = eio%proc_num_id (i_prc), &
keep_beams = eio%keep_beams, &
keep_remnants = eio%keep_remnants)
call stdhep_write (STDHEP_HEPEUP)
type is (eio_stdhep_hepevt_t)
call hepevt_from_event (event, &
keep_beams = eio%keep_beams, &
keep_remnants = eio%keep_remnants, &
ensure_order = eio%ensure_order)
call stdhep_write (STDHEP_HEPEVT)
type is (eio_stdhep_hepev4_t)
call hepevt_from_event (event, &
process_index = eio%proc_num_id (i_prc), &
keep_beams = eio%keep_beams, &
keep_remnants = eio%keep_remnants, &
ensure_order = eio%ensure_order, &
fill_hepev4 = .true.)
call stdhep_write (STDHEP_HEPEV4)
end select
else
call eio%write ()
call msg_fatal ("STDHEP file is not open for writing")
end if
end subroutine eio_stdhep_output
@ %def eio_stdhep_output
@ Input an event. We do not allow to read in STDHEP files written via
the HEPEVT common block as there is no control on the process ID.
This implies that the event index cannot be read; it is simply
incremented to count the current event sample.
<<EIO stdhep: eio stdhep: TBP>>=
procedure :: input_i_prc => eio_stdhep_input_i_prc
procedure :: input_event => eio_stdhep_input_event
<<EIO stdhep: procedures>>=
subroutine eio_stdhep_input_i_prc (eio, i_prc, iostat)
class(eio_stdhep_t), intent(inout) :: eio
integer, intent(out) :: i_prc
integer, intent(out) :: iostat
integer :: i, ilbl, proc_num_id
iostat = 0
select type (eio)
type is (eio_stdhep_hepevt_t)
if (size (eio%proc_num_id) > 1) then
call msg_fatal ("Events: only single processes allowed " // &
"with the STDHEP HEPEVT format.")
else
proc_num_id = eio%proc_num_id (1)
call stdhep_read (ilbl, lok)
end if
type is (eio_stdhep_hepev4_t)
call stdhep_read (ilbl, lok)
proc_num_id = idruplh
type is (eio_stdhep_hepeup_t)
call stdhep_read (ilbl, lok)
if (lok /= 0) call msg_error ("Events: STDHEP appears to be " // &
"empty or corrupted.")
if (ilbl == 12) then
call stdhep_read (ilbl, lok)
end if
if (ilbl == 11) then
proc_num_id = IDPRUP
end if
end select
FIND_I_PRC: do i = 1, size (eio%proc_num_id)
if (eio%proc_num_id(i) == proc_num_id) then
i_prc = i
exit FIND_I_PRC
end if
end do FIND_I_PRC
if (i_prc == 0) call err_index
contains
subroutine err_index
call msg_error ("STDHEP: reading events: undefined process ID " &
// char (str (proc_num_id)) // ", aborting read")
iostat = 1
end subroutine err_index
end subroutine eio_stdhep_input_i_prc
subroutine eio_stdhep_input_event (eio, event, iostat)
class(eio_stdhep_t), intent(inout) :: eio
class(generic_event_t), intent(inout), target :: event
integer, intent(out) :: iostat
iostat = 0
call event%reset_contents ()
call event%select (1, 1, 1)
call hepeup_to_event (event, eio%fallback_model, &
recover_beams = eio%recover_beams, &
use_alpha_s = eio%use_alphas_from_file, &
use_scale = eio%use_scale_from_file)
call event%increment_index ()
end subroutine eio_stdhep_input_event
@ %def eio_stdhep_input_i_prc
@ %def eio_stdhep_input_event
<<EIO stdhep: eio stdhep: TBP>>=
procedure :: skip => eio_stdhep_skip
<<EIO stdhep: procedures>>=
subroutine eio_stdhep_skip (eio, iostat)
class(eio_stdhep_t), intent(inout) :: eio
integer, intent(out) :: iostat
if (eio%reading) then
read (eio%unit, iostat = iostat)
else
call eio%write ()
call msg_fatal ("Raw event file is not open for reading")
end if
end subroutine eio_stdhep_skip
@ %def eio_stdhep_skip
@ STDHEP speficic routines.
<<EIO stdhep: public>>=
public :: stdhep_init_out
public :: stdhep_init_in
public :: stdhep_write
public :: stdhep_end
<<EIO stdhep: procedures>>=
subroutine stdhep_init_out (file, title, nevt)
character(len=*), intent(in) :: file, title
integer(i64), intent(in) :: nevt
integer(i32) :: nevt32
nevt32 = min (nevt, int (huge (1_i32), i64))
call stdxwinit (file, title, nevt32, istr, lok)
end subroutine stdhep_init_out
subroutine stdhep_init_in (file, nevt)
character(len=*), intent(in) :: file
integer(i64), intent(out) :: nevt
integer(i32) :: nevt32
call stdxrinit (file, nevt32, istr, lok)
if (lok /= 0) call msg_fatal ("STDHEP: error in reading file '" // &
file // "'.")
nevt = int (nevt32, i64)
end subroutine stdhep_init_in
subroutine stdhep_write (ilbl)
integer, intent(in) :: ilbl
call stdxwrt (ilbl, istr, lok)
end subroutine stdhep_write
subroutine stdhep_read (ilbl, lok)
integer, intent(out) :: ilbl, lok
call stdxrd (ilbl, istr, lok)
if (lok /= 0) return
end subroutine stdhep_read
subroutine stdhep_end
call stdxend (istr)
end subroutine stdhep_end
@ %def stdhep_init stdhep_read stdhep_write stdhep_end
@
\subsection{Variables}
<<EIO stdhep: variables>>=
integer, save :: istr, lok
integer, parameter :: &
STDHEP_HEPEVT = 1, STDHEP_HEPEV4 = 4, &
STDHEP_HEPEUP = 11, STDHEP_HEPRUP = 12
@
@
\subsection{Unit tests}
Test module, followed by the corresponding implementation module.
<<[[eio_stdhep_ut.f90]]>>=
<<File header>>
module eio_stdhep_ut
use unit_tests
use eio_stdhep_uti
<<Standard module head>>
<<EIO stdhep: public test>>
contains
<<EIO stdhep: test driver>>
end module eio_stdhep_ut
@ %def eio_stdhep_ut
@
<<[[eio_stdhep_uti.f90]]>>=
<<File header>>
module eio_stdhep_uti
<<Use kinds>>
<<Use strings>>
use io_units
use model_data
use event_base
use eio_data
use eio_base
use xdr_wo_stdhep
use eio_stdhep
use eio_base_ut, only: eio_prepare_test, eio_cleanup_test
use eio_base_ut, only: eio_prepare_fallback_model, eio_cleanup_fallback_model
<<Standard module head>>
<<EIO stdhep: test declarations>>
contains
<<EIO stdhep: tests>>
end module eio_stdhep_uti
@ %def eio_stdhep_ut
@ API: driver for the unit tests below.
<<EIO stdhep: public test>>=
public :: eio_stdhep_test
<<EIO stdhep: test driver>>=
subroutine eio_stdhep_test (u, results)
integer, intent(in) :: u
type(test_results_t), intent(inout) :: results
<<EIO stdhep: execute tests>>
end subroutine eio_stdhep_test
@ %def eio_stdhep_test
@
\subsubsection{Test I/O methods}
We test the implementation of the STDHEP HEPEVT I/O method:
<<EIO stdhep: execute tests>>=
call test (eio_stdhep_1, "eio_stdhep_1", &
"read and write event contents, format [stdhep]", &
u, results)
<<EIO stdhep: test declarations>>=
public :: eio_stdhep_1
<<EIO stdhep: tests>>=
subroutine eio_stdhep_1 (u)
integer, intent(in) :: u
class(generic_event_t), pointer :: event
type(event_sample_data_t) :: data
class(eio_t), allocatable :: eio
type(string_t) :: sample
integer :: u_file, iostat
character(215) :: buffer
write (u, "(A)") "* Test output: eio_stdhep_1"
write (u, "(A)") "* Purpose: generate an event in STDHEP HEPEVT format"
write (u, "(A)") "* and write weight to file"
write (u, "(A)")
write (u, "(A)") "* Initialize test process"
call eio_prepare_test (event)
call data%init (1)
data%n_evt = 1
data%n_beam = 2
data%pdg_beam = 25
data%energy_beam = 500
data%proc_num_id = [42]
data%cross_section(1) = 100
data%error(1) = 1
data%total_cross_section = sum (data%cross_section)
write (u, "(A)")
write (u, "(A)") "* Generate and write an event"
write (u, "(A)")
sample = "eio_stdhep_1"
allocate (eio_stdhep_hepevt_t :: eio)
select type (eio)
type is (eio_stdhep_hepevt_t)
call eio%set_parameters ()
end select
call eio%init_out (sample, data)
call event%generate (1, [0._default, 0._default])
call event%set_index (61) ! not supported by reader, actually
call event%evaluate_expressions ()
call event%pacify_particle_set ()
call eio%output (event, i_prc = 1)
call eio%write (u)
call eio%final ()
write (u, "(A)")
write (u, "(A)") "* Write STDHEP file contents to ASCII file"
write (u, "(A)")
call write_stdhep_event &
(sample // ".hep", var_str ("eio_stdhep_1.hep.out"), 1)
write (u, "(A)")
write (u, "(A)") "* Read in ASCII contents of STDHEP file"
write (u, "(A)")
u_file = free_unit ()
open (u_file, file = "eio_stdhep_1.hep.out", &
action = "read", status = "old")
do
read (u_file, "(A)", iostat = iostat) buffer
if (iostat /= 0) exit
if (trim (buffer) == "") cycle
if (buffer(1:18) == " total blocks: ") &
buffer = " total blocks: [...]"
if (buffer(1:25) == " title: WHIZARD") &
buffer = " title: WHIZARD [version]"
if (buffer(1:17) == " date:") &
buffer = " date: [...]"
if (buffer(1:17) == " closing date:") &
buffer = " closing date: [...]"
write (u, "(A)") trim (buffer)
end do
close (u_file)
write (u, "(A)")
write (u, "(A)") "* Reset data"
write (u, "(A)")
deallocate (eio)
allocate (eio_stdhep_hepevt_t :: eio)
select type (eio)
type is (eio_stdhep_hepevt_t)
call eio%set_parameters (keep_beams = .true.)
end select
call eio%write (u)
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio_cleanup_test (event)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_stdhep_1"
end subroutine eio_stdhep_1
@ %def eio_stdhep_1
@
We test the implementation of the STDHEP HEPEUP I/O method:
<<EIO stdhep: execute tests>>=
call test (eio_stdhep_2, "eio_stdhep_2", &
"read and write event contents, format [stdhep]", &
u, results)
<<EIO stdhep: test declarations>>=
public :: eio_stdhep_2
<<EIO stdhep: tests>>=
subroutine eio_stdhep_2 (u)
integer, intent(in) :: u
class(generic_event_t), pointer :: event
type(event_sample_data_t) :: data
class(model_data_t), pointer :: fallback_model
class(eio_t), allocatable :: eio
type(string_t) :: sample
integer :: u_file, iostat
character(215) :: buffer
write (u, "(A)") "* Test output: eio_stdhep_2"
write (u, "(A)") "* Purpose: generate an event in STDHEP HEPEUP format"
write (u, "(A)") "* and write weight to file"
write (u, "(A)")
write (u, "(A)") "* Initialize test process"
call eio_prepare_fallback_model (fallback_model)
call eio_prepare_test (event, unweighted = .false.)
call data%init (1)
data%n_evt = 1
data%n_beam = 2
data%pdg_beam = 25
data%energy_beam = 500
data%proc_num_id = [42]
data%cross_section(1) = 100
data%error(1) = 1
data%total_cross_section = sum (data%cross_section)
write (u, "(A)")
write (u, "(A)") "* Generate and write an event"
write (u, "(A)")
sample = "eio_stdhep_2"
allocate (eio_stdhep_hepeup_t :: eio)
select type (eio)
type is (eio_stdhep_hepeup_t)
call eio%set_parameters ()
end select
call eio%set_fallback_model (fallback_model)
call eio%init_out (sample, data)
call event%generate (1, [0._default, 0._default])
call event%set_index (62) ! not supported by reader, actually
call event%evaluate_expressions ()
call eio%output (event, i_prc = 1)
call eio%write (u)
call eio%final ()
write (u, "(A)")
write (u, "(A)") "* Write STDHEP file contents to ASCII file"
write (u, "(A)")
call write_stdhep_event &
(sample // ".up.hep", var_str ("eio_stdhep_2.hep.out"), 2)
write (u, "(A)")
write (u, "(A)") "* Read in ASCII contents of STDHEP file"
write (u, "(A)")
u_file = free_unit ()
open (u_file, file = "eio_stdhep_2.hep.out", &
action = "read", status = "old")
do
read (u_file, "(A)", iostat = iostat) buffer
if (iostat /= 0) exit
if (trim (buffer) == "") cycle
if (buffer(1:18) == " total blocks: ") &
buffer = " total blocks: [...]"
if (buffer(1:25) == " title: WHIZARD") &
buffer = " title: WHIZARD [version]"
if (buffer(1:17) == " date:") &
buffer = " date: [...]"
if (buffer(1:17) == " closing date:") &
buffer = " closing date: [...]"
write (u, "(A)") trim (buffer)
end do
close (u_file)
write (u, "(A)")
write (u, "(A)") "* Reset data"
write (u, "(A)")
deallocate (eio)
allocate (eio_stdhep_hepeup_t :: eio)
select type (eio)
type is (eio_stdhep_hepeup_t)
call eio%set_parameters (keep_beams = .true.)
end select
call eio%write (u)
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio_cleanup_test (event)
call eio_cleanup_fallback_model (fallback_model)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_stdhep_2"
end subroutine eio_stdhep_2
@ %def eio_stdhep_2
@
Check input from a StdHep file, HEPEVT block.
<<EIO stdhep: execute tests>>=
call test (eio_stdhep_3, "eio_stdhep_3", &
"read StdHep file, HEPEVT block", &
u, results)
<<EIO stdhep: test declarations>>=
public :: eio_stdhep_3
<<EIO stdhep: tests>>=
subroutine eio_stdhep_3 (u)
integer, intent(in) :: u
class(model_data_t), pointer :: fallback_model
class(generic_event_t), pointer :: event
type(event_sample_data_t) :: data
class(eio_t), allocatable :: eio
type(string_t) :: sample
integer :: iostat, i_prc
write (u, "(A)") "* Test output: eio_stdhep_3"
write (u, "(A)") "* Purpose: read a StdHep file, HEPEVT block"
write (u, "(A)")
write (u, "(A)") "* Write a StdHep data file, HEPEVT block"
write (u, "(A)")
call eio_prepare_fallback_model (fallback_model)
call eio_prepare_test (event)
call data%init (1)
data%n_evt = 1
data%n_beam = 2
data%pdg_beam = 25
data%energy_beam = 500
data%proc_num_id = [42]
data%cross_section(1) = 100
data%error(1) = 1
data%total_cross_section = sum (data%cross_section)
write (u, "(A)")
write (u, "(A)") "* Generate and write an event"
write (u, "(A)")
sample = "eio_stdhep_3"
allocate (eio_stdhep_hepevt_t :: eio)
select type (eio)
type is (eio_stdhep_hepevt_t)
call eio%set_parameters ()
end select
call eio%set_fallback_model (fallback_model)
call eio%init_out (sample, data)
call event%generate (1, [0._default, 0._default])
call event%set_index (63) ! not supported by reader, actually
call event%evaluate_expressions ()
call eio%output (event, i_prc = 1)
call eio%write (u)
call eio%final ()
call eio_cleanup_test (event)
call eio_cleanup_fallback_model (fallback_model)
deallocate (eio)
write (u, "(A)") "* Initialize test process"
write (u, "(A)")
call eio_prepare_fallback_model (fallback_model)
call eio_prepare_test (event, unweighted = .false.)
allocate (eio_stdhep_hepevt_t :: eio)
select type (eio)
type is (eio_stdhep_hepevt_t)
call eio%set_parameters (recover_beams = .false.)
end select
call eio%set_fallback_model (fallback_model)
call data%init (1)
data%n_beam = 2
data%unweighted = .true.
data%norm_mode = NORM_UNIT
data%pdg_beam = 25
data%energy_beam = 500
data%proc_num_id = [42]
call data%write (u)
write (u, *)
write (u, "(A)") "* Initialize"
write (u, "(A)")
call eio%init_in (sample, data)
call eio%write (u)
write (u, "(A)")
write (u, "(A)") "* Read event"
write (u, "(A)")
call eio%input_i_prc (i_prc, iostat)
select type (eio)
type is (eio_stdhep_hepevt_t)
write (u, "(A,I0,A,I0)") "Found process #", i_prc, &
" with ID = ", eio%proc_num_id(i_prc)
end select
call eio%input_event (event, iostat)
call event%write (u)
write (u, "(A)")
write (u, "(A)") "* Read closing"
write (u, "(A)")
call eio%input_i_prc (i_prc, iostat)
write (u, "(A,I0)") "iostat = ", iostat
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio%final ()
call eio_cleanup_test (event)
call eio_cleanup_fallback_model (fallback_model)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_stdhep_3"
end subroutine eio_stdhep_3
@ %def eio_stdhep_3
@
Check input from a StdHep file, HEPEVT block.
<<EIO stdhep: execute tests>>=
call test (eio_stdhep_4, "eio_stdhep_4", &
"read StdHep file, HEPRUP/HEPEUP block", &
u, results)
<<EIO stdhep: test declarations>>=
public :: eio_stdhep_4
<<EIO stdhep: tests>>=
subroutine eio_stdhep_4 (u)
integer, intent(in) :: u
class(model_data_t), pointer :: fallback_model
class(generic_event_t), pointer :: event
type(event_sample_data_t) :: data
class(eio_t), allocatable :: eio
type(string_t) :: sample
integer :: iostat, i_prc
write (u, "(A)") "* Test output: eio_stdhep_3"
write (u, "(A)") "* Purpose: read a StdHep file, HEPRUP/HEPEUP block"
write (u, "(A)")
write (u, "(A)") "* Write a StdHep data file, HEPRUP/HEPEUP block"
write (u, "(A)")
call eio_prepare_fallback_model (fallback_model)
call eio_prepare_test (event)
call data%init (1)
data%n_evt = 1
data%n_beam = 2
data%pdg_beam = 25
data%energy_beam = 500
data%proc_num_id = [42]
data%cross_section(1) = 100
data%error(1) = 1
data%total_cross_section = sum (data%cross_section)
write (u, "(A)")
write (u, "(A)") "* Generate and write an event, HEPEUP/HEPRUP"
write (u, "(A)")
sample = "eio_stdhep_4"
allocate (eio_stdhep_hepeup_t :: eio)
select type (eio)
type is (eio_stdhep_hepeup_t)
call eio%set_parameters ()
end select
call eio%set_fallback_model (fallback_model)
call eio%init_out (sample, data)
call event%generate (1, [0._default, 0._default])
call event%set_index (64) ! not supported by reader, actually
call event%evaluate_expressions ()
call event%pacify_particle_set ()
call eio%output (event, i_prc = 1)
call eio%write (u)
call eio%final ()
call eio_cleanup_test (event)
call eio_cleanup_fallback_model (fallback_model)
deallocate (eio)
write (u, "(A)") "* Initialize test process"
write (u, "(A)")
call eio_prepare_fallback_model (fallback_model)
call eio_prepare_test (event, unweighted = .false.)
allocate (eio_stdhep_hepeup_t :: eio)
select type (eio)
type is (eio_stdhep_hepeup_t)
call eio%set_parameters (recover_beams = .false.)
end select
call eio%set_fallback_model (fallback_model)
call data%init (1)
data%n_beam = 2
data%unweighted = .true.
data%norm_mode = NORM_UNIT
data%pdg_beam = 25
data%energy_beam = 500
data%proc_num_id = [42]
call data%write (u)
write (u, *)
write (u, "(A)") "* Initialize"
write (u, "(A)")
call eio%init_in (sample, data)
call eio%write (u)
write (u, "(A)")
write (u, "(A)") "* Read event"
write (u, "(A)")
call eio%input_i_prc (i_prc, iostat)
select type (eio)
type is (eio_stdhep_hepeup_t)
write (u, "(A,I0,A,I0)") "Found process #", i_prc, &
" with ID = ", eio%proc_num_id(i_prc)
end select
call eio%input_event (event, iostat)
call event%write (u)
write (u, "(A)")
write (u, "(A)") "* Read closing"
write (u, "(A)")
call eio%input_i_prc (i_prc, iostat)
write (u, "(A,I0)") "iostat = ", iostat
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio%final ()
call eio_cleanup_test (event)
call eio_cleanup_fallback_model (fallback_model)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_stdhep_4"
end subroutine eio_stdhep_4
@ %def eio_stdhep_4
@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
\section{HepMC Output}
The HepMC event record is standardized. It is an ASCII format. We try
our best at using it for both input and output.
<<[[eio_hepmc.f90]]>>=
<<File header>>
module eio_hepmc
<<Use strings>>
use io_units
use string_utils
use diagnostics
use particles
use model_data
use event_base
use hep_events
use eio_data
use eio_base
use hepmc_interface
<<Standard module head>>
<<EIO HepMC: public>>
<<EIO HepMC: types>>
contains
<<EIO HepMC: procedures>>
end module eio_hepmc
@ %def eio_hepmc
@
\subsection{Type}
A type [[hepmc_event]] is introduced as container to store HepMC event
data, particularly for splitting the reading into read out of the process
index and the proper event data.
Note: the [[keep_beams]] flag is not supported. Beams will always
be written. Tools like \texttt{Rivet} can use the cross section
information of a HepMC file for scaling plots. As there is no header in
HepMC and this is written for every event, we make it optional with
[[output_cross_section]].
<<EIO HepMC: public>>=
public :: eio_hepmc_t
<<EIO HepMC: types>>=
type, extends (eio_t) :: eio_hepmc_t
logical :: writing = .false.
logical :: reading = .false.
type(event_sample_data_t) :: data
! logical :: keep_beams = .false.
logical :: recover_beams = .false.
logical :: use_alphas_from_file = .false.
logical :: use_scale_from_file = .false.
logical :: output_cross_section = .false.
type(hepmc_iostream_t) :: iostream
type(hepmc_event_t) :: hepmc_event
integer, dimension(:), allocatable :: proc_num_id
contains
<<EIO HepMC: eio hepmc: TBP>>
end type eio_hepmc_t
@ %def eio_hepmc_t
@
\subsection{Specific Methods}
Set parameters that are specifically used with HepMC.
<<EIO HepMC: eio hepmc: TBP>>=
procedure :: set_parameters => eio_hepmc_set_parameters
<<EIO HepMC: procedures>>=
subroutine eio_hepmc_set_parameters &
(eio, &
recover_beams, use_alphas_from_file, use_scale_from_file, &
extension, output_cross_section)
class(eio_hepmc_t), intent(inout) :: eio
logical, intent(in), optional :: recover_beams
logical, intent(in), optional :: use_alphas_from_file
logical, intent(in), optional :: use_scale_from_file
logical, intent(in), optional :: output_cross_section
type(string_t), intent(in), optional :: extension
if (present (recover_beams)) &
eio%recover_beams = recover_beams
if (present (use_alphas_from_file)) &
eio%use_alphas_from_file = use_alphas_from_file
if (present (use_scale_from_file)) &
eio%use_scale_from_file = use_scale_from_file
if (present (extension)) then
eio%extension = extension
else
eio%extension = "hepmc"
end if
if (present (output_cross_section)) &
eio%output_cross_section = output_cross_section
end subroutine eio_hepmc_set_parameters
@ %def eio_hepmc_set_parameters
@
\subsection{Common Methods}
Output. This is not the actual event format, but a readable account
of the current object status.
<<EIO HepMC: eio hepmc: TBP>>=
procedure :: write => eio_hepmc_write
<<EIO HepMC: procedures>>=
subroutine eio_hepmc_write (object, unit)
class(eio_hepmc_t), intent(in) :: object
integer, intent(in), optional :: unit
integer :: u, i
u = given_output_unit (unit)
write (u, "(1x,A)") "HepMC event stream:"
if (object%writing) then
write (u, "(3x,A,A)") "Writing to file = ", char (object%filename)
else if (object%reading) then
write (u, "(3x,A,A)") "Reading from file = ", char (object%filename)
else
write (u, "(3x,A)") "[closed]"
end if
write (u, "(3x,A,L1)") "Recover beams = ", object%recover_beams
write (u, "(3x,A,L1)") "Alpha_s from file = ", &
object%use_alphas_from_file
write (u, "(3x,A,L1)") "Scale from file = ", &
object%use_scale_from_file
write (u, "(3x,A,A,A)") "File extension = '", &
char (object%extension), "'"
if (allocated (object%proc_num_id)) then
write (u, "(3x,A)") "Numerical process IDs:"
do i = 1, size (object%proc_num_id)
write (u, "(5x,I0,': ',I0)") i, object%proc_num_id(i)
end do
end if
end subroutine eio_hepmc_write
@ %def eio_hepmc_write
@ Finalizer: close any open file.
<<EIO HepMC: eio hepmc: TBP>>=
procedure :: final => eio_hepmc_final
<<EIO HepMC: procedures>>=
subroutine eio_hepmc_final (object)
class(eio_hepmc_t), intent(inout) :: object
if (allocated (object%proc_num_id)) deallocate (object%proc_num_id)
if (object%writing) then
write (msg_buffer, "(A,A,A)") "Events: closing HepMC file '", &
char (object%filename), "'"
call msg_message ()
call hepmc_iostream_close (object%iostream)
object%writing = .false.
else if (object%reading) then
write (msg_buffer, "(A,A,A)") "Events: closing HepMC file '", &
char (object%filename), "'"
call msg_message ()
call hepmc_iostream_close (object%iostream)
object%reading = .false.
end if
end subroutine eio_hepmc_final
@ %def eio_hepmc_final
@ Split event file: increment the counter, close the current file, open a new
one. If the file needs a header, repeat it for the new file.
<<EIO HepMC: eio hepmc: TBP>>=
procedure :: split_out => eio_hepmc_split_out
<<EIO HepMC: procedures>>=
subroutine eio_hepmc_split_out (eio)
class(eio_hepmc_t), intent(inout) :: eio
if (eio%split) then
eio%split_index = eio%split_index + 1
call eio%set_filename ()
write (msg_buffer, "(A,A,A)") "Events: writing to HepMC file '", &
char (eio%filename), "'"
call msg_message ()
call hepmc_iostream_close (eio%iostream)
call hepmc_iostream_open_out (eio%iostream, eio%filename)
end if
end subroutine eio_hepmc_split_out
@ %def eio_hepmc_split_out
@ Common initialization for input and output.
<<EIO HepMC: eio hepmc: TBP>>=
procedure :: common_init => eio_hepmc_common_init
<<EIO HepMC: procedures>>=
subroutine eio_hepmc_common_init (eio, sample, data, extension)
class(eio_hepmc_t), intent(inout) :: eio
type(string_t), intent(in) :: sample
type(string_t), intent(in), optional :: extension
type(event_sample_data_t), intent(in), optional :: data
if (.not. present (data)) &
call msg_bug ("HepMC initialization: missing data")
eio%data = data
if (data%n_beam /= 2) &
call msg_fatal ("HepMC: defined for scattering processes only")
! We could relax this condition now with weighted hepmc events
if (data%unweighted) then
select case (data%norm_mode)
case (NORM_UNIT)
case default; call msg_fatal &
("HepMC: normalization for unweighted events must be '1'")
end select
end if
eio%sample = sample
if (present (extension)) then
eio%extension = extension
end if
call eio%set_filename ()
allocate (eio%proc_num_id (data%n_proc), source = data%proc_num_id)
end subroutine eio_hepmc_common_init
@ %def eio_hepmc_common_init
@ Initialize event writing.
<<EIO HepMC: eio hepmc: TBP>>=
procedure :: init_out => eio_hepmc_init_out
<<EIO HepMC: procedures>>=
subroutine eio_hepmc_init_out (eio, sample, data, success, extension)
class(eio_hepmc_t), intent(inout) :: eio
type(string_t), intent(in) :: sample
type(string_t), intent(in), optional :: extension
type(event_sample_data_t), intent(in), optional :: data
logical, intent(out), optional :: success
call eio%set_splitting (data)
call eio%common_init (sample, data, extension)
write (msg_buffer, "(A,A,A)") "Events: writing to HepMC file '", &
char (eio%filename), "'"
call msg_message ()
eio%writing = .true.
call hepmc_iostream_open_out (eio%iostream, eio%filename)
if (present (success)) success = .true.
end subroutine eio_hepmc_init_out
@ %def eio_hepmc_init_out
@ Initialize event reading. For input, we do not (yet) support split
event files.
<<EIO HepMC: eio hepmc: TBP>>=
procedure :: init_in => eio_hepmc_init_in
<<EIO HepMC: procedures>>=
subroutine eio_hepmc_init_in (eio, sample, data, success, extension)
class(eio_hepmc_t), intent(inout) :: eio
type(string_t), intent(in) :: sample
type(string_t), intent(in), optional :: extension
type(event_sample_data_t), intent(inout), optional :: data
logical, intent(out), optional :: success
logical :: exist
eio%split = .false.
call eio%common_init (sample, data, extension)
write (msg_buffer, "(A,A,A)") "Events: reading from HepMC file '", &
char (eio%filename), "'"
call msg_message ()
inquire (file = char (eio%filename), exist = exist)
if (.not. exist) call msg_fatal ("Events: HepMC file not found.")
eio%reading = .true.
call hepmc_iostream_open_in (eio%iostream, eio%filename)
if (present (success)) success = .true.
end subroutine eio_hepmc_init_in
@ %def eio_hepmc_init_in
@ Switch from input to output: reopen the file for reading.
<<EIO HepMC: eio hepmc: TBP>>=
procedure :: switch_inout => eio_hepmc_switch_inout
<<EIO HepMC: procedures>>=
subroutine eio_hepmc_switch_inout (eio, success)
class(eio_hepmc_t), intent(inout) :: eio
logical, intent(out), optional :: success
call msg_bug ("HepMC: in-out switch not supported")
if (present (success)) success = .false.
end subroutine eio_hepmc_switch_inout
@ %def eio_hepmc_switch_inout
@ Output an event to the allocated HepMC output stream.
<<EIO HepMC: eio hepmc: TBP>>=
procedure :: output => eio_hepmc_output
<<EIO HepMC: procedures>>=
subroutine eio_hepmc_output (eio, event, i_prc, reading, passed, pacify)
class(eio_hepmc_t), intent(inout) :: eio
class(generic_event_t), intent(in), target :: event
integer, intent(in) :: i_prc
logical, intent(in), optional :: reading, passed, pacify
type(particle_set_t), pointer :: pset_ptr
if (present (passed)) then
if (.not. passed) return
end if
if (eio%writing) then
pset_ptr => event%get_particle_set_ptr ()
call hepmc_event_init (eio%hepmc_event, &
proc_id = eio%proc_num_id(i_prc), &
event_id = event%get_index ())
if (eio%output_cross_section) then
call hepmc_event_from_particle_set (eio%hepmc_event, pset_ptr, &
eio%data%cross_section(i_prc), eio%data%error(i_prc))
else
call hepmc_event_from_particle_set (eio%hepmc_event, pset_ptr)
end if
call hepmc_event_set_scale (eio%hepmc_event, event%get_fac_scale ())
call hepmc_event_set_alpha_qcd (eio%hepmc_event, event%get_alpha_s ())
if (.not. eio%data%unweighted) &
call hepmc_event_add_weight (eio%hepmc_event, event%weight_prc)
call hepmc_iostream_write_event (eio%iostream, eio%hepmc_event)
call hepmc_event_final (eio%hepmc_event)
else
call eio%write ()
call msg_fatal ("HepMC file is not open for writing")
end if
end subroutine eio_hepmc_output
@ %def eio_hepmc_output
@ Input an event.
<<EIO HepMC: eio hepmc: TBP>>=
procedure :: input_i_prc => eio_hepmc_input_i_prc
procedure :: input_event => eio_hepmc_input_event
<<EIO HepMC: procedures>>=
subroutine eio_hepmc_input_i_prc (eio, i_prc, iostat)
class(eio_hepmc_t), intent(inout) :: eio
integer, intent(out) :: i_prc
integer, intent(out) :: iostat
logical :: ok
integer :: i, proc_num_id
iostat = 0
call hepmc_event_init (eio%hepmc_event)
call hepmc_iostream_read_event (eio%iostream, eio%hepmc_event, ok)
proc_num_id = hepmc_event_get_process_id (eio%hepmc_event)
if (.not. ok) then
iostat = -1
return
end if
i_prc = 0
FIND_I_PRC: do i = 1, size (eio%proc_num_id)
if (eio%proc_num_id(i) == proc_num_id) then
i_prc = i
exit FIND_I_PRC
end if
end do FIND_I_PRC
if (i_prc == 0) call err_index
contains
subroutine err_index
call msg_error ("HepMC: reading events: undefined process ID " &
// char (str (proc_num_id)) // ", aborting read")
iostat = 1
end subroutine err_index
end subroutine eio_hepmc_input_i_prc
subroutine eio_hepmc_input_event (eio, event, iostat)
class(eio_hepmc_t), intent(inout) :: eio
class(generic_event_t), intent(inout), target :: event
integer, intent(out) :: iostat
iostat = 0
call event%reset_contents ()
call event%select (1, 1, 1)
call hepmc_to_event (event, eio%hepmc_event, &
eio%fallback_model, &
recover_beams = eio%recover_beams, &
use_alpha_s = eio%use_alphas_from_file, &
use_scale = eio%use_scale_from_file)
call hepmc_event_final (eio%hepmc_event)
end subroutine eio_hepmc_input_event
@ %def eio_hepmc_input_i_prc
@ %def eio_hepmc_input_event
@
<<EIO HepMC: eio hepmc: TBP>>=
procedure :: skip => eio_hepmc_skip
<<EIO HepMC: procedures>>=
subroutine eio_hepmc_skip (eio, iostat)
class(eio_hepmc_t), intent(inout) :: eio
integer, intent(out) :: iostat
iostat = 0
end subroutine eio_hepmc_skip
@ %def eio_hepmc_skip
@
\subsection{Unit tests}
Test module, followed by the corresponding implementation module.
<<[[eio_hepmc_ut.f90]]>>=
<<File header>>
module eio_hepmc_ut
use unit_tests
use eio_hepmc_uti
<<Standard module head>>
<<EIO HepMC: public test>>
contains
<<EIO HepMC: test driver>>
end module eio_hepmc_ut
@ %def eio_hepmc_ut
@
<<[[eio_hepmc_uti.f90]]>>=
<<File header>>
module eio_hepmc_uti
<<Use kinds>>
<<Use strings>>
use io_units
use model_data
use event_base
use eio_data
use eio_base
use eio_hepmc
use eio_base_ut, only: eio_prepare_test, eio_cleanup_test
use eio_base_ut, only: eio_prepare_fallback_model, eio_cleanup_fallback_model
<<Standard module head>>
<<EIO HepMC: test declarations>>
contains
<<EIO HepMC: tests>>
end module eio_hepmc_uti
@ %def eio_hepmc_ut
@ API: driver for the unit tests below.
<<EIO HepMC: public test>>=
public :: eio_hepmc_test
<<EIO HepMC: test driver>>=
subroutine eio_hepmc_test (u, results)
integer, intent(in) :: u
type(test_results_t), intent(inout) :: results
<<EIO HepMC: execute tests>>
end subroutine eio_hepmc_test
@ %def eio_hepmc_test
@
\subsubsection{Test I/O methods}
We test the implementation of all I/O methods.
<<EIO HepMC: execute tests>>=
call test (eio_hepmc_1, "eio_hepmc_1", &
"write event contents", &
u, results)
<<EIO HepMC: test declarations>>=
public :: eio_hepmc_1
<<EIO HepMC: tests>>=
subroutine eio_hepmc_1 (u)
integer, intent(in) :: u
class(generic_event_t), pointer :: event
type(event_sample_data_t) :: data
class(eio_t), allocatable :: eio
type(string_t) :: sample
integer :: u_file, iostat
character(116) :: buffer
write (u, "(A)") "* Test output: eio_hepmc_1"
write (u, "(A)") "* Purpose: write a HepMC file"
write (u, "(A)")
write (u, "(A)") "* Initialize test process"
call eio_prepare_test (event, unweighted=.false.)
call data%init (1)
data%n_beam = 2
data%unweighted = .true.
data%norm_mode = NORM_UNIT
data%pdg_beam = 25
data%energy_beam = 500
data%proc_num_id = [42]
data%cross_section(1) = 100
data%error(1) = 1
data%total_cross_section = sum (data%cross_section)
write (u, "(A)")
write (u, "(A)") "* Generate and write an event"
write (u, "(A)")
sample = "eio_hepmc_1"
allocate (eio_hepmc_t :: eio)
select type (eio)
type is (eio_hepmc_t)
call eio%set_parameters ()
end select
call eio%init_out (sample, data)
call event%generate (1, [0._default, 0._default])
call event%set_index (55)
call eio%output (event, i_prc = 1)
call eio%write (u)
call eio%final ()
write (u, "(A)")
write (u, "(A)") "* File contents (blanking out last two digits):"
write (u, "(A)")
u_file = free_unit ()
open (u_file, file = char (sample // ".hepmc"), &
action = "read", status = "old")
do
read (u_file, "(A)", iostat = iostat) buffer
if (iostat /= 0) exit
if (trim (buffer) == "") cycle
if (buffer(1:14) == "HepMC::Version") cycle
if (buffer(1:10) == "P 10001 25") &
call buffer_blanker (buffer, 32, 55, 78)
if (buffer(1:10) == "P 10002 25") &
call buffer_blanker (buffer, 33, 56, 79)
if (buffer(1:10) == "P 10003 25") &
call buffer_blanker (buffer, 29, 53, 78, 101)
if (buffer(1:10) == "P 10004 25") &
call buffer_blanker (buffer, 28, 51, 76, 99)
write (u, "(A)") trim (buffer)
end do
close (u_file)
write (u, "(A)")
write (u, "(A)") "* Reset data"
write (u, "(A)")
deallocate (eio)
allocate (eio_hepmc_t :: eio)
select type (eio)
type is (eio_hepmc_t)
call eio%set_parameters ()
end select
call eio%write (u)
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio_cleanup_test (event)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_hepmc_1"
contains
subroutine buffer_blanker (buf, pos1, pos2, pos3, pos4)
character(len=*), intent(inout) :: buf
integer, intent(in) :: pos1, pos2, pos3
integer, intent(in), optional :: pos4
type(string_t) :: line
line = var_str (trim (buf))
line = replace (line, pos1, "XX")
line = replace (line, pos2, "XX")
line = replace (line, pos3, "XX")
if (present (pos4)) then
line = replace (line, pos4, "XX")
end if
line = replace (line, "4999999999999", "5000000000000")
buf = char (line)
end subroutine buffer_blanker
end subroutine eio_hepmc_1
@ %def eio_hepmc_1
@ Test also the reading of HepMC events.
<<EIO HepMC: execute tests>>=
call test (eio_hepmc_2, "eio_hepmc_2", &
"read event contents", &
u, results)
<<EIO HepMC: test declarations>>=
public :: eio_hepmc_2
<<EIO HepMC: tests>>=
subroutine eio_hepmc_2 (u)
integer, intent(in) :: u
class(model_data_t), pointer :: fallback_model
class(generic_event_t), pointer :: event
type(event_sample_data_t) :: data
class(eio_t), allocatable :: eio
type(string_t) :: sample
integer :: u_file, iostat, i_prc
write (u, "(A)") "* Test output: eio_hepmc_2"
write (u, "(A)") "* Purpose: read a HepMC event"
write (u, "(A)")
write (u, "(A)") "* Write a HepMC data file"
write (u, "(A)")
u_file = free_unit ()
sample = "eio_hepmc_2"
open (u_file, file = char (sample // ".hepmc"), &
status = "replace", action = "readwrite")
write (u_file, "(A)") "HepMC::Version 2.06.09"
write (u_file, "(A)") "HepMC::IO_GenEvent-START_EVENT_LISTING"
write (u_file, "(A)") "E 66 -1 -1.0000000000000000e+00 &
&-1.0000000000000000e+00 &
&-1.0000000000000000e+00 42 0 1 10001 10002 0 0"
write (u_file, "(A)") "U GEV MM"
write (u_file, "(A)") "V -1 0 0 0 0 0 2 2 0"
write (u_file, "(A)") "P 10001 25 0 0 4.8412291827592713e+02 &
&5.0000000000000000e+02 &
&1.2499999999999989e+02 3 0 0 -1 0"
write (u_file, "(A)") "P 10002 25 0 0 -4.8412291827592713e+02 &
&5.0000000000000000e+02 &
&1.2499999999999989e+02 3 0 0 -1 0"
write (u_file, "(A)") "P 10003 25 -1.4960220911365536e+02 &
&-4.6042825611414656e+02 &
&0 5.0000000000000000e+02 1.2500000000000000e+02 1 0 0 0 0"
write (u_file, "(A)") "P 10004 25 1.4960220911365536e+02 &
&4.6042825611414656e+02 &
&0 5.0000000000000000e+02 1.2500000000000000e+02 1 0 0 0 0"
write (u_file, "(A)") "HepMC::IO_GenEvent-END_EVENT_LISTING"
close (u_file)
write (u, "(A)") "* Initialize test process"
write (u, "(A)")
call eio_prepare_fallback_model (fallback_model)
call eio_prepare_test (event, unweighted=.false.)
allocate (eio_hepmc_t :: eio)
select type (eio)
type is (eio_hepmc_t)
call eio%set_parameters (recover_beams = .false.)
end select
call eio%set_fallback_model (fallback_model)
call data%init (1)
data%n_beam = 2
data%unweighted = .true.
data%norm_mode = NORM_UNIT
data%pdg_beam = 25
data%energy_beam = 500
data%proc_num_id = [42]
call data%write (u)
write (u, "(A)")
write (u, "(A)") "* Initialize"
write (u, "(A)")
call eio%init_in (sample, data)
call eio%write (u)
write (u, "(A)")
write (u, "(A)") "* Read event"
write (u, "(A)")
call eio%input_i_prc (i_prc, iostat)
select type (eio)
type is (eio_hepmc_t)
write (u, "(A,I0,A,I0)") "Found process #", i_prc, &
" with ID = ", eio%proc_num_id(i_prc)
end select
call eio%input_event (event, iostat)
call event%write (u)
write (u, "(A)")
write (u, "(A)") "* Read closing"
write (u, "(A)")
call eio%input_i_prc (i_prc, iostat)
write (u, "(A,I0)") "iostat = ", iostat
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio%final ()
call eio_cleanup_test (event)
call eio_cleanup_fallback_model (fallback_model)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_hepmc_2"
end subroutine eio_hepmc_2
@ %def eio_hepmc_2
@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
\section{LCIO Output}
The LCIO event record is standardized for the use with Linear $e^+e^-$
colliders. It is a binary event format. We try our best at using it
for both input and output.
<<[[eio_lcio.f90]]>>=
<<File header>>
module eio_lcio
<<Use strings>>
use io_units
use string_utils
use diagnostics
use particles
use event_base
use hep_events
use eio_data
use eio_base
use lcio_interface
<<Standard module head>>
<<EIO LCIO: public>>
<<EIO LCIO: types>>
contains
<<EIO LCIO: procedures>>
end module eio_lcio
@ %def eio_lcio
@
\subsection{Type}
A type [[lcio_event]] is introduced as container to store LCIO event
data, particularly for splitting the reading into read out of the process
index and the proper event data.
Note: the [[keep_beams]] flag is not supported.
<<EIO LCIO: public>>=
public :: eio_lcio_t
<<EIO LCIO: types>>=
type, extends (eio_t) :: eio_lcio_t
logical :: writing = .false.
logical :: reading = .false.
type(event_sample_data_t) :: data
logical :: recover_beams = .false.
logical :: use_alphas_from_file = .false.
logical :: use_scale_from_file = .false.
type(lcio_writer_t) :: lcio_writer
type(lcio_reader_t) :: lcio_reader
type(lcio_run_header_t) :: lcio_run_hdr
type(lcio_event_t) :: lcio_event
integer, dimension(:), allocatable :: proc_num_id
contains
<<EIO LCIO: eio lcio: TBP>>
end type eio_lcio_t
@ %def eio_lcio_t
@
\subsection{Specific Methods}
Set parameters that are specifically used with LCIO.
<<EIO LCIO: eio lcio: TBP>>=
procedure :: set_parameters => eio_lcio_set_parameters
<<EIO LCIO: procedures>>=
subroutine eio_lcio_set_parameters &
(eio, recover_beams, use_alphas_from_file, use_scale_from_file, &
extension)
class(eio_lcio_t), intent(inout) :: eio
logical, intent(in), optional :: recover_beams
logical, intent(in), optional :: use_alphas_from_file
logical, intent(in), optional :: use_scale_from_file
type(string_t), intent(in), optional :: extension
if (present (recover_beams)) eio%recover_beams = recover_beams
if (present (use_alphas_from_file)) &
eio%use_alphas_from_file = use_alphas_from_file
if (present (use_scale_from_file)) &
eio%use_scale_from_file = use_scale_from_file
if (present (extension)) then
eio%extension = extension
else
eio%extension = "slcio"
end if
end subroutine eio_lcio_set_parameters
@ %def eio_lcio_set_parameters
@
\subsection{Common Methods}
Output. This is not the actual event format, but a readable account
of the current object status.
<<EIO LCIO: eio lcio: TBP>>=
procedure :: write => eio_lcio_write
<<EIO LCIO: procedures>>=
subroutine eio_lcio_write (object, unit)
class(eio_lcio_t), intent(in) :: object
integer, intent(in), optional :: unit
integer :: u, i
u = given_output_unit (unit)
write (u, "(1x,A)") "LCIO event stream:"
if (object%writing) then
write (u, "(3x,A,A)") "Writing to file = ", char (object%filename)
else if (object%reading) then
write (u, "(3x,A,A)") "Reading from file = ", char (object%filename)
else
write (u, "(3x,A)") "[closed]"
end if
write (u, "(3x,A,L1)") "Recover beams = ", object%recover_beams
write (u, "(3x,A,L1)") "Alpha_s from file = ", &
object%use_alphas_from_file
write (u, "(3x,A,L1)") "Scale from file = ", &
object%use_scale_from_file
write (u, "(3x,A,A,A)") "File extension = '", &
char (object%extension), "'"
if (allocated (object%proc_num_id)) then
write (u, "(3x,A)") "Numerical process IDs:"
do i = 1, size (object%proc_num_id)
write (u, "(5x,I0,': ',I0)") i, object%proc_num_id(i)
end do
end if
end subroutine eio_lcio_write
@ %def eio_lcio_write
@ Finalizer: close any open file.
<<EIO LCIO: eio lcio: TBP>>=
procedure :: final => eio_lcio_final
<<EIO LCIO: procedures>>=
subroutine eio_lcio_final (object)
class(eio_lcio_t), intent(inout) :: object
if (allocated (object%proc_num_id)) deallocate (object%proc_num_id)
if (object%writing) then
write (msg_buffer, "(A,A,A)") "Events: closing LCIO file '", &
char (object%filename), "'"
call msg_message ()
call lcio_writer_close (object%lcio_writer)
object%writing = .false.
else if (object%reading) then
write (msg_buffer, "(A,A,A)") "Events: closing LCIO file '", &
char (object%filename), "'"
call msg_message ()
call lcio_reader_close (object%lcio_reader)
object%reading = .false.
end if
end subroutine eio_lcio_final
@ %def eio_lcio_final
@ Split event file: increment the counter, close the current file, open a new
one. If the file needs a header, repeat it for the new file.
<<EIO LCIO: eio lcio: TBP>>=
procedure :: split_out => eio_lcio_split_out
<<EIO LCIO: procedures>>=
subroutine eio_lcio_split_out (eio)
class(eio_lcio_t), intent(inout) :: eio
if (eio%split) then
eio%split_index = eio%split_index + 1
call eio%set_filename ()
write (msg_buffer, "(A,A,A)") "Events: writing to LCIO file '", &
char (eio%filename), "'"
call msg_message ()
call lcio_writer_close (eio%lcio_writer)
call lcio_writer_open_out (eio%lcio_writer, eio%filename)
end if
end subroutine eio_lcio_split_out
@ %def eio_lcio_split_out
@ Common initialization for input and output.
<<EIO LCIO: eio lcio: TBP>>=
procedure :: common_init => eio_lcio_common_init
<<EIO LCIO: procedures>>=
subroutine eio_lcio_common_init (eio, sample, data, extension)
class(eio_lcio_t), intent(inout) :: eio
type(string_t), intent(in) :: sample
type(string_t), intent(in), optional :: extension
type(event_sample_data_t), intent(in), optional :: data
if (.not. present (data)) &
call msg_bug ("LCIO initialization: missing data")
eio%data = data
if (data%n_beam /= 2) &
call msg_fatal ("LCIO: defined for scattering processes only")
if (data%unweighted) then
select case (data%norm_mode)
case (NORM_UNIT)
case default; call msg_fatal &
("LCIO: normalization for unweighted events must be '1'")
end select
else
call msg_fatal ("LCIO: events must be unweighted")
end if
eio%sample = sample
if (present (extension)) then
eio%extension = extension
end if
call eio%set_filename ()
allocate (eio%proc_num_id (data%n_proc), source = data%proc_num_id)
end subroutine eio_lcio_common_init
@ %def eio_lcio_common_init
@ Initialize event writing.
<<EIO LCIO: eio lcio: TBP>>=
procedure :: init_out => eio_lcio_init_out
<<EIO LCIO: procedures>>=
subroutine eio_lcio_init_out (eio, sample, data, success, extension)
class(eio_lcio_t), intent(inout) :: eio
type(string_t), intent(in) :: sample
type(string_t), intent(in), optional :: extension
type(event_sample_data_t), intent(in), optional :: data
logical, intent(out), optional :: success
call eio%set_splitting (data)
call eio%common_init (sample, data, extension)
write (msg_buffer, "(A,A,A)") "Events: writing to LCIO file '", &
char (eio%filename), "'"
call msg_message ()
eio%writing = .true.
call lcio_writer_open_out (eio%lcio_writer, eio%filename)
call lcio_run_header_init (eio%lcio_run_hdr)
call lcio_run_header_write (eio%lcio_writer, eio%lcio_run_hdr)
if (present (success)) success = .true.
end subroutine eio_lcio_init_out
@ %def eio_lcio_init_out
@ Initialize event reading. For input, we do not (yet) support split
event files.
<<EIO LCIO: eio lcio: TBP>>=
procedure :: init_in => eio_lcio_init_in
<<EIO LCIO: procedures>>=
subroutine eio_lcio_init_in (eio, sample, data, success, extension)
class(eio_lcio_t), intent(inout) :: eio
type(string_t), intent(in) :: sample
type(string_t), intent(in), optional :: extension
type(event_sample_data_t), intent(inout), optional :: data
logical, intent(out), optional :: success
logical :: exist
eio%split = .false.
call eio%common_init (sample, data, extension)
write (msg_buffer, "(A,A,A)") "Events: reading from LCIO file '", &
char (eio%filename), "'"
call msg_message ()
inquire (file = char (eio%filename), exist = exist)
if (.not. exist) call msg_fatal ("Events: LCIO file not found.")
eio%reading = .true.
call lcio_open_file (eio%lcio_reader, eio%filename)
if (present (success)) success = .true.
end subroutine eio_lcio_init_in
@ %def eio_lcio_init_in
@ Switch from input to output: reopen the file for reading.
<<EIO LCIO: eio lcio: TBP>>=
procedure :: switch_inout => eio_lcio_switch_inout
<<EIO LCIO: procedures>>=
subroutine eio_lcio_switch_inout (eio, success)
class(eio_lcio_t), intent(inout) :: eio
logical, intent(out), optional :: success
call msg_bug ("LCIO: in-out switch not supported")
if (present (success)) success = .false.
end subroutine eio_lcio_switch_inout
@ %def eio_lcio_switch_inout
@ Output an event to the allocated LCIO writer.
<<EIO LCIO: eio lcio: TBP>>=
procedure :: output => eio_lcio_output
<<EIO LCIO: procedures>>=
subroutine eio_lcio_output (eio, event, i_prc, reading, passed, pacify)
class(eio_lcio_t), intent(inout) :: eio
class(generic_event_t), intent(in), target :: event
integer, intent(in) :: i_prc
logical, intent(in), optional :: reading, passed, pacify
type(particle_set_t), pointer :: pset_ptr
if (present (passed)) then
if (.not. passed) return
end if
if (eio%writing) then
pset_ptr => event%get_particle_set_ptr ()
call lcio_event_init (eio%lcio_event, &
proc_id = eio%proc_num_id (i_prc), &
event_id = event%get_index ())
call lcio_event_from_particle_set (eio%lcio_event, pset_ptr)
call lcio_event_set_weight (eio%lcio_event, event%weight_prc)
call lcio_event_set_sqrts (eio%lcio_event, event%get_sqrts ())
call lcio_event_set_scale (eio%lcio_event, event%get_fac_scale ())
call lcio_event_set_alpha_qcd (eio%lcio_event, event%get_alpha_s ())
call lcio_event_set_xsec (eio%lcio_event, eio%data%cross_section(i_prc), &
eio%data%error(i_prc))
call lcio_event_set_polarization (eio%lcio_event, &
event%get_polarization ())
call lcio_event_set_beam_file (eio%lcio_event, &
event%get_beam_file ())
call lcio_event_set_process_name (eio%lcio_event, &
event%get_process_name ())
call lcio_event_write (eio%lcio_writer, eio%lcio_event)
call lcio_event_final (eio%lcio_event)
else
call eio%write ()
call msg_fatal ("LCIO file is not open for writing")
end if
end subroutine eio_lcio_output
@ %def eio_lcio_output
@ Input an event.
<<EIO LCIO: eio lcio: TBP>>=
procedure :: input_i_prc => eio_lcio_input_i_prc
procedure :: input_event => eio_lcio_input_event
<<EIO LCIO: procedures>>=
subroutine eio_lcio_input_i_prc (eio, i_prc, iostat)
class(eio_lcio_t), intent(inout) :: eio
integer, intent(out) :: i_prc
integer, intent(out) :: iostat
logical :: ok
integer :: i, proc_num_id
iostat = 0
call lcio_read_event (eio%lcio_reader, eio%lcio_event, ok)
if (.not. ok) then
iostat = -1
return
end if
proc_num_id = lcio_event_get_process_id (eio%lcio_event)
i_prc = 0
FIND_I_PRC: do i = 1, size (eio%proc_num_id)
if (eio%proc_num_id(i) == proc_num_id) then
i_prc = i
exit FIND_I_PRC
end if
end do FIND_I_PRC
if (i_prc == 0) call err_index
contains
subroutine err_index
call msg_error ("LCIO: reading events: undefined process ID " &
// char (str (proc_num_id)) // ", aborting read")
iostat = 1
end subroutine err_index
end subroutine eio_lcio_input_i_prc
subroutine eio_lcio_input_event (eio, event, iostat)
class(eio_lcio_t), intent(inout) :: eio
class(generic_event_t), intent(inout), target :: event
integer, intent(out) :: iostat
iostat = 0
call event%reset_contents ()
call event%select (1, 1, 1)
call event%set_index (lcio_event_get_event_index (eio%lcio_event))
call lcio_to_event (event, eio%lcio_event, eio%fallback_model, &
recover_beams = eio%recover_beams, &
use_alpha_s = eio%use_alphas_from_file, &
use_scale = eio%use_scale_from_file)
call lcio_event_final (eio%lcio_event)
end subroutine eio_lcio_input_event
@ %def eio_lcio_input_i_prc
@ %def eio_lcio_input_event
@
<<EIO LCIO: eio lcio: TBP>>=
procedure :: skip => eio_lcio_skip
<<EIO LCIO: procedures>>=
subroutine eio_lcio_skip (eio, iostat)
class(eio_lcio_t), intent(inout) :: eio
integer, intent(out) :: iostat
iostat = 0
end subroutine eio_lcio_skip
@ %def eio_lcio_skip
@
\subsection{Unit tests}
Test module, followed by the corresponding implementation module.
<<[[eio_lcio_ut.f90]]>>=
<<File header>>
module eio_lcio_ut
use unit_tests
use eio_lcio_uti
<<Standard module head>>
<<EIO LCIO: public test>>
contains
<<EIO LCIO: test driver>>
end module eio_lcio_ut
@ %def eio_lcio_ut
@
<<[[eio_lcio_uti.f90]]>>=
<<File header>>
module eio_lcio_uti
<<Use kinds>>
<<Use strings>>
use io_units
use model_data
use particles
use event_base
use eio_data
use eio_base
use hep_events
use lcio_interface
use eio_lcio
use eio_base_ut, only: eio_prepare_test, eio_cleanup_test
use eio_base_ut, only: eio_prepare_fallback_model, eio_cleanup_fallback_model
<<Standard module head>>
<<EIO LCIO: test declarations>>
contains
<<EIO LCIO: tests>>
end module eio_lcio_uti
@ %def eio_lcio_ut
@ API: driver for the unit tests below.
<<EIO LCIO: public test>>=
public :: eio_lcio_test
<<EIO LCIO: test driver>>=
subroutine eio_lcio_test (u, results)
integer, intent(in) :: u
type(test_results_t), intent(inout) :: results
<<EIO LCIO: execute tests>>
end subroutine eio_lcio_test
@ %def eio_lcio_test
@
\subsubsection{Test I/O methods}
We test the implementation of all I/O methods.
<<EIO LCIO: execute tests>>=
call test (eio_lcio_1, "eio_lcio_1", &
"write event contents", &
u, results)
<<EIO LCIO: test declarations>>=
public :: eio_lcio_1
<<EIO LCIO: tests>>=
subroutine eio_lcio_1 (u)
integer, intent(in) :: u
class(generic_event_t), pointer :: event
type(event_sample_data_t) :: data
class(eio_t), allocatable :: eio
type(particle_set_t), pointer :: pset_ptr
type(string_t) :: sample
integer :: u_file, iostat
character(215) :: buffer
write (u, "(A)") "* Test output: eio_lcio_1"
write (u, "(A)") "* Purpose: write a LCIO file"
write (u, "(A)")
write (u, "(A)") "* Initialize test process"
call eio_prepare_test (event)
call data%init (1)
data%n_beam = 2
data%unweighted = .true.
data%norm_mode = NORM_UNIT
data%pdg_beam = 25
data%energy_beam = 500
data%proc_num_id = [42]
data%cross_section(1) = 100
data%error(1) = 1
data%total_cross_section = sum (data%cross_section)
write (u, "(A)")
write (u, "(A)") "* Generate and write an event"
write (u, "(A)")
sample = "eio_lcio_1"
allocate (eio_lcio_t :: eio)
select type (eio)
type is (eio_lcio_t)
call eio%set_parameters ()
end select
call eio%init_out (sample, data)
call event%generate (1, [0._default, 0._default])
call event%set_index (77)
call event%pacify_particle_set ()
call eio%output (event, i_prc = 1)
call eio%write (u)
call eio%final ()
write (u, "(A)")
write (u, "(A)") "* Reset data"
write (u, "(A)")
deallocate (eio)
allocate (eio_lcio_t :: eio)
select type (eio)
type is (eio_lcio_t)
call eio%set_parameters ()
end select
call eio%write (u)
write (u, "(A)")
write (u, "(A)") "* Write LCIO file contents to ASCII file"
write (u, "(A)")
select type (eio)
type is (eio_lcio_t)
call lcio_event_init (eio%lcio_event, &
proc_id = 42, &
event_id = event%get_index ())
pset_ptr => event%get_particle_set_ptr ()
call lcio_event_from_particle_set &
(eio%lcio_event, pset_ptr)
call write_lcio_event (eio%lcio_event, var_str ("test_file.slcio"))
call lcio_event_final (eio%lcio_event)
end select
write (u, "(A)")
write (u, "(A)") "* Read in ASCII contents of LCIO file"
write (u, "(A)")
u_file = free_unit ()
open (u_file, file = "test_file.slcio", &
action = "read", status = "old")
do
read (u_file, "(A)", iostat = iostat) buffer
if (iostat /= 0) exit
if (trim (buffer) == "") cycle
if (buffer(1:12) == " - timestamp") cycle
if (buffer(1:6) == " date:") cycle
write (u, "(A)") trim (buffer)
end do
close (u_file)
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio_cleanup_test (event)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_lcio_1"
end subroutine eio_lcio_1
@ %def eio_lcio_1
@ Test also the reading of LCIO events.
<<EIO LCIO: execute tests>>=
call test (eio_lcio_2, "eio_lcio_2", &
"read event contents", &
u, results)
<<EIO LCIO: test declarations>>=
public :: eio_lcio_2
<<EIO LCIO: tests>>=
subroutine eio_lcio_2 (u)
integer, intent(in) :: u
class(model_data_t), pointer :: fallback_model
class(generic_event_t), pointer :: event
type(event_sample_data_t) :: data
class(eio_t), allocatable :: eio
type(string_t) :: sample
integer :: iostat, i_prc
write (u, "(A)") "* Test output: eio_lcio_2"
write (u, "(A)") "* Purpose: read a LCIO event"
write (u, "(A)")
write (u, "(A)") "* Initialize test process"
call eio_prepare_fallback_model (fallback_model)
call eio_prepare_test (event)
call data%init (1)
data%n_beam = 2
data%unweighted = .true.
data%norm_mode = NORM_UNIT
data%pdg_beam = 25
data%energy_beam = 500
data%proc_num_id = [42]
data%cross_section(1) = 100
data%error(1) = 1
data%total_cross_section = sum (data%cross_section)
write (u, "(A)")
write (u, "(A)") "* Generate and write an event"
write (u, "(A)")
sample = "eio_lcio_2"
allocate (eio_lcio_t :: eio)
select type (eio)
type is (eio_lcio_t)
call eio%set_parameters (recover_beams = .false.)
end select
call eio%set_fallback_model (fallback_model)
call eio%init_out (sample, data)
call event%generate (1, [0._default, 0._default])
call event%set_index (88)
call event%evaluate_expressions ()
call event%pacify_particle_set ()
call eio%output (event, i_prc = 1)
call eio%write (u)
call eio%final ()
deallocate (eio)
call event%reset_contents ()
call event%reset_index ()
write (u, "(A)")
write (u, "(A)") "* Initialize"
write (u, "(A)")
allocate (eio_lcio_t :: eio)
select type (eio)
type is (eio_lcio_t)
call eio%set_parameters (recover_beams = .false.)
end select
call eio%set_fallback_model (fallback_model)
call data%init (1)
data%n_beam = 2
data%unweighted = .true.
data%norm_mode = NORM_UNIT
data%pdg_beam = 25
data%energy_beam = 500
data%proc_num_id = [42]
call data%write (u)
write (u, *)
write (u, "(A)") "* Initialize"
write (u, "(A)")
call eio%init_in (sample, data)
call eio%write (u)
write (u, "(A)")
write (u, "(A)") "* Read event"
write (u, "(A)")
call eio%input_i_prc (i_prc, iostat)
select type (eio)
type is (eio_lcio_t)
write (u, "(A,I0,A,I0)") "Found process #", i_prc, &
" with ID = ", eio%proc_num_id(i_prc)
end select
call eio%input_event (event, iostat)
call event%write (u)
write (u, "(A)")
write (u, "(A)") "* Read closing"
write (u, "(A)")
call eio%input_i_prc (i_prc, iostat)
write (u, "(A,I0)") "iostat = ", iostat
write (u, "(A)")
write (u, "(A)") "* Cleanup"
call eio%final ()
call eio_cleanup_test (event)
call eio_cleanup_fallback_model (fallback_model)
write (u, "(A)")
write (u, "(A)") "* Test output end: eio_lcio_2"
end subroutine eio_lcio_2
@ %def eio_lcio_2

File Metadata

Mime Type
text/x-diff
Expires
Tue, Nov 19, 7:06 PM (1 d, 12 h)
Storage Engine
blob
Storage Format
Raw Data
Storage Handle
3805758
Default Alt Text
(775 KB)

Event Timeline