Skip to content

Commit

Permalink
Merge pull request #12 from gustavo-marques/fill_ice_ocean_bnd
Browse files Browse the repository at this point in the history
First draft of fill ice ocean boundary
  • Loading branch information
alperaltuntas authored Jul 25, 2017
2 parents a306c90 + 6b6289a commit e6c5ddd
Show file tree
Hide file tree
Showing 2 changed files with 127 additions and 24 deletions.
79 changes: 79 additions & 0 deletions config_src/mct_driver/coupler_indices.F90
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@ module coupler_indices

! MOM types
use MOM_grid, only : ocean_grid_type
use MOM_surface_forcing, only: ice_ocean_boundary_type
! MOM functions
use MOM_domains, only : pass_var
use ocean_model_mod, only : ocean_public_type
Expand All @@ -18,6 +19,7 @@ module coupler_indices
private

public coupler_indices_init
public fill_ice_ocean_bnd
public ocn_export

type, public :: cpl_indices
Expand Down Expand Up @@ -285,4 +287,81 @@ subroutine ocn_export(ind, ocn_public, grid, o2x)

end subroutine ocn_export


subroutine fill_ice_ocean_bnd(ice_ocean_boundary, grid, x2o_o, ind)
type(ice_ocean_boundary_type), intent(in) :: ice_ocean_boundary !< A type for the ice ocean boundary
type(ocean_grid_type), intent(in) :: grid
!type(mct_aVect), intent(in) :: x2o_o
real(kind=8), intent(in) :: x2o_o(:,:)
type(cpl_indices), intent(inout) :: ind

! local variables
integer :: i, j, k, ig, jg

! variable that are not in ice_ocean_boundary:
! latent (x2o_Foxx_lat)
! surface Stokes drift, x-comp. (x2o_Sw_ustokes)
! surface Stokes drift, y-comp. (x2o_Sw_vstokes)
! wave model langmuir multiplier (x2o_Sw_lamult)

! biogeochemistry
! Black Carbon hydrophobic release from sea ice component (x2o_Fioi_bcpho)
! Black Carbon hydrophilic release from sea ice component (x2o_Fioi_bcphi)
! dust release from sea ice component (x2o_Fioi_flxdst)
! Black Carbon hydrophilic dry deposition (x2o_Faxa_bcphidry)
! Black Carbon hydrophobic dry deposition (x2o_Faxa_bcphodry)
! Black Carbon hydrophobic wet deposition (x2o_Faxa_bcphiwet)
! Organic Carbon hydrophilic dry deposition (x2o_Faxa_ocphidry)
! Organic Carbon hydrophobic dry deposition (x2o_Faxa_ocphodry)
! Organic Carbon hydrophilic dry deposition (x2o_Faxa_ocphiwet)
! Sizes 1 to 4 dust - wet deposition (x2o_Faxa_dstwet?)
! Sizes 1 to 4 dust - dry deposition (x2o_Faxa_dstdry?)


! need wind_stress_multiplier?

! Copy from x2o to ice_ocean_boundary. ice_ocean_boundary uses global indexing with no halos.
write(*,*) 'max. k is:', (grid%jec-grid%jsc+1) * (grid%iec-grid%isc+1)
! zonal wind stress (taux)
write(*,*) 'taux', SIZE(x2o_o(ind%x2o_Foxx_taux,:))
write(*,*) 'ice_ocean_boundary%u_flux', SIZE(ice_ocean_boundary%u_flux(:,:))
k = 0
do j = grid%jsc, grid%jec
jg = j + grid%jdg_offset
do i = grid%isc, grid%iec
k = k + 1 ! Increment position within gindex
ig = i + grid%idg_offset
! zonal wind stress (taux)
ice_ocean_boundary%u_flux(i,j) = x2o_o(ind%x2o_Foxx_taux,k)
! meridional wind stress (tauy)
ice_ocean_boundary%v_flux(i,j) = x2o_o(ind%x2o_Foxx_tauy,k)
! sensible heat flux
ice_ocean_boundary%t_flux(i,j) = x2o_o(ind%x2o_Foxx_sen,k)
! salt flux
ice_ocean_boundary%salt_flux(i,j) = x2o_o(ind%x2o_Fioi_salt,k)
! heat flux from snow & ice melt
ice_ocean_boundary%calving_hflx(i,j) = x2o_o(ind%x2o_Fioi_melth,k)
! snow melt flux
ice_ocean_boundary%fprec(i,j) = x2o_o(ind%x2o_Fioi_meltw,k)
! river runoff flux
ice_ocean_boundary%runoff(i,j) = x2o_o(ind%x2o_Foxx_rofl,k)
! ice runoff flux
ice_ocean_boundary%calving(i,j) = x2o_o(ind%x2o_Foxx_rofi,k)
! liquid precipitation (rain)
ice_ocean_boundary%lprec(i,j) = x2o_o(ind%x2o_Faxa_rain,k)
! froze precipitation (snow)
ice_ocean_boundary%fprec(i,j) = x2o_o(ind%x2o_Faxa_snow,k)
!!!!!!! LONGWAVE NEEDS TO BE FIXED !!!!!!!
! longwave radiation (up)
ice_ocean_boundary%lw_flux(i,j) = x2o_o(k,ind%x2o_Foxx_lwup)
! longwave radiation (down)
ice_ocean_boundary%lw_flux(i,j) = x2o_o(k,ind%x2o_Faxa_lwdn)
!!!!!!! SHORTWAVE NEEDS TO BE COMBINED !!!!!!!
! net short-wave heat flux
ice_ocean_boundary%u_flux(i,j) = x2o_o(k,ind%x2o_Foxx_swnet)
enddo
enddo

end subroutine fill_ice_ocean_bnd

end module coupler_indices
72 changes: 48 additions & 24 deletions config_src/mct_driver/ocn_comp_mct.F90
Original file line number Diff line number Diff line change
Expand Up @@ -11,27 +11,27 @@ module ocn_comp_mct
! !REVISION HISTORY:
!
! !USES:
use ESMF, only: ESMF_clock, ESMF_time, ESMF_timeInterval
use ESMF, only: ESMF_ClockGet, ESMF_TimeGet, ESMF_TimeIntervalGet
use seq_cdata_mod, only: seq_cdata
use seq_cdata_mod, only: seq_cdata_setptrs
use mct_mod, only: mct_gsMap, mct_gsmap_init, mct_gsMap_lsize, mct_gsmap_orderedpoints
use mct_mod, only: mct_aVect, mct_aVect_init, mct_aVect_zero, mct_aVect_nRattr
use mct_mod, only: mct_gGrid, mct_gGrid_init, mct_gGrid_importRAttr, mct_gGrid_importIAttr
use seq_flds_mod, only: seq_flds_x2o_fields, &
use ESMF, only: ESMF_clock, ESMF_time, ESMF_timeInterval
use ESMF, only: ESMF_ClockGet, ESMF_TimeGet, ESMF_TimeIntervalGet
use seq_cdata_mod, only: seq_cdata
use seq_cdata_mod, only: seq_cdata_setptrs
use mct_mod, only: mct_gsMap, mct_gsmap_init, mct_gsMap_lsize, mct_gsmap_orderedpoints
use mct_mod, only: mct_aVect, mct_aVect_init, mct_aVect_zero, mct_aVect_nRattr
use mct_mod, only: mct_gGrid, mct_gGrid_init, mct_gGrid_importRAttr, mct_gGrid_importIAttr
use seq_flds_mod, only: seq_flds_x2o_fields, &
seq_flds_o2x_fields, &
SEQ_FLDS_DOM_COORD, &
SEQ_FLDS_DOM_other
use seq_infodata_mod, only: seq_infodata_type, &
use seq_infodata_mod, only: seq_infodata_type, &
seq_infodata_GetData, &
seq_infodata_start_type_start, &
seq_infodata_start_type_cont, &
seq_infodata_start_type_brnch, &
seq_infodata_PutData
use seq_comm_mct, only: seq_comm_name, seq_comm_inst, seq_comm_suffix
use seq_timemgr_mod, only: seq_timemgr_EClockGetData, seq_timemgr_RestartAlarmIsOn
use perf_mod, only: t_startf, t_stopf
use shr_kind_mod, only: SHR_KIND_R8
use seq_comm_mct, only: seq_comm_name, seq_comm_inst, seq_comm_suffix
use seq_timemgr_mod, only: seq_timemgr_EClockGetData, seq_timemgr_RestartAlarmIsOn
use perf_mod, only: t_startf, t_stopf
use shr_kind_mod, only: SHR_KIND_R8


! From MOM6
Expand All @@ -44,8 +44,7 @@ module ocn_comp_mct
use MOM_error_handler, only: MOM_error, FATAL, is_root_pe
use MOM_time_manager, only: time_type, set_date, set_calendar_type, NOLEAP
use coupler_indices, only: coupler_indices_init, cpl_indices
use coupler_indices, only: ocn_export

use coupler_indices, only: ocn_export, fill_ice_ocean_bnd
!
! !PUBLIC MEMBER FUNCTIONS:
implicit none
Expand All @@ -70,8 +69,9 @@ module ocn_comp_mct
type MCT_MOM_Data
type(ocean_state_type), pointer :: ocn_state => NULL() !< Private state of ocean
type(ocean_public_type), pointer :: ocn_public => NULL() !< Public state of ocean
type(ocean_grid_type), pointer :: grid => NULL() ! A pointer to a grid structure

type(ocean_grid_type), pointer :: grid => NULL() !< A pointer to a grid structure
type(surface), pointer :: ocn_surface => NULL() !< A pointer to the ocean surface state
type(ice_ocean_boundary_type) :: ice_ocean_boundary !< A pointer to the ice ocean boundary type
type(seq_infodata_type), pointer :: infodata

type(cpl_indices), public :: ind !< Variable IDs
Expand Down Expand Up @@ -123,7 +123,8 @@ subroutine ocn_init_mct( EClock, cdata_o, x2o_o, o2x_o, NLFilename )
integer :: lsize, nsend, nrecv
logical :: ldiag_cpl = .false.
integer :: ni, nj

integer :: isc, iec, jsc, jec !< Indices for the start and end of the domain
!! in the x and y dir., respectively.
! mct variables (these are local for now)
integer :: MOM_MCT_ID
type(mct_gsMap), pointer :: MOM_MCT_gsMap => NULL() ! 2d, points to cdata
Expand Down Expand Up @@ -241,6 +242,7 @@ subroutine ocn_init_mct( EClock, cdata_o, x2o_o, o2x_o, NLFilename )

call t_stopf('MOM_init')


!---------------------------------------------------------------------
! Initialize MCT attribute vectors and indices
!---------------------------------------------------------------------
Expand Down Expand Up @@ -311,6 +313,29 @@ subroutine ocn_init_mct( EClock, cdata_o, x2o_o, o2x_o, NLFilename )
! Size of global domain
call get_global_grid_size(glb%grid, ni, nj)

! allocate ice_ocean_boundary
isc = glb%grid%isc; iec = glb%grid%iec;
jsc = glb%grid%jsc; jec = glb%grid%jec;
allocate(glb%ice_ocean_boundary%u_flux(isc:iec,jsc:jec)); glb%ice_ocean_boundary%u_flux(:,:) = 0.0
allocate(glb%ice_ocean_boundary%v_flux(isc:iec,jsc:jec)); glb%ice_ocean_boundary%v_flux(:,:) = 0.0
allocate(glb%ice_ocean_boundary%t_flux(isc:iec,jsc:jec)); glb%ice_ocean_boundary%t_flux(:,:) = 0.0
allocate(glb%ice_ocean_boundary%q_flux(isc:iec,jsc:jec)); glb%ice_ocean_boundary%q_flux(:,:) = 0.0
allocate(glb%ice_ocean_boundary%salt_flux(isc:iec,jsc:jec)); glb%ice_ocean_boundary%salt_flux(:,:) = 0.0
allocate(glb%ice_ocean_boundary%lw_flux(isc:iec,jsc:jec)); glb%ice_ocean_boundary%lw_flux(:,:) = 0.0
allocate(glb%ice_ocean_boundary%sw_flux_vis_dir(isc:iec,jsc:jec)); glb%ice_ocean_boundary%sw_flux_vis_dir(:,:) = 0.0
allocate(glb%ice_ocean_boundary%sw_flux_vis_dif(isc:iec,jsc:jec)); glb%ice_ocean_boundary%sw_flux_vis_dif(:,:) = 0.0
allocate(glb%ice_ocean_boundary%sw_flux_nir_dir(isc:iec,jsc:jec)); glb%ice_ocean_boundary%sw_flux_nir_dir(:,:) = 0.0
allocate(glb%ice_ocean_boundary%sw_flux_nir_dif(isc:iec,jsc:jec)); glb%ice_ocean_boundary%sw_flux_nir_dif(:,:) = 0.0
allocate(glb%ice_ocean_boundary%lprec(isc:iec,jsc:jec)); glb%ice_ocean_boundary%lprec(:,:) = 0.0
allocate(glb%ice_ocean_boundary%fprec(isc:iec,jsc:jec)); glb%ice_ocean_boundary%fprec(:,:) = 0.0
allocate(glb%ice_ocean_boundary%runoff(isc:iec,jsc:jec)); glb%ice_ocean_boundary%runoff(:,:) = 0.0
allocate(glb%ice_ocean_boundary%calving(isc:iec,jsc:jec)); glb%ice_ocean_boundary%calving(:,:) = 0.0
allocate(glb%ice_ocean_boundary%runoff_hflx(isc:iec,jsc:jec)); glb%ice_ocean_boundary%runoff_hflx(:,:) = 0.0
allocate(glb%ice_ocean_boundary%calving_hflx(isc:iec,jsc:jec)); glb%ice_ocean_boundary%calving_hflx(:,:) = 0.0
allocate(glb%ice_ocean_boundary%p(isc:iec,jsc:jec)); glb%ice_ocean_boundary%p(:,:) = 0.0
allocate(glb%ice_ocean_boundary%mi(isc:iec,jsc:jec)); glb%ice_ocean_boundary%mi(:,:) = 0.0


if (debug .and. root_pe().eq.pe_here()) print *, "calling seq_infodata_putdata"

call seq_infodata_PutData( glb%infodata, &
Expand Down Expand Up @@ -341,9 +366,6 @@ subroutine ocn_run_mct( EClock, cdata_o, x2o_o, o2x_o)
type(time_type) :: coupling_timestep ! Coupled time interval to pass to MOM6
character(len=128) :: err_msg

! Might need to be in glb to live on heap
type(ice_ocean_boundary_type) :: Ice_ocean_boundary

! Translate the current time (start of coupling interval)
call ESMF_ClockGet(EClock, currTime=current_time, rc=rc)
call ESMF_TimeGet(current_time, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
Expand Down Expand Up @@ -380,10 +402,12 @@ subroutine ocn_run_mct( EClock, cdata_o, x2o_o, o2x_o)
! \todo Let MOM6 know to write restart...
if (debug .and. is_root_pe()) write(6,*) 'ocn_run_mct, write_restart_at_eod=', write_restart_at_eod

!call ocn_imprt goes her
! fill ice ocean boundary
call fill_ice_ocean_bnd(glb%ice_ocean_boundary, glb%grid, x2o_o%rattr, glb%ind)
if (debug .and. is_root_pe()) write(6,*) 'fill_ice_ocean_bnd'

!call update_ocean_model(ice_ocean_boundary, glb%ocn_state, glb%ocn_public, &
! time_start, coupling_timestep)
! call update_ocean_model(glb%ice_ocean_boundary, glb%ocn_state, glb%ocn_public, &
! time_start, coupling_timestep)

end subroutine ocn_run_mct

Expand Down

0 comments on commit e6c5ddd

Please sign in to comment.