source: codes/icosagcm/devel/src/dynamics/compute_caldyn_slow_NH.F90 @ 850

Last change on this file since 850 was 850, checked in by jisesh, 5 years ago

devel: separate module for compute_caldyn_slow_NH

File size: 7.0 KB
Line 
1MODULE compute_caldyn_slow_NH_mod
2  USE grid_param, ONLY : llm
3  IMPLICIT NONE
4  PRIVATE
5
6  PUBLIC :: compute_caldyn_slow_NH
7
8CONTAINS
9
10  SUBROUTINE compute_caldyn_slow_NH(u,rhodz,Phi,W, F_el,gradPhi2,w_il, hflux,du,dPhi,dW)
11    USE icosa
12    USE caldyn_vars_mod
13    USE omp_para, ONLY : ll_begin, ll_end,ll_beginp1,ll_endp1
14    REAL(rstd),INTENT(IN)  :: u(3*iim*jjm,llm)    ! prognostic "velocity"
15    REAL(rstd),INTENT(IN)  :: rhodz(iim*jjm,llm)  ! rho*dz
16    REAL(rstd),INTENT(IN)  :: Phi(iim*jjm,llm+1)  ! prognostic geopotential
17    REAL(rstd),INTENT(IN)  :: W(iim*jjm,llm+1)    ! prognostic vertical momentum
18
19    REAL(rstd),INTENT(OUT) :: hflux(3*iim*jjm,llm) ! hflux in kg/s
20    REAL(rstd),INTENT(OUT) :: du(3*iim*jjm,llm)
21    REAL(rstd),INTENT(OUT) :: dW(iim*jjm,llm+1)
22    REAL(rstd),INTENT(OUT) :: dPhi(iim*jjm,llm+1)
23
24    REAL(rstd) :: w_il(iim*jjm,llm+1) ! Wil/mil
25    REAL(rstd) :: F_el(3*iim*jjm,llm+1) ! NH mass flux
26    REAL(rstd) :: gradPhi2(iim*jjm,llm+1) ! grad_Phi**2
27    REAL(rstd) :: DePhil(3*iim*jjm,llm+1) ! grad(Phi)
28   
29    INTEGER :: ij,l,kdown,kup
30    REAL(rstd) :: W_el, W2_el, uu_right, uu_lup, uu_ldown, gPhi2, dP, divG, u2, uu
31
32    REAL(rstd) :: berni(iim*jjm,llm)  ! Bernoulli function
33    REAL(rstd) :: G_el(3*iim*jjm,llm+1) ! horizontal flux of W
34    REAL(rstd) :: v_el(3*iim*jjm,llm+1)
35
36    REAL(rstd) :: berni1(iim*jjm)  ! Bernoulli function
37    REAL(rstd) :: G_el1(3*iim*jjm) ! horizontal flux of W
38    REAL(rstd) :: v_el1(3*iim*jjm)
39
40    CALL trace_start("compute_caldyn_slow_NH")
41
42    IF(dysl) THEN
43
44!$OMP BARRIER
45#include "../kernels_hex/caldyn_slow_NH.k90"
46!$OMP BARRIER
47     
48     ELSE
49
50#define BERNI(ij) berni1(ij)
51#define G_EL(ij) G_el1(ij)
52#define V_EL(ij) v_el1(ij)
53
54    DO l=ll_begin, ll_endp1 ! compute on l levels (interfaces)
55       IF(l==1) THEN
56          kdown=1
57       ELSE
58          kdown=l-1
59       END IF
60       IF(l==llm+1) THEN
61          kup=llm
62       ELSE
63          kup=l
64       END IF
65       ! below : "checked" means "formula also valid when kup=kdown (top/bottom)"
66       ! compute mil, wil=Wil/mil
67       DO ij=ij_begin_ext, ij_end_ext
68          w_il(ij,l) = 2.*W(ij,l)/(rhodz(ij,kdown)+rhodz(ij,kup)) ! checked
69       END DO
70       ! compute DePhi, v_el, G_el, F_el
71       ! v_el, W2_el and therefore G_el incorporate metric factor le_de
72       ! while DePhil, W_el and F_el don't
73       DO ij=ij_begin_ext, ij_end_ext
74          ! Compute on edge 'right'
75          W_el  = .5*( W(ij,l)+W(ij+t_right,l) )
76          DePhil(ij+u_right,l) = ne_right*(Phi(ij+t_right,l)-Phi(ij,l))
77          F_el(ij+u_right,l)   = DePhil(ij+u_right,l)*W_el
78          W2_el = .5*le_de(ij+u_right) * &
79               ( W(ij,l)*w_il(ij,l) + W(ij+t_right,l)*w_il(ij+t_right,l) )
80          V_EL(ij+u_right) = .5*le_de(ij+u_right)*(u(ij+u_right,kup)+u(ij+u_right,kdown)) ! checked
81          G_EL(ij+u_right) = V_EL(ij+u_right)*W_el - DePhil(ij+u_right,l)*W2_el
82          ! Compute on edge 'lup'
83          W_el  = .5*( W(ij,l)+W(ij+t_lup,l) )
84          DePhil(ij+u_lup,l) = ne_lup*(Phi(ij+t_lup,l)-Phi(ij,l))
85          F_el(ij+u_lup,l)   = DePhil(ij+u_lup,l)*W_el
86          W2_el = .5*le_de(ij+u_lup) * &
87               ( W(ij,l)*w_il(ij,l) + W(ij+t_lup,l)*w_il(ij+t_lup,l) )
88          V_EL(ij+u_lup) = .5*le_de(ij+u_lup)*( u(ij+u_lup,kup) + u(ij+u_lup,kdown)) ! checked
89          G_EL(ij+u_lup) = V_EL(ij+u_lup)*W_el - DePhil(ij+u_lup,l)*W2_el
90          ! Compute on edge 'ldown'
91          W_el  = .5*( W(ij,l)+W(ij+t_ldown,l) )
92          DePhil(ij+u_ldown,l) = ne_ldown*(Phi(ij+t_ldown,l)-Phi(ij,l))
93          F_el(ij+u_ldown,l) = DePhil(ij+u_ldown,l)*W_el
94          W2_el = .5*le_de(ij+u_ldown) * &
95               ( W(ij,l)*w_il(ij,l) + W(ij+t_ldown,l)*w_il(ij+t_ldown,l) )
96          V_EL(ij+u_ldown) = .5*le_de(ij+u_ldown)*( u(ij+u_ldown,kup) + u(ij+u_ldown,kdown)) ! checked
97          G_EL(ij+u_ldown) = V_EL(ij+u_ldown)*W_el - DePhil(ij+u_ldown,l)*W2_el
98       END DO
99       ! compute GradPhi2, dPhi, dW
100       DO ij=ij_begin_ext, ij_end_ext
101          gradPhi2(ij,l) = &
102               1/(2*Ai(ij))*(le_de(ij+u_right)*DePhil(ij+u_right,l)**2 + &
103               le_de(ij+u_rup)*DePhil(ij+u_rup,l)**2 +      &
104               le_de(ij+u_lup)*DePhil(ij+u_lup,l)**2 +      &
105               le_de(ij+u_left)*DePhil(ij+u_left,l)**2 +    &
106               le_de(ij+u_ldown)*DePhil(ij+u_ldown,l)**2 +  &
107               le_de(ij+u_rdown)*DePhil(ij+u_rdown,l)**2 )
108
109          dPhi(ij,l) = gradPhi2(ij,l)*w_il(ij,l) -1/(2*Ai(ij))* & 
110               ( DePhil(ij+u_right,l)*V_EL(ij+u_right) + & ! -v.gradPhi,
111                 DePhil(ij+u_rup,l)*V_EL(ij+u_rup) +     & ! v_el already has le_de
112                 DePhil(ij+u_lup,l)*V_EL(ij+u_lup) +     &
113                 DePhil(ij+u_left,l)*V_EL(ij+u_left) +   &
114                 DePhil(ij+u_ldown,l)*V_EL(ij+u_ldown) + &
115                 DePhil(ij+u_rdown,l)*V_EL(ij+u_rdown) )
116
117          dW(ij,l) = -1./Ai(ij)*(           & ! -div(G_el),
118               ne_right*G_EL(ij+u_right) +  & ! G_el already has le_de
119               ne_rup*G_EL(ij+u_rup) +      &
120               ne_lup*G_EL(ij+u_lup) +      & 
121               ne_left*G_EL(ij+u_left) +    &
122               ne_ldown*G_EL(ij+u_ldown) +  &
123               ne_rdown*G_EL(ij+u_rdown))
124       END DO
125    END DO
126
127    DO l=ll_begin, ll_end ! compute on k levels (layers)
128       ! Compute berni at scalar points
129       DO ij=ij_begin_ext, ij_end_ext
130          BERNI(ij) = &
131               1/(4*Ai(ij))*( &
132                    le_de(ij+u_right)*u(ij+u_right,l)**2 +    &
133                    le_de(ij+u_rup)*u(ij+u_rup,l)**2 +          &
134                    le_de(ij+u_lup)*u(ij+u_lup,l)**2 +          &
135                    le_de(ij+u_left)*u(ij+u_left,l)**2 +       &
136                    le_de(ij+u_ldown)*u(ij+u_ldown,l)**2 +    &
137                    le_de(ij+u_rdown)*u(ij+u_rdown,l)**2 ) &
138               - .25*( gradPhi2(ij,l)  *w_il(ij,l)**2 +   &
139                      gradPhi2(ij,l+1)*w_il(ij,l+1)**2 )
140       END DO
141       ! Compute mass flux and grad(berni) at edges
142       DO ij=ij_begin_ext, ij_end_ext
143          ! Compute on edge 'right'
144          uu_right = 0.5*(rhodz(ij,l)+rhodz(ij+t_right,l))*u(ij+u_right,l) &
145                    -0.5*(F_el(ij+u_right,l)+F_el(ij+u_right,l+1))
146          hflux(ij+u_right,l) = uu_right*le_de(ij+u_right)
147          du(ij+u_right,l) = ne_right*(BERNI(ij)-BERNI(ij+t_right))
148          ! Compute on edge 'lup'
149          uu_lup = 0.5*(rhodz(ij,l)+rhodz(ij+t_lup,l))*u(ij+u_lup,l) &
150                  -0.5*(F_el(ij+u_lup,l)+F_el(ij+u_lup,l+1))
151          hflux(ij+u_lup,l) = uu_lup*le_de(ij+u_lup)
152          du(ij+u_lup,l) = ne_lup*(BERNI(ij)-BERNI(ij+t_lup))
153          ! Compute on edge 'ldown'
154          uu_ldown = 0.5*(rhodz(ij,l)+rhodz(ij+t_ldown,l))*u(ij+u_ldown,l) &
155                    -0.5*(F_el(ij+u_ldown,l)+F_el(ij+u_ldown,l+1))
156          hflux(ij+u_ldown,l) = uu_ldown*le_de(ij+u_ldown)
157          du(ij+u_ldown,l) = ne_ldown*(BERNI(ij)-BERNI(ij+t_ldown))
158       END DO
159    END DO
160
161#undef V_EL
162#undef G_EL
163#undef BERNI
164
165    END IF ! dysl
166
167    CALL trace_end("compute_caldyn_slow_NH")
168
169  END SUBROUTINE compute_caldyn_slow_NH
170
171END MODULE compute_caldyn_slow_NH_mod
Note: See TracBrowser for help on using the repository browser.