COSMOS v7.655  COSMOSv7655
(AirShowerMC)
Gencol0.f File Reference

Go to the source code of this file.

Functions/Subroutines

program __gencol0.f__
 
subroutine init
 
subroutine readinpfile (eof)
 
subroutine formpjtg (confirm)
 
subroutine outresul (a, ntp)
 
subroutine gencol (a, ntp)
 
subroutine cutbyangle (a, ntp0, ntp)
 
subroutine sortbyke (a, ntp)
 
subroutine outtrace (nev, a, ntp)
 

Function/Subroutine Documentation

◆ __gencol0.f__()

program __gencol0.f__ ( )

Definition at line 8 of file Gencol0.f.

References cutbyangle(), formpjtg(), gencol(), init(), inpfileno, j, outresul(), outtrace(), readinpfile(), and sortbyke().

8  integer i, nev, j, ntp, eof, ntpo
nodes i
********************block data cblkHeavy ********************integer j data *HeavyG2symbol *data *HeavyG2code kiron data j
Definition: cblkHeavy.h:36
integer, save nev
Definition: chook.f:11
Here is the call graph for this function:

◆ cutbyangle()

subroutine cutbyangle ( type (ptcl), dimension(*)  a,
integer  ntp0,
integer  ntp 
)

Definition at line 318 of file Gencol0.f.

References a, and wzmax.

318  implicit none
319 #include "Zptcl.h"
320 #include "Zcode.h"
321 #include "Zevhnv.h"
322 #include "Zevhnp.h"
323 #include "Zmanagerp.h"
324  include "Zprivate.h"
325  type(ptcl):: a(*)
326  integer ntp0 ! input. number of ptcls. in a
327  integer ntp ! output. could be the same as ntp0
328  integer j
329  integer i
330  real*8 p, wz
331  j = 0
332  do i = 1, ntp0
333  p = a(i)%fm%p(1)**2 + a(i)%fm%p(2)**2 +
334  * a(i)%fm%p(3)**2
335  p = sqrt(p)
336  wz = a(i)%fm%p(3)/p
337  if( wz .ge. wzmin .and. wz .le. wzmax ) then
338  j = j + 1
339  a(j)=a(i)
340  endif
341  enddo
342  ntp = j
nodes i
********************block data cblkHeavy ********************integer j data *HeavyG2symbol p
Definition: cblkHeavy.h:7
integer maxn wzmax
Definition: Zprivate.h:3
********************block data cblkHeavy ********************integer j data *HeavyG2symbol *data *HeavyG2code kiron data j
Definition: cblkHeavy.h:36
real(4), save a
Definition: cNRLAtmos.f:20
Definition: Zptcl.h:75

◆ formpjtg()

subroutine formpjtg ( integer  confirm)

Definition at line 160 of file Gencol0.f.

References cbst1(), cmkptc(), kgnuc, pjcode, pjpx, pjpy, pjsub, tgcode, tgpx, tgpy, and tgsub.

160 ! ******************
161  implicit none
162 #include "Zptcl.h"
163 #include "Zcode.h"
164 #include "Zevhnp.h"
165 #include "Zevhnv.h"
166 #include "Zmass.h"
167 #include "Zmanager.h"
168 #include "Zmanagerp.h"
169 #include "Ztrackp.h"
170 
171  include "Zprivate.h"
172 
173  integer confirm ! input. if 0, root s is not printed.
174  ! else printed
175  real*8 roots, s
176 ! form projectile and target
177 
178  call cmkptc(pjcode, pjsub, pjchg, pj)
179 ! pjmnum: proj. mass number in integer
180  if(pjcode .ne. kgnuc) then
181  pjmnum = 1
182  else
183  pjmnum = pjsub
184  endif
185  pj%fm%p(1) = pjpx*pjmnum ! total mom.
186  pj%fm%p(2) = pjpy*pjmnum
187  pj%fm%p(3) = pjpz*pjmnum
188  pj%fm%p(4) =
189  * sqrt(pj%fm%p(1)**2 + pj%fm%p(2)**2 + pj%fm%p(3)**2
190  * + pj%mass**2)
191 
192 ! make taget (rest or moving -z or ...)
193  call cmkptc(tgcode, tgsub, tgchg, tg)
194  if(tgcode .ne. kgnuc) then
195  tgmnum = 1
196  else
197  tgmnum = tgsub
198  endif
199  tg%fm%p(1) = tgpx*tgmnum ! total mom.
200  tg%fm%p(2) = tgpy*tgmnum
201  tg%fm%p(3) = tgpz*tgmnum
202  tg%fm%p(4) =
203  * sqrt(tg%fm%p(1)**2 + tg%fm%p(2)**2 + tg%fm%p(3)**2
204  * + tg%mass**2)
205 !
206  if(tgpx .eq. 0. .and. tgpy .eq. 0. .and.
207  * tgpz .eq. 0.) then
208 ! target is at rest; s = (Ep+Et)^2 - (Pp+Pt)^2
209 ! = (Ep+Mt)^2 - Pp^2
210 ! = Mp^2 +2EpMt +Mt^2
211 !
212  s= 2*pj%fm%p(4)*tg%mass +tg%mass**2 + pj%mass**2
213  else
214 ! by general formula;
215 ! Mp^2 + Mt^2 +2(Ep*Et - Pp.Pt)
216  s = pj%mass**2 + tg%mass**2 +
217  * 2*(pj%fm%p(4)*tg%fm%p(4) -
218  * dot_product(pj%fm%p(1:3), tg%fm%p(1:3) ) )
219  endif
220  roots = sqrt(s)
221  if(confirm .ne. 0) then
222  write(0, *) ' roots/2=', roots/2
223  endif
224 !c boost to target rest system
225  call cbst1(1, tg, pj, plab)
integer maxn LabEquivE real outresul integer pjchg integer tgchg integer xyz real pjpz real tgpy
Definition: Zprivate.h:8
subroutine cbst1(init, p1, p2, po)
Definition: cbst1.f:54
max ptcl codes in the kgnuc
Definition: Zcode.h:2
integer maxn LabEquivE real outresul integer pjcode
Definition: Zprivate.h:8
integer maxn LabEquivE real outresul integer pjchg integer tgcode
Definition: Zprivate.h:8
integer maxn LabEquivE real outresul integer pjchg integer tgsub
Definition: Zprivate.h:8
integer maxn LabEquivE real outresul integer pjchg integer tgchg integer xyz real pjpz real * tgpx
Definition: Zprivate.h:8
integer maxn LabEquivE real outresul integer pjchg integer tgchg integer xyz real pjpy
Definition: Zprivate.h:8
subroutine cmkptc(code, subcode, charge, p)
Definition: cmkptc.f:15
integer maxn LabEquivE real outresul integer pjsub
Definition: Zprivate.h:8
integer maxn LabEquivE real outresul integer pjchg integer tgchg integer xyz real * pjpx
Definition: Zprivate.h:8
Here is the call graph for this function:

◆ gencol()

subroutine gencol ( type (ptcl), dimension(*)  a,
integer  ntp 
)

Definition at line 271 of file Gencol0.f.

References a, chacol(), cibst1(), kgnuc, and knuc.

271  implicit none
272 #include "Zptcl.h"
273 #include "Zcode.h"
274 #include "Zevhnv.h"
275 #include "Zevhnp.h"
276 #include "Zmanagerp.h"
277  include "Zprivate.h"
278  type(ptcl):: a(*)
279 ! projectile and target information (both befor
280 ! and after collision ) in different system.
281 !
282  integer ntp
283  integer j
284  integer tz, ta
285  real*8 xs
286 !
287  if( tg%code .eq. knuc ) then
288  ta = 1
289  elseif( tg%code .eq. kgnuc ) then
290  ta = tg%subcode
291  else
292  write(0,*) ' target code=', tg%code, 'invalid'
293  stop 9999
294  endif
295  tz = tg%charge
296  if(activemdl .eq. 'qgsjet2' ) then
297  call cxsecqgs(plab, ta, xs)
298  endif
299  if(activemdl .eq. 'qgsjet1') then
300 #ifdef QGSJET1
301  call qgs01event(plab, ta, tz, a, ntp)
302 #endif
303  elseif(activemdl .eq. 'sibyll') then
304 #ifdef SIBYLL
305  call sibyllevent(plab, ta, tz, a, ntp)
306 #endif
307  else
308  call chacol(plab, ta, tz, a, ntp)
309  endif
310  do j = 1, ntp
311 ! boost to target mooving system
312  call cibst1(j, tg, a(j), a(j))
313  enddo
max ptcl codes in the kgnuc
Definition: Zcode.h:2
subroutine cibst1(init, p1, p2, po)
Definition: cibst1.f:29
! constants thru Cosmos real ! if multiplied to deg radian Torad ! light velocity m sec ! infinty ! kg m2 *Togpcm2 g cm2 ! g cm2 *Tokgpm2 kg m2 ! cm *Tom m ! m *Tocm cm ! g cm3 *Tokgpm3 kg m3 ! kg m3 *Togpcm3 g cm3 ! sec *Tonsec nsec ! Tesla m ! Avogadro *A2deninv ! mfp *n * xs
Definition: Zglobalc.h:18
********************block data cblkHeavy ********************integer j data *HeavyG2symbol *data *HeavyG2code kiron data j
Definition: cblkHeavy.h:36
********************block data cblkHeavy ********************integer j data *HeavyG2symbol *data *HeavyG2code knuc
Definition: cblkHeavy.h:7
real(4), save a
Definition: cNRLAtmos.f:20
Definition: Zptcl.h:75
subroutine chacol(pj, ia, iz, a, ntp)
Definition: chAcol.f:3
Here is the call graph for this function:

◆ init()

subroutine init ( )

Definition at line 37 of file Gencol0.f.

References cfixmodel(), cfixprefix(), cgetloginn(), cintmodels(), cmkseed(), copenfw2(), cquhookc(), cquhooki(), cquhookr(), creadparam(), csetcosorepi(), formpjtg(), inpfileno, pjcode, pjpx, pjpy, pjsub, qgs01init(), readinpfile(), tgcode, tgpx, tgpy, tgsub, trackl, wzmax, and xyz.

37  implicit none
38 #include "Zptcl.h"
39 #include "Zcode.h"
40 #include "Zevhnp.h"
41 #include "Zevhnv.h"
42 #include "Zmass.h"
43 #include "Zmanager.h"
44 #include "Zmanagerp.h"
45 #include "Ztrackp.h"
46 
47  include "Zprivate.h"
48  character*200 input, file
49  character*20 uid
50  integer klena, icon, eof
51 
52  external cblkmanager
53  external cblkevhnp
54 
55  call creadparam(5)
56 
57  if(tracedir .eq. ' ') then
58  call cgetloginn(uid)
59  tracedir = '/tmp/'//uid(1:klena(uid))
60  endif
61 
62  if(desteventno(2) .eq. 0) then
63  nevent =abs( desteventno(1) )
64  else
65  nevent = abs( desteventno(2) )
66  endif
67  call cmkseed(initrn(1), initrn)
68  call rnd1i(initrn) ! random number init.
69  call cquhookr(1, wzmin)
70  call cquhookr(2, wzmax)
71  write(0,*) ' cos* min max=', wzmin, wzmax
72  call cquhookr(3, trackl)
73  call cquhooki(1, outzero)
74 ! make projectile going +z
75  call cquhookc(1, input)
76  if(input(1:4) .eq. "file") then
77  read(input(5:10), *) inpfileno
78  xyz=index(input, "xyz")
79  call cquhookc(2, input)
80  file = ' '
81  file=input(1:klena(input))
82  call copenfw2(inpfileno, file, 1, icon)
83  if(icon .ne. 1) then
84  write(0,*)
85  * ' file=', file, ' cannot be opened in Gencol'
86  stop 9999
87  endif
88  call readinpfile(eof)
89 ! once rewind to read successively for event generation
90  rewind inpfileno
91  else
92  inpfileno=0
93  read(input, *)
94  * pjcode, pjsub, pjchg, pjpx, pjpy, pjpz ! proj. mom/n
95  call cquhookc(2, input)
96  read(input, *)
97  * tgcode, tgsub, tgchg, tgpx, tgpy, tgpz ! target. mom/n
98  call cquhookc(3, input)
99  if(input .ne. ' ') then
100  read(input, *) xpos, ypos, zpos
101  xyz = 1
102  else
103  xyz = 0
104  endif
105  endif
106 
107  call formpjtg(1) ! form proj. and target
108 
109  call cfixprefix('configDummy')
110  call csetcosorepi('epics')
111  if( index( intmodel,'qgsjet1') .ne. 0 ) then
112 #ifdef QGSJET1
113  call qgs01init
114  activemdl = 'qgsjet1'
115 #else
116  write(0,*) 'to use qgsjet1, define it in Zintmodel%h'
117 #endif
118  elseif(index(intmodel, 'sibyll') .ne. 0 ) then
119 #ifdef SIBYLL
120  call sibyllinit
121  activemdl = 'sibyll'
122 #else
123  write(0,*) 'to use sibyll, define it in Zintmodel%h'
124 #endif
125  else
126  call cintmodels('epics')
127  call cfixmodel( plab )
128  endif
129 
130  write(0, *) 'Active int. model=',activemdl
131  write(0, *) ' equiv. lab E=', plab%fm%p(4)
132  if(xyz .eq. 0) then
133  write(*, '(a)') '# mulsubKEdir user '
134  else
135  write(*, '(a)') '# mulsubKExyzdir user '
136  endif
137  write(*, '(a)') '#--------------------------------'
subroutine cmkseed(dummy, seed)
Definition: cmkSeed.f:3
subroutine csetcosorepi(from)
Definition: cintModels.f:252
integer maxn LabEquivE real outresul integer pjchg integer tgchg integer xyz real pjpz real tgpy
Definition: Zprivate.h:8
integer maxn LabEquivE real outresul integer pjchg integer tgchg integer inpfileno
Definition: Zprivate.h:8
subroutine cintmodels(from)
Definition: cintModels.f:3
subroutine cfixmodel(aPtcl)
Definition: cfixModel.f:2
latitude latitude this system is used *****************************************************************! type coord sequence union map real z z in m endmap xyz map real ! latitude in deg is to the north ! longitude in deg is to the east *h ! height in m endmap llh map real ! polar angle ! azimuthal angle *radius ! radial distance endmap sph endunion character *sys ! which system xyz
Definition: Zcoord.h:25
subroutine readinpfile(eof)
Definition: Gencol.f:422
integer maxn LabEquivE real outresul integer pjcode
Definition: Zprivate.h:8
subroutine qgs01init
Definition: qgs01init.f:2
integer maxn wzmax
Definition: Zprivate.h:3
subroutine copenfw2(io, fnin, form, icon)
Definition: copenf.f:205
subroutine cquhookr(i, rv)
Definition: cqUHookr.f:2
integer maxn LabEquivE real outresul integer pjchg integer tgcode
Definition: Zprivate.h:8
subroutine creadparam(io)
Definition: creadParam.f:5
integer maxn LabEquivE real outresul integer pjchg integer tgsub
Definition: Zprivate.h:8
integer maxn LabEquivE real outresul integer pjchg integer tgchg integer xyz real pjpz real * tgpx
Definition: Zprivate.h:8
integer maxn trackl
Definition: Zprivate.h:3
subroutine cfixprefix(dsn)
Definition: cintModels.f:209
integer maxn LabEquivE real outresul integer pjchg integer tgchg integer xyz real pjpy
Definition: Zprivate.h:8
subroutine formpjtg(confirm)
Definition: Gencol.f:443
integer function klena(cha)
Definition: klena.f:20
subroutine cquhooki(i, iv)
Definition: cqUHookr.f:15
integer maxn LabEquivE real outresul integer pjsub
Definition: Zprivate.h:8
subroutine cquhookc(i, cv)
Definition: cqUHookr.f:28
integer maxn LabEquivE real outresul integer pjchg integer tgchg integer xyz real * pjpx
Definition: Zprivate.h:8
subroutine cgetloginn(userid)
Definition: cgetLoginN.f:29
Here is the call graph for this function:

◆ outresul()

subroutine outresul ( type (ptcl), dimension(ntp)  a,
integer  ntp 
)

Definition at line 229 of file Gencol0.f.

References a, getdiffcode(), and xyz.

Referenced by __gencol.f__(), __gencol0.f__(), __gencol2.f__(), __gencol3.f__(), __gencol4.f__(), and init().

229  implicit none
230 #include "Zptcl.h"
231 #include "Zcode.h"
232 #include "Zevhnp.h"
233 #include "Zevhnv.h"
234 #include "Zmass.h"
235 #include "Zmanagerp.h"
236 #include "Zmanager.h"
237 #include "Ztrackp.h"
238  include "Zprivate.h"
239 
240  integer ntp
241  type(ptcl):: a(ntp)
242  integer i, j
243  real*8 p, wx, wy, wz
244  integer nw, difcode(20)
245 
246  call getdiffcode(nw, difcode)
247 
248  do j = 1, ntp
249  i = indx(j)
250  p= sqrt( a(i)%fm%p(1)**2 + a(i)%fm%p(2)**2
251  * + a(i)%fm%p(3)**2 )
252  wx = a(i)%fm%p(1)/p
253  wy = a(i)%fm%p(2)/p
254  wz = a(i)%fm%p(3)/p
255  if(xyz .eq. 0) then
256  write(*,'(i3,i5,i4,g14.5,3f17.13, i5)')
257  * a(i)%code, a(i)%subcode, a(i)%charge,
258  * a(i)%fm%p(4)-a(i)%mass, wx, wy, wz, difcode(1)
259  else
260  write(*,'(i3,i5,i4,g14.5,1p3E11.3,0p3f17.13, i5)')
261  * a(i)%code, a(i)%subcode, a(i)%charge,
262  * a(i)%fm%p(4)-a(i)%mass, xpos, ypos, zpos,
263  * wx, wy, wz, difcode(1)
264  endif
265  enddo
266  if(ntp .gt. 0 .or. outzero .eq. 0) then
267  write(*, *)
268  endif
nodes i
latitude latitude this system is used *****************************************************************! type coord sequence union map real z z in m endmap xyz map real ! latitude in deg is to the north ! longitude in deg is to the east *h ! height in m endmap llh map real ! polar angle ! azimuthal angle *radius ! radial distance endmap sph endunion character *sys ! which system xyz
Definition: Zcoord.h:25
********************block data cblkHeavy ********************integer j data *HeavyG2symbol p
Definition: cblkHeavy.h:7
********************block data cblkHeavy ********************integer j data *HeavyG2symbol *data *HeavyG2code kiron data j
Definition: cblkHeavy.h:36
subroutine getdiffcode(nw, difcode)
Definition: getDiffCode.f:3
real(4), save a
Definition: cNRLAtmos.f:20
Definition: Zptcl.h:75
Here is the call graph for this function:
Here is the caller graph for this function:

◆ outtrace()

subroutine outtrace ( integer  nev,
type (ptcl), dimension(ntp)  a,
integer  ntp 
)

Definition at line 363 of file Gencol0.f.

References a, cerrormsg(), copenfw(), kseblk(), trackl, and xyz.

363  implicit none
364 #include "Zptcl.h"
365 #include "Zcode.h"
366 #include "Zevhnp.h"
367 #include "Zevhnv.h"
368 #include "Zmass.h"
369 #include "Zmanagerp.h"
370 #include "Zmanager.h"
371 #include "Ztrackp.h"
372  include "Zprivate.h"
373 
374  integer ntp, nev
375  type(ptcl):: a(ntp)
376  integer i, j, leng, icon, klena
377  real*8 p, wx, wy, wz
378  real x1, y1, z1, x2, y2, z2
379  character*100 tracefile
380 
381  write(tracefile, *) tracedir(1:klena(tracedir))//'/trace', nev
382  call kseblk(tracefile, ' ', leng)
383  call copenfw(tracedev, tracefile(1:leng), icon)
384  if(icon .ne. 0) then
385  call cerrormsg('tracefile could not be opened',0)
386  endif
387  do j = 1, ntp
388  i = indx(j)
389  p= sqrt( a(i)%fm%p(1)**2 + a(i)%fm%p(2)**2
390  * + a(i)%fm%p(3)**2 )
391  wx = a(i)%fm%p(1)/p
392  wy = a(i)%fm%p(2)/p
393  wz = a(i)%fm%p(3)/p
394  if(xyz .eq. 0) then
395  x1 = 0.
396  y1 = 0.
397  z1 = 0.
398  else
399  x1 = xpos
400  y1 = ypos
401  z1 = zpos
402  endif
403  x2 = x1 + wx*trackl
404  y2 = y1 + wy*trackl
405  z2 = z1 + wz*trackl
406  write(tracedev,'(3g14.5, i3, g14.4, i3, i2)')
407  * x1, y1, z1,
408  * a(i)%code, a(i)%fm%p(4) - a(i)%mass, a(i)%charge,
409  * 0
410  write(tracedev, '(3g14.5, i3, g14.4, i3, g14.4)' )
411  * x2, y2, z2,
412  * a(i)%code, a(i)%fm%p(4) - a(i)%mass, a(i)%charge,
413  * trackl
414  write(tracedev, *)
415  write(tracedev, *)
416  enddo
417  close(tracedev)
subroutine cerrormsg(msg, needrtn)
Definition: cerrorMsg.f:4
block data include Zlatfit h c fitting region data x1(1)/0.03/
nodes i
latitude latitude this system is used *****************************************************************! type coord sequence union map real z z in m endmap xyz map real ! latitude in deg is to the north ! longitude in deg is to the east *h ! height in m endmap llh map real ! polar angle ! azimuthal angle *radius ! radial distance endmap sph endunion character *sys ! which system xyz
Definition: Zcoord.h:25
integer leng
Definition: interface2.h:1
********************block data cblkHeavy ********************integer j data *HeavyG2symbol p
Definition: cblkHeavy.h:7
********************block data cblkHeavy ********************integer j data *HeavyG2symbol *data *HeavyG2code kiron data j
Definition: cblkHeavy.h:36
integer maxn trackl
Definition: Zprivate.h:3
subroutine copenfw(io, fnin, icon)
Definition: copenf.f:122
integer function klena(cha)
Definition: klena.f:20
real(4), save a
Definition: cNRLAtmos.f:20
block data include Zlatfit h c fitting region data x2(1)/0.5/data x1(2)/0.3/
Definition: Zptcl.h:75
subroutine kseblk(text, c, lc)
Definition: kseblk.f:18
integer, save nev
Definition: chook.f:11
Here is the call graph for this function:

◆ readinpfile()

subroutine readinpfile ( integer  eof)

Definition at line 140 of file Gencol0.f.

References inpfileno, pjcode, pjpx, pjpy, pjsub, tgcode, tgpx, tgpy, tgsub, and xyz.

140  implicit none
141 #include "Zptcl.h"
142  include "Zprivate.h"
143 
144  integer eof ! output . data read--> 0
145  ! eof reached --> 1
146  read(inpfileno,*, end=100)
147  * pjcode, pjsub, pjchg, pjpx, pjpy, pjpz
148  read(inpfileno,*, end=100)
149  * tgcode, tgsub, tgchg, tgpx, tgpy, tgpz
150  if(xyz .gt. 0 ) then
151  read(inpfileno,*, end=100) xpos, ypos, zpos
152  endif
153  eof = 0
154  return
155  100 continue
156  eof = 1
integer maxn LabEquivE real outresul integer pjchg integer tgchg integer xyz real pjpz real tgpy
Definition: Zprivate.h:8
integer maxn LabEquivE real outresul integer pjchg integer tgchg integer inpfileno
Definition: Zprivate.h:8
latitude latitude this system is used *****************************************************************! type coord sequence union map real z z in m endmap xyz map real ! latitude in deg is to the north ! longitude in deg is to the east *h ! height in m endmap llh map real ! polar angle ! azimuthal angle *radius ! radial distance endmap sph endunion character *sys ! which system xyz
Definition: Zcoord.h:25
integer maxn LabEquivE real outresul integer pjcode
Definition: Zprivate.h:8
integer maxn LabEquivE real outresul integer pjchg integer tgcode
Definition: Zprivate.h:8
integer maxn LabEquivE real outresul integer pjchg integer tgsub
Definition: Zprivate.h:8
integer maxn LabEquivE real outresul integer pjchg integer tgchg integer xyz real pjpz real * tgpx
Definition: Zprivate.h:8
integer maxn LabEquivE real outresul integer pjchg integer tgchg integer xyz real pjpy
Definition: Zprivate.h:8
integer maxn LabEquivE real outresul integer pjsub
Definition: Zprivate.h:8
integer maxn LabEquivE real outresul integer pjchg integer tgchg integer xyz real * pjpx
Definition: Zprivate.h:8

◆ sortbyke()

subroutine sortbyke ( type (ptcl), dimension(*)  a,
integer  ntp 
)

Definition at line 345 of file Gencol0.f.

References a, ke(), kqsortd(), and ksortinv().

345  implicit none
346 #include "Zptcl.h"
347 #include "Zcode.h"
348 
349  include "Zprivate.h"
350  integer ntp
351  type(ptcl):: a(*)
352 ! projectile and target information (both befor
353 ! and after collision ) in different system.
354  integer i
355  do i = 1, ntp
356  ke(i) = a(i)%fm%p(4) - a(i)%mass
357  enddo
358  call kqsortd(ke, indx, ntp)
359  call ksortinv(indx, ntp)
360 ! ke( indx(1) ) is the highest energy
nodes i
subroutine kqsortd(A, ORD, N)
Definition: kqsortd.f:23
subroutine ksortinv(idx, n)
Definition: ksortinv.f:2
integer maxn LabEquivE real * ke(maxn) integer indx(maxn) integer nevent integer outzero
real(4), save a
Definition: cNRLAtmos.f:20
Definition: Zptcl.h:75
Here is the call graph for this function: