UPP  V11.0.0
 All Data Structures Files Functions Pages
CALWXT_BOURG.f
Go to the documentation of this file.
1 
53 
54  subroutine calwxt_bourg_post(im,ista_2l,iend_2u,ista,iend,jm,jsta_2l,jend_2u,jsta,jend,lm,lp1, &
55  & iseed,g,pthresh, &
56  & t,q,pmid,pint,lmh,prec,zint,ptype,me)
57  implicit none
58 !
59 ! input:
60  integer,intent(in):: im,jm,jsta_2l,jend_2u,jsta,jend,lm,lp1,iseed,me,&
61  ista_2l,iend_2u,ista,iend
62  real,intent(in):: g,pthresh
63  real,intent(in), dimension(ista_2l:iend_2u,jsta_2l:jend_2u,lm) :: t, q, pmid
64  real,intent(in), dimension(ista_2l:iend_2u,jsta_2l:jend_2u,lp1) :: pint, zint
65  real,intent(in), dimension(ista_2l:iend_2u,jsta_2l:jend_2u) :: lmh, prec
66 !
67 ! output:
68 ! real,intent(out) :: ptype(im,jm)
69  integer,intent(out) :: ptype(ista:iend,jsta:jend)
70 !
71  integer i,j,ifrzl,iwrml,l,lhiwrm,lmhk,jlen
72  real pintk1,areane,tlmhk,areape,pintk2,surfw,area1,dzkl,psfck,r1,r2
73  real rn(im*jm*2)
74  integer :: rn_seed_size
75  integer, allocatable, dimension(:) :: rn_seed
76  logical, parameter :: debugprint = .false.
77 !
78 ! initialize weather type array to zero (ie, off).
79 ! we do this since we want ptype to represent the
80 ! instantaneous weather type on return.
81  if (debugprint) then
82  print *,'in calwxtbg, jsta,jend=',jsta,jend,' im=',im
83  print *,'in calwxtbg,me=',me,'iseed=',iseed
84  endif
85 !
86 !$omp parallel do
87  do j=jsta,jend
88  do i=ista,iend
89  ptype(i,j) = 0
90  enddo
91  enddo
92 !
93  jlen = jend - jsta + 1
94 
95  call random_seed(size = rn_seed_size)
96  allocate(rn_seed(rn_seed_size))
97  rn_seed = iseed
98  call random_seed(put = rn_seed)
99  call random_number(rn)
100 !
101 !!$omp parallel do &
102 ! & private(a,lmhk,tlmhk,iwrml,psfck,lhiwrm,pintk1,pintk2,area1, &
103 ! & areape,dzkl,surfw,r1,r2)
104 ! print *,'incalwxtbg, rn',maxval(rn),minval(rn)
105 
106  do j=jsta,jend
107 ! if(me==1)print *,'incalwxtbg, j=',j
108  do i=ista,iend
109  lmhk = min(nint(lmh(i,j)),lm)
110  psfck = pint(i,j,lmhk+1)
111 !
112  if (prec(i,j) <= pthresh) cycle ! skip this point if no precip this time step
113 
114 ! find the depth of the warm layer based at the surface
115 ! this will be the cut off point between computing
116 ! the surface based warm air and the warm air aloft
117 !
118  tlmhk = t(i,j,lmhk) ! lowest layer t
119  iwrml = lmhk + 1
120  if (tlmhk >= 273.15) then
121  do l = lmhk, 2, -1
122  if (t(i,j,l) >= 273.15 .and. t(i,j,l-1) < 273.15 .and. &
123  & iwrml == lmhk+1) iwrml = l
124  end do
125  end if
126 !
127 ! now find the highest above freezing level
128 !
129 ! gsm added 250 mb check to prevent stratospheric warming situations
130 ! from counting as warm layers aloft
131  lhiwrm = lmhk + 1
132  do l = lmhk, 1, -1
133  if (t(i,j,l) >= 273.15 .and. pmid(i,j,l) > 25000.) lhiwrm = l
134  end do
135 
136 ! energy variables
137 
138 ! surfw is the positive energy between ground and the first sub-freezing layer above ground
139 ! areane is the negative energy between ground and the highest layer above ground
140 ! that is above freezing
141 ! areape is the positive energy "aloft" which is the warm energy not based at the ground
142 ! (the total warm energy = surfw + areape)
143 !
144 ! pintk1 is the pressure at the bottom of the layer
145 ! pintk2 is the pressure at the top of the layer
146 ! dzkl is the thickness of the layer
147 ! ifrzl is a flag that tells us if we have hit a below freezing layer
148 !
149  pintk1 = psfck
150  ifrzl = 0
151  areane = 0.0
152  areape = 0.0
153  surfw = 0.0
154 
155  do l = lmhk, 1, -1
156  if (ifrzl == 0.and.t(i,j,l) <= 273.15) ifrzl = 1
157  pintk2 = pint(i,j,l)
158  dzkl = zint(i,j,l)-zint(i,j,l+1)
159  area1 = log(t(i,j,l)/273.15) * g * dzkl
160  if (t(i,j,l) >= 273.15.and. pmid(i,j,l) > 25000.) then
161  if (l < iwrml) areape = areape + area1
162  if (l >= iwrml) surfw = surfw + area1
163  else
164  if (l > lhiwrm) areane = areane + abs(area1)
165  end if
166  pintk1 = pintk2
167  end do
168 !
169 ! decision tree time
170 !
171  if (areape < 2.0) then
172 ! very little or no positive energy aloft, check for
173 ! positive energy just above the surface to determine rain vs. snow
174  if (surfw < 5.6) then
175 ! not enough positive energy just above the surface
176 ! snow = 1
177  ptype(i,j) = 1
178  else if (surfw > 13.2) then
179 ! enough positive energy just above the surface
180 ! rain = 8
181  ptype(i,j) = 8
182  else
183 ! transition zone, assume equally likely rain/snow
184 ! picking a random number, if <=0.5 snow
185  r1 = rn(i+im*(j-1))
186  if (r1 <= 0.5) then
187  ptype(i,j) = 1 ! snow = 1
188  else
189  ptype(i,j) = 8 ! rain = 8
190  end if
191  end if
192 !
193  else
194 ! some positive energy aloft, check for enough negative energy
195 ! to freeze and make ice pellets to determine ip vs. zr
196  if (areane > 66.0+0.66*areape) then
197 ! enough negative area to make ip,
198 ! now need to check if there is enough positive energy
199 ! just above the surface to melt ip to make rain
200  if (surfw < 5.6) then
201 ! not enough energy at the surface to melt ip
202  ptype(i,j) = 2 ! ice pellets = 2
203  else if (surfw > 13.2) then
204 ! enough energy at the surface to melt ip
205  ptype(i,j) = 8 ! rain = 8
206  else
207 ! transition zone, assume equally likely ip/rain
208 ! picking a random number, if <=0.5 ip
209  r1 = rn(i+im*(j-1))
210  if (r1 <= 0.5) then
211  ptype(i,j) = 2 ! ice pellets = 2
212  else
213  ptype(i,j) = 8 ! rain = 8
214  end if
215  end if
216  else if (areane < 46.0+0.66*areape) then
217 ! not enough negative energy to refreeze, check surface temp
218 ! to determine rain vs. zr
219  if (tlmhk < 273.15) then
220  ptype(i,j) = 4 ! freezing rain = 4
221  else
222  ptype(i,j) = 8 ! rain = 8
223  end if
224  else
225 ! transition zone, assume equally likely ip/zr
226 ! picking a random number, if <=0.5 ip
227  r1 = rn(i+im*(j-1))
228  if (r1 <= 0.5) then
229 ! still need to check positive energy
230 ! just above the surface to melt ip vs. rain
231  if (surfw < 5.6) then
232  ptype(i,j) = 2 ! ice pellets = 2
233  else if (surfw > 13.2) then
234  ptype(i,j) = 8 ! rain = 8
235  else
236 ! transition zone, assume equally likely ip/rain
237 ! picking a random number, if <=0.5 ip
238  r2 = rn(i+im*(j-1)+im*jm)
239  if (r2 <= 0.5) then
240  ptype(i,j) = 2 ! ice pellets = 2
241  else
242  ptype(i,j) = 8 ! rain = 8
243  end if
244  end if
245  else
246 ! not enough negative energy to refreeze, check surface temp
247 ! to determine rain vs. zr
248  if (tlmhk < 273.15) then
249  ptype(i,j) = 4 ! freezing rain = 4
250  else
251  ptype(i,j) = 8 ! rain = 8
252  end if
253  end if
254  end if
255  end if
256 ! write(1000+me,*)' finished for i, j, from calbourge me=',me,i,j
257  end do
258 ! write(1000+me,*)' finished for j, from calbourge me=',me,j
259  end do
260 ! write(1000+me,*)' returning from calbourge me=',me
261  return
262  end