This repository has been archived by the owner on Aug 24, 2024. It is now read-only.
-
Notifications
You must be signed in to change notification settings - Fork 0
/
EOSTABLE.f90
103 lines (74 loc) · 2.74 KB
/
EOSTABLE.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
! This Subroutine generate the EOS table that used for !
! solving the initial star according to the user input !
! which assume a ideal degenerate fermi gas EOS !
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
SUBROUTINE EOSTABLE_NM
USE DEFINITION
IMPLICIT NONE
! The dummy variable for density and pressure !
REAL(DP) :: den, pree1, pree2
! Integer Parameter !
INTEGER :: i, j, start, end
! The width of the table for each order of magnitue of density !
INTEGER :: width
! Initialize the width !
width = 3000
! We initialize the starting and ending order of magnitude for density !
start = -25
end = -2
! We open the EOS table for input !
OPEN (UNIT = 100, FILE = 'EOS_Table2.eos', STATUS = 'REPLACE')
! We do the loop the get the pressure of Fermi Gas For each density input !
DO i = start, end
DO j = 0, width - 1
! We initialize the density input !
den = (10.0E0_DP ** (DBLE(i+1)) - 10.0E0_DP ** (DBLE(i))) * DBLE(j) / DBLE(width) + 10.0E0_DP ** (DBLE(i))
! We get the pressure !
CALL GETRHO_EOSRTOP (pree2, den, gs2, mb2, me2, ye2, 2)
! We print the pressure and density to EOS table !
WRITE (100, *) pree2, den
END DO
END DO
! We assign the eosline number !
eoslineno2 = width * (end - start + 1)
! We close the file !
close(100)
END SUBROUTINE
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
! This Subroutine generate the EOS table that used for !
! solving the initial star according to the user input !
! which assume a ideal degenerate fermi gas EOS !
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
SUBROUTINE EOSTABLE_DM
USE DEFINITION
IMPLICIT NONE
! The dummy variable for density and pressure !
REAL(DP) :: den, pree1, pree2
! Integer Parameter !
INTEGER :: i, j, start, end
! The width of the table for each order of magnitue of density !
INTEGER :: width
! Initialize the width !
width = 3000
! We initialize the starting and ending order of magnitude for density !
start = -25
end = -2
! We open the EOS table for input !
OPEN (UNIT = 99, FILE = 'EOS_Table1.eos', STATUS = 'REPLACE')
! We do the loop the get the pressure of Fermi Gas For each density input !
DO i = start, end
DO j = 0, width - 1
! We initialize the density input !
den = (10.0E0_DP ** (DBLE(i+1)) - 10.0E0_DP ** (DBLE(i))) * DBLE(j) / DBLE(width) + 10.0E0_DP ** (DBLE(i))
! We get the pressure !
CALL GETRHO_EOSRTOP (pree1, den, gs1, mb1, me1, ye1, 1)
! We print the pressure and density to EOS table !
WRITE (99, *) pree1, den
END DO
END DO
! We assign the eosline number !
eoslineno1 = width * (end - start + 1)
! We close the file !
close(99)
END SUBROUTINE