source: codes/icosagcm/trunk/src/dynamics/caldyn_hevi.F90 @ 954

Last change on this file since 954 was 954, checked in by adurocher, 5 years ago

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 size: 6.4 KB
Line 
1MODULE caldyn_hevi_mod
2  USE icosa
3  USE transfert_mod
4  USE caldyn_kernels_base_mod
5  USE caldyn_kernels_hevi_mod
6  USE caldyn_gcm_mod
7  IMPLICIT NONE
8  PRIVATE
9  PUBLIC caldyn_hevi
10
11CONTAINS
12 
13  SUBROUTINE caldyn_hevi(write_out,tau, f_phis, f_ps, f_mass, f_theta_rhodz, f_u, f_q, &
14       f_W, f_geopot, f_hflux, f_wflux, f_dps, f_dmass, f_dtheta_rhodz, &
15       f_du_slow, f_du_fast, f_dPhi_slow, f_dPhi_fast, f_dW_slow, f_dW_fast) 
16    USE icosa
17    USE observable_mod
18    USE disvert_mod, ONLY : caldyn_eta, eta_mass, bp, mass_dak, mass_dbk
19    USE vorticity_mod
20    USE kinetic_mod
21    USE theta2theta_rhodz_mod
22    USE wind_mod
23    USE mpipara
24    USE trace
25    USE omp_para
26    USE output_field_mod
27    USE checksum_mod
28    USE abort_mod
29    IMPLICIT NONE
30    LOGICAL,INTENT(IN)    :: write_out
31    REAL(rstd), INTENT(IN) :: tau
32    TYPE(t_field),POINTER :: f_phis(:)
33    TYPE(t_field),POINTER :: f_ps(:)
34    TYPE(t_field),POINTER :: f_mass(:)
35    TYPE(t_field),POINTER :: f_theta_rhodz(:)
36    TYPE(t_field),POINTER :: f_u(:)
37    TYPE(t_field),POINTER :: f_q(:)
38    TYPE(t_field),POINTER :: f_W(:)
39    TYPE(t_field),POINTER :: f_geopot(:)
40    TYPE(t_field),POINTER :: f_hflux(:), f_wflux(:)
41    TYPE(t_field) :: f_dps(:)
42    TYPE(t_field) :: f_dmass(:)
43    TYPE(t_field) :: f_dtheta_rhodz(:)
44    TYPE(t_field) :: f_du_slow(:)
45    TYPE(t_field) :: f_du_fast(:)
46    TYPE(t_field) :: f_dW_slow(:)
47    TYPE(t_field) :: f_dW_fast(:)
48    TYPE(t_field) :: f_dPhi_slow(:)
49    TYPE(t_field) :: f_dPhi_fast(:)
50   
51    REAL(rstd),POINTER :: ps(:), dps(:), phis(:)
52    REAL(rstd),POINTER :: mass(:,:), theta_rhodz(:,:,:), dtheta_rhodz(:,:,:)
53    REAL(rstd),POINTER :: du(:,:), dW(:,:), dPhi(:,:), hflux(:,:), wflux(:,:)
54    REAL(rstd),POINTER :: u(:,:), w(:,:), qu(:,:), qv(:,:)
55
56! temporary shared variable
57    REAL(rstd),POINTER  :: theta(:,:,:) 
58    REAL(rstd),POINTER  :: pk(:,:)
59    REAL(rstd),POINTER  :: geopot(:,:)
60    REAL(rstd),POINTER  :: convm(:,:) 
61    REAL(rstd),POINTER  :: wwuu(:,:)
62    REAL(rstd),POINTER  :: F_el(:,:), gradPhi2(:,:), w_il(:,:) , W_etadot(:,:), pres(:,:), m_il(:,:)
63    INTEGER :: ind
64    LOGICAL,SAVE :: first=.TRUE.
65!$OMP THREADPRIVATE(first)
66   
67    IF (first) THEN
68      first=.FALSE.
69      IF(caldyn_eta==eta_mass) THEN
70         CALL init_message(f_ps,req_i1,req_ps)
71      ELSE
72         CALL init_message(f_mass,req_i1,req_mass)
73      END IF
74      CALL init_message(f_theta_rhodz,req_i1,req_theta_rhodz)
75      CALL init_message(f_u,req_e1_vect,req_u)
76      CALL init_message(f_qu,req_e1_scal,req_qu)
77      IF(.NOT.hydrostatic) THEN
78         CALL init_message(f_geopot,req_i1,req_geopot)
79         CALL init_message(f_w,req_i1,req_w)
80      END IF
81    ENDIF
82   
83    CALL trace_start("caldyn")
84   
85    IF(caldyn_eta==eta_mass) THEN
86       CALL send_message(f_ps,req_ps) ! COM00
87       CALL wait_message(req_ps) ! COM00
88    ELSE
89       CALL abort_acc("HEVI_scheme/!eta_mass")
90       CALL send_message(f_mass,req_mass) ! COM00
91       CALL wait_message(req_mass) ! COM00
92    END IF
93    CALL send_message(f_theta_rhodz,req_theta_rhodz) ! COM01
94    CALL wait_message(req_theta_rhodz) ! COM01 Moved from caldyn_pvort
95
96    IF(.NOT.hydrostatic) THEN
97       CALL abort_acc("HEVI_scheme/!hydrostatic")
98       CALL send_message(f_geopot,req_geopot) ! COM03
99       CALL wait_message(req_geopot) ! COM03
100       CALL send_message(f_w,req_w) ! COM04
101       CALL wait_message(req_w) ! COM04
102    END IF
103   
104    DO ind=1,ndomain
105       IF (.NOT. assigned_domain(ind)) CYCLE
106       CALL swap_dimensions(ind)
107       CALL swap_geometry(ind)
108       ps=f_ps(ind)
109       theta_rhodz=f_theta_rhodz(ind)
110       mass=f_mass(ind)
111       theta = f_theta(ind)
112       CALL compute_theta(ps,theta_rhodz, mass,theta, mass_dak, mass_dbk)
113       pk = f_pk(ind)
114       geopot = f_geopot(ind)
115       du=f_du_fast(ind)
116       IF(hydrostatic) THEN
117          !$acc kernels present(du) async
118          du(:,:)=0.0d0
119          !$acc end kernels
120          CALL compute_geopot(mass,theta, ps,pk,geopot)
121       ELSE
122          CALL abort_acc("HEVI_scheme/!hydrostatic")
123          phis = f_phis(ind)
124          W = f_W(ind)
125          dW = f_dW_fast(ind)
126          dPhi = f_dPhi_fast(ind)
127          ! reuse buffers
128          m_il = f_wil(ind)
129          pres = f_gradPhi2(ind)
130          CALL compute_caldyn_solver(tau,phis, mass,theta,pk,geopot,W, m_il,pres, dPhi,dW,du) ! computes d(Phi,W,du)_fast and updates Phi,W
131       END IF
132       u=f_u(ind)
133       CALL compute_caldyn_fast(tau,u,mass,theta,pk,geopot,du) ! computes du_fast and updates u
134    ENDDO
135   
136    CALL send_message(f_u,req_u) ! COM02
137    CALL wait_message(req_u)   ! COM02
138   
139    DO ind=1,ndomain
140       IF (.NOT. assigned_domain(ind)) CYCLE
141       CALL swap_dimensions(ind)
142       CALL swap_geometry(ind)
143       u=f_u(ind)
144       mass=f_mass(ind)
145       qu=f_qu(ind)
146       qv=f_qv(ind)
147       CALL compute_pvort_only(u,mass,qu,qv,Av,Riv2,fv)
148    ENDDO
149   
150    CALL send_message(f_qu,req_qu) ! COM03
151    CALL wait_message(req_qu) ! COM03
152       
153    DO ind=1,ndomain
154       IF (.NOT. assigned_domain(ind)) CYCLE
155       CALL swap_dimensions(ind)
156       CALL swap_geometry(ind)
157       u=f_u(ind)
158       mass=f_mass(ind)
159       theta = f_theta(ind)
160       qu=f_qu(ind)
161       hflux=f_hflux(ind)
162       convm = f_dmass(ind)
163       dtheta_rhodz=f_dtheta_rhodz(ind)
164       du=f_du_slow(ind)
165
166       IF(hydrostatic) THEN
167          CALL compute_caldyn_slow_hydro(u,mass,hflux,du,Ai,le_de, .TRUE.)
168       ELSE
169          CALL abort_acc("HEVI_scheme/!hydrostatic")
170          W = f_W(ind)
171          dW = f_dW_slow(ind)
172          geopot = f_geopot(ind)
173          dPhi = f_dPhi_slow(ind)
174          F_el = f_Fel(ind)
175          gradPhi2 = f_gradPhi2(ind)
176          w_il = f_wil(ind)
177          CALL compute_caldyn_slow_NH(u,mass,geopot,W, F_el,gradPhi2,w_il, hflux,du,dPhi,dW)
178       END IF
179       CALL compute_caldyn_Coriolis(hflux,theta,qu,convm,dtheta_rhodz,du,Ai,wee)
180       
181       IF(caldyn_eta==eta_mass) THEN
182          wflux=f_wflux(ind)
183          wwuu=f_wwuu(ind)
184          dps=f_dps(ind)
185          CALL compute_caldyn_vert(u,theta,mass,convm, wflux,wwuu, dps, dtheta_rhodz, du, bp)
186          IF(.NOT.hydrostatic) THEN
187             CALL abort_acc("HEVI_scheme/!hydrostatic")
188             W_etadot=f_Wetadot(ind)
189             CALL compute_caldyn_vert_NH(mass,geopot,W,wflux, W_etadot, du,dPhi,dW)
190          END IF
191       END IF
192    ENDDO
193   
194!$OMP BARRIER
195    !    CALL check_mass_conservation(f_ps,f_dps)
196    CALL trace_end("caldyn_hevi")
197!!$OMP BARRIER
198   
199  END SUBROUTINE caldyn_hevi
200
201END MODULE caldyn_hevi_mod
Note: See TracBrowser for help on using the repository browser.