Skip to content

Commit f87f3e8

Browse files
committed
Add radial diffusivity variation for Crank-Nicolson matrix construction
1 parent 3f5fd14 commit f87f3e8

File tree

3 files changed

+39
-11
lines changed

3 files changed

+39
-11
lines changed

src/Fortran_libraries/MHD_src/sph_MHD/const_r_mat_4_scalar_sph.f90

Lines changed: 16 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -121,7 +121,8 @@ end subroutine const_radial_mat_4_press_sph
121121
!
122122
subroutine const_radial_mat_4_scalar_sph(mat_name, coef_advect, &
123123
& dt, sph_params, sph_rj, r_2nd, property, &
124-
& sph_bc, bcs_S, fdm2_center, g_sph_rj, band_s_evo)
124+
& sph_bc, bcs_S, fdm2_center, g_sph_rj, k_ratio, dk_dr, &
125+
& band_s_evo)
125126
!
126127
use m_ludcmp_3band
127128
use center_sph_matrices
@@ -139,6 +140,8 @@ subroutine const_radial_mat_4_scalar_sph(mat_name, coef_advect, &
139140
real(kind = kreal), intent(in) :: g_sph_rj(sph_rj%nidx_rj(2),13)
140141
real(kind = kreal), intent(in) :: dt
141142
real(kind = kreal), intent(in) :: coef_advect
143+
real(kind = kreal), intent(in) :: k_ratio(0:sph_rj%nidx_rj(1))
144+
real(kind = kreal), intent(in) :: dk_dr(0:sph_rj%nidx_rj(1))
142145
character(len=kchara), intent(in) :: mat_name
143146
!
144147
type(band_matrices_type), intent(inout) :: band_s_evo
@@ -177,10 +180,18 @@ subroutine const_radial_mat_4_scalar_sph(mat_name, coef_advect, &
177180
end if
178181
!
179182
!
180-
call add_scalar_poisson_mat_sph &
181-
& (sph_rj%nidx_rj(1), sph_rj%nidx_rj(2), sph_rj%ar_1d_rj, &
182-
& g_sph_rj, sph_bc%kr_in, sph_bc%kr_out, r_coef(1), &
183-
& r_2nd%fdm(1)%dmat, r_2nd%fdm(2)%dmat, band_s_evo%mat)
183+
if(property%flag_val_diffuse) then
184+
call add_scalar_r_diffuse_mat_sph &
185+
& (sph_rj%nidx_rj(1), sph_rj%nidx_rj(2), sph_rj%ar_1d_rj, &
186+
& g_sph_rj, sph_bc%kr_in, sph_bc%kr_out, &
187+
& r_coef(1), k_ratio(1), dk_dr(1), &
188+
& r_2nd%fdm(1)%dmat, r_2nd%fdm(2)%dmat, band_s_evo%mat)
189+
else
190+
call add_scalar_poisson_mat_sph &
191+
& (sph_rj%nidx_rj(1), sph_rj%nidx_rj(2), sph_rj%ar_1d_rj, &
192+
& g_sph_rj, sph_bc%kr_in, sph_bc%kr_out, r_coef(1), &
193+
& r_2nd%fdm(1)%dmat, r_2nd%fdm(2)%dmat, band_s_evo%mat)
194+
end if
184195
!
185196
call sel_radial_mat_scalar_bc_sph(sph_rj, sph_bc, bcs_S, &
186197
& fdm2_center, g_sph_rj, r_coef, band_s_evo)

src/Fortran_libraries/MHD_src/sph_MHD/const_radial_mat_4_sph.f90

Lines changed: 22 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -8,14 +8,15 @@
88
!!
99
!!@verbatim
1010
!! subroutine const_radial_mat_sph_mhd(dt, MHD_prop, sph_MHD_bc, &
11-
!! & sph, r_2nd, leg, sph_MHD_mat)
11+
!! & sph, r_2nd, leg, refs, sph_MHD_mat)
1212
!! subroutine const_radial_mat_sph_snap(MHD_prop, sph_MHD_bc, &
1313
!! & sph_rj, r_2nd, leg, sph_MHD_mat)
1414
!! type(MHD_evolution_param), intent(in) :: MHD_prop
1515
!! type(sph_MHD_boundary_data), intent(in) :: sph_MHD_bc
1616
!! type(sph_grids), intent(in) :: sph
1717
!! type(fdm_matrices), intent(in) :: r_2nd
1818
!! type(legendre_4_sph_trans), intent(in) :: leg
19+
!! type(radial_reference_field), intent(in) :: refs
1920
!! type(MHD_radial_matrices), intent(inout) :: sph_MHD_mat
2021
!!@endverbatim
2122
!
@@ -33,7 +34,10 @@ module const_radial_mat_4_sph
3334
use t_spheric_rj_data
3435
use t_fdm_coefs
3536
use t_schmidt_poly_on_rtm
37+
use t_diffusion_term_labels
3638
use t_physical_property
39+
use t_phys_data
40+
use t_radial_reference_field
3741
use t_boundary_data_sph_MHD
3842
use t_boundary_params_sph_MHD
3943
use t_radial_matrices_sph_MHD
@@ -66,13 +70,14 @@ module const_radial_mat_4_sph
6670
! -----------------------------------------------------------------------
6771
!
6872
subroutine const_radial_mat_sph_mhd(dt, MHD_prop, sph_MHD_bc, &
69-
& sph, r_2nd, leg, sph_MHD_mat)
73+
& sph, r_2nd, leg, refs, sph_MHD_mat)
7074
!
7175
type(MHD_evolution_param), intent(in) :: MHD_prop
7276
type(sph_MHD_boundary_data), intent(in) :: sph_MHD_bc
7377
type(sph_grids), intent(in) :: sph
7478
type(fdm_matrices), intent(in) :: r_2nd
7579
type(legendre_4_sph_trans), intent(in) :: leg
80+
type(radial_reference_field), intent(in) :: refs
7681
!
7782
real(kind = kreal), intent(in) :: dt
7883
!
@@ -83,7 +88,9 @@ subroutine const_radial_mat_sph_mhd(dt, MHD_prop, sph_MHD_bc, &
8388
id_file = 50 + my_rank
8489
call const_radial_matrices_sph &
8590
& (id_file, dt, sph%sph_params, sph%sph_rj, r_2nd, &
86-
& MHD_prop, sph_MHD_bc, leg%g_sph_rj, sph_MHD_mat)
91+
& MHD_prop, sph_MHD_bc, leg%g_sph_rj, &
92+
& refs%iref_diffusivity, refs%iref_grad_diffusivity, &
93+
& refs%ref_field, sph_MHD_mat)
8794
!
8895
call const_radial_mat_sph_w_center &
8996
& (dt, sph%sph_rj, MHD_prop, sph_MHD_bc, sph_MHD_mat)
@@ -136,8 +143,10 @@ end subroutine const_radial_mat_sph_snap
136143
! -----------------------------------------------------------------------
137144
!
138145
subroutine const_radial_matrices_sph &
139-
& (id_file, dt, sph_params, sph_rj, r_2nd, MHD_prop, &
140-
& sph_MHD_bc, g_sph_rj, sph_MHD_mat)
146+
& (id_file, dt, sph_params, sph_rj, &
147+
& r_2nd, MHD_prop, sph_MHD_bc, g_sph_rj, &
148+
& iref_diffusivity, iref_grad_diffusivity, ref_field, &
149+
& sph_MHD_mat)
141150
!
142151
use const_r_mat_4_scalar_sph
143152
use const_r_mat_4_vector_sph
@@ -149,6 +158,10 @@ subroutine const_radial_matrices_sph &
149158
type(fdm_matrices), intent(in) :: r_2nd
150159
type(MHD_evolution_param), intent(in) :: MHD_prop
151160
type(sph_MHD_boundary_data), intent(in) :: sph_MHD_bc
161+
!
162+
type(diffusivity_adress), intent(in) :: iref_diffusivity
163+
type(diffusivity_adress), intent(in) :: iref_grad_diffusivity
164+
type(phys_data), intent(in) :: ref_field
152165
!
153166
real(kind = kreal), intent(in) :: dt
154167
real(kind = kreal), intent(in) :: g_sph_rj(sph_rj%nidx_rj(2),13)
@@ -223,6 +236,8 @@ subroutine const_radial_matrices_sph &
223236
& sph_params, sph_rj, r_2nd, MHD_prop%ht_prop, &
224237
& sph_MHD_bc%sph_bc_T, sph_MHD_bc%bcs_T, &
225238
& sph_MHD_bc%fdm2_center, g_sph_rj, &
239+
& ref_field%d_fld(1,iref_diffusivity%i_T_diffusivity), &
240+
& ref_field%d_fld(1,iref_grad_diffusivity%i_T_diffusivity), &
226241
& sph_MHD_mat%band_temp_evo)
227242
if(i_debug .eq. iflag_full_msg) then
228243
call check_radial_band_mat(id_file, sph_rj, &
@@ -236,6 +251,8 @@ subroutine const_radial_matrices_sph &
236251
& sph_params, sph_rj, r_2nd, MHD_prop%cp_prop, &
237252
& sph_MHD_bc%sph_bc_C, sph_MHD_bc%bcs_C, &
238253
& sph_MHD_bc%fdm2_center, g_sph_rj, &
254+
& ref_field%d_fld(1,iref_diffusivity%i_T_diffusivity), &
255+
& ref_field%d_fld(1,iref_grad_diffusivity%i_T_diffusivity), &
239256
& sph_MHD_mat%band_comp_evo)
240257
if(i_debug .eq. iflag_full_msg) then
241258
call check_radial_band_mat(id_file, sph_rj, &

src/programs/SPH_MHD/SPH_analyzer_MHD.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -144,7 +144,7 @@ subroutine SPH_initialize_MHD(MHD_files, SPH_model, FEM_dat, &
144144
call const_radial_mat_sph_mhd &
145145
& (MHD_step%time_d%dt, SPH_model%MHD_prop, SPH_model%sph_MHD_bc, &
146146
& SPH_MHD%sph, SPH_WK%r_2nd, SPH_WK%trans_p%leg, &
147-
& SPH_WK%MHD_mats)
147+
& SPH_model%refs, SPH_WK%MHD_mats)
148148
!*
149149
!* obtain linear terms for starting
150150
!*

0 commit comments

Comments
 (0)