UPP (develop)
Loading...
Searching...
No Matches
CALGUST.f
Go to the documentation of this file.
1
3!
23
24 SUBROUTINE calgust(LPBL,ZPBL,GUST)
25
26!
27!
28 use vrbls3d, only: uh, vh, zint, zmid
29 use vrbls2d , only: u10h, v10h, u10,v10, fis
30 use params_mod, only: d25, gi
31 use ctlblk_mod, only: jsta, jend, spval, jsta_m, jend_m, num_procs, mpi_comm_comp, lm,&
32 modelname, im, jm, jsta_2l, jend_2u, ista, iend, ista_m, iend_m, ista_2l, iend_2u
33 use gridspec_mod, only: gridtype
34
35 implicit none
36
37 include "mpif.h"
38!
39! INCLUDE ETA GRID DIMENSIONS. SET/DERIVE PARAMETERS.
40!
41! DECLARE VARIABLES.
42!
43 INTEGER,intent(in) :: LPBL(ista_2l:iend_2u,jsta_2l:jend_2u)
44 REAL,intent(in) :: ZPBL(ista_2l:iend_2u,jsta_2l:jend_2u)
45 REAL,intent(inout) :: GUST(ista_2l:iend_2u,jsta_2l:jend_2u)
46
47 integer I,J,IE,IW, L, K, ISTART, ISTOP, JSTART, JSTOP
48 integer LMIN,LXXX,IERR
49 real ZSFC,DELWIND,USFC,VSFC,SFCWIND,WIND,U0,V0,DZ
50!
51!
52!*****************************************************************************
54! START CALMXW HERE.
55!
56! LOOP OVER THE GRID.
57!
58!$omp parallel do private(i,j)
59 DO j=jsta,jend
60 DO i=ista,iend
61 gust(i,j) = spval
62 ENDDO
63 ENDDO
64
65 IF(gridtype == 'A') THEN
66 istart = ista
67 istop = iend
68 jstart = jsta
69 jstop = jend
70 ELSE
71 istart = ista_m
72 istop = iend_m
73 jstart = jsta_m
74 jstop = jend_m
75 if ( num_procs > 1 ) then
76 !CALL EXCH(U10(1,jsta_2l))
77 !CALL EXCH(V10(1,jsta_2l))
78 lmin = max(1, minval(lpbl(ista:iend,jsta:jend)))
79 CALL mpi_allreduce(lmin,lxxx,1,mpi_integer,mpi_min,mpi_comm_comp,ierr)
80 DO l=lxxx,lm
81 CALL exch(uh(ista_2l,jsta_2l,l))
82 CALL exch(vh(ista_2l,jsta_2l,l))
83 END DO
84 END IF
85 END IF
86!
87! ASSUME THAT U AND V HAVE UPDATED HALOS
88!
89!!$omp parallel do private(i,j,ie,iw,mxww,u0,v0,wind)
90 DO j=jstart,jstop
91 DO i=istart,istop
92 l=lpbl(i,j)
93 IF(gridtype == 'E') THEN
94 ie = i + mod(j+1,2)
95 iw = i + mod(j+1,2)-1
96
97 if(u10h(i,j)<spval.and.uh(i,j+1,l)<spval.and.uh(ie,j,l)<spval.and.uh(iw,j,l)<spval.and.uh(i,j-1,l)<spval) then
98
99! USFC=D25*(U10(I,J-1)+U10(IW,J)+U10(IE,J)+U10(I,J+1))
100! VSFC=D25*(V10(I,J-1)+V10(IW,J)+V10(IE,J)+V10(I,J+1))
101 usfc = u10h(i,j)
102 vsfc = v10h(i,j)
103 sfcwind = sqrt(usfc*usfc + vsfc*vsfc)
104 u0 = d25*(uh(i,j-1,l)+uh(iw,j,l)+uh(ie,j,l)+uh(i,j+1,l))
105 v0 = d25*(vh(i,j-1,l)+vh(iw,j,l)+vh(ie,j,l)+vh(i,j+1,l))
106 wind = sqrt(u0*u0 + v0*v0)
107
108 else
109 wind = spval
110 endif
111
112 ELSE IF(gridtype == 'B') THEN
113 ie = i
114 iw = i-1
115
116! USFC=D25*(U10(I,J-1)+U10(IW,J)+U10(IE,J)+U10(IW,J-1))
117! VSFC=D25*(V10(I,J-1)+V10(IW,J)+V10(IE,J)+V10(IW,J-1))
118
119 if(u10h(i,j)<spval.and.uh(iw,j-1,l)<spval) then
120
121 usfc = u10h(i,j)
122 vsfc = v10h(i,j)
123 sfcwind = sqrt(usfc*usfc + vsfc*vsfc)
124 u0 = d25*(uh(i,j-1,l)+uh(iw,j,l)+uh(ie,j,l)+uh(iw,j-1,l))
125 v0 = d25*(vh(i,j-1,l)+vh(iw,j,l)+vh(ie,j,l)+vh(iw,j-1,l))
126 wind = sqrt(u0*u0 + v0*v0)
127 else
128 wind = spval
129 endif
130 ELSE IF(gridtype == 'A') THEN
131
132 usfc = u10(i,j)
133 vsfc = v10(i,j)
134 if (usfc < spval .and. vsfc < spval) then
135 sfcwind = sqrt(usfc*usfc + vsfc*vsfc)
136 else
137 sfcwind = spval
138 endif
139 if(modelname == 'RAPR' .OR. modelname == 'GFS' .OR. modelname == 'FV3R') then
140 zsfc = zint(i,j,lm+1)
141 l = lpbl(i,j)
142! in RUC do 342 k=2,k1-1, where k1 - first level above PBLH
143 gust(i,j) = sfcwind
144 do k=lm-1,l-1,-1
145
146 if(uh(i,j,l)<spval) then
147 u0 = uh(i,j,k)
148 v0 = vh(i,j,k)
149 wind = sqrt(u0*u0 + v0*v0)
150 delwind = wind - sfcwind
151 dz = zmid(i,j,k)-zsfc
152 delwind = delwind*(1.0-min(0.5,dz/2000.))
153 gust(i,j) = max(gust(i,j),sfcwind+delwind)
154 else
155 gust(i,j) = spval
156 wind = spval
157 endif
158 enddo
159 else
160 if(uh(i,j,l)<spval) then
161 u0 = uh(i,j,l)
162 v0 = vh(i,j,l)
163 wind = sqrt(u0*u0 + v0*v0 )
164 else
165 wind = spval
166 endif
167 endif ! endif RAPR
168
169 ELSE
170! print*,'unknown grid type, not computing wind gust'
171 return
172 END IF
173
174 if(modelname /= 'RAPR' .AND. modelname /= 'GFS' .AND. modelname /= 'FV3R')then
175 if (sfcwind < spval .AND. zpbl(i,j) < spval ) then
176 delwind = wind - sfcwind
177 zsfc = fis(i,j)*gi
178 delwind = delwind*(1.0-min(0.5,zpbl(i,j)/2000.))
179 gust(i,j) = sfcwind + delwind
180 else
181 gust(i,j) = wind
182 endif
183 endif
184 enddo
185 enddo
186
187! END OF ROUTINE.
188!
189 RETURN
190 END
subroutine calgust(lpbl, zpbl, gust)
This routine computes surface wind gust by mixing down momentum from the level at the height of the P...
Definition CALGUST.f:25
subroutine exch(a)
exch() Subroutine that exchanges one halo row.
Definition EXCH.f:27