source: LMDZ6/branches/Portage_acc/libf/phylmd/thermcell_env.F90 @ 4584

Last change on this file since 4584 was 4435, checked in by Laurent Fairhead, 19 months ago

Routines adapted to GPU. Speed-up is some 200 w.r.t. 1 CPU as measured by SYSTEM_CLOCK calls
around the call to the routine, CPU takes .14 (seconds?), GPU around 6E-004 (s?) at a resolution of 144x142x95.
Comparison of the netcdf result files output with the replay method yields no difference between the
two runs

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 2.9 KB
Line 
1   SUBROUTINE thermcell_env(ngrid,nlay,po,pt,pu,pv,pplay,  &
2     &           pplev,zo,zh,zl,ztv,zthl,zu,zv,zpspsk,pqsat,lev_out)
3
4!--------------------------------------------------------------
5!thermcell_env: calcule les caracteristiques de l environnement
6!necessaires au calcul des proprietes dans le thermique
7!--------------------------------------------------------------
8
9
10   USE thermcell_ini_mod, ONLY : prt_level,RLvCp,RKAPPA,RETV
11   IMPLICIT NONE
12
13! arguments
14
15   integer,intent(in) :: ngrid,nlay,lev_out
16   real,intent(in), dimension(ngrid,nlay) :: po,pt,pu,pv,pplay
17   real,intent(in), dimension(ngrid,nlay+1) :: pplev
18   real,intent(out), dimension(ngrid,nlay) :: zo,zl,zh,ztv,zthl
19   real,intent(out), dimension(ngrid,nlay) :: zpspsk,zu,zv,pqsat
20   
21! Local
22
23   integer ig,ll
24   real dqsat_dT
25   logical mask(ngrid,nlay)
26
27   !$acc data create (mask) &
28   !$acc &    copyin (po, pt, pu, pv, pplay, pplev) &
29   !$acc &    copyout (zo, zl, zh, ztv, zthl)     &
30   !$acc &    copyout (zpspsk, zu, zv, pqsat)       &
31   !$acc &
32
33
34!^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
35! Initialisations :
36!------------------
37!!! temporary for GPU port   write(81) ngrid,nlay,lev_out,po,pt,pu,pv,pplay,pplev
38
39
40  !$acc kernels default(none) async
41   mask(:,:)=.true.
42  !$acc end kernels
43!
44! calcul des caracteristiques de l environnement
45  !$acc kernels default(none) async
46   DO  ll=1,nlay
47     DO ig=1,ngrid
48        zo(ig,ll)=po(ig,ll)
49        zl(ig,ll)=0.
50        zh(ig,ll)=pt(ig,ll)
51     enddo
52   enddo
53  !$acc end kernels
54   
55! Condensation :
56!---------------
57! Calcul de l'humidite a saturation et de la condensation
58   call thermcell_qsat(ngrid*nlay,mask,pplev,pt,po,pqsat)
59  !$acc kernels default(none) async
60   do ll=1,nlay
61      do ig=1,ngrid
62         zl(ig,ll) = max(0.,po(ig,ll)-pqsat(ig,ll))
63         zh(ig,ll) = pt(ig,ll)+RLvCp*zl(ig,ll)         !   T = Tl + Lv/Cp ql
64         zo(ig,ll) = po(ig,ll)-zl(ig,ll)
65      enddo
66   enddo
67  !$acc end kernels
68!-----------------------------------------------------------------------
69   if (prt_level.ge.1) print*,'0 OK convect8'
70
71  !$acc kernels default(none) async
72   do ll=1,nlay
73      do ig=1,ngrid
74          zpspsk(ig,ll)=(pplay(ig,ll)/100000.)**RKAPPA
75          zu(ig,ll)=pu(ig,ll)
76          zv(ig,ll)=pv(ig,ll)
77!attention zh est maintenant le profil de T et plus le profil de theta !
78! Quelle horreur ! A eviter.
79!   T-> Theta
80            ztv(ig,ll)=zh(ig,ll)/zpspsk(ig,ll)
81!Theta_v
82            ztv(ig,ll)=ztv(ig,ll)*(1.+RETV*(zo(ig,ll))-zl(ig,ll))
83!Thetal
84            zthl(ig,ll)=pt(ig,ll)/zpspsk(ig,ll)
85!           
86      enddo
87   enddo
88  !$acc end kernels
89 
90!!! temporary for GPU port !!!$acc update self(zo, zl, zh, ztv, zthl,zpspsk, zu, zv, pqsat)
91!!! temporary for GPU port include "dump_param.h" ! replay automatic include
92!!! !$acc update self(zo, zl, zh, ztv, zthl,zpspsk, zu, zv, pqsat)
93   !$acc end data
94   RETURN
95   END
Note: See TracBrowser for help on using the repository browser.