Skip to content

Commit

Permalink
Merge branch 'dev/gfdl' into FMS2_io
Browse files Browse the repository at this point in the history
  • Loading branch information
Hallberg-NOAA committed Mar 12, 2021
2 parents aab2ad6 + 250f007 commit 9123209
Show file tree
Hide file tree
Showing 10 changed files with 298 additions and 50 deletions.
3 changes: 2 additions & 1 deletion config_src/drivers/ice_solo_driver/ice_shelf_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -185,6 +185,8 @@ program Shelf_main
endif
endif

call Get_MOM_Input(param_file, dirs)

! Read ocean_solo restart, which can override settings from the namelist.
if (file_exists(trim(dirs%restart_input_dir)//'ice_solo.res')) then
call open_ASCII_file(unit, trim(dirs%restart_input_dir)//'ice_solo.res', action=READONLY_FILE)
Expand Down Expand Up @@ -215,7 +217,6 @@ program Shelf_main
Start_time = real_to_time(0.0)
endif

call Get_MOM_Input(param_file, dirs)
! Determining the internal unit scaling factors for this run.
call unit_scaling_init(param_file, US)

Expand Down
4 changes: 4 additions & 0 deletions config_src/drivers/solo_driver/MOM_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -250,6 +250,10 @@ program MOM_main
! This call sets the number and affinity of threads with openMP.
!$ call set_MOM_thread_affinity(ocean_nthreads, use_hyper_thread)

! This call is required to initiate dirs%restart_input_dir for ocean_solo.res
! The contents of dirs will be reread in initialize_MOM.
call get_MOM_input(dirs=dirs)

! Read ocean_solo restart, which can override settings from the namelist.
if (file_exists(trim(dirs%restart_input_dir)//'ocean_solo.res')) then
call open_ASCII_file(unit, trim(dirs%restart_input_dir)//'ocean_solo.res', action=READONLY_FILE)
Expand Down
101 changes: 86 additions & 15 deletions src/core/MOM_CoriolisAdv.F90
Original file line number Diff line number Diff line change
Expand Up @@ -76,8 +76,10 @@ module MOM_CoriolisAdv
integer :: id_rvxu = -1, id_rvxv = -1
! integer :: id_hf_gKEu = -1, id_hf_gKEv = -1
integer :: id_hf_gKEu_2d = -1, id_hf_gKEv_2d = -1
integer :: id_intz_gKEu_2d = -1, id_intz_gKEv_2d = -1
! integer :: id_hf_rvxu = -1, id_hf_rvxv = -1
integer :: id_hf_rvxu_2d = -1, id_hf_rvxv_2d = -1
integer :: id_intz_rvxu_2d = -1, id_intz_rvxv_2d = -1
!>@}
end type CoriolisAdv_CS

Expand Down Expand Up @@ -219,12 +221,17 @@ subroutine CorAdCalc(u, v, h, uh, vh, CAu, CAv, OBC, AD, G, GV, US, CS)
real, allocatable, dimension(:,:) :: &
hf_gKEu_2d, hf_gKEv_2d, & ! Depth sum of hf_gKEu, hf_gKEv [L T-2 ~> m s-2].
hf_rvxu_2d, hf_rvxv_2d ! Depth sum of hf_rvxu, hf_rvxv [L T-2 ~> m s-2].

!real, allocatable, dimension(:,:,:) :: &
! hf_gKEu, hf_gKEv, & ! accel. due to KE gradient x fract. thickness [L T-2 ~> m s-2].
! hf_rvxu, hf_rvxv ! accel. due to RV x fract. thickness [L T-2 ~> m s-2].
! 3D diagnostics hf_gKEu etc. are commented because there is no clarity on proper remapping grid option.
! The code is retained for degugging purposes in the future.

! Diagnostics for depth-integrated momentum budget terms
real, dimension(SZIB_(G),SZJ_(G)) :: intz_gKEu_2d, intz_rvxv_2d ! [L2 T-2 ~> m2 s-2].
real, dimension(SZI_(G),SZJB_(G)) :: intz_gKEv_2d, intz_rvxu_2d ! [L2 T-2 ~> m2 s-2].

! To work, the following fields must be set outside of the usual
! is to ie range before this subroutine is called:
! v(is-1:ie+2,js-1:je+1), u(is-1:ie+1,js-1:je+2), h(is-1:ie+2,js-1:je+2),
Expand Down Expand Up @@ -883,6 +890,22 @@ subroutine CorAdCalc(u, v, h, uh, vh, CAu, CAv, OBC, AD, G, GV, US, CS)
deallocate(hf_gKEv_2d)
endif

if (CS%id_intz_gKEu_2d > 0) then
intz_gKEu_2d(:,:) = 0.0
do k=1,nz ; do j=js,je ; do I=Isq,Ieq
intz_gKEu_2d(I,j) = intz_gKEu_2d(I,j) + AD%gradKEu(I,j,k) * AD%diag_hu(I,j,k)
enddo ; enddo ; enddo
call post_data(CS%id_intz_gKEu_2d, intz_gKEu_2d, CS%diag)
endif

if (CS%id_intz_gKEv_2d > 0) then
intz_gKEv_2d(:,:) = 0.0
do k=1,nz ; do J=Jsq,Jeq ; do i=is,ie
intz_gKEv_2d(i,J) = intz_gKEv_2d(i,J) + AD%gradKEv(i,J,k) * AD%diag_hv(i,J,k)
enddo ; enddo ; enddo
call post_data(CS%id_intz_gKEv_2d, intz_gKEv_2d, CS%diag)
endif

!if (CS%id_hf_rvxv > 0) then
! allocate(hf_rvxv(G%IsdB:G%IedB,G%jsd:G%jed,GV%ke))
! do k=1,nz ; do j=js,je ; do I=Isq,Ieq
Expand Down Expand Up @@ -918,6 +941,22 @@ subroutine CorAdCalc(u, v, h, uh, vh, CAu, CAv, OBC, AD, G, GV, US, CS)
call post_data(CS%id_hf_rvxu_2d, hf_rvxu_2d, CS%diag)
deallocate(hf_rvxu_2d)
endif

if (CS%id_intz_rvxv_2d > 0) then
intz_rvxv_2d(:,:) = 0.0
do k=1,nz ; do j=js,je ; do I=Isq,Ieq
intz_rvxv_2d(I,j) = intz_rvxv_2d(I,j) + AD%rv_x_v(I,j,k) * AD%diag_hu(I,j,k)
enddo ; enddo ; enddo
call post_data(CS%id_intz_rvxv_2d, intz_rvxv_2d, CS%diag)
endif

if (CS%id_intz_rvxu_2d > 0) then
intz_rvxu_2d(:,:) = 0.0
do k=1,nz ; do J=Jsq,Jeq ; do i=is,ie
intz_rvxu_2d(i,J) = intz_rvxu_2d(i,J) + AD%rv_x_u(i,J,k) * AD%diag_hv(i,J,k)
enddo ; enddo ; enddo
call post_data(CS%id_intz_rvxu_2d, intz_rvxu_2d, CS%diag)
endif
endif

end subroutine CorAdCalc
Expand Down Expand Up @@ -1163,59 +1202,75 @@ subroutine CoriolisAdv_init(Time, G, GV, US, param_file, diag, AD, CS)
'Potential Vorticity', 'm-1 s-1', conversion=GV%m_to_H*US%s_to_T)

CS%id_gKEu = register_diag_field('ocean_model', 'gKEu', diag%axesCuL, Time, &
'Zonal Acceleration from Grad. Kinetic Energy', 'm-1 s-2', conversion=US%L_T2_to_m_s2)
'Zonal Acceleration from Grad. Kinetic Energy', 'm s-2', conversion=US%L_T2_to_m_s2)
if (CS%id_gKEu > 0) call safe_alloc_ptr(AD%gradKEu,IsdB,IedB,jsd,jed,nz)

CS%id_gKEv = register_diag_field('ocean_model', 'gKEv', diag%axesCvL, Time, &
'Meridional Acceleration from Grad. Kinetic Energy', 'm-1 s-2', conversion=US%L_T2_to_m_s2)
'Meridional Acceleration from Grad. Kinetic Energy', 'm s-2', conversion=US%L_T2_to_m_s2)
if (CS%id_gKEv > 0) call safe_alloc_ptr(AD%gradKEv,isd,ied,JsdB,JedB,nz)

CS%id_rvxu = register_diag_field('ocean_model', 'rvxu', diag%axesCvL, Time, &
'Meridional Acceleration from Relative Vorticity', 'm-1 s-2', conversion=US%L_T2_to_m_s2)
'Meridional Acceleration from Relative Vorticity', 'm s-2', conversion=US%L_T2_to_m_s2)
if (CS%id_rvxu > 0) call safe_alloc_ptr(AD%rv_x_u,isd,ied,JsdB,JedB,nz)

CS%id_rvxv = register_diag_field('ocean_model', 'rvxv', diag%axesCuL, Time, &
'Zonal Acceleration from Relative Vorticity', 'm-1 s-2', conversion=US%L_T2_to_m_s2)
'Zonal Acceleration from Relative Vorticity', 'm s-2', conversion=US%L_T2_to_m_s2)
if (CS%id_rvxv > 0) call safe_alloc_ptr(AD%rv_x_v,IsdB,IedB,jsd,jed,nz)

!CS%id_hf_gKEu = register_diag_field('ocean_model', 'hf_gKEu', diag%axesCuL, Time, &
! 'Fractional Thickness-weighted Zonal Acceleration from Grad. Kinetic Energy', &
! 'm-1 s-2', v_extensive=.true., conversion=US%L_T2_to_m_s2)
! 'm s-2', v_extensive=.true., conversion=US%L_T2_to_m_s2)
!if (CS%id_hf_gKEu > 0) then
! call safe_alloc_ptr(AD%gradKEu,IsdB,IedB,jsd,jed,nz)
! call safe_alloc_ptr(AD%diag_hfrac_u,IsdB,IedB,jsd,jed,nz)
!endif

!CS%id_hf_gKEv = register_diag_field('ocean_model', 'hf_gKEv', diag%axesCvL, Time, &
! 'Fractional Thickness-weighted Meridional Acceleration from Grad. Kinetic Energy', &
! 'm-1 s-2', v_extensive=.true., conversion=US%L_T2_to_m_s2)
! 'm s-2', v_extensive=.true., conversion=US%L_T2_to_m_s2)
!if (CS%id_hf_gKEv > 0) then
! call safe_alloc_ptr(AD%gradKEv,isd,ied,JsdB,JedB,nz)
! call safe_alloc_ptr(AD%diag_hfrac_v,isd,ied,Jsd,JedB,nz)
! call safe_alloc_ptr(AD%diag_hfrac_v,isd,ied,JsdB,JedB,nz)
!endif

CS%id_hf_gKEu_2d = register_diag_field('ocean_model', 'hf_gKEu_2d', diag%axesCu1, Time, &
'Depth-sum Fractional Thickness-weighted Zonal Acceleration from Grad. Kinetic Energy', &
'm-1 s-2', conversion=US%L_T2_to_m_s2)
'm s-2', conversion=US%L_T2_to_m_s2)
if (CS%id_hf_gKEu_2d > 0) then
call safe_alloc_ptr(AD%gradKEu,IsdB,IedB,jsd,jed,nz)
call safe_alloc_ptr(AD%diag_hfrac_u,IsdB,IedB,jsd,jed,nz)
endif

CS%id_hf_gKEv_2d = register_diag_field('ocean_model', 'hf_gKEv_2d', diag%axesCv1, Time, &
'Depth-sum Fractional Thickness-weighted Meridional Acceleration from Grad. Kinetic Energy', &
'm-1 s-2', conversion=US%L_T2_to_m_s2)
'm s-2', conversion=US%L_T2_to_m_s2)
if (CS%id_hf_gKEv_2d > 0) then
call safe_alloc_ptr(AD%gradKEv,isd,ied,JsdB,JedB,nz)
call safe_alloc_ptr(AD%diag_hfrac_v,isd,ied,Jsd,JedB,nz)
call safe_alloc_ptr(AD%diag_hfrac_v,isd,ied,JsdB,JedB,nz)
endif

CS%id_intz_gKEu_2d = register_diag_field('ocean_model', 'intz_gKEu_2d', diag%axesCu1, Time, &
'Depth-integral of Zonal Acceleration from Grad. Kinetic Energy', &
'm2 s-2', conversion=GV%H_to_m*US%L_T2_to_m_s2)
if (CS%id_intz_gKEu_2d > 0) then
call safe_alloc_ptr(AD%gradKEu,IsdB,IedB,jsd,jed,nz)
call safe_alloc_ptr(AD%diag_hu,IsdB,IedB,jsd,jed,nz)
endif

CS%id_intz_gKEv_2d = register_diag_field('ocean_model', 'intz_gKEv_2d', diag%axesCv1, Time, &
'Depth-integral of Meridional Acceleration from Grad. Kinetic Energy', &
'm2 s-2', conversion=GV%H_to_m*US%L_T2_to_m_s2)
if (CS%id_intz_gKEv_2d > 0) then
call safe_alloc_ptr(AD%gradKEv,isd,ied,JsdB,JedB,nz)
call safe_alloc_ptr(AD%diag_hv,isd,ied,JsdB,JedB,nz)
endif

!CS%id_hf_rvxu = register_diag_field('ocean_model', 'hf_rvxu', diag%axesCvL, Time, &
! 'Fractional Thickness-weighted Meridional Acceleration from Relative Vorticity', &
! 'm-1 s-2', v_extensive=.true., conversion=US%L_T2_to_m_s2)
!if (CS%id_hf_rvxu > 0) then
! call safe_alloc_ptr(AD%rv_x_u,isd,ied,JsdB,JedB,nz)
! call safe_alloc_ptr(AD%diag_hfrac_v,isd,ied,Jsd,JedB,nz)
! call safe_alloc_ptr(AD%diag_hfrac_v,isd,ied,JsdB,JedB,nz)
!endif

!CS%id_hf_rvxv = register_diag_field('ocean_model', 'hf_rvxv', diag%axesCuL, Time, &
Expand All @@ -1227,21 +1282,37 @@ subroutine CoriolisAdv_init(Time, G, GV, US, param_file, diag, AD, CS)
!endif

CS%id_hf_rvxu_2d = register_diag_field('ocean_model', 'hf_rvxu_2d', diag%axesCv1, Time, &
'Fractional Thickness-weighted Meridional Acceleration from Relative Vorticity', &
'm-1 s-2', conversion=US%L_T2_to_m_s2)
'Depth-sum Fractional Thickness-weighted Meridional Acceleration from Relative Vorticity', &
'm s-2', conversion=US%L_T2_to_m_s2)
if (CS%id_hf_rvxu_2d > 0) then
call safe_alloc_ptr(AD%rv_x_u,isd,ied,JsdB,JedB,nz)
call safe_alloc_ptr(AD%diag_hfrac_v,isd,ied,Jsd,JedB,nz)
call safe_alloc_ptr(AD%diag_hfrac_v,isd,ied,JsdB,JedB,nz)
endif

CS%id_hf_rvxv_2d = register_diag_field('ocean_model', 'hf_rvxv_2d', diag%axesCu1, Time, &
'Depth-sum Fractional Thickness-weighted Zonal Acceleration from Relative Vorticity', &
'm-1 s-2', conversion=US%L_T2_to_m_s2)
'm s-2', conversion=US%L_T2_to_m_s2)
if (CS%id_hf_rvxv_2d > 0) then
call safe_alloc_ptr(AD%rv_x_v,IsdB,IedB,jsd,jed,nz)
call safe_alloc_ptr(AD%diag_hfrac_u,IsdB,IedB,jsd,jed,nz)
endif

CS%id_intz_rvxu_2d = register_diag_field('ocean_model', 'intz_rvxu_2d', diag%axesCv1, Time, &
'Depth-integral of Meridional Acceleration from Relative Vorticity', &
'm2 s-2', conversion=GV%H_to_m*US%L_T2_to_m_s2)
if (CS%id_intz_rvxu_2d > 0) then
call safe_alloc_ptr(AD%rv_x_u,isd,ied,JsdB,JedB,nz)
call safe_alloc_ptr(AD%diag_hv,isd,ied,JsdB,JedB,nz)
endif

CS%id_intz_rvxv_2d = register_diag_field('ocean_model', 'intz_rvxv_2d', diag%axesCu1, Time, &
'Depth-integral of Fractional Thickness-weighted Zonal Acceleration from Relative Vorticity', &
'm2 s-2', conversion=GV%H_to_m*US%L_T2_to_m_s2)
if (CS%id_intz_rvxv_2d > 0) then
call safe_alloc_ptr(AD%rv_x_v,IsdB,IedB,jsd,jed,nz)
call safe_alloc_ptr(AD%diag_hu,IsdB,IedB,jsd,jed,nz)
endif

end subroutine CoriolisAdv_init

!> Destructor for coriolisadv_cs
Expand Down
96 changes: 75 additions & 21 deletions src/core/MOM_barotropic.F90
Original file line number Diff line number Diff line change
Expand Up @@ -955,6 +955,17 @@ subroutine btstep(U_in, V_in, eta_in, dt, bc_accel_u, bc_accel_v, forces, pbce,
Datv(i,J) = 0.0 ; bt_rem_v(i,J) = 0.0 ; vhbt0(i,J) = 0.0
enddo ; enddo

if (CS%linear_wave_drag) then
!$OMP parallel do default(shared)
do j=CS%jsdw,CS%jedw ; do I=CS%isdw-1,CS%iedw
Rayleigh_u(I,j) = 0.0
enddo ; enddo
!$OMP parallel do default(shared)
do J=CS%jsdw-1,CS%jedw ; do i=CS%isdw,CS%iedw
Rayleigh_v(i,J) = 0.0
enddo ; enddo
endif

! Copy input arrays into their wide-halo counterparts.
if (interp_eta_PF) then
!$OMP parallel do default(shared)
Expand Down Expand Up @@ -1900,20 +1911,28 @@ subroutine btstep(U_in, V_in, eta_in, dt, bc_accel_u, bc_accel_v, forces, pbce,
endif ; enddo ; enddo
!$OMP end do nowait
endif

!$OMP do schedule(static)
do J=jsv-1,jev ; do i=isv-1,iev+1
vel_prev = vbt(i,J)
vbt(i,J) = bt_rem_v(i,J) * (vbt(i,J) + &
dtbt * ((BT_force_v(i,J) + Cor_v(i,J)) + PFv(i,J)))
dtbt * ((BT_force_v(i,J) + Cor_v(i,J)) + PFv(i,J)))
if (abs(vbt(i,J)) < CS%vel_underflow) vbt(i,J) = 0.0
vbt_trans(i,J) = trans_wt1*vbt(i,J) + trans_wt2*vel_prev
enddo ; enddo

if (CS%linear_wave_drag) then
if (CS%linear_wave_drag) then
!$OMP do schedule(static)
do J=jsv-1,jev ; do i=isv-1,iev+1
v_accel_bt(i,J) = v_accel_bt(i,J) + wt_accel(n) * &
((Cor_v(i,J) + PFv(i,J)) - vbt(i,J)*Rayleigh_v(i,J))
else
enddo ; enddo
else
!$OMP do schedule(static)
do J=jsv-1,jev ; do i=isv-1,iev+1
v_accel_bt(i,J) = v_accel_bt(i,J) + wt_accel(n) * (Cor_v(i,J) + PFv(i,J))
endif
enddo ; enddo
enddo ; enddo
endif

if (integral_BT_cont) then
!$OMP do schedule(static)
Expand Down Expand Up @@ -1969,22 +1988,31 @@ subroutine btstep(U_in, V_in, eta_in, dt, bc_accel_u, bc_accel_v, forces, pbce,
endif ; enddo ; enddo
!$OMP end do nowait
endif

!$OMP do schedule(static)
do j=jsv,jev ; do I=isv-1,iev
vel_prev = ubt(I,j)
ubt(I,j) = bt_rem_u(I,j) * (ubt(I,j) + &
dtbt * ((BT_force_u(I,j) + Cor_u(I,j)) + PFu(I,j)))
if (abs(ubt(I,j)) < CS%vel_underflow) ubt(I,j) = 0.0
ubt_trans(I,j) = trans_wt1*ubt(I,j) + trans_wt2*vel_prev
enddo ; enddo
!$OMP end do nowait

if (CS%linear_wave_drag) then
if (CS%linear_wave_drag) then
!$OMP do schedule(static)
do j=jsv,jev ; do I=isv-1,iev
u_accel_bt(I,j) = u_accel_bt(I,j) + wt_accel(n) * &
((Cor_u(I,j) + PFu(I,j)) - ubt(I,j)*Rayleigh_u(I,j))
else
((Cor_u(I,j) + PFu(I,j)) - ubt(I,j)*Rayleigh_u(I,j))
enddo ; enddo
!$OMP end do nowait
else
!$OMP do schedule(static)
do j=jsv,jev ; do I=isv-1,iev
u_accel_bt(I,j) = u_accel_bt(I,j) + wt_accel(n) * (Cor_u(I,j) + PFu(I,j))
endif
enddo ; enddo
!$OMP end do nowait
enddo ; enddo
!$OMP end do nowait
endif

if (integral_BT_cont) then
!$OMP do schedule(static)
Expand Down Expand Up @@ -2046,14 +2074,20 @@ subroutine btstep(U_in, V_in, eta_in, dt, bc_accel_u, bc_accel_v, forces, pbce,
dtbt * ((BT_force_u(I,j) + Cor_u(I,j)) + PFu(I,j)))
if (abs(ubt(I,j)) < CS%vel_underflow) ubt(I,j) = 0.0
ubt_trans(I,j) = trans_wt1*ubt(I,j) + trans_wt2*vel_prev
enddo ; enddo

if (CS%linear_wave_drag) then
if (CS%linear_wave_drag) then
!$OMP do schedule(static)
do j=jsv-1,jev+1 ; do I=isv-1,iev
u_accel_bt(I,j) = u_accel_bt(I,j) + wt_accel(n) * &
((Cor_u(I,j) + PFu(I,j)) - ubt(I,j)*Rayleigh_u(I,j))
else
enddo ; enddo
else
!$OMP do schedule(static)
do j=jsv-1,jev+1 ; do I=isv-1,iev
u_accel_bt(I,j) = u_accel_bt(I,j) + wt_accel(n) * (Cor_u(I,j) + PFu(I,j))
endif
enddo ; enddo
enddo ; enddo
endif

if (integral_BT_cont) then
!$OMP do schedule(static)
Expand Down Expand Up @@ -2128,15 +2162,24 @@ subroutine btstep(U_in, V_in, eta_in, dt, bc_accel_u, bc_accel_v, forces, pbce,
dtbt * ((BT_force_v(i,J) + Cor_v(i,J)) + PFv(i,J)))
if (abs(vbt(i,J)) < CS%vel_underflow) vbt(i,J) = 0.0
vbt_trans(i,J) = trans_wt1*vbt(i,J) + trans_wt2*vel_prev
enddo ; enddo
!$OMP end do nowait

if (CS%linear_wave_drag) then
if (CS%linear_wave_drag) then
!$OMP do schedule(static)
do J=jsv-1,jev ; do i=isv,iev
v_accel_bt(i,J) = v_accel_bt(i,J) + wt_accel(n) * &
((Cor_v(i,J) + PFv(i,J)) - vbt(i,J)*Rayleigh_v(i,J))
else
((Cor_v(i,J) + PFv(i,J)) - vbt(i,J)*Rayleigh_v(i,J))
enddo ; enddo
!$OMP end do nowait
else
!$OMP do schedule(static)
do J=jsv-1,jev ; do i=isv,iev
v_accel_bt(i,J) = v_accel_bt(i,J) + wt_accel(n) * (Cor_v(i,J) + PFv(i,J))
endif
enddo ; enddo
!$OMP end do nowait
enddo ; enddo
!$OMP end do nowait
endif

if (integral_BT_cont) then
!$OMP do schedule(static)
do J=jsv-1,jev ; do i=isv,iev
Expand Down Expand Up @@ -2632,6 +2675,17 @@ subroutine btstep(U_in, V_in, eta_in, dt, bc_accel_u, bc_accel_v, forces, pbce,
enddo ; enddo ; enddo
endif

if ((present(ADp)) .and. (present(BT_cont)) .and. (associated(ADp%diag_hu))) then
do k=1,nz ; do j=js,je ; do I=is-1,ie
ADp%diag_hu(I,j,k) = BT_cont%h_u(I,j,k)
enddo ; enddo ; enddo
endif
if ((present(ADp)) .and. (present(BT_cont)) .and. (associated(ADp%diag_hv))) then
do k=1,nz ; do J=js-1,je ; do i=is,ie
ADp%diag_hv(i,J,k) = BT_cont%h_v(i,J,k)
enddo ; enddo ; enddo
endif

if (G%nonblocking_updates) then
if (find_etaav) call complete_group_pass(CS%pass_etaav, G%Domain)
call complete_group_pass(CS%pass_ubta_uhbta, G%Domain)
Expand Down
Loading

0 comments on commit 9123209

Please sign in to comment.