source: codes/icosagcm/trunk/src/dynamics/caldyn_hevi.f90 @ 580

Last change on this file since 580 was 580, checked in by dubos, 7 years ago

trunk : upgrading to devel

File size: 6.0 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
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    IMPLICIT NONE
29    LOGICAL,INTENT(IN)    :: write_out
30    REAL(rstd), INTENT(IN) :: tau
31    TYPE(t_field),POINTER :: f_phis(:)
32    TYPE(t_field),POINTER :: f_ps(:)
33    TYPE(t_field),POINTER :: f_mass(:)
34    TYPE(t_field),POINTER :: f_theta_rhodz(:)
35    TYPE(t_field),POINTER :: f_u(:)
36    TYPE(t_field),POINTER :: f_q(:)
37    TYPE(t_field),POINTER :: f_W(:)
38    TYPE(t_field),POINTER :: f_geopot(:)
39    TYPE(t_field),POINTER :: f_hflux(:), f_wflux(:)
40    TYPE(t_field) :: f_dps(:)
41    TYPE(t_field) :: f_dmass(:)
42    TYPE(t_field) :: f_dtheta_rhodz(:)
43    TYPE(t_field) :: f_du_slow(:)
44    TYPE(t_field) :: f_du_fast(:)
45    TYPE(t_field) :: f_dW_slow(:)
46    TYPE(t_field) :: f_dW_fast(:)
47    TYPE(t_field) :: f_dPhi_slow(:)
48    TYPE(t_field) :: f_dPhi_fast(:)
49   
50    REAL(rstd),POINTER :: ps(:), dps(:), phis(:)
51    REAL(rstd),POINTER :: mass(:,:), theta_rhodz(:,:,:), dtheta_rhodz(:,:,:)
52    REAL(rstd),POINTER :: du(:,:), dW(:,:), dPhi(:,:), hflux(:,:), wflux(:,:)
53    REAL(rstd),POINTER :: u(:,:), w(:,:), qu(:,:), qv(:,:)
54
55! temporary shared variable
56    REAL(rstd),POINTER  :: theta(:,:,:) 
57    REAL(rstd),POINTER  :: pk(:,:)
58    REAL(rstd),POINTER  :: geopot(:,:)
59    REAL(rstd),POINTER  :: convm(:,:) 
60    REAL(rstd),POINTER  :: wwuu(:,:)
61    REAL(rstd),POINTER  :: F_el(:,:), gradPhi2(:,:), w_il(:,:) , W_etadot(:,:), pres(:,:), m_il(:,:)
62    INTEGER :: ind
63    LOGICAL,SAVE :: first=.TRUE.
64!$OMP THREADPRIVATE(first)
65   
66    IF (first) THEN
67      first=.FALSE.
68      IF(caldyn_eta==eta_mass) THEN
69         CALL init_message(f_ps,req_i1,req_ps)
70      ELSE
71         CALL init_message(f_mass,req_i1,req_mass)
72      END IF
73      CALL init_message(f_theta_rhodz,req_i1,req_theta_rhodz)
74      CALL init_message(f_u,req_e1_vect,req_u)
75      CALL init_message(f_qu,req_e1_scal,req_qu)
76      IF(.NOT.hydrostatic) THEN
77         CALL init_message(f_geopot,req_i1,req_geopot)
78         CALL init_message(f_w,req_i1,req_w)
79      END IF
80    ENDIF
81   
82    CALL trace_start("caldyn")
83   
84    IF(caldyn_eta==eta_mass) THEN
85       CALL send_message(f_ps,req_ps) ! COM00
86       CALL wait_message(req_ps) ! COM00
87    ELSE
88       CALL send_message(f_mass,req_mass) ! COM00
89       CALL wait_message(req_mass) ! COM00
90    END IF
91    CALL send_message(f_theta_rhodz,req_theta_rhodz) ! COM01
92    CALL wait_message(req_theta_rhodz) ! COM01 Moved from caldyn_pvort
93
94    IF(.NOT.hydrostatic) THEN
95       CALL send_message(f_geopot,req_geopot) ! COM03
96       CALL wait_message(req_geopot) ! COM03
97       CALL send_message(f_w,req_w) ! COM04
98       CALL wait_message(req_w) ! COM04
99    END IF
100   
101    DO ind=1,ndomain
102       IF (.NOT. assigned_domain(ind)) CYCLE
103       CALL swap_dimensions(ind)
104       CALL swap_geometry(ind)
105       ps=f_ps(ind)
106       theta_rhodz=f_theta_rhodz(ind)
107       mass=f_mass(ind)
108       theta = f_theta(ind)
109       CALL compute_theta(ps,theta_rhodz, mass,theta)
110       pk = f_pk(ind)
111       geopot = f_geopot(ind)
112       du=f_du_fast(ind)
113       IF(hydrostatic) THEN
114          du(:,:)=0.
115          CALL compute_geopot(mass,theta, ps,pk,geopot)
116       ELSE
117          phis = f_phis(ind)
118          W = f_W(ind)
119          dW = f_dW_fast(ind)
120          dPhi = f_dPhi_fast(ind)
121          ! reuse buffers
122          m_il = f_wil(ind)
123          pres = f_gradPhi2(ind)
124          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
125       END IF
126       u=f_u(ind)
127       CALL compute_caldyn_fast(tau,u,mass,theta,pk,geopot,du) ! computes du_fast and updates u
128    ENDDO
129   
130    CALL send_message(f_u,req_u) ! COM02
131    CALL wait_message(req_u)   ! COM02
132   
133    DO ind=1,ndomain
134       IF (.NOT. assigned_domain(ind)) CYCLE
135       CALL swap_dimensions(ind)
136       CALL swap_geometry(ind)
137       u=f_u(ind)
138       mass=f_mass(ind)
139       qu=f_qu(ind)
140       qv=f_qv(ind)
141       CALL compute_pvort_only(u,mass,qu,qv)
142    ENDDO
143   
144    CALL send_message(f_qu,req_qu) ! COM03
145    CALL wait_message(req_qu) ! COM03
146       
147    DO ind=1,ndomain
148       IF (.NOT. assigned_domain(ind)) CYCLE
149       CALL swap_dimensions(ind)
150       CALL swap_geometry(ind)
151       u=f_u(ind)
152       mass=f_mass(ind)
153       theta = f_theta(ind)
154       qu=f_qu(ind)
155       hflux=f_hflux(ind)
156       convm = f_dmass(ind)
157       dtheta_rhodz=f_dtheta_rhodz(ind)
158       du=f_du_slow(ind)
159
160       IF(hydrostatic) THEN
161          CALL compute_caldyn_slow_hydro(u,mass,hflux,du, .TRUE.)
162       ELSE
163          W = f_W(ind)
164          dW = f_dW_slow(ind)
165          geopot = f_geopot(ind)
166          dPhi = f_dPhi_slow(ind)
167          F_el = f_Fel(ind)
168          gradPhi2 = f_gradPhi2(ind)
169          w_il = f_wil(ind)
170          CALL compute_caldyn_slow_NH(u,mass,geopot,W, F_el,gradPhi2,w_il, hflux,du,dPhi,dW)
171       END IF
172       CALL compute_caldyn_Coriolis(hflux,theta,qu, convm,dtheta_rhodz,du)
173       IF(caldyn_eta==eta_mass) THEN
174          wflux=f_wflux(ind)
175          wwuu=f_wwuu(ind)
176          dps=f_dps(ind)
177          CALL compute_caldyn_vert(u,theta,mass,convm, wflux,wwuu, dps, dtheta_rhodz, du)
178          IF(.NOT.hydrostatic) THEN
179             W_etadot=f_Wetadot(ind)
180             CALL compute_caldyn_vert_NH(mass,geopot,W,wflux, W_etadot, du,dPhi,dW)
181          END IF
182       END IF
183    ENDDO
184   
185!$OMP BARRIER
186    !    CALL check_mass_conservation(f_ps,f_dps)
187    CALL trace_end("caldyn_hevi")
188!!$OMP BARRIER
189   
190  END SUBROUTINE caldyn_hevi
191
192END MODULE caldyn_hevi_mod
Note: See TracBrowser for help on using the repository browser.