Skip to content

Commit

Permalink
Merge branch 'dev-master-candidate-ncar-2020-03-27' of https://github…
Browse files Browse the repository at this point in the history
….com/gustavo-marques/MOM6 into gustavo-marques-dev-master-candidate-ncar-2020-03-27
  • Loading branch information
adcroft committed Mar 30, 2020
2 parents 9f31539 + 6ce3dd9 commit e73db38
Show file tree
Hide file tree
Showing 23 changed files with 1,947 additions and 604 deletions.
100 changes: 0 additions & 100 deletions config_src/mct_driver/mom_ocean_model_mct.F90
Original file line number Diff line number Diff line change
Expand Up @@ -80,16 +80,8 @@ module MOM_ocean_model_mct
public ocean_model_restart
public ice_ocn_bnd_type_chksum
public ocean_public_type_chksum
public ocean_model_data_get
public get_ocean_grid

!> This interface extracts a named scalar field or array from the ocean surface or public type
interface ocean_model_data_get
module procedure ocean_model_data1D_get
module procedure ocean_model_data2D_get
end interface


!> This type is used for communication with other components via the FMS coupler.
!! The element names and types can be changed only with great deliberation, hence
!! the persistnce of things like the cutsy element name "avg_kount".
Expand Down Expand Up @@ -1052,98 +1044,6 @@ subroutine Ocean_stock_pe(OS, index, value, time_index)

end subroutine Ocean_stock_pe

!> This subroutine extracts a named 2-D field from the ocean surface or public type
subroutine ocean_model_data2D_get(OS,Ocean, name, array2D,isc,jsc)
use MOM_constants, only : CELSIUS_KELVIN_OFFSET
type(ocean_state_type), pointer :: OS !< A pointer to the structure containing the
!! internal ocean state (intent in).
type(ocean_public_type), intent(in) :: Ocean !< A structure containing various publicly
!! visible ocean surface fields.
character(len=*) , intent(in) :: name !< The name of the field to extract
real, dimension(isc:,jsc:), intent(out):: array2D !< The values of the named field, it must
!! cover only the computational domain
integer , intent(in) :: isc !< The starting i-index of array2D
integer , intent(in) :: jsc !< The starting j-index of array2D

integer :: g_isc, g_iec, g_jsc, g_jec,g_isd, g_ied, g_jsd, g_jed, i, j

if (.not.associated(OS)) return
if (.not.OS%is_ocean_pe) return

! The problem is %areaT is on MOM domain but Ice_Ocean_Boundary%... is on mpp domain.
! We want to return the MOM data on the mpp (compute) domain
! Get MOM domain extents
call mpp_get_compute_domain(OS%grid%Domain%mpp_domain, g_isc, g_iec, g_jsc, g_jec)
call mpp_get_data_domain (OS%grid%Domain%mpp_domain, g_isd, g_ied, g_jsd, g_jed)

g_isc = g_isc-g_isd+1 ; g_iec = g_iec-g_isd+1 ; g_jsc = g_jsc-g_jsd+1 ; g_jec = g_jec-g_jsd+1


select case(name)
case('area')
array2D(isc:,jsc:) = OS%US%L_to_m**2*OS%grid%areaT(g_isc:g_iec,g_jsc:g_jec)
case('mask')
array2D(isc:,jsc:) = OS%grid%mask2dT(g_isc:g_iec,g_jsc:g_jec)
!OR same result
! do j=g_jsc,g_jec ; do i=g_isc,g_iec
! array2D(isc+i-g_isc,jsc+j-g_jsc) = OS%grid%mask2dT(i,j)
! enddo ; enddo
case('t_surf')
array2D(isc:,jsc:) = Ocean%t_surf(isc:,jsc:)-CELSIUS_KELVIN_OFFSET
case('t_pme')
array2D(isc:,jsc:) = Ocean%t_surf(isc:,jsc:)-CELSIUS_KELVIN_OFFSET
case('t_runoff')
array2D(isc:,jsc:) = Ocean%t_surf(isc:,jsc:)-CELSIUS_KELVIN_OFFSET
case('t_calving')
array2D(isc:,jsc:) = Ocean%t_surf(isc:,jsc:)-CELSIUS_KELVIN_OFFSET
case('btfHeat')
array2D(isc:,jsc:) = 0
case('tlat')
array2D(isc:,jsc:) = OS%grid%geoLatT(g_isc:g_iec,g_jsc:g_jec)
case('tlon')
array2D(isc:,jsc:) = OS%grid%geoLonT(g_isc:g_iec,g_jsc:g_jec)
case('ulat')
array2D(isc:,jsc:) = OS%grid%geoLatCu(g_isc:g_iec,g_jsc:g_jec)
case('ulon')
array2D(isc:,jsc:) = OS%grid%geoLonCu(g_isc:g_iec,g_jsc:g_jec)
case('vlat')
array2D(isc:,jsc:) = OS%grid%geoLatCv(g_isc:g_iec,g_jsc:g_jec)
case('vlon')
array2D(isc:,jsc:) = OS%grid%geoLonCv(g_isc:g_iec,g_jsc:g_jec)
case('geoLatBu')
array2D(isc:,jsc:) = OS%grid%geoLatBu(g_isc:g_iec,g_jsc:g_jec)
case('geoLonBu')
array2D(isc:,jsc:) = OS%grid%geoLonBu(g_isc:g_iec,g_jsc:g_jec)
case('cos_rot')
array2D(isc:,jsc:) = OS%grid%cos_rot(g_isc:g_iec,g_jsc:g_jec) ! =1
case('sin_rot')
array2D(isc:,jsc:) = OS%grid%sin_rot(g_isc:g_iec,g_jsc:g_jec) ! =0
case default
call MOM_error(FATAL,'get_ocean_grid_data2D: unknown argument name='//name)
end select
end subroutine ocean_model_data2D_get

!> This subroutine extracts a named scalar field from the ocean surface or public type
subroutine ocean_model_data1D_get(OS, Ocean, name, value)
type(ocean_state_type), pointer :: OS !< A pointer to the structure containing the
!! internal ocean state (intent in).
type(ocean_public_type), intent(in) :: Ocean !< A structure containing various publicly
!! visible ocean surface fields.
character(len=*) , intent(in) :: name !< The name of the field to extract
real , intent(out):: value !< The value of the named field

if (.not.associated(OS)) return
if (.not.OS%is_ocean_pe) return

select case(name)
case('c_p')
value = OS%C_p
case default
call MOM_error(FATAL,'get_ocean_grid_data1D: unknown argument name='//name)
end select

end subroutine ocean_model_data1D_get

!> Write out FMS-format checsums on fields from the ocean surface state
subroutine ocean_public_type_chksum(id, timestep, ocn)

Expand Down
5 changes: 4 additions & 1 deletion config_src/mct_driver/ocn_comp_mct.F90
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,7 @@ module ocn_comp_mct
use MOM_time_manager, only: time_type, set_date, set_time, set_calendar_type, NOLEAP
use MOM_time_manager, only: operator(+), operator(-), operator(*), operator(/)
use MOM_time_manager, only: operator(==), operator(/=), operator(>), get_time
use MOM_file_parser, only: get_param, log_version, param_file_type
use MOM_file_parser, only: get_param, log_version, param_file_type, close_param_file
use MOM_get_input, only: Get_MOM_Input, directories
use MOM_EOS, only: gsw_sp_from_sr, gsw_pt_from_ct
use MOM_constants, only: CELSIUS_KELVIN_OFFSET
Expand Down Expand Up @@ -281,6 +281,9 @@ subroutine ocn_init_mct( EClock, cdata_o, x2o_o, o2x_o, NLFilename )
glb%c1 = 0.0; glb%c2 = 0.0; glb%c3 = 0.0; glb%c4 = 0.0
endif

! Close param file before it gets opened by ocean_model_init again.
call close_param_file(param_file)

! Initialize the MOM6 model
runtype = get_runtype()
if (runtype == "initial") then
Expand Down
71 changes: 40 additions & 31 deletions config_src/nuopc_driver/mom_cap.F90
Original file line number Diff line number Diff line change
Expand Up @@ -123,6 +123,7 @@ module MOM_cap_mod
integer :: export_slice = 1
character(len=256) :: tmpstr
logical :: write_diagnostics = .false.
logical :: overwrite_timeslice = .false.
character(len=32) :: runtype !< run type
integer :: logunit !< stdout logging unit number
logical :: profile_memory = .true.
Expand Down Expand Up @@ -278,6 +279,21 @@ subroutine InitializeP0(gcomp, importState, exportState, clock, rc)
file=__FILE__)) &
return

overwrite_timeslice = .false.
call NUOPC_CompAttributeGet(gcomp, name="OverwriteSlice", value=value, &
isPresent=isPresent, isSet=isSet, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
line=__LINE__, &
file=__FILE__)) &
return
if (isPresent .and. isSet) overwrite_timeslice=(trim(value)=="true")
write(logmsg,*) overwrite_timeslice
call ESMF_LogWrite('MOM_cap:OverwriteSlice = '//trim(logmsg), ESMF_LOGMSG_INFO, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
line=__LINE__, &
file=__FILE__)) &
return

profile_memory = .false.
call NUOPC_CompAttributeGet(gcomp, name="ProfileMemory", value=value, &
isPresent=isPresent, isSet=isSet, rc=rc)
Expand Down Expand Up @@ -708,12 +724,10 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
Ice_ocean_boundary% seaice_melt (isc:iec,jsc:jec), &
Ice_ocean_boundary% mi (isc:iec,jsc:jec), &
Ice_ocean_boundary% p (isc:iec,jsc:jec), &
Ice_ocean_boundary% runoff (isc:iec,jsc:jec), &
Ice_ocean_boundary% calving (isc:iec,jsc:jec), &
Ice_ocean_boundary% runoff_hflx (isc:iec,jsc:jec), &
Ice_ocean_boundary% calving_hflx (isc:iec,jsc:jec), &
Ice_ocean_boundary% rofl_flux (isc:iec,jsc:jec), &
Ice_ocean_boundary% rofi_flux (isc:iec,jsc:jec))
Ice_ocean_boundary% lrunoff_hflx (isc:iec,jsc:jec), &
Ice_ocean_boundary% frunoff_hflx (isc:iec,jsc:jec), &
Ice_ocean_boundary% lrunoff (isc:iec,jsc:jec), &
Ice_ocean_boundary% frunoff (isc:iec,jsc:jec))

Ice_ocean_boundary%u_flux = 0.0
Ice_ocean_boundary%v_flux = 0.0
Expand All @@ -731,12 +745,10 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
Ice_ocean_boundary%seaice_melt_heat= 0.0
Ice_ocean_boundary%mi = 0.0
Ice_ocean_boundary%p = 0.0
Ice_ocean_boundary%runoff = 0.0
Ice_ocean_boundary%calving = 0.0
Ice_ocean_boundary%runoff_hflx = 0.0
Ice_ocean_boundary%calving_hflx = 0.0
Ice_ocean_boundary%rofl_flux = 0.0
Ice_ocean_boundary%rofi_flux = 0.0
Ice_ocean_boundary%lrunoff_hflx = 0.0
Ice_ocean_boundary%frunoff_hflx = 0.0
Ice_ocean_boundary%lrunoff = 0.0
Ice_ocean_boundary%frunoff = 0.0

ocean_internalstate%ptr%ocean_state_type_ptr => ocean_state
call ESMF_GridCompSetInternalState(gcomp, ocean_internalstate, rc)
Expand All @@ -745,11 +757,12 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
file=__FILE__)) &
return ! bail out

if (len_trim(scalar_field_name) > 0) then
call fld_list_add(fldsToOcn_num, fldsToOcn, trim(scalar_field_name), "will_provide")
call fld_list_add(fldsFrOcn_num, fldsFrOcn, trim(scalar_field_name), "will_provide")
end if

if (cesm_coupled) then
if (len_trim(scalar_field_name) > 0) then
call fld_list_add(fldsToOcn_num, fldsToOcn, trim(scalar_field_name), "will_provide")
call fld_list_add(fldsFrOcn_num, fldsFrOcn, trim(scalar_field_name), "will_provide")
endif
!call fld_list_add(fldsToOcn_num, fldsToOcn, "Sw_lamult" , "will provide")
!call fld_list_add(fldsToOcn_num, fldsToOcn, "Sw_ustokes" , "will provide")
!call fld_list_add(fldsToOcn_num, fldsToOcn, "Sw_vstokes" , "will provide")
Expand Down Expand Up @@ -780,11 +793,9 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
call fld_list_add(fldsToOcn_num, fldsToOcn, "Foxx_rofi" , "will provide") !-> ice runoff
call fld_list_add(fldsToOcn_num, fldsToOcn, "mean_fresh_water_to_ocean_rate", "will provide")
call fld_list_add(fldsToOcn_num, fldsToOcn, "net_heat_flx_to_ocn" , "will provide")

!call fld_list_add(fldsToOcn_num, fldsToOcn, "mean_runoff_rate" , "will provide")
!call fld_list_add(fldsToOcn_num, fldsToOcn, "mean_calving_rate" , "will provide")
!call fld_list_add(fldsToOcn_num, fldsToOcn, "mean_runoff_heat_flx" , "will provide")
!call fld_list_add(fldsToOcn_num, fldsToOcn, "mean_calving_heat_flx" , "will provide")
!These are not currently used and changing requires a nuopc dictionary change
!call fld_list_add(fldsToOcn_num, fldsToOcn, "mean_runoff_heat_flx" , "will provide")
!call fld_list_add(fldsToOcn_num, fldsToOcn, "mean_calving_heat_flx" , "will provide")

!--------- export fields -------------
call fld_list_add(fldsFrOcn_num, fldsFrOcn, "ocean_mask" , "will provide")
Expand Down Expand Up @@ -1494,13 +1505,11 @@ subroutine DataInitialize(gcomp, rc)
ocean_state => ocean_internalstate%ptr%ocean_state_type_ptr
call get_ocean_grid(ocean_state, ocean_grid)

if (cesm_coupled) then
call mom_export(ocean_public, ocean_grid, ocean_state, exportState, clock, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
line=__LINE__, &
file=__FILE__)) &
return ! bail out
endif
call mom_export(ocean_public, ocean_grid, ocean_state, exportState, clock, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
line=__LINE__, &
file=__FILE__)) &
return ! bail out

call ESMF_StateGet(exportState, itemCount=fieldCount, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
Expand Down Expand Up @@ -1543,7 +1552,7 @@ subroutine DataInitialize(gcomp, rc)

if(write_diagnostics) then
call NUOPC_Write(exportState, fileNamePrefix='field_init_ocn_export_', &
timeslice=import_slice, relaxedFlag=.true., rc=rc)
overwrite=overwrite_timeslice,timeslice=import_slice, relaxedFlag=.true., rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
line=__LINE__, &
file=__FILE__)) &
Expand Down Expand Up @@ -1697,7 +1706,7 @@ subroutine ModelAdvance(gcomp, rc)

if (write_diagnostics) then
call NUOPC_Write(importState, fileNamePrefix='field_ocn_import_', &
timeslice=import_slice, relaxedFlag=.true., rc=rc)
overwrite=overwrite_timeslice,timeslice=import_slice, relaxedFlag=.true., rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
line=__LINE__, &
file=__FILE__)) &
Expand Down Expand Up @@ -1853,7 +1862,7 @@ subroutine ModelAdvance(gcomp, rc)

if (write_diagnostics) then
call NUOPC_Write(exportState, fileNamePrefix='field_ocn_export_', &
timeslice=export_slice, relaxedFlag=.true., rc=rc)
overwrite=overwrite_timeslice,timeslice=export_slice, relaxedFlag=.true., rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
line=__LINE__, &
file=__FILE__)) &
Expand Down
48 changes: 13 additions & 35 deletions config_src/nuopc_driver/mom_cap_methods.F90
Original file line number Diff line number Diff line change
Expand Up @@ -214,64 +214,42 @@ subroutine mom_import(ocean_public, ocean_grid, importState, ice_ocean_boundary,
return ! bail out

!----
! runoff and heat content of runoff
! mass and heat content of liquid and frozen runoff
!----
! Note - preset values to 0, if field does not exist in importState, then will simply return
! and preset value will be used

! liquid runoff
ice_ocean_boundary%rofl_flux (:,:) = 0._ESMF_KIND_R8
ice_ocean_boundary%lrunoff (:,:) = 0._ESMF_KIND_R8
call state_getimport(importState, 'Foxx_rofl', &
isc, iec, jsc, jec, ice_ocean_boundary%rofl_flux,rc=rc)
isc, iec, jsc, jec, ice_ocean_boundary%lrunoff,rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
line=__LINE__, &
file=__FILE__)) &
return ! bail out

! ice runoff
ice_ocean_boundary%rofi_flux (:,:) = 0._ESMF_KIND_R8
ice_ocean_boundary%frunoff (:,:) = 0._ESMF_KIND_R8
call state_getimport(importState, 'Foxx_rofi', &
isc, iec, jsc, jec, ice_ocean_boundary%rofi_flux,rc=rc)
isc, iec, jsc, jec, ice_ocean_boundary%frunoff,rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
line=__LINE__, &
file=__FILE__)) &
return ! bail out

! total runoff
ice_ocean_boundary%runoff (:,:) = 0._ESMF_KIND_R8
call state_getimport(importState, 'mean_runoff_rate', &
isc, iec, jsc, jec, ice_ocean_boundary%runoff, rc=rc)
! heat content of lrunoff
ice_ocean_boundary%lrunoff_hflx(:,:) = 0._ESMF_KIND_R8
call state_getimport(importState, 'mean_runoff_heat_flx', &
isc, iec, jsc, jec, ice_ocean_boundary%lrunoff_hflx, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
line=__LINE__, &
file=__FILE__)) &
return ! bail out

! heat content of runoff
ice_ocean_boundary%runoff_hflx(:,:) = 0._ESMF_KIND_R8
call state_getimport(importState, 'mean_runoff_heat_flux', &
isc, iec, jsc, jec, ice_ocean_boundary%runoff_hflx, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
line=__LINE__, &
file=__FILE__)) &
return ! bail out

!----
! calving rate and heat flux
!----
! Note - preset values to 0, if field does not exist in importState, then will simply return
! and preset value will be used

ice_ocean_boundary%calving(:,:) = 0._ESMF_KIND_R8
call state_getimport(importState, 'mean_calving_rate', &
isc, iec, jsc, jec, ice_ocean_boundary%calving, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
line=__LINE__, &
file=__FILE__)) &
return ! bail out

ice_ocean_boundary%calving_hflx(:,:) = 0._ESMF_KIND_R8
call state_getimport(importState, 'mean_calving_heat_flux', &
isc, iec, jsc, jec, ice_ocean_boundary%calving_hflx, rc=rc)
! heat content of frunoff
ice_ocean_boundary%frunoff_hflx(:,:) = 0._ESMF_KIND_R8
call state_getimport(importState, 'mean_calving_heat_flx', &
isc, iec, jsc, jec, ice_ocean_boundary%frunoff_hflx, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
line=__LINE__, &
file=__FILE__)) &
Expand Down
Loading

0 comments on commit e73db38

Please sign in to comment.