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

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

devel : cleanup USE data_unstructured_mod

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