-
Notifications
You must be signed in to change notification settings - Fork 10
/
Copy pathgravity.f90
123 lines (91 loc) · 3.08 KB
/
gravity.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
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
subroutine gravity(U, g)
! compute the cell-centered gravitational acceleration
use datatypes_module
use grid_module
use variables_module
use params_module, only : grav, gravity_monopole
use constants_module
implicit none
type(gridvar_t), intent(in) :: U
type(gridvar_t), intent(inout) :: g
type(grid_t) :: grid
integer :: i, ic, ip, ir
real (kind=dp_t) :: M_enclosed, g_edge_lo, g_edge_hi
grid = U%grid
if (gravity_monopole == 0) then
g%data(:,1) = grav
else
! compute the acceleration on edges and average to the center.
! This is the same as doing the potential at centers and doing
! a centered difference
M_enclosed = ZERO
g_edge_lo = ZERO
do i = grid%lo, grid%hi
! mass enclosed in this zone
M_enclosed = M_enclosed + FOURTHIRDS*pi* &
(grid%xr(i)**2 + grid%xl(i)**2 + grid%xl(i)*grid%xr(i)) * &
grid%dx * &
U%data(i,iudens)
! gravitational acceleration on this right edge
g_edge_hi = -G_newton*M_enclosed/grid%xr(i)**2
! cell-centered gravity
g%data(i,1) = HALF*(g_edge_lo + g_edge_hi)
g_edge_lo = g_edge_hi
enddo
endif
! fill boundary conditions -- this is necessary for the interface
! state construction
! Note: at the moment, we cannot use the bc routines here, since they
! are coded specifically for hydro, so we'll hack something in. This
! needs to be improved.
! lower boundary (-x)
select case (U%grid%xlboundary)
case ("reflect")
! ir is the index that corresponds to the reflected ghostcell
ir = U%grid%lo
do i = U%grid%lo-1, U%grid%lo-U%grid%ng, -1
! odd-reflect the acceleration
g%data(i,1) = -g%data(ir,1)
ir = ir + 1
enddo
case ("outflow", "hse", "user")
do i = U%grid%lo-1, U%grid%lo-U%grid%ng, -1
! give all quantities a zero-gradient
g%data(i,1) = g%data(i+1,1)
enddo
case ("periodic")
ip = U%grid%hi
do i = U%grid%lo-1, U%grid%lo-U%grid%ng, -1
g%data(i,1) = g%data(ip,1)
ip = ip - 1
enddo
case default
print *, "ERROR: xlboundary not valid"
stop
end select
! upper boundary (+x)
select case (U%grid%xrboundary)
case ("reflect")
! ir is the index that corresponds to the reflected ghostcell
ir = U%grid%hi
do i = U%grid%hi+1, U%grid%hi+U%grid%ng
! odd reflect the acceleration
g%data(i,1) = -g%data(ir,1)
ir = ir - 1
enddo
case ("outflow", "hse", "user", "diode")
do i = U%grid%hi+1, U%grid%hi+U%grid%ng
! give all quantities a zero-gradient
g%data(i,1) = g%data(i-1,1)
enddo
case ("periodic")
ip = U%grid%lo
do i = U%grid%hi+1, U%grid%hi+U%grid%ng
g%data(i,1) = g%data(ip,1)
ip = ip + 1
enddo
case default
print *, "ERROR: xrboundary not valid"
stop
end select
end subroutine gravity