da_get_innov_vector_geoamv.inc

References to this file elsewhere.
1 subroutine da_get_innov_vector_geoamv( it, xb, xp, ob, iv)
2 
3    !-------------------------------------------------------------------------
4    ! Purpose: Calculates innovation vector does QC for  Geo. AMV's
5    !               
6    ! Update :
7    !     01/24/2007    Syed RH Rizvi
8    !     Updated for "VERIFY"       
9    !-------------------------------------------------------------------------
10 
11    implicit none
12 
13    integer, intent(in)           :: it      ! External iteration.
14    type(xb_type), intent(in)    :: xb      ! first guess state.
15    type(xpose_type), intent(in) :: xp      ! Domain decomposition vars.
16    type(y_type),  intent(in)    :: ob      ! Observation structure.
17    type(ob_type), intent(inout) :: iv      ! O-B structure.
18 
19    integer                        :: n        ! Loop counter.
20    integer                        :: i, j, k  ! Index dimension.
21    integer                        :: num_levs ! Number of obs levels.
22 
23    real                         :: dx, dxm  ! Interpolation weights.
24    real                         :: dy, dym  ! Interpolation weights.
25    real, dimension(1:max_ob_levels) :: model_u  ! Model value u at ob location.
26    real, dimension(1:max_ob_levels) :: model_v  ! Model value v at ob location.
27 
28    real, dimension(xp%kms:xp%kme) :: v_p      ! Model value p at ob hor. location.
29 
30    integer           :: itu,ituf,itvv,itvvf
31 
32    if (iv % num_geoamv < 1) return
33    
34    if (trace_use) call da_trace_entry("da_get_innov_vector_geoamv")
35 
36    itu   = 0
37    itvv  = 0
38    ituf  = 0
39    itvvf = 0
40 
41    do n=iv%ob_numb(iv%current_ob_time-1)%geoamv + 1, iv%ob_numb(iv%current_ob_time)%geoamv
42 
43       ! [1.3] Get horizontal interpolation weights:
44 
45       num_levs = iv % geoamv(n) % info % levels
46       if (num_levs < 1) cycle
47 
48       model_u(:) = 0.0
49       model_v(:) = 0.0
50 
51       i = iv%geoamv(n)%loc%i
52       j = iv%geoamv(n)%loc%j
53       dx = iv%geoamv(n)%loc%dx
54       dy = iv%geoamv(n)%loc%dy
55       dxm = iv%geoamv(n)%loc%dxm
56       dym = iv%geoamv(n)%loc%dym
57 
58       do k=xp%kts,xp%kte
59          v_p(k) = dym*(dxm*xb%p(i,j  ,k) + dx*xb%p(i+1,j  ,k)) &
60                 + dy *(dxm*xb%p(i,j+1,k) + dx*xb%p(i+1,j+1,k))
61       end do
62 
63       do k=1, iv % geoamv(n) % info % levels
64          iv%geoamv(n)%zk(k)=missing_r
65 
66          if (iv % geoamv(n) % p(k) > 1.0) then
67             call da_to_zk(iv % geoamv(n) % p(k), v_p, xp, v_interp_p, iv%geoamv(n)%zk(k))
68          end if
69 
70          if (iv%geoamv(n)%zk(k) < 0.0 .and.  .not.anal_type_verify) then
71             iv % geoamv(n) % u(k) % qc = missing
72             iv % geoamv(n) % v(k) % qc = missing
73          end if
74       end do
75 
76       call da_interp_lin_3d( xb % u, xp, i, j, dx, dy, dxm, dym, &
77                           model_u, max_ob_levels,iv%geoamv(n)%zk,num_levs)
78       call da_interp_lin_3d( xb % v, xp, i, j, dx, dy, dxm, dym, &
79                           model_v, max_ob_levels,iv%geoamv(n)%zk,num_levs)
80 
81       do k = 1, iv % geoamv(n) % info % levels
82          iv % geoamv(n) % u(k) % inv = 0.0
83          iv % geoamv(n) % v(k) % inv = 0.0
84          if (ob % geoamv(n) % u(k) > missing_r .AND. &
85               iv % geoamv(n) % u(k) % qc >= obs_qc_pointer) then
86             iv % geoamv(n) % u(k) % inv = ob % geoamv(n) % u(k) - model_u(k)
87          end if
88 
89          if (ob % geoamv(n) % v(k) > missing_r .AND. &
90               iv % geoamv(n) % v(k) % qc >= obs_qc_pointer) then
91             iv % geoamv(n) % v(k) % inv = ob % geoamv(n) % v(k) - model_v(k)
92          end if
93       end do
94 
95       !------------------------------------------------------------------------
96       ! Perform optional maximum error check:
97       !------------------------------------------------------------------------
98 
99       if (check_max_iv) then
100         call da_check_max_iv_geoamv(it, iv % geoamv(n),itu,ituf,itvv,itvvf)
101       end if
102    end do
103 
104    if (rootproc .and. check_max_iv_print) then
105       write(unit = check_max_iv_unit, fmt ='(A,i5,A)')'For outer iteration ',it, &
106          ', Total Rejections for Geo. AMVs follows:'
107       write(unit = check_max_iv_unit, fmt = '(/,10(2(A,I6),/))') &
108          'Number of failed u-wind observations:     ',ituf, ' on ',itu,   &
109          'Number of failed v-wind observations:     ',itvvf,' on ',itvv,   &
110          'Finally Total Geo. AMVs rejections ',ituf+itvvf,' on ',itu+itvv
111    end if
112    
113    if (trace_use) call da_trace_exit("da_get_innov_vector_geoamv")
114    
115 end subroutine da_get_innov_vector_geoamv
116 
117