]> git.uio.no Git - u/mrichter/AliRoot.git/blame - GEANT321/gphys/gmcoul.F
Bugfix in AliPoints2Memory
[u/mrichter/AliRoot.git] / GEANT321 / gphys / gmcoul.F
CommitLineData
fe4da5cc 1*
2* $Id$
3*
4* $Log$
5* Revision 1.1.1.1 1995/10/24 10:21:26 cernlib
6* Geant
7*
8*
9* NEW
10#include "geant321/pilot.h"
11*CMZ : 3.21/02 29/03/94 15.41.22 by S.Giani
12*-- Author :
13 SUBROUTINE GMCOUL(OMEGA,DIN)
14C.
15C. ******************************************************************
16C. * *
17C * Generate NSCA single scatters in small angle approxima. *
18C. * for a particle with parameters VECT in common /GCTRAK/ *
19C. * *
20C. * This subroutine must be called with the correct values *
21C. * of the constants OMC & CHC which depend of the medium *
22C. * *
23C. * OMC and CHC are computed at initialisation time (GMOLI) *
24C. * No lateral displacement of the particle with respect *
25C. * the incident direction is included. *
26C. * No path length correction is included *
27C. * *
28C. * Output angles overwrite VECT *
29C. * *
30C. * ==>Called by : GMULTS *
31C. * Author G. Lynch (LBL) (adapted by M. Maire 1.02.90) *
32C. * *
33C. ******************************************************************
34C.
35#include "geant321/gctrak.inc"
36#include "geant321/gconsp.inc"
37#include "geant321/gcmulo.inc"
38 PARAMETER (NSCMX = 50)
39 DIMENSION DIN(3),RNDM(2*NSCMX)
40 PARAMETER (OMCF=1.167)
41*
42* ------------------------------------------------------------------
43*
44* *** Compute number of scatters (Poisson distr. with mean OMEGA0)
45*
46 OMEGA0 = OMCF*OMEGA
47 CALL GPOISS (OMEGA0,NSCA,1)
48 IF (NSCA.LE.0)THEN
49 DIN(1) = 0.
50 DIN(2) = 0.
51 DIN(3) = 1.
52 RETURN
53 ENDIF
54 NSCA = MIN(NSCA,NSCMX)
55 CALL GRNDM (RNDM,2*NSCA)
56*
57* *** THMIN2 is the screening angle
58 THMIN2 = (CHCMOL**2)/(OMCF*OMCMOL*(VECT(7)**2))
59*
60 SUMX = 0.
61 SUMY = 0.
62 DO 12 I=1,NSCA
63 THET = SQRT(THMIN2*((1./RNDM(I)) - 1.))
64 PHI = TWOPI*RNDM(NSCA+I)
65 SUMX = SUMX + THET*COS(PHI)
66 SUMY = SUMY + THET*SIN(PHI)
67 12 CONTINUE
68 THETA = SQRT(SUMX**2 + SUMY**2)
69 IF(THETA.NE.0.) THEN
70 COSTH = COS(THETA)
71 SINTH = SIN(THETA)
72 CSPHI = SUMX/THETA
73 SNPHI = SUMY/THETA
74*
75 DIN(1) = SINTH*CSPHI
76 DIN(2) = SINTH*SNPHI
77 DIN(3) = COSTH
78 ELSE
79 DIN(1) = 0.
80 DIN(2) = 0.
81 DIN(3) = 1.
82 ENDIF
83*
84 END