Skip to content

Commit

Permalink
WIP add routines to try to ensure data consistency
Browse files Browse the repository at this point in the history
Add routines to transfer to/from the GPU before/after calling
atm_do_timestep. This is to try to ensure the GPU MPAS-A dycore has the
data it needs based on fields in dyn_in and that the fields CAM needs in
dyn_out are updated on the CPU.
  • Loading branch information
gdicker1 committed Oct 16, 2024
1 parent 5d0a989 commit f4e84e7
Showing 1 changed file with 102 additions and 1 deletion.
103 changes: 102 additions & 1 deletion src/dynamics/mpas/driver/cam_mpas_subdriver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -2222,7 +2222,7 @@ subroutine cam_mpas_run(integrationLength)
type (MPAS_Time_Type) :: currTime
type (MPAS_Time_type) :: runUntilTime
character(len=StrKIND) :: timeStamp
type (mpas_pool_type), pointer :: state, diag, mesh
type (mpas_pool_type), pointer :: state, diag, mesh, tend_physics

integer, pointer :: index_qv
integer, pointer :: nCellsSolve
Expand All @@ -2238,6 +2238,11 @@ subroutine cam_mpas_run(integrationLength)
call mpas_pool_get_subpool(domain_ptr % blocklist % structs, 'state', state)
call mpas_pool_get_subpool(domain_ptr % blocklist % structs, 'diag', diag)
call mpas_pool_get_subpool(domain_ptr % blocklist % structs, 'mesh', mesh)
call mpas_pool_get_subpool(domain_ptr % blocklist % structs, 'tend_physics', tend_physics)

#ifdef MPAS_OPENACC
call cam_mpas_gpudata_host_to_device(state, diag, tend_physics)
#endif !MPAS_OPENACC

! During integration, time level 1 stores the model state at the beginning of the
! time step, and time level 2 stores the state advanced dt in time by timestep(...)
Expand All @@ -2263,6 +2268,10 @@ subroutine cam_mpas_run(integrationLength)
currTime = mpas_get_clock_time(clock, MPAS_NOW, ierr)
end do

#ifdef MPAS_OPENACC
call cam_mpas_gpudata_device_to_host(state, diag, tend_physics)
#endif !MPAS_OPENACC

!
! Compute diagnostic fields from the final prognostic state
!
Expand All @@ -2281,6 +2290,98 @@ subroutine cam_mpas_run(integrationLength)
end subroutine cam_mpas_run


!-----------------------------------------------------------------------
! routine cam_mpas_gpudata_host_to_device
!
!> \brief Transfer data from CPU to GPU before atm_do_timestep
!> \author G. Dylan Dickerson
!> \date 15 October 2024
!> \details
!> SOME DETAIL HERE
!
!-----------------------------------------------------------------------
subroutine cam_mpas_gpudata_host_to_device(state, diag, tend_physics)

use mpas_derived_types, only : mpas_pool_type
use mpas_kind_types, only : RKIND
use mpas_pool_routines, only : mpas_pool_get_array_gpu

type (mpas_pool_type), pointer :: state, diag, tend_physics
real(kind=RKIND), dimension(:,:), pointer :: u, w, theta_m, rho_zz
real(kind=RKIND), dimension(:,:,:), pointer :: scalars
real(kind=RKIND), dimension(:,:), pointer :: theta, exner, rho, uReconstructZonal, uReconstructMeridional
real(kind=RKIND), dimension(:,:), pointer :: tend_ru_physics, tend_rho_physics, tend_rtheta_physics

! state pool arrays, modify the "current" state in timeLevel=1
call mpas_pool_get_array_gpu(state, 'u', u, timeLevel=1)
call mpas_pool_get_array_gpu(state, 'w', w, timeLevel=1)
call mpas_pool_get_array_gpu(state, 'theta_m', theta_m, timeLevel=1)
call mpas_pool_get_array_gpu(state, 'rho_zz', rho_zz, timeLevel=1)
call mpas_pool_get_array_gpu(state, 'scalars', scalars, timeLevel=1)
!$acc update device(u,w,theta_m,rho_zz,scalars)

! diag pool arrays
call mpas_pool_get_array_gpu(diag, 'theta', theta)
call mpas_pool_get_array_gpu(diag, 'exner', exner)
call mpas_pool_get_array_gpu(diag, 'rho', rho)
call mpas_pool_get_array_gpu(diag, 'uReconstructZonal', uReconstructZonal)
call mpas_pool_get_array_gpu(diag, 'uReconstructMeridional', uReconstructMeridional)
!$acc update device(theta,exner,rho,uReconstructZonal,uReconstructMeridional)

! tend pool arrays
call mpas_pool_get_array_gpu(tend_physics, 'tend_ru_physics', tend_ru_physics)
call mpas_pool_get_array_gpu(tend_physics, 'tend_rtheta_physics', tend_rtheta_physics)
call mpas_pool_get_array_gpu(tend_physics, 'tend_rho_physics', tend_rho_physics)
!$acc update device(tend_ru_physics,tend_rtheta_physics,tend_rho_physics)

end subroutine cam_mpas_gpudata_host_to_device


!-----------------------------------------------------------------------
! routine cam_mpas_gpudata_device_to_host
!
!> \brief Transfer data from GPU to CPU after atm_do_timestep
!> \author G. Dylan Dickerson
!> \date 15 October 2024
!> \details
!> SOME DETAIL HERE
!
!-----------------------------------------------------------------------
subroutine cam_mpas_gpudata_device_to_host(state, diag, tend_physics)

use mpas_derived_types, only : mpas_pool_type
use mpas_kind_types, only : RKIND
use mpas_pool_routines, only : mpas_pool_get_array_gpu

type (mpas_pool_type), pointer :: state, diag, tend_physics
real(kind=RKIND), dimension(:,:), pointer :: u, w, theta_m, rho_zz
real(kind=RKIND), dimension(:,:,:), pointer :: scalars
real(kind=RKIND), dimension(:,:), pointer :: theta, exner, rho, uReconstructZonal, uReconstructMeridional, &
v, vorticity, divergence

! state pool arrays, modify the "current" state in timeLevel=1
call mpas_pool_get_array_gpu(state, 'u', u, timeLevel=1)
call mpas_pool_get_array_gpu(state, 'w', w, timeLevel=1)
call mpas_pool_get_array_gpu(state, 'theta_m', theta_m, timeLevel=1)
call mpas_pool_get_array_gpu(state, 'rho_zz', rho_zz, timeLevel=1)
call mpas_pool_get_array_gpu(state, 'scalars', scalars, timeLevel=1)
!$acc update host(u,w,theta_m,rho_zz,scalars)

! diag pool arrays
call mpas_pool_get_array_gpu(diag, 'theta', theta)
call mpas_pool_get_array_gpu(diag, 'exner', exner)
call mpas_pool_get_array_gpu(diag, 'rho', rho)
call mpas_pool_get_array_gpu(diag, 'uReconstructZonal', uReconstructZonal)
call mpas_pool_get_array_gpu(diag, 'uReconstructMeridional', uReconstructMeridional)
call mpas_pool_get_array_gpu(diag, 'v', v)
call mpas_pool_get_array_gpu(diag, 'vorticity', vorticity)
call mpas_pool_get_array_gpu(diag, 'divergence', divergence)
!$acc update host(theta,exner,rho,uReconstructZonal,uReconstructMeridional, &
!$acc v,vorticity,divergence)

end subroutine cam_mpas_gpudata_device_to_host


!-----------------------------------------------------------------------
! routine cam_mpas_finalize
!
Expand Down

0 comments on commit f4e84e7

Please sign in to comment.