EIC Software
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
mrseb.F
Go to the documentation of this file. Or view the newest version in sPHENIX GitHub for file mrseb.F
1 *72*********************************************************************
2  SUBROUTINE mrseb
3  & (x,scale,mode,upv,dnv,usea,dsea,str,chm,bot,glu)
4 C***************************************************************C
5 C C
6 C This is a package for the new MRS(A prime,G) parton C
7 C distributions. The minimum Q^2 value is 5 GeV^2 and the C
8 C x range is, as before 10^-5 < x < 1. MSbar factorization C
9 C is used. The package reads 2 grids, which are in separate C
10 C files (A prime=for020.dat/ftn20, G=for021.dat/ftn21). C
11 C Note that x times the parton distribution is returned, C
12 C Q is the scale in GeV, C
13 C and Lambda(MSbar,nf=4) = 231/255 MeV for A prime/G. C
14 C C
15 C MODE=20 for MRS(A prime) C
16 C MODE=21 for MRS(G) C
17 C C
18 C The reference is : C
19 C A.D. Martin, R.G. Roberts and W.J. Stirling, C
20 C Phys. Lett. B354 (1995) 155-162 C
21 C C
22 C Comments to : W.J.Stirling@durham.ac.uk C
23 C C
24 C >>>>>>>> CROSS CHECK <<<<<<<< C
25 C C
26 C THE FIRST NUMBER IN THE 20 GRID IS 0.00341 C
27 C THE FIRST NUMBER IN THE 21 GRID IS 0.00269 C
28 C C
29 C HI: changed SCALE to Q^2 C
30 C***************************************************************C
31  IMPLICIT REAL*8(a-h,o-z)
32  DATA icount /0/
33 *
34 * to avoid variable conflictions, a second keep element is necessary
35 * with the same common block name (see LEPTO2)
36 *
37 
38  COMMON /leptou/ cut(14),lst(40),parl(30),
39  & xlp,ylp,w2lp,q2lp,ulp
40  REAL cut,parl,xlp,ylp,w2lp,q2lp,ulp
41  INTEGER lst
42  SAVE /leptou/
43 
44  q2=scale
45 * Q2STA= .5D0
46  q2sta = .625d0
47  q2fin = 1310720.d0
48  xmin = 1d-5
49  xmax = 1d0
50 
51  if (q2.lt.q2sta) then
52  q2=q2sta
53  IF(cut(5).lt.q2.and.cut(6).gt.q2.AND.icount.lt.10) THEN
54  icount = icount + 1
55  WRITE(*,*) 'WARNING : MRSEB : Q^2 set to minimal value !',q2
56  ENDIF
57  endif
58  if (q2.gt.q2fin) then
59  q2=q2fin
60  IF(cut(5).lt.q2.and.cut(6).gt.q2.AND.icount.lt.10) THEN
61  icount = icount + 1
62  WRITE(*,*) 'WARNING : MRSEB : Q^2 set to maximal value !',q2
63  ENDIF
64  endif
65  if (x.lt.xmin) then
66  x=xmin
67  IF(cut(1).lt.x.and.cut(2).gt.x.AND.icount.lt.10) THEN
68  icount = icount + 1
69  WRITE(*,*) 'WARNING : MRSEB : X set to minimal value !',x
70  ENDIF
71  endif
72  if (x.gt.xmax) then
73  x=xmax
74  IF(cut(1).lt.x.and.cut(2).gt.x.AND.icount.lt.10) THEN
75  icount = icount + 1
76  WRITE(*,*) 'WARNING : MRSEB : X set to maximal value !',x
77  ENDIF
78  endif
79 
80  IF(mode.EQ.20)
81  . CALL strc20(x,scale,upv,dnv,usea,dsea,str,chm,bot,glu)
82  IF(mode.EQ.21)
83  . CALL strc21(x,scale,upv,dnv,usea,dsea,str,chm,bot,glu)
84  IF(mode.EQ.10) THEN
85  IF(q2.LT.0.625d0.OR.q2.GT.1310720.d0) print 99
86  IF(q2.GT.5d0) CALL strc10(x,scale,upv,dnv,usea,dsea,str,chm,bot,
87  x glu)
88  IF(q2.LE.5d0) CALL strc11(x,scale,upv,dnv,usea,dsea,str,chm,bot,
89  x glu)
90  99 FORMAT(' WARNING: Q^2 VALUE IS OUT OF RANGE ')
91  ENDIF
92 * check for positive definiteness
93 
94  IF(upv.LT.0.0) upv=0.0
95  IF(dnv.LT.0.0) dnv=0.0
96  IF(usea.LT.0.0) usea=0.0
97  IF(dsea.LT.0.0) dsea=0.0
98  IF(glu.LT.0.0) glu=0.0
99  IF(str.LT.0.0) str=0.0
100  IF(chm.LT.0.0) chm=0.0
101  IF(bot.LT.0.0) bot=0.0
102 
103  RETURN
104  END