]> git.uio.no Git - u/mrichter/AliRoot.git/blob - TAmpt/AMPT/ampt.f
o remove warning
[u/mrichter/AliRoot.git] / TAmpt / AMPT / ampt.f
1 c.....driver program for A Multi-Phase Transport model
2       SUBROUTINE AMPT(FRAME0,BMIN,BMAX)
3 c
4       double precision xmp, xmu, alpha, rscut2, cutof2
5       double precision smearp,smearh,dpcoal,drcoal,ecritl
6 cgsfs added following line to match C++ call
7       double precision BMIN, BMAX
8       integer K
9 c     CHARACTER*(*) FRAME0
10 c     CHARACTER FRAME0*8
11       CHARACTER*(*) FRAME0
12       CHARACTER FRAME*8
13 cgsfs  added to match specification in AMPTSET
14       character*25 amptvn
15
16
17       COMMON/HMAIN1/EATT,JATT,NATT,NT,NP,N0,N01,N10,N11
18       COMMON /HPARNT/HIPR1(100), IHPR2(50), HINT1(100), IHNT2(50)
19       COMMON/LUDAT1A/MSTU(200),PARU(200),MSTJ(200),PARJ(200)
20       COMMON /ARPRNT/ ARPAR1(100), IAPAR2(50), ARINT1(100), IAINT2(50)
21       COMMON /AROUT/ IOUT
22       COMMON /AREVT/ IAEVT, IARUN, MISS
23       COMMON /smearz/smearp,smearh
24       COMMON/RNDF77/NSEED
25       common/anim/nevent,isoft,isflag,izpc
26 c     parton coalescence radii in case of string melting:
27       common /coal/dpcoal,drcoal,ecritl
28       common/snn/efrm,npart1,npart2
29 c     initialization value for parton cascade:
30       common /para2/ xmp, xmu, alpha, rscut2, cutof2
31       common /para7/ ioscar,nsmbbbar,nsmmeson
32       common /para8/ idpert,npertd,idxsec
33       common /rndm3/ iseedp
34 c     initialization value for hadron cascade:
35       COMMON /RUN/ NUM
36       common/input1/ MASSPR,MASSTA,ISEED,IAVOID,DT
37       COMMON /INPUT2/ ILAB, MANYB, NTMAX, ICOLL, INSYS, IPOT, MODE, 
38      &   IMOMEN, NFREQ, ICFLOW, ICRHO, ICOU, KPOTEN, KMUL
39       common/oscar1/iap,izp,iat,izt
40       common/oscar2/FRAME,amptvn
41       common/resdcy/NSAV,iksdcy
42 clin-6/2009:
43 c      common/phidcy/iphidcy
44       common/phidcy/iphidcy,pttrig,ntrig,maxmiss
45       common/embed/iembed,pxqembd,pyqembd,xembd,yembd
46
47       EXTERNAL HIDATA, PYDATA, LUDATA, ARDATA, PPBDAT, zpcbdt
48       SAVE   
49 c****************
50
51       FRAME=FRAME0
52       imiss=0
53 cgsfs This line should not be here, but the value needs to be set for ARINI2
54 cgsfs      K=K+1
55       K=1
56
57  100  CALL HIJING(FRAME, BMIN, BMAX)
58       IAINT2(1) = NATT             
59
60
61 c     evaluate Npart (from primary NN collisions) for both proj and targ:
62       call getnp
63 c     switch for final parton fragmentation:
64       IF (IHPR2(20) .EQ. 0) GOTO 2000
65 c     In the unlikely case of no interaction (even after loop of 20 in HIJING),
66 c     still repeat the event to get an interaction 
67 c     (this may have an additional "trigger" effect):
68       if(NATT.eq.0) then
69          imiss=imiss+1
70          if(imiss.le.20) then
71             write(6,*) 'repeated event: natt=0,j,imiss=',j,imiss
72             goto 100
73          else
74             write(6,*) 'missed event: natt=0,j=',j
75             goto 2000
76          endif
77       endif
78 c.....ART initialization and run
79       CALL ARINI
80       CALL ARINI2(K)
81       CALL ARTAN1
82       CALL HJANA3
83       CALL ARTMN
84       CALL HJANA4
85       CALL ARTAN2
86
87  2000 CONTINUE
88 c
89 c       CALL ARTOUT(NEVNT)
90 clin-5/2009 ctest off:
91 c       call flowh0(NEVNT,2)
92 c       call flowp(2)
93 c       call iniflw(NEVNT,2)
94 c       call frztm(NEVNT,2)
95 c
96       RETURN
97       END