Nbody6
 All Files Functions Variables
tcirc.f
Go to the documentation of this file.
1  SUBROUTINE tcirc(RP,ES0,I1,I2,ICIRC,TC)
2 *
3 *
4 * Circularization time.
5 * ---------------------
6 *
7 * Theory of Piet Hut, A & A 99, 126 (1981).
8 * Developed by Rosemary Mardling (31/1/97).
9 * @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
10 *
11  include 'common6.h'
12  REAL*8 ww(3),qq(3),w(2),q(2),at0(2),m21,wg(2),qg(2),
13  & wscale(2),qscale(2),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  DATA eccm,eccm1 /0.002,0.002001/
21  SAVE itime
22  DATA itime /0/
23 *
24 *
25 * Set large circularization time for merged binary or BHs.
26  IF (radius(i1).EQ.0.0d0.OR.radius(i2).EQ.0.0d0.OR.
27  & (kstar(i1).EQ.14.AND.kstar(i2).EQ.14)) THEN
28  tc = 1.0d+10
29  go to 30
30  END IF
31 *
32 * Specify index J1 as biggest radius to be used with AT0(1).
33  IF (radius(i1).GE.radius(i2)) THEN
34  j1 = i1
35  j2 = i2
36  ELSE
37  j1 = i2
38  j2 = i1
39  END IF
40 *
41 * Include an appropriate numerical factor (Chris Tout 07/08).
42  ar = rp/((1.0 - es0)*radius(j1))
43  ff = 1.0
44  IF (kstar(j1).EQ.1.AND.body(j1)*smu.GT.1.25) THEN
45  ff = 100.0
46  ELSE IF (kstar(j1).EQ.4.OR.kstar(j1).EQ.7) THEN
47  ff = 100.0
48  ELSE IF (kstar(j1).GE.10) THEN
49  ff = 1.0d+17/ar**2
50  END IF
51  q12 = body(j1)/body(j2)
52  tauc = ff*2.0*q12**2/(1.0 + q12)*ar**8
53 * Exit on TC > 1.0D+08 yr (Chris Tout, Cambody Book 2008).
54  IF (tauc.GT.1.0d+08) THEN
55  tc = 1.0d+10
56  go to 30
57  END IF
58 *
59 * Define oscillation period (dimensionless time) and damping constants.
60  xn = 0.0
61  DO 5 k = 1,2
62  IF (k.EQ.1) THEN
63  ik = j1
64  ELSE
65  ik = j2
66  END IF
67 * Specify polytropic index for each star (n = 3, 2 or 3/2).
68  IF (kstar(ik).EQ.3.OR.kstar(ik).EQ.5.OR.
69  & kstar(ik).EQ.6.OR.kstar(ik).EQ.9) THEN
70  ipair = kvec(i1)
71  CALL giant(ipair,ik,wg,qg,wscale,qscale,xn,ql)
72  w(k) = wg(1)
73  q(k) = qg(1)
74  ELSE
75  ql = 1.0d+04
76  ip = 3
77  IF (kstar(ik).GE.3) ip = 2
78  IF (kstar(ik).EQ.4.OR.kstar(ik).EQ.7) ip = 3
79  IF (kstar(ik).EQ.8) ip = 3
80  IF (kstar(ik).EQ.0) ip = 1
81  w(k) = ww(ip)
82  q(k) = qq(ip)
83  END IF
84  tl = twopi*radius(ik)*sqrt(radius(ik)/body(ik)/w(k))
85  at0(k) = 1.0/(ql*tl)
86  5 CONTINUE
87 *
88 * Form mass, radius & pericentre ratio.
89  IF (radius(i1).GE.radius(i2)) THEN
90  m21 = body(i2)/body(i1)
91  r21 = radius(i2)/radius(i1)
92  rp1 = rp/radius(i1)
93  ELSE
94  m21 = body(i1)/body(i2)
95  r21 = radius(i1)/radius(i2)
96  rp1 = rp/radius(i2)
97  END IF
98 *
99 * Evaluate damping coefficient.
100  rr = rp1*(1.0 + es0)
101  const = 2.0*(at0(1)*(q(1)/w(1))**2*(1.0 + m21)*m21 +
102  & at0(2)*(q(2)/w(2))**2*((1.0 + m21)/m21**2)*r21**8)/
103  & rr**8
104 *
105 * Adopt WD scaling for any NS/BH to avoid numerical problem.
106  IF (kstar(i1).GE.13.OR.kstar(i2).GE.13) THEN
107  const = 1.0d-04*const
108  END IF
109 *
110 * Form rational function approximation to Hut solution.
111  ff = (( a(2)*es0 + a(1))*es0 + 1.0 )/
112  & (( b(2)*es0 + b(1))*es0 + 1.0 )
113 * FF = MIN(FF,0.999D0)
114 *
115 * See whether we only want the modified eccentricity (routine BINPOP).
116  IF (icirc.LE.0) go to 10
117 *
118  time0 = 0.0
119 * Obtain the new eccentricity.
120  z = (time - time0)*const + ff
121  ecc = (-1.0 + c(1)*z - sqrt(c(2)*z**2 + c(3)*z + c(4)))
122  & /(c(5) + c(6)*z)
123 *
124  ecc = max(ecc,eccm)
125  rp = rp*(1.0 + es0)/(1.0 + ecc)
126  es0 = ecc
127  go to 30
128 *
129 * Evaluate circularization time (in units of 10**6 yrs).
130  10 tc = tstar*(1.0 - ff)/const
131 *
132 * Activate tidal indicator if TC < 2x10**9 yrs or hyperbolic orbit.
133  IF (tc.LT.2000.0.OR.es0.GT.1.0) THEN
134  ip = kvec(i1)
135  itime = itime + 1
136 * Note possibility of counter exceeding the limit.
137  IF (itime.GT.2000000000) itime = 0
138  IF (icirc.EQ.0.AND.kz(27).EQ.2.AND.itime.LT.100) THEN
139  semi = -0.5*body(n+ip)/h(ip)
140  WRITE (6,20) i1, nchaos, es0, rp1, m21, tc, semi, xn
141  20 FORMAT (' TCIRC: I1 NCH E RP M21 TC A n ',
142  & 2i5,f8.4,f8.1,f6.2,1p,2e10.2,0p,f5.1)
143  END IF
144  icirc = 1
145 * Define Roche search indicator for circularized orbit (ECCM1 > 0.002).
146  IF (es0.LE.eccm1.AND.kstar(n+ip).EQ.0) THEN
147  kstar(n+ip) = 10
148  END IF
149  ELSE
150 * Note ICIRC = -1 for some calls.
151  icirc = 0
152  END IF
153 *
154  30 RETURN
155 *
156  END