Ignore:
Timestamp:
07/15/19 12:29:31 (5 years ago)
Author:
adurocher
Message:

trunk : Added metric terms to kernels parameters to avoid Host/GPU transferts

Metric terms are now subroutine parameters instead of module variables in kernel subroutines. Dummy arguments for metric terms are now defined as fixed-size arrays, and arrays dimensions are well known when entering an 'acc data' region. Array descriptors are no longer transferred form host to device each time the data region is executed.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/trunk/src/transport/advect.F90

    r953 r954  
    4949  !======================================================================================= 
    5050 
    51   SUBROUTINE compute_gradq3d(qi,sqrt_leng,gradq3d,xyz_i, xyz_v) 
     51  SUBROUTINE compute_gradq3d(qi,sqrt_leng,gradq3d,xyz_i,xyz_v) 
    5252    USE trace 
    5353    USE omp_para 
     
    348348 
    349349  ! Backward trajectories, for use with Miura approach 
    350   SUBROUTINE compute_backward_traj(normal,tangent,ue,tau,cc) 
    351     USE geometry, ONLY : xyz_e, de, wee, le 
     350  SUBROUTINE compute_backward_traj(normal,tangent,ue,tau, cc, & 
     351                                   xyz_e, de, wee, le         ) ! metrics terms 
    352352    USE trace 
    353353    USE omp_para 
     
    358358    REAL(rstd),INTENT(OUT)   :: cc(3*iim*jjm,llm,3) ! start of backward trajectory 
    359359    REAL(rstd),INTENT(IN)    :: tau 
     360! metrics terms 
     361    REAL(rstd),INTENT(IN)    :: xyz_e(iim*3*jjm,3) 
     362    REAL(rstd),INTENT(IN)    :: de(iim*3*jjm) 
     363    REAL(rstd),INTENT(IN)    :: wee(iim*3*jjm,5,2) 
     364    REAL(rstd),INTENT(IN)    :: le(iim*3*jjm) 
    360365 
    361366    REAL(rstd) :: v_e(3), up_e    
     
    427432  ! Horizontal transport (S. Dubey, T. Dubos) 
    428433  ! Slope-limited van Leer approach with hexagons 
    429   SUBROUTINE compute_advect_horiz(update_mass,diagflux_on, hfluxt,cc,gradq3d, mass, qi, qfluxt) 
     434  SUBROUTINE compute_advect_horiz(update_mass,diagflux_on, hfluxt,cc,gradq3d, mass, qi, qfluxt,  & 
     435                                  Ai, xyz_i)   ! metrics terms  
    430436    USE trace 
    431437    USE omp_para 
    432438    USE abort_mod 
    433     USE geometry, only : Ai, xyz_i 
    434439    IMPLICIT NONE 
    435440    LOGICAL, INTENT(IN)       :: update_mass, diagflux_on 
     
    441446    REAL(rstd), INTENT(INOUT) :: qfluxt(3*iim*jjm,MERGE(llm,1,diagflux_on)) ! time-integrated tracer flux 
    442447! metrics terms 
     448    REAL(rstd), INTENT(IN)    :: Ai(iim*jjm) 
     449    REAL(rstd), INTENT(IN)    :: xyz_i(iim*jjm,3) 
    443450     
    444451    REAL(rstd) :: dq,dmass,qe,newmass 
Note: See TracChangeset for help on using the changeset viewer.