source: codes/icosagcm/trunk/src/caldyn_hevi.f90 @ 362

Last change on this file since 362 was 362, checked in by dubos, 9 years ago

Introduced DEC convention for velocity - HEVI only - cleanup to follow

File size: 4.2 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_geopot, f_hflux, f_wflux, f_dps, f_dmass, f_dtheta_rhodz, f_du_slow, f_du_fast)
15    USE icosa
16    USE observable_mod
17    USE disvert_mod, ONLY : caldyn_eta, eta_mass
18    USE vorticity_mod
19    USE kinetic_mod
20    USE theta2theta_rhodz_mod
21    USE wind_mod
22    USE mpipara
23    USE trace
24    USE omp_para
25    USE output_field_mod
26    USE checksum_mod
27    IMPLICIT NONE
28    LOGICAL,INTENT(IN)    :: write_out
29    REAL(rstd), INTENT(IN) :: tau
30    TYPE(t_field),POINTER :: f_phis(:)
31    TYPE(t_field),POINTER :: f_ps(:)
32    TYPE(t_field),POINTER :: f_mass(:)
33    TYPE(t_field),POINTER :: f_theta_rhodz(:)
34    TYPE(t_field),POINTER :: f_u(:)
35    TYPE(t_field),POINTER :: f_q(:)
36    TYPE(t_field),POINTER :: f_geopot(:)
37    TYPE(t_field),POINTER :: f_hflux(:), f_wflux(:)
38    TYPE(t_field) :: f_dps(:)
39    TYPE(t_field) :: f_dmass(:)
40    TYPE(t_field) :: f_dtheta_rhodz(:)
41    TYPE(t_field) :: f_du_slow(:)
42    TYPE(t_field) :: f_du_fast(:)
43   
44    REAL(rstd),POINTER :: ps(:), dps(:)
45    REAL(rstd),POINTER :: mass(:,:), theta_rhodz(:,:), dtheta_rhodz(:,:)
46    REAL(rstd),POINTER :: du(:,:), hflux(:,:), wflux(:,:)
47    REAL(rstd),POINTER :: u(:,:), qu(:,:), qv(:,:)
48
49! temporary shared variable
50    REAL(rstd),POINTER  :: theta(:,:) 
51    REAL(rstd),POINTER  :: pk(:,:)
52    REAL(rstd),POINTER  :: geopot(:,:)
53    REAL(rstd),POINTER  :: convm(:,:) 
54    REAL(rstd),POINTER  :: wwuu(:,:)
55       
56    INTEGER :: ind
57    LOGICAL,SAVE :: first=.TRUE.
58!$OMP THREADPRIVATE(first)
59   
60    IF (first) THEN
61      first=.FALSE.
62      IF(caldyn_eta==eta_mass) THEN
63         CALL init_message(f_ps,req_i1,req_ps)
64      ELSE
65         CALL init_message(f_mass,req_i1,req_mass)
66      END IF
67      CALL init_message(f_theta_rhodz,req_i1,req_theta_rhodz)
68      CALL init_message(f_u,req_e1_vect,req_u)
69      CALL init_message(f_qu,req_e1_scal,req_qu)
70    ENDIF
71   
72    CALL trace_start("caldyn")
73   
74    IF(caldyn_eta==eta_mass) THEN
75       CALL send_message(f_ps,req_ps) ! COM00
76       CALL wait_message(req_ps) ! COM00
77    ELSE
78       CALL send_message(f_mass,req_mass) ! COM00
79       CALL wait_message(req_mass) ! COM00
80    END IF
81    CALL send_message(f_theta_rhodz,req_theta_rhodz) ! COM01
82    CALL wait_message(req_theta_rhodz) ! COM01 Moved from caldyn_pvort
83   
84    DO ind=1,ndomain
85       IF (.NOT. assigned_domain(ind)) CYCLE
86       CALL swap_dimensions(ind)
87       CALL swap_geometry(ind)
88       ps=f_ps(ind)
89       u=f_u(ind)
90       du=f_du_fast(ind)
91       theta_rhodz=f_theta_rhodz(ind)
92       mass=f_mass(ind)
93       theta = f_theta(ind)
94       pk = f_pk(ind)
95       geopot = f_geopot(ind)
96       CALL compute_theta(ps,theta_rhodz, mass,theta)
97       CALL compute_geopot(ps,mass,theta, pk,geopot)
98       CALL compute_caldyn_fast(tau,u,mass,theta,pk,geopot, du) ! computes du_fast and updates u
99    ENDDO
100   
101    CALL send_message(f_u,req_u) ! COM02
102    CALL wait_message(req_u)   ! COM02
103   
104    DO ind=1,ndomain
105       IF (.NOT. assigned_domain(ind)) CYCLE
106       CALL swap_dimensions(ind)
107       CALL swap_geometry(ind)
108       u=f_u(ind)
109       mass=f_mass(ind)
110       qu=f_qu(ind)
111       qv=f_qv(ind)
112       CALL compute_pvort_only(u,mass,qu,qv)
113    ENDDO
114   
115    CALL send_message(f_qu,req_qu) ! COM03
116   
117    DO ind=1,ndomain
118       IF (.NOT. assigned_domain(ind)) CYCLE
119       CALL swap_dimensions(ind)
120       CALL swap_geometry(ind)
121       u=f_u(ind)
122       mass=f_mass(ind)
123       theta = f_theta(ind)
124       qu=f_qu(ind)
125       hflux=f_hflux(ind)
126       convm = f_dmass(ind)
127       dtheta_rhodz=f_dtheta_rhodz(ind)
128       du=f_du_slow(ind)
129       CALL compute_caldyn_slow(u,mass,qu,theta, hflux,convm,dtheta_rhodz,du) ! COM03
130       IF(caldyn_eta==eta_mass) THEN
131          wflux=f_wflux(ind)
132          wwuu=f_wwuu(ind)
133          dps=f_dps(ind)
134          CALL compute_caldyn_vert(u,theta,mass,convm, wflux,wwuu, dps, dtheta_rhodz, du)
135       END IF
136    ENDDO
137   
138!$OMP BARRIER
139    !    CALL check_mass_conservation(f_ps,f_dps)
140    CALL trace_end("caldyn_hevi")
141!!$OMP BARRIER
142   
143  END SUBROUTINE caldyn_hevi
144
145END MODULE caldyn_hevi_mod
Note: See TracBrowser for help on using the repository browser.