[cig-commits] [commit] Hiro_latest: Use structures for boundary condition list for node groups (4f8e9dd)

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


Repository : ssh://geoshell/calypso

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

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

commit 4f8e9ddab96d21667c7f43e549075bbaccf008ba
Author: Hiroaki Matsui <h_kemono at mac.com>
Date:   Wed Oct 9 22:49:45 2013 -0700

    Use structures for boundary condition list for node groups


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

4f8e9ddab96d21667c7f43e549075bbaccf008ba
 .../MHD_src/IO/check_read_bc_file.f90              |  18 +-
 .../MHD_src/IO/m_bc_data_list.f90                  | 240 +++++++++------------
 .../MHD_src/IO/m_surf_data_list.f90                |   4 +-
 .../MHD_src/IO/set_control_4_composition.f90       |  26 +--
 .../MHD_src/IO/set_control_4_magne.f90             |  48 ++---
 .../MHD_src/IO/set_control_4_press.f90             |  28 +--
 .../MHD_src/IO/set_control_4_temp.f90              |  30 +--
 .../MHD_src/IO/set_control_4_velo.f90              |  60 +++---
 .../MHD_src/sph_MHD/set_bc_flag_sph_velo.f90       |  14 +-
 .../MHD_src/sph_MHD/set_bc_sph_mhd.f90             |  50 ++---
 10 files changed, 244 insertions(+), 274 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 7c10150..22ceba7 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,7 +33,7 @@
 !
       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)
+     &      temp_nod%num_bc, temp_nod%ibc_type)
         call set_serch_boundary_file_flag(iflag_boundary_file,          &
      &      h_flux_surf%num_bc, h_flux_surf%ibc_type)
       end if
@@ -42,21 +42,21 @@
 !
       if ( iflag_t_evo_4_velo .gt. id_no_evolution) then
         call set_serch_boundary_file_flag(iflag_boundary_file,          &
-     &      num_bc_v, ibc_v_type)
+     &      velo_nod%num_bc, velo_nod%ibc_type)
         call set_serch_boundary_file_flag(iflag_boundary_file,          &
      &      torque_surf%num_bc, torque_surf%ibc_type)
 !
 !  set boundary conditions for pressure
 !
         call set_serch_boundary_file_flag(iflag_boundary_file,          &
-     &      num_bc_p, ibc_p_type)
+     &      press_nod%num_bc, press_nod%ibc_type)
       end if
 !
 ! ----  read boundary data for dummy scalar
 !
       if ( iflag_t_evo_4_composit .gt. id_no_evolution) then
         call set_serch_boundary_file_flag(iflag_boundary_file,          &
-     &      num_bc_composit, ibc_composit_type)
+     &      light_nod%num_bc, light_nod%ibc_type)
       end if
 !
 ! ----  read boundary data for magnetic field
@@ -65,14 +65,14 @@
      &      .or. iflag_t_evo_4_vect_p .gt. id_no_evolution) then
 !
         call set_serch_boundary_file_flag(iflag_boundary_file,          &
-     &      num_bc_b, ibc_b_type)
+     &      magne_nod%num_bc, magne_nod%ibc_type)
         call set_serch_boundary_file_flag(iflag_boundary_file,          &
      &      magne_surf%num_bc, magne_surf%ibc_type)
 !
 ! ----  read boundary data for magnetic potential
 !
         call set_serch_boundary_file_flag(iflag_boundary_file,          &
-     &      num_bc_mag_p, ibc_mag_p_type)
+     &      e_potential_nod%num_bc, e_potential_nod%ibc_type)
       end if
 !
 ! ----  read boundary data for vector potential
@@ -80,14 +80,14 @@
       if ( iflag_t_evo_4_vect_p .gt. id_no_evolution) then
 !
         call set_serch_boundary_file_flag(iflag_boundary_file,          &
-     &      num_bc_vp, ibc_vp_type)
+     &      a_potential_nod%num_bc, a_potential_nod%ibc_type)
         call set_serch_boundary_file_flag(iflag_boundary_file,          &
      &      a_potential_surf%num_bc, a_potential_surf%ibc_type)
 !
 ! ----  read boundary data for magnetic potential
 !
         call set_serch_boundary_file_flag(iflag_boundary_file,          &
-     &      num_bc_mag_p, ibc_mag_p_type)
+     &      e_potential_nod%num_bc, e_potential_nod%ibc_type)
       end if
 !
 ! ----  read boundary data for current density
@@ -96,7 +96,7 @@
      &      .or. iflag_t_evo_4_vect_p .gt. id_no_evolution) then
 !
         call set_serch_boundary_file_flag(iflag_boundary_file,          &
-     &      num_bc_j, ibc_j_type)
+     &      current_nod%num_bc, current_nod%ibc_type)
         call set_serch_boundary_file_flag(iflag_boundary_file,          &
      &      current_surf%num_bc, current_surf%ibc_type)
       end if
diff --git a/src/Fortran_libraries/MHD_src/IO/m_bc_data_list.f90 b/src/Fortran_libraries/MHD_src/IO/m_bc_data_list.f90
index 8496c47..1370146 100644
--- a/src/Fortran_libraries/MHD_src/IO/m_bc_data_list.f90
+++ b/src/Fortran_libraries/MHD_src/IO/m_bc_data_list.f90
@@ -1,93 +1,111 @@
+!>@file   m_bc_data_list.f90
+!!@brief  module m_bc_data_list
+!!
+!!@author H. Matsui
+!!@date Programmed by H. Matsui in 2009
+!
+!>@brief  Boundary condition lists for MHD dynamo model
+!!
+!!@verbatim
+!!      subroutine allocate_nod_bc_list_temp
+!!      subroutine allocate_nod_bc_list_velo
+!!      subroutine allocate_nod_bc_list_press
+!!      subroutine allocate_nod_bc_list_vecp
+!!      subroutine allocate_nod_bc_list_magne
+!!      subroutine allocate_nod_bc_list_mag_p
+!!      subroutine allocate_nod_bc_list_j
+!!      subroutine allocate_nod_bc_list_composit
+!!
+!!      subroutine deallocate_nod_bc_list_temp
+!!      subroutine deallocate_nod_bc_list_velo
+!!      subroutine deallocate_nod_bc_list_press
+!!      subroutine deallocate_nod_bc_list_vecp
+!!      subroutine deallocate_nod_bc_list_magne
+!!      subroutine deallocate_nod_bc_list_mag_p
+!!      subroutine deallocate_nod_bc_list_j
+!!      subroutine deallocate_nod_bc_list_composit
+!!@endverbatim
 !
-!      module m_bc_data_list
+      module m_bc_data_list
 !
-!      Written by H. Matsui on Jan., 2009
+      use m_precision
 !
-!      subroutine allocate_nod_bc_list_temp
-!      subroutine allocate_nod_bc_list_velo
-!      subroutine allocate_nod_bc_list_press
-!      subroutine allocate_nod_bc_list_vecp
-!      subroutine allocate_nod_bc_list_magne
-!      subroutine allocate_nod_bc_list_mag_p
-!      subroutine allocate_nod_bc_list_j
-!      subroutine allocate_nod_bc_list_composit
+      implicit  none
 !
-!      subroutine deallocate_nod_bc_list_temp
-!      subroutine deallocate_nod_bc_list_velo
-!      subroutine deallocate_nod_bc_list_press
-!      subroutine deallocate_nod_bc_list_vecp
-!      subroutine deallocate_nod_bc_list_magne
-!      subroutine deallocate_nod_bc_list_mag_p
-!      subroutine deallocate_nod_bc_list_j
-!      subroutine deallocate_nod_bc_list_composit
 !
-      module m_bc_data_list
+!>       Structure for surface group data list
+      type nod_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 nod_bc_list_type
 !
-      use m_precision
+!>       Node group data list for velocity
+      type(nod_bc_list_type), save :: velo_nod
+!>       Node group data list for pressure
+      type(nod_bc_list_type), save :: press_nod
 !
-      implicit  none
+!>       Node group data list for temperarure
+      type(nod_bc_list_type), save :: temp_nod
+!>       Node group data list for composition
+      type(nod_bc_list_type), save :: light_nod
 !
+!>       Node group data list for magnetic field
+      type(nod_bc_list_type), save :: magne_nod
+!>       Node group data list for magnetic vector potential
+      type(nod_bc_list_type), save :: a_potential_nod
+!>       Node group data list for electric scalar potential
+      type(nod_bc_list_type), save :: e_potential_nod
+!>       Node group data list for current density
+      type(nod_bc_list_type), save :: current_nod
 !
-      integer (kind=kint) :: num_bc_e
-      real (kind=kreal),      allocatable :: bc_e_magnitude(:)
-      integer (kind=kint),    allocatable :: ibc_e_type(:)
-      character (len=kchara), allocatable :: bc_e_name(:)
+! -----------------------------------------------------------------------
 !
+      contains 
 !
-      integer (kind=kint) :: num_bc_v
-      real (kind=kreal),      allocatable :: bc_v_magnitude(:)
-      integer (kind=kint),    allocatable :: ibc_v_type(:)
-      character (len=kchara), allocatable :: bc_v_name(:)
+! -----------------------------------------------------------------------
 !
-      integer (kind=kint) :: num_bc_p
-      real (kind=kreal),      allocatable :: bc_p_magnitude(:)
-      integer (kind=kint),    allocatable :: ibc_p_type(:)
-      character (len=kchara), allocatable :: bc_p_name(:)
+      subroutine alloc_bc_type_ctl(nod_bc_list)
 !
+      type(nod_bc_list_type), intent(inout) :: nod_bc_list
 !
-      integer (kind=kint) :: num_bc_vp
-      real (kind=kreal),      allocatable :: bc_vp_magnitude(:)
-      integer (kind=kint),    allocatable :: ibc_vp_type(:)
-      character (len=kchara), allocatable :: bc_vp_name(:)
 !
-      integer (kind=kint) :: num_bc_b
-      real (kind=kreal),      allocatable :: bc_b_magnitude(:)
-      integer (kind=kint),    allocatable :: ibc_b_type(:)
-      character (len=kchara), allocatable :: bc_b_name(:)
+      allocate(nod_bc_list%bc_magnitude(nod_bc_list%num_bc))
+      allocate(nod_bc_list%ibc_type(nod_bc_list%num_bc))
+      allocate(nod_bc_list%bc_name(nod_bc_list%num_bc))
 !
-      integer (kind=kint) :: num_bc_j
-      real (kind=kreal),      allocatable :: bc_j_magnitude(:)
-      integer (kind=kint),    allocatable :: ibc_j_type(:)
-      character (len=kchara), allocatable :: bc_j_name(:)
+      if(nod_bc_list%num_bc .gt. 0) then
+        nod_bc_list%ibc_type =     0
+        nod_bc_list%bc_magnitude = 0.0d0
+      end if
 !
+      end subroutine alloc_bc_type_ctl
 !
-      integer (kind=kint) :: num_bc_mag_p
-      real (kind=kreal), allocatable :: bc_mag_p_magnitude(:)
-      integer (kind=kint), allocatable :: ibc_mag_p_type(:)
-      character (len=kchara), allocatable :: bc_mag_p_name(:)
+!-----------------------------------------------------------------------
 !
+      subroutine dealloc_bc_type_ctl(nod_bc_list)
 !
-      integer (kind=kint) :: num_bc_composit
-      real (kind=kreal), allocatable :: bc_composit_magnitude(:)
-      integer (kind=kint), allocatable :: ibc_composit_type(:)
-      character (len=kchara), allocatable :: bc_composit_name(:)
+      type(nod_bc_list_type), intent(inout) :: nod_bc_list
 !
-! -----------------------------------------------------------------------
 !
-      contains 
+      deallocate(nod_bc_list%bc_magnitude)
+      deallocate(nod_bc_list%ibc_type)
+      deallocate(nod_bc_list%bc_name)
 !
-! -----------------------------------------------------------------------
+      end subroutine dealloc_bc_type_ctl
+!
+!-----------------------------------------------------------------------
+!-----------------------------------------------------------------------
 !
       subroutine allocate_nod_bc_list_temp
 !
-        allocate(bc_e_name(num_bc_e))
-        allocate(bc_e_magnitude(num_bc_e))
-        allocate(ibc_e_type(num_bc_e))
 !
-        if(num_bc_e .gt. 0) then
-          ibc_e_type = 0
-          bc_e_magnitude = 0.0d0
-        end if
+      call alloc_bc_type_ctl(temp_nod)
 !
       end subroutine allocate_nod_bc_list_temp
 !
@@ -95,14 +113,8 @@
 !
       subroutine allocate_nod_bc_list_velo
 !
-        allocate(bc_v_name(num_bc_v))
-        allocate(bc_v_magnitude(num_bc_v))
-        allocate(ibc_v_type(num_bc_v))
 !
-        if(num_bc_v .gt. 0) then
-          ibc_v_type = 0
-          bc_v_magnitude = 0.0d0
-        end if
+      call alloc_bc_type_ctl(velo_nod)
 !
       end subroutine allocate_nod_bc_list_velo
 !
@@ -110,14 +122,8 @@
 !
       subroutine allocate_nod_bc_list_press
 !
-        allocate(bc_p_name(num_bc_p))
-        allocate(bc_p_magnitude(num_bc_p))
-        allocate(ibc_p_type(num_bc_p))
 !
-        if(num_bc_p .gt. 0) then
-          ibc_p_type = 0
-          bc_p_magnitude = 0.0d0
-        end if
+      call alloc_bc_type_ctl(press_nod)
 !
       end subroutine allocate_nod_bc_list_press
 !
@@ -125,14 +131,8 @@
 !
       subroutine allocate_nod_bc_list_vecp
 !
-        allocate(bc_vp_name(num_bc_vp))
-        allocate(bc_vp_magnitude(num_bc_vp))
-        allocate(ibc_vp_type(num_bc_vp))
 !
-        if(num_bc_vp .gt. 0) then
-          ibc_vp_type = 0
-          bc_vp_magnitude = 0.0d0
-        end if
+      call alloc_bc_type_ctl(a_potential_nod)
 !
       end subroutine allocate_nod_bc_list_vecp
 !
@@ -140,14 +140,8 @@
 !
       subroutine allocate_nod_bc_list_magne
 !
-        allocate(bc_b_name(num_bc_b))
-        allocate(bc_b_magnitude(num_bc_b))
-        allocate(ibc_b_type(num_bc_b))
 !
-        if(num_bc_b .gt. 0) then
-          ibc_b_type = 0
-          bc_b_magnitude = 0.0d0
-        end if
+      call alloc_bc_type_ctl(magne_nod)
 !
       end subroutine allocate_nod_bc_list_magne
 !
@@ -155,14 +149,8 @@
 !
       subroutine allocate_nod_bc_list_j
 !
-        allocate(bc_j_name(num_bc_j))
-        allocate(bc_j_magnitude(num_bc_j))
-        allocate(ibc_j_type(num_bc_j))
 !
-        if(num_bc_j .gt. 0) then
-          ibc_j_type = 0
-          bc_j_magnitude = 0.0d0
-        end if
+      call alloc_bc_type_ctl(current_nod)
 !
       end subroutine allocate_nod_bc_list_j
 !
@@ -170,14 +158,8 @@
 !
       subroutine allocate_nod_bc_list_mag_p
 !
-        allocate(bc_mag_p_name(num_bc_mag_p))
-        allocate(bc_mag_p_magnitude(num_bc_mag_p))
-        allocate(ibc_mag_p_type(num_bc_mag_p))
 !
-        if(num_bc_mag_p .gt. 0) then
-          ibc_mag_p_type = 0
-          bc_mag_p_magnitude = 0.0d0
-        end if
+      call alloc_bc_type_ctl(e_potential_nod)
 !
       end subroutine allocate_nod_bc_list_mag_p
 !
@@ -185,14 +167,8 @@
 !
       subroutine allocate_nod_bc_list_composit
 !
-        allocate(bc_composit_magnitude(num_bc_composit))
-        allocate(ibc_composit_type(num_bc_composit))
-        allocate(bc_composit_name(num_bc_composit))
 !
-        if(num_bc_composit .gt. 0) then
-          ibc_composit_type = 0
-          bc_composit_magnitude = 0.0d0
-        end if
+      call alloc_bc_type_ctl(light_nod)
 !
       end subroutine allocate_nod_bc_list_composit
 !
@@ -201,9 +177,8 @@
 !
       subroutine deallocate_nod_bc_list_temp
 !
-        deallocate(bc_e_name)
-        deallocate(bc_e_magnitude)
-        deallocate(ibc_e_type)
+!
+      call dealloc_bc_type_ctl(temp_nod)
 !
       end subroutine deallocate_nod_bc_list_temp
 !
@@ -211,9 +186,8 @@
 !
       subroutine deallocate_nod_bc_list_velo
 !
-        deallocate(bc_v_name)
-        deallocate(bc_v_magnitude)
-        deallocate(ibc_v_type)
+!
+      call dealloc_bc_type_ctl(velo_nod)
 !
       end subroutine deallocate_nod_bc_list_velo
 !
@@ -221,9 +195,8 @@
 !
       subroutine deallocate_nod_bc_list_press
 !
-        deallocate(bc_p_name)
-        deallocate(bc_p_magnitude)
-        deallocate(ibc_p_type)
+!
+      call dealloc_bc_type_ctl(press_nod)
 !
       end subroutine deallocate_nod_bc_list_press
 !
@@ -231,9 +204,8 @@
 !
       subroutine deallocate_nod_bc_list_vecp
 !
-        deallocate(bc_vp_name)
-        deallocate(bc_vp_magnitude)
-        deallocate(ibc_vp_type)
+!
+      call dealloc_bc_type_ctl(a_potential_nod)
 !
       end subroutine deallocate_nod_bc_list_vecp
 !
@@ -241,9 +213,8 @@
 !
       subroutine deallocate_nod_bc_list_magne
 !
-        deallocate(bc_b_name)
-        deallocate(bc_b_magnitude)
-        deallocate(ibc_b_type)
+!
+      call dealloc_bc_type_ctl(magne_nod)
 !
       end subroutine deallocate_nod_bc_list_magne
 !
@@ -251,9 +222,8 @@
 !
       subroutine deallocate_nod_bc_list_mag_p
 !
-        deallocate(bc_mag_p_name)
-        deallocate(bc_mag_p_magnitude)
-        deallocate(ibc_mag_p_type)
+!
+      call dealloc_bc_type_ctl(e_potential_nod)
 !
       end subroutine deallocate_nod_bc_list_mag_p
 !
@@ -261,9 +231,8 @@
 !
       subroutine deallocate_nod_bc_list_j
 !
-        deallocate(bc_j_name)
-        deallocate(bc_j_magnitude)
-        deallocate(ibc_j_type)
+!
+      call dealloc_bc_type_ctl(current_nod)
 !
       end subroutine deallocate_nod_bc_list_j
 !
@@ -271,9 +240,8 @@
 !
       subroutine deallocate_nod_bc_list_composit
 !
-        deallocate(bc_composit_magnitude)
-        deallocate(ibc_composit_type)
-        deallocate(bc_composit_name)
+!
+      call dealloc_bc_type_ctl(light_nod)
 !
       end subroutine deallocate_nod_bc_list_composit
 !
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 ad2d7d6..a4e37fe 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
@@ -15,7 +15,7 @@
 !!      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
@@ -47,7 +47,7 @@
 !
 !>       Surface group data list for stresses
       type(surface_bc_list_type), save :: torque_surf
-!>       Surface group data list for walls (special velocity)
+!>       Surface group data list for pressure
       type(surface_bc_list_type), save :: wall_surf
 !
 !>       Surface group data list for temperature
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 1aecc4c..cc7bd55 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,41 +40,41 @@
 !
 !
       if (iflag_t_evo_4_composit .eq. id_no_evolution) then
+        light_nod%num_bc =  0
         light_surf%num_bc = 0
-        num_bc_composit =   0
       else
-        num_bc_composit = num_bc_composit_ctl
+        light_nod%num_bc =  num_bc_composit_ctl
         light_surf%num_bc = num_bc_grad_ds_ctl
       end if
 !
 !   set boundary conditions for composition
 !
       if (iflag_debug .eq. iflag_full_msg)                              &
-     &   write(*,*) 'num_bc_composit ',num_bc_composit
+     &   write(*,*) 'light_nod%num_bc ',light_nod%num_bc
 !
-      if (num_bc_composit .gt. 0) then
+      if (light_nod%num_bc .gt. 0) then
 !
         call allocate_nod_bc_list_composit
 !
-        bc_composit_name      = bc_composit_name_ctl
-        bc_composit_magnitude = bc_composit_magnitude_ctl
+        light_nod%bc_name =      bc_composit_name_ctl
+        light_nod%bc_magnitude = bc_composit_magnitude_ctl
 !
-        do i = 1, num_bc_composit
+        do i = 1, light_nod%num_bc
           if(bc_composit_type_ctl(i) .eq. 'fixed') then
-            ibc_composit_type(i) =  iflag_bc_fix_s
+            light_nod%ibc_type(i) =  iflag_bc_fix_s
           else if(bc_composit_type_ctl(i) .eq. 'file') then
-            ibc_composit_type(i) = -iflag_bc_fix_s
+            light_nod%ibc_type(i) = -iflag_bc_fix_s
           else if(bc_composit_type_ctl(i) .eq. 'fixed_flux') then
-            ibc_composit_type(i) =  iflag_bc_fix_flux
+            light_nod%ibc_type(i) =  iflag_bc_fix_flux
           end if
         end do
 !
 !
         if (iflag_debug .eq. iflag_full_msg) then
           write(*,*)  'i, bc_c_type, bc_c_magnitude,  bc_c_name'
-          do i = 1, num_bc_composit
-            write(*,*)  i, ibc_composit_type(i),                        &
-     &         bc_composit_magnitude(i), trim(bc_composit_name(i))
+          do i = 1, light_nod%num_bc
+            write(*,*)  i, light_nod%ibc_type(i),                       &
+     &         light_nod%bc_magnitude(i), trim(light_nod%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 87f7d98..eee8dfa 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
@@ -42,60 +42,60 @@
 !
       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
+        magne_nod%num_bc =  0
         magne_surf%num_bc = 0
       else
-        num_bc_b = num_bc_b_ctl
+        magne_nod%num_bc =  num_bc_b_ctl
         magne_surf%num_bc = num_bc_grad_b_ctl
       end if
 !
 !   set boundary_conditons for magnetic field
 !
       if (iflag_debug .ge. iflag_routine_msg)                           &
-     &       write(*,*) 'num_bc_b ',num_bc_b
-      if (num_bc_b .gt. 0) then
+     &       write(*,*) 'magne_nod%num_bc ',magne_nod%num_bc
+      if (magne_nod%num_bc .gt. 0) then
 !
         call allocate_nod_bc_list_magne
 !
-        bc_b_name      = bc_b_name_ctl
-        bc_b_magnitude = bc_b_magnitude_ctl
+        magne_nod%bc_name =      bc_b_name_ctl
+        magne_nod%bc_magnitude = bc_b_magnitude_ctl
 !
-        do i = 1, num_bc_b
+        do i = 1, magne_nod%num_bc
           tmpchara = bc_b_type_ctl(i)
           if ( tmpchara .eq. 'fix_x' ) then
-            ibc_b_type(i) = iflag_bc_fixed + 1
+            magne_nod%ibc_type(i) = iflag_bc_fixed + 1
           else if ( tmpchara .eq. 'fix_y' ) then
-            ibc_b_type(i) = iflag_bc_fixed + 2
+            magne_nod%ibc_type(i) = iflag_bc_fixed + 2
           else if ( tmpchara .eq. 'fix_z' ) then
-            ibc_b_type(i) = iflag_bc_fixed + 3
+            magne_nod%ibc_type(i) = iflag_bc_fixed + 3
           else if ( tmpchara .eq. 'file_x' ) then
-            ibc_b_type(i) = iflag_bc_fixed - 1
+            magne_nod%ibc_type(i) = iflag_bc_fixed - 1
           else if ( tmpchara .eq. 'file_y' ) then
-            ibc_b_type(i) = iflag_bc_fixed - 2
+            magne_nod%ibc_type(i) = iflag_bc_fixed - 2
           else if ( tmpchara .eq. 'file_z' ) then
-            ibc_b_type(i) = iflag_bc_fixed - 3
+            magne_nod%ibc_type(i) = iflag_bc_fixed - 3
           else if ( tmpchara .eq. 'insulator' ) then
-            ibc_b_type(i) = iflag_insulator
+            magne_nod%ibc_type(i) = iflag_insulator
           else if ( tmpchara .eq. 'sph_to_center' ) then
-            ibc_b_type(i) = iflag_sph_2_center
+            magne_nod%ibc_type(i) = iflag_sph_2_center
           else if ( tmpchara .eq. 'pseudo_vacuum' ) then
-            ibc_b_type(i) = iflag_pseudo_vacuum
+            magne_nod%ibc_type(i) = iflag_pseudo_vacuum
 !          else if ( tmpchara .eq. 'sph' ) then
-!            ibc_b_type(i) = 999
+!            magne_nod%ibc_type(i) = 999
           else if ( tmpchara .eq. 'sgs_x' ) then
-            ibc_b_type(i) = iflag_bc_sgs + 1
+            magne_nod%ibc_type(i) = iflag_bc_sgs + 1
           else if ( tmpchara .eq. 'sgs_y' ) then
-            ibc_b_type(i) = iflag_bc_sgs + 2
+            magne_nod%ibc_type(i) = iflag_bc_sgs + 2
           else if ( tmpchara .eq. 'sgs_z' ) then
-            ibc_b_type(i) = iflag_bc_sgs + 3
+            magne_nod%ibc_type(i) = iflag_bc_sgs + 3
           end if
         end do
 !
         if (iflag_debug .ge. iflag_routine_msg) then
-          write(*,*)'i, ibc_b_type, bc_b_magnitude, bc_b_name'
-          do i = 1, num_bc_b
-            write(*,*) i, ibc_b_type(i), bc_b_magnitude(i),             &
-     &                 trim(bc_b_name(i))
+          write(*,*)'i, magne_nod'
+          do i = 1, magne_nod%num_bc
+            write(*,*) i, magne_nod%ibc_type(i),                        &
+     &         magne_nod%bc_magnitude(i), trim(magne_nod%bc_name(i))
           end do
         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 3a568a5..201be37 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
@@ -42,41 +42,41 @@
 !
 !
       if (iflag_t_evo_4_velo .eq. id_no_evolution) then
-        num_bc_p = 0
+        press_nod%num_bc = 0
         wall_surf%num_bc = 0
       else
-        num_bc_p = num_bc_p_ctl
+        press_nod%num_bc = num_bc_p_ctl
         wall_surf%num_bc = num_bc_grad_p_ctl
       end if
 !
 !  set boundary conditions for pressure
 !
       if(iflag_debug.eq.iflag_full_msg)                                 &
-     &    write(*,*) 'num_bc_p ', num_bc_p
-      if(num_bc_p .gt. 0) then
+     &    write(*,*) 'press_nod%num_bc ', press_nod%num_bc
+      if(press_nod%num_bc .gt. 0) then
 !
         call allocate_nod_bc_list_press
 !
-        bc_p_name     = bc_p_name_ctl
-        bc_p_magnitude = bc_p_magnitude_ctl
+        press_nod%bc_name =      bc_p_name_ctl
+        press_nod%bc_magnitude = bc_p_magnitude_ctl
 !
-        do i = 1, num_bc_p
+        do i = 1, press_nod%num_bc
           tmpchara = bc_p_type_ctl(i)
           if ( tmpchara .eq. 'fixed' ) then
-            ibc_p_type(i) =  iflag_bc_fix_s
+            press_nod%ibc_type(i) =  iflag_bc_fix_s
           else if ( tmpchara .eq. 'file' ) then
-            ibc_p_type(i) = -iflag_bc_fix_s
+            press_nod%ibc_type(i) = -iflag_bc_fix_s
           else if ( tmpchara .eq. 'sgs' ) then
-            ibc_p_type(i) =  iflag_bc_sgs_s
+            press_nod%ibc_type(i) =  iflag_bc_sgs_s
           end if
         end do
 !
 !
         if (iflag_debug .eq. iflag_full_msg) then
-          write(*,*) 'i, ibc_p_type, bc_p_magnitude, bc_p_name'
-          do i = 1, num_bc_p
-            write(*,*)  i, ibc_p_type(i), bc_p_magnitude(i),            &
-     &                 trim(bc_p_name(i))
+          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))
           end do
         end if
       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 ff5d0c1..9be9110 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
@@ -40,41 +40,41 @@
 !
 !
       if (iflag_t_evo_4_temp .eq. id_no_evolution) then
-        num_bc_e = 0
+        temp_nod%num_bc =    0
         h_flux_surf%num_bc = 0
       else
-        num_bc_e =      num_bc_e_ctl
+        temp_nod%num_bc =    num_bc_e_ctl
         h_flux_surf%num_bc = num_bc_h_flux_ctl
       end if
 !
 !   set boundary conditions for temperature
 !
       if(iflag_debug .eq. iflag_full_msg)                               &
-     &          write(*,*)  'num_bc_e ',num_bc_e
-      if(num_bc_e .gt. 0) then
+     &          write(*,*)  'temp_nod%num_bc ',temp_nod%num_bc
+      if(temp_nod%num_bc .gt. 0) then
 !
         call allocate_nod_bc_list_temp
 !
-        bc_e_name      =  bc_e_name_ctl
-        bc_e_magnitude = bc_e_magnitude_ctl
+        temp_nod%bc_name =      bc_e_name_ctl
+        temp_nod%bc_magnitude = bc_e_magnitude_ctl
 !
-        do i = 1, num_bc_e
+        do i = 1, temp_nod%num_bc
           if ( bc_e_type_ctl(i) .eq. 'fixed' ) then
-            ibc_e_type(i) =  iflag_bc_fix_s
+            temp_nod%ibc_type(i) =  iflag_bc_fix_s
           else if ( bc_e_type_ctl(i) .eq. 'file' ) then
-            ibc_e_type(i) = -iflag_bc_fix_s
+            temp_nod%ibc_type(i) = -iflag_bc_fix_s
           else if ( bc_e_type_ctl(i) .eq. 'fixed_flux' ) then
-            ibc_e_type(i) =  iflag_bc_fix_flux
+            temp_nod%ibc_type(i) =  iflag_bc_fix_flux
           else if ( bc_e_type_ctl(i) .eq. 'sgs' ) then
-            ibc_e_type(i) =  iflag_bc_sgs_s
+            temp_nod%ibc_type(i) =  iflag_bc_sgs_s
           end if
         end do
 !
         if (iflag_debug .eq. iflag_full_msg) then
-          write(*,*) 'i, ibc_e_type, bc_e_magnitude, bc_e_name'
-          do i = 1, num_bc_e
-            write(*,*)  i, ibc_e_type(i), bc_e_magnitude(i),            &
-     &                 trim(bc_e_name(i))
+          write(*,*) 'i, temp_nod'
+          do i = 1, temp_nod%num_bc
+            write(*,*)  i, temp_nod%ibc_type(i),                        &
+     &         temp_nod%bc_magnitude(i), trim(temp_nod%bc_name(i))
           end do
         end if
       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 9d89fae..b87bc53 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
@@ -42,75 +42,75 @@
 !
 !
       if (iflag_t_evo_4_velo .eq. id_no_evolution) then
-        num_bc_v = 0
+        velo_nod%num_bc =    0
         torque_surf%num_bc = 0
       else
-        num_bc_v =  num_bc_v_ctl
+        velo_nod%num_bc =    num_bc_v_ctl
         torque_surf%num_bc = num_bc_torque_ctl
       end if
 !
 !  set boundary conditions for velocity
 !
       if (iflag_debug .eq. iflag_full_msg)                              &
-     &      write(*,*) 'num_bc_v ',num_bc_v
-      if (num_bc_v .gt. 0) then
+     &      write(*,*) 'velo_nod%num_bc ',velo_nod%num_bc
+      if (velo_nod%num_bc .gt. 0) then
 !
         call allocate_nod_bc_list_velo
 !
-        bc_v_name      = bc_v_name_ctl
-        bc_v_magnitude = bc_v_magnitude_ctl
+        velo_nod%bc_name =      bc_v_name_ctl
+        velo_nod%bc_magnitude = bc_v_magnitude_ctl
 !
         iflag_4_hemi = 0
-        do i = 1, num_bc_v
-          if ( bc_v_name(i)  .eq. 'equator') then
+        do i = 1, velo_nod%num_bc
+          if ( velo_nod%bc_name(i)  .eq. 'equator') then
             iflag_4_hemi = 1
           end if
         end do
 !
-        do i = 1, num_bc_v
+        do i = 1, velo_nod%num_bc
           tmpchara = bc_v_type_ctl(i)
           if ( tmpchara .eq. 'fix_x' ) then
-            ibc_v_type(i) = iflag_bc_fixed + 1
+            velo_nod%ibc_type(i) = iflag_bc_fixed + 1
           else if ( tmpchara .eq. 'fix_y' ) then
-            ibc_v_type(i) = iflag_bc_fixed + 2
+            velo_nod%ibc_type(i) = iflag_bc_fixed + 2
           else if ( tmpchara .eq. 'fix_z' ) then
-            ibc_v_type(i) = iflag_bc_fixed + 3
+            velo_nod%ibc_type(i) = iflag_bc_fixed + 3
           else if ( tmpchara .eq. 'file_x' ) then
-            ibc_v_type(i) = iflag_bc_fixed - 1
+            velo_nod%ibc_type(i) = iflag_bc_fixed - 1
           else if ( tmpchara .eq. 'file_y' ) then
-            ibc_v_type(i) = iflag_bc_fixed - 2
+            velo_nod%ibc_type(i) = iflag_bc_fixed - 2
           else if ( tmpchara .eq. 'file_z' ) then
-            ibc_v_type(i) = iflag_bc_fixed - 3
+            velo_nod%ibc_type(i) = iflag_bc_fixed - 3
           else if ( tmpchara .eq. 'rot_x' ) then
-            ibc_v_type(i) = iflag_bc_rot + 1
+            velo_nod%ibc_type(i) = iflag_bc_rot + 1
           else if ( tmpchara .eq. 'rot_y' ) then
-            ibc_v_type(i) = iflag_bc_rot + 2
+            velo_nod%ibc_type(i) = iflag_bc_rot + 2
           else if ( tmpchara .eq. 'rot_z' ) then
-            ibc_v_type(i) = iflag_bc_rot + 3
+            velo_nod%ibc_type(i) = iflag_bc_rot + 3
           else if ( tmpchara .eq. 'vr_0' ) then
-            ibc_v_type(i) = iflag_no_vr
+            velo_nod%ibc_type(i) = iflag_no_vr
           else if ( tmpchara .eq. 'free_slip_sph' ) then
-            ibc_v_type(i) = iflag_free_sph
+            velo_nod%ibc_type(i) = iflag_free_sph
           else if ( tmpchara .eq. 'non_slip_sph' ) then
-            ibc_v_type(i) = iflag_non_slip_sph
+            velo_nod%ibc_type(i) = iflag_non_slip_sph
           else if ( tmpchara .eq. 'rot_inner_core' ) then
-            ibc_v_type(i) = iflag_rotatable_icore
+            velo_nod%ibc_type(i) = iflag_rotatable_icore
           else if ( tmpchara .eq. 'special' ) then
-            ibc_v_type(i) = iflag_bc_special
+            velo_nod%ibc_type(i) = iflag_bc_special
           else if ( tmpchara .eq. 'sgs_x' ) then
-            ibc_v_type(i) =  iflag_bc_sgs + 1
+            velo_nod%ibc_type(i) =  iflag_bc_sgs + 1
           else if ( tmpchara .eq. 'sgs_y' ) then
-            ibc_v_type(i) =  iflag_bc_sgs + 2
+            velo_nod%ibc_type(i) =  iflag_bc_sgs + 2
           else if ( tmpchara .eq. 'sgs_z' ) then
-            ibc_v_type(i) =  iflag_bc_sgs + 3
+            velo_nod%ibc_type(i) =  iflag_bc_sgs + 3
           end if
         end do
 !
         if (iflag_debug .eq. iflag_full_msg) then
-          write(*,*) 'i, ibc_v_type, bc_v_magnitude, bc_v_name'
-          do i = 1, num_bc_v
-            write(*,*)  i, ibc_v_type(i), bc_v_magnitude(i),            &
-     &                 trim(bc_v_name(i))
+          write(*,*) 'i, velo_nod'
+          do i = 1, velo_nod%num_bc
+            write(*,*)  i, velo_nod%ibc_type(i),                        &
+     &         velo_nod%bc_magnitude(i), trim(velo_nod%bc_name(i))
           end do
         end if
       end if
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 3590905..51eff91 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
@@ -43,10 +43,11 @@
       call allocate_vsp_bc_array( nidx_rj(2) )
 !
 !
-      do i = 1, num_bc_v
+      do i = 1, velo_nod%num_bc
         if(iflag_icb_velocity .ne. iflag_fixed_velo) exit
-        if(bc_v_name(i) .eq. 'ICB') then 
-          call set_sph_velo_ICB_flag(ibc_v_type(i), bc_v_magnitude(i))
+        if(velo_nod%bc_name(i) .eq. 'ICB') then
+          call set_sph_velo_ICB_flag(velo_nod%ibc_type(i),              &
+     &        velo_nod%bc_magnitude(i))
         end if
       end do
 !
@@ -61,10 +62,11 @@
 !
 !
 !
-      do i = 1, num_bc_v
+      do i = 1, velo_nod%num_bc
         if(iflag_cmb_velocity .ne. iflag_fixed_velo) exit
-        if(bc_v_name(i) .eq. 'CMB') then 
-          call set_sph_velo_CMB_flag(ibc_v_type(i), bc_v_magnitude(i))
+        if(velo_nod%bc_name(i) .eq. 'CMB') then 
+          call set_sph_velo_CMB_flag(velo_nod%ibc_type(i),              &
+     &        velo_nod%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 e67d15d..a60f548 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
@@ -112,18 +112,18 @@
         write(*,*)  h_flux_CMB_bc(1)
       end if
 !
-      do i = 1, num_bc_e
-        if ( ibc_e_type(i)  .eq. iflag_bc_fix_flux) then
+      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,                        &
-     &        bc_e_name(i), bc_e_magnitude(i),                          &
+     &        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,                        &
-     &        bc_e_name(i), bc_e_magnitude(i),                          &
+     &        temp_nod%bc_name(i), temp_nod%bc_magnitude(i),            &
      &        nidx_rj(2), h_flux_CMB_bc, iflag_cmb_temp)
 !
-        else if ( ibc_e_type(i)  .eq. -iflag_bc_fix_flux) then
+        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)
@@ -132,15 +132,15 @@
      &        nidx_rj(2), h_flux_CMB_bc, iflag_cmb_temp)
 !
 !
-        else if ( ibc_e_type(i)  .eq. iflag_bc_fix_s) then
+        else if ( temp_nod%ibc_type(i)  .eq. iflag_bc_fix_s) then
           call set_homogenious_scalar_bc(ICB_nod_grp_name,              &
-     &        bc_e_name(i), bc_e_magnitude(i),                          &
+     &        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,              &
-     &        bc_e_name(i), bc_e_magnitude(i),                          &
+     &        temp_nod%bc_name(i), temp_nod%bc_magnitude(i),            &
      &        nidx_rj(2), temp_CMB_bc, iflag_cmb_temp)
 !
-        else if ( ibc_e_type(i)  .eq. -iflag_bc_fix_s) then
+        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,  &
@@ -189,21 +189,21 @@
       iflag_icb_magne = iflag_sph_insulator
       iflag_cmb_magne = iflag_sph_insulator
 !
-      do i = 1, num_bc_b
-        if(bc_b_name(i) .eq. 'ICB') then
-          if(ibc_b_type(i) .eq. iflag_pseudo_vacuum) then
+      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(bc_b_name(i) .eq. 'CMB') then
-          if(ibc_b_type(i) .eq. iflag_pseudo_vacuum) then
+        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(bc_b_name(i) .eq. 'to_Center') then
-          if      (ibc_b_type(i) .eq. iflag_sph_2_center) then
+        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
@@ -273,18 +273,18 @@
 !
 !      Boundary setting using boundary group data
 !
-      do i = 1, num_bc_composit
-        if ( ibc_composit_type(i)  .eq. iflag_bc_fix_flux) then
+      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,                        &
-     &        bc_composit_name(i), bc_composit_magnitude(i),            &
+     &        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,                        &
-     &        bc_composit_name(i), bc_composit_magnitude(i),            &
+     &        light_nod%bc_name(i), light_nod%bc_magnitude(i),          &
      &        nidx_rj(2), c_flux_CMB_bc, iflag_cmb_composition)
 !
-        else if ( ibc_composit_type(i)  .eq. -iflag_bc_fix_flux) then
+        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)
@@ -293,15 +293,15 @@
      &        nidx_rj(2), c_flux_CMB_bc, iflag_cmb_composition)
 !
 !
-        else if ( ibc_composit_type(i)  .eq. iflag_bc_fix_s) then
+        else if ( light_nod%ibc_type(i)  .eq. iflag_bc_fix_s) then
           call set_homogenious_scalar_bc(ICB_nod_grp_name,              &
-     &        bc_composit_name(i), bc_composit_magnitude(i),            &
+     &        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,              &
-     &        bc_composit_name(i), bc_composit_magnitude(i),            &
+     &        light_nod%bc_name(i), light_nod%bc_magnitude(i),          &
      &        nidx_rj(2), composition_CMB_bc, iflag_cmb_composition)
 !
-        else if ( ibc_composit_type(i)  .eq. -iflag_bc_fix_s) then
+        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, &



More information about the CIG-COMMITS mailing list