]> git.uio.no Git - u/mrichter/AliRoot.git/blob - GEANT321/fluka/rakekv.F
Default compile option changed to -g (Alpha)
[u/mrichter/AliRoot.git] / GEANT321 / fluka / rakekv.F
1 *
2 * $Id$
3 *
4 * $Log$
5 * Revision 1.1.1.1  1995/10/24 10:19:58  cernlib
6 * Geant
7 *
8 *
9 #include "geant321/pilot.h"
10 *CMZ :  3.21/02 29/03/94  15.41.44  by  S.Giani
11 *-- Author :
12 *$ CREATE RAKEKV.FOR
13 *COPY RAKEKV
14 *                                                                      *
15 *=== rakekv ===========================================================*
16 *                                                                      *
17       SUBROUTINE RAKEKV ( IT, EXSOP, BBTAR, TKIN, TSTRCK, PSTRCK,
18      &                    ARECL, TKRECL, EFERMI, CDE, SDE )
19  
20 #include "geant321/dblprc.inc"
21 #include "geant321/dimpar.inc"
22 #include "geant321/iounit.inc"
23 *
24 *----------------------------------------------------------------------*
25 *     version by                     Alfredo Ferrari
26 *                                    INFN - Milan
27 *     last change 03 january 93 by   Alfredo Ferrari
28 *                                    INFN - Milan
29 *
30 *     To be called from the high energy production
31 *
32 *     this is a subroutine of fluka to sample intranuclear cascade
33 *     particles: it is based on the old Rakeka from J. Ranft
34 *
35 *     input variables:
36 *        it    = type of the secondary requested; 1=proton, 2=neutron
37 *        bbtar = atomic weight of the medium
38 *
39 *     output variables:
40 *        tkin  = kinetic energy of the secondary in GeV before applying
41 *                the nuclear well (and eventually the Coulomb barreer)
42 *        tstrck= kinetic energy of the secondary in GeV
43 *        pstrck= momentum of the secondary in GeV/c
44 *        cde,sde = cosine and sine of the angle between the
45 *                  directions of the primary
46 *                  and secondary particles
47 *
48 *********************************************************************
49 *
50 #include "geant321/nucdat.inc"
51 #include "geant321/parevt.inc"
52       COMMON / FKNUCO / HELP (2), HHLP (2), FTVTH (2), FINCX (2),
53      &                  EKPOLD (2), BBOLD, ZZOLD, SQROLD, ASEASQ,
54      &                  FSPRED, FEX0RD
55       COMMON / FKCASF / PKFRMI, COSTH, PKIN
56       DIMENSION EXSOP (2)
57       REAL RNDM(4), RNGSS, DUMNOR
58 *  In this version the low energy component has been suppressed, since
59 *  they are now produced by the evaporation model, A. Ferrari.
60 *  The parameters needed for the sampling have been already set in
61 *  Corrin
62       EXSOP (IT) = 0.D+00
63 *  +-------------------------------------------------------------------*
64 *  |
65  100  CONTINUE
66 *  |  Sample the Fermi momentum
67          CALL GRNDM(RNDM,4)
68          PKFRMI = PFRMMX (IT) * MAX ( RNDM (1), RNDM (2),
69      &            RNDM (3) )
70          PKFRSQ = PKFRMI * PKFRMI
71          TKIN   = - ESLOPE (IT) * LOG ( EXMNNU (IT) - RNDM (4) * (
72      &              EXMNNU (IT) - EXUPNU (IT) ) )
73          TKRECL = 0.5D+00 * PKFRSQ / ( AMUC12 * ARECL ) * ( 1.D+00 -
74      &            0.25D+00 * PKFRSQ / ( ARECL**2 * AMUCSQ ) )
75          EFERMI = SQRT ( AMNUSQ (IT) + PKFRSQ )
76          TSTRCK = EFERMI + TKIN - AMNUCL (IT) - V0WELL (IT) - TKRECL -
77      &            EBNDNG (IT)
78 *  |  +----------------------------------------------------------------*
79 *  |  |  Record the energy spent without emitting nucleons
80          IF ( TSTRCK .LE. VEFFNU (IT) - V0WELL (IT) ) THEN
81 *  |  |  Reduce that energy according to Fspred:
82             EXSOP (IT) = EXSOP (IT) + TKIN * FEX0RD
83             GO TO 100
84 *  +-<|--<--<--<--<--< go to resampling
85          END IF
86 *  |  |
87 *  |  +----------------------------------------------------------------*
88 *  |
89 *  +-------------------------------------------------------------------*
90       PSTRCK = SQRT ( TSTRCK * ( TSTRCK + 2.D+00 * AMNUCL (IT) ) )
91 *   Sample the angle between the incident particle and the Fermi
92 *   momentum
93 *   Solution assuming that the momentum transfer is equal to the
94 *   the momentum loss of the projectile for the energy loss Tkin,
95 *   roughly given by Tkin again. Use this with the "usual" eventv
96       PKIN   = TKIN
97       PKIN2  = PKIN * PKIN
98       CALL GRNDM(RNDM,1)
99       COSTH  = 2.D+00 * RNDM (1) - 1.D+00
100       COSDE2 = PKFRMI * COSTH + PKIN
101       CSIGN  = SIGN ( ONEONE, COSDE2 )
102       COSDE2 = COSDE2 * COSDE2 / ( PKIN2 + PKFRSQ +
103      &           2.D+00 * COSTH * PKIN * PKFRMI )
104       CDE = CSIGN * SQRT ( COSDE2 )
105 * Original
106       SDE0 = MAX ( ONEONE - CDE, ANGLGB )
107       SDE1 = SDE0
108       FCORR0 = 0.10D+00
109       TMPSDE = 3.5D+00 * SDE0
110       FCORR  = ATO1O3 * MIN ( FCORR0, TMPSDE )
111  2000 CONTINUE
112          CALL GRANOR ( RNGSS, DUMNOR )
113          SDE = SDE0 + FCORR * RNGSS
114          CDE = 1.D+00 - SDE
115       IF ( ABS ( CDE ) .GE. 1.D+00 ) GO TO 2000
116       SDE = SQRT ( ( 1.D+00 - CDE ) * ( 1.D+00 + CDE ) )
117       RETURN
118       END