Skip to content

Commit

Permalink
Cleanup: removal of redundant 'return' statements before an 'end subr…
Browse files Browse the repository at this point in the history
…outine' statement
  • Loading branch information
scrasmussen committed Jul 20, 2024
1 parent 0b02804 commit 0c4b24a
Show file tree
Hide file tree
Showing 14 changed files with 16 additions and 184 deletions.
16 changes: 4 additions & 12 deletions src/CPL/CLM_cpl/module_clm_HYDRO.F
Original file line number Diff line number Diff line change
Expand Up @@ -210,7 +210,6 @@ subroutine clm_cpl_HYDRO()
write(6,*) "end of drive ndhms"
#endif

return
end subroutine clm_cpl_HYDRO

subroutine Toclm3d (v1d_out,nn,kk1,z1_in,ix,jx,kk2,z2,v2_in)
Expand All @@ -235,7 +234,6 @@ subroutine Toclm3d (v1d_out,nn,kk1,z1_in,ix,jx,kk2,z2,v2_in)
call Toclm2d(v1(:,:,k),ix,jx,v1d_out(:,k),nn)
end do

return
end subroutine Toclm3d

subroutine Toclm2d(v1,ix,jx,v1d_out,nn)
Expand Down Expand Up @@ -266,7 +264,6 @@ subroutine Toclm2d(v1,ix,jx,v1d_out,nn)
write(6,*) "after scatter_1d_r"

#endif
return
end subroutine Toclm2d

subroutine TO1d(vg2d,v1d,nx,ny)
Expand All @@ -280,7 +277,6 @@ subroutine TO1d(vg2d,v1d,nx,ny)
v1d(n) = vg2d(i,j)
enddo
enddo
return
end subroutine TO1d

subroutine clm2ND3d (v1d_in,nn,kk1,z1_in,ix,jx,kk2,z2,vout)
Expand All @@ -302,8 +298,6 @@ subroutine clm2ND3d (v1d_in,nn,kk1,z1_in,ix,jx,kk2,z2,vout)
end do
call Interp3D (z1(1:kk1),v1,kk1,z2(1:kk2),vout,ix,jx,kk2)


return
end subroutine clm2ND3d

subroutine clm2ND2d (v1d_in,nn,vout,ix,jx)
Expand Down Expand Up @@ -346,7 +340,6 @@ subroutine clm2ND2d (v1d_in,nn,vout,ix,jx)
! domain decomposition
call decompose_data_real(v2d_g,vout)

return
end subroutine clm2ND2d

subroutine Interp3D (z1,v1,kk1,z,vout,ix,jx,kk)
Expand All @@ -366,8 +359,8 @@ subroutine Interp3D (z1,v1,kk1,z,vout,ix,jx,kk)
do j = 1, jx
do i = 1, ix
do k = 1, kk
! call interpLayer(abs(Z1),v1(i,j,1:kk1),kk1,abs( Z(k) ),vout(i,j,k))
call interpLayer(Z1(1:kk1),v1(i,j,1:kk1),kk1,Z(k),vout(i,j,k))
! call interpLayer(abs(Z1),v1(i,j,1:kk1),kk1,abs( Z(k) ),vout(i,j,k))
call interpLayer(Z1(1:kk1),v1(i,j,1:kk1),kk1,Z(k),vout(i,j,k))
end do
end do
end do
Expand Down Expand Up @@ -408,7 +401,7 @@ subroutine interpLayer(inZ,inV,inK,outZ,outV)
if(inZ(k1) .eq. inZ(k2)) then
write(6,*) "FATAL ERROR: inZ(k1)=inZ(k2) ", inZ(k1),inZ(k2)
!stop 99
stop("FATAL ERROR: In module_clm_HYDRO.F interpLayer()- inZ(k1)=inZ(k2)")
stop("FATAL ERROR: In module_clm_HYDRO.F interpLayer()- inZ(k1)=inZ(k2)")
end if
w1 = (outZ-inZ(k1))/(inZ(k2)-inZ(k1))
w2 = (inZ(k2)-outZ)/(inZ(k2)-inZ(k1))
Expand Down Expand Up @@ -692,7 +685,6 @@ subroutine output_nc(array,idim,jdim, var_name, file_name)
iret = nf_inq_varid(ncid,var_name,varid)
iret = nf_put_var_real(ncid,varid,array)
iret=nf_close(ncid)
return
end subroutine output_nc

subroutine g2c_2d(lbc, ubc, lbl, ubl, lbg, ubg, num2d, carr, garr, &
Expand Down Expand Up @@ -995,7 +987,7 @@ subroutine g2c_2d_tmp(lbc, ubc, lbl, ubl, lbg, ubg, num2d, carr, garr, &
!w_yw = scale_c2l(c) * scale_l2g(l) * wtgcell(c)
w_yw = scale_c2l(c) * scale_l2g(l)
if(w_yw .ne. 0) then
if(abs(garr(g,j)) .gt. minv .and. abs(garr(g,j)) .lt. maxv) then
if(abs(garr(g,j)) .gt. minv .and. abs(garr(g,j)) .lt. maxv) then
! carr(c,j) = garr(g,j) / w_yw *sumwt(g)
yw_r = garr(g,j) / w_yw
if(yw_r .gt. 0) then
Expand Down
3 changes: 0 additions & 3 deletions src/CPL/Noah_cpl/module_hrldas_HYDRO.F
Original file line number Diff line number Diff line change
Expand Up @@ -133,8 +133,6 @@ subroutine hrldas_cpl_HYDRO(STC,SMC,SH2OX,infxsrt,sfcheadrt,soldrain,ii,jj,kk, q
!? not sure for the following
! grid%xice(its:ite,jts:jte) = rt_domain(did)%sice


return
end subroutine hrldas_cpl_HYDRO

subroutine hrldas_cpl_HYDRO_ini(STC,SMC,SH2OX,infxsrt,sfcheadrt,soldrain,ii,jj,kk,kt,dt, olddate,zsoil)
Expand Down Expand Up @@ -234,7 +232,6 @@ subroutine hrldas_cpl_HYDRO_ini(STC,SMC,SH2OX,infxsrt,sfcheadrt,soldrain,ii,jj,k
#endif
endif

return
end subroutine hrldas_cpl_HYDRO_ini

subroutine open_print_mpp(iunit)
Expand Down
1 change: 0 additions & 1 deletion src/Data_Rec/module_namelist.F
Original file line number Diff line number Diff line change
Expand Up @@ -554,7 +554,6 @@ subroutine read_rt_nlst(nlst)
if(channel_option .eq. 4) nlst%rtFlag = 0
! if(CHANRTSWCRT .eq. 0 .and. SUBRTSWCRT .eq. 0 .and. OVRTSWCRT .eq. 0 .and. GWBASESWCRT .eq. 0) nlst%rtFlag = 0
if(SUBRTSWCRT .eq. 0 .and. OVRTSWCRT .eq. 0 .and. GWBASESWCRT .eq. 0) nlst%rtFlag = 0
return
end subroutine read_rt_nlst

subroutine rt_nlst_check(nlst)
Expand Down
6 changes: 2 additions & 4 deletions src/Land_models/Noah/HRLDAS_COLLECT_DATA/lib/module_grib1.F
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,6 @@ subroutine grib1_parameter_text_information(sec1, name, units, description)
name = trim(grib1_parameter_table(sec1%parameter)%abbr)
units = trim(grib1_parameter_table(sec1%parameter)%units)
description = trim(grib1_parameter_table(sec1%parameter)%name)
return

end subroutine grib1_parameter_text_information

Expand Down Expand Up @@ -353,7 +352,6 @@ subroutine grib1_unpack_sec1(buffer, buffsize, iskip, sec1)
write(sec1%hdate, '(I4.4,"-",I2.2,"-",I2.2,"_",I2.2,":",I2.2,":",I2.2)') &
sec1%year, sec1%month, sec1%day, sec1%hour, sec1%minute, 00

return
end subroutine grib1_unpack_sec1

!=================================================================================
Expand Down Expand Up @@ -609,7 +607,7 @@ end subroutine grib1_unpack_sec4

subroutine grib1_unpack_sec5(buffer, buffsize, iskip)
implicit none
! Real simple. Just check for the "7777" flag which marks the end of the
! Real simple. Just check for the "7777" flag which marks the end of the
! GRIB1 record.
integer, intent(in) :: buffsize
character(len=1), dimension(buffsize), intent(in) :: buffer
Expand Down Expand Up @@ -888,7 +886,7 @@ subroutine GRIB1_SGUP_BITMAP(grib, array, bitmap, nx, ny)
! Unpack the data according to packing parameters DFAC, BFAC, and XEC4(1),
! Unpack the data according to packing parameters DFAC, BFAC, and XEC4(1),
! and masked by the bitmap BITMAP.
nn = 0
do i = 1, ndat
Expand Down
6 changes: 2 additions & 4 deletions src/Land_models/NoahMP/HRLDAS_forcing/lib/module_grib1.F
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,6 @@ subroutine grib1_parameter_text_information(sec1, name, units, description)
name = trim(grib1_parameter_table(sec1%parameter)%abbr)
units = trim(grib1_parameter_table(sec1%parameter)%units)
description = trim(grib1_parameter_table(sec1%parameter)%name)
return

end subroutine grib1_parameter_text_information

Expand Down Expand Up @@ -350,7 +349,6 @@ subroutine grib1_unpack_sec1(buffer, buffsize, iskip, sec1)
write(sec1%hdate, '(I4.4,"-",I2.2,"-",I2.2,"_",I2.2,":",I2.2,":",I2.2)') &
sec1%year, sec1%month, sec1%day, sec1%hour, sec1%minute, 00

return
end subroutine grib1_unpack_sec1

!=================================================================================
Expand Down Expand Up @@ -612,7 +610,7 @@ end subroutine grib1_unpack_sec4

subroutine grib1_unpack_sec5(buffer, buffsize, iskip)
implicit none
! Real simple. Just check for the "7777" flag which marks the end of the
! Real simple. Just check for the "7777" flag which marks the end of the
! GRIB1 record.
integer, intent(in) :: buffsize
character(len=1), dimension(buffsize), intent(in) :: buffer
Expand Down Expand Up @@ -891,7 +889,7 @@ subroutine GRIB1_SGUP_BITMAP(grib, array, bitmap, nx, ny)
! Unpack the data according to packing parameters DFAC, BFAC, and XEC4(1),
! Unpack the data according to packing parameters DFAC, BFAC, and XEC4(1),
! and masked by the bitmap BITMAP.
nn = 0
do i = 1, ndat
Expand Down
7 changes: 0 additions & 7 deletions src/MPP/CPL_WRF.F
Original file line number Diff line number Diff line change
Expand Up @@ -104,7 +104,6 @@ subroutine CPL_LAND_INIT(istart,iend,jstart,jend)
p_left_right = coords(1)

initialized = .false. ! land model need to be initialized.
return
END subroutine CPL_LAND_INIT

subroutine send_info()
Expand Down Expand Up @@ -133,7 +132,6 @@ subroutine send_info()

call MPI_barrier( HYDRO_COMM_WORLD ,ierr)

return
end subroutine send_info

subroutine find_left()
Expand All @@ -150,7 +148,6 @@ subroutine find_left()
return
endif
end do
return
end subroutine find_left

subroutine find_right()
Expand All @@ -167,7 +164,6 @@ subroutine find_right()
return
endif
end do
return
end subroutine find_right

subroutine find_up()
Expand All @@ -184,7 +180,6 @@ subroutine find_up()
return
endif
end do
return
end subroutine find_up

subroutine find_down()
Expand All @@ -201,7 +196,6 @@ subroutine find_down()
return
endif
end do
return
end subroutine find_down

! stop the job due to the fatal error.
Expand All @@ -212,6 +206,5 @@ subroutine fatal_error_stop(msg)
call flush(error_unit)
CALL MPI_Abort(HYDRO_COMM_WORLD, 1, ierr)
call MPI_Finalize(ierr)
return
end subroutine fatal_error_stop
END MODULE MODULE_CPL_LAND
Loading

0 comments on commit 0c4b24a

Please sign in to comment.