[cig-commits] [commit] Hiro_latest: Update definitions of boundary conditions (cbdeb45)

cig_noreply at geodynamics.org cig_noreply at geodynamics.org
Mon Nov 18 16:21:10 PST 2013


Repository : ssh://geoshell/calypso

On branch  : Hiro_latest
Link       : https://github.com/geodynamics/calypso/compare/93e9f8f974c7a247c8f02e54ec18de063f86c8fb...3c548304673360ddedd7d68c8095b3fb74a2b9ce

>---------------------------------------------------------------

commit cbdeb4509e63191e05c319de57bdfb2b559da884
Author: Hiroaki Matsui <h_kemono at mac.com>
Date:   Wed Oct 23 14:47:34 2013 -0700

    Update definitions of boundary conditions


>---------------------------------------------------------------

cbdeb4509e63191e05c319de57bdfb2b559da884
 .../MHD_src/IO/m_boundary_condition_IDs.f90        |   4 +-
 .../MHD_src/IO/set_control_4_composition.f90       |  15 +-
 .../MHD_src/IO/set_control_4_magne.f90             |  26 +-
 .../MHD_src/IO/set_control_4_press.f90             |  21 +-
 .../MHD_src/IO/set_control_4_temp.f90              |  20 +-
 .../MHD_src/IO/set_control_4_velo.f90              |  50 ++--
 .../MHD_src/IO/set_node_group_types.f90            | 118 +++++++++
 .../MHD_src/IO/set_surface_group_types.f90         |   9 +-
 .../MHD_src/sph_MHD/m_control_params_sph_MHD.f90   |   6 +-
 .../MHD_src/sph_MHD/set_bc_flag_sph_velo.f90       |  27 +-
 .../MHD_src/sph_MHD/set_bc_sph_mhd.f90             | 280 +++------------------
 .../{set_bc_sph_mhd.f90 => set_bc_sph_scalars.f90} | 123 ++-------
 12 files changed, 259 insertions(+), 440 deletions(-)

diff --git a/src/Fortran_libraries/MHD_src/IO/m_boundary_condition_IDs.f90 b/src/Fortran_libraries/MHD_src/IO/m_boundary_condition_IDs.f90
index fe32e82..f76fe53 100644
--- a/src/Fortran_libraries/MHD_src/IO/m_boundary_condition_IDs.f90
+++ b/src/Fortran_libraries/MHD_src/IO/m_boundary_condition_IDs.f90
@@ -58,14 +58,14 @@
 !>      non slip boundary
       integer(kind = kint), parameter :: iflag_non_slip_sph =    200
 !>      eliminate radial flow
-      integer(kind = kint), parameter :: iflag_no_vr =           200
+      integer(kind = kint), parameter :: iflag_no_vr =           201
 !>      rotatable inner core
       integer(kind = kint), parameter :: iflag_rotatable_icore = 301
 !
 !>      insulated magnetic boundary
       integer(kind = kint), parameter :: iflag_insulator =       100
 !>      boundary to connect center field
-      integer(kind = kint), parameter :: iflag_sph_2_center =    200
+      integer(kind = kint), parameter :: iflag_sph_2_center =    501
 !
 !>      pseudo vacuum boundary
       integer(kind = kint), parameter :: iflag_pseudo_vacuum =   400
diff --git a/src/Fortran_libraries/MHD_src/IO/set_control_4_composition.f90 b/src/Fortran_libraries/MHD_src/IO/set_control_4_composition.f90
index cc7bd55..13be94b 100644
--- a/src/Fortran_libraries/MHD_src/IO/set_control_4_composition.f90
+++ b/src/Fortran_libraries/MHD_src/IO/set_control_4_composition.f90
@@ -34,6 +34,7 @@
       use m_node_group
       use m_bc_data_list
       use m_surf_data_list
+      use set_node_group_types
       use set_surface_group_types
 !
       integer (kind = kint) :: i
@@ -60,12 +61,13 @@
         light_nod%bc_magnitude = bc_composit_magnitude_ctl
 !
         do i = 1, light_nod%num_bc
-          if(bc_composit_type_ctl(i) .eq. 'fixed') then
-            light_nod%ibc_type(i) =  iflag_bc_fix_s
-          else if(bc_composit_type_ctl(i) .eq. 'file') then
-            light_nod%ibc_type(i) = -iflag_bc_fix_s
-          else if(bc_composit_type_ctl(i) .eq. 'fixed_flux') then
+          call set_nod_group_types_scalar(bc_composit_type_ctl(i),      &
+     &        light_nod%ibc_type(i))
+!
+          if(bc_composit_type_ctl(i) .eq. 'fixed_flux') then
             light_nod%ibc_type(i) =  iflag_bc_fix_flux
+          else if(bc_composit_type_ctl(i) .eq. 'sph_to_center') then
+            light_nod%ibc_type(i) =  iflag_sph_2_center
           end if
         end do
 !
@@ -95,6 +97,9 @@
         do i = 1, light_surf%num_bc
           call set_surf_group_types_scalar(bc_grad_ds_type_ctl(i),      &
      &        light_surf%ibc_type(i) )
+!
+          if(bc_grad_ds_type_ctl(i) .eq. 'sph_to_center') then
+            light_surf%ibc_type(i) =  iflag_sph_2_center
         end do
 !
         call deallocate_sf_dscalar_ctl
diff --git a/src/Fortran_libraries/MHD_src/IO/set_control_4_magne.f90 b/src/Fortran_libraries/MHD_src/IO/set_control_4_magne.f90
index eee8dfa..5ed2b2f 100644
--- a/src/Fortran_libraries/MHD_src/IO/set_control_4_magne.f90
+++ b/src/Fortran_libraries/MHD_src/IO/set_control_4_magne.f90
@@ -34,6 +34,7 @@
       use m_node_group
       use m_bc_data_list
       use m_surf_data_list
+      use set_node_group_types
       use set_surface_group_types
 !
       character(len=kchara) :: tmpchara
@@ -61,20 +62,13 @@
         magne_nod%bc_magnitude = bc_b_magnitude_ctl
 !
         do i = 1, magne_nod%num_bc
+         call set_nod_group_types_vector(bc_b_type_ctl(i),              &
+     &       magne_nod%ibc_type(i))
+         call set_nod_group_types_sgs_vect(bc_b_type_ctl(i),            &
+     &       magne_nod%ibc_type(i))
+!
           tmpchara = bc_b_type_ctl(i)
-          if ( tmpchara .eq. 'fix_x' ) then
-            magne_nod%ibc_type(i) = iflag_bc_fixed + 1
-          else if ( tmpchara .eq. 'fix_y' ) then
-            magne_nod%ibc_type(i) = iflag_bc_fixed + 2
-          else if ( tmpchara .eq. 'fix_z' ) then
-            magne_nod%ibc_type(i) = iflag_bc_fixed + 3
-          else if ( tmpchara .eq. 'file_x' ) then
-            magne_nod%ibc_type(i) = iflag_bc_fixed - 1
-          else if ( tmpchara .eq. 'file_y' ) then
-            magne_nod%ibc_type(i) = iflag_bc_fixed - 2
-          else if ( tmpchara .eq. 'file_z' ) then
-            magne_nod%ibc_type(i) = iflag_bc_fixed - 3
-          else if ( tmpchara .eq. 'insulator' ) then
+          if ( tmpchara .eq. 'insulator' ) then
             magne_nod%ibc_type(i) = iflag_insulator
           else if ( tmpchara .eq. 'sph_to_center' ) then
             magne_nod%ibc_type(i) = iflag_sph_2_center
@@ -82,12 +76,6 @@
             magne_nod%ibc_type(i) = iflag_pseudo_vacuum
 !          else if ( tmpchara .eq. 'sph' ) then
 !            magne_nod%ibc_type(i) = 999
-          else if ( tmpchara .eq. 'sgs_x' ) then
-            magne_nod%ibc_type(i) = iflag_bc_sgs + 1
-          else if ( tmpchara .eq. 'sgs_y' ) then
-            magne_nod%ibc_type(i) = iflag_bc_sgs + 2
-          else if ( tmpchara .eq. 'sgs_z' ) then
-            magne_nod%ibc_type(i) = iflag_bc_sgs + 3
           end if
         end do
 !
diff --git a/src/Fortran_libraries/MHD_src/IO/set_control_4_press.f90 b/src/Fortran_libraries/MHD_src/IO/set_control_4_press.f90
index 201be37..3d9086d 100644
--- a/src/Fortran_libraries/MHD_src/IO/set_control_4_press.f90
+++ b/src/Fortran_libraries/MHD_src/IO/set_control_4_press.f90
@@ -35,9 +35,9 @@
       use m_node_group
       use m_bc_data_list
       use m_surf_data_list
+      use set_node_group_types
       use set_surface_group_types
 !
-      character(len=kchara) :: tmpchara
       integer (kind = kint) :: i
 !
 !
@@ -61,14 +61,10 @@
         press_nod%bc_magnitude = bc_p_magnitude_ctl
 !
         do i = 1, press_nod%num_bc
-          tmpchara = bc_p_type_ctl(i)
-          if ( tmpchara .eq. 'fixed' ) then
-            press_nod%ibc_type(i) =  iflag_bc_fix_s
-          else if ( tmpchara .eq. 'file' ) then
-            press_nod%ibc_type(i) = -iflag_bc_fix_s
-          else if ( tmpchara .eq. 'sgs' ) then
-            press_nod%ibc_type(i) =  iflag_bc_sgs_s
-          end if
+          call set_nod_group_types_scalar(bc_p_type_ctl(i),             &
+     &        press_nod%ibc_type(i))
+          call set_nod_group_types_sgs_scalar(bc_p_type_ctl(i),         &
+     &        press_nod%ibc_type(i))
         end do
 !
 !
@@ -76,7 +72,7 @@
           write(*,*) 'i, press_nod'
           do i = 1, press_nod%num_bc
             write(*,*)  i, press_nod%ibc_type(i),                       &
-     &         press_nod%bc_magnitude(i), trim(press_nod%bc_name(i))
+     &        press_nod%bc_magnitude(i), trim(press_nod%bc_name(i))
           end do
         end if
       end if
@@ -91,11 +87,10 @@
         wall_surf%bc_name =       bc_grad_p_name_ctl
 !
         do i = 1, wall_surf%num_bc
-          tmpchara = bc_grad_p_type_ctl(i)
           call set_surf_group_types_scalar(bc_grad_p_type_ctl(i),       &
-     &        wall_surf%ibc_type(i) )
+     &       wall_surf%ibc_type(i) )
           call set_surf_wall_group_types(bc_grad_p_type_ctl(i),         &
-     &        wall_surf%ibc_type(i) )
+     &       wall_surf%ibc_type(i) )
         end do
       end if
 !
diff --git a/src/Fortran_libraries/MHD_src/IO/set_control_4_temp.f90 b/src/Fortran_libraries/MHD_src/IO/set_control_4_temp.f90
index 9be9110..c58f946 100644
--- a/src/Fortran_libraries/MHD_src/IO/set_control_4_temp.f90
+++ b/src/Fortran_libraries/MHD_src/IO/set_control_4_temp.f90
@@ -34,6 +34,7 @@
       use m_node_group
       use m_bc_data_list
       use m_surf_data_list
+      use set_node_group_types
       use set_surface_group_types
 !
       integer(kind = kint) :: i
@@ -59,14 +60,15 @@
         temp_nod%bc_magnitude = bc_e_magnitude_ctl
 !
         do i = 1, temp_nod%num_bc
-          if ( bc_e_type_ctl(i) .eq. 'fixed' ) then
-            temp_nod%ibc_type(i) =  iflag_bc_fix_s
-          else if ( bc_e_type_ctl(i) .eq. 'file' ) then
-            temp_nod%ibc_type(i) = -iflag_bc_fix_s
-          else if ( bc_e_type_ctl(i) .eq. 'fixed_flux' ) then
+          call set_nod_group_types_scalar(bc_e_type_ctl(i),             &
+     &        temp_nod%ibc_type(i))
+          call set_nod_group_types_sgs_scalar(bc_e_type_ctl(i),         &
+     &        temp_nod%ibc_type(i))
+!
+          if ( bc_e_type_ctl(i) .eq. 'fixed_flux' ) then
             temp_nod%ibc_type(i) =  iflag_bc_fix_flux
-          else if ( bc_e_type_ctl(i) .eq. 'sgs' ) then
-            temp_nod%ibc_type(i) =  iflag_bc_sgs_s
+          else if(bc_e_type_ctl(i) .eq. 'sph_to_center') then
+            temp_nod%ibc_type(i) =  iflag_sph_2_center
           end if
         end do
 !
@@ -91,6 +93,10 @@
         do i = 1, h_flux_surf%num_bc
           call set_surf_group_types_scalar(bc_h_flux_type_ctl(i),       &
      &            h_flux_surf%ibc_type(i))
+!
+          if(bc_h_flux_type_ctl(i) .eq. 'sph_to_center') then
+            h_flux_surf%ibc_type(i) =  iflag_sph_2_center
+          end if
         end do
       end if
 !
diff --git a/src/Fortran_libraries/MHD_src/IO/set_control_4_velo.f90 b/src/Fortran_libraries/MHD_src/IO/set_control_4_velo.f90
index b87bc53..04bbc5a 100644
--- a/src/Fortran_libraries/MHD_src/IO/set_control_4_velo.f90
+++ b/src/Fortran_libraries/MHD_src/IO/set_control_4_velo.f90
@@ -35,9 +35,9 @@
       use m_node_group
       use m_bc_data_list
       use m_surf_data_list
+      use set_node_group_types
       use set_surface_group_types
 !
-      character(len=kchara) :: tmpchara
       integer (kind = kint) :: i, iflag_4_hemi
 !
 !
@@ -57,7 +57,7 @@
 !
         call allocate_nod_bc_list_velo
 !
-        velo_nod%bc_name =      bc_v_name_ctl
+        velo_nod%bc_name = bc_v_name_ctl
         velo_nod%bc_magnitude = bc_v_magnitude_ctl
 !
         iflag_4_hemi = 0
@@ -68,41 +68,25 @@
         end do
 !
         do i = 1, velo_nod%num_bc
-          tmpchara = bc_v_type_ctl(i)
-          if ( tmpchara .eq. 'fix_x' ) then
-            velo_nod%ibc_type(i) = iflag_bc_fixed + 1
-          else if ( tmpchara .eq. 'fix_y' ) then
-            velo_nod%ibc_type(i) = iflag_bc_fixed + 2
-          else if ( tmpchara .eq. 'fix_z' ) then
-            velo_nod%ibc_type(i) = iflag_bc_fixed + 3
-          else if ( tmpchara .eq. 'file_x' ) then
-            velo_nod%ibc_type(i) = iflag_bc_fixed - 1
-          else if ( tmpchara .eq. 'file_y' ) then
-            velo_nod%ibc_type(i) = iflag_bc_fixed - 2
-          else if ( tmpchara .eq. 'file_z' ) then
-            velo_nod%ibc_type(i) = iflag_bc_fixed - 3
-          else if ( tmpchara .eq. 'rot_x' ) then
-            velo_nod%ibc_type(i) = iflag_bc_rot + 1
-          else if ( tmpchara .eq. 'rot_y' ) then
-            velo_nod%ibc_type(i) = iflag_bc_rot + 2
-          else if ( tmpchara .eq. 'rot_z' ) then
-            velo_nod%ibc_type(i) = iflag_bc_rot + 3
-          else if ( tmpchara .eq. 'vr_0' ) then
+         call set_nod_group_types_vector(bc_v_type_ctl(i),              &
+     &       velo_nod%ibc_type(i))
+         call set_nod_group_types_sgs_vect(bc_v_type_ctl(i),            &
+     &       velo_nod%ibc_type(i))
+         call set_nod_group_types_rotatin(bc_v_type_ctl(i),             &
+     &       velo_nod%ibc_type(i))
+!
+          if (bc_v_type_ctl(i) .eq. 'vr_0' ) then
             velo_nod%ibc_type(i) = iflag_no_vr
-          else if ( tmpchara .eq. 'free_slip_sph' ) then
+          else if ( bc_v_type_ctl(i) .eq. 'free_slip_sph' ) then
             velo_nod%ibc_type(i) = iflag_free_sph
-          else if ( tmpchara .eq. 'non_slip_sph' ) then
+          else if ( bc_v_type_ctl(i) .eq. 'non_slip_sph' ) then
             velo_nod%ibc_type(i) = iflag_non_slip_sph
-          else if ( tmpchara .eq. 'rot_inner_core' ) then
+          else if ( bc_v_type_ctl(i) .eq. 'rot_inner_core' ) then
             velo_nod%ibc_type(i) = iflag_rotatable_icore
-          else if ( tmpchara .eq. 'special' ) then
+          else if ( bc_v_type_ctl(i) .eq. 'sph_to_center' ) then
+            velo_nod%ibc_type(i) = iflag_sph_2_center
+          else if ( bc_v_type_ctl(i) .eq. 'special' ) then
             velo_nod%ibc_type(i) = iflag_bc_special
-          else if ( tmpchara .eq. 'sgs_x' ) then
-            velo_nod%ibc_type(i) =  iflag_bc_sgs + 1
-          else if ( tmpchara .eq. 'sgs_y' ) then
-            velo_nod%ibc_type(i) =  iflag_bc_sgs + 2
-          else if ( tmpchara .eq. 'sgs_z' ) then
-            velo_nod%ibc_type(i) =  iflag_bc_sgs + 3
           end if
         end do
 !
@@ -138,6 +122,8 @@
             torque_surf%ibc_type(i) = iflag_non_slip_sph
           else if (bc_torque_type_ctl(i) .eq. 'rot_inner_core' ) then
             torque_surf%ibc_type(i) = iflag_rotatable_icore
+          else if (bc_torque_type_ctl(i) .eq. 'sph_to_center'  ) then
+            torque_surf%ibc_type(i) = iflag_sph_2_center
           end if
         end do
 !
diff --git a/src/Fortran_libraries/MHD_src/IO/set_node_group_types.f90 b/src/Fortran_libraries/MHD_src/IO/set_node_group_types.f90
new file mode 100644
index 0000000..f08cbf9
--- /dev/null
+++ b/src/Fortran_libraries/MHD_src/IO/set_node_group_types.f90
@@ -0,0 +1,118 @@
+!>@file   set_node_group_types.f90
+!!@brief  module set_node_group_types
+!!
+!!@author H. Matsui and H. Okuda
+!!@date Programmed by H. Matsui in Sep. 2005
+!
+!> @brief set surface boundary condition flags from conterol input
+!!
+!!@verbatim
+!!      subroutine set_nod_group_types_scalar(bc_type_ctl, ibc_type)
+!!      subroutine set_nod_group_types_vector(bc_type_ctl, ibc_type)
+!!      subroutine set_nod_group_types_sgs_scalar(bc_type_ctl, ibc_type)
+!!      subroutine set_nod_group_types_sgs_vect(bc_type_ctl, ibc_type)
+!!      subroutine set_nod_group_types_rotatin(bc_type_ctl, ibc_type)
+!!@endverbatim
+!
+      module set_node_group_types
+!
+      use m_precision
+      use m_boundary_condition_IDs
+!
+      implicit none
+!
+!-----------------------------------------------------------------------
+!
+      contains
+!
+!-----------------------------------------------------------------------
+!
+      subroutine set_nod_group_types_scalar(bc_type_ctl, ibc_type)
+!
+      character (len=kchara), intent(in) :: bc_type_ctl
+      integer(kind = kint), intent(inout) :: ibc_type
+!
+!
+      if ( bc_type_ctl .eq. 'fixed' ) then
+        ibc_type =  iflag_bc_fix_s
+      else if ( bc_type_ctl .eq. 'file' ) then
+        ibc_type = -iflag_bc_fix_s
+      end if
+!
+      end subroutine set_nod_group_types_scalar
+!
+!-----------------------------------------------------------------------
+!
+      subroutine set_nod_group_types_vector(bc_type_ctl, ibc_type)
+!
+      character (len=kchara), intent(in) :: bc_type_ctl
+      integer(kind = kint), intent(inout) :: ibc_type
+!
+!
+      if      ( bc_type_ctl .eq. 'fix_x' ) then
+        ibc_type = iflag_bc_fixed + 1
+      else if ( bc_type_ctl .eq. 'fix_y' ) then
+        ibc_type = iflag_bc_fixed + 2
+      else if ( bc_type_ctl .eq. 'fix_z' ) then
+        ibc_type = iflag_bc_fixed + 3
+      else if ( bc_type_ctl .eq. 'file_x' ) then
+        ibc_type = iflag_bc_fixed - 1
+      else if ( bc_type_ctl .eq. 'file_y' ) then
+        ibc_type = iflag_bc_fixed - 2
+      else if ( bc_type_ctl .eq. 'file_z' ) then
+        ibc_type = iflag_bc_fixed - 3
+      end if
+!
+      end subroutine set_nod_group_types_vector
+!
+!-----------------------------------------------------------------------
+!
+      subroutine set_nod_group_types_sgs_scalar(bc_type_ctl, ibc_type)
+!
+      character (len=kchara), intent(in) :: bc_type_ctl
+      integer(kind = kint), intent(inout) :: ibc_type
+!
+!
+      if( bc_type_ctl .eq. 'sgs' )  ibc_type = iflag_bc_sgs_s
+!
+      end subroutine set_nod_group_types_sgs_scalar
+!
+!-----------------------------------------------------------------------
+!
+      subroutine set_nod_group_types_sgs_vect(bc_type_ctl, ibc_type)
+!
+      character (len=kchara), intent(in) :: bc_type_ctl
+      integer(kind = kint), intent(inout) :: ibc_type
+!
+!
+      if      ( bc_type_ctl .eq. 'sgs_x' ) then
+        ibc_type = iflag_bc_sgs + 1
+      else if ( bc_type_ctl .eq. 'sgs_y' ) then
+        ibc_type = iflag_bc_sgs + 2
+      else if ( bc_type_ctl .eq. 'sgs_z' ) then
+        ibc_type = iflag_bc_sgs + 3
+      end if
+!
+      end subroutine set_nod_group_types_sgs_vect
+!
+!-----------------------------------------------------------------------
+!
+      subroutine set_nod_group_types_rotatin(bc_type_ctl, ibc_type)
+!
+      character (len=kchara), intent(in) :: bc_type_ctl
+      integer(kind = kint), intent(inout) :: ibc_type
+!
+!
+      if      ( bc_type_ctl .eq. 'rot_x' ) then
+        ibc_type = iflag_bc_rot + 1
+      else if ( bc_type_ctl .eq. 'rot_y' ) then
+        ibc_type = iflag_bc_rot + 2
+      else if ( bc_type_ctl .eq. 'rot_z' ) then
+        ibc_type = iflag_bc_rot + 3
+      end if
+!
+      end subroutine set_nod_group_types_rotatin
+!
+!-----------------------------------------------------------------------
+!
+      end module set_node_group_types
diff --git a/src/Fortran_libraries/MHD_src/IO/set_surface_group_types.f90 b/src/Fortran_libraries/MHD_src/IO/set_surface_group_types.f90
index 446e76e..19d09bd 100644
--- a/src/Fortran_libraries/MHD_src/IO/set_surface_group_types.f90
+++ b/src/Fortran_libraries/MHD_src/IO/set_surface_group_types.f90
@@ -33,6 +33,7 @@
       character (len=kchara), intent(in) :: bc_type_ctl
       integer(kind = kint), intent(inout) :: ibc_type
 !
+!
       if      ( bc_type_ctl .eq. 'fixed_ctl'                            &
      &    .or.  bc_type_ctl .eq. 'fixed') then
         ibc_type =  iflag_surf_fix_s
@@ -61,6 +62,7 @@
       character (len=kchara), intent(in) :: bc_type_ctl
       integer(kind = kint), intent(inout) :: ibc_type
 !
+!
          if      ( bc_type_ctl .eq. 'fix_ctl_x'                         &
      &        .or. bc_type_ctl .eq. 'fix_x') then
           ibc_type = iflag_surf_fix_x
@@ -118,6 +120,7 @@
       character (len=kchara), intent(in) :: bc_type_ctl
       integer(kind = kint), intent(inout) :: ibc_type
 !
+!
          if ( bc_type_ctl .eq. 'free_sph_in' ) then
           ibc_type = iflag_surf_free_sph_in
          else if ( bc_type_ctl .eq. 'free_sph_out' ) then
@@ -151,6 +154,7 @@
       character (len=kchara), intent(in) :: bc_type_ctl
       integer(kind = kint), intent(inout) :: ibc_type
 !
+!
          if ( bc_type_ctl .eq. 'pseudo_vacuum_in' ) then
           ibc_type = iflag_surf_qvc_sph_in
          else if ( bc_type_ctl .eq. 'pseudo_vacuum_out' ) then
@@ -166,9 +170,8 @@
       character (len=kchara), intent(in) :: bc_type_ctl
       integer(kind = kint), intent(inout) :: ibc_type
 !
-      if ( bc_type_ctl .eq. 'infinity' ) then
-       ibc_type = iflag_surf_infty
-      end if
+!
+      if ( bc_type_ctl .eq. 'infinity' ) ibc_type = iflag_surf_infty
 !
       end subroutine set_surf_infty_group_types
 !
diff --git a/src/Fortran_libraries/MHD_src/sph_MHD/m_control_params_sph_MHD.f90 b/src/Fortran_libraries/MHD_src/sph_MHD/m_control_params_sph_MHD.f90
index 3d5978e..0ab908a 100644
--- a/src/Fortran_libraries/MHD_src/sph_MHD/m_control_params_sph_MHD.f90
+++ b/src/Fortran_libraries/MHD_src/sph_MHD/m_control_params_sph_MHD.f90
@@ -31,7 +31,9 @@
 !>      integer flag for free-slip boundary at inner core
       integer(kind = kint), parameter :: iflag_free_slip =  1
 !>      integer flag for rotatable inner core
-      integer(kind = kint), parameter :: iflag_rotatable_ic = 10
+      integer(kind = kint), parameter :: iflag_rotatable_ic =    10
+!>      integer flag for whole sphere model
+      integer(kind = kint), parameter :: iflag_sph_fill_center = 41
 !
 !>      integer flag for fixed velocity boundary
       integer(kind = kint), parameter :: iflag_fixed_field = 0
@@ -40,8 +42,6 @@
 !
 !>      integer flag for insulated magnetic boundary
       integer(kind = kint), parameter :: iflag_sph_insulator =   0
-!>      integer flag for insulated magnetic boundary
-      integer(kind = kint), parameter :: iflag_sph_fill_center = 1
 !>      integer flag for pseudo vacuum magnetic boundary
       integer(kind = kint), parameter :: iflag_radial_magne =   11
 !
diff --git a/src/Fortran_libraries/MHD_src/sph_MHD/set_bc_flag_sph_velo.f90 b/src/Fortran_libraries/MHD_src/sph_MHD/set_bc_flag_sph_velo.f90
index 51eff91..ba27b91 100644
--- a/src/Fortran_libraries/MHD_src/sph_MHD/set_bc_flag_sph_velo.f90
+++ b/src/Fortran_libraries/MHD_src/sph_MHD/set_bc_flag_sph_velo.f90
@@ -45,7 +45,8 @@
 !
       do i = 1, velo_nod%num_bc
         if(iflag_icb_velocity .ne. iflag_fixed_velo) exit
-        if(velo_nod%bc_name(i) .eq. 'ICB') then
+        if(velo_nod%bc_name(i) .eq. ICB_nod_grp_name                    &
+     &    .or. velo_nod%bc_name(i) .eq. CTR_nod_grp_name) then
           call set_sph_velo_ICB_flag(velo_nod%ibc_type(i),              &
      &        velo_nod%bc_magnitude(i))
         end if
@@ -53,8 +54,10 @@
 !
       do i = 1, torque_surf%num_bc
         if(iflag_icb_velocity .ne. iflag_fixed_velo) exit
-        if    (torque_surf%bc_name(i) .eq. 'ICB_surf'                   &
-     &    .or. torque_surf%bc_name(i) .eq. 'ICB') then
+        if    (torque_surf%bc_name(i) .eq. ICB_sf_grp_name              &
+     &    .or. torque_surf%bc_name(i) .eq. ICB_nod_grp_name             &
+     &    .or. torque_surf%bc_name(i) .eq. CTR_sf_grp_name              &
+     &    .or. torque_surf%bc_name(i) .eq. CTR_nod_grp_name) then
           call set_sph_velo_ICB_flag(torque_surf%ibc_type(i),           &
      &        torque_surf%bc_magnitude(i))
         end if
@@ -64,7 +67,7 @@
 !
       do i = 1, velo_nod%num_bc
         if(iflag_cmb_velocity .ne. iflag_fixed_velo) exit
-        if(velo_nod%bc_name(i) .eq. 'CMB') then 
+        if(velo_nod%bc_name(i) .eq. CMB_nod_grp_name) then
           call set_sph_velo_CMB_flag(velo_nod%ibc_type(i),              &
      &        velo_nod%bc_magnitude(i))
         end if
@@ -72,13 +75,21 @@
 !
       do i = 1, torque_surf%num_bc
         if(iflag_cmb_velocity .ne. iflag_fixed_velo) exit
-        if(     torque_surf%bc_name(i) .eq. 'CMB_surf'                  &
-     &     .or. torque_surf%bc_name(i) .eq. 'CMB') then 
+        if(     torque_surf%bc_name(i) .eq. CMB_sf_grp_name             &
+     &     .or. torque_surf%bc_name(i) .eq. CMB_nod_grp_name) then
           call set_sph_velo_CMB_flag(torque_surf%ibc_type(i),           &
      &        torque_surf%bc_magnitude(i))
         end if
       end do
 !
+!
+      if(iflag_icb_velocity .eq. iflag_sph_fill_center) then
+        kr_rj_fluid_start = nlayer_2_center
+      else
+        kr_rj_fluid_start = nlayer_ICB
+      end if
+      kr_rj_fluid_end = nlayer_CMB
+!
       end subroutine set_sph_bc_velo_sph
 !
 ! -----------------------------------------------------------------------
@@ -92,11 +103,12 @@
 !
       if      (ibc_type .eq. iflag_free_sph) then
         iflag_icb_velocity = iflag_free_slip
-        return
       else if (ibc_type .eq. iflag_non_slip_sph) then
         iflag_icb_velocity = iflag_fixed_velo
       else if (ibc_type .eq. iflag_rotatable_icore) then
         iflag_icb_velocity = iflag_rotatable_ic
+      else if (ibc_type .eq. iflag_sph_2_center) then
+        iflag_icb_velocity = iflag_sph_fill_center
 !
       else if (ibc_type .eq. (iflag_bc_rot+1)) then
         iflag_icb_velocity = iflag_fixed_velo
@@ -127,7 +139,6 @@
 !
       if      (ibc_type .eq. iflag_free_sph) then
         iflag_cmb_velocity = iflag_free_slip
-        return
       else if (ibc_type .eq. iflag_non_slip_sph) then
         iflag_cmb_velocity = iflag_fixed_velo
 !
diff --git a/src/Fortran_libraries/MHD_src/sph_MHD/set_bc_sph_mhd.f90 b/src/Fortran_libraries/MHD_src/sph_MHD/set_bc_sph_mhd.f90
index a60f548..af44095 100644
--- a/src/Fortran_libraries/MHD_src/sph_MHD/set_bc_sph_mhd.f90
+++ b/src/Fortran_libraries/MHD_src/sph_MHD/set_bc_sph_mhd.f90
@@ -19,20 +19,11 @@
       use m_control_params_sph_MHD
       use m_boundary_condition_IDs
       use m_phys_labels
+      use m_spheric_parameter
 !
       implicit none
 !
-      character(len=kchara), parameter :: ICB_nod_grp_name = 'ICB'
-      character(len=kchara), parameter :: CMB_nod_grp_name = 'CMB'
-      character(len=kchara), parameter :: ICB_sf_grp_name = 'ICB_surf'
-      character(len=kchara), parameter :: CMB_sf_grp_name = 'CMB_surf'
-!
-      private :: ICB_nod_grp_name, ICB_sf_grp_name
-      private :: CMB_nod_grp_name, CMB_sf_grp_name
-      private :: set_sph_bc_temp_sph
-      private :: set_sph_bc_magne_sph, set_sph_bc_composition_sph
-!
-      private :: set_homogenious_scalar_bc, set_homogenious_grad_bc
+      private :: set_sph_bc_magne_sph
 !
 ! -----------------------------------------------------------------------
 !
@@ -43,6 +34,7 @@
       subroutine s_set_bc_sph_mhd
 !
       use set_bc_flag_sph_velo
+      use set_bc_sph_scalars
 !
 !
       if (iflag_t_evo_4_velo .gt.     id_no_evolution) then
@@ -61,119 +53,37 @@
         call set_sph_bc_composition_sph
       end if
 !
-      end subroutine s_set_bc_sph_mhd
-!
-! -----------------------------------------------------------------------
-!
-      subroutine set_sph_bc_temp_sph
-!
-      use m_spheric_parameter
-      use m_bc_data_list
-      use m_surf_data_list
-      use m_constants
-      use m_sph_spectr_data
-      use m_sph_boundary_input_data
-!
-!
-      integer(kind = kint) :: i
 !
 !
-      call allocate_temp_bc_array( nidx_rj(2) )
-!
-      if(iflag_debug .gt. 0) then
-        write(*,*) 'h_flux_surf%num_bc',       h_flux_surf%num_bc
-        write(*,*) 'h_flux_surf%ibc_type',     h_flux_surf%ibc_type
-        write(*,*) 'h_flux_surf%bc_magnitude', h_flux_surf%bc_magnitude
+      if(iflag_icb_velocity .eq. iflag_sph_fill_center) then
+        kr_rj_fluid_start = nlayer_2_center
+      else
+        kr_rj_fluid_start = nlayer_ICB
       end if
+      kr_rj_fluid_end = nlayer_CMB
 !
-      do i = 1, h_flux_surf%num_bc
-        if ( h_flux_surf%ibc_type(i)  .eq. iflag_surf_fix_s) then
-          call set_homogenious_grad_bc                                  &
-     &       (ICB_nod_grp_name, ICB_sf_grp_name,                        &
-     &        h_flux_surf%bc_name(i), h_flux_surf%bc_magnitude(i),      &
-     &        nidx_rj(2), h_flux_ICB_bc, iflag_icb_temp)
-          call set_homogenious_grad_bc                                  &
-     &       (CMB_nod_grp_name, CMB_sf_grp_name,                        &
-     &        h_flux_surf%bc_name(i), h_flux_surf%bc_magnitude(i),      &
-     &        nidx_rj(2), h_flux_CMB_bc, iflag_cmb_temp)
-        else if (h_flux_surf%ibc_type(i)  .eq. -iflag_surf_fix_s) then
-          call set_fixed_gradient_bc_by_file                            &
-     &       (fhd_temp, ICB_nod_grp_name, ICB_sf_grp_name,              &
-     &        nidx_rj(2), h_flux_ICB_bc, iflag_icb_temp)
-          call set_fixed_gradient_bc_by_file                            &
-     &       (fhd_temp, CMB_nod_grp_name, CMB_sf_grp_name,              &
-     &        nidx_rj(2), h_flux_CMB_bc, iflag_cmb_temp)
-        end if
-      end do
-!
-      if(iflag_debug .gt. 0) then
-        write(*,*) 'iflag_icb_temp', iflag_icb_temp
-        write(*,*) 'iflag_cmb_temp', iflag_cmb_temp
-        write(*,*)  h_flux_CMB_bc(1)
+      if(iflag_icb_composition .eq. iflag_sph_fill_center) then
+        kr_rj_thermal_start = nlayer_2_center
+      else
+        kr_rj_thermal_start = nlayer_ICB
       end if
+      kr_rj_thermal_end = nlayer_CMB
 !
-      do i = 1, temp_nod%num_bc
-        if ( temp_nod%ibc_type(i)  .eq. iflag_bc_fix_flux) then
-          call set_homogenious_grad_bc                                  &
-     &       (ICB_nod_grp_name, ICB_sf_grp_name,                        &
-     &        temp_nod%bc_name(i), temp_nod%bc_magnitude(i),            &
-     &        nidx_rj(2), h_flux_ICB_bc, iflag_icb_temp)
-          call set_homogenious_grad_bc                                  &
-     &       (CMB_nod_grp_name, CMB_sf_grp_name,                        &
-     &        temp_nod%bc_name(i), temp_nod%bc_magnitude(i),            &
-     &        nidx_rj(2), h_flux_CMB_bc, iflag_cmb_temp)
-!
-        else if ( temp_nod%ibc_type(i)  .eq. -iflag_bc_fix_flux) then
-          call set_fixed_gradient_bc_by_file                            &
-     &       (fhd_h_flux, ICB_nod_grp_name, ICB_sf_grp_name,            &
-     &        nidx_rj(2), h_flux_ICB_bc, iflag_icb_temp)
-          call set_fixed_gradient_bc_by_file                            &
-     &       (fhd_h_flux, CMB_nod_grp_name, CMB_sf_grp_name,            &
-     &        nidx_rj(2), h_flux_CMB_bc, iflag_cmb_temp)
-!
-!
-        else if ( temp_nod%ibc_type(i)  .eq. iflag_bc_fix_s) then
-          call set_homogenious_scalar_bc(ICB_nod_grp_name,              &
-     &        temp_nod%bc_name(i), temp_nod%bc_magnitude(i),            &
-     &        nidx_rj(2), temp_ICB_bc, iflag_icb_temp)
-          call set_homogenious_scalar_bc(CMB_nod_grp_name,              &
-     &        temp_nod%bc_name(i), temp_nod%bc_magnitude(i),            &
-     &        nidx_rj(2), temp_CMB_bc, iflag_cmb_temp)
-!
-        else if ( temp_nod%ibc_type(i)  .eq. -iflag_bc_fix_s) then
-          call set_fixed_scalar_bc_by_file(fhd_temp, ICB_nod_grp_name,  &
-     &        nidx_rj(2), temp_ICB_bc, iflag_icb_temp)
-          call set_fixed_scalar_bc_by_file(fhd_temp, CMB_nod_grp_name,  &
-     &        nidx_rj(2), temp_CMB_bc, iflag_cmb_temp)
-        end if
-      end do
-!
-      h_flux_ICB_bc(1:nidx_rj(2)) = - h_flux_ICB_bc(1:nidx_rj(2))
-!
-      if(idx_rj_degree_zero .gt. 0                                      &
-     &      .and. iflag_4_ref_temp .eq. id_sphere_ref_temp) then
-        temp_ICB_bc(idx_rj_degree_zero)                                 &
-     &   = temp_ICB_bc(idx_rj_degree_zero) - reftemp_rj(nlayer_ICB,0)
-        temp_CMB_bc(idx_rj_degree_zero)                                 &
-     &   = temp_CMB_bc(idx_rj_degree_zero) - reftemp_rj(nlayer_CMB,0)
-        h_flux_ICB_bc(idx_rj_degree_zero)                               &
-     &   = h_flux_ICB_bc(idx_rj_degree_zero) - reftemp_rj(nlayer_ICB,1)
-        h_flux_CMB_bc(idx_rj_degree_zero)                               &
-     &   = h_flux_CMB_bc(idx_rj_degree_zero) - reftemp_rj(nlayer_CMB,1)
+      if(iflag_icb_composition .eq. iflag_sph_fill_center) then
+        kr_rj_light_start = nlayer_2_center
+      else
+        kr_rj_light_start = nlayer_ICB
       end if
+      kr_rj_conduct_end = nlayer_CMB
 !
-      if(iflag_debug .gt. 0 .and. idx_rj_degree_zero .gt. 0) then
-        write(*,*) 'iflag_icb_temp', iflag_icb_temp,                    &
-     &             reftemp_rj(nlayer_ICB,0),                            &
-     &             temp_ICB_bc(idx_rj_degree_zero),                     &
-     &             h_flux_ICB_bc(idx_rj_degree_zero)
-        write(*,*) 'iflag_cmb_temp', iflag_cmb_temp,                    &
-     &             reftemp_rj(nlayer_CMB,0),                            &
-     &             temp_CMB_bc(idx_rj_degree_zero),                     &
-     &             h_flux_CMB_bc(idx_rj_degree_zero)
+      if(iflag_icb_magne .eq. iflag_sph_fill_center) then
+        kr_rj_conduct_start = nlayer_2_center
+      else
+        kr_rj_conduct_start = nlayer_ICB
       end if
+      kr_rj_light_end = nlayer_CMB
 !
-      end subroutine set_sph_bc_temp_sph
+      end subroutine s_set_bc_sph_mhd
 !
 ! -----------------------------------------------------------------------
 !
@@ -190,19 +100,19 @@
       iflag_cmb_magne = iflag_sph_insulator
 !
       do i = 1, magne_nod%num_bc
-        if(magne_nod%bc_name(i) .eq. 'ICB') then
+        if(magne_nod%bc_name(i) .eq. ICB_nod_grp_name) then
           if(magne_nod%ibc_type(i) .eq. iflag_pseudo_vacuum) then
             iflag_icb_magne =  iflag_radial_magne
           end if
         end if
 !
-        if(magne_nod%bc_name(i) .eq. 'CMB') then
+        if(magne_nod%bc_name(i) .eq. CMB_nod_grp_name) then
           if(magne_nod%ibc_type(i) .eq. iflag_pseudo_vacuum) then
             iflag_cmb_magne =  iflag_radial_magne
           end if
         end if
 !
-        if(magne_nod%bc_name(i) .eq. 'to_Center') then
+        if(magne_nod%bc_name(i) .eq. CTR_nod_grp_name) then
           if      (magne_nod%ibc_type(i) .eq. iflag_sph_2_center) then
             iflag_icb_magne =  iflag_sph_fill_center
           end if
@@ -211,157 +121,27 @@
 !
 !
       do i = 1, magne_surf%num_bc
-        if(magne_surf%bc_name(i) .eq. 'ICB') then
+        if(magne_surf%bc_name(i) .eq. ICB_nod_grp_name) then
           if(magne_surf%ibc_type(i) .eq. iflag_pseudo_vacuum) then
             iflag_icb_magne =  iflag_radial_magne
           end if
         end if
 !
-        if(magne_surf%bc_name(i) .eq. 'CMB') then
+        if(magne_surf%bc_name(i) .eq. CMB_nod_grp_name) then
           if(magne_surf%ibc_type(i) .eq. iflag_pseudo_vacuum) then
             iflag_cmb_magne =  iflag_radial_magne
           end if
         end if
 !
-        if(magne_surf%bc_name(i) .eq. 'to_Center') then
+        if(magne_surf%bc_name(i) .eq. CTR_nod_grp_name) then
           if(magne_surf%ibc_type(i) .eq. iflag_sph_2_center) then
             iflag_icb_magne =  iflag_sph_fill_center
           end if
         end if
       end do
 !
-!
       end subroutine set_sph_bc_magne_sph
 !
 ! -----------------------------------------------------------------------
 !
-      subroutine set_sph_bc_composition_sph
-!
-      use m_spheric_parameter
-      use m_bc_data_list
-      use m_surf_data_list
-      use m_sph_spectr_data
-      use m_sph_boundary_input_data
-!
-      integer(kind = kint) :: i
-!
-!
-      call allocate_dscalar_bc_array( nidx_rj(2) )
-!
-!      Boundary setting using surface group data
-!
-      do i = 1, light_surf%num_bc
-        if (light_surf%ibc_type(i)  .eq. iflag_surf_fix_s) then
-          call set_homogenious_grad_bc                                  &
-     &       (ICB_nod_grp_name, ICB_sf_grp_name,                        &
-     &        light_surf%bc_name(i), light_surf%bc_magnitude(i),        &
-     &        nidx_rj(2), c_flux_ICB_bc, iflag_icb_composition)
-          call set_homogenious_grad_bc                                  &
-     &       (CMB_nod_grp_name, CMB_sf_grp_name,                        &
-     &        light_surf%bc_name(i), light_surf%bc_magnitude(i),        &
-     &        nidx_rj(2), c_flux_CMB_bc, iflag_cmb_composition)
-        else if (light_surf%ibc_type(i)  .eq. -iflag_surf_fix_s)        &
-     &         then
-          call set_fixed_gradient_bc_by_file                            &
-     &       (fhd_light, ICB_nod_grp_name, ICB_sf_grp_name,             &
-     &        nidx_rj(2), c_flux_ICB_bc, iflag_icb_composition)
-          call set_fixed_gradient_bc_by_file                            &
-     &       (fhd_light, CMB_nod_grp_name, CMB_sf_grp_name,             &
-     &        nidx_rj(2), c_flux_CMB_bc, iflag_cmb_composition)
-        end if
-      end do
-!
-!      Boundary setting using boundary group data
-!
-      do i = 1, light_nod%num_bc
-        if ( light_nod%ibc_type(i)  .eq. iflag_bc_fix_flux) then
-          call set_homogenious_grad_bc                                  &
-     &       (ICB_nod_grp_name, ICB_sf_grp_name,                        &
-     &        light_nod%bc_name(i), light_nod%bc_magnitude(i),          &
-     &        nidx_rj(2), c_flux_ICB_bc, iflag_icb_composition)
-          call set_homogenious_grad_bc                                  &
-     &       (CMB_nod_grp_name, CMB_sf_grp_name,                        &
-     &        light_nod%bc_name(i), light_nod%bc_magnitude(i),          &
-     &        nidx_rj(2), c_flux_CMB_bc, iflag_cmb_composition)
-!
-        else if ( light_nod%ibc_type(i)  .eq. -iflag_bc_fix_flux) then
-          call set_fixed_gradient_bc_by_file                            &
-     &       (fhd_c_flux, ICB_nod_grp_name, ICB_sf_grp_name,            &
-     &        nidx_rj(2), c_flux_ICB_bc, iflag_icb_composition)
-          call set_fixed_gradient_bc_by_file                            &
-     &       (fhd_c_flux, CMB_nod_grp_name, CMB_sf_grp_name,            &
-     &        nidx_rj(2), c_flux_CMB_bc, iflag_cmb_composition)
-!
-!
-        else if ( light_nod%ibc_type(i)  .eq. iflag_bc_fix_s) then
-          call set_homogenious_scalar_bc(ICB_nod_grp_name,              &
-     &        light_nod%bc_name(i), light_nod%bc_magnitude(i),          &
-     &        nidx_rj(2), composition_ICB_bc, iflag_icb_composition)
-          call set_homogenious_scalar_bc(CMB_nod_grp_name,              &
-     &        light_nod%bc_name(i), light_nod%bc_magnitude(i),          &
-     &        nidx_rj(2), composition_CMB_bc, iflag_cmb_composition)
-!
-        else if ( light_nod%ibc_type(i)  .eq. -iflag_bc_fix_s) then
-          call set_fixed_scalar_bc_by_file(fhd_light, ICB_nod_grp_name, &
-     &        nidx_rj(2), composition_ICB_bc, iflag_icb_composition)
-          call set_fixed_scalar_bc_by_file(fhd_light, CMB_nod_grp_name, &
-     &        nidx_rj(2), composition_CMB_bc, iflag_cmb_composition)
-        end if
-      end do
-!
-      c_flux_ICB_bc(1:nidx_rj(2)) = -c_flux_ICB_bc(1:nidx_rj(2))
-!
-      end subroutine set_sph_bc_composition_sph
-!
-! -----------------------------------------------------------------------
-!
-      subroutine set_homogenious_scalar_bc(reference_grp, bc_name,      &
-     &          bc_magnitude,jmax, bc_data, iflag_bc_scalar)
-!
-      use m_spheric_parameter
-!
-      character(len=kchara), intent(in) :: reference_grp
-      character(len=kchara), intent(in) :: bc_name
-      real(kind = kreal), intent(in) :: bc_magnitude
-      integer(kind = kint), intent(in) :: jmax
-      real(kind = kreal), intent(inout) :: bc_data(jmax)
-      integer(kind = kint), intent(inout) :: iflag_bc_scalar
-!
-!
-      if     (bc_name .eq. reference_grp) then
-        iflag_bc_scalar =  iflag_fixed_field
-        if(idx_rj_degree_zero .gt. 0) then
-          bc_data(idx_rj_degree_zero) = bc_magnitude
-        end if
-      end if
-!
-      end subroutine set_homogenious_scalar_bc
-!
-! -----------------------------------------------------------------------
-!
-      subroutine set_homogenious_grad_bc(ref_nod_grp, ref_sf_grp,       &
-     &          bc_name, bc_magnitude, jmax, bc_data, iflag_bc_scalar)
-!
-      use m_spheric_parameter
-!
-      character(len=kchara), intent(in) :: ref_nod_grp, ref_sf_grp
-      character(len=kchara), intent(in) :: bc_name
-      real(kind = kreal), intent(in) :: bc_magnitude
-      integer(kind = kint), intent(in) :: jmax
-      real(kind = kreal), intent(inout) :: bc_data(jmax)
-      integer(kind = kint), intent(inout) :: iflag_bc_scalar
-!
-!
-      if     (bc_name .eq. ref_nod_grp                                  &
-     &   .or. bc_name .eq. ref_sf_grp ) then
-        iflag_bc_scalar =  iflag_fixed_flux
-        if(idx_rj_degree_zero .gt. 0) then
-          bc_data(idx_rj_degree_zero) = bc_magnitude
-        end if
-      end if
-!
-      end subroutine set_homogenious_grad_bc
-!
-! -----------------------------------------------------------------------
-!
       end module set_bc_sph_mhd
diff --git a/src/Fortran_libraries/MHD_src/sph_MHD/set_bc_sph_mhd.f90 b/src/Fortran_libraries/MHD_src/sph_MHD/set_bc_sph_scalars.f90
similarity index 79%
copy from src/Fortran_libraries/MHD_src/sph_MHD/set_bc_sph_mhd.f90
copy to src/Fortran_libraries/MHD_src/sph_MHD/set_bc_sph_scalars.f90
index a60f548..90e0bef 100644
--- a/src/Fortran_libraries/MHD_src/sph_MHD/set_bc_sph_mhd.f90
+++ b/src/Fortran_libraries/MHD_src/sph_MHD/set_bc_sph_scalars.f90
@@ -1,16 +1,16 @@
-!>@file   set_bc_sph_mhd.f90
-!!@brief  module set_bc_sph_mhd
+!>@file   set_bc_sph_scalars.f90
+!!@brief  module set_bc_sph_scalars
 !!
 !!@author H. Matsui
 !!@date    programmed by H.Matsui in Oct., 2009
 !
-!>@brief Set boundary conditions for MHD dynamo simulation
+!>@brief Set boundary conditions for scalar fields
 !!
 !!@verbatim
 !!      subroutine s_set_bc_sph_mhd
 !!@endverbatim
 !
-      module set_bc_sph_mhd
+      module set_bc_sph_scalars
 !
       use m_precision
 !
@@ -22,16 +22,6 @@
 !
       implicit none
 !
-      character(len=kchara), parameter :: ICB_nod_grp_name = 'ICB'
-      character(len=kchara), parameter :: CMB_nod_grp_name = 'CMB'
-      character(len=kchara), parameter :: ICB_sf_grp_name = 'ICB_surf'
-      character(len=kchara), parameter :: CMB_sf_grp_name = 'CMB_surf'
-!
-      private :: ICB_nod_grp_name, ICB_sf_grp_name
-      private :: CMB_nod_grp_name, CMB_sf_grp_name
-      private :: set_sph_bc_temp_sph
-      private :: set_sph_bc_magne_sph, set_sph_bc_composition_sph
-!
       private :: set_homogenious_scalar_bc, set_homogenious_grad_bc
 !
 ! -----------------------------------------------------------------------
@@ -40,31 +30,6 @@
 !
 ! -----------------------------------------------------------------------
 !
-      subroutine s_set_bc_sph_mhd
-!
-      use set_bc_flag_sph_velo
-!
-!
-      if (iflag_t_evo_4_velo .gt.     id_no_evolution) then
-        call set_sph_bc_velo_sph
-      end if
-!
-      if (iflag_t_evo_4_temp .gt.     id_no_evolution) then
-        call set_sph_bc_temp_sph
-      end if
-!
-      if (iflag_t_evo_4_magne .gt.    id_no_evolution) then
-        call set_sph_bc_magne_sph
-      end if
-!
-      if (iflag_t_evo_4_composit .gt. id_no_evolution) then
-        call set_sph_bc_composition_sph
-      end if
-!
-      end subroutine s_set_bc_sph_mhd
-!
-! -----------------------------------------------------------------------
-!
       subroutine set_sph_bc_temp_sph
 !
       use m_spheric_parameter
@@ -103,6 +68,9 @@
           call set_fixed_gradient_bc_by_file                            &
      &       (fhd_temp, CMB_nod_grp_name, CMB_sf_grp_name,              &
      &        nidx_rj(2), h_flux_CMB_bc, iflag_cmb_temp)
+        else if ( h_flux_surf%ibc_type(i) .eq. iflag_sph_2_center       &
+     &       .and. h_flux_surf%bc_name(i) .eq. CTR_sf_grp_name) then
+         iflag_icb_temp = iflag_sph_fill_center
         end if
       end do
 !
@@ -145,6 +113,13 @@
      &        nidx_rj(2), temp_ICB_bc, iflag_icb_temp)
           call set_fixed_scalar_bc_by_file(fhd_temp, CMB_nod_grp_name,  &
      &        nidx_rj(2), temp_CMB_bc, iflag_cmb_temp)
+!
+        else if ( temp_nod%ibc_type(i) .eq. iflag_sph_2_center          &
+     &       .and. temp_nod%bc_name(i) .eq. CTR_sf_grp_name) then
+         iflag_icb_temp = iflag_sph_fill_center
+        else if ( temp_nod%ibc_type(i) .eq. iflag_sph_2_center          &
+     &       .and. temp_nod%bc_name(i) .eq. CTR_nod_grp_name) then
+         iflag_icb_temp = iflag_sph_fill_center
         end if
       end do
 !
@@ -177,64 +152,6 @@
 !
 ! -----------------------------------------------------------------------
 !
-      subroutine set_sph_bc_magne_sph
-!
-      use m_bc_data_list
-      use m_surf_data_list
-!
-!
-      integer(kind = kint) :: i
-!
-!
-      iflag_icb_magne = iflag_sph_insulator
-      iflag_cmb_magne = iflag_sph_insulator
-!
-      do i = 1, magne_nod%num_bc
-        if(magne_nod%bc_name(i) .eq. 'ICB') then
-          if(magne_nod%ibc_type(i) .eq. iflag_pseudo_vacuum) then
-            iflag_icb_magne =  iflag_radial_magne
-          end if
-        end if
-!
-        if(magne_nod%bc_name(i) .eq. 'CMB') then
-          if(magne_nod%ibc_type(i) .eq. iflag_pseudo_vacuum) then
-            iflag_cmb_magne =  iflag_radial_magne
-          end if
-        end if
-!
-        if(magne_nod%bc_name(i) .eq. 'to_Center') then
-          if      (magne_nod%ibc_type(i) .eq. iflag_sph_2_center) then
-            iflag_icb_magne =  iflag_sph_fill_center
-          end if
-        end if
-      end do
-!
-!
-      do i = 1, magne_surf%num_bc
-        if(magne_surf%bc_name(i) .eq. 'ICB') then
-          if(magne_surf%ibc_type(i) .eq. iflag_pseudo_vacuum) then
-            iflag_icb_magne =  iflag_radial_magne
-          end if
-        end if
-!
-        if(magne_surf%bc_name(i) .eq. 'CMB') then
-          if(magne_surf%ibc_type(i) .eq. iflag_pseudo_vacuum) then
-            iflag_cmb_magne =  iflag_radial_magne
-          end if
-        end if
-!
-        if(magne_surf%bc_name(i) .eq. 'to_Center') then
-          if(magne_surf%ibc_type(i) .eq. iflag_sph_2_center) then
-            iflag_icb_magne =  iflag_sph_fill_center
-          end if
-        end if
-      end do
-!
-!
-      end subroutine set_sph_bc_magne_sph
-!
-! -----------------------------------------------------------------------
-!
       subroutine set_sph_bc_composition_sph
 !
       use m_spheric_parameter
@@ -268,6 +185,9 @@
           call set_fixed_gradient_bc_by_file                            &
      &       (fhd_light, CMB_nod_grp_name, CMB_sf_grp_name,             &
      &        nidx_rj(2), c_flux_CMB_bc, iflag_cmb_composition)
+        else if ( light_surf%ibc_type(i) .eq. iflag_sph_2_center        &
+     &       .and. light_surf%bc_name(i) .eq. CTR_sf_grp_name) then
+         iflag_icb_composition = iflag_sph_fill_center
         end if
       end do
 !
@@ -306,6 +226,13 @@
      &        nidx_rj(2), composition_ICB_bc, iflag_icb_composition)
           call set_fixed_scalar_bc_by_file(fhd_light, CMB_nod_grp_name, &
      &        nidx_rj(2), composition_CMB_bc, iflag_cmb_composition)
+!
+        else if ( light_nod%ibc_type(i) .eq. iflag_sph_2_center         &
+     &       .and. light_nod%bc_name(i) .eq. CTR_sf_grp_name) then
+         iflag_icb_composition = iflag_sph_fill_center
+        else if ( light_nod%ibc_type(i) .eq. iflag_sph_2_center         &
+     &       .and. light_nod%bc_name(i) .eq. CTR_nod_grp_name) then
+         iflag_icb_composition = iflag_sph_fill_center
         end if
       end do
 !
@@ -364,4 +291,4 @@
 !
 ! -----------------------------------------------------------------------
 !
-      end module set_bc_sph_mhd
+      end module set_bc_sph_scalars



More information about the CIG-COMMITS mailing list