]> git.uio.no Git - u/mrichter/AliRoot.git/blob - GEANT321/gstrag/gdifmg.F
Fix needed on Sun and Alpha
[u/mrichter/AliRoot.git] / GEANT321 / gstrag / gdifmg.F
1 *
2 * $Id$
3 *
4 * $Log$
5 * Revision 1.1.1.1  1995/10/24 10:21:37  cernlib
6 * Geant
7 *
8 *
9 #include "geant321/pilot.h"
10 #if defined(CERNLIB_ASHO)
11 *CMZ :  3.21/02 29/03/94  15.41.25  by  S.Giani
12 *-- Author :
13       SUBROUTINE GDIFMG(DEL)
14  
15 #include "geant321/gccuts.inc"
16 #include "geant321/gcasho.inc"
17 C-----------------------------------------------------------------------
18 C      This program calculates the final distribution coef-
19 C      ficients until the integral S is more or equal to L2.
20 C      In case of S < L2 or miscalculations due to FORTRAN
21 C      limits DONE = FALSE.
22 C-----------------------------------------------------------------------
23 C      Update history: 10-08-93
24 C
25 C-----------------------------------------------------------------------
26       REAL BN(50),BNA(50),L2
27       INTEGER FLMAX
28       PARAMETER (DL2=.1)
29       DATA CORMAX/80./
30 C-----------------------------------------------------------------------
31 C      Initialization steps
32 C-----------------------------------------------------------------------
33       XX = 0.
34       Z = 1.
35       DO 10 K=1,NOSC
36          BN(K) = BOSC(K)*IOSC(K)
37          BNA(K) = BN(K)*(AOSC(K) - 1.)
38          XX = XX + AOSC(K)*BOSC(K)
39    10 CONTINUE
40 C
41       FLMAX = 0
42       CORR = CORMAX - XX
43       CMGO(1) = EXP(-CORMAX)
44       CMGO(2) = CMGO(1)*BNA(1)
45       Z = Z-(CMGO(1)+CMGO(2))*EXP(CORR)
46 C-----------------------------------------------------------------------
47 C      Calculation of the current Ci
48 C-----------------------------------------------------------------------
49       CALL GRNDM(RNDM,1)
50  
51       L2 = DL2
52       IF (RNDM.GE.L2) THEN
53          L2 = RNDM
54          FLMAX = 1
55       ENDIF
56       DO 40 NMGO=3,NMGOMA
57          CMGO(NMGO) = CMGO(NMGO - 1)*BNA(1)
58          DO 30 J = 1,NMGO - 2
59             M = NMGO - 1 - J
60             X = BOSC(1)/J
61             DO 20 K=2,NOSC
62                IF(MOD(J+1,IOSC(K)).EQ.0) THEN
63                   L = (J+1)/IOSC(K)
64                   IF(L.EQ.1) THEN
65                      X = X + BNA(K)
66                   ELSE
67                      X = X + BN(K)/(L-1)
68                   ENDIF
69                ENDIF
70    20       CONTINUE
71             CMGO(NMGO) = CMGO(NMGO) + X*CMGO(M)
72    30    CONTINUE
73          CMGO(NMGO) = CMGO(NMGO)/(NMGO-1)
74          Z = Z - CMGO(NMGO)*EXP(CORR)
75          IF (Z.LE.L2) GOTO 50
76    40 CONTINUE
77  
78    50 IF (FLMAX.EQ.1) THEN
79          DEL = (NMGO-1)*EOSC(1)
80       ELSE
81          DEL = (NMGO-1)*EOSC(1)*L2/RNDM
82       ENDIF
83       IF (DEL.GE.DCUTE*1E6) DEL = DCUTE*1E6
84  
85       END
86 #endif