Skip to content

Commit

Permalink
Point to ccpp version of sfcsub.F Update cycle.f90 for new
Browse files Browse the repository at this point in the history
interface to sfcsub.F.

Fixes ufs-community#424.
  • Loading branch information
GeorgeGayno-NOAA committed Mar 25, 2021
1 parent 2fffb11 commit 04b8974
Show file tree
Hide file tree
Showing 3 changed files with 12 additions and 9,737 deletions.
2 changes: 1 addition & 1 deletion sorc/global_cycle.fd/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ set(fortran_src
cycle.f90
machine.f90
num_parthds.f90
sfcsub.F
../../ccpp-physics/physics/sfcsub.F
read_write_data.f90)

if(CMAKE_Fortran_COMPILER_ID MATCHES "^(Intel)$")
Expand Down
12 changes: 11 additions & 1 deletion sorc/global_cycle.fd/cycle.f90
Original file line number Diff line number Diff line change
Expand Up @@ -286,6 +286,7 @@ SUBROUTINE SFCDRV(LUGB, IDIM,JDIM,LENSFC,LSOIL,DELTSFC, &
ZSEA1,ZSEA2,ISOT,IVEGSRC,MYRANK)
!
USE READ_WRITE_DATA
use machine

IMPLICIT NONE

Expand All @@ -307,6 +308,10 @@ SUBROUTINE SFCDRV(LUGB, IDIM,JDIM,LENSFC,LSOIL,DELTSFC, &
INTEGER :: I, IERR
INTEGER :: I_INDEX(LENSFC), J_INDEX(LENSFC)
INTEGER :: IDUM(IDIM,JDIM)
integer :: num_parthds, num_threads

logical :: lake(lensfc)
real(kind=kind_io8) :: min_lakeice, min_seaice

REAL :: SLMASK(LENSFC), OROG(LENSFC)
REAL :: SIHFCS(LENSFC), SICFCS(LENSFC)
Expand Down Expand Up @@ -443,6 +448,10 @@ SUBROUTINE SFCDRV(LUGB, IDIM,JDIM,LENSFC,LSOIL,DELTSFC, &
!--------------------------------------------------------------------------------

IF (.NOT. ADJT_NST_ONLY) THEN
num_threads = num_parthds()
lake = .false.
min_seaice = 0.15
min_lakeice = 0.15
PRINT*
PRINT*,"CALL SFCCYCLE TO UPDATE SURFACE FIELDS."
CALL SFCCYCLE(LUGB,LENSFC,LSOIL,SIG1T,DELTSFC, &
Expand All @@ -453,8 +462,9 @@ SUBROUTINE SFCDRV(LUGB, IDIM,JDIM,LENSFC,LSOIL,DELTSFC, &
TSFFCS,SNOFCS,ZORFCS,ALBFCS,TG3FCS, &
CNPFCS,SMCFCS,STCFCS,SLIFCS,AISFCS, &
VEGFCS,VETFCS,SOTFCS,ALFFCS, &
CVFCS,CVBFCS,CVTFCS,MYRANK,NLUNIT, &
CVFCS,CVBFCS,CVTFCS,MYRANK,num_threads, NLUNIT, &
SZ_NML, INPUT_NML_FILE, &
lake, min_lakeice, min_seaice, &
IALB,ISOT,IVEGSRC,TILE_NUM,I_INDEX,J_INDEX)
ENDIF

Expand Down
Loading

0 comments on commit 04b8974

Please sign in to comment.