source: codes/icosagcm/devel/src/dynamics/caldyn_hevi.f90 @ 836

Last change on this file since 836 was 831, checked in by dubos, 5 years ago

devel : separate module for compute_theta

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