Skip to content

Commit

Permalink
Merge branch 'NOAA-EMC:develop' into develop
Browse files Browse the repository at this point in the history
  • Loading branch information
HelinWei-NOAA authored Apr 19, 2024
2 parents d7bb15f + 979bcab commit b29bd0f
Show file tree
Hide file tree
Showing 32 changed files with 1,422 additions and 301 deletions.
5 changes: 4 additions & 1 deletion CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ option(ENABLE_DOCS "Enable generation of doxygen-based documentation." OFF)
# Determine whether or not to generate documentation.
if(ENABLE_DOCS)
find_package(Doxygen REQUIRED)
add_subdirectory(docs)
add_subdirectory(docs)
endif()

# Enable CI build & unit testing:
Expand All @@ -22,6 +22,7 @@ endif()
### CCPP
###############################################################################

set(MPI ON)
add_subdirectory(ccpp)

###############################################################################
Expand All @@ -37,6 +38,7 @@ if(MOVING_NEST)
set(MOVING_NEST ON)
endif()
add_subdirectory(atmos_cubed_sphere)
target_compile_definitions(fv3 PRIVATE BYPASS_BREED_SLP_INLINE)

###############################################################################
### fv3atm
Expand Down Expand Up @@ -104,6 +106,7 @@ add_library(fv3atm
cpl/module_block_data.F90
cpl/module_cplfields.F90
cpl/module_cap_cpl.F90
cpl/module_cplscalars.F90
io/fv3atm_common_io.F90
io/fv3atm_clm_lake_io.F90
io/fv3atm_rrfs_sd_io.F90
Expand Down
111 changes: 84 additions & 27 deletions atmos_model.F90
Original file line number Diff line number Diff line change
Expand Up @@ -450,7 +450,7 @@ end subroutine update_atmos_radiation_physics
! variable type are allocated for the global grid (without halo regions).
! </INOUT>
subroutine atmos_timestep_diagnostics(Atmos)
use mpi
use mpi_f08
implicit none
type (atmos_data_type), intent(in) :: Atmos
!--- local variables---
Expand Down Expand Up @@ -582,7 +582,8 @@ subroutine atmos_model_init (Atmos, Time_init, Time, Time_step)
call atmosphere_diag_axes (Atmos%axes)
call atmosphere_etalvls (Atmos%ak, Atmos%bk, flip=flip_vc)

call atmosphere_control_data (isc, iec, jsc, jec, nlev, p_hydro, hydro, tile_num)
tile_num=-1
call atmosphere_control_data (isc, iec, jsc, jec, nlev, p_hydro, hydro, global_tile_num=tile_num)

allocate (Atmos%lon(nlon,nlat), Atmos%lat(nlon,nlat))
call atmosphere_grid_ctr (Atmos%lon, Atmos%lat)
Expand Down Expand Up @@ -1977,6 +1978,58 @@ subroutine assign_importdata(jdat, rc)
endif
endif

! get zonal ocean current:
!--------------------------------------------------------------------------
fldname = 'ocn_current_zonal'
if (trim(impfield_name) == trim(fldname)) then
findex = queryImportFields(fldname)
if (importFieldsValid(findex) .and. GFS_control%cplocn2atm) then
!$omp parallel do default(shared) private(i,j,nb,ix)
do j=jsc,jec
do i=isc,iec
nb = Atm_block%blkno(i,j)
ix = Atm_block%ixp(i,j)
GFS_Data(nb)%Sfcprop%usfco(ix) = zero
if (GFS_Data(nb)%Sfcprop%oceanfrac(ix) > zero) then ! ocean points
if(mergeflg(i,j)) then
GFS_Data(nb)%Sfcprop%usfco(ix) = zero
datar8(i,j) = zero
else
GFS_Data(nb)%Sfcprop%usfco(ix) = datar8(i,j)
endif
endif
enddo
enddo
if (mpp_pe() == mpp_root_pe() .and. debug) print *,'get usfco from mediator'
endif
endif

! get meridional ocean current:
!--------------------------------------------------------------------------
fldname = 'ocn_current_merid'
if (trim(impfield_name) == trim(fldname)) then
findex = queryImportFields(fldname)
if (importFieldsValid(findex) .and. GFS_control%cplocn2atm) then
!$omp parallel do default(shared) private(i,j,nb,ix)
do j=jsc,jec
do i=isc,iec
nb = Atm_block%blkno(i,j)
ix = Atm_block%ixp(i,j)
GFS_Data(nb)%Sfcprop%vsfco(ix) = zero
if (GFS_Data(nb)%Sfcprop%oceanfrac(ix) > zero) then ! ocean points
if(mergeflg(i,j)) then
GFS_Data(nb)%Sfcprop%vsfco(ix) = zero
datar8(i,j) = zero
else
GFS_Data(nb)%Sfcprop%vsfco(ix) = datar8(i,j)
endif
endif
enddo
enddo
if (mpp_pe() == mpp_root_pe() .and. debug) print *,'get vsfco from mediator'
endif
endif

! get sea ice fraction: fice or sea ice concentration from the mediator
!-----------------------------------------------------------------------
fldname = 'ice_fraction'
Expand Down Expand Up @@ -3090,7 +3143,8 @@ subroutine setup_exportdata(rc)

use ESMF

use module_cplfields, only: exportFields, chemistryFieldNames
use module_cplfields, only: exportFields, chemistryFieldNames
use module_cplscalars, only: flds_scalar_name

!--- arguments
integer, optional, intent(out) :: rc
Expand Down Expand Up @@ -3140,33 +3194,36 @@ subroutine setup_exportdata(rc)
if (isFound) then
call ESMF_FieldGet(exportFields(n), name=fieldname, rank=rank, typekind=datatype, rc=localrc)
if (ESMF_LogFoundError(rcToCheck=localrc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__, rcToReturn=rc)) return
if (datatype == ESMF_TYPEKIND_R8) then
select case (rank)
case (2)
call ESMF_FieldGet(exportFields(n),farrayPtr=datar82d,localDE=0, rc=localrc)
if (ESMF_LogFoundError(rcToCheck=localrc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__, rcToReturn=rc)) return
case (3)
call ESMF_FieldGet(exportFields(n),farrayPtr=datar83d,localDE=0, rc=localrc)
if (ESMF_LogFoundError(rcToCheck=localrc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__, rcToReturn=rc)) return
case default
!--- skip field
isFound = .false.
end select
else if (datatype == ESMF_TYPEKIND_R4) then
select case (rank)
case (2)
call ESMF_FieldGet(exportFields(n),farrayPtr=datar42d,localDE=0, rc=localrc)
if (ESMF_LogFoundError(rcToCheck=localrc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__, rcToReturn=rc)) return
case default
!--- skip field
isFound = .false.
end select
else
!--- skip field
if (trim(fieldname) == trim(flds_scalar_name)) then
isFound = .false.
else
if (datatype == ESMF_TYPEKIND_R8) then
select case (rank)
case (2)
call ESMF_FieldGet(exportFields(n),farrayPtr=datar82d,localDE=0, rc=localrc)
if (ESMF_LogFoundError(rcToCheck=localrc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__, rcToReturn=rc)) return
case (3)
call ESMF_FieldGet(exportFields(n),farrayPtr=datar83d,localDE=0, rc=localrc)
if (ESMF_LogFoundError(rcToCheck=localrc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__, rcToReturn=rc)) return
case default
!--- skip field
isFound = .false.
end select
else if (datatype == ESMF_TYPEKIND_R4) then
select case (rank)
case (2)
call ESMF_FieldGet(exportFields(n),farrayPtr=datar42d,localDE=0, rc=localrc)
if (ESMF_LogFoundError(rcToCheck=localrc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__, rcToReturn=rc)) return
case default
!--- skip field
isFound = .false.
end select
else
!--- skip field
isFound = .false.
end if
end if
end if

!--- skip field if only required for chemistry
if (isFound .and. GFS_control%cplchm) isFound = .not.any(trim(fieldname) == chemistryFieldNames)

Expand Down
1 change: 1 addition & 0 deletions ccpp/config/ccpp_prebuild_config.py
Original file line number Diff line number Diff line change
Expand Up @@ -29,6 +29,7 @@
TYPEDEFS_NEW_METADATA = {
'ccpp_types' : {
'ccpp_t' : 'cdata',
'MPI_Comm' : '',
'ccpp_types' : '',
},
'machine' : {
Expand Down
2 changes: 1 addition & 1 deletion ccpp/data/CCPP_typedefs.F90
Original file line number Diff line number Diff line change
Expand Up @@ -690,7 +690,7 @@ subroutine gfs_interstitial_create (Interstitial, IM, Model)
allocate (Interstitial%sigma (IM))
allocate (Interstitial%sigmaf (IM))
allocate (Interstitial%sigmafrac (IM,Model%levs))
allocate (Interstitial%sigmatot (IM,Model%levs))
allocate (Interstitial%sigmatot (IM,Model%levs+1))
allocate (Interstitial%snowc (IM))
allocate (Interstitial%snohf (IM))
allocate (Interstitial%snowmt (IM))
Expand Down
2 changes: 1 addition & 1 deletion ccpp/data/CCPP_typedefs.meta
Original file line number Diff line number Diff line change
Expand Up @@ -1952,7 +1952,7 @@
standard_name = convective_updraft_area_fraction_at_model_interfaces
long_name = convective updraft area fraction at model interfaces
units = frac
dimensions = (horizontal_loop_extent,vertical_layer_dimension)
dimensions = (horizontal_loop_extent,vertical_interface_dimension)
type = real
kind = kind_phys
[skip_macro]
Expand Down
Loading

0 comments on commit b29bd0f

Please sign in to comment.