EIC Software
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
lremh.F
Go to the documentation of this file. Or view the newest version in sPHENIX GitHub for file lremh.F
1 
2 C **********************************************************************
3 
4  SUBROUTINE lremh(IFLRO,PT,IFLR,K2,Z)
5 
6  IMPLICIT NONE
7 
8 C...Gives flavour and energy-momentum fraction Z for the particle
9 C...to be produced out of the target remnant when that is not a
10 C...simple diquark.
11 
12 *
13 * to avoid variable conflictions, a second keep element is necessary
14 * with the same common block name (see LPTOU2)
15 *
16  COMMON /leptou/ cut(14),lst(40),parl(30),
17  & x,y,w2,q2,u
18  REAL cut,parl,x,y,w2,q2,u
19  INTEGER lst
20  SAVE /leptou/
21 
22  common/ludat1/mstu(200),paru(200),mstj(200),parj(200)
23  INTEGER mstu,mstj
24  REAL paru,parj
25  SAVE /ludat1/
26 
27  COMMON /linter/ pari(50),ewqc(2,2,8),qc(8),zl(2,4),zq(2,8),pq(17)
28  REAL pari,ewqc,qc,zl,zq,pq
29  SAVE /linter/
30 
31  INTEGER iflro,iflr,k2,idum,ksp,kc2,k2a
32  INTEGER iflq,iflqq,lucomp
33  REAL rlu,ulmass,tm2,pt
34  REAL z,amsp,amk2,a,fc
35 
36 C...Flavours fixed when calling from LQQBEV OR LYREMN
37  IF(iflro.EQ.0) goto 200
38 
39 C...Split target remnant qqqQ -> qqQ + q or qqqQbar -> qQbar + qq
40 C...Q (Qbar) is the partner to the struck sea quark
41 C...qqq are the nucleon valence quarks from which a quark q or a
42 C...diquark qq is chosen at random to form a jet system with the
43 C...scattered sea antiquark or quark, respectively, the other parton
44 C...forms a baryon qqQ or meson qQbar, respectively.
45  100 iflq=int(1.+lst(22)/3.+rlu(0))
46  IF(iflq.EQ.lst(22)) THEN
47  iflqq=2101
48  IF(rlu(0).GT.parl(4)) iflqq =2103
49  ELSE
50  iflqq=1000*iflq+100*iflq+3
51  ENDIF
52  iflq=3-iflq
53 
54 C...Choose flavour of hadron and parton for jet system
55  IF(iflro.GT.0) THEN
56  CALL lukfdi(iflqq,iflro,idum,k2)
57  IF(k2.EQ.0) goto 100
58  iflr=iflq
59  ELSE
60  CALL lukfdi(iflq,iflro,idum,k2)
61  IF(k2.EQ.0) goto 100
62  iflr=iflqq
63  ENDIF
64 
65 C...Entry from LQQBEV & LYREMN with flavours given, choose E-p fraction
66  200 ksp=iflr
67 C...Split energy-momentum of target remnant according to functions P(z)
68 C...z=E-pz fraction for qq (q) forming jet-system with struck Q (Qbar)
69 C...1-z=E-pz fraction for qQbar (qqQ) hadron
70 C...mq=mass of (light) parton remnant q (qq) in jet system
71 C...mQ=mass of produced (heavy flavour) hadron
72  mstj(93)=1
73  amsp=ulmass(ksp)
74  mstj(93)=1
75  amk2=ulmass(k2)
76  IF(lst(14).EQ.1) THEN
77 C...P(z)=(a+1)(1-z)**a with <z>=1/(a+2)=1/3 since a=1 fixed
78  z=1.-sqrt(rlu(0))
79 C...Flip if baryon produced
80  kc2=iabs(lucomp(k2))
81  IF(kc2.GE.301.AND.kc2.LE.400) z=1.-z
82  ELSEIF(lst(14).EQ.2) THEN
83 C...P(z)=(a+1)(1-z)**a with <z>=1/(a+2)=mq/(mq+mQ) --> a=a(mq,mQ)
84  a=(amsp+amk2)/amsp - 2.
85  z=rlu(0)**(1./(a+1.))
86  ELSEIF(lst(14).EQ.3) THEN
87 C...Using Peterson fragmentation function
88 C...P(z)=N/(z(1-1/z-c/(1-z))**2) where c=(mq/mQ)**2 (FC=-c)
89  fc=-(amsp/amk2)**2
90  300 z=rlu(0)
91  IF(-4.*fc*z*(1.-z)**2.LT.rlu(0)*((1.-z)**2-fc*z)**2) goto 300
92  ELSEIF(lst(14).EQ.4) THEN
93 C...Using chosen fragmentation function in JETSET
94  tm2=amk2**2+pt**2
95  CALL luzdis(1,0,tm2,z)
96  ENDIF
97  lst(27)=1
98  k2a=iabs(k2)
99  IF((k2a.GE.1.AND.k2a.LE.8).OR.k2a.EQ.21.OR.lucomp(k2a).EQ.90)
100  &lst(27)=2
101 
102  RETURN
103  END