| 1 | ! $Id: gfz2ropp.f90 2105 2009-05-21 16:23:48Z frhl $
|
|---|
| 2 |
|
|---|
| 3 | !****x* Programs/gfz2ropp *
|
|---|
| 4 | !
|
|---|
| 5 | ! SYNOPSIS
|
|---|
| 6 | ! Convert GFZ NRT DAT/DSC files to ROPP netCDF
|
|---|
| 7 | !
|
|---|
| 8 | ! > gfz2ropp <gfz-nrt.dat> [-o opfile] [-d] [-h|?] [-v]
|
|---|
| 9 | !
|
|---|
| 10 | ! ARGUMENTS
|
|---|
| 11 | ! gfz-nrt.dat - GFZ 'NRT' DAT (.dat) file containing Level 1b,2a,2b RO
|
|---|
| 12 | ! profiles.
|
|---|
| 13 | ! May include a path. The companion DSC file containing
|
|---|
| 14 | ! meta-data is assumed to be in the same path and have
|
|---|
| 15 | ! the same name at the DAT file, but with a type of .dsc.
|
|---|
| 16 | ! There is no default for this argument.
|
|---|
| 17 | ! -o - specifies the output netCDF file name. The default name
|
|---|
| 18 | ! is the same as the DAT/DSC file path/name, but with a
|
|---|
| 19 | ! type of .nc
|
|---|
| 20 | ! -d - writes additional diagnostic information to stdout
|
|---|
| 21 | ! -h or ? - writes usage help information to stdout (and does
|
|---|
| 22 | ! nothing more)
|
|---|
| 23 | ! -v - write program version to stdout (and does nothing more)
|
|---|
| 24 | !
|
|---|
| 25 | ! INPUTS
|
|---|
| 26 | ! Pair of GFZ NRT .dat (profile) and .dsc (meta information)
|
|---|
| 27 | !
|
|---|
| 28 | ! OUTPUTS
|
|---|
| 29 | ! ROPP netCDF file - As given with the -o option, or defaults to the
|
|---|
| 30 | ! same path and file name as for input DAT file,
|
|---|
| 31 | ! but with type .nc
|
|---|
| 32 | !
|
|---|
| 33 | ! CALLS
|
|---|
| 34 | ! ropp_io_free
|
|---|
| 35 | ! ropp_io_init
|
|---|
| 36 | ! ropp_io_occid
|
|---|
| 37 | ! ropp_io_write
|
|---|
| 38 | ! ropp_io_rangecheck
|
|---|
| 39 | !
|
|---|
| 40 | ! DESCRIPTION
|
|---|
| 41 | ! Conversion from GFZ native-format GPSRO 'NRT' data (ROPP Levels 1b,2a,2b)
|
|---|
| 42 | ! to ROPP netCDF format. Input is the pair of DAT (data) & DCS (description)
|
|---|
| 43 | ! files; the profiles are taken from the former, and meta-data (non-profile
|
|---|
| 44 | ! header info) from the latter. The data is then written out to a ROPP-
|
|---|
| 45 | ! standard netCDF file. Only the name of the DAT file is given on the
|
|---|
| 46 | ! command line; the companion DSC file is assumed to be in the same path and
|
|---|
| 47 | ! have the same name at the DAT file, but with a type of .dsc.
|
|---|
| 48 | !
|
|---|
| 49 | ! TODO
|
|---|
| 50 | ! Incorporate GFZ 'PD' pair of DAT/DSC files so as to include Level 1a
|
|---|
| 51 | ! (phase/SNR/POD) data into ROPP netCDF.
|
|---|
| 52 | !
|
|---|
| 53 | ! REFERENCES
|
|---|
| 54 | ! ROPP Interface File Format. Ref: SAF/GRAS/METO/FMT/ROPP/001
|
|---|
| 55 | ! ROPP User Guide. Ref: SAF/GRAS/METO/UG/ROPP/002
|
|---|
| 56 | !
|
|---|
| 57 | ! AUTHOR
|
|---|
| 58 | ! Met Office, Exeter, UK.
|
|---|
| 59 | ! Any comments on this software should be given via the GRAS SAF
|
|---|
| 60 | ! Helpdesk at http://www.grassaf.org
|
|---|
| 61 | !
|
|---|
| 62 | ! COPYRIGHT
|
|---|
| 63 | ! (c) EUMETSAT. All rights reserved.
|
|---|
| 64 | ! For further details please refer to the file COPYRIGHT
|
|---|
| 65 | ! which you should have received as part of this distribution.
|
|---|
| 66 | !
|
|---|
| 67 | !****
|
|---|
| 68 |
|
|---|
| 69 | PROGRAM gfz2ropp
|
|---|
| 70 |
|
|---|
| 71 | USE ropp_utils, ONLY: To_Upper
|
|---|
| 72 | USE ropp_io_types, ONLY: ROprof, &
|
|---|
| 73 | PCD_rising, &
|
|---|
| 74 | wp
|
|---|
| 75 | USE ropp_io, ONLY: ropp_io_free, &
|
|---|
| 76 | ropp_io_init, &
|
|---|
| 77 | ropp_io_occid, &
|
|---|
| 78 | ropp_io_write, &
|
|---|
| 79 | ropp_io_addvar
|
|---|
| 80 |
|
|---|
| 81 | IMPLICIT NONE
|
|---|
| 82 |
|
|---|
| 83 | ! Fixed parameters
|
|---|
| 84 |
|
|---|
| 85 | ! 'Version' is the version number of this complete application program
|
|---|
| 86 |
|
|---|
| 87 | CHARACTER (LEN=*), PARAMETER :: Version = "V3.0 1-June-2009"
|
|---|
| 88 | CHARACTER (LEN=1), PARAMETER :: SysEndDirChr = "/"
|
|---|
| 89 | INTEGER, PARAMETER :: funit = 11
|
|---|
| 90 | REAL(wp), PARAMETER :: CtoK = 273.15_wp
|
|---|
| 91 | REAL(wp), PARAMETER :: KMtoM = 1000.0_wp
|
|---|
| 92 | REAL(wp), PARAMETER :: SecsPerDay = 86400.0_wp
|
|---|
| 93 |
|
|---|
| 94 | ! Local variables
|
|---|
| 95 |
|
|---|
| 96 | TYPE(ROprof) :: ROdata ! RO main profile structure
|
|---|
| 97 |
|
|---|
| 98 | CHARACTER (LEN=256) :: prognam, arg ! Program name & command line argument
|
|---|
| 99 | CHARACTER (LEN=256) :: datfile, dscfile, opfile ! I/P & O/P file names
|
|---|
| 100 | CHARACTER (LEN=200) :: line ! Line read from I/P file
|
|---|
| 101 | CHARACTER (LEN=80) :: key ! key word(s) in DSC file
|
|---|
| 102 | INTEGER :: i, j ! Loop counters / indices
|
|---|
| 103 | INTEGER :: iarg ! Command line argument index
|
|---|
| 104 | INTEGER :: narg ! No. of command line arguments
|
|---|
| 105 | INTEGER :: iostatus ! I/O Status
|
|---|
| 106 | INTEGER :: NLevs ! Number of vertical points in DAT file
|
|---|
| 107 | INTEGER :: SatID ! Satellite ID
|
|---|
| 108 | INTEGER :: Year, Month, Day ! Processing date from DSC file
|
|---|
| 109 | INTEGER :: Hour, Minute, Second ! Occultation end time from DSC file
|
|---|
| 110 | INTEGER :: SWrev ! GFZ revision number
|
|---|
| 111 | LOGICAL :: exists ! File exists flag
|
|---|
| 112 | LOGICAL :: setting_occ ! .T. if a setting occultation
|
|---|
| 113 | LOGICAL :: DEBUG ! Diagnostics dump flag
|
|---|
| 114 | REAL(wp) :: SWver ! GFZ POCS software version number
|
|---|
| 115 | REAL(wp) :: sTime, eTime ! Start & end time of occultation (secs)
|
|---|
| 116 |
|
|---|
| 117 | INTEGER :: qflag ! parameters read but not used in ROPP
|
|---|
| 118 | REAL(wp) :: density, snr1, snr2, basmth ! parameters read but not used in ROPP
|
|---|
| 119 | REAL(wp) :: alpha, beta, gamma, phaseLC ! parameters read but not used in ROPP
|
|---|
| 120 |
|
|---|
| 121 | LOGICAL :: lev_1a_exist ! Reading Level1a data flag
|
|---|
| 122 | REAL(wp), DIMENSION(:), ALLOCATABLE :: LCF ! Lost carrier flag from Level 1a file
|
|---|
| 123 |
|
|---|
| 124 | ! Some compilers may need the following declaration to be commented out
|
|---|
| 125 | INTEGER :: IARGC
|
|---|
| 126 |
|
|---|
| 127 | !-------------------------------------------------------------
|
|---|
| 128 | ! 1. Initialise & parse command line options
|
|---|
| 129 | !-------------------------------------------------------------
|
|---|
| 130 |
|
|---|
| 131 | lev_1a_exist = .false.
|
|---|
| 132 |
|
|---|
| 133 | CALL GETARG ( 0, ProgNam )
|
|---|
| 134 | i = LEN_TRIM(ProgNam)
|
|---|
| 135 | DO WHILE ( i > 0 .AND. &
|
|---|
| 136 | ProgNam(i:i) /= SysEndDirChr )
|
|---|
| 137 | i = i - 1
|
|---|
| 138 | END DO
|
|---|
| 139 | ProgNam = ProgNam(i+1:)
|
|---|
| 140 | IF ( ProgNam == " " ) ProgNam = "gfz2ropp"
|
|---|
| 141 |
|
|---|
| 142 | datfile = " " ! no default for i/p file name
|
|---|
| 143 | opfile = " " ! assume a default generated from i/p file name
|
|---|
| 144 | DEBUG = .FALSE. ! no diagnostic o/p
|
|---|
| 145 |
|
|---|
| 146 | narg = IARGC()
|
|---|
| 147 | iarg = 1
|
|---|
| 148 |
|
|---|
| 149 | DO WHILE ( iarg <= narg )
|
|---|
| 150 | CALL GETARG ( iarg, arg )
|
|---|
| 151 |
|
|---|
| 152 | SELECT CASE (arg)
|
|---|
| 153 | CASE ("-d","-D","--debug")
|
|---|
| 154 | DEBUG = .TRUE.
|
|---|
| 155 |
|
|---|
| 156 | CASE ("-h","-H","--help","?")
|
|---|
| 157 | narg = 0
|
|---|
| 158 | datfile = "dummy"
|
|---|
| 159 |
|
|---|
| 160 | CASE ("-o","-O","--output")
|
|---|
| 161 | iarg = iarg + 1
|
|---|
| 162 | CALL GETARG ( iarg, arg )
|
|---|
| 163 | opfile = arg
|
|---|
| 164 |
|
|---|
| 165 | CASE ("-v","-V","--version")
|
|---|
| 166 | WRITE ( *, FMT="(A/)" ) TRIM(ProgNam)//": Version "//TRIM(Version)
|
|---|
| 167 | CALL EXIT(0)
|
|---|
| 168 |
|
|---|
| 169 | CASE DEFAULT
|
|---|
| 170 | datfile = arg
|
|---|
| 171 |
|
|---|
| 172 | END SELECT
|
|---|
| 173 |
|
|---|
| 174 | iarg = iarg + 1
|
|---|
| 175 | END DO
|
|---|
| 176 |
|
|---|
| 177 | IF ( datfile == " " ) THEN
|
|---|
| 178 | WRITE ( *, FMT="(/A/)" ) " *** No input file(s) specified ***"
|
|---|
| 179 | narg = 0
|
|---|
| 180 | END IF
|
|---|
| 181 |
|
|---|
| 182 | IF ( narg == 0 ) THEN
|
|---|
| 183 | WRITE ( *, * ) " "
|
|---|
| 184 | WRITE ( *, * ) "Purpose:"
|
|---|
| 185 | WRITE ( *, * ) " Convert a GFZ NRT DAT/DSC pair of RO files to a ROPP netCDF file"
|
|---|
| 186 | WRITE ( *, * ) "Usage:"
|
|---|
| 187 | WRITE ( *, * ) "> " // TRIM(prognam) // &
|
|---|
| 188 | " ip_file [-o op_file] [-d] [-h|?] [-v]"
|
|---|
| 189 | WRITE ( *, * ) " where ip_file is a GFZ formated NRT .dat file name with an assumed"
|
|---|
| 190 | WRITE ( *, * ) " companion .dsc file with the same name and in the same directory."
|
|---|
| 191 | WRITE ( *, * ) " -o specifies the output (netCDF) file name"
|
|---|
| 192 | WRITE ( *, * ) " -d prints out some additional diagnostics to stdout"
|
|---|
| 193 | WRITE ( *, * ) " -h (or ?) causes only this summary help to be output"
|
|---|
| 194 | WRITE ( *, * ) " -v outputs program version ID (and does nothing else)"
|
|---|
| 195 | WRITE ( *, * ) "Defaults:"
|
|---|
| 196 | WRITE ( *, * ) " Input file name : required"
|
|---|
| 197 | WRITE ( *, * ) " Output file name : from ip_file but .nc"
|
|---|
| 198 | WRITE ( *, * ) "See gfz2ropp(1) for details."
|
|---|
| 199 | WRITE ( *, * ) " "
|
|---|
| 200 | CALL EXIT(0)
|
|---|
| 201 | END IF
|
|---|
| 202 |
|
|---|
| 203 | !-------------------------------------------------------------
|
|---|
| 204 | ! 2. Check GFZ .dat and .dsc input files exist;
|
|---|
| 205 | ! make output file name if not given on command line
|
|---|
| 206 | !-------------------------------------------------------------
|
|---|
| 207 |
|
|---|
| 208 | INQUIRE ( FILE=datfile, EXIST=exists )
|
|---|
| 209 | IF ( .NOT. exists ) THEN
|
|---|
| 210 | WRITE ( *, FMT="(A/)" ) "*** GFZ input file " // &
|
|---|
| 211 | TRIM(datfile) // &
|
|---|
| 212 | " not found"
|
|---|
| 213 | CALL EXIT(1)
|
|---|
| 214 | ENDIF
|
|---|
| 215 |
|
|---|
| 216 | i = INDEX ( datfile, ".dat" )
|
|---|
| 217 | IF ( i == 0 ) THEN
|
|---|
| 218 | WRITE ( *, FMT="(A/)" ) "*** GFZ input file " // &
|
|---|
| 219 | TRIM(datfile) // &
|
|---|
| 220 | " not of type '.dat'"
|
|---|
| 221 | CALL EXIT(1)
|
|---|
| 222 | END IF
|
|---|
| 223 |
|
|---|
| 224 | dscfile = datfile(1:i-1)//".dsc"
|
|---|
| 225 | INQUIRE ( FILE=dscfile, EXIST=exists )
|
|---|
| 226 | IF ( .NOT. exists ) THEN
|
|---|
| 227 | WRITE ( *, FMT="(A/)" ) "*** GFZ input file " // &
|
|---|
| 228 | TRIM(dscfile) // &
|
|---|
| 229 | " not found"
|
|---|
| 230 | CALL EXIT(1)
|
|---|
| 231 | END IF
|
|---|
| 232 |
|
|---|
| 233 | IF ( opfile == " " ) opfile = datfile(1:i-1)//".nc"
|
|---|
| 234 |
|
|---|
| 235 | !-------------------------------------------------------------
|
|---|
| 236 | ! 3. Read data (.dat) file
|
|---|
| 237 | !-------------------------------------------------------------
|
|---|
| 238 |
|
|---|
| 239 | WRITE ( *, FMT="(A)" ) "Reading " // TRIM(datfile)
|
|---|
| 240 |
|
|---|
| 241 | OPEN ( UNIT=funit, &
|
|---|
| 242 | FILE=datfile, &
|
|---|
| 243 | STATUS="OLD", &
|
|---|
| 244 | ACTION="READ" )
|
|---|
| 245 |
|
|---|
| 246 | !-------------------------------------------------------------
|
|---|
| 247 | ! 3.1 Read DAT file header data & extract no. of points in
|
|---|
| 248 | ! data section plus other meta-info.
|
|---|
| 249 | !-------------------------------------------------------------
|
|---|
| 250 |
|
|---|
| 251 | DO
|
|---|
| 252 | READ ( UNIT=funit, FMT="(A)", IOSTAT=iostatus ) line
|
|---|
| 253 | IF ( iostatus /= 0 .OR. &
|
|---|
| 254 | line(1:1) /= "#" ) EXIT
|
|---|
| 255 |
|
|---|
| 256 | CALL To_Upper ( Line )
|
|---|
| 257 | key = line(2:30)
|
|---|
| 258 | arg = ADJUSTL(line(31:))
|
|---|
| 259 |
|
|---|
| 260 | SELECT CASE (key)
|
|---|
| 261 | CASE ("NUMBER OF DATA LINES")
|
|---|
| 262 | READ ( arg, FMT=* ) NLevs
|
|---|
| 263 |
|
|---|
| 264 | CASE ("STARTTIME(UTC)") ! Date/Time of start of occultation (& secs since midnight)
|
|---|
| 265 | READ ( arg, FMT="(I4,5(1X,I2))" ) ROdata%DTocc%Year, &
|
|---|
| 266 | ROdata%DTocc%Month, &
|
|---|
| 267 | ROdata%DTocc%Day, &
|
|---|
| 268 | ROdata%DTocc%Hour, &
|
|---|
| 269 | ROdata%DTocc%Minute, &
|
|---|
| 270 | ROdata%DTocc%Second
|
|---|
| 271 | ROdata%DTocc%Msec = 000
|
|---|
| 272 | sTime = ((ROdata%DTocc%Hour*60.0_wp) &
|
|---|
| 273 | + ROdata%DTocc%Minute)*60.0_wp &
|
|---|
| 274 | + ROdata%DTocc%Second
|
|---|
| 275 |
|
|---|
| 276 | CASE ("STARTTIME (UTC)") ! Date/Time of start of occultation (& secs since midnight)
|
|---|
| 277 | READ ( arg, FMT="(I4,5(1X,I2))" ) ROdata%DTocc%Year, &
|
|---|
| 278 | ROdata%DTocc%Month, &
|
|---|
| 279 | ROdata%DTocc%Day, &
|
|---|
| 280 | ROdata%DTocc%Hour, &
|
|---|
| 281 | ROdata%DTocc%Minute, &
|
|---|
| 282 | ROdata%DTocc%Second
|
|---|
| 283 | ROdata%DTocc%Msec = 000
|
|---|
| 284 | sTime = ((ROdata%DTocc%Hour*60.0_wp) &
|
|---|
| 285 | + ROdata%DTocc%Minute)*60.0_wp &
|
|---|
| 286 | + ROdata%DTocc%Second
|
|---|
| 287 |
|
|---|
| 288 | CASE ("ENDTIME(UTC)") ! Date/Time of end of occultation (secs since midnight)
|
|---|
| 289 | READ ( arg, FMT="(10X,3(1X,I2))" ) Hour, Minute, Second
|
|---|
| 290 | eTime = ((Hour*60.0_wp) &
|
|---|
| 291 | + Minute)*60.0_wp &
|
|---|
| 292 | + Second
|
|---|
| 293 |
|
|---|
| 294 | CASE ("ENDTIME (UTC)") ! Date/Time of end of occultation (secs since midnight)
|
|---|
| 295 | READ ( arg, FMT="(10X,3(1X,I2))" ) Hour, Minute, Second
|
|---|
| 296 | eTime = ((Hour*60.0_wp) &
|
|---|
| 297 | + Minute)*60.0_wp &
|
|---|
| 298 | + Second
|
|---|
| 299 |
|
|---|
| 300 | CASE ("OCCSAT(PRN)") ! GNSS (GPS) satellite ID
|
|---|
| 301 | READ ( arg, FMT=* ) SatID
|
|---|
| 302 | WRITE ( ROdata%GNS_ID, FMT="(A1,I3.3)" ) "G", SatID
|
|---|
| 303 |
|
|---|
| 304 | CASE ("OCCULTATION DIRECTION") ! Azimuth angle GNSS-->LEO (deg)
|
|---|
| 305 | READ ( arg, FMT=* ) ROdata%GeoRef%Azimuth
|
|---|
| 306 |
|
|---|
| 307 | CASE ("ALT_MSL(KM)|LATITUDE(DEG)|LON")
|
|---|
| 308 | lev_1a_exist = .false.
|
|---|
| 309 | WRITE(*,fmt="(A)") "Reading Level 1b, 2a, 2b data file"
|
|---|
| 310 |
|
|---|
| 311 | CASE(" T|SNR_CA|SNR_P1|SNR_P2|X_LEO")
|
|---|
| 312 | lev_1a_exist = .true.
|
|---|
| 313 | WRITE(*,fmt="(A)") "Reading Level 1a data file"
|
|---|
| 314 | NLevs = -1 ! Find number of entries in file
|
|---|
| 315 | DO
|
|---|
| 316 | READ ( UNIT=funit, FMT="(A)", IOSTAT=iostatus ) line
|
|---|
| 317 | IF (iostatus /= 0) THEN
|
|---|
| 318 | Exit
|
|---|
| 319 | ENDIF
|
|---|
| 320 | NLevs = NLevs + 1
|
|---|
| 321 | END DO
|
|---|
| 322 | DO i=1,Nlevs+1
|
|---|
| 323 | BACKSPACE (UNIT=funit)
|
|---|
| 324 | END DO
|
|---|
| 325 |
|
|---|
| 326 | CASE DEFAULT
|
|---|
| 327 | END SELECT
|
|---|
| 328 | END DO
|
|---|
| 329 | IF ( iostatus == 0 ) BACKSPACE ( UNIT=funit )
|
|---|
| 330 |
|
|---|
| 331 | !-------------------------------------------------------------
|
|---|
| 332 | ! 3.2 Initialise ROPP structures & fill in static header data
|
|---|
| 333 | ! not in DAT or DSC files
|
|---|
| 334 | !-------------------------------------------------------------
|
|---|
| 335 |
|
|---|
| 336 | if(lev_1a_exist)then
|
|---|
| 337 | CALL ropp_io_init ( ROdata, NLevs, 0, 0, 0, 0, 0 )
|
|---|
| 338 | allocate(lcf(NLevs))
|
|---|
| 339 | else
|
|---|
| 340 | CALL ropp_io_init ( ROdata, 0, NLevs, NLevs, NLevs, 0, 0 )
|
|---|
| 341 | endif
|
|---|
| 342 |
|
|---|
| 343 | ROdata%Processing_Centre = "GFZ GeoForschungsZentrum Potsdam"
|
|---|
| 344 | ROdata%Overall_Qual = 100.0_wp
|
|---|
| 345 |
|
|---|
| 346 | !-------------------------------------------------------------
|
|---|
| 347 | ! 3.3 Read levels data
|
|---|
| 348 | !-------------------------------------------------------------
|
|---|
| 349 |
|
|---|
| 350 | DO i = 1, NLevs
|
|---|
| 351 |
|
|---|
| 352 | if(lev_1a_exist)then
|
|---|
| 353 |
|
|---|
| 354 | READ ( UNIT=funit, FMT=*, IOSTAT=iostatus ) ROdata%Lev1a%dtime(i), &
|
|---|
| 355 | ROdata%Lev1a%snr_L1ca(i), &
|
|---|
| 356 | ROdata%Lev1a%snr_L1p(i), &
|
|---|
| 357 | ROdata%Lev1a%snr_L2p(i), &
|
|---|
| 358 | ROdata%Lev1a%r_leo(i,:), &
|
|---|
| 359 | ROdata%Lev1a%v_leo(i,:), &
|
|---|
| 360 | ROdata%Lev1a%r_gns(i,:), &
|
|---|
| 361 | ROdata%Lev1a%v_gns(i,:), &
|
|---|
| 362 | phaseLC, &
|
|---|
| 363 | ROdata%Lev1a%phase_L1(i), &
|
|---|
| 364 | ROdata%Lev1a%phase_L2(i), &
|
|---|
| 365 | lcf(i)
|
|---|
| 366 | else
|
|---|
| 367 |
|
|---|
| 368 | READ ( UNIT=funit, FMT=*, IOSTAT=iostatus ) ROdata%Lev2a%Alt_Refrac(i), &
|
|---|
| 369 | ROdata%Lev1b%Lat_tp(i), &
|
|---|
| 370 | ROdata%Lev1b%Lon_tp(i), &
|
|---|
| 371 | ROdata%Lev2a%Refrac(i), &
|
|---|
| 372 | density, &
|
|---|
| 373 | ROdata%Lev2b%Press(i), &
|
|---|
| 374 | ROdata%Lev2b%Temp(i), &
|
|---|
| 375 | basmth, &
|
|---|
| 376 | ROdata%Lev1b%Impact(i), &
|
|---|
| 377 | alpha, beta, gamma, &
|
|---|
| 378 | snr1, snr2, qflag, &
|
|---|
| 379 | ROdata%Lev2a%Geop_Refrac(i), &
|
|---|
| 380 | ROdata%Lev1b%Bangle(i)
|
|---|
| 381 | endif
|
|---|
| 382 |
|
|---|
| 383 | IF ( iostatus /= 0 ) EXIT
|
|---|
| 384 | END DO
|
|---|
| 385 |
|
|---|
| 386 | CLOSE ( UNIT=funit )
|
|---|
| 387 |
|
|---|
| 388 | IF ( iostatus > 0 ) THEN
|
|---|
| 389 | WRITE ( *, FMT="(A/)" ) "ERROR: I/O error while reading DAT file"
|
|---|
| 390 | CALL EXIT(1)
|
|---|
| 391 | END IF
|
|---|
| 392 |
|
|---|
| 393 | !-------------------------------------------------------------
|
|---|
| 394 | ! 3.4 Copy/convert units to ROPP standard
|
|---|
| 395 | !-------------------------------------------------------------
|
|---|
| 396 |
|
|---|
| 397 | if(lev_1a_exist)then
|
|---|
| 398 |
|
|---|
| 399 | ROdata%Lev1a%r_leo(:,:) = ROdata%Lev1a%r_leo(:,:) * KMtoM
|
|---|
| 400 | ROdata%Lev1a%v_leo(:,:) = ROdata%Lev1a%v_leo(:,:) * KMtoM
|
|---|
| 401 | ROdata%Lev1a%r_gns(:,:) = ROdata%Lev1a%r_gns(:,:) * KMtoM
|
|---|
| 402 | ROdata%Lev1a%v_gns(:,:) = ROdata%Lev1a%v_gns(:,:) * KMtoM
|
|---|
| 403 | ROdata%Lev1a%phase_qual(:) = 100.0_wp
|
|---|
| 404 | ROdata%Lev1a%reference_frame%r_leo = "ECI"
|
|---|
| 405 | ROdata%Lev1a%reference_frame%r_gns = "ECI"
|
|---|
| 406 |
|
|---|
| 407 | else
|
|---|
| 408 |
|
|---|
| 409 | ROdata%Lev1b%Impact(:) = ROdata%Lev1b%Impact(:) * KMtoM
|
|---|
| 410 | ROdata%Lev1b%Bangle_Qual(:) = 100.0_wp
|
|---|
| 411 |
|
|---|
| 412 | ROdata%Lev2a%Alt_Refrac(:) = ROdata%Lev2a%Alt_Refrac(:) * KMtoM
|
|---|
| 413 | ROdata%Lev2a%Refrac_Qual(:) = 100.0_wp
|
|---|
| 414 |
|
|---|
| 415 | ROdata%Lev2b%Geop(:) = ROdata%Lev2a%Geop_Refrac(:)
|
|---|
| 416 | ROdata%Lev2b%Temp(:) = ROdata%Lev2b%Temp(:) + CtoK
|
|---|
| 417 |
|
|---|
| 418 | endif
|
|---|
| 419 |
|
|---|
| 420 | !-------------------------------------------------------------
|
|---|
| 421 | ! 3.5 Add lost carrier flag data (Level 1a)
|
|---|
| 422 | !-------------------------------------------------------------
|
|---|
| 423 |
|
|---|
| 424 | if(lev_1a_exist)then
|
|---|
| 425 | call ropp_io_addvar(ROdata, name = "lcf", &
|
|---|
| 426 | long_name= "Lost carrier flag", &
|
|---|
| 427 | units = " ", &
|
|---|
| 428 | range = (/0.0_wp, 1.0_wp/), &
|
|---|
| 429 | data = lcf )
|
|---|
| 430 | deallocate(lcf)
|
|---|
| 431 | endif
|
|---|
| 432 |
|
|---|
| 433 | !-------------------------------------------------------------
|
|---|
| 434 | ! 4. Read DSC file
|
|---|
| 435 | !-------------------------------------------------------------
|
|---|
| 436 |
|
|---|
| 437 | WRITE ( *, FMT="(A)" ) "Reading " // TRIM(dscfile)
|
|---|
| 438 | OPEN ( UNIT=funit, &
|
|---|
| 439 | FILE=dscfile, &
|
|---|
| 440 | STATUS="OLD", &
|
|---|
| 441 | ACTION="READ" )
|
|---|
| 442 |
|
|---|
| 443 | !-------------------------------------------------------------
|
|---|
| 444 | ! 4.1 Parse lines for key words and extract values for those
|
|---|
| 445 | ! meta-data that are not in the DAT file
|
|---|
| 446 | !-------------------------------------------------------------
|
|---|
| 447 |
|
|---|
| 448 | setting_occ = .TRUE.
|
|---|
| 449 |
|
|---|
| 450 | DO
|
|---|
| 451 | READ ( UNIT=funit, FMT="(A)", IOSTAT=iostatus ) line
|
|---|
| 452 | IF ( iostatus /= 0 ) EXIT
|
|---|
| 453 |
|
|---|
| 454 | CALL To_Upper ( Line )
|
|---|
| 455 | i = INDEX ( line, "=" ) + 1
|
|---|
| 456 | IF ( i < 3 ) CYCLE
|
|---|
| 457 | key = line(1:i-2)
|
|---|
| 458 |
|
|---|
| 459 | j = INDEX ( line, ';' ) - 1
|
|---|
| 460 | IF ( j < i ) j = LEN_TRIM ( line )
|
|---|
| 461 | arg = ADJUSTL(line(i:j))
|
|---|
| 462 |
|
|---|
| 463 | SELECT CASE (key)
|
|---|
| 464 |
|
|---|
| 465 | ! DSC file has Processing Date but not the Time. ropp_io_init will have
|
|---|
| 466 | ! intialised Processing Date/Time to current time; if Date in DSC file
|
|---|
| 467 | ! is not today, use it & set Time to the end of the day, else leave
|
|---|
| 468 | ! current time as processing time.
|
|---|
| 469 |
|
|---|
| 470 | CASE ("GENERATION DATE") ! Date/Time of processing
|
|---|
| 471 | READ ( arg, FMT="(I4,2(1X,I2))" ) Year, Month, Day
|
|---|
| 472 | IF ( Year /= ROdata%DTpro%Year .OR. &
|
|---|
| 473 | Month /= ROdata%DTpro%Month .OR. &
|
|---|
| 474 | Day /= ROdata%DTpro%Day ) THEN
|
|---|
| 475 | ROdata%DTpro%Year = Year
|
|---|
| 476 | ROdata%DTpro%Month = Month
|
|---|
| 477 | ROdata%DTpro%Day = Day
|
|---|
| 478 | ROdata%DTpro%Hour = 23
|
|---|
| 479 | ROdata%DTpro%Minute = 59
|
|---|
| 480 | ROdata%DTpro%Second = 59
|
|---|
| 481 | ROdata%DTpro%Msec = 999
|
|---|
| 482 | ELSE
|
|---|
| 483 | ROdata%DTpro%Msec = 000
|
|---|
| 484 | END IF
|
|---|
| 485 |
|
|---|
| 486 | CASE ("LOCAL RADIUS OF CURVATURE") ! Earth's radius of curvature at occ. point (m)
|
|---|
| 487 | READ ( arg, FMT=* ) ROdata%GeoRef%RoC
|
|---|
| 488 | ROdata%GeoRef%RoC = ROdata%GeoRef%RoC * KMtoM
|
|---|
| 489 |
|
|---|
| 490 | CASE ("GEOID UNDULATION EGM96") ! Geoid undulation (EGM96-WGS-84) at occ. point (m)
|
|---|
| 491 | READ ( arg, FMT=* ) ROdata%GeoRef%Undulation
|
|---|
| 492 |
|
|---|
| 493 | ! CASE ("MISSION") ! LEO Satellite ID
|
|---|
| 494 | !---------------------------------------------------------------------
|
|---|
| 495 | ! The DSC file seems to have "mission=CHAMP;" even for GRACE-A, so we
|
|---|
| 496 | ! detect the satellite ID from the DAT file name. Remove the marked code
|
|---|
| 497 | ! (and these comments) if/when the DSC file properly states the satellite name.
|
|---|
| 498 | !-------------------------------------------remove from here --------
|
|---|
| 499 | IF ( datfile(8:9) == "CH" ) arg = "CHAMP"
|
|---|
| 500 | IF ( datfile(8:9) == "GA" ) arg = "GRACE-A"
|
|---|
| 501 | IF ( datfile(8:9) == "GB" ) arg = "GRACE-B"
|
|---|
| 502 | IF ( datfile(8:9) == "TS" ) arg = "TERRASAR-X"
|
|---|
| 503 | !-------------------------------------------remove to here --------
|
|---|
| 504 | SELECT CASE (arg)
|
|---|
| 505 | CASE ("CHAMP")
|
|---|
| 506 | ROdata%LEO_ID = "CHMP"
|
|---|
| 507 | CASE ("GRACE","GRACE-A")
|
|---|
| 508 | ROdata%LEO_ID = "GRAA"
|
|---|
| 509 | CASE ("GRACE-B")
|
|---|
| 510 | ROdata%LEO_ID = "GRAB"
|
|---|
| 511 | CASE ("TERRASAR-X")
|
|---|
| 512 | ROdata%LEO_ID = "TSRX"
|
|---|
| 513 | CASE DEFAULT
|
|---|
| 514 | ROdata%LEO_ID = arg(1:4)
|
|---|
| 515 | END SELECT
|
|---|
| 516 |
|
|---|
| 517 | CASE ("SETTING(1)/RISING OCCULTATION") ! rising or setting occultation
|
|---|
| 518 | IF ( arg /= "1" ) setting_occ = .FALSE.
|
|---|
| 519 |
|
|---|
| 520 | !CASE ("SOFTWARE PACKAGE") ! Software ID (major)
|
|---|
| 521 | ! READ ( arg(6:), FMT=* ) SWver
|
|---|
| 522 |
|
|---|
| 523 | CASE ("REVISION") ! Software ID (minor)
|
|---|
| 524 | READ ( arg, FMT=* ) SWrev
|
|---|
| 525 |
|
|---|
| 526 | CASE ("OCCULTATION DIRECTION") ! Azimuth angle GNSS-->LEO (deg)
|
|---|
| 527 | READ ( arg, FMT=* ) ROdata%GeoRef%Azimuth
|
|---|
| 528 |
|
|---|
| 529 | CASE DEFAULT
|
|---|
| 530 |
|
|---|
| 531 | END SELECT
|
|---|
| 532 |
|
|---|
| 533 | END DO
|
|---|
| 534 |
|
|---|
| 535 | CLOSE ( UNIT=funit )
|
|---|
| 536 |
|
|---|
| 537 | IF ( iostatus > 0 ) THEN
|
|---|
| 538 | WRITE ( *, FMT="(A/)" ) "ERROR: I/O error while reading DSC file"
|
|---|
| 539 | CALL EXIT(1)
|
|---|
| 540 | END IF
|
|---|
| 541 |
|
|---|
| 542 | !-------------------------------------------------------------
|
|---|
| 543 | ! 4.2 Convert GFZ parameters to ROPP standard
|
|---|
| 544 | !-------------------------------------------------------------
|
|---|
| 545 |
|
|---|
| 546 | WRITE ( ROdata%Software_Version, FMT="(F6.3)" ) SWver + SWrev * 0.001_wp
|
|---|
| 547 | IF ( SWver < 10.0 ) THEN
|
|---|
| 548 | ROdata%Software_Version = "V0"//ADJUSTL(ROdata%Software_Version)
|
|---|
| 549 | ELSE
|
|---|
| 550 | ROdata%Software_Version = "V" //ADJUSTL(ROdata%Software_Version)
|
|---|
| 551 | END IF
|
|---|
| 552 |
|
|---|
| 553 | ! Take nominal lat/lon items from lowest point in profile
|
|---|
| 554 | ! with time offset of zero for rising occultations or end-start
|
|---|
| 555 | ! time for setting. Set PCD rising bit accordingly.
|
|---|
| 556 |
|
|---|
| 557 | if (.not. lev_1a_exist) then
|
|---|
| 558 |
|
|---|
| 559 | IF ( ROdata%Lev2a%Alt_Refrac(1) < &
|
|---|
| 560 | ROdata%Lev2a%Alt_Refrac(NLevs) ) THEN
|
|---|
| 561 | ROdata%GeoRef%Lat = ROdata%Lev1b%Lat_tp(1)
|
|---|
| 562 | ROdata%GeoRef%Lon = ROdata%Lev1b%Lon_tp(1)
|
|---|
| 563 | ELSE
|
|---|
| 564 | ROdata%GeoRef%Lat = ROdata%Lev1b%Lat_tp(Nlevs)
|
|---|
| 565 | ROdata%GeoRef%Lon = ROdata%Lev1b%Lon_tp(Nlevs)
|
|---|
| 566 | END IF
|
|---|
| 567 |
|
|---|
| 568 | endif
|
|---|
| 569 |
|
|---|
| 570 | ROdata%PCD = 0
|
|---|
| 571 | IF ( setting_occ ) THEN
|
|---|
| 572 | IF ( eTime < sTime ) eTime = eTime + SecsPerDay ! in case event spans midnight
|
|---|
| 573 | ROdata%GeoRef%Time_Offset = eTime - sTime
|
|---|
| 574 | ELSE
|
|---|
| 575 | ROdata%GeoRef%Time_Offset = 0.0
|
|---|
| 576 | ROdata%PCD = IBSET(ROdata%PCD,PCD_rising)
|
|---|
| 577 | END IF
|
|---|
| 578 |
|
|---|
| 579 | !-------------------------------------------------------------
|
|---|
| 580 | ! 5. Generate ROPP Occultation ID; optionally dump some key data
|
|---|
| 581 | !-------------------------------------------------------------
|
|---|
| 582 |
|
|---|
| 583 | CALL ropp_io_occid ( ROdata )
|
|---|
| 584 | IF ( DEBUG ) THEN
|
|---|
| 585 | WRITE ( *, FMT="(A)" ) " Occultation ID : "// &
|
|---|
| 586 | ROdata%Occ_ID
|
|---|
| 587 | WRITE ( *, FMT="(A,2F9.3)" ) " Latitude/Longitude :", &
|
|---|
| 588 | ROdata%GeoRef%Lat, &
|
|---|
| 589 | ROdata%GeoRef%Lon
|
|---|
| 590 | WRITE ( *, FMT="(A,I6)" ) " No. of phase/SNR samples :", &
|
|---|
| 591 | ROdata%Lev1a%Npoints
|
|---|
| 592 | WRITE ( *, FMT="(A,I6)" ) " No. of bending angle samples :", &
|
|---|
| 593 | ROdata%Lev1b%Npoints
|
|---|
| 594 | WRITE ( *, FMT="(A,I6)" ) " No. of refractivity samples :", &
|
|---|
| 595 | ROdata%Lev2a%Npoints
|
|---|
| 596 | WRITE ( *, FMT="(A,I6)" ) " No. of geophysical samples :", &
|
|---|
| 597 | ROdata%Lev2b%Npoints
|
|---|
| 598 | WRITE ( *, FMT="(A,I6)" ) " No. of surface geo. samples :", &
|
|---|
| 599 | ROdata%Lev2c%Npoints
|
|---|
| 600 | WRITE ( *, FMT="(A,I6)" ) " No. of model coeff. levels :", &
|
|---|
| 601 | ROdata%Lev2d%Npoints
|
|---|
| 602 | ELSE
|
|---|
| 603 | i = 1
|
|---|
| 604 | WRITE ( *, FMT="(I5,2A,2F8.1)" ) i, " : ", &
|
|---|
| 605 | ROdata%occ_id, &
|
|---|
| 606 | ROdata%georef%lat, &
|
|---|
| 607 | ROdata%georef%lon
|
|---|
| 608 | END IF
|
|---|
| 609 |
|
|---|
| 610 | !-------------------------------------------------------------
|
|---|
| 611 | ! 6. Write ROPP netCDF file
|
|---|
| 612 | !-------------------------------------------------------------
|
|---|
| 613 |
|
|---|
| 614 | CALL ropp_io_rangecheck ( ROdata )
|
|---|
| 615 |
|
|---|
| 616 | WRITE ( *, FMT="(A)" ) "Writing " // TRIM(opfile)
|
|---|
| 617 | CALL ropp_io_write ( ROdata, file=opfile, ierr=iostatus )
|
|---|
| 618 | IF ( iostatus > 0 ) THEN
|
|---|
| 619 | WRITE ( *, FMT="(A/)" ) "ERROR: I/O error while writing output file"
|
|---|
| 620 | END IF
|
|---|
| 621 |
|
|---|
| 622 | !-------------------------------------------------------------
|
|---|
| 623 | ! 7. Tidy up - deallocate structures & free memory
|
|---|
| 624 | !-------------------------------------------------------------
|
|---|
| 625 |
|
|---|
| 626 | CALL ropp_io_free ( ROdata )
|
|---|
| 627 |
|
|---|
| 628 | END Program gfz2ropp
|
|---|