Nbody6
 All Files Functions Variables
cloud.f
Go to the documentation of this file.
1  SUBROUTINE cloud(J)
2 *
3 *
4 * Initialization of interstellar cloud.
5 * -------------------------------------
6 *
7  include 'common6.h'
8  common/clouds/ xcl(3,mcl),xdotcl(3,mcl),bodycl(mcl),rcl2(mcl),
9  & clm(mcl),clmdot(mcl),cldot,vcl,sigma,rb2,pcl2,
10  & tcl,stepcl,ncl,newcl
11  REAL*8 ran2,a(13)
12 *
13 *
14 * Increase new cloud counter.
15  newcl = newcl + 1
16 * Generate a random position on the boundary sphere.
17  1 a(1) = 0.0
18  DO 2 k = 1,3
19 * Note that IDUM1 is saved in COMMON6 for restarts.
20  a(k+1) = 2.0*ran2(idum1) - 1.0
21  a(1) = a(1) + a(k+1)**2
22  2 CONTINUE
23  IF (a(1).GT.1.0) go to 1
24  DO 3 k = 1,3
25  xcl(k,j) = a(k+1)*sqrt(rb2/a(1))
26  3 CONTINUE
27  ranphi = twopi*ran2(idum1)
28  randi = sqrt(ran2(idum1))
29  randi = dasin(randi)
30 * Azimuth & inclination for velocity from Henon (A & A, 19, 488).
31  a(1) = sin(ranphi)
32  a(2) = cos(ranphi)
33  a(3) = sin(randi)
34  a(4) = cos(randi)
35  IF (kz(13).GE.2) THEN
36  DO 10 k = 1,3
37  a(5) = ran2(idum1)
38  a(6) = twopi*ran2(idum1)
39  a(k+10) = vcl + sigma*sqrt(-2.0d0*log(a(5)))*cos(a(6))
40  10 CONTINUE
41  a(10) = sqrt(a(11)**2 + a(12)**2 + a(13)**2)
42  ELSE
43  a(10) = vcl
44  END IF
45  a(11) = a(10)*a(2)*a(3)
46  a(12) = a(10)*a(1)*a(3)
47  a(13) = -a(10)*a(4)
48  phi = datan2(-xcl(1,j),(-xcl(2,j)))
49  a(1) = xcl(3,j)/sqrt(rb2)
50  theta = dacos(a(1))
51 * Eulerian angles of the transformation.
52  a(1) = sin(phi)
53  a(2) = cos(phi)
54  a(3) = sin(theta)
55  a(4) = cos(theta)
56 * Generate isotropic velocities ignoring c.m. motion of cluster.
57  xdotcl(1,j) = -a(4)*a(1)*a(11) + a(2)*a(12) - a(3)*a(1)*a(13)
58  xdotcl(2,j) = -a(4)*a(2)*a(11) - a(1)*a(12) - a(3)*a(2)*a(13)
59  xdotcl(3,j) = -a(3)*a(11) + a(4)*a(13)
60 * Convert to rotating coordinates.
61  xdotcl(1,j) = xdotcl(1,j) + 0.5*tidal(4)*xcl(2,j)
62  xdotcl(2,j) = xdotcl(2,j) - 0.5*tidal(4)*xcl(1,j)
63  bodycl(j) = 0.0
64 * The cloud mass is increased smoothly from zero at boundary.
65  DO 20 k = 1,3
66  xcl(k,j) = xcl(k,j) - rdens(k)
67  20 CONTINUE
68 * Coordinates transformed from density centre to inertial frame.
69 *
70  RETURN
71 *
72  END