EIC Software
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
lscale.F
Go to the documentation of this file. Or view the newest version in sPHENIX GitHub for file lscale.F
1 
2 C **********************************************************************
3 
4  SUBROUTINE lscale(INFIN,QMAX)
5 
6  IMPLICIT NONE
7 
8 C...Give maximum virtuality of partons in parton showers.
9 
10 *
11 * to avoid variable conflictions, a second keep element is necessary
12 * with the same common block name (see LPTOU2)
13 *
14  COMMON /leptou/ cut(14),lst(40),parl(30),
15  & x,y,w2,q2,u
16  REAL cut,parl,x,y,w2,q2,u
17  INTEGER lst
18  SAVE /leptou/
19 
20  COMMON /pypara/ ipy(80),pypar(80),pyvar(80)
21  REAL pypar,pyvar
22  INTEGER ipy
23  SAVE /pypara/
24 
25  INTEGER nlupdm,nplbuf
26  parameter(nlupdm=4000,nplbuf=5)
27  common/lujets/n,k(nlupdm,5),p(nlupdm,nplbuf),v(nlupdm,5)
28  INTEGER n,k
29  REAL p,v
30  SAVE /lujets/
31 
32 C... Power in f(x0)=(1-x0)**power used for scale x0*W2
33  INTEGER infin,i,j
34  REAL power,qmax,four,x0,rlu
35  DATA power/3./
36  four(i,j)=p(i,4)*p(j,4)-p(i,1)*p(j,1)-p(i,2)*p(j,2)-p(i,3)*p(j,3)
37 
38  qmax=0.1
39  IF(lst(8).GE.2.AND.lst(8).LE.5) THEN
40 C...Parton showers without matrix elements matching
41  IF(lst(9).EQ.1) THEN
42  qmax=q2
43  ELSEIF(lst(9).EQ.2) THEN
44  qmax=w2
45  ELSEIF(lst(9).EQ.3) THEN
46  qmax=sqrt(w2*q2)
47  ELSEIF(lst(9).EQ.4) THEN
48  qmax=q2*(1.-x)
49  ELSEIF(lst(9).EQ.5) THEN
50  qmax=q2*(1.-x)*max(1.,log(1./max(1.e-06,x)))
51  ELSEIF(lst(9).EQ.6) THEN
52  x0=1.d0-(1.d0-dble(x))*rlu(0)**(1./(power+1.))
53  qmax=x0*w2
54  ELSEIF(lst(9).EQ.9) THEN
55  qmax=w2**(2./3.)
56  ELSE
57  WRITE(6,*) ' Warning, LSCALE: LST(9)=',lst(9),' not allowed'
58  ENDIF
59  ELSEIF(lst(8).GT.10.AND.lst(24).EQ.1.AND.mod(lst(8),10).NE.9) THEN
60 C...Parton showers added to q-event from 1st order matrix elements
61  IF(lst(20).LE.1) THEN
62  qmax=parl(27)*w2
63  ELSEIF(lst(20).EQ.2) THEN
64  qmax=parl(27)*q2
65  ELSEIF(lst(20).EQ.3) THEN
66  qmax=parl(9)*q2
67  ELSEIF(lst(20).EQ.4) THEN
68  qmax=parl(9)*q2
69  IF(infin.LT.0) qmax=parl(27)*q2/x
70  ELSEIF(lst(20).EQ.5) THEN
71  qmax=parl(9)
72  IF(infin.LT.0) qmax=parl(27)*q2/x
73  ELSEIF(lst(20).EQ.6) THEN
74  qmax=parl(27)
75  IF(infin.LT.0) qmax=parl(8)*q2/x
76  ELSE
77  WRITE(6,*) 'LSCALE: No such jet scheme!'
78  ENDIF
79  ELSEIF(lst(8).GT.10.AND.mod(lst(8),10).NE.9) THEN
80 C...Parton showers added to qg-/qqbar-event from 1st order matrix elements
81 C...Scale given by invariant mass of final parton pair
82  qmax=p(27,5)**2
83  IF(infin.LT.0)
84  & qmax=max(abs(-q2-2.*four(25,21)),abs(-q2-2.*four(26,21)))
85  ENDIF
86  qmax=sqrt(qmax)
87 
88  RETURN
89  END