2D simulation of a geometrically thin, self-gravitating accretion disk around a supermassive black hole in polar geometry with logarithmic radial spacing. The standard setup solves the non-isothermal inviscid Euler equations with thin-disk gray cooling (see sources_diskcooling_mod::lambda_gray ). Gravitational forces account for the central point mass as well as self-gravity of the disk.
80 REAL,
PARAMETER :: GN = 6.67384e-11
81 REAL,
PARAMETER :: YEAR = 3.15576e+7
82 REAL,
PARAMETER :: PARSEC = 3.0857e+16
83 REAL,
PARAMETER :: AU = 1.49598e+11
84 REAL,
PARAMETER :: MSUN = 1.989e+30
85 REAL,
PARAMETER :: RG = 8.31
87 REAL,
PARAMETER :: SIMTIME = 1.0e+4*year
88 REAL,
PARAMETER :: MBH = 1.0e+7*msun
89 REAL,
PARAMETER :: MRATIO = 0.1
90 REAL,
PARAMETER :: MDISK = mratio*mbh
91 REAL,
PARAMETER :: TEMP = 100.0
92 REAL,
PARAMETER :: NOISE = 0.3
94 INTEGER,
PARAMETER :: PHYS = euler
95 REAL,
PARAMETER :: MU = 6.02e-4
96 REAL,
PARAMETER :: GAMMA = 1.4
97 REAL,
PARAMETER :: BETA_VIS = 1.0e-3
99 REAL,
PARAMETER :: RMIN = 5.0e-2 * parsec
100 REAL,
PARAMETER :: RMAX = 1.e+0 * parsec
101 REAL,
PARAMETER :: RGEO = 1.0 * parsec
102 INTEGER,
PARAMETER :: MGEO = logcylindrical
103 INTEGER,
PARAMETER :: XRES = 64
104 INTEGER,
PARAMETER :: YRES = 128
105 INTEGER,
PARAMETER :: ZRES = 1
107 INTEGER,
PARAMETER :: ONUM = 100
108 CHARACTER(LEN=256),
PARAMETER :: &
109 OFNAME =
'markward', &
112 CLASS(fosite),
ALLOCATABLE :: Sim
118 CALL asl_library_initialize()
121 CALL sim%InitFosite()
124 CALL initdata(sim%Timedisc,sim%Mesh,sim%Physics,sim%Fluxes,sim%Sources)
129 CALL asl_library_finalize()
138 TYPE(Dict_TYP),
POINTER :: config
141 TYPE(Dict_TYP),
POINTER :: mesh,boundary,timedisc,datafile,&
142 sources,fluxes,grav,physics,&
147 "output/bccsound" / 1, &
155 "variables" / primitive, &
156 "limiter" / vanleer, &
160 "meshtype" / midpoint, &
165 "xmin" / log(rmin/parsec), &
166 "xmax" / log(rmax/parsec), &
174 "decomposition" / (/-1,1,1/), &
175 "output/volume" / 1 )
178 "western" / custom, &
179 "eastern" / custom, &
180 "southern" / periodic, &
181 "northern" / periodic, &
182 "bottomer" / reflecting, &
183 "topper" / reflecting)
189 "output/height" / 1, &
190 "self/gtype" / spectral, &
192 "pmass/gtype" / pointmass, &
193 "pmass/potential" / newton, &
194 "pmass/mass" / mbh, &
195 "pmass/outbound" / 1)
199 "stype" / disk_cooling, &
204 "rhomin" / 1.0e-30, &
209 "stype" / viscosity, &
211 "dynconst" / beta_vis, &
212 "output/stress" / 1, &
213 "output/dynvis" / 1, &
214 "output/kinvis" / 1, &
219 "diskcooling" / cooling, &
226 "tol_rel" / 1.0e-3, &
228 "stoptime" / simtime, &
229 "dtlimit" / 1.0e-4, &
232 "maxiter" / 2000000000)
237 CALL setattr(timedisc,
"tol_abs", (/1.0e-3, 1.0e-1, 1.0e-01, 1.0e+10/))
238 CALL setattr(timedisc,
"output/xmomentum", 0)
239 CALL setattr(timedisc,
"output/ymomentum", 0)
240 CALL setattr(timedisc,
"output/energy", 0)
241 CALL setattr(timedisc,
"output/rhs", 0)
242 CALL setattr(timedisc,
"output/external_sources", 0)
244 CALL error(sim,
"MakeConfig",
"Physics model not supported.")
249 "fileformat" / vtk, &
250 "filename" /
"mestel", &
255 "physics" / physics, &
258 "boundary" / boundary, &
259 "sources" / sources, &
260 "timedisc" / timedisc, &
261 "datafile" / datafile)
266 SUBROUTINE initdata(Timedisc,Mesh,Physics,Fluxes,Sources)
270 CLASS(timedisc_base),
INTENT(INOUT) :: Timedisc
271 CLASS(mesh_base),
INTENT(IN) :: Mesh
272 CLASS(physics_base),
INTENT(INOUT) :: Physics
273 CLASS(fluxes_base),
INTENT(INOUT) :: Fluxes
274 CLASS(sources_base),
POINTER :: Sources
277 CLASS(sources_base),
POINTER :: sp
278 CLASS(sources_gravity),
POINTER :: gp
279 CLASS(marray_base),
ALLOCATABLE :: rands,Sigma
284 CHARACTER(LEN=20) :: mdisk_str
289 ALLOCATE(rands,sigma)
293 IF (
ASSOCIATED(sp).EQV..false.)
RETURN 295 CLASS IS(sources_gravity)
301 IF (.NOT.
ASSOCIATED(sp))
CALL physics%Error(
"mestel::InitData",
"no gravity term initialized")
304 rands = marray_base()
307 CALL random_number(rands%data1d)
309 CALL asl_random_create(rng, asl_randommethod_mt19937_64)
310 CALL asl_random_distribute_uniform(rng)
311 n = (mesh%IGMAX-mesh%IGMIN+1)*(mesh%JGMAX-mesh%JGMIN+1)*(mesh%KGMAX-mesh%KGMIN+1)
312 CALL asl_random_generate_d(rng, n, rands%data1d)
313 CALL asl_random_destroy(rng)
315 rands%data1d(:) = rands%data1d(:) * noise * 2.0 + (1.0 - noise)
318 sigma = marray_base()
319 sigma%data1d(:) = rands%data1d(:) * rmin/mesh%radius%data2d(:,2)
322 mass = sum(mesh%volume%data1d(:)*sigma%data1d(:),mask=mesh%without_ghost_zones%mask1d(:))
324 CALL mpi_allreduce(mpi_in_place,mass,1,default_mpi_real,mpi_sum, &
325 mesh%comm_cart,ierror)
329 SELECT TYPE(bwest => timedisc%Boundary%boundary(west)%p)
330 CLASS IS (boundary_custom)
331 CALL bwest%SetCustomBoundaries(mesh,physics, &
332 (/custom_nograd,custom_outflow,custom_kepler,custom_nograd/))
336 SELECT TYPE(beast => timedisc%Boundary%boundary(east)%p)
337 CLASS IS (boundary_custom)
338 CALL beast%SetCustomBoundaries(mesh,physics, &
339 (/custom_reflect,custom_reflect,custom_logexpol,custom_reflect/))
342 SELECT TYPE (pvar => timedisc%pvar)
345 pvar%density%data1d(:) = sigma%data1d(:) * mdisk / mass
347 CALL gp%UpdateGravity(mesh,physics,fluxes,pvar,0.0,0.0)
350 pvar%velocity%data4d(:,:,:,1:physics%VDIM) = &
351 timedisc%GetCentrifugalVelocity(mesh,physics,fluxes,sources,(/0.,0.,1./),gp%accel%data4d)
354 IF (mesh%OMEGA.GT.0.0) &
355 pvar%velocity%data2d(:,2) = pvar%velocity%data2d(:,2) - mesh%OMEGA*mesh%radius%data2d(:,2)
357 pvar%pressure%data1d(:) = physics%constants%RG/physics%MU * temp * pvar%density%data1d(:)
359 CALL physics%Error(
"mestel::InitData",
"unsupported state vector")
362 IF (mesh%FARGO.EQ.2) &
363 timedisc%w(:,:) = sqrt(physics%constants%GN*(mbh/mesh%radius%bcenter(:,mesh%JMIN,:)))
365 CALL physics%Convert2Conservative(timedisc%pvar,timedisc%cvar)
368 WRITE (mdisk_str,
'(ES8.2)') mdisk/msun
369 CALL mesh%Info(
" DATA-----> initial condition: Mestel's disk")
370 CALL mesh%Info(
" disk mass: " // trim(mdisk_str) //
" M_sun")
374 DEALLOCATE(rands,sigma)
380 CLASS(physics_base),
INTENT(IN) :: Physics
381 INTEGER :: i, n, clock
382 INTEGER,
DIMENSION(:),
ALLOCATABLE :: seed
386 CALL random_seed(
size = n)
388 CALL system_clock(count=clock)
389 seed = clock + 37 * (/ (i - 1, i = 1, n) /)
391 seed = seed + physics%GetRank()
393 CALL random_seed(put = seed)