root / TrouNoir / trou_noir_1994.f @ 238
Historique | Voir | Annoter | Télécharger (18,29 ko)
1 |
PROGRAM MODELISATION_NUMERIQUE |
---|---|
2 |
|
3 |
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc |
4 |
c c |
5 |
c MODELISATION NUMERIQUE D'UN DISQUE D'ACCRETION AUTOUR D'UN TROU NOIR : c |
6 |
c c |
7 |
c APPARENCE & SPECTRE c |
8 |
c c |
9 |
c Programme realise par : Herve AUSSEL c |
10 |
c Emmanuel QUEMENER c |
11 |
c c |
12 |
c Dans le cadre de l'unite de modelisation numerique du DEA c |
13 |
c d'Astrophysique & Techniques Spatiales (Paris 7 & 11) c |
14 |
c c |
15 |
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc |
16 |
|
17 |
IMPLICIT NONE |
18 |
REAL*8 pi |
19 |
PARAMETER (pi=3.141592654) |
20 |
|
21 |
c |
22 |
c PARAMETRES PHYSIQUES DU SYSTEME DISQUE, TROU-NOIR, OBSERVATEUR |
23 |
c |
24 |
|
25 |
REAL*8 m ! masse reduite du trou noir |
26 |
REAL*8 rs,ri,re ! rayons de Schwarzschild,interieur et exterieur |
27 |
REAL*8 tho ! angle normale-disque & direction-observateur |
28 |
REAL*8 ro ! distance entre l'observateur et le trou noir |
29 |
INTEGER*4 q ! parametre de spectre |
30 |
REAL*4 bss ! borne superieure du spectre |
31 |
|
32 |
c |
33 |
c PARAMETRES DE LA PLAQUE PHOTOGRAPHIQUE |
34 |
c |
35 |
|
36 |
INTEGER*4 dim ! dimension de la plaque photographique (en pixels) |
37 |
PARAMETER (dim=512) |
38 |
REAL*4 stp ! pas d'iteration en pixels sur la plaque |
39 |
INTEGER*4 nmx ! nombre total d'iterations |
40 |
REAL*8 d ! distance exploree du centre de la plaque |
41 |
REAL*8 bmx ! parametre d'impact maximal |
42 |
|
43 |
c |
44 |
c PARAMETRES INITIAUX D' INTEGRATION |
45 |
c |
46 |
|
47 |
REAL*8 db ! avancement du parametre d'impact |
48 |
REAL*8 b ! parametre d'impact du photon |
49 |
REAL*8 h ! avancement angulaire initial |
50 |
|
51 |
c |
52 |
c PARAMETRES D'INTEGRATION DU SYSTEME DIFFERENTIEL |
53 |
c |
54 |
|
55 |
REAL*8 up,vp,pp ! parametres du SED , precedents |
56 |
REAL*8 us,vs,ps ! parametres du SED , suivants |
57 |
|
58 |
c |
59 |
c RESULTATS DE L'INTEGRATION DE L'EQUATION DIFFERENTIELLE |
60 |
c |
61 |
|
62 |
REAL*8 rp(2000) ! vecteur polaire |
63 |
REAL*8 nh ! nombre d'avancements angulaires |
64 |
|
65 |
c |
66 |
c RESULTATS DE LA SIMULATION |
67 |
c |
68 |
|
69 |
REAL*4 zp(dim,dim) ! image en decalage spectral |
70 |
REAL*4 fp(dim,dim) ! image en flux |
71 |
REAL*8 fx(200) ! flux par tranche de decalage de frequence |
72 |
INTEGER*4 nt(200) ! nombre de photon par tranche de decalage |
73 |
|
74 |
c |
75 |
c AUTRES VARIABLES... |
76 |
c |
77 |
|
78 |
INTEGER*4 pc ! pourcentage du balayage realise |
79 |
REAL*8 phi ! angle de la plaque photographique |
80 |
REAL*8 thi ! angle trou noir-observateur & direction emission |
81 |
REAL*8 thx ! angle thi maximal |
82 |
REAL*8 phd ! angle donnant l'intersection des plans |
83 |
REAL*8 php ! angle d'intersection intermediaire |
84 |
REAL*8 nr ! indice d'intersection reel du vecteur |
85 |
INTEGER*4 ni ! indice d'intersection entier du vecteur |
86 |
INTEGER*4 ii ! indice de 1' image (primaire, secondaire, ...) |
87 |
REAL*8 r ! rayon moyen d'impact sur le disque |
88 |
INTEGER*4 nbr ! nombre de bandes de rapport de frequence |
89 |
INTEGER*4 i,imx,j,n |
90 |
LOGICAL tst |
91 |
REAL*8 atanp ! fonction arctangente : resultat entre 0 et 2*pi |
92 |
LOGICAL raie ! variable interactive de type de spectre |
93 |
LOGICAL dist ! variable interactive de distance |
94 |
|
95 |
c |
96 |
c TYPE DE SPECTRE |
97 |
c |
98 |
|
99 |
c raie=.TRUE. ! TRUE -> raie infiniment fine |
100 |
raie=.FALSE. ! FALSE -> corps noir |
101 |
|
102 |
c |
103 |
c TYPE DE DISTANCE |
104 |
c |
105 |
|
106 |
dist=.TRUE. ! TRUE -> distance infinie |
107 |
c ! FALSE -> distance finie |
108 |
|
109 |
c |
110 |
c INITIALISATION DES TABLEAUX |
111 |
c |
112 |
|
113 |
DO i=1,200 |
114 |
fx(i)=0. |
115 |
nt(i)=0 |
116 |
END DO |
117 |
|
118 |
DO i=1,dim |
119 |
DO j=1,dim |
120 |
zp(i,j)=0. |
121 |
fp(i,j)=0. |
122 |
END DO |
123 |
END DO |
124 |
|
125 |
c |
126 |
c DEFINITION DES PARAMETRES PHYSIQUES |
127 |
c |
128 |
|
129 |
m=1. |
130 |
rs=2.*m |
131 |
ri=3.*rs |
132 |
re=12. |
133 |
ro=100. |
134 |
tho=pi/180.*80. |
135 |
IF (raie .EQV. .TRUE.) THEN |
136 |
q=-2 |
137 |
ELSE |
138 |
q=-3/4 |
139 |
ENDIF |
140 |
|
141 |
c |
142 |
c DEFINITION DES PARAMETRES NUMERIQUES |
143 |
c |
144 |
|
145 |
nmx=dim |
146 |
stp=dim/(2.*nmx) |
147 |
bmx=1.25*re |
148 |
b=0. |
149 |
thx=asin(bmx/ro) |
150 |
pc=0 |
151 |
nbr=200 |
152 |
IF (raie .EQV. .TRUE.) THEN |
153 |
bss=2. |
154 |
ELSE |
155 |
bss=1.e19 |
156 |
ENDIF |
157 |
|
158 |
c |
159 |
c BOUCLE PRINCIPALE DE LA SIMULATION |
160 |
c |
161 |
|
162 |
DO n=1,nmx |
163 |
pc=INT(100./nmx*n) |
164 |
IF (pc.NE.INT(100./nmx*(n-1))) WRITE (*,*) pc, ' %' |
165 |
|
166 |
c |
167 |
c Affectation des conditions initiales de la resolution Runge-Kutta |
168 |
c ( Premier etage d'imbrication -> n ) |
169 |
c |
170 |
h=pi/500. |
171 |
d=stp*n |
172 |
IF (dist .EQV. .TRUE.) THEN |
173 |
db=bmx/nmx |
174 |
b=db*n |
175 |
up=0. |
176 |
vp=1. |
177 |
ELSE |
178 |
thi=thx/nmx*n |
179 |
db=ro*DSIN(thi)-b |
180 |
b=ro*DSIN(thi) |
181 |
up=DSIN(thi) |
182 |
vp=DCOS(thi) |
183 |
ENDIF |
184 |
pp=0. |
185 |
nh=1 |
186 |
CALL rungekutta(ps,us,vs,pp,up,vp,h,m,b) |
187 |
rp(nh)=ABS(b/us) |
188 |
|
189 |
c |
190 |
c Resolution de l'equation differentielle pour un parametre b donne |
191 |
c Les resultats sont stockes dans le vecteur polaire rp(n) |
192 |
c ( Deuxieme etage d'imbrication -> n & nh ) |
193 |
c |
194 |
|
195 |
DO WHILE ((rp(nh).GE.rs).AND.(rp(nh).LE.rp(1))) |
196 |
nh=nh+1 |
197 |
pp=ps |
198 |
up=us |
199 |
vp=vs |
200 |
CALL rungekutta(ps,us,vs,pp,up,vp,h,m,b) |
201 |
rp(nh)=b/us |
202 |
END DO |
203 |
|
204 |
c |
205 |
c Mise a zero de tous les termes non redefinis du vecteur polaire |
206 |
c ( Deuxieme etage d'imbrication -> n & 1 ) |
207 |
c |
208 |
|
209 |
DO i=nh+1,2000 |
210 |
rp(i)=0. |
211 |
END DO |
212 |
|
213 |
c |
214 |
c Determination des points de la trajectoire coupant le plan du disque |
215 |
c par echantillonnage de 1' angle phi sur un cercle, a pas radial constant |
216 |
c ( Deuxieme etage d'imbrication -> n & 1 ) |
217 |
c |
218 |
|
219 |
imx=INT(8*d) |
220 |
DO i=0,imx |
221 |
phi=2*pi/imx*i |
222 |
|
223 |
c Calcul de l'angle "brut" d'intersection dans la base polaire |
224 |
|
225 |
phd=atanp(DCOS(phi)*DSIN(tho),DCOS(tho)) |
226 |
phd=phd-INT(phd/pi)*pi |
227 |
ii=0 |
228 |
tst=.FALSE. |
229 |
|
230 |
c |
231 |
c Boucle tant que - que l'image tertiaire n'a pas ete teste |
232 |
c - le rayon n'est pas dans le domaine du disque |
233 |
c ( Troisieme etage d'imbrication -> n , 1 , (ii, tst) , r ) |
234 |
c |
235 |
|
236 |
DO WHILE((ii.LE.2).AND.(tst.EQV..FALSE.)) |
237 |
|
238 |
c Calcul de l'angle d'intersection pour chacune des images |
239 |
|
240 |
php=phd+ii*pi |
241 |
nr=php/h |
242 |
ni=INT(nr) |
243 |
|
244 |
c Interpolation lineaire de la distance photon-trou noir |
245 |
|
246 |
IF (ni.LT.nh) THEN |
247 |
r=(rp(ni+1)-rp(ni))*(nr-ni*1.)+rp(ni) |
248 |
ELSE |
249 |
r=rp(ni) |
250 |
ENDIF |
251 |
|
252 |
|
253 |
c |
254 |
c Test d'impact sur le disque |
255 |
c ( Quatrieme etage d'imbrication -> n , i , (ii,tst) , r ) |
256 |
c |
257 |
|
258 |
IF ((r.LE.re).AND.(r.GE.ri)) then |
259 |
tst=.TRUE. |
260 |
|
261 |
c S'il y a impact calcul - du rapport de frequence |
262 |
c - du spectre de photons et de flux |
263 |
|
264 |
CALL impact(raie,d,phi,dim,r,b,tho,m,zp,fp,nt, |
265 |
& fx,q,db,h,nbr,bss) |
266 |
|
267 |
END IF |
268 |
|
269 |
ii=ii+1 |
270 |
END DO |
271 |
END DO |
272 |
END DO |
273 |
|
274 |
c Appel de la routine d'affichage |
275 |
|
276 |
CALL affichage(zp,fp,nt,fx,dim,nbr,bss,bmx,m,ri,re,tho,pi) |
277 |
|
278 |
WRITE(*,*) |
279 |
WRITE(*,*) 'C''est TERMINE ! ' |
280 |
WRITE(*,*) |
281 |
|
282 |
STOP |
283 |
END PROGRAM |
284 |
|
285 |
c |
286 |
c Cette fonction permet de trouver un arctangente entre 0 et 2*pi |
287 |
c |
288 |
|
289 |
REAL*8 function atanp(x,y) |
290 |
REAL*8 x,y,pi,eps |
291 |
pi=3.141592654 |
292 |
eps=1.e-20 |
293 |
IF (ABS(x).LE.eps) then |
294 |
IF (ABS(y).EQ.Y) then |
295 |
atanp=pi/2. |
296 |
ELSE |
297 |
atanp=3.*pi/2. |
298 |
END IF |
299 |
ELSE |
300 |
IF (ABS(x).EQ.x) then |
301 |
IF (ABS(y).EQ.Y) then |
302 |
atanp=DATAN(y/x) |
303 |
ELSE |
304 |
atanp=DATAN(y/x)+2.*pi |
305 |
END IF |
306 |
ELSE |
307 |
atanp=DATAN(y/x)+pi |
308 |
END IF |
309 |
END IF |
310 |
RETURN |
311 |
END |
312 |
|
313 |
c |
314 |
c Premiere fonction du systeme -> ( d(u)/d(phi)=f(phi,u,v) ) |
315 |
c |
316 |
|
317 |
REAL*8 function f(v) |
318 |
REAL*8 v |
319 |
f=v |
320 |
RETURN |
321 |
END |
322 |
|
323 |
c |
324 |
c Deuxieme fonction du systeme -> ( d(v)/d(phi)=g(phi,u,v) ) |
325 |
c |
326 |
|
327 |
REAL*8 function g(u,m,b) |
328 |
REAL*8 u, m, b |
329 |
g=3.*m/b*u**2-u |
330 |
RETURN |
331 |
END |
332 |
|
333 |
c |
334 |
c Routine de d'intergration par la methode de Runge-Kutta |
335 |
c |
336 |
|
337 |
SUBROUTINE rungekutta(ps,us,vs,pp,up,vp,h,m,b) |
338 |
REAL*8 ps,us,vs,pp,up,vp,h,m,b |
339 |
CALL calcul(us,vs,up,vp,h,m,b) |
340 |
ps=pp+h |
341 |
RETURN |
342 |
END |
343 |
|
344 |
SUBROUTINE calcul(us,vs,up,vp,h,m,b) |
345 |
REAL*8 us,vs,up,vp,h,m,b |
346 |
REAL*8 c(4),d(4),f,g |
347 |
c(1)=h*f(vp) |
348 |
c(2)=h* f(vp+c(1)/2.) |
349 |
c(3)=h*f(vp+c(2)/2.) |
350 |
c(4)=h*f(vp+c(3)) |
351 |
d(1)=h*g(up,m,b) |
352 |
d(2)=h*g(up+d(1)/2.,m,b) |
353 |
d(3)=h*g(up+d(2)/2.,m,b) |
354 |
d(4)=h*g(up+d(3),m,b) |
355 |
us=up+(c(1)+2.*c(2)+2.*c(3)+c(4))/6. |
356 |
vs=vp+(d(1)+2.*d(2)+2.*d(3)+d(4))/6. |
357 |
RETURN |
358 |
END |
359 |
|
360 |
c |
361 |
c En cas d'impact, cette procedure : |
362 |
c - etablit la position du pixel consisdere sur les images |
363 |
c - appelle la routine de calcul de decalage spectral |
364 |
c - appelle la routine de calcul du flux et du spectre |
365 |
c - affecte a chacun des pixels sa valeur calculee |
366 |
c |
367 |
|
368 |
SUBROUTINE impact(raie,d,phi,dim,r,b,tho,m,zp,fp, |
369 |
& nt,fx,q,db,h,nbr,bss) |
370 |
REAL*8 d,phi,r,b,tho,m,fx(200),db,h |
371 |
INTEGER*4 dim,nt(200),q,nbr |
372 |
REAL*4 zp(dim,dim),fp(dim,dim),bss |
373 |
REAL*4 xe,ye |
374 |
INTEGER*4 xi,yi |
375 |
REAL*8 flx,rf |
376 |
LOGICAL raie |
377 |
xe=d*DSIN(phi) |
378 |
ye=-d*DCOS(phi) |
379 |
|
380 |
c Calcul des coordonnees (x,y) du pixel sur chacune des images |
381 |
|
382 |
xi=INT(xe)+INT(dim/2.) |
383 |
yi=INT(ye)+INT(dim/2.) |
384 |
|
385 |
c Appel de la routine de decalage spectral |
386 |
|
387 |
CALL decalage_spectral(rf,r,b,phi,tho,m) |
388 |
|
389 |
c Appel de la routine de calcul de flux et de modification de spectre |
390 |
c pour le cas d'une raie infiniment fine ou un corps noir |
391 |
|
392 |
IF (raie .EQV. .TRUE.) THEN |
393 |
CALL spectre(nt,fx,rf,q,b,db,h,r,m,nbr,bss,flx) |
394 |
ELSE |
395 |
CALL spectre_bb(nt,fx,rf,q,b,db,h,r,m,nbr,bss,flx) |
396 |
END IF |
397 |
|
398 |
c Affectation sur chacune des images du decalage spectral et du flux |
399 |
|
400 |
IF(zp(xi,yi).EQ.0.) zp(xi,yi)=1./rf |
401 |
IF(fp(xi,yi).EQ.0.) fp(xi,yi)=flx |
402 |
|
403 |
RETURN |
404 |
END |
405 |
|
406 |
c Calcul du rapport entre la frequence recue et la frequence emise |
407 |
|
408 |
SUBROUTINE decalage_spectral(rf,r,b,phi,tho,m) |
409 |
REAL*8 rf,r,b,phi,tho,m |
410 |
rf=sqrt(1-3*m/r)/(1+sqrt(m/r**3)*b*sin(tho)*sin(phi)) |
411 |
RETURN |
412 |
END |
413 |
|
414 |
c Calcul du flux puis du spectre pour une raie infiniment fine |
415 |
|
416 |
SUBROUTINE spectre(nt,fx,rf,q,b,db,h,r,m,nbr,bss,flx) |
417 |
REAL*8 fx(200) |
418 |
REAL*8 rf,b,db,h,r,m,flx |
419 |
REAL*4 bss |
420 |
INTEGER*4 nt(200),q,nbr |
421 |
INTEGER*4 fi |
422 |
fi=INT(rf*nbr/bss) |
423 |
nt(fi)=nt(fi)+1 |
424 |
flx=(r/m)**q*rf**4*b*db*h |
425 |
fx(fi)=fx(fi)+flx |
426 |
RETURN |
427 |
END |
428 |
|
429 |
c Calcul du flux puis du spectre pour un corps noir |
430 |
|
431 |
SUBROUTINE spectre_bb(nr,fx,rf,q,b,db,h,r,m,nbr,bss,flx) |
432 |
REAL*8 fx(200),nu_rec,nu_em,qu,v |
433 |
REAL*8 rf,b,db,h,r,m,flx,temp,temp_em,flux_int |
434 |
REAL*8 m_point |
435 |
REAL*4 bss |
436 |
INTEGER*4 nr(200),q,nbr |
437 |
INTEGER*4 fi,posfreq |
438 |
REAL*8 planck,c,k |
439 |
PARAMETER (planck=6.62e-34) ! definition des constantes |
440 |
PARAMETER (c=3.e8) |
441 |
PARAMETER (k=1.38e-23) |
442 |
|
443 |
c |
444 |
c Definition des parametres pour le calcul de la temperature d'emission |
445 |
c puis calcul |
446 |
c |
447 |
|
448 |
temp=3.e7 |
449 |
m_point=1. |
450 |
|
451 |
c v -> C du rapport |
452 |
|
453 |
v=1.-3./r |
454 |
|
455 |
c qu -> Q du rapport |
456 |
|
457 |
qu=((1-3./r)**-.5)*(r**-.5)*((r**.5-6.**.5)+ |
458 |
& ((3.**.5)/2.)*log ((r**.5)-(3.**.5))*0.171517) |
459 |
qu=abs(qu) |
460 |
temp_em=temp*m**.5 |
461 |
temp_em=temp_em*m_point**.25 |
462 |
temp_em=temp_em*r**(-.75) |
463 |
temp_em=temp_em*v**(-1./8.) |
464 |
temp_em=temp_em*qu**.25 |
465 |
|
466 |
c |
467 |
c initialisation des compteurs de flux |
468 |
c flux int : flux recu pour le pixel dans la tranque posfreq |
469 |
c flx : flux "bolometrique", integre de 0. a bss |
470 |
c |
471 |
|
472 |
flux_int=0. |
473 |
flx=0. |
474 |
|
475 |
c |
476 |
c Balayage en frequence du spectre |
477 |
c |
478 |
|
479 |
DO fi=1,nbr |
480 |
nu_em=bss*fi/nbr !frequence d' emission |
481 |
nu_rec=nu_em*rf !frequence de reception |
482 |
posfreq=INT(nu_rec*200./bss) !case ou se trouve nu rec |
483 |
|
484 |
c |
485 |
c test pour savoir si la frequence de reception est bien dans le |
486 |
c domaine du spectre calcule |
487 |
c |
488 |
|
489 |
if ((posfreq.GE.1).AND.(posfreq.LE.nbr)) THEN |
490 |
nr(posfreq)=nr(posfreq)+1 |
491 |
|
492 |
c Loi du corps noir |
493 |
|
494 |
flux_int=(2.*h*(nu_em**3/c**2))* |
495 |
& (1./(exp(planck*nu_em/(k*temp_em))-1.)) |
496 |
|
497 |
c Integration sur le pixel |
498 |
|
499 |
flux_int=flux_int*rf**3*b*db*h |
500 |
|
501 |
c Remplissage du spectre |
502 |
|
503 |
fx(posfreq)=flux_int+fx(posfreq) |
504 |
|
505 |
c Intergration bolometrique |
506 |
|
507 |
flx=flx+flux_int |
508 |
ENDIF |
509 |
END DO |
510 |
RETURN |
511 |
END |
512 |
|
513 |
c |
514 |
c AFFICHAGE DES RESULTATS : 6 fenetres de sortie |
515 |
c |
516 |
c - Image en decalage spectral |
517 |
c - Image en flux |
518 |
c - Dessin de parametres physiques interessants |
519 |
c - Dessin des limites du disque a l'infini |
520 |
c - Dessin du spectre en flux |
521 |
c - Dessin du spectre en nombre de photons |
522 |
c |
523 |
|
524 |
SUBROUTINE affichage(zp,fp,nt,fx,dim,nbr,bss,bmx,m,ri,re,tho,pi) |
525 |
INTEGER*4 nt(200),dim,nbr |
526 |
REAL*4 zp(dim,dim),fp(dim,dim),bss |
527 |
REAL*8 fx(200),bmx,m,ri,re,tho,pi |
528 |
INTEGER*4 np,i,j |
529 |
REAL*8 fm,nm |
530 |
REAL*4 fmx,zmx,x(200),y(200),tr(6),c(20),bmp |
531 |
LOGICAL tg |
532 |
LOGICAL ps |
533 |
|
534 |
tg=.TRUE. ! TRUE : affichage en tons de gris |
535 |
c ! FALSE : affichage en contours |
536 |
|
537 |
ps=.FALSE. ! TRUE : affichage postscript |
538 |
c ! FALSE : affichage fenetre Xwindow |
539 |
|
540 |
|
541 |
c |
542 |
c TRANSFORMATION DE L'IMAGE DES FLUX : FLUX -> FLUX RELATIFS |
543 |
c |
544 |
|
545 |
np=0 |
546 |
fm=0. |
547 |
DO i=1,dim |
548 |
DO j=1,dim |
549 |
IF (fp(i,j).NE.0.) np=np+1 |
550 |
fm=fm+fp(i,j) |
551 |
END DO |
552 |
END DO |
553 |
fm=fm/np |
554 |
|
555 |
c |
556 |
c DETERMINATION DU DECALAGE SPECTRAL MAXIMUM ET DU FLUX MAXIMUM |
557 |
c |
558 |
|
559 |
fmx=0. |
560 |
zmx=0. |
561 |
DO i=1,dim |
562 |
DO j=1,dim |
563 |
fp(i,j)=fp(i,j)/fm |
564 |
IF (fmx.LT.fp(i,j)) fmx=fp(i,j) |
565 |
IF (zmx.LT.zp(i,j)) zmx=zp(i,j) |
566 |
END DO |
567 |
END DO |
568 |
|
569 |
DATA tr/0.,1.,0.,0.,0.,1./ |
570 |
|
571 |
c |
572 |
c AFFICHAGE DE L'IMAGE DES DECALAGES SPECTRAUX |
573 |
c |
574 |
|
575 |
if (ps .EQV. .TRUE.) THEN |
576 |
CALL PGBEGIN (0,'image1.ps/ps',1,1) |
577 |
ELSE |
578 |
CALL PGBEGIN (0,'/xwindow',1,1) |
579 |
END IF |
580 |
CALL PGENV (1.,dim/1.,1.,dim/1.,1,-1) |
581 |
CALL PGLABEL('Image des decalages spectraux','', |
582 |
&'DISQUE D''ACCRETION AUTOUR D''UN TROU NOIR') |
583 |
IF (tg .EQV. .TRUE.) THEN |
584 |
DO i=0,25 |
585 |
DO j=0,25 |
586 |
zp(i+25,j+25)=1. |
587 |
END DO |
588 |
END DO |
589 |
CALL PGGRAY(zp,dim,dim,2,dim-1,2,dim-1,zmx,0.,tr) |
590 |
ELSE |
591 |
DO i=1,20 |
592 |
c(i)=0.2*(i-1) |
593 |
END DO |
594 |
CALL PGCONS(zp,dim,dim,1,dim,1,dim,c,12,tr) |
595 |
END IF |
596 |
CALL PGEND |
597 |
|
598 |
c |
599 |
c AFFICHAGE DE L'IMAGE DES FLUX |
600 |
c |
601 |
|
602 |
if (ps .EQV. .TRUE.) THEN |
603 |
CALL PGBEGIN (0,'image2.ps/ps',1,1) |
604 |
ELSE |
605 |
CALL PGBEGIN (0,'/xwindow',1,1) |
606 |
END IF |
607 |
CALL PGENV(1.,dim/1.,1.,dim/1.,1,-1) |
608 |
CALL PGLABEL(' Image des flux','', |
609 |
&'DISQUE D''ACCRETION AUTOUR D''UN TROU NOIR') |
610 |
if (tg) THEN |
611 |
DO i=0,25 |
612 |
DO j=0,25 |
613 |
fp(i+25,j+25)=1. |
614 |
END DO |
615 |
END DO |
616 |
CALL PGGRAY(fp,dim,dim,2,dim-1,2,dim-1,fmx,0.,tr) |
617 |
ELSE |
618 |
DO i=1,8 |
619 |
c(i)=0.0625*2.**(i-1) |
620 |
END DO |
621 |
CALL PGCONS(fp,dim,dim,1,dim,1,dim,c,8,tr) |
622 |
END IF |
623 |
CALL PGEND |
624 |
|
625 |
c |
626 |
c AFFICHAGE DES DONNEES PHYSIQUES |
627 |
c |
628 |
|
629 |
bmp=bmx |
630 |
|
631 |
if (ps .EQV. .TRUE.) THEN |
632 |
CALL PGBEGIN (0,'image3.ps/ps',1,1) |
633 |
ELSE |
634 |
CALL PGBEGIN (0,'/xwindow',1,1) |
635 |
END IF |
636 |
CALL PGENV (-bmp,bmp,-bmp,bmp,1,0) |
637 |
CALL PGLABEL('Rayon de Schwarzschild & |
638 |
&Parametre d''impact critique','', |
639 |
&'DISQUE D''ACCRETION AUTOUR D''UN TROU NOIR') |
640 |
DO i=1,200 |
641 |
x(i)=2.*m*cos(2.*pi*i/200.) |
642 |
y(i)=2.*m*sin(2.*pi*i/200.) |
643 |
END DO |
644 |
CALL PGLINE(200,x,y) |
645 |
DO i=1,200 |
646 |
x(i)=m*SQRT(27.)*cos(2.*pi*i/200.) |
647 |
y(i)=m*SQRT(27.)*sin(2.*pi*i/200.) |
648 |
END DO |
649 |
CALL PGLINE(200,x,y) |
650 |
CALL PGEND |
651 |
|
652 |
c |
653 |
c AFFICHAGE DES CONTOURS DU DISQUE |
654 |
c |
655 |
|
656 |
if (ps .EQV. .TRUE.) THEN |
657 |
CALL PGBEGIN (0,'image4.ps/ps',1,1) |
658 |
ELSE |
659 |
CALL PGBEGIN (0,'/xwindow',1,1) |
660 |
END IF |
661 |
CALL PGENV(-bmp,bmp,-bmp,bmp,1,0) |
662 |
CALL PGLABEL('Limites interieure & |
663 |
&exterieure du disque a l''infini','', |
664 |
&'DISQUE D''ACCRETION AUTOUR D''UN TROU NOIR') |
665 |
DO i=1,200 |
666 |
x(i)=ri*cos(2.*pi*i/200.) |
667 |
y(i)=ri*cos(tho)*sin (2.*pi*i/200.) |
668 |
END DO |
669 |
CALL PGLINE(200,x,y) |
670 |
DO i=1,200 |
671 |
x(i)=re*cos(2.*pi*i/200.) |
672 |
y(i)=re*cos(tho)*sin(2.*pi*i/200.) |
673 |
END DO |
674 |
CALL PGLINE(200,x,y) |
675 |
CALL PGEND |
676 |
|
677 |
c |
678 |
c DETERMINATION DES FLUX ET NOMBRE D'IMPACTS MOYENS SUR LES SPECTRES |
679 |
c |
680 |
|
681 |
fm=0. |
682 |
nm=0. |
683 |
stp=bss/nbr |
684 |
j=0 |
685 |
do i=1,nbr |
686 |
x(i)=i*stp |
687 |
fm=fm+fx(i) |
688 |
nm=nm+1.*nt(i) |
689 |
IF (nt(i).GT.0) j=j+1 |
690 |
END DO |
691 |
fm=fm/j |
692 |
nm=nm/j |
693 |
|
694 |
c |
695 |
c AFFICHAGE DU SPECTRE EN FLUX |
696 |
c |
697 |
|
698 |
DO i=1,nbr |
699 |
y(i)=fx(i)/fm |
700 |
END DO |
701 |
if (ps .EQV. .TRUE.) THEN |
702 |
CALL PGBEGIN (0,'image5.ps/ps',1,1) |
703 |
ELSE |
704 |
CALL PGBEGIN (0,'/xwindow',1,1) |
705 |
END IF |
706 |
CALL PGENV (0.,2.,0.,10.,0,1) |
707 |
CALL PGLABEL('Rapport des frequences recue/emise', |
708 |
&'Flux relatif','SPECTRE DU DISQUE') |
709 |
CALL PGLINE(200,x,y) |
710 |
CALL PGEND |
711 |
|
712 |
c |
713 |
c AFFICHAGE DU SPECTRE EN NOMBRE D'IMPACTS |
714 |
c |
715 |
|
716 |
DO i=1,nbr |
717 |
y(i)=1.*nt(i)/nm |
718 |
END DO |
719 |
if (ps .EQV. .TRUE.) THEN |
720 |
CALL PGBEGIN (0,'image6.ps/ps',1,1) |
721 |
ELSE |
722 |
CALL PGBEGIN (0,'/xwindow',1,1) |
723 |
END IF |
724 |
CALL PGENV(0.,2.,0.,10.,0,1) |
725 |
CALL PGLABEL('Rapport des frequences recue/emise', |
726 |
&' Nombre relatif d''impacts','SPECTRE DU DISQUE') |
727 |
CALL PGLINE(200,x,y) |
728 |
CALL PGEND |
729 |
|
730 |
RETURN |
731 |
END |
732 |
|
733 |
c compilation : g77 -o trou_noir trou_noir.f -lpgplot |
734 |
c -L/usr/local/lib/pgplot -lX11 -L/usr/X11/lib |
735 |
c SORTIE GRAPHIQUE : -> Envoi sur l'ecran : /xwindow |
736 |
c ( dans PGBEGIN ) -> Envoi en format postscript : nom image.ps/ps |
737 |
|
738 |
|
739 |
|
740 |
|
741 |
|