]> git.uio.no Git - u/mrichter/AliRoot.git/blob - HIJING/hipyset1_35/pystfe_hijing.F
CMake: Retrieve Git information
[u/mrichter/AliRoot.git] / HIJING / hipyset1_35 / pystfe_hijing.F
1 * $Id$
2     
3 C*********************************************************************  
4     
5       SUBROUTINE PYSTFE_HIJING(KF,X,Q2,XPQ)    
6     
7 C...This is a dummy routine, where the user can introduce an interface  
8 C...to his own external structure function parametrization. 
9 C...Arguments in:   
10 C...KF : 2212 for p, 211 for pi+; isospin conjugation for n and charge  
11 C...    conjugation for pbar, nbar or pi- is performed by PYSTFU.   
12 C...X : x value.    
13 C...Q2 : Q^2 value. 
14 C...Arguments out:  
15 C...XPQ(-6:6) : x * f(x,Q2), with index according to KF code,   
16 C...    except that gluon is placed in 0. Thus XPQ(0) = xg, 
17 C...    XPQ(1) = xd, XPQ(-1) = xdbar, XPQ(2) = xu, XPQ(-2) = xubar, 
18 C...    XPQ(3) = xs, XPQ(-3) = xsbar, XPQ(4) = xc, XPQ(-4) = xcbar, 
19 C...    XPQ(5) = xb, XPQ(-5) = xbbar, XPQ(6) = xt, XPQ(-6) = xtbar. 
20 C...    
21 C...One such interface, to the Diemos, Ferroni, Longo, Martinelli   
22 C...proton structure functions, already comes with the package. What    
23 C...the user needs here is external files with the three routines   
24 C...FXG160, FXG260 and FXG360 of the authors above, plus the    
25 C...interpolation routine FINT, which is part of the CERN library   
26 C...KERNLIB package. To avoid problems with unresolved external 
27 C...references, the external calls are commented in the current 
28 C...version. To enable this option, remove the C* at the beginning  
29 C...of the relevant lines.  
30 C...    
31 C...Alternatively, the routine can be used as an interface to the   
32 C...structure function evolution program of Tung. This can be achieved  
33 C...by removing C* at the beginning of some of the lines below. 
34 #include "ludat1_hijing.inc"
35 #include "ludat2_hijing.inc"
36 #include "pypars_hijing.inc"
37       DIMENSION XPQ(-6:6),XFDFLM(9) 
38       CHARACTER CHDFLM(9)*5,HEADER*40   
39       DATA CHDFLM/'UPVAL','DOVAL','GLUON','QBAR ','UBAR ','SBAR ',  
40      &'CBAR ','BBAR ','TBAR '/  
41       DATA HEADER/'Tung evolution package has been invoked'/    
42       DATA INIT/0/  
43     
44 C...Proton structure functions from Diemoz, Ferroni, Longo, Martinelli. 
45 C...Allowed variable range 10 GeV2 < Q2 < 1E8 GeV2, 5E-5 < x < .95. 
46       IF(MSTP(51).GE.11.AND.MSTP(51).LE.13.AND.MSTP(52).LE.1) THEN  
47         XDFLM=MAX(0.51E-4,X)    
48         Q2DFLM=MAX(10.,MIN(1E8,Q2)) 
49         IF(MSTP(52).EQ.0) Q2DFLM=10.    
50         DO 100 J=1,9    
51         IF(MSTP(52).EQ.1.AND.J.EQ.9) THEN   
52           Q2DFLM=Q2DFLM*(40./PMAS(6,1))**2  
53           Q2DFLM=MAX(10.,MIN(1E8,Q2))   
54         ENDIF   
55         XFDFLM(J)=0.    
56 C...Remove C* on following three lines to enable the DFLM options.  
57 C*      IF(MSTP(51).EQ.11) CALL FXG160(XDFLM,Q2DFLM,CHDFLM(J),XFDFLM(J))    
58 C*      IF(MSTP(51).EQ.12) CALL FXG260(XDFLM,Q2DFLM,CHDFLM(J),XFDFLM(J))    
59 C*      IF(MSTP(51).EQ.13) CALL FXG360(XDFLM,Q2DFLM,CHDFLM(J),XFDFLM(J))    
60   100   CONTINUE    
61         IF(X.LT.0.51E-4.AND.ABS(PARP(51)-1.).GT.0.01) THEN  
62           CXS=(0.51E-4/X)**(PARP(51)-1.)    
63           DO 110 J=1,7  
64   110     XFDFLM(J)=XFDFLM(J)*CXS   
65         ENDIF   
66         XPQ(0)=XFDFLM(3)    
67         XPQ(1)=XFDFLM(2)+XFDFLM(5)  
68         XPQ(2)=XFDFLM(1)+XFDFLM(5)  
69         XPQ(3)=XFDFLM(6)    
70         XPQ(4)=XFDFLM(7)    
71         XPQ(5)=XFDFLM(8)    
72         XPQ(6)=XFDFLM(9)    
73         XPQ(-1)=XFDFLM(5)   
74         XPQ(-2)=XFDFLM(5)   
75         XPQ(-3)=XFDFLM(6)   
76         XPQ(-4)=XFDFLM(7)   
77         XPQ(-5)=XFDFLM(8)   
78         XPQ(-6)=XFDFLM(9)   
79     
80 C...Proton structure function evolution from Wu-Ki Tung: parton 
81 C...distribution functions incorporating heavy quark mass effects.  
82 C...Allowed variable range: PARP(52) < Q < PARP(53); PARP(54) < x < 1.  
83       ELSE  
84         IF(INIT.EQ.0) THEN  
85           I1=0  
86           IF(MSTP(52).EQ.4) I1=1    
87           IHDRN=1   
88           NU=MSTP(53)   
89           I2=MSTP(51)   
90           IF(MSTP(51).GE.11) I2=MSTP(51)-3  
91           I3=0  
92           IF(MSTP(52).EQ.3) I3=1    
93     
94 C...Convert to Lambda in CWZ scheme (approximately linear relation).    
95           ALAM=0.75*PARP(1) 
96           TPMS=PMAS(6,1)    
97           QINI=PARP(52) 
98           QMAX=PARP(53) 
99           XMIN=PARP(54) 
100     
101 C...Initialize evolution (perform calculation or read results from  
102 C...file).  
103 C...Remove C* on following two lines to enable Tung initialization. 
104 C*        CALL PDFSET(I1,IHDRN,ALAM,TPMS,QINI,QMAX,XMIN,NU,HEADER,  
105 C*   &    I2,I3,IRET,IRR)   
106           INIT=1    
107         ENDIF   
108     
109 C...Put into output array.  
110         Q=SQRT(Q2)  
111         DO 200 I=-6,6   
112         FIXQ=0. 
113 C...Remove C* on following line to enable structure function call.  
114 C*      FIXQ=MAX(0.,PDF(10,1,I,X,Q,IR)) 
115   200   XPQ(I)=X*FIXQ   
116     
117 C...Change order of u and d quarks from Tung to PYTHIA convention.  
118         XPS=XPQ(1)  
119         XPQ(1)=XPQ(2)   
120         XPQ(2)=XPS  
121         XPS=XPQ(-1) 
122         XPQ(-1)=XPQ(-2) 
123         XPQ(-2)=XPS 
124       ENDIF 
125     
126       RETURN    
127       END