source: codes/icosagcm/devel/src/dynamics/compute_caldyn_vert_NH.F90 @ 990

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

devel : separate modules for caldyn_vert and caldyn_vert_NH

File size: 3.7 KB
Line 
1MODULE compute_caldyn_vert_NH_mod
2  USE prec, ONLY : rstd
3  USE grid_param
4  USE disvert_mod
5  USE omp_para
6  USE trace
7  IMPLICIT NONE
8  PRIVATE
9  SAVE
10
11  PUBLIC :: compute_caldyn_vert_nh_manual, &
12       compute_caldyn_vert_nh_hex
13
14CONTAINS
15
16  SUBROUTINE compute_caldyn_vert_NH_hex(mass,geopot,W,wflux, W_etadot, du,dPhi,dW)
17    REAL(rstd),INTENT(IN) :: mass(iim*jjm,llm)
18    REAL(rstd),INTENT(IN) :: geopot(iim*jjm,llm+1)
19    REAL(rstd),INTENT(IN) :: W(iim*jjm,llm+1)
20    REAL(rstd),INTENT(IN) :: wflux(iim*jjm,llm+1)
21    REAL(rstd),INTENT(INOUT) :: du(iim*3*jjm,llm)
22    REAL(rstd),INTENT(INOUT) :: dPhi(iim*jjm,llm+1)
23    REAL(rstd),INTENT(INOUT) :: dW(iim*jjm,llm+1)
24    REAL(rstd) :: W_etadot(iim*jjm,llm) ! vertical flux of vertical momentum
25    ! local arrays
26    REAL(rstd) :: eta_dot(iim*jjm, llm) ! eta_dot in full layers
27    REAL(rstd) :: wcov(iim*jjm,llm) ! covariant vertical momentum in full layers
28    ! indices and temporary values
29    INTEGER    :: ij, l
30    REAL(rstd) :: wflux_ij, w_ij
31
32    CALL trace_start("compute_caldyn_vert_nh")
33
34!$OMP BARRIER
35#include "../kernels_hex/caldyn_vert_NH.k90"
36!$OMP BARRIER
37    CALL trace_end("compute_caldyn_vert_nh")
38  END SUBROUTINE compute_caldyn_vert_NH_hex
39
40  SUBROUTINE compute_caldyn_vert_NH_manual(mass,geopot,W,wflux, W_etadot, du,dPhi,dW)
41    REAL(rstd),INTENT(IN) :: mass(iim*jjm,llm)
42    REAL(rstd),INTENT(IN) :: geopot(iim*jjm,llm+1)
43    REAL(rstd),INTENT(IN) :: W(iim*jjm,llm+1)
44    REAL(rstd),INTENT(IN) :: wflux(iim*jjm,llm+1)
45    REAL(rstd),INTENT(INOUT) :: du(iim*3*jjm,llm)
46    REAL(rstd),INTENT(INOUT) :: dPhi(iim*jjm,llm+1)
47    REAL(rstd),INTENT(INOUT) :: dW(iim*jjm,llm+1)
48    REAL(rstd) :: W_etadot(iim*jjm,llm) ! vertical flux of vertical momentum
49    ! local arrays
50    REAL(rstd) :: eta_dot(iim*jjm, llm) ! eta_dot in full layers
51    REAL(rstd) :: wcov(iim*jjm,llm) ! covariant vertical momentum in full layers
52    ! indices and temporary values
53    INTEGER    :: ij, l
54    REAL(rstd) :: wflux_ij, w_ij
55
56    CALL trace_start("compute_caldyn_vert_nh")
57
58#define ETA_DOT(ij) eta_dot(ij,1)
59#define WCOV(ij) wcov(ij,1)
60
61    DO l=ll_begin,ll_end
62       ! compute the local arrays
63       !DIR$ SIMD
64       DO ij=ij_begin_ext,ij_end_ext
65          wflux_ij = .5*(wflux(ij,l)+wflux(ij,l+1))
66          w_ij = .5*(W(ij,l)+W(ij,l+1))/mass(ij,l)
67          W_etadot(ij,l) = wflux_ij*w_ij
68          ETA_DOT(ij) = wflux_ij / mass(ij,l)
69          WCOV(ij) = w_ij*(geopot(ij,l+1)-geopot(ij,l))
70       ENDDO
71       ! add NH term to du
72      !DIR$ SIMD
73      DO ij=ij_begin,ij_end
74          du(ij+u_right,l) = du(ij+u_right,l) &
75               - .5*(WCOV(ij+t_right)+WCOV(ij)) &
76               *ne_right*(ETA_DOT(ij+t_right)-ETA_DOT(ij))
77          du(ij+u_lup,l) = du(ij+u_lup,l) &
78               - .5*(WCOV(ij+t_lup)+WCOV(ij)) &
79               *ne_lup*(ETA_DOT(ij+t_lup)-ETA_DOT(ij))
80          du(ij+u_ldown,l) = du(ij+u_ldown,l) &
81               - .5*(WCOV(ij+t_ldown)+WCOV(ij)) &
82               *ne_ldown*(ETA_DOT(ij+t_ldown)-ETA_DOT(ij))
83       END DO
84    ENDDO
85    ! add NH terms to dW, dPhi
86    ! FIXME : TODO top and bottom
87    DO l=ll_beginp1,ll_end ! inner interfaces only
88       !DIR$ SIMD
89       DO ij=ij_begin,ij_end
90          dPhi(ij,l) = dPhi(ij,l) - wflux(ij,l) &
91               * (geopot(ij,l+1)-geopot(ij,l-1))/(mass(ij,l-1)+mass(ij,l))
92       END DO
93    END DO
94    DO l=ll_begin,ll_end
95       !DIR$ SIMD
96       DO ij=ij_begin,ij_end
97          dW(ij,l+1) = dW(ij,l+1) + W_etadot(ij,l) ! update inner+top interfaces
98          dW(ij,l)   = dW(ij,l)   - W_etadot(ij,l) ! update bottom+inner interfaces
99       END DO
100    END DO
101
102#undef ETA_DOT
103#undef WCOV
104
105    CALL trace_end("compute_caldyn_vert_nh")
106
107  END SUBROUTINE compute_caldyn_vert_NH_manual
108
109END MODULE compute_caldyn_vert_NH_mod
Note: See TracBrowser for help on using the repository browser.