FV3 Bundle
gsidiag_aod_bin2nc4.f90
Go to the documentation of this file.
2 
5  USE ncd_kinds,ONLY: r_quad, r_single
6 
7  USE nc_diag_write_mod, ONLY: nc_diag_init, nc_diag_header, nc_diag_metadata, &
8  nc_diag_write, nc_diag_data2d, nc_diag_chaninfo_dim_set, nc_diag_chaninfo
9 
10  IMPLICIT NONE
11 
12  REAL,PARAMETER:: missing = -9.99e9
13  INTEGER,PARAMETER:: imissing = -999999
14 
15  INTEGER nargs, iargc, n
16  CHARACTER*256, ALLOCATABLE :: arg(:)
17 
18  TYPE(diag_header_fix_list_aod ) :: header_fix
19  TYPE(diag_header_chan_list_aod),ALLOCATABLE :: header_chan(:)
20  TYPE(diag_data_name_list_aod) :: headname
21 
22  TYPE(diag_data_fix_list_aod) :: data_fix
23  TYPE(diag_data_chan_list_aod) ,ALLOCATABLE :: data_chan(:)
24 
25 
26  INTEGER i
27 !!! real(r_quad) :: ret_var
28 !!! real(r_quad) :: ret_stddev
29 
30 ! commandline variables
31  LOGICAL :: debug
32  LOGICAL :: append_suffix
33 
34  CHARACTER*256 infn, outfn
35  LOGICAL linfile, loutfile
36 
37  INTEGER,PARAMETER :: inlun = 51
38  INTEGER,PARAMETER :: outlun= 52
39  INTEGER,PARAMETER :: nllun = 53
40 
41  INTEGER strlen, iflag
42  INTEGER iuse, ich, nch, ipr
43 
44  LOGICAL,DIMENSION(:),ALLOCATABLE :: luse
45  LOGICAL lqcpass
46 
47  INTEGER,PARAMETER :: nvar = 4 ! number of positions in array needed for inline variance calc
48 ! variables for output, all to be allocated as nchan. Variances will be calculated using inline algorithm
49 ! accredited to Welford, according
50 !!! real(r_quad),dimension(:),allocatable :: nobstotal, nobsassim, tbtotal, tbassim, omf_nbc , omf_bc , sigo, jo
51 !!! real(r_quad),dimension(:,:),allocatable :: vomf_nbc, vomf_bc
52 ! total bias and fixed bias terms. When Yanqui's variational angle correction is brought in, this may need to be updated.
53 !!! real(r_quad),dimension(:),allocatable :: totbias , fixbias
54 !!! real(r_quad),dimension(:,:),allocatable :: vtotbias, vfixbias
55 ! variational bias correction variables, which will be allocated as nchan and npred_read
56 !!! real(r_quad),dimension(:,:),allocatable :: biasterms
57 !!! real(r_quad),dimension(:,:,:),allocatable :: vbiasterms
58 ! Definitions for above variables -
59 ! nobstotal - number of observations considered - total
60 ! nobsassim - number of observations that are assimilated
61 ! tbtotal - mean brightness temperature of all observations
62 ! tbassim - mean brightness temperature of assimilated observations
63 ! omf_nbc/vomf_nbc - mean/variance of O-F without bias correction applied
64 ! omf_bc/vomf_bc - mean/variance of O-F with bias correction applied
65 ! sigo - mean observation error of assimilated observations
66 ! jo - mean cost (Jo) of assimilated observations
67 ! totbias/vtotbias - mean/variance of bias correction applied to assimilated observations
68 ! fixbias/vfixbias - mean/variance of fixed scan angle position bias correction (sac.x-derived)
69 ! biasterms
70 ! /vbiasterms - means/variances of the variational terms as defined by npred_read.
71 
72 ! single variables used later for printing purposes
73  INTEGER :: inobstotal, inobsassim
74  CHARACTER(len=13),DIMENSION(:),ALLOCATABLE :: chfrwn
75 
76  REAL(r_quad) :: cvar, rch
77 
78  nargs = iargc()
79  IF( nargs.EQ.0 ) THEN
80  CALL usage
81  ELSE
82  debug = .false.
83  append_suffix = .false.
84 
85  ALLOCATE(arg(nargs))
86  DO n=1,nargs
87  CALL getarg(n,arg(n))
88  ENDDO
89  DO n=1,nargs
90  IF (trim(arg(n)).EQ.'-debug' ) debug=.true.
91  IF (trim(arg(n)).EQ.'-append_nc4') append_suffix=.true.
92  ENDDO
93  ENDIF
94 
95  IF (debug) WRITE(*,*)'Debugging on - Verbose Printing'
96 
97 ! get infn from command line
98  CALL getarg(nargs, infn)
99 
100  strlen = len(trim(infn))
101 
102  WRITE(*,*)'Input bin diag: ',trim(infn)
103  INQUIRE(file=trim(infn), exist=linfile)
104  IF (.NOT. linfile) THEN
105  WRITE(*,*)trim(infn) // ' does not exist - exiting'
106  CALL abort
107  ENDIF
108 
109  IF (.NOT. append_suffix) THEN
110  outfn = infn(1:strlen-3) // 'nc4' ! assumes GMAO diag filename format ending with .bin, and replaces it
111  ELSE
112  outfn = infn(1:strlen) // '.nc4' ! if not GMAO format, use append_suffix = .true. in namelist
113 ! to simply append infile with .nc4 suffix
114  ENDIF
115 
116  WRITE(*,*)'Output NC4 diag: ',trim(outfn)
117  INQUIRE(file=trim(outfn), exist=loutfile)
118  IF (loutfile) WRITE(*,*)'WARNING: ' // trim(infn) // ' exists - overwriting'
119 
120  iflag = 0
121 
122  OPEN(inlun,file=infn,form='unformatted',convert='big_endian')
123  CALL nc_diag_init(outfn)
124 
125  CALL read_aoddiag_header( inlun, header_fix, header_chan, headname, iflag, debug )
126 
127  CALL nc_diag_chaninfo_dim_set(header_fix%nchan)
128 
129  CALL nc_diag_header("Satellite_Sensor", header_fix%isis )
130  CALL nc_diag_header("Satellite", header_fix%id ) ! sat type
131  CALL nc_diag_header("Observation_type", header_fix%obstype ) ! observation type
132  CALL nc_diag_header("Outer_Loop_Iteration", header_fix%jiter )
133  CALL nc_diag_header("Number_of_channels", header_fix%nchan ) ! number of channels in the sensor
134  CALL nc_diag_header("date_time", header_fix%idate ) ! time (yyyymmddhh)
135  CALL nc_diag_header("ireal_aoddiag", header_fix%ireal )
136  CALL nc_diag_header("ipchan_aoddiag", header_fix%ipchan )
137  CALL nc_diag_header("ioff0", header_fix%isens ) ! i think ioff0 = isens
138 
139 
140  nch = header_fix%nchan
141 
142  ALLOCATE(luse(nch))
143 
144  IF (debug) THEN
145  WRITE(*,*)'Number of Channels: ',nch
146  ENDIF
147 
148  DO i=1,nch
149  CALL nc_diag_chaninfo("chaninfoidx", i )
150  CALL nc_diag_chaninfo("frequency", header_chan(i)%freq )
151  CALL nc_diag_chaninfo("polarization", header_chan(i)%polar )
152  CALL nc_diag_chaninfo("wavenumber", header_chan(i)%wave )
153  CALL nc_diag_chaninfo("error_variance", header_chan(i)%varch )
154  CALL nc_diag_chaninfo("use_flag", header_chan(i)%iuse )
155  CALL nc_diag_chaninfo("sensor_chan", header_chan(i)%nuchan )
156  CALL nc_diag_chaninfo("satinfo_chan", header_chan(i)%iochan )
157  END DO
158 
159 
160  DO WHILE (iflag .GE. 0) ! iflag == 0 means the end of the file
161  CALL read_aoddiag_data ( inlun, header_fix, data_fix, data_chan, iflag )
162 
163  IF (iflag .LT. 0) cycle
164 
165  DO ich=1,nch
166  lqcpass = luse(ich) .AND. nint(data_chan(ich)%qcmark) .EQ. 0
167 
168  CALL nc_diag_metadata("Channel_Index", ich )
169  CALL nc_diag_metadata("Observation_Class", ' aod' )
170  CALL nc_diag_metadata("Latitude", data_fix%lat ) ! observation latitude (degrees)
171  CALL nc_diag_metadata("Longitude", data_fix%lon ) ! observation longitude (degrees)
172 
173  CALL nc_diag_metadata("Psfc", data_fix%psfc ) ! observation surface pressure (hPa)
174 
175  CALL nc_diag_metadata("Obs_Time", data_fix%obstime ) ! observation time (hours relative to analysis time)
176 
177  CALL nc_diag_metadata("Sol_Zenith_Angle", data_fix%solzen_ang ) ! solar zenith angle (degrees)
178  CALL nc_diag_metadata("Sol_Azimuth_Angle", data_fix%solazm_ang ) ! solar azimuth angle (degrees)
179  CALL nc_diag_metadata("Observation", data_chan(ich)%aodobs ) ! observed aod
180  CALL nc_diag_metadata("Obs_Minus_Forecast_unadjusted", data_chan(ich)%omgaod ) ! observed - simulated Tb with no bias correction (K)
181 ! errinv = sqrt(varinv(ich_diag(i)))
182  CALL nc_diag_metadata("Inverse_Observation_Error", data_chan(ich)%errinv )
183 
184 ! useflag=one
185 ! if (iuse_aod(ich(ich_diag(i))) < 1) useflag=-one
186 
187  CALL nc_diag_metadata("QC_Flag", data_chan(ich)%qcmark ) ! quality control mark or event indicator
188 
189  ENDDO
190 
191  ENDDO
192 
193 ! finalize NCDIAG
194  CALL nc_diag_write
195 END PROGRAM convert_aod_diag
196 
197 SUBROUTINE usage
198  WRITE(6,100)
199 100 FORMAT( "Usage: ",/,/ &
200  " convert_aod_diag.x <options> <filename>",/,/ &
201  "where options:",/ &
202  " -debug : Set debug verbosity",/ &
203  " -append_txt : Append .txt suffix, instead of replace last three",/ &
204  " characters (default: replaced)",/ &
205  " Note: The GMAO diag files end with .bin or .nc4,",/ &
206  " which is where fixed 3-char truncation originates",/,/,/ &
207  " Example:",/ &
208  " convert_aod_diag.x nc_4emily.diag_hirs4_n19_ges.20161202_00z.bin",/ &
209  " Output file:",/ &
210  " nc_4emily.diag_hirs4_n19_ges.20161202_00z.nc4",/ &
211  )
212  stop
213 
214 END SUBROUTINE usage
215 
subroutine, public read_aoddiag_data(ftin, header_fix, data_fix, data_chan, iflag)
program convert_aod_diag
integer, parameter, public strlen
subroutine nc_diag_init(filename, append)
subroutine usage
integer, parameter, public r_quad
Definition: ncd_kinds.F90:82
subroutine, public read_aoddiag_header(ftin, header_fix, header_chan, data_name, iflag, lverbose)
integer, parameter, public r_single
Definition: ncd_kinds.F90:79