Skip to content

Commit

Permalink
Revert changes to gcycle.F90 and sfcsub.F
Browse files Browse the repository at this point in the history
  • Loading branch information
climbfuji committed Mar 16, 2020
1 parent 3dd9a86 commit 874e5ec
Show file tree
Hide file tree
Showing 3 changed files with 920 additions and 969 deletions.
22 changes: 7 additions & 15 deletions gfsphysics/physics/gcycle.F90
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ SUBROUTINE GCYCLE (nblks, Model, Grid, Sfcprop, Cldprop)
GFS_sfcprop_type, GFS_cldprop_type
implicit none

integer, intent(in) :: nblks
integer :: nblks
type(GFS_control_type), intent(in) :: Model
type(GFS_grid_type), intent(in) :: Grid(nblks)
type(GFS_sfcprop_type), intent(inout) :: Sfcprop(nblks)
Expand All @@ -33,7 +33,7 @@ SUBROUTINE GCYCLE (nblks, Model, Grid, Sfcprop, Cldprop)
TG3FCS (Model%nx*Model%ny), &
CNPFCS (Model%nx*Model%ny), &
AISFCS (Model%nx*Model%ny), &
! F10MFCS(Model%nx*Model%ny), &
F10MFCS(Model%nx*Model%ny), &
VEGFCS (Model%nx*Model%ny), &
VETFCS (Model%nx*Model%ny), &
SOTFCS (Model%nx*Model%ny), &
Expand All @@ -54,8 +54,6 @@ SUBROUTINE GCYCLE (nblks, Model, Grid, Sfcprop, Cldprop)
STCFC1 (Model%nx*Model%ny*Model%lsoil), &
SLCFC1 (Model%nx*Model%ny*Model%lsoil)

logical :: lake(Model%nx*Model%ny)

character(len=6) :: tile_num_ch
real(kind=kind_phys), parameter :: pifac=180.0/pi
real(kind=kind_phys) :: sig1t, dt_warm
Expand Down Expand Up @@ -104,7 +102,7 @@ SUBROUTINE GCYCLE (nblks, Model, Grid, Sfcprop, Cldprop)
ZORFCS (len) = Sfcprop(nb)%zorl (ix)
TG3FCS (len) = Sfcprop(nb)%tg3 (ix)
CNPFCS (len) = Sfcprop(nb)%canopy (ix)
! F10MFCS (len) = Sfcprop(nb)%f10m (ix)
F10MFCS (len) = Sfcprop(nb)%f10m (ix)
VEGFCS (len) = Sfcprop(nb)%vfrac (ix)
VETFCS (len) = Sfcprop(nb)%vtype (ix)
SOTFCS (len) = Sfcprop(nb)%stype (ix)
Expand Down Expand Up @@ -145,11 +143,6 @@ SUBROUTINE GCYCLE (nblks, Model, Grid, Sfcprop, Cldprop)
ELSE
AISFCS(len) = 0.
ENDIF
if (Sfcprop(nb)%lakefrac(ix) > 0.0) then
lake(len) = .true.
else
lake(len) = .false.
endif

! if (Model%me .eq. 0)
! & print *,' len=',len,' rla=',rla(len),' rlo=',rlo(len)
Expand Down Expand Up @@ -184,7 +177,6 @@ SUBROUTINE GCYCLE (nblks, Model, Grid, Sfcprop, Cldprop)
CVBFCS, CVTFCS, Model%me, Model%nlunit, &
size(Model%input_nml_file), &
Model%input_nml_file, &
lake, Model%min_lakeice, Model%min_seaice, &
Model%ialb, Model%isot, Model%ivegsrc, &
trim(tile_num_ch), i_index, j_index)
#ifndef INTERNAL_FILE_NML
Expand All @@ -197,10 +189,10 @@ SUBROUTINE GCYCLE (nblks, Model, Grid, Sfcprop, Cldprop)
len = len + 1
Sfcprop(nb)%slmsk (ix) = SLIFCS (len)
if ( Model%nstf_name(1) > 0 ) then
Sfcprop(nb)%tref(ix) = TSFFCS (len)
! if ( Model%nstf_name(2) == 0 ) then
Sfcprop(nb)%tref(ix) = TSFFCS (len)
! if (Model%nstf_name(2) == 0) then
! dt_warm = (Sfcprop(nb)%xt(ix) + Sfcprop(nb)%xt(ix) ) &
! / Sfcprop(nb)%xz(ix)
! / Sfcprop(nb)%xz(ix)
! Sfcprop(nb)%tsfco(ix) = Sfcprop(nb)%tref(ix) &
! + dt_warm - Sfcprop(nb)%dt_cool(ix)
! endif
Expand All @@ -212,7 +204,7 @@ SUBROUTINE GCYCLE (nblks, Model, Grid, Sfcprop, Cldprop)
Sfcprop(nb)%zorl (ix) = ZORFCS (len)
Sfcprop(nb)%tg3 (ix) = TG3FCS (len)
Sfcprop(nb)%canopy (ix) = CNPFCS (len)
! Sfcprop(nb)%f10m (ix) = F10MFCS (len)
Sfcprop(nb)%f10m (ix) = F10MFCS (len)
Sfcprop(nb)%vfrac (ix) = VEGFCS (len)
Sfcprop(nb)%vtype (ix) = VETFCS (len)
Sfcprop(nb)%stype (ix) = SOTFCS (len)
Expand Down
Loading

0 comments on commit 874e5ec

Please sign in to comment.