Analysis Software
Documentation for sPHENIX simulation software
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
upevnt.f
Go to the documentation of this file. Or view the newest version in sPHENIX GitHub for file upevnt.f
1 
2 C...Old example: handles a simple Pythia 6.4 initialization file.
3 
4 c SUBROUTINE UPINIT
5 
6 C...Double precision and integer declarations.
7 c IMPLICIT DOUBLE PRECISION(A-H, O-Z)
8 c IMPLICIT INTEGER(I-N)
9 
10 C...Commonblocks.
11 c COMMON/PYDAT1/MSTU(200),PARU(200),MSTJ(200),PARJ(200)
12 c COMMON/PYPARS/MSTP(200),PARP(200),MSTI(200),PARI(200)
13 c SAVE /PYDAT1/,/PYPARS/
14 
15 C...User process initialization commonblock.
16 c INTEGER MAXPUP
17 c PARAMETER (MAXPUP=100)
18 c INTEGER IDBMUP,PDFGUP,PDFSUP,IDWTUP,NPRUP,LPRUP
19 c DOUBLE PRECISION EBMUP,XSECUP,XERRUP,XMAXUP
20 c COMMON/HEPRUP/IDBMUP(2),EBMUP(2),PDFGUP(2),PDFSUP(2),
21 c &IDWTUP,NPRUP,XSECUP(MAXPUP),XERRUP(MAXPUP),XMAXUP(MAXPUP),
22 c &LPRUP(MAXPUP)
23 c SAVE /HEPRUP/
24 
25 C...Read info from file.
26 c IF(MSTP(161).GT.0) THEN
27 c READ(MSTP(161),*,END=110,ERR=110) IDBMUP(1),IDBMUP(2),EBMUP(1),
28 c & EBMUP(2),PDFGUP(1),PDFGUP(2),PDFSUP(1),PDFSUP(2),IDWTUP,NPRUP
29 c DO 100 IPR=1,NPRUP
30 c READ(MSTP(161),*,END=110,ERR=110) XSECUP(IPR),XERRUP(IPR),
31 c & XMAXUP(IPR),LPRUP(IPR)
32 c 100 CONTINUE
33 c RETURN
34 C...Error or prematurely reached end of file.
35 c 110 WRITE(MSTU(11),5000)
36 c STOP
37 
38 C...Else not implemented.
39 c ELSE
40 c WRITE(MSTU(11),5100)
41 c STOP
42 c ENDIF
43 
44 C...Format for error printout.
45 c 5000 FORMAT(1X,'Error: UPINIT routine failed to read information'/
46 c &1X,'Execution stopped!')
47 c 5100 FORMAT(1X,'Error: You have not implemented UPINIT routine'/
48 c &1X,'Dummy routine in PYTHIA file called instead.'/
49 c &1X,'Execution stopped!')
50 
51 c RETURN
52 c END
53 
54 C*********************************************************************
55 
56 C...UPEVNT
57 C...Dummy routine, to be replaced by a user implementing external
58 C...processes. Depending on cross section model chosen, it either has
59 C...to generate a process of the type IDPRUP requested, or pick a type
60 C...itself and generate this event. The event is to be stored in the
61 C...HEPEUP commonblock, including (often) an event weight.
62 
63 C...New example: handles a standard Les Houches Events File.
64 
65  SUBROUTINE upevnt
66 
67 C...Double precision and integer declarations.
68  IMPLICIT DOUBLE PRECISION(a-h, o-z)
69  IMPLICIT INTEGER(i-n)
70 
71 C...PYTHIA commonblock: only used to provide read unit MSTP(162).
72  common/pypars/mstp(200),parp(200),msti(200),pari(200)
73  SAVE /pypars/
74 
75 C...User process event common block.
76  INTEGER maxnup
77  parameter(maxnup=500)
78  INTEGER nup,idprup,idup,istup,mothup,icolup
79  DOUBLE PRECISION xwgtup,scalup,aqedup,aqcdup,pup,vtimup,spinup
80  common/hepeup/nup,idprup,xwgtup,scalup,aqedup,aqcdup,idup(maxnup),
81  &istup(maxnup),mothup(2,maxnup),icolup(2,maxnup),pup(5,maxnup),
82  &vtimup(maxnup),spinup(maxnup)
83  SAVE /hepeup/
84 
85 C...Lines to read in assumed never longer than 200 characters.
86  parameter(maxlen=200)
87  CHARACTER*(MAXLEN) string
88 
89 C...Format for reading lines.
90  CHARACTER*6 strfmt
91  strfmt='(A000)'
92  WRITE(strfmt(3:5),'(I3)') maxlen
93 
94 C...Loop until finds line beginning with "<event>" or "<event ".
95  100 READ(mstp(162),strfmt,end=130,err=130) string
96  ibeg=0
97  110 ibeg=ibeg+1
98 C...Allow indentation.
99  IF(string(ibeg:ibeg).EQ.' '.AND.ibeg.LT.maxlen-6) goto 110
100  IF(string(ibeg:ibeg+6).NE.'<event>'.AND.
101  &string(ibeg:ibeg+6).NE.'<event ') goto 100
102 
103 C...Read first line of event info.
104  READ(mstp(162),*,end=130,err=130) nup,idprup,xwgtup,scalup,
105  &aqedup,aqcdup
106 
107 C...Read NUP subsequent lines with information on each particle.
108  DO 120 i=1,nup
109  READ(mstp(162),*,end=130,err=130) idup(i),istup(i),
110  & mothup(1,i),mothup(2,i),icolup(1,i),icolup(2,i),
111  & (pup(j,i),j=1,5),vtimup(i),spinup(i)
112  120 CONTINUE
113  RETURN
114 
115 C...Error exit, typically when no more events.
116  130 WRITE(*,*) ' Failed to read LHEF event information.'
117  WRITE(*,*) ' Will assume end of file has been reached.'
118  nup=0
119  msti(51)=1
120 
121  RETURN
122  END