Nbody6
 All Files Functions Variables
hicirc.f
Go to the documentation of this file.
1  SUBROUTINE hicirc(RP,ES0,I1,I2,BODYI,TG,TC,ECC1,EDOT,W)
2 *
3 *
4 * Eccentricity for given circularization time.
5 * --------------------------------------------
6 *
7 * Theory of Rosemary Mardling, Ap. J. XX, YYY, 1995.
8 * @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
9 *
10  include 'common6.h'
11  REAL*8 ww(3),qq(3),w(2),q(2),at0(2),m21,wg(2),qg(2),
12  & bodyi(2),bod(2)
13  REAL*8 a(2),b(2),c(6)
14  DATA ww /2.119,3.113,8.175/
15  DATA qq /0.4909,0.4219,0.2372/
16  DATA a /6.306505,-7.297806/
17  DATA b /32.17211,13.01598/
18  DATA c /5.101417,24.71539,-9.627739,1.733964,
19  & -2.314374,-4.127795/
20 *
21 *
22 * Specify index J1 as biggest radius to be used with AT0(1).
23  IF (radius(i1).GE.radius(i2)) THEN
24  j1 = i1
25  j2 = i2
26  bod(1) = bodyi(1)
27  bod(2) = bodyi(2)
28  ELSE
29  j1 = i2
30  j2 = i1
31  bod(1) = bodyi(2)
32  bod(2) = bodyi(1)
33  END IF
34 *
35 * Define oscillation period (dimensionless time) and damping constants.
36  DO 5 k = 1,2
37  IF (k.EQ.1) THEN
38  ik = j1
39  ELSE
40  ik = j2
41  END IF
42 * Specify polytropic index for each star (n = 3, 2 or 3/2).
43  IF (kstar(ik).EQ.3.OR.kstar(ik).EQ.5.OR.
44  & kstar(ik).EQ.6.OR.kstar(ik).EQ.9) THEN
45  bodi = bod(k)
46  CALL giant3(ik,bodi,wg,qg,xn,ql)
47  w(k) = wg(1)
48  q(k) = qg(1)
49  CONTINUE
50  ELSE
51  ql = 1.0d+04
52  ip = 3
53  IF (kstar(ik).GE.3) ip = 2
54  IF (kstar(ik).EQ.4.OR.kstar(ik).EQ.7) ip = 3
55  IF (kstar(ik).EQ.8) ip = 3
56  IF (kstar(ik).EQ.0) ip = 1
57  w(k) = ww(ip)
58  q(k) = qq(ip)
59  END IF
60  tl = twopi*radius(ik)*sqrt(radius(ik)/bod(k)/w(k))
61  at0(k) = 1.0/(ql*tl)
62  5 CONTINUE
63 *
64 * Form mass, radius & pericentre ratio (note BODYI(2) is a ghost).
65  IF (radius(i1).GE.radius(i2)) THEN
66  m21 = bodyi(2)/bodyi(1)
67  r21 = radius(i2)/radius(i1)
68  rp1 = rp/radius(i1)
69  ELSE
70  m21 = bodyi(1)/bodyi(2)
71  r21 = radius(i1)/radius(i2)
72  rp1 = rp/radius(i2)
73  END IF
74 *
75 * Evaluate damping coefficient.
76  rr = rp1*(1.0 + es0)
77  const = 2.0*(at0(1)*(q(1)/w(1))**2*(1.0 + m21)*m21 +
78  & at0(2)*(q(2)/w(2))**2*((1.0 + m21)/m21**2)*r21**8)/
79  & rr**8
80 *
81 * Form rational function approximation to Hut solution.
82  ff = (( a(2)*es0 + a(1))*es0 + 1.0 )/
83  & (( b(2)*es0 + b(1))*es0 + 1.0 )
84  ff = min(ff,0.999d0)
85 *
86 * Determine eccentricity corresponding to t_{circ} = t_{grow}.
87  z = tg*const/tstar + ff
88  ecc1 = (-1.0 + c(1)*z - sqrt(c(2)*z**2 + c(3)*z + c(4)))
89  & /(c(5) + c(6)*z)
90 *
91 * Evaluate circularization time (in units of 10**6 yrs).
92  tc = tstar*(1.0 - ff)/const
93 *
94 * Obtain (de/dt) due to tidal circularization.
95  fe = 1.0 + 3.75*es0**2 + 1.875*es0**4 + (5.0/64.0)*es0**6
96  fe = (9.0*twopi/10.0)*es0*(1.0 - es0**2)**1.5*fe
97  edot = -const*fe
98 *
99  RETURN
100 *
101  END