[cig-commits] [commit] Hiro_latest: Use structure for boundary condition list for surface groups (b00d4d4)

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


Repository : ssh://geoshell/calypso

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

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

commit b00d4d4459c43ae4f121892c44e6ad5362de2965
Author: Hiroaki Matsui <h_kemono at mac.com>
Date:   Wed Oct 9 18:45:41 2013 -0700

    Use structure for boundary condition list for surface groups


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

b00d4d4459c43ae4f121892c44e6ad5362de2965
 .../MHD_src/IO/check_read_bc_file.f90              |  12 +-
 .../MHD_src/IO/m_surf_data_list.f90                | 240 ++++++++++-----------
 .../MHD_src/IO/set_control_4_composition.f90       |  24 +--
 .../MHD_src/IO/set_control_4_magne.f90             |  30 +--
 .../MHD_src/IO/set_control_4_press.f90             |  16 +-
 .../MHD_src/IO/set_control_4_temp.f90              |  14 +-
 .../MHD_src/IO/set_control_4_velo.f90              |  33 +--
 .../MHD_src/IO/set_surface_group_types.f90         |  72 ++++---
 .../MHD_src/sph_MHD/set_bc_flag_sph_velo.f90       |  18 +-
 .../MHD_src/sph_MHD/set_bc_sph_mhd.f90             |  40 ++--
 10 files changed, 242 insertions(+), 257 deletions(-)

diff --git a/src/Fortran_libraries/MHD_src/IO/check_read_bc_file.f90 b/src/Fortran_libraries/MHD_src/IO/check_read_bc_file.f90
index 29dbd28..7c10150 100644
--- a/src/Fortran_libraries/MHD_src/IO/check_read_bc_file.f90
+++ b/src/Fortran_libraries/MHD_src/IO/check_read_bc_file.f90
@@ -33,9 +33,9 @@
 !
       if ( iflag_t_evo_4_temp .gt. id_no_evolution) then
         call set_serch_boundary_file_flag(iflag_boundary_file,          &
-     &    num_bc_e, ibc_e_type)
+     &      num_bc_e, ibc_e_type)
         call set_serch_boundary_file_flag(iflag_boundary_file,          &
-     &    num_bc_h_flux, ibc_h_flux_type)
+     &      h_flux_surf%num_bc, h_flux_surf%ibc_type)
       end if
 !
 ! ----  read boundary data for velocity
@@ -44,7 +44,7 @@
         call set_serch_boundary_file_flag(iflag_boundary_file,          &
      &      num_bc_v, ibc_v_type)
         call set_serch_boundary_file_flag(iflag_boundary_file,          &
-     &      num_bc_tq, ibc_tq_type)
+     &      torque_surf%num_bc, torque_surf%ibc_type)
 !
 !  set boundary conditions for pressure
 !
@@ -67,7 +67,7 @@
         call set_serch_boundary_file_flag(iflag_boundary_file,          &
      &      num_bc_b, ibc_b_type)
         call set_serch_boundary_file_flag(iflag_boundary_file,          &
-     &      num_bc_bs, ibc_bs_type)
+     &      magne_surf%num_bc, magne_surf%ibc_type)
 !
 ! ----  read boundary data for magnetic potential
 !
@@ -82,7 +82,7 @@
         call set_serch_boundary_file_flag(iflag_boundary_file,          &
      &      num_bc_vp, ibc_vp_type)
         call set_serch_boundary_file_flag(iflag_boundary_file,          &
-     &     num_bc_vps, ibc_vps_type)
+     &      a_potential_surf%num_bc, a_potential_surf%ibc_type)
 !
 ! ----  read boundary data for magnetic potential
 !
@@ -98,7 +98,7 @@
         call set_serch_boundary_file_flag(iflag_boundary_file,          &
      &      num_bc_j, ibc_j_type)
         call set_serch_boundary_file_flag(iflag_boundary_file,          &
-     &      num_bc_js, ibc_js_type)
+     &      current_surf%num_bc, current_surf%ibc_type)
       end if
 !
       end subroutine check_read_boundary_files
diff --git a/src/Fortran_libraries/MHD_src/IO/m_surf_data_list.f90 b/src/Fortran_libraries/MHD_src/IO/m_surf_data_list.f90
index 33a5799..ad2d7d6 100644
--- a/src/Fortran_libraries/MHD_src/IO/m_surf_data_list.f90
+++ b/src/Fortran_libraries/MHD_src/IO/m_surf_data_list.f90
@@ -1,25 +1,30 @@
-!m_surf_data_list.f90
-!     module m_surf_data_list
-!
-!     Written by H. Matsui on Feb., 2009
-!
-!      subroutine allocate_velo_surf_ctl
-!      subroutine allocate_press_surf_ctl
-!      subroutine allocate_temp_surf_ctl
-!      subroutine allocate_magne_surf_ctl
-!      subroutine allocate_vect_p_surf_ctl
-!      subroutine allocate_magp_surf_ctl
-!      subroutine allocate_current_surf_ctl
-!      subroutine allocate_d_scalar_surf_ctl
-!
-!      subroutine deallocate_velo_surf_ctl
-!      subroutine deallocate_press_surf_ctl
-!      subroutine deallocate_temp_surf_ctl
-!      subroutine deallocate_magne_surf_ctl
-!      subroutine deallocate_vect_p_surf_ctl
-!      subroutine deallocate_magp_surf_ctl
-!      subroutine deallocate_current_surf_ctl
-!      subroutine deallocate_composit_surf_ctl
+!>@file   m_surf_data_list.f90
+!!@brief  module m_surf_data_list
+!!
+!!@author H. Matsui
+!!@date Programmed by H. Matsui in 2009
+!
+!>@brief flux boundary condition lists for MHD dynamo model
+!!
+!!@verbatim
+!!      subroutine allocate_velo_surf_ctl
+!!      subroutine allocate_press_surf_ctl
+!!      subroutine allocate_temp_surf_ctl
+!!      subroutine allocate_magne_surf_ctl
+!!      subroutine allocate_vect_p_surf_ctl
+!!      subroutine allocate_magp_surf_ctl
+!!      subroutine allocate_current_surf_ctl
+!!      subroutine allocate_d_scalar_surf_ctl
+!
+!!      subroutine deallocate_velo_surf_ctl
+!!      subroutine deallocate_press_surf_ctl
+!!      subroutine deallocate_temp_surf_ctl
+!!      subroutine deallocate_magne_surf_ctl
+!!      subroutine deallocate_vecp_surf_ctl
+!!      subroutine deallocate_magp_surf_ctl
+!!      subroutine deallocate_current_surf_ctl
+!!      subroutine deallocate_composit_surf_ctl
+!!@endverbatim
 ! 
       module m_surf_data_list
 !
@@ -28,64 +33,79 @@
       implicit  none
 !
 !
-      integer (kind=kint) :: num_bc_tq
-      real (kind=kreal), allocatable :: bc_tq_magnitude(:)
-      integer (kind=kint), allocatable :: ibc_tq_type(:)
-      character (len=kchara), allocatable :: bc_tq_name(:)
+!>       Structure for surface group data list
+      type surface_bc_list_type
+!>       number of boundary condition list
+        integer (kind=kint) :: num_bc
+!>       Value for the boundary condition
+        real (kind=kreal), pointer :: bc_magnitude(:)
+!>       Type of the boundary condition
+        integer (kind=kint), pointer :: ibc_type(:)
+!>       Name of group to apply the boundary condition
+        character (len=kchara), pointer :: bc_name(:)
+      end type surface_bc_list_type
 !
-      integer (kind=kint) :: num_bc_wall
-      real (kind=kreal), allocatable :: bc_wall_magnitude(:)
-      integer (kind=kint), allocatable :: ibc_wall_type(:)
-      character (len=kchara), allocatable :: bc_wall_name(:)
+!>       Surface group data list for stresses
+      type(surface_bc_list_type), save :: torque_surf
+!>       Surface group data list for walls (special velocity)
+      type(surface_bc_list_type), save :: wall_surf
 !
-      integer (kind=kint) :: num_bc_h_flux
-      real (kind=kreal), allocatable :: bc_h_flux_magnitude(:)
-      integer (kind=kint), allocatable :: ibc_h_flux_type(:)
-      character (len=kchara), allocatable :: bc_h_flux_name(:)
+!>       Surface group data list for temperature
+      type(surface_bc_list_type), save :: h_flux_surf
+!>       Surface group data list for composition
+      type(surface_bc_list_type), save :: light_surf
 !
+!>       Surface group data list for magnetic field
+      type(surface_bc_list_type), save :: magne_surf
+!>       Surface group data list for magnetic vector potential
+      type(surface_bc_list_type), save :: a_potential_surf
+!>       Surface group data list for electrical potential
+      type(surface_bc_list_type), save :: e_potential_surf
+!>       Surface group data list for current density
+      type(surface_bc_list_type), save :: current_surf
 !
-      integer (kind=kint) :: num_bc_bs
-      real (kind=kreal),      allocatable :: bc_bs_magnitude(:)
-      integer (kind=kint),    allocatable :: ibc_bs_type(:)
-      character (len=kchara), allocatable :: bc_bs_name(:)
+!-----------------------------------------------------------------------
+!
+      contains 
 !
-      integer (kind=kint) :: num_bc_vps
-      real (kind=kreal), allocatable :: bc_vps_magnitude(:)
-      integer (kind=kint), allocatable :: ibc_vps_type(:)
-      character (len=kchara), allocatable :: bc_vps_name(:)
+!-----------------------------------------------------------------------
 !
-      integer (kind=kint) :: num_bc_js
-      real (kind=kreal),      allocatable :: bc_js_magnitude(:)
-      integer (kind=kint),    allocatable :: ibc_js_type(:)
-      character (len=kchara), allocatable :: bc_js_name(:)
+      subroutine alloc_surface_bc_type_ctl(surf_bc_list)
 !
-      integer (kind=kint) :: num_surf_magp
-      real (kind=kreal), allocatable :: surf_magp_magnitude(:)
-      integer (kind=kint), allocatable :: isurf_magp_type(:)
-      character (len=kchara), allocatable :: surf_magp_name(:)
+      type(surface_bc_list_type), intent(inout) :: surf_bc_list
 !
 !
-      integer (kind=kint) :: num_surf_composition
-      real (kind=kreal), allocatable :: surf_composit_magnitude(:)
-      integer (kind=kint), allocatable :: isurf_composit_type(:)
-      character (len=kchara), allocatable :: surf_composit_name(:)
+      allocate(surf_bc_list%bc_magnitude(surf_bc_list%num_bc))
+      allocate(surf_bc_list%ibc_type(surf_bc_list%num_bc))
+      allocate(surf_bc_list%bc_name(surf_bc_list%num_bc))
+!
+      if(surf_bc_list%num_bc .gt. 0) then
+        surf_bc_list%ibc_type =     0
+        surf_bc_list%bc_magnitude = 0.0d0
+      end if
+!
+      end subroutine alloc_surface_bc_type_ctl
 !
 !-----------------------------------------------------------------------
 !
-      contains 
+      subroutine dealloc_surface_bc_type_ctl(surf_bc_list)
+!
+      type(surface_bc_list_type), intent(inout) :: surf_bc_list
+!
+!
+      deallocate(surf_bc_list%bc_magnitude)
+      deallocate(surf_bc_list%ibc_type)
+      deallocate(surf_bc_list%bc_name)
 !
+      end subroutine dealloc_surface_bc_type_ctl
+!
+!-----------------------------------------------------------------------
 !-----------------------------------------------------------------------
 !
       subroutine allocate_velo_surf_ctl
 !
-      allocate(bc_tq_magnitude(num_bc_tq))
-      allocate(ibc_tq_type(num_bc_tq))
-      allocate(bc_tq_name(num_bc_tq))
 !
-      if(num_bc_tq .gt. 0) then
-        ibc_tq_type = 0
-        bc_tq_magnitude = 0.0d0
-      end if
+      call alloc_surface_bc_type_ctl(torque_surf)
 !
       end subroutine allocate_velo_surf_ctl
 !
@@ -93,11 +113,8 @@
 !
       subroutine allocate_press_surf_ctl
 !
-      allocate(bc_wall_magnitude(num_bc_wall))
-      allocate(bc_wall_name(    num_bc_wall))
-      allocate(ibc_wall_type(num_bc_wall))
 !
-      if(num_bc_wall .gt. 0) ibc_wall_type= 0
+      call alloc_surface_bc_type_ctl(wall_surf)
 !
       end subroutine allocate_press_surf_ctl
 !
@@ -105,14 +122,8 @@
 !
       subroutine allocate_temp_surf_ctl
 !
-      allocate(bc_h_flux_magnitude(num_bc_h_flux))
-      allocate(ibc_h_flux_type(num_bc_h_flux))
-      allocate(bc_h_flux_name(num_bc_h_flux))
 !
-      if(num_bc_h_flux .gt. 0) then
-        ibc_h_flux_type = 0
-        bc_h_flux_magnitude = 0.0d0
-      end if
+      call alloc_surface_bc_type_ctl(h_flux_surf)
 !
       end subroutine allocate_temp_surf_ctl
 !
@@ -120,14 +131,8 @@
 !
       subroutine allocate_magne_surf_ctl
 !
-      allocate(bc_bs_magnitude(num_bc_bs))
-      allocate(ibc_bs_type(num_bc_bs))
-      allocate(bc_bs_name(num_bc_bs))
 !
-      if(num_bc_bs .gt. 0) then
-        ibc_bs_type = 0
-        bc_bs_magnitude = 0.0d0
-      end if
+      call alloc_surface_bc_type_ctl(magne_surf)
 !
       end subroutine allocate_magne_surf_ctl
 !
@@ -135,14 +140,8 @@
 !
       subroutine allocate_vect_p_surf_ctl
 !
-      allocate(bc_vps_magnitude(num_bc_vps))
-      allocate(ibc_vps_type(num_bc_vps))
-      allocate(bc_vps_name(num_bc_vps))
 !
-      if(num_bc_vps .gt. 0) then
-        ibc_vps_type = 0
-        bc_vps_magnitude = 0.0d0
-      end if
+      call alloc_surface_bc_type_ctl(a_potential_surf)
 !
       end subroutine allocate_vect_p_surf_ctl
 !
@@ -150,14 +149,8 @@
 !
       subroutine allocate_magp_surf_ctl
 !
-      allocate(surf_magp_magnitude(num_surf_magp))
-      allocate(isurf_magp_type(num_surf_magp))
-      allocate(surf_magp_name(num_surf_magp))
 !
-      if(num_surf_magp .gt. 0) then
-        isurf_magp_type = 0
-        surf_magp_magnitude = 0.0d0
-      end if
+      call alloc_surface_bc_type_ctl(e_potential_surf)
 !
       end subroutine allocate_magp_surf_ctl
 !
@@ -165,14 +158,8 @@
 !
       subroutine allocate_current_surf_ctl
 !
-      allocate(bc_js_magnitude(num_bc_js))
-      allocate(ibc_js_type(num_bc_js))
-      allocate(bc_js_name(num_bc_js))
 !
-      if(num_bc_js .gt. 0) then
-        ibc_js_type = 0
-        bc_js_magnitude = 0.0d0
-      end if
+      call alloc_surface_bc_type_ctl(current_surf)
 !
       end subroutine allocate_current_surf_ctl
 !
@@ -180,9 +167,8 @@
 !
       subroutine allocate_d_scalar_surf_ctl
 !
-        allocate(surf_composit_magnitude(num_surf_composition))
-        allocate(isurf_composit_type(num_surf_composition))
-        allocate(surf_composit_name(num_surf_composition))
+!
+      call alloc_surface_bc_type_ctl(light_surf)
 !
       end subroutine allocate_d_scalar_surf_ctl
 !
@@ -191,9 +177,8 @@
 !
       subroutine deallocate_velo_surf_ctl
 !
-        deallocate(bc_tq_magnitude)
-        deallocate(ibc_tq_type)
-        deallocate(bc_tq_name)
+!
+      call dealloc_surface_bc_type_ctl(torque_surf)
 !
       end subroutine deallocate_velo_surf_ctl
 !
@@ -201,11 +186,8 @@
 !
        subroutine deallocate_press_surf_ctl
 !
-       if (num_bc_wall .ge.0) then
-        deallocate(bc_wall_magnitude)
-        deallocate(bc_wall_name)
-        deallocate(ibc_wall_type)
-       end if
+!
+      call dealloc_surface_bc_type_ctl(wall_surf)
 !
        end subroutine deallocate_press_surf_ctl
 !
@@ -213,9 +195,8 @@
 !
       subroutine deallocate_temp_surf_ctl
 !
-        deallocate(bc_h_flux_magnitude)
-        deallocate(ibc_h_flux_type)
-        deallocate(bc_h_flux_name)
+!
+      call dealloc_surface_bc_type_ctl(h_flux_surf)
 !
       end subroutine deallocate_temp_surf_ctl
 !
@@ -223,29 +204,26 @@
 !
       subroutine deallocate_magne_surf_ctl
 !
-        deallocate(bc_bs_magnitude)
-        deallocate(ibc_bs_type)
-        deallocate(bc_bs_name)
+!
+      call dealloc_surface_bc_type_ctl(magne_surf)
 !
       end subroutine deallocate_magne_surf_ctl
 !
 !-----------------------------------------------------------------------
 !
-      subroutine deallocate_vect_p_surf_ctl
+      subroutine deallocate_vecp_surf_ctl
+!
 !
-        deallocate(bc_vps_magnitude)
-        deallocate(ibc_vps_type)
-        deallocate(bc_vps_name)
+      call dealloc_surface_bc_type_ctl(a_potential_surf)
 !
-      end subroutine deallocate_vect_p_surf_ctl
+      end subroutine deallocate_vecp_surf_ctl
 !
 !-----------------------------------------------------------------------
 !
       subroutine deallocate_magp_surf_ctl
 !
-        deallocate(surf_magp_magnitude)
-        deallocate(isurf_magp_type)
-        deallocate(surf_magp_name)
+!
+      call dealloc_surface_bc_type_ctl(e_potential_surf)
 !
       end subroutine deallocate_magp_surf_ctl
 !
@@ -253,9 +231,8 @@
 !
       subroutine deallocate_current_surf_ctl
 !
-        deallocate(bc_js_magnitude)
-        deallocate(ibc_js_type)
-        deallocate(bc_js_name)
+!
+      call dealloc_surface_bc_type_ctl(current_surf)
 !
       end subroutine deallocate_current_surf_ctl
 !
@@ -263,9 +240,8 @@
 !
       subroutine deallocate_composit_surf_ctl
 !
-        deallocate(surf_composit_magnitude)
-        deallocate(isurf_composit_type)
-        deallocate(surf_composit_name)
+!
+      call dealloc_surface_bc_type_ctl(light_surf)
 !
       end subroutine deallocate_composit_surf_ctl
 !
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 2390fe1..1aecc4c 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
@@ -40,11 +40,11 @@
 !
 !
       if (iflag_t_evo_4_composit .eq. id_no_evolution) then
-        num_surf_composition = 0
+        light_surf%num_bc = 0
         num_bc_composit =   0
       else
         num_bc_composit = num_bc_composit_ctl
-        num_surf_composition = num_bc_grad_ds_ctl
+        light_surf%num_bc = num_bc_grad_ds_ctl
       end if
 !
 !   set boundary conditions for composition
@@ -83,27 +83,27 @@
 !   set boundary conditions for composition flux
 !
       if (iflag_debug .eq. iflag_full_msg)                              &
-     &       write(*,*) 'num_surf_composition ',num_surf_composition
-      if (num_surf_composition .gt. 0) then
+     &       write(*,*) 'light_surf%num_bc ',light_surf%num_bc
+      if (light_surf%num_bc .gt. 0) then
 !
         call allocate_d_scalar_surf_ctl
 !
-        surf_composit_name      = bc_grad_ds_name_ctl
-        surf_composit_magnitude = bc_grad_ds_magnitude_ctl
-        isurf_composit_type = 0
+        light_surf%bc_name      = bc_grad_ds_name_ctl
+        light_surf%bc_magnitude = bc_grad_ds_magnitude_ctl
+        light_surf%ibc_type = 0
 !
-        do i = 1, num_surf_composition
+        do i = 1, light_surf%num_bc
           call set_surf_group_types_scalar(bc_grad_ds_type_ctl(i),      &
-     &        isurf_composit_type(i) )
+     &        light_surf%ibc_type(i) )
         end do
 !
         call deallocate_sf_dscalar_ctl
 !
         if (iflag_debug .eq. iflag_full_msg) then
           write(*,*)  'i, isurf_c_type, surf_c_magnitude, surf_c_name'
-          do i = 1, num_surf_composition
-            write(*,*)  i, isurf_composit_type(i),                      &
-     &         surf_composit_magnitude(i), trim(surf_composit_name(i))
+          do i = 1, light_surf%num_bc
+            write(*,*)  i, light_surf%ibc_type(i),                      &
+     &         light_surf%bc_magnitude(i), trim(light_surf%bc_name(i))
           end do
         end if
       end if
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 f91448c..87f7d98 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
@@ -43,10 +43,10 @@
       if (iflag_t_evo_4_magne .eq. id_no_evolution                      &
      &       .and.  iflag_t_evo_4_vect_p .eq. id_no_evolution) then
         num_bc_b = 0
-        num_bc_bs = 0
+        magne_surf%num_bc = 0
       else
         num_bc_b = num_bc_b_ctl
-        num_bc_bs = num_bc_grad_b_ctl
+        magne_surf%num_bc = num_bc_grad_b_ctl
       end if
 !
 !   set boundary_conditons for magnetic field
@@ -103,32 +103,32 @@
 !
 !
       if (iflag_debug .ge. iflag_routine_msg)                           &
-     &           write(*,*) 'num_bc_bs ',num_bc_bs
-      if (num_bc_bs .gt. 0) then
+     &           write(*,*) 'magne_surf%num_bc ',magne_surf%num_bc
+      if (magne_surf%num_bc .gt. 0) then
 !
         call allocate_magne_surf_ctl
 !
-        bc_bs_name     =   bc_grad_b_name_ctl
-        bc_bs_magnitude =  bc_grad_b_magnitude_ctl
+        magne_surf%bc_name =       bc_grad_b_name_ctl
+        magne_surf%bc_magnitude =  bc_grad_b_magnitude_ctl
 !
-        do i = 1, num_bc_bs
+        do i = 1, magne_surf%num_bc
           call set_surf_group_types_vector(bc_grad_b_type_ctl(i),       &
-     &       ibc_bs_type(i))
+     &        magne_surf%ibc_type(i))
 !
           if (bc_grad_b_type_ctl(i) .eq. 'insulator' ) then
-            ibc_bs_type(i) = iflag_insulator
+            magne_surf%ibc_type(i) = iflag_insulator
           else if (bc_grad_b_type_ctl(i) .eq. 'sph_to_center' ) then
-            ibc_bs_type(i) = iflag_sph_2_center
+            magne_surf%ibc_type(i) = iflag_sph_2_center
           else if (bc_grad_b_type_ctl(i) .eq. 'pseudo_vacuum' ) then
-            ibc_bs_type(i) = iflag_pseudo_vacuum
+            magne_surf%ibc_type(i) = iflag_pseudo_vacuum
           end if
         end do
 !
         if (iflag_debug .ge. iflag_routine_msg) then
-          write(*,*) 'i, ibc_bs_type, bc_bs_magnitude, bc_bs_name'
-          do i = 1, num_bc_bs
-            write(*,*) i, ibc_bs_type(i), bc_bs_magnitude(i),           &
-     &                 trim(bc_bs_name(i))
+          write(*,*) 'i, magne_surf'
+          do i = 1, magne_surf%num_bc
+            write(*,*) i, magne_surf%ibc_type(i),                       &
+     &         magne_surf%bc_magnitude(i), trim(magne_surf%bc_name(i))
           end do
         end if
       end if
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 9055b48..3a568a5 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
@@ -43,10 +43,10 @@
 !
       if (iflag_t_evo_4_velo .eq. id_no_evolution) then
         num_bc_p = 0
-        num_bc_wall = 0
+        wall_surf%num_bc = 0
       else
         num_bc_p = num_bc_p_ctl
-        num_bc_wall = num_bc_grad_p_ctl
+        wall_surf%num_bc = num_bc_grad_p_ctl
       end if
 !
 !  set boundary conditions for pressure
@@ -83,19 +83,19 @@
 !
 !
 !
-      if (num_bc_wall .gt. 0) then
+      if (wall_surf%num_bc .gt. 0) then
 !
         call allocate_press_surf_ctl
 !
-        bc_wall_magnitude =  bc_grad_p_magnitude_ctl
-        bc_wall_name      =  bc_grad_p_name_ctl
+        wall_surf%bc_magnitude =  bc_grad_p_magnitude_ctl
+        wall_surf%bc_name =       bc_grad_p_name_ctl
 !
-        do i = 1, num_bc_wall
+        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),       &
-     &       ibc_wall_type(i) )
+     &        wall_surf%ibc_type(i) )
           call set_surf_wall_group_types(bc_grad_p_type_ctl(i),         &
-     &       ibc_wall_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 896957f..ff5d0c1 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
@@ -41,10 +41,10 @@
 !
       if (iflag_t_evo_4_temp .eq. id_no_evolution) then
         num_bc_e = 0
-        num_bc_h_flux = 0
+        h_flux_surf%num_bc = 0
       else
         num_bc_e =      num_bc_e_ctl
-        num_bc_h_flux = num_bc_h_flux_ctl
+        h_flux_surf%num_bc = num_bc_h_flux_ctl
       end if
 !
 !   set boundary conditions for temperature
@@ -81,16 +81,16 @@
 !
 !   set boundary conditions for heat flux
 !
-      if (num_bc_h_flux .gt. 0) then
+      if (h_flux_surf%num_bc .gt. 0) then
 !
         call allocate_temp_surf_ctl
 !
-        bc_h_flux_magnitude = bc_h_flux_magnitude_ctl
-        bc_h_flux_name     =  bc_h_flux_name_ctl
+        h_flux_surf%bc_magnitude = bc_h_flux_magnitude_ctl
+        h_flux_surf%bc_name =      bc_h_flux_name_ctl
 !
-        do i = 1, num_bc_h_flux
+        do i = 1, h_flux_surf%num_bc
           call set_surf_group_types_scalar(bc_h_flux_type_ctl(i),       &
-     &            ibc_h_flux_type(i))
+     &            h_flux_surf%ibc_type(i))
         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 58c1350..9d89fae 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
@@ -43,10 +43,10 @@
 !
       if (iflag_t_evo_4_velo .eq. id_no_evolution) then
         num_bc_v = 0
-        num_bc_tq = 0
+        torque_surf%num_bc = 0
       else
         num_bc_v =  num_bc_v_ctl
-        num_bc_tq = num_bc_torque_ctl
+        torque_surf%num_bc = num_bc_torque_ctl
       end if
 !
 !  set boundary conditions for velocity
@@ -118,34 +118,35 @@
 !
 !
       if(iflag_debug .eq. iflag_full_msg)                               &
-     &            write(*,*) 'num_bc_tq', num_bc_tq
-      if(num_bc_tq .gt. 0) then
+     &            write(*,*) 'torque_surf%num_bc', torque_surf%num_bc
+      if(torque_surf%num_bc .gt. 0) then
 !
         call allocate_velo_surf_ctl
 !
-        bc_tq_name      =  bc_torque_name_ctl
-        bc_tq_magnitude =  bc_torque_magnitude_ctl
+        torque_surf%bc_name =      bc_torque_name_ctl
+        torque_surf%bc_magnitude = bc_torque_magnitude_ctl
 !
-        do i = 1, num_bc_tq
+        do i = 1, torque_surf%num_bc
           call set_surf_group_types_vector(bc_torque_type_ctl(i),       &
-     &       ibc_tq_type(i) )
+     &       torque_surf%ibc_type(i) )
           call set_stress_free_group_types(bc_torque_type_ctl(i),       &
-     &       ibc_tq_type(i) )
+     &       torque_surf%ibc_type(i) )
 !
           if      (bc_torque_type_ctl(i) .eq. 'free_slip_sph' ) then
-            ibc_tq_type(i) = iflag_free_sph
+            torque_surf%ibc_type(i) = iflag_free_sph
           else if (bc_torque_type_ctl(i) .eq. 'non_slip_sph' ) then
-            ibc_tq_type(i) = iflag_non_slip_sph
+            torque_surf%ibc_type(i) = iflag_non_slip_sph
           else if (bc_torque_type_ctl(i) .eq. 'rot_inner_core' ) then
-            ibc_tq_type(i) = iflag_rotatable_icore
+            torque_surf%ibc_type(i) = iflag_rotatable_icore
           end if
         end do
 !
         if (iflag_debug .eq. iflag_full_msg) then
-          write(*,*) 'i, ibc_tq_type, bc_tq_magnitude, bc_tq_name'
-          do i = 1, num_bc_tq
-            write(*,*)  i, ibc_tq_type(i), bc_tq_magnitude(i),          &
-     &                 trim(bc_tq_name(i))
+          write(*,*) 'i, torque_surf'
+          do i = 1, torque_surf%num_bc
+            write(*,*)  i, torque_surf%ibc_type(i),                     &
+     &                 torque_surf%bc_magnitude(i),                     &
+     &                 trim(torque_surf%bc_name(i))
           end do
         end if
       end if
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 2bd187a..446e76e 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,21 +33,24 @@
       character (len=kchara), intent(in) :: bc_type_ctl
       integer(kind = kint), intent(inout) :: ibc_type
 !
-         if ( bc_type_ctl .eq. 'fixed_ctl' ) then
-          ibc_type =  iflag_surf_fix_s
-         else if ( bc_type_ctl .eq. 'fixed_dat' ) then
-          ibc_type = -iflag_surf_fix_s
-         else if ( bc_type_ctl .eq. 'sgs_correct' ) then
-          ibc_type = iflag_bc_sgs_commute_s
-!
-         else if ( bc_type_ctl .eq. 'grad_ctl' ) then
-          ibc_type =  iflag_fixed_grad_s
-         else if ( bc_type_ctl .eq. 'grad_dat' ) then
-          ibc_type = -iflag_fixed_grad_s
-!
-         else if ( bc_type_ctl .eq. 'lead_grad' ) then
-          ibc_type = iflag_lead_grad_s
-         end if
+      if      ( bc_type_ctl .eq. 'fixed_ctl'                            &
+     &    .or.  bc_type_ctl .eq. 'fixed') then
+        ibc_type =  iflag_surf_fix_s
+      else if ( bc_type_ctl .eq. 'fixed_dat' ) then
+        ibc_type = -iflag_surf_fix_s
+      else if ( bc_type_ctl .eq. 'sgs_correct' ) then
+        ibc_type = iflag_bc_sgs_commute_s
+!
+      else if ( bc_type_ctl .eq. 'grad_ctl'                             &
+     &    .or.  bc_type_ctl .eq. 'grad'                                 &
+     &    .or.  bc_type_ctl .eq. 'gradient' ) then
+        ibc_type =  iflag_fixed_grad_s
+      else if ( bc_type_ctl .eq. 'grad_dat' ) then
+        ibc_type = -iflag_fixed_grad_s
+!
+      else if ( bc_type_ctl .eq. 'lead_grad' ) then
+        ibc_type = iflag_lead_grad_s
+      end if
 !
       end subroutine set_surf_group_types_scalar
 !
@@ -58,11 +61,14 @@
       character (len=kchara), intent(in) :: bc_type_ctl
       integer(kind = kint), intent(inout) :: ibc_type
 !
-         if ( bc_type_ctl .eq. 'fix_ctl_x' ) then
+         if      ( bc_type_ctl .eq. 'fix_ctl_x'                         &
+     &        .or. bc_type_ctl .eq. 'fix_x') then
           ibc_type = iflag_surf_fix_x
-         else if ( bc_type_ctl .eq. 'fix_ctl_y' ) then
+         else if ( bc_type_ctl .eq. 'fix_ctl_y'                         &
+     &        .or. bc_type_ctl .eq. 'fix_y' ) then
           ibc_type = iflag_surf_fix_y
-         else if ( bc_type_ctl .eq. 'fix_ctl_z' ) then
+         else if ( bc_type_ctl .eq. 'fix_ctl_z'                         &
+     &        .or. bc_type_ctl .eq. 'fix_z' ) then
           ibc_type = iflag_surf_fix_z
          else if ( bc_type_ctl .eq. 'fix_dat_x' ) then
           ibc_type = -iflag_surf_fix_x
@@ -122,21 +128,6 @@
 !
 !-----------------------------------------------------------------------
 !
-      subroutine set_pseudo_vacuum_group_types(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. 'pseudo_vacuum_in' ) then
-          ibc_type = iflag_surf_qvc_sph_in
-         else if ( bc_type_ctl .eq. 'pseudo_vacuum_out' ) then
-          ibc_type = iflag_surf_qvc_sph_out
-         end if
-!
-      end subroutine set_pseudo_vacuum_group_types
-!
-!-----------------------------------------------------------------------
-!
       subroutine set_surf_wall_group_types(bc_type_ctl, ibc_type)
 !
       character (len=kchara), intent(in) :: bc_type_ctl
@@ -155,6 +146,21 @@
 !
 !-----------------------------------------------------------------------
 !
+      subroutine set_pseudo_vacuum_group_types(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. 'pseudo_vacuum_in' ) then
+          ibc_type = iflag_surf_qvc_sph_in
+         else if ( bc_type_ctl .eq. 'pseudo_vacuum_out' ) then
+          ibc_type = iflag_surf_qvc_sph_out
+         end if
+!
+      end subroutine set_pseudo_vacuum_group_types
+!
+!-----------------------------------------------------------------------
+!
       subroutine set_surf_infty_group_types(bc_type_ctl, ibc_type)
 !
       character (len=kchara), intent(in) :: bc_type_ctl
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 daf4b9d..3590905 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
@@ -50,11 +50,12 @@
         end if
       end do
 !
-      do i = 1, num_bc_tq
+      do i = 1, torque_surf%num_bc
         if(iflag_icb_velocity .ne. iflag_fixed_velo) exit
-        if    (bc_tq_name(i) .eq. 'ICB_surf'                            &
-     &    .or. bc_tq_name(i) .eq. 'ICB') then 
-          call set_sph_velo_ICB_flag(ibc_tq_type(i), bc_tq_magnitude(i))
+        if    (torque_surf%bc_name(i) .eq. 'ICB_surf'                   &
+     &    .or. torque_surf%bc_name(i) .eq. 'ICB') then
+          call set_sph_velo_ICB_flag(torque_surf%ibc_type(i),           &
+     &        torque_surf%bc_magnitude(i))
         end if
       end do
 !
@@ -67,11 +68,12 @@
         end if
       end do
 !
-      do i = 1, num_bc_tq
+      do i = 1, torque_surf%num_bc
         if(iflag_cmb_velocity .ne. iflag_fixed_velo) exit
-        if(     bc_tq_name(i) .eq. 'CMB_surf'                           &
-     &     .or. bc_tq_name(i) .eq. 'CMB') then 
-          call set_sph_velo_CMB_flag(ibc_tq_type(i), bc_tq_magnitude(i))
+        if(     torque_surf%bc_name(i) .eq. 'CMB_surf'                  &
+     &     .or. torque_surf%bc_name(i) .eq. 'CMB') then 
+          call set_sph_velo_CMB_flag(torque_surf%ibc_type(i),           &
+     &        torque_surf%bc_magnitude(i))
         end if
       end do
 !
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 6cfa9fc..e67d15d 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
@@ -81,22 +81,22 @@
       call allocate_temp_bc_array( nidx_rj(2) )
 !
       if(iflag_debug .gt. 0) then
-        write(*,*) 'num_bc_h_flux', num_bc_h_flux
-        write(*,*) 'ibc_h_flux_type', ibc_h_flux_type
-        write(*,*) 'bc_h_flux_magnitude', bc_h_flux_magnitude
+        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
       end if
 !
-      do i = 1, num_bc_h_flux
-        if ( ibc_h_flux_type(i)  .eq. iflag_fixed_grad_s) then
+      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,                        &
-     &        bc_h_flux_name(i), bc_h_flux_magnitude(i),                &
+     &        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,                        &
-     &        bc_h_flux_name(i), bc_h_flux_magnitude(i),                &
+     &        h_flux_surf%bc_name(i), h_flux_surf%bc_magnitude(i),      &
      &        nidx_rj(2), h_flux_CMB_bc, iflag_cmb_temp)
-        else if (ibc_h_flux_type(i)  .eq. -iflag_fixed_grad_s) then
+        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)
@@ -210,21 +210,21 @@
       end do
 !
 !
-      do i = 1, num_bc_bs
-        if(bc_bs_name(i) .eq. 'ICB') then
-          if(ibc_bs_type(i) .eq. iflag_pseudo_vacuum) then
+      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(bc_bs_name(i) .eq. 'CMB') then
-          if(ibc_bs_type(i) .eq. iflag_pseudo_vacuum) then
+        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(bc_bs_name(i) .eq. 'to_Center') then
-          if      (ibc_bs_type(i) .eq. iflag_sph_2_center) then
+        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
@@ -250,17 +250,17 @@
 !
 !      Boundary setting using surface group data
 !
-      do i = 1, num_surf_composition
-        if (isurf_composit_type(i)  .eq. iflag_fixed_grad_s) then
+      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,                        &
-     &        surf_composit_name(i), surf_composit_magnitude(i),        &
+     &        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,                        &
-     &        surf_composit_name(i), surf_composit_magnitude(i),        &
+     &        light_surf%bc_name(i), light_surf%bc_magnitude(i),        &
      &        nidx_rj(2), c_flux_CMB_bc, iflag_cmb_composition)
-        else if (isurf_composit_type(i)  .eq. -iflag_fixed_grad_s)      &
+        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,             &



More information about the CIG-COMMITS mailing list