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

Last change on this file since 980 was 949, checked in by dubos, 5 years ago

devel : generic compute_caldyn_slow_hydro + fixes

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