source: codes/icosagcm/devel/src/dynamics/compute_geopot.F90 @ 920

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

devel : separate module for compute_geopot

File size: 6.6 KB
Line 
1MODULE compute_geopot_mod
2  USE prec, ONLY : rstd
3  USE grid_param
4  USE earth_const
5  USE disvert_mod
6  USE omp_para
7  USE trace
8  IMPLICIT NONE
9  PRIVATE
10  SAVE
11
12  PUBLIC :: compute_geopot_hex, compute_geopot_manual
13
14CONTAINS
15
16  !**************************** Geopotential *****************************
17
18  SUBROUTINE compute_geopot_hex(rhodz,theta, ps,pk,geopot) 
19    REAL(rstd),INTENT(IN)    :: rhodz(iim*jjm,llm)
20    REAL(rstd),INTENT(IN)    :: theta(iim*jjm,llm,nqdyn) ! active scalars : theta/entropy, moisture, ...
21    REAL(rstd),INTENT(INOUT) :: ps(iim*jjm)
22    REAL(rstd),INTENT(OUT)   :: pk(iim*jjm,llm)       ! Exner function (compressible) /Lagrange multiplier (Boussinesq)
23    REAL(rstd),INTENT(INOUT) :: geopot(iim*jjm,llm+1) ! geopotential
24
25    INTEGER :: i,j,ij,l
26    REAL(rstd) :: p_ik, exner_ik, Cp_ik, temp_ik, qv, chi, Rmix, gv
27    INTEGER    :: ij_omp_begin_ext, ij_omp_end_ext
28
29    CALL trace_start("compute_geopot")
30    !$OMP BARRIER
31    CALL distrib_level(ij_begin_ext,ij_end_ext, ij_omp_begin_ext,ij_omp_end_ext)
32#include "../kernels_hex/compute_geopot.k90"
33    !$OMP BARRIER
34
35    CALL trace_end("compute_geopot")
36  END SUBROUTINE compute_geopot_hex
37
38  SUBROUTINE compute_geopot_manual(rhodz,theta, ps,pk,geopot) 
39    REAL(rstd),INTENT(IN)    :: rhodz(iim*jjm,llm)
40    REAL(rstd),INTENT(IN)    :: theta(iim*jjm,llm,nqdyn) ! active scalars : theta/entropy, moisture, ...
41    REAL(rstd),INTENT(INOUT) :: ps(iim*jjm)
42    REAL(rstd),INTENT(OUT)   :: pk(iim*jjm,llm)       ! Exner function (compressible) /Lagrange multiplier (Boussinesq)
43    REAL(rstd),INTENT(INOUT) :: geopot(iim*jjm,llm+1) ! geopotential
44
45    INTEGER :: i,j,ij,l
46    REAL(rstd) :: p_ik, exner_ik, Cp_ik, temp_ik, qv, chi, Rmix, gv
47    INTEGER    :: ij_omp_begin_ext, ij_omp_end_ext
48
49    CALL trace_start("compute_geopot")
50
51!$OMP BARRIER
52
53    CALL distrib_level(ij_begin_ext,ij_end_ext, ij_omp_begin_ext,ij_omp_end_ext)
54
55    ! Pressure is computed first top-down (temporarily stored in pk)
56    ! Then Exner pressure and geopotential are computed bottom-up
57    ! Works also when caldyn_eta=eta_mass         
58
59    IF(boussinesq) THEN ! compute geopotential and pk=Lagrange multiplier
60       ! specific volume 1 = dphi/g/rhodz
61       !         IF (is_omp_level_master) THEN ! no openMP on vertical due to dependency
62       DO l = 1,llm
63          !DIR$ SIMD
64          DO ij=ij_omp_begin_ext,ij_omp_end_ext         
65             geopot(ij,l+1) = geopot(ij,l) + g*rhodz(ij,l)
66          ENDDO
67       ENDDO
68       ! use hydrostatic balance with theta*rhodz to find pk (Lagrange multiplier=pressure)
69       ! uppermost layer
70       !DIR$ SIMD
71       DO ij=ij_begin_ext,ij_end_ext         
72          pk(ij,llm) = ptop + (.5*g)*theta(ij,llm,1)*rhodz(ij,llm)
73       END DO
74       ! other layers
75       DO l = llm-1, 1, -1
76          !          !$OMP DO SCHEDULE(STATIC)
77          !DIR$ SIMD
78          DO ij=ij_begin_ext,ij_end_ext         
79             pk(ij,l) = pk(ij,l+1) + (.5*g)*(theta(ij,l,1)*rhodz(ij,l)+theta(ij,l+1,1)*rhodz(ij,l+1))
80          END DO
81       END DO
82       ! now pk contains the Lagrange multiplier (pressure)
83    ELSE ! non-Boussinesq, compute pressure, Exner pressure or temperature, then geopotential
84       ! uppermost layer
85       
86       SELECT CASE(caldyn_thermo)
87          CASE(thermo_theta, thermo_entropy)
88             !DIR$ SIMD
89             DO ij=ij_omp_begin_ext,ij_omp_end_ext
90                pk(ij,llm) = ptop + (.5*g)*rhodz(ij,llm)
91             END DO
92             ! other layers
93             DO l = llm-1, 1, -1
94                !DIR$ SIMD
95                DO ij=ij_omp_begin_ext,ij_omp_end_ext         
96                   pk(ij,l) = pk(ij,l+1) + (.5*g)*(rhodz(ij,l)+rhodz(ij,l+1))
97                END DO
98             END DO
99             ! surface pressure (for diagnostics)
100             IF(caldyn_eta==eta_lag) THEN
101                DO ij=ij_omp_begin_ext,ij_omp_end_ext         
102                   ps(ij) = pk(ij,1) + (.5*g)*rhodz(ij,1)
103                END DO
104             END IF
105          CASE(thermo_moist) ! theta(ij,l,2) = qv = mv/md
106             !DIR$ SIMD
107             DO ij=ij_omp_begin_ext,ij_omp_end_ext
108                pk(ij,llm) = ptop + (.5*g)*rhodz(ij,llm)*(1.+theta(ij,l,2))
109             END DO
110             ! other layers
111             DO l = llm-1, 1, -1
112                !DIR$ SIMD
113                DO ij=ij_omp_begin_ext,ij_omp_end_ext         
114                   pk(ij,l) = pk(ij,l+1) + (.5*g)*(          &
115                        rhodz(ij,l)  *(1.+theta(ij,l,2)) +   &
116                        rhodz(ij,l+1)*(1.+theta(ij,l+1,2)) )
117                END DO
118             END DO
119             ! surface pressure (for diagnostics)
120             IF(caldyn_eta==eta_lag) THEN
121                DO ij=ij_omp_begin_ext,ij_omp_end_ext         
122                   ps(ij) = pk(ij,1) + (.5*g)*rhodz(ij,1)*(1.+theta(ij,l,2))
123                END DO
124             END IF
125          END SELECT
126
127       DO l = 1,llm
128          SELECT CASE(caldyn_thermo)
129          CASE(thermo_theta)
130             !DIR$ SIMD
131             DO ij=ij_omp_begin_ext,ij_omp_end_ext
132                p_ik = pk(ij,l)
133                exner_ik = cpp * (p_ik/preff) ** kappa
134                pk(ij,l) = exner_ik
135                ! specific volume v = kappa*theta*pi/p = dphi/g/rhodz
136                geopot(ij,l+1) = geopot(ij,l) + (g*kappa)*rhodz(ij,l)*theta(ij,l,1)*exner_ik/p_ik
137             ENDDO
138          CASE(thermo_entropy) ! theta is in fact entropy = cpp*log(theta/Treff) = cpp*log(T/Treff) - Rd*log(p/preff)
139             !DIR$ SIMD
140             DO ij=ij_omp_begin_ext,ij_omp_end_ext
141                p_ik = pk(ij,l)
142                temp_ik = Treff*exp((theta(ij,l,1) + Rd*log(p_ik/preff))/cpp)
143                pk(ij,l) = temp_ik
144                ! specific volume v = Rd*T/p = dphi/g/rhodz
145                geopot(ij,l+1) = geopot(ij,l) + (g*Rd)*rhodz(ij,l)*temp_ik/p_ik
146             ENDDO
147          CASE(thermo_moist) ! theta is moist pseudo-entropy per dry air mass
148             DO ij=ij_omp_begin_ext,ij_omp_end_ext
149                p_ik = pk(ij,l)
150                qv = theta(ij,l,2) ! water vaper mixing ratio = mv/md
151                Rmix = Rd+qv*Rv
152                chi = ( theta(ij,l,1) + Rmix*log(p_ik/preff) ) / (cpp + qv*cppv) ! log(T/Treff)
153                temp_ik = Treff*exp(chi)
154                pk(ij,l) = temp_ik
155                ! specific volume v = R*T/p = dphi/g/rhodz
156                ! R = (Rd + qv.Rv)/(1+qv)
157                geopot(ij,l+1) = geopot(ij,l) + g*Rmix*rhodz(ij,l)*temp_ik/(p_ik*(1+qv))
158             ENDDO
159          CASE DEFAULT
160             STOP
161          END SELECT
162       ENDDO
163    END IF
164
165    !ym flush geopot
166    !$OMP BARRIER
167
168    CALL trace_end("compute_geopot")
169
170  END SUBROUTINE compute_geopot_manual
171
172END MODULE compute_geopot_mod
Note: See TracBrowser for help on using the repository browser.