1module obsVariableTransforms_mod
2 ! MODULE obsVariableTransforms_mod (prefix='ovt' category='4. Data Object transformations')
3 !
4 !:Purpose: To store various functions for variable transforms using inputs
5 ! from obsSpaceData. Outputs are also placed ObsSpaceData.
6 !
7
8 use obsSpaceData_mod
9 use bufr_mod
10 use codePrecision_mod
11 use mathPhysConstants_mod
12 use earthConstants_mod
13 use codtyp_mod
14 use utilities_mod
15 use obsFilter_mod
16
17 implicit none
18 save
19 private
20
21 public :: ovt_setup, ovt_transformObsValues, ovt_transformResiduals
22 public :: ovt_getDestinationBufrCode, ovt_getSourceBufrCode, ovt_bufrCodeSkipped
23 public :: ovt_isWindObs, ovt_isTransformedVariable, ovt_adjustHumGZ
24
25 integer, parameter :: nTransformSupported = 3
26
27 type :: struct_transform
28 character(len=48) :: name
29 integer :: nBufrCode
30 integer, allocatable :: sourceBufrCode (:)
31 integer, allocatable :: sourceBufrCodeExtra (:)
32 integer, allocatable :: destinationBufrCode (:)
33 integer, allocatable :: destinationBufrCodeExtra(:)
34 logical :: wind = .false.
35 logical :: active = .false.
36 end type struct_transform
37
38 type(struct_transform) :: transform(nTransformSupported)
39
40 integer :: nSkippedBufrCodes = 0
41 integer :: skippedBufrCodes(50) = -999
42
43 logical :: initialized = .false.
44
45contains
46
47 !--------------------------------------------------------------------------
48 ! ovt_initStructure
49 !--------------------------------------------------------------------------
50 subroutine ovt_initStructure
51 !
52 !:Purpose: To set the transforms handled by this module
53 !
54 implicit none
55
56 ! Locals:
57 integer :: transformIndex
58
59 ! Upper and surface winds
60 transformIndex = 1
61 transform(transformIndex)%name = 'windSpeedDirectionToUV'
62 transform(transformIndex)%nBufrCode = 2
63 allocate(transform(transformIndex)%sourceBufrCode (transform(transformIndex)%nBufrCode))
64 allocate(transform(transformIndex)%sourceBufrCodeExtra (transform(transformIndex)%nBufrCode))
65 allocate(transform(transformIndex)%destinationBufrCode (transform(transformIndex)%nBufrCode))
66 allocate(transform(transformIndex)%destinationBufrCodeExtra(transform(transformIndex)%nBufrCode))
67 transform(transformIndex)%sourceBufrCode (:) = (/bufr_nedd, bufr_neds/) ! direction
68 transform(transformIndex)%sourceBufrCodeExtra (:) = (/bufr_neff, bufr_nefs/) ! speed
69 transform(transformIndex)%destinationBufrCode (:) = (/bufr_neuu, bufr_neus/) ! u-wind
70 transform(transformIndex)%destinationBufrCodeExtra(:) = (/bufr_nevv, bufr_nevs/) ! v-wind
71 transform(transformIndex)%wind = .true.
72
73 ! log of visibility
74 transformIndex = 2
75 transform(transformIndex)%name = 'visToLogVis'
76 transform(transformIndex)%nBufrCode = 1
77 allocate(transform(transformIndex)%sourceBufrCode (transform(transformIndex)%nBufrCode))
78 allocate(transform(transformIndex)%destinationBufrCode(transform(transformIndex)%nBufrCode))
79 transform(transformIndex)%sourceBufrCode (:) = (/bufr_vis /) ! visibility
80 transform(transformIndex)%destinationBufrCode(:) = (/bufr_logVis/) ! log(visibility)
81 transform(transformIndex)%wind = .false.
82
83 ! log of precipitation rate
84 transformIndex = 3
85 transform(transformIndex)%name = 'precipToLogPrecip'
86 transform(transformIndex)%nBufrCode = 1
87 allocate(transform(transformIndex)%sourceBufrCode (transform(transformIndex)%nBufrCode))
88 allocate(transform(transformIndex)%destinationBufrCode(transform(transformIndex)%nBufrCode))
89 transform(transformIndex)%sourceBufrCode (:) = (/bufr_radarPrecip /) ! precipitation
90 transform(transformIndex)%destinationBufrCode(:) = (/bufr_logRadarPrecip/) ! log(precipitation)
91 transform(transformIndex)%wind = .false.
92
93 ! Skipped variables
94 nSkippedBufrCodes = 2
95 skippedBufrCodes(1) = bufr_neff ! because we still want to be able ...
96 skippedBufrCodes(2) = bufr_nefs ! ... to assimilate wind speed obs alone
97
98 end subroutine ovt_initStructure
99
100 !--------------------------------------------------------------------------
101 ! ovt_setup
102 !--------------------------------------------------------------------------
103 subroutine ovt_setup(bufrCodeRead)
104 !
105 !:Purpose: To determine which transform must be actived
106 !
107 implicit none
108
109 ! Arguments:
110 integer, intent(in) :: bufrCodeRead(:) ! The list of bufr code read
111
112 ! Locals:
113 integer, allocatable :: bufrCodeAssimilated(:) ! The list of bufr code assimilated
114 integer :: nBufrCodeRead, nBufrCodeAssimilated
115 integer :: readBufrCodeIndex, transformIndex, assimBufrCodeIndex
116 logical :: variableTransformNeeded, foundTransformation
117 logical, save :: firstTime = .true.
118
119 if (firstTime) then
120 call ovt_initStructure
121 firstTime = .false.
122 end if
123
124 nBufrCodeAssimilated = filt_nBufrCodeAssimilated()
125 nBufrCodeRead = size(bufrCodeRead)
126 variableTransformNeeded = .false.
127
128 allocate(bufrCodeAssimilated(nBufrCodeAssimilated))
129 call filt_getBufrCodeAssimilated(bufrCodeAssimilated)
130
131 do readBufrCodeIndex = 1, nBufrCodeRead
132
133 ! Check if a transform is neeeded
134 if (filt_bufrCodeAssimilated(bufrCodeRead(readBufrCodeIndex)) .or. &
135 bufrCodeRead(readBufrCodeIndex) == bufr_neff .or. &
136 bufrCodeRead(readBufrCodeIndex) == bufr_nefs ) then
137 cycle ! No transformation needed. Move on.
138 ! Note that this is where we decide that wind speed will be ignored,
139 ! because we do all the appropriate wind manipulations when we encounter direction.
140 ! This strategy allow to assimilate lonely speed observations, like SAR winds.
141 end if
142
143 ! Find and activate the appropriate transform
144 foundTransformation = .false.
145
146 transformLoop : do transformIndex = 1, nTransformSupported
147 assimBufrCodeLoop : do assimBufrCodeIndex = 1, nBufrCodeAssimilated
148 if (any(transform(transformIndex)%sourceBufrCode(:) == bufrCodeRead(readBufrCodeIndex)) .and. &
149 any(transform(transformIndex)%destinationBufrCode(:) == bufrCodeAssimilated(assimBufrCodeIndex)) ) then
150 if (.not. transform(transformIndex)%active) then
151 write(*,*) 'ovt_setup: transform activated : ', trim(transform(transformIndex)%name)
152 transform(transformIndex)%active = .true.
153 end if
154 foundTransformation = .true.
155 exit transformLoop
156 end if
157 end do assimBufrCodeLoop
158 end do transformLoop
159
160 if (.not. foundTransformation) then
161 if ( .not. any( skippedBufrCodes(:) == bufrCodeRead(readBufrCodeIndex) ) ) then
162 write(*,*)
163 write(*,*) 'ovt_setup: !WARNING! No transform found for the read bufr code = ', bufrCodeRead(readBufrCodeIndex)
164 write(*,*) ' We are assuming that this observation is read but not assimilated.'
165 write(*,*) ' Please consider removing this bufr code from the read observation list'
166 write(*,*) ' unless the bufr element is read for another purpose.'
167 nSkippedBufrCodes = nSkippedBufrCodes + 1
168 skippedBufrCodes(nSkippedBufrCodes) = bufrCodeRead(readBufrCodeIndex)
169 end if
170 end if
171
172 end do
173
174 initialized = .true.
175
176 deallocate(bufrCodeAssimilated)
177
178 end subroutine ovt_setup
179
180 !--------------------------------------------------------------------------
181 ! ovt_bufrCodeSkipped
182 !--------------------------------------------------------------------------
183 function ovt_bufrCodeSkipped(sourceBufrCode) result(skip)
184 !
185 !:Purpose: To NEVER activate a variable transform for this bufr code,
186 ! even when this bufr_code is read but not found in the assimilated list.
187 ! So far, this function is only used to "skipped" wind speed reports
188 ! because we do all the appropriate wind manipulations when we encounter direction.
189 !
190 implicit none
191
192 ! Arguments:
193 integer, intent(in) :: sourceBufrCode ! The input bufr code
194 ! Result:
195 logical :: skip ! The decision
196
197 ! Locals:
198 integer :: bufrCodeIndex
199
200 if (.not. initialized) then
201 call utl_abort(' ovt_bufrCodeSkipped: this module has not been setup')
202 end if
203
204 skip = .false.
205 do bufrCodeIndex = 1, nSkippedBufrCodes
206 if (skippedBufrCodes(bufrCodeIndex) == sourceBufrCode) then
207 skip = .true.
208 exit
209 end if
210 end do
211
212 end function ovt_bufrCodeSkipped
213
214 !--------------------------------------------------------------------------
215 ! ovt_getDestinationBufrCode
216 !--------------------------------------------------------------------------
217 function ovt_getDestinationBufrCode(sourceBufrCode,extra_opt) result(destinationBufrCode)
218 !
219 !:Purpose: To get the bufr code of the transformed/destination variable based on the
220 ! bufr code of the source variable
221 !
222 implicit none
223
224 ! Arguments:
225 integer, intent(in) :: sourceBufrCode ! The input source bufr code
226 logical, optional, intent(in) :: extra_opt ! Should we look in the "extra" bufr code list or not
227 ! Result:
228 integer :: destinationBufrCode ! The returned destination/transform bufr code
229
230 ! Locals:
231 logical :: extra
232 integer :: transformIndex, bufrCodeIndex
233
234 if (.not. initialized) then
235 call utl_abort(' ovt_getDestinationBufrCode: this module has not been setup')
236 end if
237
238 if (present(extra_opt)) then
239 extra = extra_opt
240 else
241 extra = .false. ! default
242 end if
243
244 destinationBufrCode = -1
245
246 transformLoop : do transformIndex = 1, nTransformSupported
247 bufrCodeLoop : do bufrCodeIndex = 1, transform(transformIndex)%nBufrCode
248 if (transform(transformIndex)%sourceBufrCode(bufrCodeIndex) == sourceBufrCode) then
249 if (extra) then
250 destinationBufrCode = transform(transformIndex)%destinationBufrCodeExtra(bufrCodeIndex)
251 else
252 destinationBufrCode = transform(transformIndex)%destinationBufrCode(bufrCodeIndex)
253 end if
254 exit transformLoop
255 end if
256 end do bufrCodeLoop
257 end do transformLoop
258
259 if (destinationBufrCode == -1) then
260 write(*,*)
261 write(*,*) 'ovt_getDestinationBufrCode: source bufrCode = ', sourceBufrCode
262 call utl_abort('ovt_getDestinationBufrCode: found no associated bufrCode for the above source variable bufr code')
263 end if
264
265 end function ovt_getDestinationBufrCode
266
267 !--------------------------------------------------------------------------
268 ! ovt_getSourceBufrCode
269 !--------------------------------------------------------------------------
270 function ovt_getSourceBufrCode(destinationBufrCode,extra_opt) result(sourceBufrCode)
271 !
272 !:Purpose: To get the bufr code of the source variable based on the
273 ! bufr code of the destination/transformed variable
274 !
275 implicit none
276
277 ! Arguments:
278 integer, intent(in) :: destinationBufrCode ! The input destination/transform bufr code
279 logical, optional, intent(in) :: extra_opt ! Should we look in the "extra" bufr code list or not
280 ! Result:
281 integer :: sourceBufrCode ! The returned source bufr code
282
283 ! Locals:
284 logical :: extra
285 integer :: transformIndex, destinationBufrCodeIndex
286
287 if (.not. initialized) then
288 call utl_abort(' ovt_getSourceBufrCode: this module has not been setup')
289 end if
290
291 if (present(extra_opt)) then
292 extra = extra_opt
293 else
294 extra = .false. ! default
295 end if
296
297 sourceBufrCode = -1
298
299 transformLoop : do transformIndex = 1, nTransformSupported
300 destinationBufrCodeLoop : do destinationBufrCodeIndex = 1, transform(transformIndex)%nBufrCode
301 if (transform(transformIndex)%destinationBufrCode(destinationBufrCodeIndex) == destinationBufrCode) then
302 if (extra) then
303 sourceBufrCode = transform(transformIndex)%sourceBufrCodeExtra(destinationBufrCodeIndex)
304 else
305 sourceBufrCode = transform(transformIndex)%sourceBufrCode(destinationBufrCodeIndex)
306 end if
307 exit transformLoop
308 end if
309 end do destinationBufrCodeLoop
310 end do transformLoop
311
312 if (sourceBufrCode == -1) then
313 write(*,*)
314 write(*,*) 'ovt_getSourceBufrCode: tranform variable bufr code = ', destinationBufrCode
315 call utl_abort('ovt_getSourceBufrCode: found no associated variable bufr code for the above transform variable bufr code')
316 end if
317
318 end function ovt_getSourceBufrCode
319
320 !--------------------------------------------------------------------------
321 ! ovt_isWindObs
322 !--------------------------------------------------------------------------
323 function ovt_isWindObs(sourceBufrCode) result(wind)
324 !
325 !:Purpose: To determine if a bufr code is wind related
326 !
327 implicit none
328
329 ! Arguments:
330 integer, intent(in) :: sourceBufrCode ! The input source bufr code
331 ! Result:
332 logical :: wind ! Is this bufr code linked to wind or not
333
334 ! Locals:
335 integer :: transformIndex, bufrCodeIndex
336
337 if (.not. initialized) then
338 call utl_abort(' ovt_isWindObs: this module has not been setup')
339 end if
340
341 transformLoop : do transformIndex = 1, nTransformSupported
342 bufrCodeLoop : do bufrCodeIndex = 1, transform(transformIndex)%nBufrCode
343 if (transform(transformIndex)%sourceBufrCode(bufrCodeIndex) == sourceBufrCode) then
344 wind = transform(transformIndex)%wind
345 exit transformLoop
346 end if
347 end do bufrCodeLoop
348 end do transformLoop
349
350 end function ovt_isWindObs
351
352 !--------------------------------------------------------------------------
353 ! ovt_isTransformedVariable
354 !--------------------------------------------------------------------------
355 function ovt_isTransformedVariable(bufrCode) result(transformed)
356 !
357 !:Purpose: To determine if a bufr code is a transfomed variabled
358 !
359 implicit none
360
361 ! Arguments:
362 integer, intent(in) :: bufrCode ! The input bufr code
363 ! Result:
364 logical :: transformed ! Is this a bufr code associated to a transform variable or not
365
366 ! Locals:
367 integer :: transformIndex, bufrCodeIndex
368
369 if (.not. initialized) then
370 call utl_abort(' ovt_isTransformedVariable: this module has not been setup')
371 end if
372
373 transformed = .false.
374
375 transformLoop : do transformIndex = 1, nTransformSupported
376 if (transform(transformIndex)%active) then
377 bufrCodeLoop : do bufrCodeIndex = 1, transform(transformIndex)%nBufrCode
378 if (transform(transformIndex)%destinationBufrCode(bufrCodeIndex) == bufrCode) then
379 transformed = .true.
380 exit transformLoop
381 end if
382 end do bufrCodeLoop
383 end if
384 end do transformLoop
385
386 end function ovt_isTransformedVariable
387
388 !--------------------------------------------------------------------------
389 ! ovt_transformObsValues
390 !--------------------------------------------------------------------------
391 subroutine ovt_transformObsValues(obsSpaceData, headerIndexStart, headerIndexEnd)
392 !
393 !:Purpose: To perform observation variable transforms
394 !
395 implicit none
396
397 ! Arguments:
398 type (struct_obs), intent(inout) :: obsSpaceData ! The observation database
399 integer , intent(in) :: headerIndexStart ! The initial header index to analyse
400 integer , intent(in) :: headerIndexEnd ! The final header index to analyse
401
402 ! Locals:
403 integer :: transformIndex
404
405 if (obs_numHeader(obsSpaceData) == 0) return
406
407 if (.not. initialized) then
408 call utl_abort('ovt_transformObsValues: this module has not been setup')
409 end if
410
411 do transformIndex = 1, nTransformSupported
412
413 if (transform(transformIndex)%active) then
414 select case(trim(transform(transformIndex)%name))
415 case ('windSpeedDirectionToUV')
416 call ovt_windSpeedDirectionToUV(obsSpaceData, headerIndexStart, headerIndexEnd)
417 case ('visToLogVis')
418 call ovt_visToLogVis (obsSpaceData, headerIndexStart, headerIndexEnd)
419 case ('precipToLogPrecip')
420 call ovt_precipToLogPrecip (obsSpaceData, headerIndexStart, headerIndexEnd)
421 case default
422 call utl_abort('ovt_transformObsValues: Unsupported function ' // trim(transform(transformIndex)%name))
423 end select
424 end if
425
426 end do
427
428 end subroutine ovt_transformObsValues
429
430 !--------------------------------------------------------------------------
431 ! ovt_TransformResiduals
432 !--------------------------------------------------------------------------
433 subroutine ovt_transformResiduals(obsSpaceData, residualTypeID)
434 !
435 !:Purpose: To compute the o-p or o-a of the source variable(s)
436 !
437 implicit none
438
439 ! Arguments:
440 type (struct_obs), intent(inout) :: obsSpaceData ! The observation database
441 integer , intent(in) :: residualTypeID ! The residual type ID (o-p or o-a)
442
443 ! Local:
444 integer :: transformIndex
445
446 if (obs_numHeader(obsSpaceData) == 0) return
447
448 if (.not. initialized) then
449 call utl_abort('ovt_transformResiduals: this module has not been setup')
450 end if
451
452 do transformIndex = 1, nTransformSupported
453
454 if (transform(transformIndex)%active) then
455 select case(trim(transform(transformIndex)%name))
456 case ('windSpeedDirectionToUV')
457 call ovt_UVtoWindSpeedDirection_residual(obsSpaceData, residualTypeID)
458 case ('visToLogVis')
459 call ovt_visToLogVis_residual (obsSpaceData, residualTypeID)
460 case ('precipToLogPrecip')
461 call ovt_precipToLogPrecip_residual (obsSpaceData, residualTypeID)
462 case default
463 call utl_abort('ovt_transformResiduals: Unsupported function ' // trim(transform(transformIndex)%name))
464 end select
465 end if
466
467 end do
468
469 end subroutine ovt_transformResiduals
470
471 !--------------------------------------------------------------------------
472 ! ovt_windSpeedDirectionToUV
473 !--------------------------------------------------------------------------
474 subroutine ovt_windSpeedDirectionToUV(obsSpaceData, headerIndexStart, headerIndexEnd)
475 !
476 !:Purpose: To transform wind observation in terms of speed and direction to u and v
477 !
478 implicit none
479
480 ! Arguments:
481 type (struct_obs), intent(inout) :: obsSpaceData ! The observation database
482 integer , intent(in) :: headerIndexStart ! The initial header index to analyse
483 integer , intent(in) :: headerIndexEnd ! The final header index to analyse
484
485 ! Locals:
486 integer :: bufrCode, bufrCode2, bufrCode3
487 integer :: headerIndex, bodyIndex, bodyIndexStart, bodyIndexEnd, bodyIndex2, bufrCodeAssociated
488 integer :: directionFlag, speedFlag, combinedFlag, uWindFlag, vWindFlag
489 integer :: speedBufrCode, uWindBufrCode, vWindBufrCode, uWindbodyIndex, vWindBodyIndex
490 logical :: direction_missing, speed_missing
491 logical :: uWind_present, vWind_present
492 real(pre_obsReal) :: uWind, vWind, direction, speed
493 real(pre_obsReal) :: level_direction, level, level2, level3
494
495 speedFlag = 0
496
497 ! Loop through headers
498 header: do headerIndex = headerIndexStart, headerIndexEnd
499
500 bodyIndexStart = obs_headElem_i(obsSpaceData, OBS_RLN, headerIndex )
501 bodyIndexEnd = obs_headElem_i(obsSpaceData, OBS_NLV, headerIndex ) + bodyIndexStart - 1
502
503 ! Find the wind direction report
504 body: do bodyIndex = bodyIndexStart, bodyIndexEnd
505
506 direction = obs_missingValue_R
507 speed = obs_missingValue_R
508 bufrCode = obs_bodyElem_i(obsSpaceData, OBS_VNM, bodyIndex)
509 direction_missing = .true.
510
511 if ( bufrCode /= bufr_nedd .and. bufrCode /= bufr_neds ) cycle body
512
513 if( bufrCode == bufr_neds) then
514 ! Surface obs
515 speedBufrCode = bufr_nefs
516 uWindBufrCode = bufr_neus
517 vWindBufrCode = bufr_nevs
518 else
519 ! Upper air obs
520 speedBufrCode = bufr_neff
521 uWindBufrCode = bufr_neuu
522 vWindBufrCode = bufr_nevv
523 end if
524
525 direction = obs_bodyElem_r(obsSpaceData, OBS_VAR, bodyIndex )
526 directionFlag = obs_bodyElem_i(obsSpaceData, OBS_FLG, bodyIndex )
527 level_direction = obs_bodyElem_r(obsSpaceData, OBS_PPP, bodyIndex )
528 uWind_present = .false.
529 vWind_present = .false.
530
531 ! Check if u and v are present in obsSpaceData
532 do bodyIndex2 = bodyIndexStart, bodyIndexEnd
533
534 level3 = obs_bodyElem_r(obsSpaceData, OBS_PPP, bodyIndex2 )
535
536 if (level3 == level_direction) then
537 bufrCode3 = obs_bodyElem_i(obsSpaceData, OBS_VNM, bodyIndex2 )
538
539 if ( bufrCode3 == uWindBufrCode ) then
540 uWind_present = .true.
541 uWindbodyIndex = bodyIndex2
542 else if ( bufrCode3 == vWindBufrCode) then
543 vWind_present = .true.
544 vWindBodyIndex = bodyIndex2
545 end if
546
547 end if
548
549 end do
550
551 if (.not. uWind_present .or. .not. vWind_present) then
552 call utl_abort('ovt_windSpeedDirectionToUV: uWind and/or vWind bodyIndex not found!')
553 end if
554
555 ! Find the speed report and compute uWind and vWind
556 calcuv: do bodyIndex2 = bodyIndexStart, bodyIndexEnd
557 speed_missing = .true.
558 direction_missing = .true.
559 level = obs_bodyElem_r(obsSpaceData, OBS_PPP, bodyIndex2 )
560
561 if ( level /= level_direction) cycle calcuv
562
563 bufrCode2 = obs_bodyElem_i(obsSpaceData, OBS_VNM, bodyIndex2 )
564
565 if ( bufrCode2 == speedBufrCode ) then
566
567 speed = obs_bodyElem_r(obsSpaceData, OBS_VAR, bodyIndex2 )
568 speedFlag = obs_bodyElem_i(obsSpaceData, OBS_FLG, bodyIndex2 )
569
570 if ( direction == 0.d0 .and. speed > 0. .or. direction > 360. .or. direction < 0. ) then
571 direction_missing = .true.
572 speed_missing = .true.
573 else if ( direction == obs_missingValue_R .or. speed == obs_missingValue_R ) then
574 direction_missing = .true.
575 speed_missing = .true.
576 else
577 direction_missing = .false.
578 speed_missing = .false.
579 end if
580
581 if ( direction_missing .or. speed_missing ) then
582
583 call obs_bodySet_i(obsSpaceData, OBS_VNM, uWindbodyIndex, -1 )
584 call obs_bodySet_i(obsSpaceData, OBS_VNM, vWindBodyIndex, -1 )
585
586 else
587
588 if (speed == 0.d0) direction = 0.d0
589 direction = direction + 180.
590 if ( direction > 360.) direction = direction - 360.
591 direction = direction * mpc_radians_per_degree_r8
592
593 ! (speed,direction) -> (u,v)
594 uWind = speed * sin(direction)
595 vWind = speed * cos(direction)
596
597 combinedFlag = ior(directionFlag, speedFlag )
598
599 call obs_bodySet_r(obsSpaceData, OBS_VAR, uWindbodyIndex, uWind )
600 call obs_bodySet_i(obsSpaceData, OBS_FLG, uWindbodyIndex, combinedFlag )
601 call obs_bodySet_r(obsSpaceData, OBS_VAR, vWindBodyIndex, vWind )
602 call obs_bodySet_i(obsSpaceData, OBS_FLG, vWindBodyIndex, combinedFlag )
603
604 end if
605
606 end if
607
608 end do calcuv
609
610 end do body
611
612 end do header
613
614 !
615 !- Merge uWind and vWind flags (JFC: not sure why this is needed because this was already done above)
616 !
617 header2: do headerIndex = headerIndexStart, headerIndexEnd
618
619 bodyIndexStart = obs_headElem_i(obsSpaceData, OBS_RLN, headerIndex)
620 bodyIndexEnd = obs_headElem_i(obsSpaceData, OBS_NLV, headerIndex) + bodyIndexStart - 1
621
622 ! Search uWind component
623 body2: do bodyIndex = bodyIndexStart, bodyIndexEnd
624 bufrCode = obs_bodyElem_i(obsSpaceData, OBS_VNM, bodyIndex)
625 level = obs_bodyElem_r(obsSpaceData, OBS_PPP, bodyIndex)
626
627 select case (bufrCode)
628 case (bufr_neuu)
629 bufrCodeAssociated = bufr_nevv
630 case (bufr_neus)
631 bufrCodeAssociated = bufr_nevs
632 case default
633 cycle body2
634 end select
635
636 uWindbodyIndex = bodyIndex
637
638 ! Eleminate entries where uWind is missing
639 uWind = obs_bodyElem_r(obsSpaceData, OBS_VAR, uWindbodyIndex)
640 if ( uWind == obs_missingValue_R ) then
641 call obs_bodySet_i(obsSpaceData, OBS_VNM, uWindbodyIndex, -1)
642 end if
643
644 ! Search the associated vWind component
645 vWindBodyIndex = -1
646 body3: do bodyIndex2 = bodyIndexStart, bodyIndexEnd
647 bufrCode2 = obs_bodyElem_i(obsSpaceData, OBS_VNM, bodyIndex2)
648 level2 = obs_bodyElem_r(obsSpaceData, OBS_PPP, bodyIndex2)
649
650 if ( bufrCode2 /= bufrCodeAssociated .or. level2 /= level ) cycle
651
652 vWindBodyIndex = bodyIndex2
653
654 if ( uWind == obs_missingValue_R ) then
655 call obs_bodySet_i(obsSpaceData, OBS_VNM, vWindBodyIndex, -1)
656 else
657 uWindFlag = obs_bodyElem_i(obsSpaceData, OBS_FLG, uWindbodyIndex)
658 vWindFlag = obs_bodyElem_i(obsSpaceData, OBS_FLG, vWindBodyIndex)
659 combinedFlag = ior( uWindFlag, vWindFlag )
660 call obs_bodySet_i(obsSpaceData, OBS_FLG, uWindbodyIndex, combinedFlag)
661 call obs_bodySet_i(obsSpaceData, OBS_FLG, vWindBodyIndex, combinedFlag)
662 end if
663
664 exit body3
665
666 end do body3
667
668 ! Eleminate entries where vWind is missing
669 if (vWindBodyIndex < 0 .and. uWind /= obs_missingValue_R) then
670 call obs_bodySet_i(obsSpaceData, OBS_VNM, uWindbodyIndex, -1)
671 end if
672
673 end do body2
674
675 end do header2
676
677 end subroutine ovt_windSpeedDirectionToUV
678
679 !--------------------------------------------------------------------------
680 ! ovt_UVtoWindSpeedDirection_residual
681 !--------------------------------------------------------------------------
682 subroutine ovt_UVtoWindSpeedDirection_residual(obsSpaceData, residualTypeID)
683 !
684 !:Purpose: To transform wind residuals in terms of u and v to speed and direction
685 !
686 implicit none
687
688 ! Arguments:
689 type(struct_obs), intent(inout) :: obsSpaceData ! The observation database
690 integer, intent(in) :: residualTypeID ! The residual type ID (o-p or o-a)
691
692 ! Locals:
693 integer :: uWindBufrCode, vWindBufrCode, speedBufrCode, directionBufrCode
694 integer :: headerIndex, headerIndexStart, headerIndexEnd, windTypeIndex, bodyIndex, bodyIndex2
695 real(pre_obsReal) :: uWindLevel, speed, direction, uWind, vWind
696
697 windType: do windTypeIndex = 1, 2
698 if (windTypeIndex == 1) then
699 uWindBufrCode = bufr_neuu
700 vWindBufrCode = bufr_nevv
701 directionBufrCode = bufr_nedd
702 speedBufrCode = bufr_neff
703 else
704 uWindBufrCode = bufr_neus
705 vWindBufrCode = bufr_nevs
706 directionBufrCode = bufr_neds
707 speedBufrCode = bufr_nefs
708 end if
709
710 ! Process all data within the domain of the model
711 body: do bodyIndex = 1, obs_numBody(obsSpaceData)
712
713 if ( obs_bodyElem_i(obsSpaceData, OBS_ASS, bodyIndex) == obs_assimilated .and. &
714 obs_bodyElem_i(obsSpaceData, OBS_VNM, bodyIndex) == uWindBufrCode ) then
715
716 headerIndex = obs_bodyElem_i(obsSpaceData, OBS_HIND, bodyIndex )
717 headerIndexStart = obs_headElem_i(obsSpaceData, OBS_RLN , headerIndex )
718 headerIndexEnd = obs_headElem_i(obsSpaceData, OBS_NLV , headerIndex ) + headerIndexStart - 1
719 uWindLevel = obs_bodyElem_r(obsSpaceData, OBS_PPP , bodyIndex )
720 uWind = - obs_bodyElem_r(obsSpaceData, residualTypeID, bodyIndex ) + obs_bodyElem_r(obsSpaceData, OBS_VAR, bodyIndex )
721
722 body2: do bodyIndex2 = headerIndexStart, headerIndexEnd
723
724 if ( obs_bodyElem_i(obsSpaceData, OBS_VNM, bodyIndex2) == vWindBufrCode .and. &
725 obs_bodyElem_r(obsSpaceData, OBS_PPP, bodyIndex2) == uWindLevel ) then
726
727 vWind = -obs_bodyElem_r(obsSpaceData, residualTypeID, bodyIndex2 ) + obs_bodyElem_r(obsSpaceData, OBS_VAR, bodyIndex2 )
728
729 ! Calculate angle
730 speed = sqrt((uWind**2)+(vWind**2))
731
732 if (speed == 0.) then
733 direction = 0.0d0
734 else
735 direction = atan2(vWind,uWind)
736 direction = (270.0d0 - direction * MPC_DEGREES_PER_RADIAN_R8 )
737 ! Change to meteorological definition of wind direction.
738 if (direction > 360.0d0 ) direction = direction - 360.0d0
739 if (direction <= 0.0d0 ) direction = direction + 360.0d0
740 end if
741
742 end if
743
744 end do body2
745
746 ! insert resduals into obsSpaceData
747 body2_2: do bodyIndex2 = headerIndexStart, headerIndexEnd
748
749 if ( obs_bodyElem_i( obsSpaceData, OBS_VNM, bodyIndex2) == directionBufrCode .and. &
750 obs_bodyElem_r( obsSpaceData, OBS_PPP, bodyIndex2) == uWindLevel ) then
751 call obs_bodySet_r( obsSpaceData, residualTypeID, bodyIndex2, &
752 obs_bodyElem_r(obsSpaceData, OBS_VAR, bodyIndex2 ) - direction )
753
754 if ( obs_bodyElem_r( obsSpaceData,residualTypeID,bodyIndex2) > 180.0d0) &
755 call obs_bodySet_r( obsSpaceData, residualTypeID, bodyIndex2, &
756 obs_bodyElem_r(obsSpaceData, residualTypeID, bodyIndex2 ) - real(360.0d0,pre_obsReal) )
757 if ( obs_bodyElem_r(obsSpaceData,residualTypeID,bodyIndex2) <= -180.0d0) &
758 call obs_bodySet_r( obsSpaceData, residualTypeID, bodyIndex2, &
759 obs_bodyElem_r(obsSpaceData, residualTypeID, bodyIndex2 ) + real(360.0d0,pre_obsReal) )
760 call obs_bodySet_r( obsSpaceData, residualTypeID, bodyIndex2, &
761 - real(1.0d0,pre_obsReal) * obs_bodyElem_r(obsSpaceData,residualTypeID,bodyIndex2 ) )
762 call obs_bodySet_r( obsSpaceData, OBS_OER, bodyIndex2, real(1.0d0,pre_obsReal) )
763 call obs_bodySet_i( obsSpaceData, OBS_ASS, bodyIndex2, obs_assimilated )
764 call obs_bodySet_i( obsSpaceData, OBS_FLG, bodyIndex2, 0 )
765 end if
766 if ( obs_bodyElem_i( obsSpaceData, OBS_VNM, bodyIndex2 ) == speedBufrCode .and. &
767 obs_bodyElem_r( obsSpaceData, OBS_PPP, bodyIndex2 ) == uWindLevel ) then
768 call obs_bodySet_r( obsSpaceData, residualTypeID, bodyIndex2, &
769 obs_bodyElem_r(obsSpaceData, OBS_VAR, bodyIndex2 ) - speed )
770 call obs_bodySet_r( obsSpaceData, OBS_OER, bodyIndex2, real(1.0d0,pre_obsReal) )
771 call obs_bodySet_i( obsSpaceData, OBS_ASS, bodyIndex2, obs_assimilated)
772 call obs_bodySet_i( obsSpaceData, OBS_FLG, bodyIndex2, 0)
773 end if
774
775 end do body2_2
776
777 end if
778
779 end do body
780
781 end do windType
782
783 end subroutine ovt_UVtoWindSpeedDirection_residual
784
785 !--------------------------------------------------------------------------
786 ! ovt_visToLogVis
787 !--------------------------------------------------------------------------
788 subroutine ovt_visToLogVis(obsSpaceData, headerIndexStart, headerIndexEnd)
789 !
790 !:Purpose: To transform visibily observation to log(visibility)
791 !
792 implicit none
793
794 ! Arguments:
795 type (struct_obs), intent(inout) :: obsSpaceData ! The observation database
796 integer , intent(in) :: headerIndexStart ! The initial header index to analyse
797 integer , intent(in) :: headerIndexEnd ! The final header index to analyse
798
799 ! Locals:
800 integer :: headerIndex, bodyIndex, bodyIndexStart, bodyIndexEnd, bodyIndex2
801 integer :: visFlag, logVisFlag
802 real(pre_obsReal) :: visObs, visLevel, logVisObs, level
803 logical :: logVisFound
804
805 ! Loop through headers
806 header: do headerIndex = headerIndexStart, headerIndexEnd
807
808 bodyIndexStart = obs_headElem_i(obsSpaceData, OBS_RLN, headerIndex )
809 bodyIndexEnd = obs_headElem_i(obsSpaceData, OBS_NLV, headerIndex ) + bodyIndexStart - 1
810
811 ! Find each visibily report
812 body: do bodyIndex = bodyIndexStart, bodyIndexEnd
813
814 if (obs_bodyElem_i(obsSpaceData, OBS_VNM, bodyIndex) /= bufr_vis) cycle body
815
816 visObs = obs_bodyElem_r(obsSpaceData, OBS_VAR, bodyIndex )
817 visFlag = obs_bodyElem_i(obsSpaceData, OBS_FLG, bodyIndex )
818 visLevel = obs_bodyElem_r(obsSpaceData, OBS_PPP, bodyIndex )
819
820 ! Find the associated logVis body created earlier in the proper reading routine
821 logVisFound = .false.
822 body2: do bodyIndex2 = bodyIndex, bodyIndexEnd
823
824 level = obs_bodyElem_r(obsSpaceData, OBS_PPP, bodyIndex2 )
825
826 if ( level /= visLevel ) cycle body2
827
828 if (obs_bodyElem_i(obsSpaceData, OBS_VNM, bodyIndex2 ) /= bufr_logVis) cycle body2
829
830 if (visObs == obs_missingValue_R) then
831 logVisObs = visObs
832 else
833 ! vis -> log(vis)
834 logVisObs = log(max(min(visObs,MPC_MAXIMUM_VIS_R8),MPC_MINIMUM_VIS_R8))
835 end if
836 call obs_bodySet_r(obsSpaceData, OBS_VAR, bodyIndex2, logVisObs)
837
838 logVisFlag = visFlag
839 call obs_bodySet_i(obsSpaceData, OBS_FLG, bodyIndex2, logVisFlag )
840
841 logVisFound = .true.
842 exit body2
843
844 end do body2
845
846 if (.not. logVisFound) then
847 call utl_abort('ovt_visToLogVis: logVis bodyIndex not found!')
848 end if
849
850 end do body
851
852 end do header
853
854 end subroutine ovt_visToLogVis
855
856 !--------------------------------------------------------------------------
857 ! ovt_visToLogVis_residual
858 !--------------------------------------------------------------------------
859 subroutine ovt_visToLogVis_residual(obsSpaceData, residualTypeID)
860 !
861 !:Purpose: To transform log(visibily) residuals to visibility
862 !
863 implicit none
864
865 ! Arguments:
866 type (struct_obs), intent(inout) :: obsSpaceData ! The observation database
867 integer , intent(in) :: residualTypeID ! The residual type ID (o-p or o-a)
868
869 ! Locals:
870 integer :: headerIndex, bodyIndex, bodyIndexStart, bodyIndexEnd, bodyIndex2
871 real(pre_obsReal) :: visObs, logVisLevel, logVisObs, level
872 real(pre_obsReal) :: visResidual, logVisResidual
873 logical :: visFound
874
875 ! Find each log of visibily assimilated observations
876 body: do bodyIndex = 1, obs_numBody(obsSpaceData)
877
878 if ( obs_bodyElem_i(obsSpaceData, OBS_ASS, bodyIndex) /= obs_assimilated .or. &
879 obs_bodyElem_i(obsSpaceData, OBS_VNM, bodyIndex) /= bufr_logVis ) cycle
880
881 headerIndex = obs_bodyElem_i(obsSpaceData, OBS_HIND, bodyIndex )
882 bodyIndexStart = obs_headElem_i(obsSpaceData, OBS_RLN , headerIndex )
883 bodyIndexEnd = obs_headElem_i(obsSpaceData, OBS_NLV , headerIndex ) + bodyIndexStart - 1
884 logVisLevel = obs_bodyElem_r(obsSpaceData, OBS_PPP , bodyIndex )
885
886 logVisObs = obs_bodyElem_r(obsSpaceData, OBS_VAR, bodyIndex )
887 logVisResidual = obs_bodyElem_r(obsSpaceData, residualTypeID, bodyIndex )
888
889 ! Find the associated vis body
890 visFound = .false.
891 body2: do bodyIndex2 = bodyIndexStart, bodyIndexEnd
892
893 level = obs_bodyElem_r(obsSpaceData, OBS_PPP, bodyIndex2 )
894
895 if (level /= logVisLevel) cycle body2
896 if (obs_bodyElem_i(obsSpaceData, OBS_VNM, bodyIndex2) /= bufr_vis) cycle body2
897
898 ! log(vis) -> vis
899 visObs = obs_bodyElem_r(obsSpaceData, OBS_VAR, bodyIndex2 )
900 visResidual = visObs - exp(logVisObs-logVisResidual) ! o-p or o-a
901 call obs_bodySet_r(obsSpaceData, residualTypeID, bodyIndex2, visResidual)
902
903 ! Set the obs error to missing
904 call obs_bodySet_r(obsSpaceData, OBS_OER, bodyIndex2, obs_missingValue_R)
905
906 ! Set flags
907 call obs_bodySet_i(obsSpaceData, OBS_ASS, bodyIndex2, obs_assimilated)
908 call obs_bodySet_i(obsSpaceData, OBS_FLG, bodyIndex2, 0)
909
910 visFound = .true.
911 exit body2
912
913 end do body2
914
915 if (.not. visFound) then
916 call utl_abort('ovt_visToLogVis_residual: vis bodyIndex not found!')
917 end if
918
919 end do body
920
921 end subroutine ovt_visToLogVis_residual
922
923 !--------------------------------------------------------------------------
924 ! ovt_precipToLogPrecip
925 !--------------------------------------------------------------------------
926 subroutine ovt_precipToLogPrecip(obsSpaceData, headerIndexStart, headerIndexEnd)
927 !
928 !:Purpose: To transform precipitation observation to log(precipitation)
929 !
930 implicit none
931
932 ! Arguments:
933 type (struct_obs), intent(inout) :: obsSpaceData ! The observation database
934 integer , intent(in) :: headerIndexStart ! The initial header index to analyse
935 integer , intent(in) :: headerIndexEnd ! The final header index to analyse
936
937 ! Locals:
938 integer :: headerIndex, bodyIndex, bodyIndexStart, bodyIndexEnd, bodyIndex2
939 integer :: precipFlag, logPrecipFlag
940 real(pre_obsReal) :: precipObs, precipLevel, logPrecipObs, level
941 logical :: logPrecipFound
942
943 ! Loop through headers
944 header: do headerIndex = headerIndexStart, headerIndexEnd
945
946 bodyIndexStart = obs_headElem_i(obsSpaceData, OBS_RLN, headerIndex )
947 bodyIndexEnd = obs_headElem_i(obsSpaceData, OBS_NLV, headerIndex ) + bodyIndexStart - 1
948
949 ! Find each precipitation report
950 body: do bodyIndex = bodyIndexStart, bodyIndexEnd
951
952 if (obs_bodyElem_i(obsSpaceData, OBS_VNM, bodyIndex) /= bufr_radarPrecip) cycle body
953
954 precipObs = obs_bodyElem_r(obsSpaceData, OBS_VAR, bodyIndex )
955 precipFlag = obs_bodyElem_i(obsSpaceData, OBS_FLG, bodyIndex )
956 precipLevel = obs_bodyElem_r(obsSpaceData, OBS_PPP, bodyIndex )
957
958 ! Find the associated logPrecip body created earlier in the proper reading routine
959 logPrecipFound = .false.
960 body2: do bodyIndex2 = bodyIndex, bodyIndexEnd
961
962 level = obs_bodyElem_r(obsSpaceData, OBS_PPP, bodyIndex2 )
963
964 if ( level /= precipLevel ) cycle body2
965
966 if (obs_bodyElem_i(obsSpaceData, OBS_VNM, bodyIndex2 ) /= bufr_logRadarPrecip) cycle body2
967
968 if (precipObs == obs_missingValue_R) then
969 logPrecipObs = precipObs
970 else
971 ! precip -> log(precip)
972 logPrecipObs = log(MPC_MINIMUM_PR_R8 + max(0.0d0,precipObs))
973 end if
974 call obs_bodySet_r(obsSpaceData, OBS_VAR, bodyIndex2, logPrecipObs)
975
976 logPrecipFlag = precipFlag
977 call obs_bodySet_i(obsSpaceData, OBS_FLG, bodyIndex2, logPrecipFlag )
978
979 logPrecipFound = .true.
980 exit body2
981
982 end do body2
983
984 if (.not. logPrecipFound) then
985 call utl_abort('ovt_precipToLogPrecip: logPrecip bodyIndex not found!')
986 end if
987
988 end do body
989
990 end do header
991
992 end subroutine ovt_precipToLogPrecip
993
994 !--------------------------------------------------------------------------
995 ! ovt_precipToLogPrecip_residual
996 !--------------------------------------------------------------------------
997 subroutine ovt_precipToLogPrecip_residual(obsSpaceData, residualTypeID)
998 !
999 !:Purpose: To transform log(precip) residuals to precip
1000 !
1001 implicit none
1002
1003 ! Arguments:
1004 type (struct_obs), intent(inout) :: obsSpaceData ! The observation database
1005 integer , intent(in) :: residualTypeID ! The residual type ID (o-p or o-a)
1006
1007 ! Locals:
1008 integer :: headerIndex, bodyIndex, bodyIndexStart, bodyIndexEnd, bodyIndex2
1009 real(pre_obsReal) :: precipObs, logPrecipLevel, logPrecipObs, level
1010 real(pre_obsReal) :: precipResidual, logPrecipResidual
1011 logical :: precipFound
1012
1013 ! Find each log of precipitation assimilated observations
1014 body: do bodyIndex = 1, obs_numBody(obsSpaceData)
1015
1016 if ( obs_bodyElem_i(obsSpaceData, OBS_ASS, bodyIndex) /= obs_assimilated .or. &
1017 obs_bodyElem_i(obsSpaceData, OBS_VNM, bodyIndex) /= bufr_logRadarPrecip ) cycle
1018
1019 headerIndex = obs_bodyElem_i(obsSpaceData, OBS_HIND, bodyIndex )
1020 bodyIndexStart = obs_headElem_i(obsSpaceData, OBS_RLN , headerIndex )
1021 bodyIndexEnd = obs_headElem_i(obsSpaceData, OBS_NLV , headerIndex ) + bodyIndexStart - 1
1022 logPrecipLevel = obs_bodyElem_r(obsSpaceData, OBS_PPP , bodyIndex )
1023
1024 logPrecipObs = obs_bodyElem_r(obsSpaceData, OBS_VAR, bodyIndex )
1025 logPrecipResidual = obs_bodyElem_r(obsSpaceData, residualTypeID, bodyIndex )
1026
1027 ! Find the associated precip body
1028 precipFound = .false.
1029 body2: do bodyIndex2 = bodyIndexStart, bodyIndexEnd
1030
1031 level = obs_bodyElem_r(obsSpaceData, OBS_PPP, bodyIndex2 )
1032
1033 if (level /= logPrecipLevel) cycle body2
1034 if (obs_bodyElem_i(obsSpaceData, OBS_VNM, bodyIndex2) /= bufr_radarPrecip) cycle body2
1035
1036 ! log(precip) -> precip
1037 precipObs = obs_bodyElem_r(obsSpaceData, OBS_VAR, bodyIndex2 )
1038 precipResidual = precipObs - max(0.0D0, & ! o-p or o-a
1039 exp(logPrecipObs - logPrecipResidual - MPC_MINIMUM_PR_R8))
1040 call obs_bodySet_r(obsSpaceData, residualTypeID, bodyIndex2, precipResidual)
1041
1042 ! Set the obs error to missing
1043 call obs_bodySet_r(obsSpaceData, OBS_OER, bodyIndex2, obs_missingValue_R)
1044
1045 ! Set flags
1046 call obs_bodySet_i(obsSpaceData, OBS_ASS, bodyIndex2, obs_assimilated)
1047 call obs_bodySet_i(obsSpaceData, OBS_FLG, bodyIndex2, 0)
1048
1049 precipFound = .true.
1050 exit body2
1051
1052 end do body2
1053
1054 if (.not. precipFound) then
1055 call utl_abort('ovt_precipToLogPrecip_residual: precip bodyIndex not found!')
1056 end if
1057
1058 end do body
1059
1060 end subroutine ovt_precipToLogPrecip_residual
1061
1062 !--------------------------------------------------------------------------
1063 ! ovt_adjustHumGZ
1064 !--------------------------------------------------------------------------
1065 subroutine ovt_adjustHumGZ(obsSpaceData, headerIndexStart, headerIndexEnd )
1066 !
1067 !:Purpose: To apply a threshold on dew-point departure values and to
1068 ! transform geopotential height values to geopotential
1069 !
1070 implicit none
1071
1072 ! Arguments:
1073 type (struct_obs), intent(inout) :: obsSpaceData ! The observation database
1074 integer , intent(in) :: headerIndexStart ! The initial header index to analyse
1075 integer , intent(in) :: headerIndexEnd ! The final header index to analyse
1076
1077 ! Locals:
1078 integer :: bodyIndex, headerIndex, bodyIndexStart, bodyIndexEnd
1079 integer :: bufrCode
1080 real(pre_obsReal), parameter :: ESmax = 30.0
1081 real(pre_obsReal) :: gz, obsValue
1082
1083 do headerIndex = headerIndexStart, headerIndexEnd
1084
1085 bodyIndexStart = obs_headElem_i(obsSpaceData, OBS_RLN, headerIndex )
1086 bodyIndexEnd = obs_headElem_i(obsSpaceData, OBS_NLV, headerIndex ) + bodyIndexStart - 1
1087
1088 do bodyIndex = bodyIndexStart, bodyIndexEnd
1089
1090 bufrCode = obs_bodyElem_i(obsSpaceData, OBS_VNM, bodyIndex )
1091
1092 select case(bufrCode)
1093 case(bufr_nees, bufr_ness)
1094 obsValue = obs_bodyElem_r(obsSpaceData, OBS_VAR, bodyIndex )
1095 if ( obsValue > ESmax ) obsValue = ESmax
1096 call obs_bodySet_r(obsSpaceData, OBS_VAR, bodyIndex, obsValue )
1097 case(bufr_negz)
1098 obsValue = obs_bodyElem_r(obsSpaceData,OBS_VAR, bodyIndex )
1099 gz = obsValue * ec_rg
1100 call obs_bodySet_r(obsSpaceData, OBS_VAR, bodyIndex, gz )
1101 end select
1102
1103 end do
1104
1105 end do
1106
1107 end subroutine ovt_adjustHumGZ
1108
1109end module obsVariableTransforms_mod