]> git.uio.no Git - u/mrichter/AliRoot.git/blobdiff - PYTHIA6/pythia6150.f
the MIXT geometry (IHEP+GPS2) has been introduced
[u/mrichter/AliRoot.git] / PYTHIA6 / pythia6150.f
index bd912462b2aaea6fdf40befaabda68a273bf013f..cfffeb5fec03980c01c953500207a257dd605af4 100644 (file)
@@ -228,6 +228,8 @@ C  S   PYTIME   dummy routine for giving date and time               *
 C                                                                    *
 C*********************************************************************
  
+C*********************************************************************
 C...PYDATA
 C...Default values for switches and parameters,
 C...and particle, decay and process data.
@@ -1623,8 +1625,6 @@ C...Data for histogramming routines.
  
       END
  
-C*********************************************************************
 C...PYTEST
 C...A simple program (disguised as subroutine) to run at installation
 C...as a check that the program works as intended.
@@ -2293,7 +2293,8 @@ C...Initialize parton distributions: PDFLIB.
         VALUE(3)=MOD(MSTP(51),1000)
         PARM(4)='TMAS'
         VALUE(4)=PMAS(6,1)
-        CALL PDFSET(PARM,VALUE)
+C...ALICE
+        CALL PDFSET_ALICE(PARM,VALUE)
         MINT(93)=1000000+MSTP(51)
       ENDIF
  
@@ -7248,6 +7249,10 @@ C...Calculate parton distribution weights.
             MINT(105)=MINT(102+I)
             MINT(109)=MINT(106+I)
             VINT(120)=VINT(2+I)
+C.... ALICE
+C.... Store side in MINT(124)
+            MINT(124) = I
+C.... 
             IF(MSTP(57).LE.1) THEN
               CALL PYPDFU(MINT(10+I),VINT(40+I),Q2UP(0),XPQ)
             ELSE
@@ -10467,6 +10472,14 @@ C...Weighting with new parton distributions.
       MINT(105)=MINT(102+JT)
       MINT(109)=MINT(106+JT)
       VINT(120)=VINT(2+JT)
+C.... ALICE
+C.... Store side in MINT(124)
+      MINT(124)=JT
+C....
+C.... ALICE
+C.... Store side in MINT(124)
+      MINT(124)=JT
+C....
       IF(MSTP(57).LE.1) THEN
         CALL PYPDFU(KFBEAM(JT),XB,Q2REF,XFN)
       ELSE
@@ -10495,6 +10508,10 @@ C...Weighting with new parton distributions.
         XFB(KFL)=XFN(KFL)
   240 CONTINUE
       XA=XB/Z
+C.... ALICE
+C.... Store side in MINT(124)
+      MINT(124) = JT
+C....
       IF(MSTP(57).LE.1) THEN
         CALL PYPDFU(KFBEAM(JT),XA,Q2REF,XFA)
       ELSE
@@ -18939,6 +18956,10 @@ C...Calculate parton distributions
           MINT(105)=MINT(102+I)
           MINT(109)=MINT(106+I)
           VINT(120)=VINT(2+I)
+C.... ALICE
+C.... Store side in MINT(124)
+          MINT(124)=I
+C....
           IF(MSTP(57).LE.1) THEN
             CALL PYPDFU(MINT(10+I),XSF,Q2SF,XPQ)
           ELSE
@@ -24676,13 +24697,16 @@ C...Call PDFLIB parton distributions.
           PARM(3)='NSET'
           VALUE(3)=MOD(MSTP(51),1000)
           IF(MINT(93).NE.1000000+MSTP(51)) THEN
-            CALL PDFSET(PARM,VALUE)
+C...ALICE
+            CALL PDFSET_ALICE(PARM,VALUE)
             MINT(93)=1000000+MSTP(51)
           ENDIF
           XX=X
           QQ=SQRT(MAX(0D0,Q2MIN,Q2))
           IF(MSTP(57).EQ.0) QQ=SQRT(Q2MIN)
-          CALL STRUCTM(XX,QQ,UPV,DNV,USEA,DSEA,STR,CHM,BOT,TOP,GLU)
+C...ALICE
+          CALL STRUCTM_ALICE(
+     +         XX,QQ,UPV,DNV,USEA,DSEA,STR,CHM,BOT,TOP,GLU)
           VINT(231)=Q2MIN
           XPQ(0)=GLU
           XPQ(1)=DNV+DSEA
@@ -45974,171 +45998,171 @@ C...Commonblocks.
       RETURN
       END
  
-C*********************************************************************
-C...PYR
-C...Generates random numbers uniformly distributed between
-C...0 and 1, excluding the endpoints.
-      FUNCTION PYR(IDUMMY)
-C...Double precision and integer declarations.
-      IMPLICIT DOUBLE PRECISION(A-H, O-Z)
-      IMPLICIT INTEGER(I-N)
-      INTEGER PYK,PYCHGE,PYCOMP
-C...Commonblocks.
-      COMMON/PYDATR/MRPY(6),RRPY(100)
-      SAVE /PYDATR/
-C...Equivalence between commonblock and local variables.
-      EQUIVALENCE (MRPY1,MRPY(1)),(MRPY2,MRPY(2)),(MRPY3,MRPY(3)),
-     &(MRPY4,MRPY(4)),(MRPY5,MRPY(5)),(MRPY6,MRPY(6)),
-     &(RRPY98,RRPY(98)),(RRPY99,RRPY(99)),(RRPY00,RRPY(100))
-C...Initialize generation from given seed.
-      IF(MRPY2.EQ.0) THEN
-        IJ=MOD(MRPY1/30082,31329)
-        KL=MOD(MRPY1,30082)
-        I=MOD(IJ/177,177)+2
-        J=MOD(IJ,177)+2
-        K=MOD(KL/169,178)+1
-        L=MOD(KL,169)
-        DO 110 II=1,97
-          S=0D0
-          T=0.5D0
-          DO 100 JJ=1,48
-            M=MOD(MOD(I*J,179)*K,179)
-            I=J
-            J=K
-            K=M
-            L=MOD(53*L+1,169)
-            IF(MOD(L*M,64).GE.32) S=S+T
-            T=0.5D0*T
-  100     CONTINUE
-          RRPY(II)=S
-  110   CONTINUE
-        TWOM24=1D0
-        DO 120 I24=1,24
-          TWOM24=0.5D0*TWOM24
-  120   CONTINUE
-        RRPY98=362436D0*TWOM24
-        RRPY99=7654321D0*TWOM24
-        RRPY00=16777213D0*TWOM24
-        MRPY2=1
-        MRPY3=0
-        MRPY4=97
-        MRPY5=33
-      ENDIF
-C...Generate next random number.
-  130 RUNI=RRPY(MRPY4)-RRPY(MRPY5)
-      IF(RUNI.LT.0D0) RUNI=RUNI+1D0
-      RRPY(MRPY4)=RUNI
-      MRPY4=MRPY4-1
-      IF(MRPY4.EQ.0) MRPY4=97
-      MRPY5=MRPY5-1
-      IF(MRPY5.EQ.0) MRPY5=97
-      RRPY98=RRPY98-RRPY99
-      IF(RRPY98.LT.0D0) RRPY98=RRPY98+RRPY00
-      RUNI=RUNI-RRPY98
-      IF(RUNI.LT.0D0) RUNI=RUNI+1D0
-      IF(RUNI.LE.0D0.OR.RUNI.GE.1D0) GOTO 130
-C...Update counters. Random number to output.
-      MRPY3=MRPY3+1
-      IF(MRPY3.EQ.1000000000) THEN
-        MRPY2=MRPY2+1
-        MRPY3=0
-      ENDIF
-      PYR=RUNI
-      RETURN
-      END
-C*********************************************************************
-C...PYRGET
-C...Dumps the state of the random number generator on a file
-C...for subsequent startup from this state onwards.
-      SUBROUTINE PYRGET(LFN,MOVE)
-C...Double precision and integer declarations.
-      IMPLICIT DOUBLE PRECISION(A-H, O-Z)
-      IMPLICIT INTEGER(I-N)
-      INTEGER PYK,PYCHGE,PYCOMP
-C...Commonblocks.
-      COMMON/PYDATR/MRPY(6),RRPY(100)
-      SAVE /PYDATR/
-C...Local character variable.
-      CHARACTER CHERR*8
-C...Backspace required number of records (or as many as there are).
-      IF(MOVE.LT.0) THEN
-        NBCK=MIN(MRPY(6),-MOVE)
-        DO 100 IBCK=1,NBCK
-          BACKSPACE(LFN,ERR=110,IOSTAT=IERR)
-  100   CONTINUE
-        MRPY(6)=MRPY(6)-NBCK
-      ENDIF
-C...Unformatted write on unit LFN.
-      WRITE(LFN,ERR=110,IOSTAT=IERR) (MRPY(I1),I1=1,5),
-     &(RRPY(I2),I2=1,100)
-      MRPY(6)=MRPY(6)+1
-      RETURN
-C...Write error.
-  110 WRITE(CHERR,'(I8)') IERR
-      CALL PYERRM(18,'(PYRGET:) error when accessing file, IOSTAT ='//
-     &CHERR)
-      RETURN
-      END
-C*********************************************************************
-C...PYRSET
-C...Reads a state of the random number generator from a file
-C...for subsequent generation from this state onwards.
-      SUBROUTINE PYRSET(LFN,MOVE)
-C...Double precision and integer declarations.
-      IMPLICIT DOUBLE PRECISION(A-H, O-Z)
-      IMPLICIT INTEGER(I-N)
-      INTEGER PYK,PYCHGE,PYCOMP
-C...Commonblocks.
-      COMMON/PYDATR/MRPY(6),RRPY(100)
-      SAVE /PYDATR/
-C...Local character variable.
-      CHARACTER CHERR*8
-C...Backspace required number of records (or as many as there are).
-      IF(MOVE.LT.0) THEN
-        NBCK=MIN(MRPY(6),-MOVE)
-        DO 100 IBCK=1,NBCK
-          BACKSPACE(LFN,ERR=120,IOSTAT=IERR)
-  100   CONTINUE
-        MRPY(6)=MRPY(6)-NBCK
-      ENDIF
-C...Unformatted read from unit LFN.
-      NFOR=1+MAX(0,MOVE)
-      DO 110 IFOR=1,NFOR
-        READ(LFN,ERR=120,IOSTAT=IERR) (MRPY(I1),I1=1,5),
-     &  (RRPY(I2),I2=1,100)
-  110 CONTINUE
-      MRPY(6)=MRPY(6)+NFOR
-      RETURN
-C...Write error.
-  120 WRITE(CHERR,'(I8)') IERR
-      CALL PYERRM(18,'(PYRSET:) error when accessing file, IOSTAT ='//
-     &CHERR)
-      RETURN
-      END
+*C*********************************************************************
+* 
+*C...PYR
+*C...Generates random numbers uniformly distributed between
+*C...0 and 1, excluding the endpoints.
+* 
+*      FUNCTION PYR(IDUMMY)
+* 
+*C...Double precision and integer declarations.
+*      IMPLICIT DOUBLE PRECISION(A-H, O-Z)
+*      IMPLICIT INTEGER(I-N)
+*      INTEGER PYK,PYCHGE,PYCOMP
+*C...Commonblocks.
+*      COMMON/PYDATR/MRPY(6),RRPY(100)
+*      SAVE /PYDATR/
+*C...Equivalence between commonblock and local variables.
+*      EQUIVALENCE (MRPY1,MRPY(1)),(MRPY2,MRPY(2)),(MRPY3,MRPY(3)),
+*     &(MRPY4,MRPY(4)),(MRPY5,MRPY(5)),(MRPY6,MRPY(6)),
+*     &(RRPY98,RRPY(98)),(RRPY99,RRPY(99)),(RRPY00,RRPY(100))
+* 
+*C...Initialize generation from given seed.
+*      IF(MRPY2.EQ.0) THEN
+*        IJ=MOD(MRPY1/30082,31329)
+*        KL=MOD(MRPY1,30082)
+*        I=MOD(IJ/177,177)+2
+*        J=MOD(IJ,177)+2
+*        K=MOD(KL/169,178)+1
+*        L=MOD(KL,169)
+*        DO 110 II=1,97
+*          S=0D0
+*          T=0.5D0
+*          DO 100 JJ=1,48
+*            M=MOD(MOD(I*J,179)*K,179)
+*            I=J
+*            J=K
+*            K=M
+*            L=MOD(53*L+1,169)
+*            IF(MOD(L*M,64).GE.32) S=S+T
+*            T=0.5D0*T
+*  100     CONTINUE
+*          RRPY(II)=S
+*  110   CONTINUE
+*        TWOM24=1D0
+*        DO 120 I24=1,24
+*          TWOM24=0.5D0*TWOM24
+*  120   CONTINUE
+*        RRPY98=362436D0*TWOM24
+*        RRPY99=7654321D0*TWOM24
+*        RRPY00=16777213D0*TWOM24
+*        MRPY2=1
+*        MRPY3=0
+*        MRPY4=97
+*        MRPY5=33
+*      ENDIF
+* 
+*C...Generate next random number.
+*  130 RUNI=RRPY(MRPY4)-RRPY(MRPY5)
+*      IF(RUNI.LT.0D0) RUNI=RUNI+1D0
+*      RRPY(MRPY4)=RUNI
+*      MRPY4=MRPY4-1
+*      IF(MRPY4.EQ.0) MRPY4=97
+*      MRPY5=MRPY5-1
+*      IF(MRPY5.EQ.0) MRPY5=97
+*      RRPY98=RRPY98-RRPY99
+*      IF(RRPY98.LT.0D0) RRPY98=RRPY98+RRPY00
+*      RUNI=RUNI-RRPY98
+*      IF(RUNI.LT.0D0) RUNI=RUNI+1D0
+*      IF(RUNI.LE.0D0.OR.RUNI.GE.1D0) GOTO 130
+* 
+*C...Update counters. Random number to output.
+*      MRPY3=MRPY3+1
+*      IF(MRPY3.EQ.1000000000) THEN
+*        MRPY2=MRPY2+1
+*        MRPY3=0
+*      ENDIF
+*      PYR=RUNI
+* 
+*      RETURN
+*      END
+* 
+*C*********************************************************************
+* 
+*C...PYRGET
+*C...Dumps the state of the random number generator on a file
+*C...for subsequent startup from this state onwards.
+* 
+*      SUBROUTINE PYRGET(LFN,MOVE)
+* 
+*C...Double precision and integer declarations.
+*      IMPLICIT DOUBLE PRECISION(A-H, O-Z)
+*      IMPLICIT INTEGER(I-N)
+*      INTEGER PYK,PYCHGE,PYCOMP
+*C...Commonblocks.
+*      COMMON/PYDATR/MRPY(6),RRPY(100)
+*      SAVE /PYDATR/
+*C...Local character variable.
+*      CHARACTER CHERR*8
+* 
+*C...Backspace required number of records (or as many as there are).
+*      IF(MOVE.LT.0) THEN
+*        NBCK=MIN(MRPY(6),-MOVE)
+*        DO 100 IBCK=1,NBCK
+*          BACKSPACE(LFN,ERR=110,IOSTAT=IERR)
+*  100   CONTINUE
+*        MRPY(6)=MRPY(6)-NBCK
+*      ENDIF
+* 
+*C...Unformatted write on unit LFN.
+*      WRITE(LFN,ERR=110,IOSTAT=IERR) (MRPY(I1),I1=1,5),
+*     &(RRPY(I2),I2=1,100)
+*      MRPY(6)=MRPY(6)+1
+*      RETURN
+* 
+*C...Write error.
+*  110 WRITE(CHERR,'(I8)') IERR
+*      CALL PYERRM(18,'(PYRGET:) error when accessing file, IOSTAT ='//
+*     &CHERR)
+* 
+*      RETURN
+*      END
+* 
+*C*********************************************************************
+* 
+*C...PYRSET
+*C...Reads a state of the random number generator from a file
+*C...for subsequent generation from this state onwards.
+* 
+*      SUBROUTINE PYRSET(LFN,MOVE)
+* 
+*C...Double precision and integer declarations.
+*      IMPLICIT DOUBLE PRECISION(A-H, O-Z)
+*      IMPLICIT INTEGER(I-N)
+*      INTEGER PYK,PYCHGE,PYCOMP
+*C...Commonblocks.
+*      COMMON/PYDATR/MRPY(6),RRPY(100)
+*      SAVE /PYDATR/
+*C...Local character variable.
+*      CHARACTER CHERR*8
+* 
+*C...Backspace required number of records (or as many as there are).
+*      IF(MOVE.LT.0) THEN
+*        NBCK=MIN(MRPY(6),-MOVE)
+*        DO 100 IBCK=1,NBCK
+*          BACKSPACE(LFN,ERR=120,IOSTAT=IERR)
+*  100   CONTINUE
+*        MRPY(6)=MRPY(6)-NBCK
+*      ENDIF
+* 
+*C...Unformatted read from unit LFN.
+*      NFOR=1+MAX(0,MOVE)
+*      DO 110 IFOR=1,NFOR
+*        READ(LFN,ERR=120,IOSTAT=IERR) (MRPY(I1),I1=1,5),
+*     &  (RRPY(I2),I2=1,100)
+*  110 CONTINUE
+*      MRPY(6)=MRPY(6)+NFOR
+*      RETURN
+* 
+*C...Write error.
+*  120 WRITE(CHERR,'(I8)') IERR
+*      CALL PYERRM(18,'(PYRSET:) error when accessing file, IOSTAT ='//
+*     &CHERR)
+* 
+*      RETURN
+*      END
+* 
 C*********************************************************************
  
 C...PYROBO