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