source: codes/icosagcm/devel/src/dynamics/compute_pvort_only.F90 @ 840

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

devel : work around intel-15 compiler issue

File size: 3.1 KB
Line 
1MODULE compute_pvort_only_mod
2  USE compute_mod, ONLY : comp_pvort_only
3  USE grid_param, ONLY : llm
4  IMPLICIT NONE
5  PRIVATE
6
7#include "../unstructured/unstructured.h90"
8
9  PUBLIC :: compute_pvort_only_hex, compute_pvort_only_unst
10
11CONTAINS
12
13  SUBROUTINE check_interface
14    PROCEDURE(comp_pvort_only), POINTER :: ptr
15    ptr => compute_pvort_only_unst
16    ptr => compute_pvort_only_hex
17  END SUBROUTINE check_interface
18 
19  SUBROUTINE compute_pvort_only_unst(u,rhodz,qu,qv, hv_)
20    USE ISO_C_BINDING, only : C_DOUBLE, C_FLOAT
21    USE data_unstructured_mod, ONLY : enter_trace, exit_trace, &
22         id_pvort_only, primal_num, dual_num, edge_num, &
23         dual_deg, dual_edge, dual_ne, dual_vertex, up, down, Av, fv, Riv2
24    FIELD_MASS :: rhodz
25    FIELD_U    :: u,qu
26    FIELD_Z    :: qv, hv_
27    DECLARE_INDICES
28    DECLARE_EDGES
29    DECLARE_VERTICES
30    NUM :: etav, hv
31    START_TRACE(id_pvort_only, 1,1,2) ! primal, dual, edge
32#include "../kernels_unst/pvort_only.k90"
33    STOP_TRACE
34  END SUBROUTINE compute_pvort_only_unst
35
36  SUBROUTINE compute_pvort_only_hex(u,rhodz,qu,qv,hv_)
37    USE icosa
38    USE trace, ONLY : trace_start, trace_end
39    USE caldyn_vars_mod, ONLY : dysl_pvort_only
40    USE omp_para, ONLY : ll_begin, ll_end
41    REAL(rstd),INTENT(IN)  :: u(iim*3*jjm,llm)
42    REAL(rstd),INTENT(INOUT) :: rhodz(iim*jjm,llm)
43    REAL(rstd),INTENT(OUT) :: qu(iim*3*jjm,llm)
44    REAL(rstd),INTENT(OUT) :: qv(iim*2*jjm,llm)
45    REAL(rstd),INTENT(OUT) :: hv_(iim*2*jjm,llm)
46
47    INTEGER :: ij,l
48    REAL(rstd) :: etav,hv,radius_m2
49
50    CALL trace_start("compute_pvort_only") 
51!!! Compute shallow-water potential vorticity
52    IF(dysl_pvort_only) THEN
53#include "../kernels_hex/pvort_only.k90"
54    ELSE
55
56    radius_m2=radius**(-2)
57    DO l = ll_begin,ll_end
58       !DIR$ SIMD
59       DO ij=ij_begin_ext,ij_end_ext
60          etav= 1./Av(ij+z_up)*(  ne_rup  * u(ij+u_rup,l)   &
61                  + ne_left * u(ij+t_rup+u_left,l)          &
62                  - ne_lup  * u(ij+u_lup,l) )                               
63          hv =   Riv2(ij,vup)          * rhodz(ij,l)        &
64               + Riv2(ij+t_rup,vldown) * rhodz(ij+t_rup,l)  &
65               + Riv2(ij+t_lup,vrdown) * rhodz(ij+t_lup,l)
66          qv(ij+z_up,l) = ( etav+fv(ij+z_up) )/hv
67          hv_(ij+z_up,l) = hv
68         
69          etav = 1./Av(ij+z_down)*(  ne_ldown * u(ij+u_ldown,l)   &
70               + ne_right * u(ij+t_ldown+u_right,l)               &
71               - ne_rdown * u(ij+u_rdown,l) )
72          hv =   Riv2(ij,vdown)        * rhodz(ij,l)              &
73               + Riv2(ij+t_ldown,vrup) * rhodz(ij+t_ldown,l)      &
74               + Riv2(ij+t_rdown,vlup) * rhodz(ij+t_rdown,l)
75          qv(ij+z_down,l) =( etav+fv(ij+z_down) )/hv
76          hv_(ij+z_down,l) = hv
77       ENDDO
78
79       !DIR$ SIMD
80       DO ij=ij_begin,ij_end
81          qu(ij+u_right,l) = 0.5*(qv(ij+z_rdown,l)+qv(ij+z_rup,l)) 
82          qu(ij+u_lup,l) = 0.5*(qv(ij+z_up,l)+qv(ij+z_lup,l)) 
83          qu(ij+u_ldown,l) = 0.5*(qv(ij+z_ldown,l)+qv(ij+z_down,l)) 
84       END DO
85
86    ENDDO
87   
88    END IF ! dysl
89    CALL trace_end("compute_pvort_only")
90
91  END SUBROUTINE compute_pvort_only_hex
92
93END MODULE compute_pvort_only_mod
Note: See TracBrowser for help on using the repository browser.