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