8 nc_diag_write, nc_diag_data2d, nc_diag_chaninfo_dim_set, nc_diag_chaninfo
12 REAL,
PARAMETER:: missing = -9.99e9
13 INTEGER,
PARAMETER:: imissing = -999999
15 INTEGER nargs, iargc, n
16 CHARACTER*256,
ALLOCATABLE :: arg(:)
32 LOGICAL :: append_suffix
34 CHARACTER*256 infn, outfn
35 LOGICAL linfile, loutfile
37 INTEGER,
PARAMETER :: inlun = 51
38 INTEGER,
PARAMETER :: outlun= 52
39 INTEGER,
PARAMETER :: nllun = 53
42 INTEGER iuse, ich, nch, ipr
44 LOGICAL,
DIMENSION(:),
ALLOCATABLE :: luse
47 INTEGER,
PARAMETER :: nvar = 4
73 INTEGER :: inobstotal, inobsassim
74 CHARACTER(len=13),
DIMENSION(:),
ALLOCATABLE :: chfrwn
76 REAL(r_quad) :: cvar, rch
83 append_suffix = .false.
90 IF (trim(arg(n)).EQ.
'-debug' ) debug=.true.
91 IF (trim(arg(n)).EQ.
'-append_nc4') append_suffix=.true.
95 IF (debug)
WRITE(*,*)
'Debugging on - Verbose Printing' 98 CALL getarg(nargs, infn)
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' 109 IF (.NOT. append_suffix)
THEN 110 outfn = infn(1:
strlen-3) //
'nc4' 112 outfn = infn(1:
strlen) //
'.nc4' 116 WRITE(*,*)
'Output NC4 diag: ',trim(outfn)
117 INQUIRE(file=trim(outfn), exist=loutfile)
118 IF (loutfile)
WRITE(*,*)
'WARNING: ' // trim(infn) //
' exists - overwriting' 122 OPEN(inlun,file=infn,form=
'unformatted',convert=
'big_endian')
125 CALL read_aoddiag_header( inlun, header_fix, header_chan, headname, iflag, debug )
127 CALL nc_diag_chaninfo_dim_set(header_fix%nchan)
129 CALL nc_diag_header(
"Satellite_Sensor", header_fix%isis )
130 CALL nc_diag_header(
"Satellite", header_fix%id )
131 CALL nc_diag_header(
"Observation_type", header_fix%obstype )
132 CALL nc_diag_header(
"Outer_Loop_Iteration", header_fix%jiter )
133 CALL nc_diag_header(
"Number_of_channels", header_fix%nchan )
134 CALL nc_diag_header(
"date_time", header_fix%idate )
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 )
140 nch = header_fix%nchan
145 WRITE(*,*)
'Number of Channels: ',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 )
160 DO WHILE (iflag .GE. 0)
163 IF (iflag .LT. 0) cycle
166 lqcpass = luse(ich) .AND. nint(data_chan(ich)%qcmark) .EQ. 0
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 )
171 CALL nc_diag_metadata(
"Longitude", data_fix%lon )
173 CALL nc_diag_metadata(
"Psfc", data_fix%psfc )
175 CALL nc_diag_metadata(
"Obs_Time", data_fix%obstime )
177 CALL nc_diag_metadata(
"Sol_Zenith_Angle", data_fix%solzen_ang )
178 CALL nc_diag_metadata(
"Sol_Azimuth_Angle", data_fix%solazm_ang )
179 CALL nc_diag_metadata(
"Observation", data_chan(ich)%aodobs )
180 CALL nc_diag_metadata(
"Obs_Minus_Forecast_unadjusted", data_chan(ich)%omgaod )
182 CALL nc_diag_metadata(
"Inverse_Observation_Error", data_chan(ich)%errinv )
187 CALL nc_diag_metadata(
"QC_Flag", data_chan(ich)%qcmark )
199 100
FORMAT(
"Usage: ",/,/ &
200 " convert_aod_diag.x <options> <filename>",/,/ &
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",/,/,/ &
208 " convert_aod_diag.x nc_4emily.diag_hirs4_n19_ges.20161202_00z.bin",/ &
210 " nc_4emily.diag_hirs4_n19_ges.20161202_00z.nc4",/ &
subroutine, public read_aoddiag_data(ftin, header_fix, data_fix, data_chan, iflag)
integer, parameter, public strlen
subroutine nc_diag_init(filename, append)
integer, parameter, public r_quad
subroutine, public read_aoddiag_header(ftin, header_fix, header_chan, data_name, iflag, lverbose)
integer, parameter, public r_single