da_qc_hirs.inc
 
References to this file elsewhere.
1 subroutine da_qc_hirs (i, nchan, ob, iv)
2 
3    !---------------------------------------------------------------------------
4    ! Purpose: perform quality control for HIRS data.
5    !---------------------------------------------------------------------------
6 
7    implicit none
8 
9    integer, intent(in)             :: i          ! sensor index.
10    integer, intent(in)             :: nchan      ! number of channel
11    type (y_type),  intent(in)      :: ob         ! Observation structure.
12    type (ob_type), intent(inout)   :: iv         ! O-B structure.
13 
14 
15    ! local variables
16    integer   :: n,scanpos,k,isflg,ios,fgat_rad_unit
17    logical   :: lmix
18    ! real    :: satzen
19    integer   :: ngood(nchan),nrej(nchan),nrej_omb_abs(nchan), &
20                 nrej_omb_std(nchan),      &
21                 nrej_mixsurface,nrej_windowchanl, nrej_si,    &
22                 nrej_clw,nrej_topo,num_rad, num_proc_domain,  &
23                 nrej_limb
24 
25    character(len=30)  :: filename
26 
27    if (trace_use) call da_trace_entry("da_qc_hirs")
28 
29    ngood(:)        = 0
30    nrej(:)         = 0
31    nrej_omb_abs(:) = 0
32    nrej_omb_std(:) = 0
33    nrej_mixsurface = 0
34    nrej_windowchanl= 0
35    nrej_si         = 0
36    nrej_clw        = 0
37    nrej_topo       = 0
38    nrej_limb       = 0
39    num_rad         = iv%ob_numb(iv%current_ob_time)%radiance(i)- &
40                       iv%ob_numb(iv%current_ob_time-1)%radiance(i)
41    ! num_rad        = iv%instid(i)%num_rad
42    num_proc_domain = 0
43 
44    if (num_rad > 0) then
45 
46       ! do n= 1, iv%instid(i)%num_rad           ! loop for pixel
47       do n= iv%ob_numb(iv%current_ob_time-1)%radiance(i)+1, iv%ob_numb(iv%current_ob_time)%radiance(i)
48 
49          if (iv%instid(i)%proc_domain(n)) &
50                num_proc_domain = num_proc_domain + 1
51 
52          !  0.0  initialise QC by flags assuming good obs
53          !---------------------------------------------
54          iv%instid(i)%tb_qc(:,n) = qc_good
55 
56          !  a.  reject all channels over mixture surface type
57          !------------------------------------------------------
58          isflg = iv%instid(i)%isflg(n)
59          lmix  = (isflg==4) .or. (isflg==5) .or. (isflg==6) .or. (isflg==7)
60          if (lmix) then
61             iv%instid(i)%tb_qc(:,n)  =  qc_bad
62             if (iv%instid(i)%proc_domain(n)) &
63                nrej_mixsurface = nrej_mixsurface + 1
64          end if
65 
66          !  b.  reject all channels over land/sea-ice/snow
67          !------------------------------------------------------
68          if (isflg > 0) then 
69             iv%instid(i)%tb_qc(:,n)  = qc_bad
70             if (iv%instid(i)%proc_domain(n)) &
71                nrej_windowchanl = nrej_windowchanl + 1
72          end if
73 
74          !  c.  reject channels 13,14(above top model 10mb),15 
75          !------------------------------------------------------
76          !iv%instid(i)%tb_qc(13:15,n)  = qc_bad
77 
78          !    reject limb obs 
79          !------------------------------------------------------
80          scanpos = iv%instid(i)%scanpos(n)
81          if (scanpos <= 3 .or. scanpos >= 54) then
82             iv%instid(i)%tb_qc(:,n)  =  qc_bad
83             if (iv%instid(i)%proc_domain(n)) &
84                   nrej_limb = nrej_limb + 1
85          end if
86 
87          !  d. cloud detection to be added
88          !-----------------------------------------------------------
89          if (iv%instid(i)%clwp(n) >= 0.2) then
90             iv%instid(i)%tb_qc(:,n) = qc_bad
91             iv%instid(i)%cloud_flag(:,n) = qc_bad
92             if (iv%instid(i)%proc_domain(n)) &
93                nrej_clw = nrej_clw + 1
94          end if
95 
96          !  e. check surface height/pressure
97          !-----------------------------------------------------------
98          ! sfchgt = ivrad%info(n)%elv
99          ! if (sfchgt >=) then
100          ! else 
101          ! end if
102 
103          !if ((isflg .ne. 0) .and. (iv%instid(i)%ps(n) < 850.)) then
104          !   iv%instid(i)%tb_qc(5,n)  = qc_bad
105          !   if (iv%instid(i)%proc_domain(n)) &
106          !      nrej_topo = nrej_topo + 1
107          !end if
108 
109          !  g. check iuse from information file (channel selection)
110          !-----------------------------------------------------------
111          do k = 1, nchan
112             if (satinfo(i)%iuse(k) .eq. -1) &
113                iv%instid(i)%tb_qc(k,n)  = qc_bad
114          end do
115 
116          !  f. check innovation
117          !-----------------------------------------------------------
118          do k = 1, nchan
119 
120          !  1. check absolute value of innovation
121          !------------------------------------------------
122             if (abs(iv%instid(i)%tb_inv(k,n)) > 15.) then
123                iv%instid(i)%tb_qc(k,n)  = qc_bad
124                if (iv%instid(i)%proc_domain(n)) &
125                   nrej_omb_abs(k) = nrej_omb_abs(k) + 1
126             end if
127 
128          !  2. check relative value of innovation
129          !      and assign of the observation error (standard deviation)
130          !------------------------------------------------------------------------
131             if (use_error_factor_rad) then         ! if use error tuning factor
132                iv%instid(i)%tb_error(k,n) = &
133                   satinfo(i)%error(k)*satinfo(i)%error_factor(k)
134             else
135                 iv%instid(i)%tb_error(k,n) = satinfo(i)%error(k)
136             end if
137 
138             if (abs(iv%instid(i)%tb_inv(k,n)) > 3.0*iv%instid(i)%tb_error(k,n)) then
139                iv%instid(i)%tb_qc(k,n)  = qc_bad
140                if (iv%instid(i)%proc_domain(n)) &
141                   nrej_omb_std(k) = nrej_omb_std(k) + 1
142             end if
143 
144            ! 3. Final QC decision
145            !---------------------------------------------
146             if (iv%instid(i)%tb_qc(k,n) == qc_bad) then  ! bad obs
147                iv%instid(i)%tb_error(k,n) = 500.0
148                if (iv%instid(i)%proc_domain(n)) &
149                   nrej(k) = nrej(k) + 1
150             else                                         ! good obs
151                if (iv%instid(i)%proc_domain(n)) &
152                   ngood(k) = ngood(k) + 1
153             end if
154          end do ! chan
155       end do ! end loop pixel
156    end if
157  
158    ! Do inter-processor communication to gather statistics.
159    call da_proc_sum_int (num_proc_domain)
160    call da_proc_sum_int (nrej_mixsurface)
161    call da_proc_sum_int (nrej_windowchanl)
162    call da_proc_sum_int (nrej_si )
163    call da_proc_sum_int (nrej_clw)
164    call da_proc_sum_int (nrej_topo)
165    call da_proc_sum_int (nrej_limb)
166    call da_proc_sum_ints (nrej_omb_abs(:))
167    call da_proc_sum_ints (nrej_omb_std(:))
168    call da_proc_sum_ints (nrej(:))
169    call da_proc_sum_ints (ngood(:))
170 
171    if (rootproc) then
172       if (num_fgat_time > 1) then
173          write(filename,'(a,i2.2)') 'qcstat_'//trim(iv%instid(i)%rttovid_string)//'_',iv%current_ob_time
174       else
175          filename = 'qcstat_'//trim(iv%instid(i)%rttovid_string)
176       end if
177 
178       call da_get_unit(fgat_rad_unit)
179       open(fgat_rad_unit,file=trim(filename),form='formatted',iostat=ios)
180       if (ios /= 0) Then
181          write(unit=message(1),fmt='(A,A)') 'error opening the output file ', filename
182          call da_error(__FILE__,__LINE__,message(1:1))
183       end if
184 
185       write(fgat_rad_unit, fmt='(/a/)') ' Quality Control Statistics for '//iv%instid(i)%rttovid_string
186       write(fgat_rad_unit,'(a20,i7)') ' num_proc_domain  = ', num_proc_domain
187       write(fgat_rad_unit,'(a20,i7)') ' nrej_mixsurface  = ', nrej_mixsurface
188       write(fgat_rad_unit,'(a20,i7)') ' nrej_windowchanl = ', nrej_windowchanl
189       write(fgat_rad_unit,'(a20,i7)') ' nrej_si          = ', nrej_si
190       write(fgat_rad_unit,'(a20,i7)') ' nrej_clw         = ', nrej_clw
191       write(fgat_rad_unit,'(a20,i7)') ' nrej_topo        = ', nrej_topo
192       write(fgat_rad_unit,'(a20,i7)') ' nrej_limb        = ', nrej_limb
193       write(fgat_rad_unit,'(a20)')    ' nrej_omb_abs(:)  = '
194       write(fgat_rad_unit,'(10i7)')     nrej_omb_abs(:)
195       write(fgat_rad_unit,'(a20)')    ' nrej_omb_std(:)  = '
196       write(fgat_rad_unit,'(10i7)')     nrej_omb_std(:)
197       write(fgat_rad_unit,'(a20)')    ' nrej(:)          = '
198       write(fgat_rad_unit,'(10i7)')     nrej(:)
199       write(fgat_rad_unit,'(a20)')    ' ngood(:)         = '
200       write(fgat_rad_unit,'(10i7)')     ngood(:)
201 
202       close(fgat_rad_unit)
203       call da_free_unit(fgat_rad_unit)
204    end if
205 
206    if (trace_use) call da_trace_exit("da_qc_hirs")
207 
208 end subroutine da_qc_hirs
209