Ignore:
Timestamp:
08/20/20 16:22:41 (4 years ago)
Author:
ymipsl
Message:

Introduce modification from A. Durocher github to make held&suarez testcase working on GPU

YM & AD

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/trunk/src/physics/physics.f90

    r953 r1046  
    113113 
    114114!$OMP PARALLEL 
    115     CALL allocate_field(f_du_phys,field_u,type_real,llm, name='du_phys') 
     115    CALL allocate_field(f_du_phys,field_u,type_real,llm, name='du_phys', ondevice=.TRUE.) 
    116116 
    117117    IF(is_mpi_root) PRINT *, 'phys_type = ',phys_type 
     
    119119     
    120120!$OMP END PARALLEL 
    121     IF (phys_type /= phys_none) THEN 
    122        CALL abort_acc("physics /= 'none'") 
     121    IF (phys_type /= phys_none .AND. phys_type /= phys_HS94) THEN 
     122       CALL abort_acc("only phys_type == 'phys_none' or 'phys_HS94' supported") 
    123123    END IF 
    124124  END SUBROUTINE init_physics 
     
    133133       CALL swap_geometry(ind) 
    134134       du=f_du_phys(ind) 
     135 
     136       !$acc kernels default(present) async 
    135137       du(:,ll_begin:ll_end) = 0. 
     138       !$acc end kernels 
     139           
    136140    END DO 
    137141  END SUBROUTINE zero_du_phys 
     
    141145    TYPE(t_field),POINTER :: f_u(:) ! velocity field before/after call to physics 
    142146    REAL(rstd), DIMENSION(:,:), POINTER :: u, du 
    143     INTEGER :: ind 
     147    INTEGER :: ind, ij 
     148 
    144149    DO ind=1,ndomain 
    145150       IF (.NOT. assigned_domain(ind)) CYCLE 
     
    148153       du=f_du_phys(ind) 
    149154       u=f_u(ind) 
    150        du(:,ll_begin:ll_end) = du(:,ll_begin:ll_end) + coef*u(:,ll_begin:ll_end) 
     155 
     156       !$acc parallel loop default(present) async 
     157       DO ij = ij_begin, ij_end 
     158          du(ij,ll_begin:ll_end) = du(ij,ll_begin:ll_end) + coef*u(ij,ll_begin:ll_end) 
     159       END DO 
     160 
    151161    END DO 
    152162  END SUBROUTINE add_du_phys 
     
    228238    USE wind_mod 
    229239    USE output_field_mod 
    230     CALL transfert_request(f_du_phys,req_e1_vect) 
     240 
     241    CALL transfert_request(f_du_phys,req_e1_vect)     
     242    CALL update_host_field(f_du_phys) 
     243 
    231244    CALL un2ulonlat(f_du_phys, f_buf_ulon, f_buf_ulat, (1./(dt*itau_out))) 
    232245    CALL output_field("dulon_phys",f_buf_ulon) 
Note: See TracChangeset for help on using the changeset viewer.