]> git.uio.no Git - u/mrichter/AliRoot.git/blob - PDF/spdf/ctq3pf.F
Introduction of the Copyright and cvs Log
[u/mrichter/AliRoot.git] / PDF / spdf / ctq3pf.F
1 *
2 * $Id$
3 *
4 * $Log$
5 * Revision 1.1.1.2  1996/10/30 08:27:51  cernlib
6 * Version 7.04
7 *
8 * Revision 1.1.1.1  1996/04/12 15:29:15  plothow
9 * Version 7.01
10 *
11 *
12 #include "pdf/pilot.h"
13 C     Version 3 CTEQ distribution function in a parametrized form.
14
15 C   By: H.L. Lai, J. Botts, J. Huston, J.G. Morfin, J.F. Owens, J. Qiu,
16 C       W.K. Tung & H. Weerts;  Preprint MSU-HEP/41024, CTEQ 404
17
18 C   This file contains three versions of the same CTEQ3 parton distributions:
19 C
20 C Two "front-end" subprograms:
21 C     FUNCTION Ctq3Pf (Iset, Iparton, X, Q, Irt)
22 C         returns the PROBABILITY density for a GIVEN flavor;
23 C     SUBROUTINE Ctq3Pds(Iset, Pdf, XX, QQ, Irt)
24 C         returns an array of MOMENTUM densities for ALL flavors;
25 C One lower-level subprogram:
26 C     FUNCTION Ctq3Pd (Iset, Iprtn, XX, QQ, Irt)
27 C         returns the MOMENTUM density of a GIVEN valence or sea distribution.
28
29 C      One supplementary function to return the QCD lambda parameter
30 C      concerning these distributions is also included (see below).
31
32 C     Although DOUBLE PRECISION is used, conversion to SINGLE PRECISION
33 C     is straightforward by removing the
34 C     Implicit Double Precision statements.
35
36 C     Since this is an initial distribution of version 3, it is
37 C     useful for the authors to maintain a record of the distribution
38 C     list in case there are revisions or corrections.
39 C     In the interest of maintaining the integrity of this package,
40 C     please do not freely distribute this program package; instead, refer
41 C     any interested colleagues to direct their request for a copy to:
42 C     Lai@cteq11.pa.msu.edu or Tung@msupa.pa.msu.edu.
43
44 C   If you have detailed questions concerning these CTEQ3 distributions,
45 C   or if you find problems/bugs using this initial distribution, direct
46 C   inquires to Hung-Liang Lai or Wu-Ki Tung.
47
48 C     -------------------------------------------
49 C     Detailed instructions follow.
50
51 C     Name convention for CTEQ distributions:  CTEQnSx  where
52 C        n : version number                      (currently n = 3)
53 C        S : factorization scheme label: = [M L D] for [MS-bar LO DIS]
54 c               resp.
55 C        x : special characteristics, if any
56 C        (e.g. S(F) for singular (flat) small-x, L for "LEP lambda value")
57 C        (not applicable to CTEQ3 since only three standard sets are given.)
58
59 C    Explanation of functional arguments:
60
61 C    Iset is the set label; in this version, Iset = 1, 2, 3
62 C                           correspond to the following CTEQ global fits:
63
64 C          cteq3M  : best fit in the MS-bar scheme
65 C          cteq3L  : best fit in Leading order QCD
66 C          cteq3D  : best fit in the DIS scheme
67
68 C   Iprtn  is the parton label (6, 5, 4, 3, 2, 1, 0, -1, ......, -6)
69 C                          for (t, b, c, s, d, u, g, u_bar, ..., t_bar)
70 C  *** WARNING: We use the parton label 2 as D-quark, and 1 as U-quark which
71 C               might be different with your labels.
72
73 C   X, Q are the usual x, Q;
74 C   Irt is a return error code (see individual modules for explanation).
75 C
76 C     ---------------------------------------------
77
78 C  Since the QCD Lambda value for the various sets are needed more often than
79 C  the other parameters in most applications, a special function
80 C     Wlamd3 (Iset, Iorder, Neff)                    is provided
81 C  which returns the lambda value for Neff = 4,5,6 effective flavors as well as
82 C  the order these values pertain to.
83
84 C     ----------------------------------------------
85 C     The range of (x, Q) used in this round of global analysis is, approxi-
86 C     mately,  0.01 < x < 0.75 ; and 4 GeV^2 < Q^2 < 400 GeV^2 for fixed target
87 C     experiments and 0.0001 < x < 0.1 from HERA data.
88
89 C    The range of (x, Q) used in the reparametrization of the QCD evolved
90 C    parton distributions is 10E-6 < x < 1 ; 1.6 GeV < Q < 10 TeV.  The
91 C    functional form of this parametrization is:
92
93 C      A0 * x^A1 * (1-x)^A2 * (1 + A3 * x^A4) * [log(1+1/x)]^A5
94
95 C   with the A'coefficients being smooth functions of Q.  For heavy quarks,
96 C   a threshold factor is applied to A0 which simulates the proper Q-dependence
97 C   of the QCD evolution in that region according to the renormalization
98 C   scheme defined in Collins-Tung, Nucl. Phys. B278, 934 (1986).
99
100 C   Since this function is positive definite and smooth, it provides sensible
101 C   extrapolations of the parton distributions if they are called beyond
102 C   the original range in an application. There is no artificial boundaries
103 C   or sharp cutoff's.
104 C    ------------------------------------------------
105
106       FUNCTION Ctq3Pf (Iset, Iparton, X, Q, Irt)
107
108 C   This function returns the CTEQ parton distributions f^Iset_Iprtn/proton
109 C   --- the PROBABILITY density
110
111 C   (Iset, Iparton, X, Q): explained above;
112
113 C    Irt : return error code: see module Ctq3Pd for explanation.
114
115 C     IMPLICIT DOUBLE PRECISION (A-H, O-Z)
116 C+SEQ, IMPDP.
117
118       Ifl = Iparton
119       JFL = ABS(Ifl)
120 C                                                             Valence
121       IF (Ifl.Eq.1 .or. Ifl.Eq.2) THEN
122         VL = Ctq3Pd(Iset, Ifl, X, Q, Irt)
123       ELSE
124         VL = 0.
125       ENDIF
126 C                                                             Sea
127       SEA = Ctq3Pd (Iset, -JFL, X, Q, Irt)
128 C                                              Full (probability) Distribution
129       Ctq3Pf = (VL + SEA) / X
130
131       Return
132 C                         *************************
133       END