Skip to content

Commit

Permalink
Merge pull request #75 from NCAR/dev/nuopc_alper
Browse files Browse the repository at this point in the history
minor fixes and stylistic changes to dev/nuopc
  • Loading branch information
rsdunlapiv authored Jul 23, 2018
2 parents 8606be9 + 116fdfb commit 353f60f
Show file tree
Hide file tree
Showing 9 changed files with 1,583 additions and 1,499 deletions.
129 changes: 63 additions & 66 deletions config_src/mct_driver/MOM_ocean_model.F90
Original file line number Diff line number Diff line change
Expand Up @@ -56,7 +56,7 @@ module MOM_ocean_model
use MOM_variables, only : surface
use MOM_verticalGrid, only : verticalGrid_type
use MOM_ice_shelf, only : initialize_ice_shelf, shelf_calc_flux, ice_shelf_CS
use MOM_ice_shelf, only : ice_shelf_end, ice_shelf_save_restart
use MOM_ice_shelf, only : add_shelf_forces, ice_shelf_end, ice_shelf_save_restart
use coupler_types_mod, only : coupler_1d_bc_type, coupler_2d_bc_type
use coupler_types_mod, only : coupler_type_spawn, coupler_type_write_chksums
use coupler_types_mod, only : coupler_type_initialized, coupler_type_copy_data
Expand Down Expand Up @@ -105,8 +105,8 @@ module MOM_ocean_model
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".
!! The element names and types can be changed only with great deliberation, hence
!! the persistnce of things like the cutsy element name "avg_kount".
type, public :: ocean_public_type
type(domain2d) :: Domain !< The domain for the surface fields.
logical :: is_ocean_pe !! .true. on processors that run the ocean model.
Expand Down Expand Up @@ -205,7 +205,7 @@ module MOM_ocean_model
diag => NULL() !< A pointer to the diagnostic regulatory structure
end type ocean_state_type

integer :: id_clock_forcing
integer :: id_clock_forcing

!=======================================================================
contains
Expand Down Expand Up @@ -286,14 +286,14 @@ subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, gas_fields_ocn, i
"returned to the coupler. Valid values include \n"//&
"'A', 'B', or 'C'.", default="C")
if (uppercase(stagger(1:1)) == 'A') then
Ocean_sfc%stagger = AGRID
Ocean_sfc%stagger = AGRID
elseif (uppercase(stagger(1:1)) == 'B') then
Ocean_sfc%stagger = BGRID_NE
Ocean_sfc%stagger = BGRID_NE
elseif (uppercase(stagger(1:1)) == 'C') then
Ocean_sfc%stagger = CGRID_NE
Ocean_sfc%stagger = CGRID_NE
else
call MOM_error(FATAL,"ocean_model_init: OCEAN_SURFACE_STAGGER = "// &
trim(stagger)//" is invalid.")
call MOM_error(FATAL,"ocean_model_init: OCEAN_SURFACE_STAGGER = "// &
trim(stagger)//" is invalid.")
end if

call get_param(param_file, mdl, "RESTORE_SALINITY",OS%restore_salinity, &
Expand Down Expand Up @@ -472,7 +472,8 @@ subroutine update_ocean_model(Ice_ocean_boundary, OS, Ocean_sfc, &

! Add ice shelf fluxes
if (OS%use_ice_shelf) then
call shelf_calc_flux(OS%sfc_state, OS%forces, OS%fluxes, OS%Time, time_step, OS%Ice_shelf_CSp)
call shelf_calc_flux(OS%sfc_state, OS%fluxes, OS%Time, time_step, OS%Ice_shelf_CSp)
call add_shelf_forces(OS%grid, OS%Ice_shelf_CSp, OS%forces)
endif

! GMM, check ocean_model_MOM.F90 to enable the following option
Expand All @@ -495,7 +496,8 @@ subroutine update_ocean_model(Ice_ocean_boundary, OS, Ocean_sfc, &
OS%sfc_state, OS%restore_salinity, OS%restore_temp)

if (OS%use_ice_shelf) then
call shelf_calc_flux(OS%sfc_state, OS%forces, OS%flux_tmp, OS%Time, time_step, OS%Ice_shelf_CSp)
call shelf_calc_flux(OS%sfc_state, OS%flux_tmp, OS%Time, time_step, OS%Ice_shelf_CSp)
call add_shelf_forces(OS%grid, OS%Ice_shelf_CSp, OS%forces)
endif

! GMM, check ocean_model_MOM.F90 to enable the following option
Expand Down Expand Up @@ -661,9 +663,9 @@ subroutine ocean_model_save_restart(OS, Time, directory, filename_suffix)
"restart files can only be created after the buoyancy forcing is applied.")

if (present(directory)) then
restart_dir = directory
restart_dir = directory
else
restart_dir = OS%dirs%restart_output_dir
restart_dir = OS%dirs%restart_output_dir
endif

call save_restart(restart_dir, Time, OS%grid, OS%restart_CSp, GV=OS%GV)
Expand Down Expand Up @@ -698,9 +700,9 @@ subroutine initialize_ocean_public_type(input_domain, Ocean_sfc, diag, maskmap,
call mpp_get_layout(input_domain,layout)
call mpp_get_global_domain(input_domain, xsize=xsz, ysize=ysz)
if(PRESENT(maskmap)) then
call mpp_define_domains((/1,xsz,1,ysz/),layout,Ocean_sfc%Domain, maskmap=maskmap)
call mpp_define_domains((/1,xsz,1,ysz/),layout,Ocean_sfc%Domain, maskmap=maskmap)
else
call mpp_define_domains((/1,xsz,1,ysz/),layout,Ocean_sfc%Domain)
call mpp_define_domains((/1,xsz,1,ysz/),layout,Ocean_sfc%Domain)
endif
call mpp_get_compute_domain(Ocean_sfc%Domain, isc, iec, jsc, jec)

Expand Down Expand Up @@ -819,19 +821,14 @@ subroutine convert_state_to_ocean_type(state, Ocean_sfc, G, patm, press_to_z)

end subroutine convert_state_to_ocean_type

!=======================================================================
! <SUBROUTINE NAME="ocean_model_init_sfc">
!
! <DESCRIPTION>
! This subroutine extracts the surface properties from the ocean's internal
! state and stores them in the ocean type returned to the calling ice model.
! It has to be separate from the ocean_initialization call because the coupler
! module allocates the space for some of these variables.
! </DESCRIPTION>

!> This subroutine extracts the surface properties from the ocean's internal
!! state and stores them in the ocean type returned to the calling ice model.
!! It has to be separate from the ocean_initialization call because the coupler
!! module allocates the space for some of these variables.
subroutine ocean_model_init_sfc(OS, Ocean_sfc)
type(ocean_state_type), pointer :: OS
type(ocean_public_type), intent(inout) :: Ocean_sfc
type(ocean_state_type), pointer :: OS !< A pointer to the structure containing the
!! internal ocean state (in).
type(ocean_public_type), intent(inout) :: Ocean_sfc !< Ocean surface state

integer :: is, ie, js, je

Expand Down Expand Up @@ -940,45 +937,45 @@ subroutine ocean_model_data2D_get(OS,Ocean, name, array2D,isc,jsc)

select case(name)
case('area')
array2D(isc:,jsc:) = OS%grid%areaT(g_isc:g_iec,g_jsc:g_jec)
array2D(isc:,jsc:) = 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)
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
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
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
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
array2D(isc:,jsc:) = Ocean%t_surf(isc:,jsc:)-CELSIUS_KELVIN_OFFSET
case('btfHeat')
array2D(isc:,jsc:) = 0
array2D(isc:,jsc:) = 0
case('tlat')
array2D(isc:,jsc:) = OS%grid%geoLatT(g_isc:g_iec,g_jsc:g_jec)
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)
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)
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)
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)
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)
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)
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)
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
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
array2D(isc:,jsc:) = OS%grid%sin_rot(g_isc:g_iec,g_jsc:g_jec) ! =0
case default
call MOM_error(FATAL,'ocean_model_data2D_get: unknown argument name='//name)
call MOM_error(FATAL,'ocean_model_data2D_get: unknown argument name='//name)
end select
end subroutine ocean_model_data2D_get

Expand All @@ -993,30 +990,30 @@ subroutine ocean_model_data1D_get(OS,Ocean, name, value)

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

subroutine ocean_public_type_chksum(id, timestep, ocn)

character(len=*), intent(in) :: id
integer , intent(in) :: timestep
type(ocean_public_type), intent(in) :: ocn
integer :: n,m, outunit
character(len=*), intent(in) :: id
integer , intent(in) :: timestep
type(ocean_public_type), intent(in) :: ocn
integer :: n,m, outunit

outunit = stdout()
outunit = stdout()

write(outunit,*) "BEGIN CHECKSUM(ocean_type):: ", id, timestep
write(outunit,100) 'ocean%t_surf ',mpp_chksum(ocn%t_surf )
write(outunit,100) 'ocean%s_surf ',mpp_chksum(ocn%s_surf )
write(outunit,100) 'ocean%u_surf ',mpp_chksum(ocn%u_surf )
write(outunit,100) 'ocean%v_surf ',mpp_chksum(ocn%v_surf )
write(outunit,100) 'ocean%sea_lev ',mpp_chksum(ocn%sea_lev)
write(outunit,100) 'ocean%frazil ',mpp_chksum(ocn%frazil )
write(outunit,*) "BEGIN CHECKSUM(ocean_type):: ", id, timestep
write(outunit,100) 'ocean%t_surf ',mpp_chksum(ocn%t_surf )
write(outunit,100) 'ocean%s_surf ',mpp_chksum(ocn%s_surf )
write(outunit,100) 'ocean%u_surf ',mpp_chksum(ocn%u_surf )
write(outunit,100) 'ocean%v_surf ',mpp_chksum(ocn%v_surf )
write(outunit,100) 'ocean%sea_lev ',mpp_chksum(ocn%sea_lev)
write(outunit,100) 'ocean%frazil ',mpp_chksum(ocn%frazil )

call coupler_type_write_chksums(ocn%fields, outunit, 'ocean%')
call coupler_type_write_chksums(ocn%fields, outunit, 'ocean%')
100 FORMAT(" CHECKSUM::",A20," = ",Z20)
end subroutine ocean_public_type_chksum

Expand All @@ -1027,14 +1024,14 @@ end subroutine ocean_public_type_chksum
! Obtain the ocean grid.
! </DESCRIPTION>
!
subroutine get_ocean_grid(OS, Gridp)
type(ocean_state_type) :: OS
type(ocean_grid_type) , pointer :: Gridp
subroutine get_ocean_grid(OS, Gridp)
type(ocean_state_type) :: OS
type(ocean_grid_type) , pointer :: Gridp

Gridp => OS%grid
return
Gridp => OS%grid
return

end subroutine get_ocean_grid
end subroutine get_ocean_grid
! </SUBROUTINE> NAME="get_ocean_grid"

end module MOM_ocean_model
Loading

0 comments on commit 353f60f

Please sign in to comment.