EIC Software
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
pepsiMaineRHIC_noradcorr.f
Go to the documentation of this file. Or view the newest version in sPHENIX GitHub for file pepsiMaineRHIC_noradcorr.f
1 C...As an example, consider a main program of the form
2 *======================================================================
3  program pepsimainerhic
4 
5  implicit none
6  include "leptou.inc"
7  include "lujets.inc"
8  include "ludat1.inc"
9  include "mcRadCor.inc"
10  include "phiout.inc"
11  include "mc_set.inc"
12 
13  common/lypara/ipy(80),pypar(80),pyvar(80)
14  INTEGER ipy
15  REAL pypar, pyvar
16  SAVE /lypara/
17 
18  integer nevgen, i, j, lastgenevent, genevent
19  integer iev, nev, nprt
20  integer idum1, idum2, initseed
21  integer ltype, tracknr, t1, t2
22  integer*4 today(3), now(3)
23  real rval, alpha
24  real mcfixedweight, mcextraweight
25  double precision dilut, f1, f2, r, da1, da2
26  double precision gendilut, genf1, genf2, genr, gena1, gena2
27  DOUBLE PRECISION radgamenucl
28  DOUBLE PRECISION pbeame, pbeta, pgamma, ebeame, epznucl
29  DOUBLE PRECISION depol, gamma2, d, eta, eps, chi
30  DOUBLE PRECISION gendepol, gend, geneta, geneps, genchi
31  DOUBLE PRECISION dbrack, dxsec
32 
33  logical usepypar21
34  real pypar21val
35 
36  CHARACTER param*20
37 
38 c---------------------------------------------------------------------
39 c ASCII output file
40 c ---------------------------------------------------------------------
41  integer asciilun
42  parameter(asciilun=29)
43  CHARACTER*256 outputfilename
44  CHARACTER*256 outname
45 
46  alpha = 1./137.
47 C Initialize event generation counter
48  qedrad = 0
49  nevgen = 0
50  genevent = 0
51  lastgenevent = 0.
52  dilut= 1.
53  r = 0.
54  depol =0.
55  da1 = 0.
56  da2 = 0.
57  f1 = 0.
58  f2 = 0.
59  gamma2= 1.
60  d = 0.
61  eta = 0.
62  eps = 0.
63  chi = 0.
64  gendilut= 1.
65  genr = 0.
66  gendepol =0.
67  gena1 = 0.
68  gena2 = 0.
69  genf1 = 0.
70  genf2 = 0.
71  gend = 0.
72  geneta = 0.
73  geneps = 0.
74  genchi = 0.
75  radgamenucl = 0.
76  mcfixedweight=1.
77  mcextraweight=1.
78  weight=1.
79 C Init all the parameters and read them in
80  ltype = 11
81  pbeam = 100.
82  ebeam = 4.
83 
84  usepypar21=.false.
85 
86 C...Read parameters for LINIT call
87 C...Read output file name
88  READ(*,*) outname
89 C...Read beam target particle type
90  READ(*,*) ltype
91 C...Read beam and target particle energy
92  READ(*,*) pbeam, ebeam
93 C...Read number of events to generate, and to print.
94  READ(*,*) nev,nprt
95 C...Read min/max x of radgen lookup table
96  READ(*,*) mcset_xmin, mcset_xmax
97 C...Read min/max y of generation range
98  READ(*,*) mcset_ymin, mcset_ymax
99 C...Read min/max Q2 of generation range
100  READ(*,*) mcset_q2min, mcset_q2max
101 C...Read information for cross section used in radgen
102  READ(*,*) genset_fstruct, genset_r
103 C...Read switch for rad-corrections
104  READ(*,*) qedrad
105 C...Read min/max W2 of generation range
106  READ(*,*) mcset_w2min,mcset_w2max
107 C...Read min/max Nu of generation range
108  READ(*,*) mcset_numin,mcset_numax
109 C...Read Beam and Target polarisation direction
110  READ(*,*) mcset_pbvalue, mcset_ptvalue
111 C...Read Beam and Target polarisation
112  READ(*,*) mcset_pbeam, mcset_ptarget
113 C...Read all the pepsi/lepto parameters
114  100 READ(*,*, end=200) param, j, rval
115  if (param.eq.'LST') then
116  lst(j)=rval
117  write(*,*) 'LST(',j,')=',rval
118  endif
119  if (param.eq.'PARL') then
120  parl(j)=rval
121  write(*,*) 'PARL(',j,')=',rval
122  endif
123  if (param.eq.'PARJ') then
124  parj(j)=rval
125  write(*,*) 'PARJ(',j,')=',rval
126  endif
127  if (param.eq.'MSTJ') then
128  mstj(j)=rval
129  write(*,*) 'MSTJ(',j,')=',rval
130  endif
131  if (param.eq.'MSTU') then
132  mstu(j)=rval
133  write(*,*) 'MSTU(',j,')=',rval
134  endif
135  if (param.eq.'PARU') then
136  paru(j)=rval
137  write(*,*) 'PARU(',j,')=',rval
138  endif
139  if (param.eq.'PYPAR') then
140  pypar(j)=rval
141  write(*,*) 'PYPAR(',j,')=',rval
142  if (j.eq.21) then
143  usepypar21=.true.
144  pypar21val=rval
145  endif
146  endif
147  goto 100
148  200 write(*,*) '*********************************************'
149  write(*,*) 'NOW all parameters are read by PEPSI'
150  write(*,*) '*********************************************'
151 
152 C ... PEPSI polarization
153  if (mcset_pbvalue*mcset_ptvalue.lt.0.) then
154  lst(40) = 1.
155  elseif (mcset_pbvalue*mcset_ptvalue.gt.0.) then
156  lst(40) = -1.
157  else
158  lst(40) = 0.
159  endif
160 
161 C ... polarization for helium 3 !
162 C use lst(39)=1 for ideal helium 3 (no S prime and D state)
163 C use lst(39)=3 or (02 should work too ?) for a real helium 3.
164 C lst(39) = 0
165  if (lst(40).ne.0.and.parl(1).eq.3.and.parl(2).eq.2) then
166  lst(39) = 3
167  lst(36) = 1
168  endif
169 
170 C ... xmin,xmax
171  cut(1)=mcset_xmin
172  cut(2)=mcset_xmax
173 C ... ymin,ymax
174  cut(3)=mcset_ymin
175  cut(4)=mcset_ymax
176 C ... Q2min, Q2max
177  cut(5)=mcset_q2min
178  cut(6)=mcset_q2max
179 C ... W2min, W2max
180  cut(7)=mcset_w2min
181 C cut(8)=mcSet_W2Max
182 C ... numin, numax
183 C cut(9)=mcSet_NuMin
184 C cut(10)=mcSet_NuMax
185 
186  mcset_tara=parl(1)
187  mcset_tarz=parl(2)
188 
189 C Getting the date and time of the event generation
190  call idate(today) ! today(1)=day, (2)=month, (3)=year
191  call itime(now) ! now(1)=hour, (2)=minute, (3)=second
192 C
193 C Take date as the SEED for the random number generation
194  initseed = today(1) + 10*today(2) + today(3) + now(1) + 5*now(3)
195  write(6,*) 'SEED = ', initseed
196  call rndmq(idum1,idum2,initseed,' ')
197 
198  if (abs(ltype).eq.11) then
199  masse=0.000510998910
200  else
201  write(*,*) "Only positron and electron beam supported"
202  endif
203 
204  if ((parl(1).eq.1).and.(parl(2).eq.1)) then
205  massp=0.938272013
206  elseif ((parl(1).eq.1).and.(parl(2).eq.0)) then
207  massp=0.93956536
208  elseif ((parl(1).eq.2).and.(parl(2).eq.1)) then
209  massp=1.875612793
210  elseif ((parl(1).eq.3).and.(parl(2).eq.2)) then
211  massp=3.0160293
212  else
213  write(*,*) "Currently only p,n,d,he-3 as target supported"
214  endif
215 
216  pbeame=sqrt(pbeam**2+massp**2)
217  pbeta=pbeam/pbeame
218  pgamma=pbeame/massp
219  ebeame=sqrt(ebeam**2+masse**2)
220  ebeamenucl=pgamma*ebeame-pgamma*pbeta*(-ebeam)
221  epznucl=-pgamma*pbeta*(ebeame)+pgamma*(-ebeam)
222  write(*,*) ebeamenucl, ebeame, epznucl, -ebeam
223  mcset_enebeam=sngl(ebeamenucl)
224 
225 C Initialize PEPSI
226  CALL timex(t1)
227  call linit(0,ltype,(-ebeam),pbeam,lst(23))
228  CALL timex(t2)
229 
230 C PYPAR21 must be set after LINIT which sets it to PARP(1)
231  if (usepypar21) then
232  pypar(21)=pypar21val
233  endif
234 
235 c ---------------------------------------------------------------------
236 c Open ascii output file
237 c ---------------------------------------------------------------------
238  outputfilename=outname
239  open(asciilun, file=outputfilename)
240  write(*,*) 'the outputfile will be named: ', outname
241 
242 C The total integrated xsec, in pbarns
243  mcextraweight = parl(23)
244 
245 ! ============== Generate until happy (past cuts) =================
246 
247 C This is what we write in the ascii-file
248 
249  write(29,*)' PEPSI EVENT FILE '
250  write(29,*)'============================================'
251  write(29,30)
252 30 format('I, ievent, genevent, process, subprocess, nucleon,
253  & struckparton, partontrck, trueY, trueQ2, trueX, trueW2,
254  & trueNu, FixedWeight, weight, dxsec, Extraweight,
255  & dilut, F1, F2, A1, A2, R, Depol, d, eta, eps, chi,
256  & gendilut, genF1, genF2, genA1, genA2, genR, genDepol, gend,
257  & geneta, geneps, genchi, Sigcor, radgamEnucl, nrTracks')
258 
259  write(29,*)'============================================'
260  write(29,*)' I K(I,1) K(I,2) K(I,3) K(I,4) K(I,5)
261  & P(I,1) P(I,2) P(I,3) P(I,4) P(I,5) V(I,1) V(I,2) V(I,3)'
262  write(29,*)'============================================'
263 
264  DO 300 iev=1,nev
265 
266 C Count generated events
267 10 nevgen = nevgen+1
268 
269  if (qedrad.eq.0) then
270  If (iev.eq.1) then
271  write(*,*) 'Generating full event with LEPTO/PEPSI.'
272  endif
273  DO i=1,mstu(4)
274  DO j=1,5
275  k(i,j)=0.
276  p(i,j)=0.
277  v(i,j)=0.
278  enddo
279  enddo
280  lst(7) = 1
281  call lepto
282  if (lst(21).ne.0) then
283  write(*,*) 'PEPSI failed, trying again,
284  & no rad-corrections'
285  goto 10
286  endif
287  da2=0.
288  da1=0.
289  f1=0.
290  f2=0.
291  dilut=1.
292  r=0.
293  depol=0.
294  gamma2=0.
295  d=0.
296  eta=0.
297  eps=0.
298  chi=0.
299  genevent=nevgen-lastgenevent
300 
301  endif
302 
303  tracknr=n
304 
305 C Get some info for the event
306  call mkasym(dble(q2), dble(x), mcset_tara, mcset_tarz, da1, da2)
307  call mkf2(dble(q2), dble(x), mcset_tara, mcset_tarz, f2, f1)
308  call mkr(dble(q2), dble(x), r)
309  call fdilut(dble(q2), dble(x), mcset_tara, dilut)
310 
311 C... Calculate some kinematic variables
312  gamma2=q2/u**2
313  depol=(y*((1.+gamma2*y/2.)*(2.-y)-2*y**2*masse**2/q2))/
314  & (y**2*(1.-2.*masse**2/q2)*(1.+gamma2)+2.*(1.+r)*
315  & (1.-y-gamma2*(y**2)/4.))
316  d=depol*((sqrt(1.-y-gamma2*(y**2)/4.)*(1+gamma2*y/2.)) /
317  & (1.-y/2.)*(1+gamma2*y/2.)-y**2*masse**2/q2)
318  eta=(sqrt(gamma2)*(1.-y-gamma2*y**2/4.-y**2*masse**2/q2)) /
319  & ((1.+gamma2**2*y/2.)*(1-y/2.)-y**2*masse**2/q2)
320  chi=(sqrt(gamma2)*(1.-y/2.-y**2.*masse**2/q2))/(1.+gamma2*y/2.)
321  eps=1./(1.+1./2.*(1.-2.*masse**2/q2)*((y**2+gamma2*y**2)/
322  & (1.-y-gamma2*(y**2)/4.)))
323 
324  dbrack = (4.*paru(1)*alpha**2)/q2**2
325 c cross section in hbar^2c^2/GeV^2/dQ^2/dx
326  dxsec = (1.-y-(massp*x*y/2./ebeame))*f2/x+y**2*f1
327 c cross sectin in mbarn/dQ^2/dx
328  dxsec = dbrack * dxsec * 0.389379292
329 
330  write(29,32) 0, iev, genevent, lst(23), lst(24), lst(22),
331  & lst(25), lst(26), y, q2, x, w2, u, mcfixedweight, weight,
332  & dxsec, mcextraweight, real(dilut), real(F1),
333  & real(F2), real(dA1), real(dA2), real(R), real(Depol), real(d),
334  & real(eta), real(eps), real(chi), real(gendilut), real(genF1),
335  & real(genF2), real(genA1), real(genA2), real(genR),
336  & real(genDepol), real(gend), real(geneta), real(geneps),
337  & real(genchi), mcradcor_sigcor, radgamenucl, tracknr
338  32 format((i4,1x,$),(i10,1x,$),6(i6,1x,$),
339  & 33(e18.10,1x,$),i12,/)
340  write(29,*)'============================================'
341 
342  DO i=1,tracknr
343  write(29,34) i,k(i,1),k(i,2),k(i,3),k(i,4),k(i,5),
344  & p(i,1),p(i,2),p(i,3),p(i,4),p(i,5),
345  & v(i,1),v(i,2),v(i,3)
346  ENDDO
347  34 format(2(i6,1x,$),i10,1x,$,3(i6,1x,$),8(f15.6,1x,$),/)
348  write(29,*)'=============== Event finished ==============='
349 
350  lastgenevent=nevgen
351 
352  300 CONTINUE
353 
354 C...Print the Pythia cross section which is needed to get an absolut
355 C normalisation the number is in pbarns
356  write(*,*)'==================================================='
357  write(*,*)'Pepsi total cross section in pb from numerical',
358  & ' integration', parl(23)
359  write(*,*)'Pepsi total cross section in pb from MC simulation',
360  & parl(24)
361  write(*,*)'Total Number of generated events', nev
362  write(*,*)'Total Number of trials', nevgen
363  write(*,*)'==================================================='
364  close(29)
365  END