1 | ! $Id: gfz2ropp.f90 4452 2015-01-29 14:42:02Z idculv $
|
---|
2 |
|
---|
3 | PROGRAM gfz2ropp
|
---|
4 |
|
---|
5 | !****x* Programs/gfz2ropp *
|
---|
6 | !
|
---|
7 | ! NAME
|
---|
8 | ! gfz2ropp
|
---|
9 | !
|
---|
10 | ! SYNOPSIS
|
---|
11 | ! Convert GFZ NRT DAT/DSC files to ROPP netCDF
|
---|
12 | !
|
---|
13 | ! > gfz2ropp <gfzfile.dat> [-o opfile] [-d] [-h] [-v]
|
---|
14 | !
|
---|
15 | ! ARGUMENTS
|
---|
16 | ! gfzfile.dat - GFZ 'PD' or 'NRT' DAT (.dat) file containing Level 1b,2a,2b
|
---|
17 | ! RO profiles. May include a path. The companion DSC file
|
---|
18 | ! containing meta-data is assumed to be in the same path and
|
---|
19 | ! have the same name at the DAT file, but with a type of .dsc.
|
---|
20 | ! There is no default for this argument.
|
---|
21 | !
|
---|
22 | ! OPTIONS
|
---|
23 | ! -o - specifies the output netCDF file name. The default name
|
---|
24 | ! is the same as the DAT/DSC file name, but with a type of
|
---|
25 | ! .nc and in the current working directory.
|
---|
26 | ! -d - writes additional diagnostic information to stdout
|
---|
27 | ! -h - help
|
---|
28 | ! -v - version information
|
---|
29 | !
|
---|
30 | ! INPUTS
|
---|
31 | ! Pair of GFZ NRT .dat (profile) and .dsc (meta information)
|
---|
32 | !
|
---|
33 | ! OUTPUTS
|
---|
34 | ! ROPP netCDF file - As given with the -o option, or defaults to the
|
---|
35 | ! same path and file name as for input DAT file,
|
---|
36 | ! but with type .nc
|
---|
37 | !
|
---|
38 | ! MODULES
|
---|
39 | ! typesizes
|
---|
40 | ! messages
|
---|
41 | ! ropp_utils
|
---|
42 | ! ropp_io_types
|
---|
43 | ! ropp_io
|
---|
44 | !
|
---|
45 | ! CALLS
|
---|
46 | ! usage
|
---|
47 | ! ropp_io_init
|
---|
48 | ! ropp_io_occid
|
---|
49 | ! ropp_io_ascend
|
---|
50 | ! ropp_io_write
|
---|
51 | ! ropp_io_free
|
---|
52 | ! ropp_io_version
|
---|
53 | ! message
|
---|
54 | ! message_set_routine
|
---|
55 | !
|
---|
56 | ! ERRORS
|
---|
57 | ! Program (shell) return codes:
|
---|
58 | ! 0 = OK
|
---|
59 | ! 1 = At least one Warning occured
|
---|
60 | ! 2 = At least one Error occured
|
---|
61 | ! 3 = A Fatal error occured
|
---|
62 | !
|
---|
63 | ! DESCRIPTION
|
---|
64 | ! Conversion from GFZ native-format GPSRO 'PD' (ROPP Level1a) or 'NRT'
|
---|
65 | ! (ROPP Levels 1b,2a,2b) data to ROPP netCDF format. Input is the pair of
|
---|
66 | ! DAT (data) & DCS (description) files; the profiles are taken from the
|
---|
67 | ! former, and meta-data (non-profile header info) from the latter.
|
---|
68 | ! The data is then written out to a ROPP-standard netCDF file in PWD.
|
---|
69 | ! Only the name of the DAT file is given on the command line; the companion
|
---|
70 | ! DSC file is assumed to be in the same path and have the same name at the
|
---|
71 | ! DAT file, but with a type of .dsc.
|
---|
72 | !
|
---|
73 | ! REFERENCES
|
---|
74 | ! 1. ROPP User Guide - Part I.
|
---|
75 | ! SAF/ROM/METO/UG/ROPP/002
|
---|
76 | !!
|
---|
77 | ! AUTHOR
|
---|
78 | ! Met Office, Exeter, UK.
|
---|
79 | ! Any comments on this software should be given via the ROM SAF
|
---|
80 | ! Helpdesk at http://www.romsaf.org
|
---|
81 | !
|
---|
82 | ! COPYRIGHT
|
---|
83 | ! (c) EUMETSAT. All rights reserved.
|
---|
84 | ! For further details please refer to the file COPYRIGHT
|
---|
85 | ! which you should have received as part of this distribution.
|
---|
86 | !
|
---|
87 | !****
|
---|
88 |
|
---|
89 | USE typesizes, dp => EightByteReal
|
---|
90 | USE messages
|
---|
91 | USE ropp_utils, ONLY: To_Upper
|
---|
92 | USE ropp_io_types, ONLY: ROprof, &
|
---|
93 | PCD_rising
|
---|
94 | USE ropp_io, ONLY: ropp_io_free, &
|
---|
95 | ropp_io_init, &
|
---|
96 | ropp_io_occid, &
|
---|
97 | ropp_io_write, &
|
---|
98 | ropp_io_addvar, &
|
---|
99 | ropp_io_version
|
---|
100 |
|
---|
101 | IMPLICIT NONE
|
---|
102 |
|
---|
103 | ! Fixed parameters
|
---|
104 |
|
---|
105 | INTEGER, PARAMETER :: funit = 11
|
---|
106 | REAL(dp), PARAMETER :: CtoK = 273.15_dp
|
---|
107 | REAL(dp), PARAMETER :: KMtoM = 1000.0_dp
|
---|
108 | REAL(dp), PARAMETER :: SecsPerDay = 86400.0_dp
|
---|
109 |
|
---|
110 | CHARACTER (LEN=*), PARAMETER :: DTfmt1 = & ! hh:mm dd-mm-yyyy
|
---|
111 | "(I2.2,':',I2.2,'UT ',I2.2,'-',A3,'-',I4.4)"
|
---|
112 |
|
---|
113 | ! Local variables
|
---|
114 |
|
---|
115 | TYPE(ROprof) :: ROdata ! RO main profile structure
|
---|
116 |
|
---|
117 | CHARACTER (LEN=256) :: arg ! Command line argument
|
---|
118 | CHARACTER (LEN=256) :: datfile, dscfile, opfile ! I/P & O/P file names
|
---|
119 | CHARACTER (LEN=256) :: line ! Line read from I/P file
|
---|
120 | CHARACTER (LEN=80) :: key ! key word(s) in DSC file
|
---|
121 | INTEGER :: i, j ! Loop counters / indices
|
---|
122 | INTEGER :: iarg ! Command line argument index
|
---|
123 | INTEGER :: narg ! No. of command line arguments
|
---|
124 | INTEGER :: iostatus ! I/O Status
|
---|
125 | INTEGER :: NLevs ! Number of samples in DAT file
|
---|
126 | INTEGER :: SatID ! Satellite ID
|
---|
127 | INTEGER :: Year, Month, Day ! Processing date from DSC file
|
---|
128 | INTEGER :: Hour, Minute, Second ! Occultation end time from DSC file
|
---|
129 | INTEGER :: SWrev = 0 ! GFZ revision number
|
---|
130 | LOGICAL :: exists ! File exists flag
|
---|
131 | LOGICAL :: setting_occ ! .T. if a setting occultation
|
---|
132 | REAL(dp) :: SWver = 0.0_dp ! GFZ POCS software version number
|
---|
133 | REAL(dp) :: sTime, eTime ! Start & end time of occultation (secs)
|
---|
134 |
|
---|
135 | INTEGER :: qflag ! parameters read but not used in ROPP
|
---|
136 | REAL(dp) :: snr1, snr2 ! parameters read but not used in ROPP
|
---|
137 | REAL(dp) :: density, pressure, basmth ! parameters read but not used in ROPP
|
---|
138 | REAL(dp) :: alpha, beta, gamma, phaseLC ! parameters read but not used in ROPP
|
---|
139 |
|
---|
140 | LOGICAL :: lev1a_exists = .FALSE. ! Reading Level 1a data flag
|
---|
141 | LOGICAL :: l1l2_exists = .FALSE. ! Reading L1, L2 bending angle data flag
|
---|
142 | LOGICAL :: no_productid = .TRUE. ! No Product_ID present flag
|
---|
143 | REAL :: Start_Lat, Start_Lon ! Nominal start lat/lon (for Level 1a data)
|
---|
144 | REAL(dp), DIMENSION(:), ALLOCATABLE :: LCF ! Lost carrier flag from Level 1a file
|
---|
145 | CHARACTER (LEN=80) :: outstr ! Formatted output string
|
---|
146 | CHARACTER (LEN=10) :: number ! Number as string
|
---|
147 |
|
---|
148 | ! Some compilers may need the following declaration to be commented out
|
---|
149 | INTEGER :: IARGC
|
---|
150 |
|
---|
151 | !-------------------------------------------------------------
|
---|
152 | ! 1. Initialise
|
---|
153 | !-------------------------------------------------------------
|
---|
154 |
|
---|
155 | CALL message_set_routine ( "gfz2ropp" )
|
---|
156 |
|
---|
157 | CALL message(msg_noin, '')
|
---|
158 | CALL message(msg_noin, &
|
---|
159 | '---------------------------------------------------------------------')
|
---|
160 | CALL message(msg_noin, &
|
---|
161 | ' GFZ to ROPP Converter' )
|
---|
162 | CALL message(msg_noin, &
|
---|
163 | '---------------------------------------------------------------------')
|
---|
164 | CALL message(msg_noin, '')
|
---|
165 |
|
---|
166 | !-------------------------------------------------------------
|
---|
167 | ! 2. Parse command line options
|
---|
168 | !-------------------------------------------------------------
|
---|
169 |
|
---|
170 | narg = IARGC()
|
---|
171 |
|
---|
172 | datfile = " " ! no default for i/p file name
|
---|
173 | opfile = " " ! assume a default generated from i/p file name
|
---|
174 |
|
---|
175 | iarg = 1
|
---|
176 | DO WHILE ( iarg <= narg )
|
---|
177 | CALL GETARG ( iarg, arg )
|
---|
178 |
|
---|
179 | SELECT CASE (arg)
|
---|
180 | CASE ("-d","-D","--debug")
|
---|
181 | msg_MODE = VerboseMode
|
---|
182 |
|
---|
183 | CASE ("-h","-H","--help","?")
|
---|
184 | narg = 0
|
---|
185 | datfile = "dummy"
|
---|
186 |
|
---|
187 | CASE ("-o","-O","--output")
|
---|
188 | iarg = iarg + 1
|
---|
189 | CALL GETARG ( iarg, arg )
|
---|
190 | opfile = arg
|
---|
191 |
|
---|
192 | CASE ("-v","-V","--version")
|
---|
193 | CALL version_info()
|
---|
194 | CALL EXIT(msg_exit_ok)
|
---|
195 |
|
---|
196 | CASE DEFAULT
|
---|
197 | IF ( arg(1:1) /= '-' ) THEN
|
---|
198 | datfile = arg
|
---|
199 | END IF
|
---|
200 | END SELECT
|
---|
201 |
|
---|
202 | iarg = iarg + 1
|
---|
203 | END DO
|
---|
204 |
|
---|
205 | IF ( datfile == " " ) THEN
|
---|
206 | CALL message ( msg_error, "No input file(s) specified" )
|
---|
207 | narg = 0
|
---|
208 | END IF
|
---|
209 |
|
---|
210 | IF ( narg == 0 ) THEN
|
---|
211 | CALL Usage
|
---|
212 | CALL EXIT(msg_exit_status)
|
---|
213 | END IF
|
---|
214 |
|
---|
215 | !-------------------------------------------------------------
|
---|
216 | ! 3. Check GFZ .dat and .dsc input files exist;
|
---|
217 | ! make output file name if not given on command line
|
---|
218 | !-------------------------------------------------------------
|
---|
219 |
|
---|
220 | INQUIRE ( FILE=datfile, EXIST=exists )
|
---|
221 | IF ( .NOT. exists ) &
|
---|
222 | CALL message ( msg_fatal, "GFZ input file " // TRIM(datfile) // &
|
---|
223 | " not found" )
|
---|
224 |
|
---|
225 | i = INDEX ( datfile, ".dat" )
|
---|
226 | IF ( i == 0 ) &
|
---|
227 | CALL message ( msg_fatal, "GFZ input file " // TRIM(datfile) // &
|
---|
228 | " not of type '.dat'.\n" // &
|
---|
229 | "Check input file type." )
|
---|
230 |
|
---|
231 | dscfile = datfile(1:i-1)//".dsc"
|
---|
232 | INQUIRE ( FILE=dscfile, EXIST=exists )
|
---|
233 | IF ( .NOT. exists ) &
|
---|
234 | CALL message ( msg_fatal, "GFZ input file " // TRIM(dscfile) // &
|
---|
235 | " not found" )
|
---|
236 |
|
---|
237 | IF ( opfile == " " ) THEN
|
---|
238 | j = INDEX(datfile, "/", BACK=.TRUE.)
|
---|
239 | opfile = datfile(j+1:i-1)//".nc"
|
---|
240 | END IF
|
---|
241 |
|
---|
242 | !-------------------------------------------------------------
|
---|
243 | ! 4. Read data (.dat) file
|
---|
244 | !-------------------------------------------------------------
|
---|
245 |
|
---|
246 | CALL message ( msg_info, "Reading file " // TRIM(datfile) )
|
---|
247 |
|
---|
248 | OPEN ( UNIT=funit, &
|
---|
249 | FILE=datfile, &
|
---|
250 | STATUS="OLD", &
|
---|
251 | ACTION="READ" )
|
---|
252 |
|
---|
253 | !-------------------------------------------------------------
|
---|
254 | ! 4.1 Read DAT file header data & extract no. of points in
|
---|
255 | ! data section plus other meta-info.
|
---|
256 | !-------------------------------------------------------------
|
---|
257 |
|
---|
258 | DO
|
---|
259 | READ ( UNIT=funit, FMT="(A)", IOSTAT=iostatus ) line
|
---|
260 | IF ( iostatus /= 0 .OR. &
|
---|
261 | line(1:1) /= "#" ) EXIT
|
---|
262 |
|
---|
263 | CALL To_Upper ( Line )
|
---|
264 | key = line(2:30)
|
---|
265 | arg = ADJUSTL(line(31:))
|
---|
266 |
|
---|
267 | SELECT CASE (key)
|
---|
268 | CASE ("NUMBER OF DATA LINES")
|
---|
269 | READ ( arg, FMT=* ) NLevs
|
---|
270 |
|
---|
271 | CASE ("STARTTIME(UTC)", "STARTTIME (UTC)") ! Date/Time of start of occultation (& secs since midnight)
|
---|
272 | READ ( arg, FMT="(I4,5(1X,I2))" ) ROdata%DTocc%Year, &
|
---|
273 | ROdata%DTocc%Month, &
|
---|
274 | ROdata%DTocc%Day, &
|
---|
275 | ROdata%DTocc%Hour, &
|
---|
276 | ROdata%DTocc%Minute, &
|
---|
277 | ROdata%DTocc%Second
|
---|
278 | ROdata%DTocc%Msec = 000
|
---|
279 | sTime = ((ROdata%DTocc%Hour*60.0_dp) &
|
---|
280 | + ROdata%DTocc%Minute)*60.0_dp &
|
---|
281 | + ROdata%DTocc%Second
|
---|
282 |
|
---|
283 | CASE ("ENDTIME(UTC)","ENDTIME (UTC)") ! Date/Time of end of occultation (secs since midnight)
|
---|
284 | READ ( arg, FMT="(10X,3(1X,I2))" ) Hour, Minute, Second
|
---|
285 | eTime = ((Hour*60.0_dp) &
|
---|
286 | + Minute)*60.0_dp &
|
---|
287 | + Second
|
---|
288 |
|
---|
289 | CASE ("OCCSAT(PRN)") ! GNSS (GPS) satellite ID
|
---|
290 | READ ( arg, FMT=* ) SatID
|
---|
291 | WRITE ( ROdata%GNS_ID, FMT="(A1,I3.3)" ) "G", SatID
|
---|
292 |
|
---|
293 | CASE ("OCCULTATION DIRECTION") ! Azimuth angle GNSS-->LEO (deg) (if not in DSC)
|
---|
294 | READ ( arg, FMT=* ) ROdata%GeoRef%Azimuth
|
---|
295 |
|
---|
296 | CASE ("ALT_MSL(KM)|LATITUDE(DEG)|LON")
|
---|
297 | lev1a_exists = .FALSE.
|
---|
298 | CALL message ( msg_diag, "File contains Level 1b, 2a, 2b data" )
|
---|
299 |
|
---|
300 | IF (INDEX(arg, "BA L1 (RAD)|BA L2 (RAD)") .NE. 0) THEN
|
---|
301 | l1l2_exists = .TRUE.
|
---|
302 | CALL message ( msg_diag, "File contains Level L1, L2 bending angle data" )
|
---|
303 | END IF
|
---|
304 |
|
---|
305 | CASE(" T|SNR_CA|SNR_P1|SNR_P2|X_LEO")
|
---|
306 | lev1a_exists = .TRUE.
|
---|
307 | CALL message ( msg_diag, "File contains Level 1a data" )
|
---|
308 | NLevs = -1 ! Find number of entries in file
|
---|
309 | DO
|
---|
310 | READ ( UNIT=funit, FMT="(A)", IOSTAT=iostatus ) line
|
---|
311 | IF (iostatus /= 0) THEN
|
---|
312 | EXIT
|
---|
313 | ENDIF
|
---|
314 | NLevs = NLevs + 1
|
---|
315 | END DO
|
---|
316 | DO i=1,Nlevs+1
|
---|
317 | BACKSPACE (UNIT=funit)
|
---|
318 | END DO
|
---|
319 |
|
---|
320 | CASE DEFAULT
|
---|
321 | END SELECT
|
---|
322 | END DO
|
---|
323 | IF ( iostatus == 0 ) BACKSPACE ( UNIT=funit )
|
---|
324 |
|
---|
325 | !-------------------------------------------------------------
|
---|
326 | ! 4.2 Initialise ROPP structures & fill in static header data
|
---|
327 | ! if not in DAT or DSC files
|
---|
328 | !-------------------------------------------------------------
|
---|
329 |
|
---|
330 | IF ( lev1a_exists ) THEN
|
---|
331 | CALL ropp_io_init ( ROdata, NLevs, 0, 0, 0, 0, 0 )
|
---|
332 | ALLOCATE ( lcf(NLevs) )
|
---|
333 | ELSE
|
---|
334 | CALL ropp_io_init ( ROdata, 0, NLevs, NLevs, 0, 0, 0 )
|
---|
335 | END IF
|
---|
336 |
|
---|
337 | ROdata%Processing_Centre = "GFZ Helmholtz Centre, Potsdam"
|
---|
338 | ROdata%Overall_Qual = 100.0_dp
|
---|
339 |
|
---|
340 | !-------------------------------------------------------------
|
---|
341 | ! 4.3 Read levels data
|
---|
342 | !-------------------------------------------------------------
|
---|
343 |
|
---|
344 | DO i = 1, NLevs
|
---|
345 |
|
---|
346 | IF ( lev1a_exists ) THEN
|
---|
347 | READ ( UNIT=funit, &
|
---|
348 | FMT=*, &
|
---|
349 | IOSTAT=iostatus ) ROdata%Lev1a%dtime(i), &
|
---|
350 | ROdata%Lev1a%snr_L1ca(i), &
|
---|
351 | ROdata%Lev1a%snr_L1p(i), &
|
---|
352 | ROdata%Lev1a%snr_L2p(i), &
|
---|
353 | ROdata%Lev1a%r_leo(i,:), &
|
---|
354 | ROdata%Lev1a%v_leo(i,:), &
|
---|
355 | ROdata%Lev1a%r_gns(i,:), &
|
---|
356 | ROdata%Lev1a%v_gns(i,:), &
|
---|
357 | phaseLC, &
|
---|
358 | ROdata%Lev1a%phase_L1(i), &
|
---|
359 | ROdata%Lev1a%phase_L2(i), &
|
---|
360 | lcf(i)
|
---|
361 | ELSE
|
---|
362 | IF (l1l2_exists ) THEN
|
---|
363 | READ ( UNIT=funit, &
|
---|
364 | FMT=*, &
|
---|
365 | IOSTAT=iostatus ) ROdata%Lev2a%Alt_Refrac(i), &
|
---|
366 | ROdata%Lev1b%Lat_tp(i), &
|
---|
367 | ROdata%Lev1b%Lon_tp(i), &
|
---|
368 | ROdata%Lev2a%Refrac(i), &
|
---|
369 | density, &
|
---|
370 | pressure, &
|
---|
371 | ROdata%Lev2a%Dry_Temp(i), &
|
---|
372 | basmth, &
|
---|
373 | ROdata%Lev1b%Impact(i), &
|
---|
374 | alpha, beta, gamma, &
|
---|
375 | snr1, snr2, qflag, &
|
---|
376 | ROdata%Lev2a%Geop_Refrac(i), &
|
---|
377 | ROdata%Lev1b%Bangle(i), &
|
---|
378 | ROdata%Lev1b%Bangle_L1(i), &
|
---|
379 | ROdata%Lev1b%Bangle_L2(i)
|
---|
380 |
|
---|
381 | ELSE
|
---|
382 | READ ( UNIT=funit, &
|
---|
383 | FMT=*, &
|
---|
384 | IOSTAT=iostatus ) ROdata%Lev2a%Alt_Refrac(i), &
|
---|
385 | ROdata%Lev1b%Lat_tp(i), &
|
---|
386 | ROdata%Lev1b%Lon_tp(i), &
|
---|
387 | ROdata%Lev2a%Refrac(i), &
|
---|
388 | density, &
|
---|
389 | pressure, &
|
---|
390 | ROdata%Lev2a%Dry_Temp(i), &
|
---|
391 | basmth, &
|
---|
392 | ROdata%Lev1b%Impact(i), &
|
---|
393 | alpha, beta, gamma, &
|
---|
394 | snr1, snr2, qflag, &
|
---|
395 | ROdata%Lev2a%Geop_Refrac(i), &
|
---|
396 | ROdata%Lev1b%Bangle(i)
|
---|
397 | END IF
|
---|
398 | END IF
|
---|
399 |
|
---|
400 | IF ( iostatus /= 0 ) EXIT
|
---|
401 | END DO
|
---|
402 |
|
---|
403 | CLOSE ( UNIT=funit )
|
---|
404 |
|
---|
405 | IF ( iostatus > 0 ) THEN
|
---|
406 | CALL message ( msg_fatal, "I/O error while reading DAT file" )
|
---|
407 | END IF
|
---|
408 |
|
---|
409 | !-------------------------------------------------------------
|
---|
410 | ! 4.4 Copy/convert units to ROPP standard
|
---|
411 | !-------------------------------------------------------------
|
---|
412 |
|
---|
413 | IF ( lev1a_exists ) THEN
|
---|
414 | ROdata%Lev1a%r_leo(:,:) = ROdata%Lev1a%r_leo(:,:) * KMtoM
|
---|
415 | ROdata%Lev1a%v_leo(:,:) = ROdata%Lev1a%v_leo(:,:) * KMtoM
|
---|
416 | ROdata%Lev1a%r_gns(:,:) = ROdata%Lev1a%r_gns(:,:) * KMtoM
|
---|
417 | ROdata%Lev1a%v_gns(:,:) = ROdata%Lev1a%v_gns(:,:) * KMtoM
|
---|
418 | ROdata%Lev1a%phase_qual(:) = 100.0_dp
|
---|
419 | ROdata%Lev1a%reference_frame%r_leo = "ECI"
|
---|
420 | ROdata%Lev1a%reference_frame%r_gns = "ECI"
|
---|
421 | ELSE
|
---|
422 | ROdata%Lev1b%Impact(:) = ROdata%Lev1b%Impact(:) * KMtoM
|
---|
423 | ROdata%Lev1b%Bangle_Qual(:) = 100.0_dp
|
---|
424 | ROdata%Lev2a%Alt_Refrac(:) = ROdata%Lev2a%Alt_Refrac(:) * KMtoM
|
---|
425 | ROdata%Lev2a%Refrac_Qual(:) = 100.0_dp
|
---|
426 | ROdata%Lev2a%Dry_Temp(:) = ROdata%Lev2a%Dry_Temp(:) + CtoK
|
---|
427 | END IF
|
---|
428 |
|
---|
429 | !-------------------------------------------------------------
|
---|
430 | ! 4.5 Add lost carrier flag data (Level 1a)
|
---|
431 | !-------------------------------------------------------------
|
---|
432 |
|
---|
433 | IF ( lev1a_exists ) THEN
|
---|
434 | CALL ropp_io_addvar ( ROdata, name = "lcf", &
|
---|
435 | long_name= "Lost carrier flag", &
|
---|
436 | units = " ", &
|
---|
437 | range = (/0.0_dp, 1.0_dp/), &
|
---|
438 | data = lcf )
|
---|
439 | DEALLOCATE ( lcf )
|
---|
440 | END IF
|
---|
441 |
|
---|
442 | !-------------------------------------------------------------
|
---|
443 | ! 5. Read DSC file
|
---|
444 | !-------------------------------------------------------------
|
---|
445 |
|
---|
446 | CALL message ( msg_info, "Reading file " // TRIM(dscfile) )
|
---|
447 | OPEN ( UNIT=funit, &
|
---|
448 | FILE=dscfile, &
|
---|
449 | STATUS="OLD", &
|
---|
450 | ACTION="READ" )
|
---|
451 |
|
---|
452 | !-------------------------------------------------------------
|
---|
453 | ! 5.1 Parse lines for key words and extract values for those
|
---|
454 | ! meta-data that are not in the DAT file
|
---|
455 | !-------------------------------------------------------------
|
---|
456 |
|
---|
457 | setting_occ = .TRUE.
|
---|
458 |
|
---|
459 | DO
|
---|
460 | READ ( UNIT=funit, FMT="(A)", IOSTAT=iostatus ) line
|
---|
461 | IF ( iostatus /= 0 ) EXIT
|
---|
462 |
|
---|
463 | CALL To_Upper ( Line )
|
---|
464 | i = INDEX ( line, "=" ) + 1
|
---|
465 | IF ( i < 3 ) CYCLE
|
---|
466 | key = line(1:i-2)
|
---|
467 |
|
---|
468 | j = INDEX ( line, ';' ) - 1
|
---|
469 | IF ( j < i ) j = LEN_TRIM ( line )
|
---|
470 | arg = ADJUSTL(line(i:j))
|
---|
471 |
|
---|
472 | SELECT CASE (key)
|
---|
473 |
|
---|
474 | ! DSC file has Processing Date but not the Time. ropp_io_init will have
|
---|
475 | ! intialised Processing Date/Time to current time; if Date in DSC file
|
---|
476 | ! is not today, use it & set Time to the end of the day, else leave
|
---|
477 | ! current time as processing time.
|
---|
478 |
|
---|
479 | CASE ("GENERATION DATE") ! Date/Time of processing
|
---|
480 | READ ( arg, FMT="(I4,2(1X,I2))" ) Year, Month, Day
|
---|
481 | IF ( Year /= ROdata%DTpro%Year .OR. &
|
---|
482 | Month /= ROdata%DTpro%Month .OR. &
|
---|
483 | Day /= ROdata%DTpro%Day ) THEN
|
---|
484 | ROdata%DTpro%Year = Year
|
---|
485 | ROdata%DTpro%Month = Month
|
---|
486 | ROdata%DTpro%Day = Day
|
---|
487 | ROdata%DTpro%Hour = 23
|
---|
488 | ROdata%DTpro%Minute = 59
|
---|
489 | ROdata%DTpro%Second = 59
|
---|
490 | ROdata%DTpro%Msec = 999
|
---|
491 | ELSE
|
---|
492 | ROdata%DTpro%Msec = 000
|
---|
493 | END IF
|
---|
494 |
|
---|
495 | CASE ("LOCAL RADIUS OF CURVATURE") ! Earth's radius of curvature at occ. point (m)
|
---|
496 | READ ( arg, FMT=* ) ROdata%GeoRef%RoC
|
---|
497 | ROdata%GeoRef%RoC = ROdata%GeoRef%RoC * KMtoM
|
---|
498 |
|
---|
499 | CASE ("GEOID UNDULATION EGM96") ! Geoid undulation (EGM96-WGS-84) at occ. point (m)
|
---|
500 | READ ( arg, FMT=* ) ROdata%GeoRef%Undulation
|
---|
501 |
|
---|
502 | CASE ("MISSION") ! LEO Satellite IDx
|
---|
503 |
|
---|
504 | ! Older GFZ DSC files did not contain the PRODUCT_ID keyword, so we
|
---|
505 | ! attempt to extact it here if PRODUCT_ID is not present (if it is,
|
---|
506 | ! it will be at the top of the file and processed before this line).
|
---|
507 | ! Unfortunately, older DSC files always had "mission=CHAMP;" even for
|
---|
508 | ! GRACE-A & TerraSAR-X, so MISSION wasn't very useful either. [Even today,
|
---|
509 | ! mission=GRACE doesn't distinguish the (potential) -A from -B, but we
|
---|
510 | ! can assume GRACE-A.] Instead we detect the satellite ID from the DAT
|
---|
511 | ! file basename. Normally this is the same as the PRODUCT_ID. NB: This
|
---|
512 | ! only works if the file has not been renamed!
|
---|
513 |
|
---|
514 | IF ( no_productid ) THEN ! if no PRODUCT_ID key present (thus far)
|
---|
515 | SELECT CASE (arg)
|
---|
516 | CASE ( "CHAMP" ) ! don't trust this! Use the file name
|
---|
517 | i = LEN_TRIM(datfile)
|
---|
518 | DO WHILE ( i > 0 .AND. &
|
---|
519 | datfile(i:i) /= "/" )
|
---|
520 | i = i - 1
|
---|
521 | END DO
|
---|
522 | arg = datfile(i+1:)
|
---|
523 | CALL To_Upper ( arg )
|
---|
524 | SELECT CASE (arg(1:2))
|
---|
525 | CASE ("CH")
|
---|
526 | ROdata%LEO_ID = "CHMP"
|
---|
527 | CASE ("GA")
|
---|
528 | ROdata%LEO_ID = "GRAA"
|
---|
529 | CASE ("GB")
|
---|
530 | ROdata%LEO_ID = "GRAB"
|
---|
531 | CASE ("TS")
|
---|
532 | ROdata%LEO_ID = "TSRX"
|
---|
533 | CASE ("TD")
|
---|
534 | ROdata%LEO_ID = "TDMX"
|
---|
535 | CASE DEFAULT
|
---|
536 | ROdata%LEO_ID = "UNKN"
|
---|
537 | END SELECT
|
---|
538 | CASE ("GRACE") ! potentially ambiguous but assume -A
|
---|
539 | ROdata%LEO_ID = "GRAA"
|
---|
540 | CASE ("TERRASAR-X")
|
---|
541 | ROdata%LEO_ID = "TSRX"
|
---|
542 | CASE ("TANDEM-X")
|
---|
543 | ROdata%LEO_ID = "TDMX"
|
---|
544 | CASE DEFAULT
|
---|
545 | ROdata%LEO_ID = "UNKN"
|
---|
546 | END SELECT
|
---|
547 | END IF
|
---|
548 |
|
---|
549 | CASE ("OCCULTATION DIRECTION") ! Azimuth angle GNSS-->LEO (deg) (if not in DAT)
|
---|
550 | READ ( arg, FMT=* ) ROdata%GeoRef%Azimuth
|
---|
551 |
|
---|
552 | CASE ("START LATITUDE") ! Start latitude
|
---|
553 | READ ( arg, FMT=* ) Start_Lat
|
---|
554 |
|
---|
555 | CASE ("START LONGITUDE") ! Start longitude
|
---|
556 | READ ( arg, FMT=* ) Start_Lon
|
---|
557 |
|
---|
558 | CASE ("PRODUCT_ID") ! LEO satellite ID
|
---|
559 | SELECT CASE (arg(1:2))
|
---|
560 | CASE ("CH")
|
---|
561 | ROdata%LEO_ID = "CHMP"
|
---|
562 | CASE ("GA")
|
---|
563 | ROdata%LEO_ID = "GRAA"
|
---|
564 | CASE ("GB")
|
---|
565 | ROdata%LEO_ID = "GRAB"
|
---|
566 | CASE ("TS")
|
---|
567 | ROdata%LEO_ID = "TSRX"
|
---|
568 | CASE ("TD")
|
---|
569 | ROdata%LEO_ID = "TDMX"
|
---|
570 | CASE DEFAULT
|
---|
571 | ROdata%LEO_ID = "UNKN"
|
---|
572 | END SELECT
|
---|
573 | no_productid = .FALSE.
|
---|
574 |
|
---|
575 | CASE ("PROCESSING FACILITY")
|
---|
576 | ROdata%Processing_Centre = arg
|
---|
577 |
|
---|
578 | CASE ("SETTING(1)/RISING OCCULTATION") ! rising or setting occultation
|
---|
579 | IF ( arg /= "1" ) setting_occ = .FALSE.
|
---|
580 |
|
---|
581 | CASE ("SOFTWARE PACKAGE") ! Software ID (major) "POCS-n.n"
|
---|
582 | READ ( arg(6:), FMT=*, IOSTAT=iostatus ) SWver
|
---|
583 | IF ( iostatus /= 0 ) SWver = 0.0
|
---|
584 |
|
---|
585 | CASE ("REVISION") ! Software ID (minor)
|
---|
586 | READ ( arg, FMT=* ) SWrev
|
---|
587 |
|
---|
588 | CASE DEFAULT
|
---|
589 |
|
---|
590 | END SELECT
|
---|
591 |
|
---|
592 | END DO
|
---|
593 |
|
---|
594 | CLOSE ( UNIT=funit )
|
---|
595 |
|
---|
596 | IF ( iostatus > 0 ) THEN
|
---|
597 | CALL message ( msg_fatal, "I/O error while reading DSC file" )
|
---|
598 | END IF
|
---|
599 |
|
---|
600 | !-------------------------------------------------------------
|
---|
601 | ! 5.2 Convert GFZ parameters to ROPP standard
|
---|
602 | !-------------------------------------------------------------
|
---|
603 |
|
---|
604 | WRITE ( ROdata%Software_Version, FMT="(F6.3)" ) SWver + SWrev * 0.001_dp
|
---|
605 | IF ( SWver < 10.0 ) THEN
|
---|
606 | ROdata%Software_Version = "V0"//ADJUSTL(ROdata%Software_Version)
|
---|
607 | ELSE
|
---|
608 | ROdata%Software_Version = "V" //ADJUSTL(ROdata%Software_Version)
|
---|
609 | END IF
|
---|
610 |
|
---|
611 | ! If Lev1a data, take nominal lat/lon from occulation start lat/lon.
|
---|
612 | ! Otherwise, take nominal lat/lon items from lowest point in (Lev1b) profile
|
---|
613 | ! with time offset of zero for rising occultations or end-start time for
|
---|
614 | ! setting. Set PCD rising bit accordingly.
|
---|
615 |
|
---|
616 | IF ( lev1a_exists ) THEN
|
---|
617 | ROdata%GeoRef%Lat = Start_Lat
|
---|
618 | ROdata%GeoRef%Lon = Start_Lon
|
---|
619 | ELSE
|
---|
620 | IF ( ROdata%Lev2a%Alt_Refrac(1) < &
|
---|
621 | ROdata%Lev2a%Alt_Refrac(NLevs) ) THEN
|
---|
622 | ROdata%GeoRef%Lat = ROdata%Lev1b%Lat_tp(1)
|
---|
623 | ROdata%GeoRef%Lon = ROdata%Lev1b%Lon_tp(1)
|
---|
624 | ELSE
|
---|
625 | ROdata%GeoRef%Lat = ROdata%Lev1b%Lat_tp(Nlevs)
|
---|
626 | ROdata%GeoRef%Lon = ROdata%Lev1b%Lon_tp(Nlevs)
|
---|
627 | END IF
|
---|
628 | END IF
|
---|
629 |
|
---|
630 | ROdata%PCD = 0
|
---|
631 | IF ( setting_occ ) THEN
|
---|
632 | IF ( eTime < sTime ) eTime = eTime + SecsPerDay ! in case event spans midnight
|
---|
633 | ROdata%GeoRef%Time_Offset = eTime - sTime
|
---|
634 | ELSE
|
---|
635 | ROdata%GeoRef%Time_Offset = 0.0
|
---|
636 | ROdata%PCD = IBSET(ROdata%PCD,PCD_rising)
|
---|
637 | END IF
|
---|
638 |
|
---|
639 | CALL ropp_io_ascend ( ROdata )
|
---|
640 |
|
---|
641 | !-------------------------------------------------------------
|
---|
642 | ! 6. Generate ROPP Occultation ID; optionally dump some key data
|
---|
643 | !-------------------------------------------------------------
|
---|
644 |
|
---|
645 | CALL ropp_io_occid ( ROdata )
|
---|
646 | CALL message ( msg_info, "Profile 1: "//ROdata%occ_id )
|
---|
647 | WRITE ( outstr, FMT="(F6.2,',',F7.2)" ) ROdata%GeoRef%Lat, ROdata%GeoRef%Lon
|
---|
648 | CALL message ( msg_diag, " Latitude/Longitude : "//TRIM(outstr) )
|
---|
649 | WRITE ( number, FMT="(I6)") ROdata%Lev1a%Npoints
|
---|
650 | CALL message ( msg_diag, " No. of phase/SNR samples : "//TRIM(number) )
|
---|
651 | WRITE ( number, FMT="(I6)" ) ROdata%Lev1b%Npoints
|
---|
652 | CALL message ( msg_diag, " No. of bending angle samples : "//TRIM(number) )
|
---|
653 | WRITE ( number, FMT="(I6)" ) ROdata%Lev2a%Npoints
|
---|
654 | CALL message ( msg_diag, " No. of refractivity samples : "//TRIM(number) )
|
---|
655 | WRITE ( number, FMT="(I6)" ) ROdata%Lev2b%Npoints
|
---|
656 | CALL message ( msg_diag, " No. of geophysical samples : "//TRIM(number) )
|
---|
657 | WRITE ( number, FMT="(I6)" ) ROdata%Lev2c%Npoints
|
---|
658 | CALL message ( msg_diag, " No. of surface geo. samples : "//TRIM(number) )
|
---|
659 | WRITE ( number, FMT="(I6)" ) ROdata%Lev2d%Npoints
|
---|
660 | CALL message ( msg_diag, " No. of model coeff. levels : "//TRIM(number) )
|
---|
661 |
|
---|
662 | !-------------------------------------------------------------
|
---|
663 | ! 7. Write ROPP netCDF file
|
---|
664 | !-------------------------------------------------------------
|
---|
665 |
|
---|
666 | CALL message ( msg_info, "Writing " // TRIM(opfile) )
|
---|
667 | CALL ropp_io_write ( ROdata, file=opfile, ierr=iostatus )
|
---|
668 | IF ( iostatus > 0 ) THEN
|
---|
669 | CALL message ( msg_warn, "I/O error while writing output file" )
|
---|
670 | END IF
|
---|
671 |
|
---|
672 | !-------------------------------------------------------------
|
---|
673 | ! 8. Tidy up - deallocate structures & free memory
|
---|
674 | !-------------------------------------------------------------
|
---|
675 |
|
---|
676 | CALL ropp_io_free ( ROdata )
|
---|
677 | CALL message ( msg_noin, " " )
|
---|
678 | CALL EXIT(msg_exit_status)
|
---|
679 |
|
---|
680 | CONTAINS
|
---|
681 |
|
---|
682 | !-------------------------------------------------------------------------------
|
---|
683 | ! 9. Usage (help) information
|
---|
684 | !-------------------------------------------------------------------------------
|
---|
685 |
|
---|
686 | SUBROUTINE Usage()
|
---|
687 | PRINT *, 'Purpose:'
|
---|
688 | PRINT *, ' Convert a GFZ PD or NRT DAT/DSC pair of RO files to a'
|
---|
689 | PRINT *, ' ROPP netCDF file'
|
---|
690 | PRINT *, 'Usage:'
|
---|
691 | PRINT *, ' > gfz2ropp ip_file [-o op_file] [-d] [-h] [-v]'
|
---|
692 | PRINT *, ' where ip_file is a GFZ formated PD or NRT .dat file name with an'
|
---|
693 | PRINT *, ' assumed companion .dsc file with the same name and in the same'
|
---|
694 | PRINT *, ' directory.'
|
---|
695 | PRINT *, 'Options:'
|
---|
696 | PRINT *, ' -o specifies the output (netCDF) file name'
|
---|
697 | PRINT *, ' -d prints out some additional diagnostics to stdout'
|
---|
698 | PRINT *, ' -h this help'
|
---|
699 | PRINT *, ' -v version information'
|
---|
700 | PRINT *, 'Defaults:'
|
---|
701 | PRINT *, ' Input file name : required'
|
---|
702 | PRINT *, ' Output file name : from ip_file but .nc and in PWD'
|
---|
703 | PRINT *, 'See gfz2ropp(1) for details.'
|
---|
704 | PRINT *, ''
|
---|
705 | END SUBROUTINE Usage
|
---|
706 |
|
---|
707 | !-------------------------------------------------------------------------------
|
---|
708 | ! 10. Version information
|
---|
709 | !-------------------------------------------------------------------------------
|
---|
710 |
|
---|
711 | SUBROUTINE version_info()
|
---|
712 | CHARACTER (LEN=40) :: version
|
---|
713 | version = ropp_io_version()
|
---|
714 | PRINT *, 'gfz2ropp - convert GFZ RO data files to ROPP netCDF'
|
---|
715 | PRINT *, ''
|
---|
716 | PRINT *, 'This program is part of ROPP (IO) Release ' // TRIM(version)
|
---|
717 | PRINT *, ''
|
---|
718 | END SUBROUTINE version_info
|
---|
719 |
|
---|
720 | END Program gfz2ropp
|
---|