12 integer,
private,
parameter :: rho_ = 1
18 character(len=*),
intent(in) :: files(:)
24 open(
unitpar, file=trim(files(n)), status=
"old")
25 read(
unitpar, rotating_frame_list,
end=111)
48 integer,
intent(in) :: ixI^L, ixO^L
49 double precision,
intent(in) :: qdt, dtfactor,x(ixI^S,1:ndim)
50 double precision,
intent(in) :: wCT(ixI^S,1:nw)
51 double precision,
intent(inout) :: w(ixI^S,1:nw)
55 double precision :: rotating_terms(ixI^S), frame_omega(ixI^S)
56 double precision :: work(ixI^S)
62 rotating_terms(ixo^s) =
omega_frame**2 * x(ixo^s,
r_) * wct(ixo^s,iw_rho)
65 rotating_terms(ixo^s) = rotating_terms(ixo^s) + 2.d0 *
omega_frame *wct(ixo^s,iw_mom(
phi_))
69 w(ixo^s, iw_mom(
r_)) = w(ixo^s, iw_mom(
r_)) +
block%dt(ixo^s)*dtfactor * rotating_terms(ixo^s)
71 w(ixo^s, iw_mom(
r_)) = w(ixo^s, iw_mom(
r_)) + qdt * rotating_terms(ixo^s)
75 rotating_terms(ixo^s) = - 2.0d0*
omega_frame * wct(ixo^s,iw_mom(
r_))
77 w(ixo^s, iw_mom(
phi_)) = w(ixo^s, iw_mom(
phi_)) +
block%dt(ixo^s)*dtfactor * rotating_terms(ixo^s)
79 w(ixo^s, iw_mom(
phi_)) = w(ixo^s, iw_mom(
phi_)) + qdt * rotating_terms(ixo^s)
86 w(ixo^s, iw_e) = w(ixo^s, iw_e) +
block%dt(ixo^s) *dtfactor *
omega_frame**2 * x(ixo^s,
r_) * wct(ixo^s,iw_mom(
r_))
88 w(ixo^s, iw_e) = w(ixo^s, iw_e) + qdt *
omega_frame**2 * x(ixo^s,
r_) * wct(ixo^s,iw_mom(
r_))
93 frame_omega(ixo^s) =
omega_frame{^nooned * dsin(x(ixo^s,2))}
96 rotating_terms(ixo^s) = frame_omega(ixo^s)**2 * x(ixo^s,
r_) * wct(ixo^s,iw_rho)
99 rotating_terms(ixo^s) = rotating_terms(ixo^s) + &
100 2.d0 * frame_omega(ixo^s) * wct(ixo^s,iw_mom(
phi_))
103 w(ixo^s, iw_mom(
r_)) = w(ixo^s, iw_mom(
r_)) +
block%dt(ixo^s)*dtfactor * rotating_terms(ixo^s)
105 w(ixo^s, iw_mom(
r_)) = w(ixo^s, iw_mom(
r_)) + qdt * rotating_terms(ixo^s)
110 w(ixo^s, iw_mom(2)) = w(ixo^s, iw_mom(2)) +
block%dt(ixo^s)*dtfactor * rotating_terms(ixo^s)/ tan(x(ixo^s, 2))
112 w(ixo^s, iw_mom(2)) = w(ixo^s, iw_mom(2)) + qdt * rotating_terms(ixo^s)/ tan(x(ixo^s, 2))
116 rotating_terms(ixo^s) = -2.d0*frame_omega(ixo^s)* wct(ixo^s, iw_mom(
r_))&
117 - 2.d0*wct(ixo^s, iw_mom(2)) * frame_omega(ixo^s)/ tan(x(ixo^s, 2))
119 w(ixo^s, iw_mom(3)) = w(ixo^s, iw_mom(3)) +
block%dt(ixo^s)*dtfactor * rotating_terms(ixo^s)
121 w(ixo^s, iw_mom(3)) = w(ixo^s, iw_mom(3)) + qdt * rotating_terms(ixo^s)
128 work(ixo^s) = frame_omega(ixo^s)**2 * x(ixo^s,
r_) * wct(ixo^s,iw_mom(
r_))
130 work(ixo^s) = work(ixo^s) + frame_omega(ixo^s)**2 * x(ixo^s,
r_) * wct(ixo^s, iw_mom(2))/ tan(x(ixo^s, 2))
133 w(ixo^s, iw_e) = w(ixo^s, iw_e) +
block%dt(ixo^s)*dtfactor* work(ixo^s)
135 w(ixo^s, iw_e) = w(ixo^s, iw_e) + qdt * work(ixo^s)
140 call mpistop(
"Rotating frame not implemented in this geometry")
subroutine, public mpistop(message)
Exit MPI-AMRVAC with an error message.
Module with geometry-related routines (e.g., divergence, curl)
integer, parameter spherical
integer, parameter cylindrical
This module contains definitions of global parameters and variables and some generic functions/subrou...
type(state), pointer block
Block pointer for using one block and its previous state.
integer, parameter unitpar
file handle for IO
character(len=std_len), dimension(:), allocatable par_files
Which par files are used as input.
logical local_timestep
each cell has its own timestep or not
integer r_
Indices for cylindrical coordinates FOR TESTS, negative value when not used:
This module defines the procedures of a physics module. It contains function pointers for the various...
logical phys_internal_e
Solve internal energy instead of total energy.
logical phys_energy
Solve energy equation or not.
Module for including rotating frame in (magneto)hydrodynamics simulations The rotation vector is assu...
subroutine rotating_frame_params_read(files)
Read this module's parameters from a file.
subroutine rotating_frame_add_source(qdt, dtfactor, ixIL, ixOL, wCT, w, x)
w[iw]=w[iw]+qdt*S[wCT,qtC,x] where S is the source based on wCT within ixO
double precision omega_frame
Rotation frequency of the frame.
subroutine rotating_frame_init()
Initialize the module.
Module with all the methods that users can customize in AMRVAC.