Line data Source code
1 : module geopotential
2 :
3 : !---------------------------------------------------------------------------------
4 : ! Compute geopotential from temperature or
5 : ! compute geopotential and temperature from dry static energy.
6 : !
7 : ! The hydrostatic matrix elements must be consistent with the dynamics algorithm.
8 : ! The diagonal element is the itegration weight from interface k+1 to midpoint k.
9 : ! The offdiagonal element is the weight between interfaces.
10 : !
11 : ! Author: B.Boville, Feb 2001 from earlier code by Boville and S.J. Lin
12 : !---------------------------------------------------------------------------------
13 :
14 : use shr_kind_mod, only: r8 => shr_kind_r8
15 : use ppgrid, only: pver, pverp
16 : use dycore, only: dycore_is
17 :
18 : implicit none
19 : private
20 : save
21 :
22 : public geopotential_t
23 :
24 : contains
25 :
26 : !===============================================================================
27 23907312 : subroutine geopotential_t( &
28 23907312 : piln , pmln , pint , pmid , pdel , rpdel , &
29 47814624 : t , q , rair , gravit , zvir , &
30 47814624 : zi , zm , ncol )
31 :
32 : !-----------------------------------------------------------------------
33 : !
34 : ! Purpose:
35 : ! Compute the geopotential height (above the surface) at the midpoints and
36 : ! interfaces using the input temperatures and pressures.
37 : !
38 : !-----------------------------------------------------------------------
39 :
40 : use ppgrid, only: pcols
41 : use constituents, only: pcnst, cnst_get_ind
42 : use ccpp_constituent_prop_mod, only: ccpp_const_props !CCPP constituent properties array (CAM version)
43 : use geopotential_temp, only: geopotential_temp_run !CCPP version
44 : !------------------------------Arguments--------------------------------
45 : !
46 : ! Input arguments
47 : !
48 : integer, intent(in) :: ncol ! Number of longitudes
49 :
50 : real(r8), intent(in) :: piln (:,:) ! (pcols,pverp) - Log interface pressures
51 : real(r8), intent(in) :: pmln (:,:) ! (pcols,pver) - Log midpoint pressures
52 : real(r8), intent(in) :: pint (:,:) ! (pcols,pverp) - Interface pressures
53 : real(r8), intent(in) :: pmid (:,:) ! (pcols,pver) - Midpoint pressures
54 : real(r8), intent(in) :: pdel (:,:) ! (pcols,pver) - layer thickness
55 : real(r8), intent(in) :: rpdel(:,:) ! (pcols,pver) - inverse of layer thickness
56 : real(r8), intent(in) :: t (:,:) ! (pcols,pver) - temperature
57 : real(r8), intent(in) :: q (:,:,:) ! (pcols,pver,:)- tracers (moist mixing ratios)
58 : real(r8), intent(in) :: rair (:,:) ! (pcols,pver) - Gas constant for dry air
59 : real(r8), intent(in) :: gravit ! - Acceleration of gravity
60 : real(r8), intent(in) :: zvir (:,:) ! (pcols,pver) - rh2o/rair - 1
61 :
62 : ! Output arguments
63 :
64 : real(r8), intent(out) :: zi(:,:) ! (pcols,pverp) - Height above surface at interfaces
65 : real(r8), intent(out) :: zm(:,:) ! (pcols,pver) - Geopotential height at mid level
66 : !
67 : !---------------------------Local variables-----------------------------
68 : !
69 : logical :: lagrang ! Lagrangian vertical coordinate flag
70 : integer :: ixq ! state constituent array index for water vapor
71 : integer :: i,k,idx ! Lon, level indices, water species index
72 47814624 : real(r8) :: hkk(ncol) ! diagonal element of hydrostatic matrix
73 47814624 : real(r8) :: hkl(ncol) ! off-diagonal element
74 47814624 : real(r8) :: rog(ncol,pver) ! Rair / gravit
75 : real(r8) :: tv ! virtual temperature
76 : real(r8) :: tvfac ! Tv/T
77 : real(r8) :: qfac(ncol,pver) ! factor to convert from wet to dry mixing ratio
78 : real(r8) :: sum_dry_mixing_ratio(ncol,pver)! sum of dry water mixing ratios
79 :
80 : !CCPP-required variables (not used):
81 : integer :: errflg
82 : character(len=512) :: errmsg
83 :
84 : !
85 : !-----------------------------------------------------------------------
86 : !
87 : !Determine index for water vapor mass mixing ratio
88 23907312 : call cnst_get_ind('Q', ixq)
89 :
90 : !
91 : ! original code for backwards compatability with FV and EUL
92 : !
93 23907312 : if (.not.(dycore_is('MPAS') .or. dycore_is('SE'))) then
94 :
95 : !dry air gas constant over gravity
96 0 : rog(:ncol,:) = rair(:ncol,:) / gravit
97 :
98 : ! The surface height is zero by definition.
99 0 : do i = 1,ncol
100 0 : zi(i,pverp) = 0.0_r8
101 : end do
102 :
103 : ! Compute zi, zm from bottom up.
104 : ! Note, zi(i,k) is the interface above zm(i,k)
105 0 : do k = pver, 1, -1
106 :
107 : ! First set hydrostatic elements consistent with dynamics
108 :
109 0 : if ((dycore_is('LR') .or. dycore_is('FV3'))) then
110 0 : do i = 1,ncol
111 0 : hkl(i) = piln(i,k+1) - piln(i,k)
112 0 : hkk(i) = 1._r8 - pint(i,k) * hkl(i) * rpdel(i,k)
113 : end do
114 : else
115 0 : do i = 1,ncol
116 0 : hkl(i) = pdel(i,k) / pmid(i,k)
117 0 : hkk(i) = 0.5_r8 * hkl(i)
118 : end do
119 : end if
120 :
121 : ! Now compute tv, zm, zi
122 :
123 0 : do i = 1,ncol
124 0 : tvfac = 1._r8 + zvir(i,k) * q(i,k,ixq)
125 0 : tv = t(i,k) * tvfac
126 :
127 0 : zm(i,k) = zi(i,k+1) + rog(i,k) * tv * hkk(i)
128 0 : zi(i,k) = zi(i,k+1) + rog(i,k) * tv * hkl(i)
129 : end do
130 : end do
131 : else !Using MPAS or SE dycore
132 :
133 : !Determine vertical coordinate type,
134 : !NOTE: Currently the FV (LR) or FV3 dycores
135 : ! do not allow for condensate loading,
136 : ! so for now 'lagrang' will always be FALSE.
137 23907312 : if ((dycore_is('LR') .or. dycore_is('FV3'))) then
138 0 : lagrang = .true.
139 : else
140 23907312 : lagrang = .false.
141 : end if
142 :
143 : !Use CCPP version of geopotential_t:
144 : call geopotential_temp_run(pver, lagrang, pver, 1, pverp, 1, &
145 71721936 : pcnst, piln(1:ncol,:), pint(1:ncol,:), pmid(1:ncol,:), &
146 71721936 : pdel(1:ncol,:), rpdel(1:ncol,:), t(1:ncol,:), &
147 23907312 : q(1:ncol,:,ixq), q(1:ncol,:,:), ccpp_const_props, &
148 71721936 : rair(1:ncol,:), gravit, zvir(1:ncol,:), zi(1:ncol,:), &
149 262980432 : zm(1:ncol,:), ncol, errflg, errmsg)
150 :
151 : end if
152 23907312 : end subroutine geopotential_t
153 : end module geopotential
|