Back to home page

sPhenix code displayed by LXR

 
 

    


File indexing completed on 2025-08-05 08:21:08

0001  
0002 C*********************************************************************
0003  
0004 C...PY2FRM
0005 C...An interface from a two-fermion generator to include
0006 C...parton showers and hadronization.
0007  
0008       SUBROUTINE PY2FRM(IRAD,ITAU,ICOM)
0009  
0010 C...Double precision and integer declarations.
0011       IMPLICIT DOUBLE PRECISION(A-H, O-Z)
0012       IMPLICIT INTEGER(I-N)
0013       INTEGER PYK,PYCHGE,PYCOMP
0014 C...Commonblocks.
0015       COMMON/PYJETS/N,NPAD,K(4000,5),P(4000,5),V(4000,5)
0016       COMMON/PYDAT1/MSTU(200),PARU(200),MSTJ(200),PARJ(200)
0017       SAVE /PYJETS/,/PYDAT1/
0018 C...Local arrays.
0019       DIMENSION IJOIN(2),INTAU(2)
0020  
0021 C...Call PYHEPC to convert input from HEPEVT to PYJETS common.
0022       IF(ICOM.EQ.0) THEN
0023         MSTU(28)=0
0024         CALL PYHEPC(2)
0025       ENDIF
0026  
0027 C...Loop through entries and pick up all final fermions/antifermions.
0028       I1=0
0029       I2=0
0030       DO 100 I=1,N
0031       IF(K(I,1).LE.0.OR.K(I,1).GT.10) GOTO 100
0032       KFA=IABS(K(I,2))
0033       IF((KFA.GE.1.AND.KFA.LE.6).OR.(KFA.GE.11.AND.KFA.LE.16)) THEN
0034         IF(K(I,2).GT.0) THEN
0035           IF(I1.EQ.0) THEN
0036             I1=I
0037           ELSE
0038             CALL PYERRM(16,'(PY2FRM:) more than one fermion')
0039           ENDIF
0040         ELSE
0041           IF(I2.EQ.0) THEN
0042             I2=I
0043           ELSE
0044             CALL PYERRM(16,'(PY2FRM:) more than one antifermion')
0045           ENDIF
0046         ENDIF
0047       ENDIF
0048   100 CONTINUE
0049  
0050 C...Check that event is arranged according to conventions.
0051       IF(I1.EQ.0.OR.I2.EQ.0) THEN
0052         CALL PYERRM(16,'(PY2FRM:) event contains too few fermions')
0053       ENDIF
0054       IF(I2.LT.I1) THEN
0055         CALL PYERRM(6,'(PY2FRM:) fermions arranged in wrong order')
0056       ENDIF
0057  
0058 C...Check whether fermion pair is quarks or leptons.
0059       IF(IABS(K(I1,2)).LT.10.AND.IABS(K(I2,2)).LT.10) THEN
0060         IQL12=1
0061       ELSEIF(IABS(K(I1,2)).GT.10.AND.IABS(K(I2,2)).GT.10) THEN
0062         IQL12=2
0063       ELSE
0064         CALL PYERRM(16,'(PY2FRM:) fermion pair inconsistent')
0065       ENDIF
0066  
0067 C...Decide whether to allow or not photon radiation in showers.
0068       MSTJ(41)=2
0069       IF(IRAD.EQ.0) MSTJ(41)=1
0070  
0071 C...Do colour joining and parton showers.
0072       IP1=I1
0073       IP2=I2
0074       IF(IQL12.EQ.1) THEN
0075         IJOIN(1)=IP1
0076         IJOIN(2)=IP2
0077         CALL PYJOIN(2,IJOIN)
0078       ENDIF
0079       IF(IQL12.EQ.1.OR.IRAD.EQ.1) THEN
0080         PM12S=(P(IP1,4)+P(IP2,4))**2-(P(IP1,1)+P(IP2,1))**2-
0081      &  (P(IP1,2)+P(IP2,2))**2-(P(IP1,3)+P(IP2,3))**2
0082         CALL PYSHOW(IP1,IP2,SQRT(MAX(0D0,PM12S)))
0083       ENDIF
0084  
0085 C...Do fragmentation and decays. Possibly except tau decay.
0086       IF(ITAU.EQ.0) THEN
0087         NTAU=0
0088         DO 110 I=1,N
0089         IF(IABS(K(I,2)).EQ.15.AND.K(I,1).EQ.1) THEN
0090           NTAU=NTAU+1
0091           INTAU(NTAU)=I
0092           K(I,1)=11
0093         ENDIF
0094   110   CONTINUE
0095       ENDIF
0096       CALL PYEXEC
0097       IF(ITAU.EQ.0) THEN
0098         DO 120 I=1,NTAU
0099         K(INTAU(I),1)=1
0100   120   CONTINUE
0101       ENDIF
0102  
0103 C...Call PYHEPC to convert output from PYJETS to HEPEVT common.
0104       IF(ICOM.EQ.0) THEN
0105         MSTU(28)=0
0106         CALL PYHEPC(1)
0107       ENDIF
0108  
0109       END