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/initial/etat0_heldsz.f90

    r970 r1046  
    8989       theta=f_theta(ind) 
    9090       CALL compute_etat0_heldsz(theta_eq,theta) 
    91        CALL compute_theta2theta_rhodz(ps,theta,theta_rhodz(:,:,1),1) 
     91       CALL compute_theta2theta_rhodz(ps,theta,theta_rhodz(:,:,1),1, ondevice=.false.) 
    9292       IF(nqtot>0) THEN 
    9393          q=f_q(ind) 
     
    9696          IF(nqtot>2) q(:,:,3:)=0. 
    9797       END IF 
     98    
     99       call update_device_field(f_theta_eq) 
     100       call update_device_field(f_theta) 
     101      !$acc enter data copyin(knewt_t(:)) async 
     102      !$acc enter data copyin(kfrict(:)) async 
     103 
    98104    ENDDO 
    99105  END SUBROUTINE etat0 
     
    236242    INTEGER :: i,j,l,ij 
    237243 
    238     CALL compute_theta_rhodz2theta(ps,theta_rhodz,theta,1) 
     244    CALL compute_theta_rhodz2theta(ps,theta_rhodz,theta,1, ondevice=.TRUE.) 
    239245    DO l=ll_begin,ll_end 
    240246       DO j=jj_begin-1,jj_end+1 
     
    246252       ENDDO 
    247253    ENDDO 
    248     CALL compute_theta2theta_rhodz(ps,theta,theta_rhodz,1) 
    249  
    250     Do l=ll_begin,ll_end 
     254    CALL compute_theta2theta_rhodz(ps,theta,theta_rhodz,1, ondevice=.true.) 
     255 
     256    !$acc kernels default(present) async 
     257    DO l=ll_begin,ll_end 
    251258       u(:,l)=u(:,l)*(1.-itau_physics*dt*kfrict(l)) 
    252259    END DO 
     260    !$acc end kernels 
    253261 
    254262  END SUBROUTINE compute_heldsz 
Note: See TracChangeset for help on using the changeset viewer.