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

Last change on this file since 731 was 731, checked in by dubos, 6 years ago

devel : cleanup and reorganization in dynamics/

File size: 6.0 KB
RevLine 
[361]1MODULE caldyn_hevi_mod
2  USE icosa
3  USE transfert_mod
[731]4  USE caldyn_vars_mod
5  USE caldyn_kernels_hevi_mod
[362]6  USE caldyn_kernels_base_mod
[361]7  USE caldyn_gcm_mod
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, &
[366]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) 
[361]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    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(:)
[366]38    TYPE(t_field),POINTER :: f_W(:)
[361]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(:)
[366]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(:)
[361]50   
[562]51    REAL(rstd),POINTER :: ps(:), dps(:), phis(:)
[387]52    REAL(rstd),POINTER :: mass(:,:), theta_rhodz(:,:,:), dtheta_rhodz(:,:,:)
[366]53    REAL(rstd),POINTER :: du(:,:), dW(:,:), dPhi(:,:), hflux(:,:), wflux(:,:)
54    REAL(rstd),POINTER :: u(:,:), w(:,:), qu(:,:), qv(:,:)
[361]55
56! temporary shared variable
[404]57    REAL(rstd),POINTER  :: theta(:,:,:) 
[361]58    REAL(rstd),POINTER  :: pk(:,:)
59    REAL(rstd),POINTER  :: geopot(:,:)
60    REAL(rstd),POINTER  :: convm(:,:) 
61    REAL(rstd),POINTER  :: wwuu(:,:)
[558]62    REAL(rstd),POINTER  :: F_el(:,:), gradPhi2(:,:), w_il(:,:) , W_etadot(:,:), pres(:,:), m_il(:,:)
[361]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)
[366]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
[361]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
[362]87       CALL wait_message(req_ps) ! COM00
[361]88    ELSE
89       CALL send_message(f_mass,req_mass) ! COM00
90       CALL wait_message(req_mass) ! COM00
91    END IF
92    CALL send_message(f_theta_rhodz,req_theta_rhodz) ! COM01
93    CALL wait_message(req_theta_rhodz) ! COM01 Moved from caldyn_pvort
[366]94
95    IF(.NOT.hydrostatic) THEN
96       CALL send_message(f_geopot,req_geopot) ! COM03
97       CALL wait_message(req_geopot) ! COM03
98       CALL send_message(f_w,req_w) ! COM04
99       CALL wait_message(req_w) ! COM04
100    END IF
[361]101   
102    DO ind=1,ndomain
103       IF (.NOT. assigned_domain(ind)) CYCLE
104       CALL swap_dimensions(ind)
105       CALL swap_geometry(ind)
106       ps=f_ps(ind)
107       theta_rhodz=f_theta_rhodz(ind)
108       mass=f_mass(ind)
109       theta = f_theta(ind)
[404]110       CALL compute_theta(ps,theta_rhodz, mass,theta)
[361]111       pk = f_pk(ind)
[362]112       geopot = f_geopot(ind)
[369]113       du=f_du_fast(ind)
[366]114       IF(hydrostatic) THEN
[369]115          du(:,:)=0.
[404]116          CALL compute_geopot(mass,theta, ps,pk,geopot)
[366]117       ELSE
[562]118          phis = f_phis(ind)
[366]119          W = f_W(ind)
120          dW = f_dW_fast(ind)
121          dPhi = f_dPhi_fast(ind)
[558]122          ! reuse buffers
123          m_il = f_wil(ind)
124          pres = f_gradPhi2(ind)
[562]125          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]126       END IF
127       u=f_u(ind)
[373]128       CALL compute_caldyn_fast(tau,u,mass,theta,pk,geopot,du) ! computes du_fast and updates u
[361]129    ENDDO
130   
131    CALL send_message(f_u,req_u) ! COM02
132    CALL wait_message(req_u)   ! COM02
133   
134    DO ind=1,ndomain
135       IF (.NOT. assigned_domain(ind)) CYCLE
136       CALL swap_dimensions(ind)
137       CALL swap_geometry(ind)
138       u=f_u(ind)
139       mass=f_mass(ind)
140       qu=f_qu(ind)
141       qv=f_qv(ind)
142       CALL compute_pvort_only(u,mass,qu,qv)
143    ENDDO
144   
145    CALL send_message(f_qu,req_qu) ! COM03
[369]146    CALL wait_message(req_qu) ! COM03
147       
[361]148    DO ind=1,ndomain
149       IF (.NOT. assigned_domain(ind)) CYCLE
150       CALL swap_dimensions(ind)
151       CALL swap_geometry(ind)
152       u=f_u(ind)
153       mass=f_mass(ind)
154       theta = f_theta(ind)
155       qu=f_qu(ind)
156       hflux=f_hflux(ind)
157       convm = f_dmass(ind)
158       dtheta_rhodz=f_dtheta_rhodz(ind)
159       du=f_du_slow(ind)
[377]160
[369]161       IF(hydrostatic) THEN
[529]162          CALL compute_caldyn_slow_hydro(u,mass,hflux,du, .TRUE.)
[369]163       ELSE
164          W = f_W(ind)
165          dW = f_dW_slow(ind)
166          geopot = f_geopot(ind)
167          dPhi = f_dPhi_slow(ind)
[558]168          F_el = f_Fel(ind)
169          gradPhi2 = f_gradPhi2(ind)
170          w_il = f_wil(ind)
171          CALL compute_caldyn_slow_NH(u,mass,geopot,W, F_el,gradPhi2,w_il, hflux,du,dPhi,dW)
[369]172       END IF
[404]173       CALL compute_caldyn_Coriolis(hflux,theta,qu, convm,dtheta_rhodz,du)
[361]174       IF(caldyn_eta==eta_mass) THEN
175          wflux=f_wflux(ind)
176          wwuu=f_wwuu(ind)
177          dps=f_dps(ind)
[373]178          CALL compute_caldyn_vert(u,theta,mass,convm, wflux,wwuu, dps, dtheta_rhodz, du)
179          IF(.NOT.hydrostatic) THEN
[559]180             W_etadot=f_Wetadot(ind)
[558]181             CALL compute_caldyn_vert_NH(mass,geopot,W,wflux, W_etadot, du,dPhi,dW)
[369]182          END IF
[361]183       END IF
184    ENDDO
185   
186!$OMP BARRIER
187    !    CALL check_mass_conservation(f_ps,f_dps)
188    CALL trace_end("caldyn_hevi")
189!!$OMP BARRIER
190   
191  END SUBROUTINE caldyn_hevi
192
193END MODULE caldyn_hevi_mod
Note: See TracBrowser for help on using the repository browser.