bufr.pm:bufrdump

Differences

This shows you the differences between two versions of the page.

Link to this comparison view

Both sides previous revision Previous revision
Next revision
Previous revision
bufr.pm:bufrdump [2010-02-26 15:36:57]
pals
bufr.pm:bufrdump [2022-05-31 09:29:31] (current)
Line 1: Line 1:
-Use this in Makefile, with $(FC) set to your Fortran compiler (e.g. gfortran or g77), $(LDIR) set to the directory where libbufr.a is located+Use this in Makefile, with $(FC) set to your Fortran compiler (e.g. gfortran or g77), $(LDIR) set to the directory where libbufr.a is located, and $(FCFLAGS) set to -fbackslash for gfortran. Note that code for comfilter.f is found at the end of this page (below the code for bufrdump.F).
  
 <code> <code>
 bufrdump: bufrdump.F comfilter.f bufrdump: bufrdump.F comfilter.f
- $(FC) -o bufrdump  $< -L $(LDIR) -lbufr+ $(FC) $(FCFLAGS) -o bufrdump  $< -L $(LDIR) -lbufr
 </code> </code>
  
- +<code fortran bufrdump.F> 
-bufrdump.F+C (C) Copyright 2010-2016 MET Norway
-<file+
-C (C) Copyright 2010, met.no+
 C C
 C This program is free software; you can redistribute it and/or modify C This program is free software; you can redistribute it and/or modify
Line 27: Line 25:
  
  
-C Extract BUFR messages from bufr file(s) using the Fortran program +C Extract BUFR messages from bufr file(s) and print the data as 
-C bufrdump and print the data as 'parameter=value' lines. See +'parameter=value' lines. See usage_verbose for explanation of the 
-usage_verbose for explanation of the options allowed.+options allowed.
 C C
 C Usage: bufrdump <bufr file> C Usage: bufrdump <bufr file>
 C        [--help] C        [--help]
 C        [--filter <filter file>] C        [--filter <filter file>]
 +C        [--obstype] <amdar|ocea|surface|sounding|sounding->
 +C        [--stop_on_error]
 C        [--rectangle x1 y1 x2 y2] C        [--rectangle x1 y1 x2 y2]
 C        or one or more of C        or one or more of
Line 49: Line 49:
 C export BUFR_TABLES=/usr/local/lib/bufrtables/ C export BUFR_TABLES=/usr/local/lib/bufrtables/
 C C
-C Author: P.Sannes met.no 2010+C Author: P.Sannes, MET Norway
  
  
Line 56: Line 56:
       IMPLICIT NONE       IMPLICIT NONE
  
-      CHARACTER(LEN=80) bufr_file        ! Bufr file to read from+      CHARACTER(LEN=200) bufr_file       ! Bufr file to read from
       LOGICAL data_only                  ! TRUE if only data section is to be printed       LOGICAL data_only                  ! TRUE if only data section is to be printed
       LOGICAL filter                     ! TRUE if observations should be filtered       LOGICAL filter                     ! TRUE if observations should be filtered
       LOGICAL rectangle                  ! TRUE if observations are wanted for a rectangle only       LOGICAL rectangle                  ! TRUE if observations are wanted for a rectangle only
-      CHARACTER(LEN=80filter_file      ! File containing the filter criteria +      LOGICAL stop_on_error              ! TRUE if program should stop if a libbufr call returns an error 
-      CHARACTER(LEN=80) descriptor_file  ! File containing the descriptors requested for partial expansion+      CHARACTER(LEN=10obstype 
 +      CHARACTER(LEN=200) filter_file     ! File containing the filter criteria 
 +      CHARACTER(LEN=200) descriptor_file ! File containing the descriptors requested for partial expansion
       INTEGER verbose                    ! Level of verbose output: 0 - 3 (default 1)       INTEGER verbose                    ! Level of verbose output: 0 - 3 (default 1)
       INTEGER nlibbufr_errors            ! Number of errors encountered in libbufr calls       INTEGER nlibbufr_errors            ! Number of errors encountered in libbufr calls
Line 82: Line 84:
       verbose = 1       verbose = 1
  
-      CALL get_arguments(bufr_file,filter,filter_file,rectangle)+      CALL get_arguments(bufr_file,filter,filter_file,rectangle
 +         stop_on_error,obstype)
  
       IF (filter) CALL read_filter(filter,filter_file,verbose)       IF (filter) CALL read_filter(filter,filter_file,verbose)
Line 104: Line 107:
                              ! but copy how it is done in decode_bufr in libbufr                              ! but copy how it is done in decode_bufr in libbufr
          CALL BUFRdecode(ibuff,wlen,filter,rectangle,verbose,          CALL BUFRdecode(ibuff,wlen,filter,rectangle,verbose,
-            nlibbufr_errors)+            stop_on_error,obstype,nlibbufr_errors)
       END DO       END DO
  900  CONTINUE  900  CONTINUE
Line 147: Line 150:
  
       SUBROUTINE BUFRdecode(ibuff,ilen,filter,rectangle,       SUBROUTINE BUFRdecode(ibuff,ilen,filter,rectangle,
-         verbose,nlibbufr_errors)+         verbose,stop_on_error,obstype,nlibbufr_errors)
       IMPLICIT NONE       IMPLICIT NONE
       INTEGER ibuff(*)       INTEGER ibuff(*)
Line 153: Line 156:
       LOGICAL filter       LOGICAL filter
       LOGICAL rectangle       LOGICAL rectangle
 +      LOGICAL stop_on_error
 +      CHARACTER(LEN=*) obstype
       INTEGER nlibbufr_errors   ! Number of errors encountered in libbufr calls       INTEGER nlibbufr_errors   ! Number of errors encountered in libbufr calls
       INTEGER verbose       INTEGER verbose
  
 +      LOGICAL metar             ! Set to TRUE if metar (data subcategory 5) 
 +      
       INTEGER kelem,kxelem      ! expected (max) number of expanded elements       INTEGER kelem,kxelem      ! expected (max) number of expanded elements
       INTEGER kvals             ! expected (max) number of data values       INTEGER kvals             ! expected (max) number of data values
Line 203: Line 209:
  
       kerr = 0       kerr = 0
 +      metar = .FALSE. 
 +      
 C     Do a partial expansion without quality control C     Do a partial expansion without quality control
       kreq(1) = 1               ! All original elements without quality control       kreq(1) = 1               ! All original elements without quality control
Line 212: Line 219:
       CALL BUSRQ(kreq,krql,rqd,rqv,kerr)       CALL BUSRQ(kreq,krql,rqd,rqv,kerr)
       IF (kerr.NE.0) THEN       IF (kerr.NE.0) THEN
 +         IF (stop_on_error) STOP 1
          WRITE(*,*) 'ERROR IN BUSRQ: KERR= ',kerr          WRITE(*,*) 'ERROR IN BUSRQ: KERR= ',kerr
          nlibbufr_errors = nlibbufr_errors + 1          nlibbufr_errors = nlibbufr_errors + 1
Line 220: Line 228:
 C C
  
-C     Using parameter kelem in call to BUFREX might be too big for +C     Using parameter kelem in call to BUFREX might be too big for some 
-C     multisubset messages. Have copied the method used in decode_bufr.F +C     multisubset messages (or too small for other messages). Have 
-C     in libbufr, first calling BUS012 in order to get number of subsets +C     copied the method used in decode_bufr.F in libbufr, first calling 
-C     ksup(6)+C     BUS012 in order to get number of subsets ksup(6)
       CALL BUS012(ilen,ibuff,ksup,ksec0,ksec1,ksec2,kerr)       CALL BUS012(ilen,ibuff,ksup,ksec0,ksec1,ksec2,kerr)
       IF (kerr.NE.0) THEN       IF (kerr.NE.0) THEN
 +         IF (stop_on_error) STOP 1
          WRITE(*,*) 'ERROR IN BUS012: KERR= ',kerr          WRITE(*,*) 'ERROR IN BUS012: KERR= ',kerr
          nlibbufr_errors = nlibbufr_errors + 1          nlibbufr_errors = nlibbufr_errors + 1
Line 231: Line 240:
       END IF       END IF
       kxelem = kvals/ksup(6)       kxelem = kvals/ksup(6)
-      IF (kxelem .GT. kelem) kxelem = kelem+C     The second IF-condition is not in decode_bufr.F, but else I get 'KELEM 
 +C     ARGUMENT TOO SMALL' from BUUPWT when decoding large radiosondefiles 
 +      IF (kxelem.GT.kelem .AND. ksup(6).GT.10) kxelem = kelem
  
       CALL BUFREX (ilen,ibuff,ksup,ksec0,ksec1,ksec2,       CALL BUFREX (ilen,ibuff,ksup,ksec0,ksec1,ksec2,
Line 238: Line 249:
       IF (kerr.EQ.45) RETURN      ! No requested elements in data       IF (kerr.EQ.45) RETURN      ! No requested elements in data
       IF (kerr.NE.0) THEN       IF (kerr.NE.0) THEN
 +         IF (stop_on_error) STOP 1
          WRITE(*,*) 'ERROR IN BUFREX: KERR= ',kerr          WRITE(*,*) 'ERROR IN BUFREX: KERR= ',kerr
          nlibbufr_errors = nlibbufr_errors + 1          nlibbufr_errors = nlibbufr_errors + 1
Line 245: Line 257:
          'Number of subsets:',ksup(6)          'Number of subsets:',ksup(6)
  
-C     Convert messages with data category (BUFR table A) 0-2 only.  0 = +C     Convert messages with data category (BUFR table A) 0-2,4,6 and 31 only. 
-C     Surface data - land, 1 = Surface data - sea, 2 = Vertical sounding +C     0 = Surface data - land, 1 = Surface data - sea, 2 = Vertical 
-C     (other than satellite) +C     sounding (other than satellite) 4 = Single level upper-air data 
-      IF (ksec1(6).GT.2) RETURN+C     (other than satellite) 6 = Radar data 31 = Oceanographic data 
 +      IF (ksec1(6).GT.2 .AND. ksec1(6).NE.4 .AND. ksec1(6).NE.6 
 +         .AND. ksec1(6).NE.31) RETURN 
 + 
 +C     MET (and perhaps also other ECMWF based software?) uses local 
 +C     subcategory 5 for metar (and BUFR edition 3) 
 +      IF (KSEC1(2).EQ.3 .AND. KSEC1(6).EQ.0 .AND. KSEC1(7).EQ.5) THEN 
 +         metar = .TRUE. 
 +      END IF
  
       IF (filter) THEN       IF (filter) THEN
Line 259: Line 279:
          CALL BUSEL(ktdlen,ktdlst,ktdexl,ktdexp,kerr)          CALL BUSEL(ktdlen,ktdlst,ktdexl,ktdexp,kerr)
          IF (kerr .GT. 0) THEN          IF (kerr .GT. 0) THEN
 +            IF (stop_on_error) STOP 1
             WRITE(*,*) 'ERROR IN BUSEL: KERR= ',kerr             WRITE(*,*) 'ERROR IN BUSEL: KERR= ',kerr
             nlibbufr_errors = nlibbufr_errors + 1             nlibbufr_errors = nlibbufr_errors + 1
Line 275: Line 296:
                cnames,cunits,kerr)                cnames,cunits,kerr)
             IF (kerr.NE.0) THEN             IF (kerr.NE.0) THEN
 +               IF (stop_on_error) STOP 1
                WRITE(*,*) 'ERROR IN BUSEL2: KERR= ',kerr                WRITE(*,*) 'ERROR IN BUSEL2: KERR= ',kerr
                nlibbufr_errors = nlibbufr_errors + 1                nlibbufr_errors = nlibbufr_errors + 1
Line 280: Line 302:
             END IF             END IF
  
-            IF (ksec1(6).LE.1) THEN+            IF (obstype.EQ.'surface') THEN
                CALL print_surface_values(ksub,kxelem,ktdexl,ktdexp,                CALL print_surface_values(ksub,kxelem,ktdexl,ktdexp,
 +                  values,cvals,rectangle,metar,verbose)
 +            ELSE IF (obstype(1:8).EQ.'sounding') THEN
 +               CALL print_sounding_values(ksub,kxelem,ktdexl,ktdexp,
 +                  values,cvals,rectangle,obstype,verbose)
 +            ELSE IF (obstype.EQ.'amdar') THEN
 +               CALL print_amdar_values(ksub,kxelem,ktdexl,ktdexp,
                   values,cvals,rectangle,verbose)                   values,cvals,rectangle,verbose)
 +            ELSE IF (obstype.EQ.'ocea') THEN
 +               CALL print_oceanographic_values(ksub,kxelem,ktdexl,
 +                  ktdexp,values,cvals,rectangle,verbose)
 +            ELSE IF (ksec1(6).LE.1) THEN
 +               CALL print_surface_values(ksub,kxelem,ktdexl,ktdexp,
 +                  values,cvals,rectangle,metar,verbose)
             ELSE IF (ksec1(6).EQ.2) THEN             ELSE IF (ksec1(6).EQ.2) THEN
                CALL print_sounding_values(ksub,kxelem,ktdexl,ktdexp,                CALL print_sounding_values(ksub,kxelem,ktdexl,ktdexp,
 +                  values,cvals,rectangle,obstype,verbose)
 +            ELSE IF (ksec1(6).EQ.4) THEN
 +               CALL print_amdar_values(ksub,kxelem,ktdexl,ktdexp,
                   values,cvals,rectangle,verbose)                   values,cvals,rectangle,verbose)
 +            ELSE IF (ksec1(6).EQ.6) THEN
 +               CALL print_radar_profiler_values(ksub,kxelem,ktdexl,
 +                  ktdexp,values,cvals,rectangle,verbose)
 +            ELSE IF (ksec1(6).EQ.31) THEN
 +               CALL print_oceanographic_values(ksub,kxelem,ktdexl,
 +                  ktdexp,values,cvals,rectangle,verbose)
             END IF             END IF
          ENDDO          ENDDO
Line 293: Line 336:
                cnames,cunits,kerr)                cnames,cunits,kerr)
             IF (kerr.NE.0) THEN             IF (kerr.NE.0) THEN
 +               IF (stop_on_error) STOP 1
                WRITE(*,*) 'ERROR IN BUSEL2: KERR= ',kerr                WRITE(*,*) 'ERROR IN BUSEL2: KERR= ',kerr
                nlibbufr_errors = nlibbufr_errors + 1                nlibbufr_errors = nlibbufr_errors + 1
Line 298: Line 342:
             END IF             END IF
  
-            IF (ksec1(6).LE.1) THEN+            IF (obstype.EQ.'surface') THEN
                CALL print_surface_values(ksub,kxelem,ktdexl,ktdexp,                CALL print_surface_values(ksub,kxelem,ktdexl,ktdexp,
 +                  values,cvals,rectangle,metar,verbose)
 +            ELSE IF (obstype(1:8).EQ.'sounding') THEN
 +               CALL print_sounding_values(ksub,kxelem,ktdexl,ktdexp,
 +                  values,cvals,rectangle,obstype,verbose)
 +            ELSE IF (obstype.EQ.'amdar') THEN
 +               CALL print_amdar_values(ksub,kxelem,ktdexl,ktdexp,
                   values,cvals,rectangle,verbose)                   values,cvals,rectangle,verbose)
 +            ELSE IF (obstype.EQ.'ocea') THEN
 +               CALL print_oceanographic_values(ksub,kxelem,ktdexl,
 +                  ktdexp,values,cvals,rectangle,verbose)
 +            ELSE IF (ksec1(6).LE.1) THEN
 +               CALL print_surface_values(ksub,kxelem,ktdexl,ktdexp,
 +                  values,cvals,rectangle,metar,verbose)
             ELSE IF (ksec1(6).EQ.2) THEN             ELSE IF (ksec1(6).EQ.2) THEN
                CALL print_sounding_values(ksub,kxelem,ktdexl,ktdexp,                CALL print_sounding_values(ksub,kxelem,ktdexl,ktdexp,
 +                  values,cvals,rectangle,obstype,verbose)
 +            ELSE IF (ksec1(6).EQ.4) THEN
 +               CALL print_amdar_values(ksub,kxelem,ktdexl,ktdexp,
                   values,cvals,rectangle,verbose)                   values,cvals,rectangle,verbose)
 +            ELSE IF (ksec1(6).EQ.6) THEN
 +               CALL print_radar_profiler_values(ksub,kxelem,ktdexl,
 +                  ktdexp,values,cvals,rectangle,verbose)
 +            ELSE IF (ksec1(6).EQ.31) THEN
 +C     For ocea files at met.no data category is 31. But note that IOB
 +C     bulletins all have data category 1 (and sub-category 25 or 255),
 +C     so for these we end up calling print_surface_values (unless
 +C     --obstype ocea is used)
 +               CALL print_oceanographic_values(ksub,kxelem,ktdexl,
 +                  ktdexp,values,cvals,rectangle,verbose)
             END IF             END IF
          END DO          END DO
Line 313: Line 382:
  
       SUBROUTINE get_arguments(bufr_file,filter,filter_file,       SUBROUTINE get_arguments(bufr_file,filter,filter_file,
-         rectangle)+         rectangle,stop_on_error,obstype)
  
       IMPLICIT NONE       IMPLICIT NONE
Line 321: Line 390:
       LOGICAL filter             ! TRUE if observations should be filtered       LOGICAL filter             ! TRUE if observations should be filtered
       LOGICAL rectangle          ! TRUE if observations are wanted for a rectangle only       LOGICAL rectangle          ! TRUE if observations are wanted for a rectangle only
 +      LOGICAL stop_on_error      ! TRUE if program should stop if a libbufr call returns an error
       CHARACTER(LEN=*) filter_file ! File containing the filter criteria       CHARACTER(LEN=*) filter_file ! File containing the filter criteria
 +      CHARACTER(LEN=*) obstype
  
-      CHARACTER(LEN=80) argument ! Buffer for next argument +      CHARACTER(LEN=200) argument ! Buffer for next argument 
-      CHARACTER(LEN=850) Usage +      CHARACTER(LEN=1350) Usage 
-      CHARACTER(LEN=800) Help+      CHARACTER(LEN=950) Help
       INTEGER iargc,iarg       INTEGER iargc,iarg
  
Line 345: Line 416:
          // '\t\t\tDecode observations meeting criteria in '          // '\t\t\tDecode observations meeting criteria in '
          // '<filter file> only\n'          // '<filter file> only\n'
 +         // '\t--obstype <amdar|ocea|surface|sounding|sounding->\n'
 +         // '\t\t\tForce observation type. If this option '
 +         // 'is not set, bufrdump\n\t\t\twill make an '
 +         // 'educated guess of observation type based on\n'
 +         // '\t\t\tmetadata in section 1 of each BUFR message. '
 +         // 'The special value\n\t\t\t"sounding-" results in '
 +         // 'levels with no vss being skipped\n'
 +         // '\t--stop_on_error\tIf a libbufr call returns an '
 +         // 'error, bufrdump will return\n\t\t\timmediately with '
 +         // 'exit status 1\n'
          // '\t--rectangle x1 y1 x2 y2\n'          // '\t--rectangle x1 y1 x2 y2\n'
          // '\t\t\tDecode observations inside rectangle with lower '          // '\t\t\tDecode observations inside rectangle with lower '
Line 362: Line 443:
  
       Help = '\nYou should probably set\n'       Help = '\nYou should probably set\n'
-         // '\texport BUFR_TABLES=/usr/local/lib/emos/bufrtables/\n'+         // '\texport BUFR_TABLES=/usr/local/lib/bufrtables/\n'
          // '\texport PRINT_TABLE_NAMES=false\n'          // '\texport PRINT_TABLE_NAMES=false\n'
          // '\nUsing --filter will decode only those observations '          // '\nUsing --filter will decode only those observations '
Line 376: Line 457:
          // 'which decodes all observations with block number 01, '          // 'which decodes all observations with block number 01, '
          // 'two other specific wmo\nstations and one ship. '          // 'two other specific wmo\nstations and one ship. '
-         // 'So far only filtering on excact matches on integer and\n'+         // 'So far only filtering on exact matches on integer and\n'
          // 'character valued BUFR descriptors has been implemented.'          // 'character valued BUFR descriptors has been implemented.'
 +         // ' But note that the\nclosely related program bufrdump.pl'
 +         // ' has a lot more options for filtering.'
          // '\n\nIf an error occurs during decoding (typically '          // '\n\nIf an error occurs during decoding (typically '
          // 'because the required BUFR table\nis missing or message '          // 'because the required BUFR table\nis missing or message '
          // 'is corrupt) the message is skipped, and the number '          // 'is corrupt) the message is skipped, and the number '
-         // 'of\nerrors is reported at end of output.\n'+         // 'of\nerrors is reported at end of output - unless ' 
 +         // 'option --stop_on_error has been\napplied (note that ' 
 +         // 'some error messages from libbufr might still have been ' 
 +         // 'sent\nto STDOUT).\n'
  
 C     Default values C     Default values
       filter = .FALSE.       filter = .FALSE.
 +      obstype = ''
       rectangle = .FALSE.       rectangle = .FALSE.
 +      stop_on_error = .FALSE.
       bufr_file = ''       bufr_file = ''
       iarg = 0       iarg = 0
Line 408: Line 496:
          iarg = iarg + 1          iarg = iarg + 1
          CALL getarg(iarg,filter_file)          CALL getarg(iarg,filter_file)
 +      ELSE IF (argument .EQ. '--obstype' .OR.
 +         argument .EQ. '--o' .OR. argument .EQ. '-o') THEN
 +         iarg = iarg + 1
 +         CALL getarg(iarg,obstype)
 +      ELSE IF (argument .EQ. '--stop_on_error') THEN
 +         stop_on_error = .TRUE.
       ELSE IF (argument .EQ. '--rectangle' .OR.       ELSE IF (argument .EQ. '--rectangle' .OR.
          argument .EQ. '--r' .OR. argument .EQ. '-r') THEN          argument .EQ. '--r' .OR. argument .EQ. '-r') THEN
Line 456: Line 550:
       IF (bufr_file .EQ. '') THEN       IF (bufr_file .EQ. '') THEN
          WRITE(*,*) 'No BUFR file given'          WRITE(*,*) 'No BUFR file given'
 +         CALL EXIT(1)
 +      END IF
 +
 +      IF (obstype.NE.'' .AND. obstype.NE.'amdar' .AND. obstype.NE.'ocea'
 +         .AND. obstype.NE.'surface' .AND. obstype.NE.'sounding'
 +         .AND. obstype.NE.'sounding-') THEN
 +         WRITE(*,*) 'Argument to --obstype must be one of amdar, ocea,',
 +       ' surface, sounding or sounding-'
          CALL EXIT(1)          CALL EXIT(1)
       END IF       END IF
Line 465: Line 567:
       SUBROUTINE err_msg(msg)       SUBROUTINE err_msg(msg)
       IMPLICIT NONE       IMPLICIT NONE
-      CHARACTER*80 msg+      CHARACTER(LEN=*msg
       WRITE(*,*) msg       WRITE(*,*) msg
       STOP       STOP
Line 474: Line 576:
       SUBROUTINE err_msg1(msg,kerr)       SUBROUTINE err_msg1(msg,kerr)
       IMPLICIT NONE       IMPLICIT NONE
-      CHARACTER*80 msg+      CHARACTER(LEN=*msg
       INTEGER kerr       INTEGER kerr
       WRITE(*,*) msg,kerr       WRITE(*,*) msg,kerr
Line 493: Line 595:
       LOGICAL filter            ! TRUE on input. Might be changed to FALSE on output       LOGICAL filter            ! TRUE on input. Might be changed to FALSE on output
                                 ! if no filter condition is found in filter file                                 ! if no filter condition is found in filter file
-      CHARACTER(LEN=80) filter_file+      CHARACTER(LEN=200) filter_file
       INTEGER verbose,ios,inplen,i1,i2,i3,ifid,jfid,lenstr,fmt_len       INTEGER verbose,ios,inplen,i1,i2,i3,ifid,jfid,lenstr,fmt_len
       CHARACTER*100 inpline,readformat       CHARACTER*100 inpline,readformat
Line 515: Line 617:
          inplen = lenstr(inpline,1)          inplen = lenstr(inpline,1)
          IF (inplen.EQ.0) EXIT filter_loop          IF (inplen.EQ.0) EXIT filter_loop
-C     Allow comment line 
-         IF (inpline(1:1).EQ.'#') CYCLE filter_loop 
          i1 = 0          i1 = 0
          i2 = 0          i2 = 0
          CALL advance_word(inpline,inplen,i1,i2)          CALL advance_word(inpline,inplen,i1,i2)
          IF (i1 .EQ. 0) EXIT filter_loop          IF (i1 .EQ. 0) EXIT filter_loop
-         IF (inpline(1:2).EQ.'D:') THEN+         IF (inpline(i1:i1).EQ.'#') CYCLE filter_loop ! Comment line 
 + 
 +         IF (inpline(i1:i1+1).EQ.'D:') THEN
 C     Descriptor line (e.g. D: 001001 I2.2 001002 I3.3) C     Descriptor line (e.g. D: 001001 I2.2 001002 I3.3)
             ifid = ifid + 1             ifid = ifid + 1
Line 576: Line 678:
       CLOSE(11)       CLOSE(11)
  
 +      IF (verbose.GT.2) WRITE(*,*) 'nfidlines=',nfidlines
       IF (nfivlines.EQ.0) filter = .FALSE.       IF (nfivlines.EQ.0) filter = .FALSE.
  
Line 648: Line 751:
  
       num_found = 0       num_found = 0
-      ifiv = 0 
 C     loop through all subsets: C     loop through all subsets:
       DO nsub = 1,num_subsets       DO nsub = 1,num_subsets
 C     loop through all different conditions: C     loop through all different conditions:
 +         ifiv = 0
          DO i1 = 1,nfidlines          DO i1 = 1,nfidlines
-C     loop through all filter values lines (for given) condition:+C     loop through all filter value lines (for given) condition:
             DO ifvl = 1,nvl_fid(i1)             DO ifvl = 1,nvl_fid(i1)
                ifiv = ifiv + 1                ifiv = ifiv + 1
Line 672: Line 775:
                         IF (values(iv).EQ.rvind)                         IF (values(iv).EQ.rvind)
                            GOTO 400 ! next condition, no point in checking                            GOTO 400 ! next condition, no point in checking
-                                      ! other filter values lines+                                      ! other filter value lines
                         IF (int_fid) THEN                         IF (int_fid) THEN
                            IF (nint(values(iv)).EQ.fivI(ifiv,i2)) THEN                            IF (nint(values(iv)).EQ.fivI(ifiv,i2)) THEN
Line 686: Line 789:
                         END IF                         END IF
                      END IF                      END IF
-                   END DO        ! all data in subset+                   END DO       ! all data in subset
                    IF (.NOT.match) ! there is one descriptor in condition which                    IF (.NOT.match) ! there is one descriptor in condition which
-                      GO TO 300  ! subset does not match, so go to next value line +                      EXIT       ! subset does not match, so go to next 
-                END DO           ! all descriptors in condition+                                   value line 
 +                END DO          ! all descriptors in condition
                 IF (match) THEN                 IF (match) THEN
                    num_found = num_found + 1                    num_found = num_found + 1
                    found_list(num_found) = nsub                    found_list(num_found) = nsub
                    GO TO 500    ! next subset                    GO TO 500    ! next subset
-               END IF +                END IF 
- 300           CONTINUE +            END DO              ! all filter value lines (for given) condition
-            END DO              ! all filter values lines (for given) condition+
  400        CONTINUE  400        CONTINUE
          END DO                 ! all different conditions          END DO                 ! all different conditions
Line 707: Line 810:
  
 C     Identify pressure, temperature etc and print parameter=value to C     Identify pressure, temperature etc and print parameter=value to
-C     screen. Note: have seen one example (high resolution data) where +C     screen. Note: have seen high resolution data with 7002 HEIGHT OR 
-C     7002 HEIGHT OR ALTITUDE was used as vertical coordinate instead of +C     ALTITUDE and wind profiler data with 007009 GEOPOTENTIAL HEIGHT 
-C     7004 PRESSURE (10004 was used for pressure). Not able to handle +C     used as vertical coordinate instead of 7004 PRESSURE (10004 was 
-C     that in present code.+C     used for pressure in the first case). Not able to handle that in 
 +C     present code.
       SUBROUTINE print_sounding_values(ksub,kxelem,ktdexl,ktdexp,values,       SUBROUTINE print_sounding_values(ksub,kxelem,ktdexl,ktdexp,values,
-         cvals,rectangle,verbose)+         cvals,rectangle,obstype,verbose)
       IMPLICIT NONE       IMPLICIT NONE
  
Line 722: Line 826:
       CHARACTER*80 cvals(*)     ! Input: CCITTIA5 Bufr elements entries (one subset)       CHARACTER*80 cvals(*)     ! Input: CCITTIA5 Bufr elements entries (one subset)
       LOGICAL rectangle         ! Input: TRUE if observations are wanted for a rectangle only       LOGICAL rectangle         ! Input: TRUE if observations are wanted for a rectangle only
 +      CHARACTER(LEN=*) obstype  ! Input: influence flow if set to 'sounding-'
       INTEGER verbose           ! Input: verbose level       INTEGER verbose           ! Input: verbose level
  
Line 728: Line 833:
  
       REAL*8 II,iii,ix,year,month,day,hour,minute,       REAL*8 II,iii,ix,year,month,day,hour,minute,
-         longitude,latitude,height +         longitude,latitude,height,wigos_series 
-      CHARACTER*9 DDDD,missing9+      CHARACTER*5 wigos_issuer,wigos_issueno,missing5 
 +      CHARACTER*9 call_sign,missing9 
 +      CHARACTER*8 flight_number,missing8 
 +      CHARACTER*16 wigos_localid,missing16 
       CHARACTER one_bits       CHARACTER one_bits
       REAL*8 value       REAL*8 value
-      INTEGER idx,cidx,desc,n,maxlevel,numlevels +      INTEGER idx,cidx,desc,n,maxlevel,numlevels,i,ind,ind2,ind3 
-      PARAMETER(maxlevel=1000)+      PARAMETER(maxlevel=100000)
  
       REAL*8 P(maxlevel),D(maxlevel),F(maxlevel),       REAL*8 P(maxlevel),D(maxlevel),F(maxlevel),
          T(maxlevel),TD(maxlevel),h(maxlevel),          T(maxlevel),TD(maxlevel),h(maxlevel),
          la(maxlevel),lo(maxlevel),tp(maxlevel), ! displacements (lat, lon, time)          la(maxlevel),lo(maxlevel),tp(maxlevel), ! displacements (lat, lon, time)
-         wsb(maxlevel),wsa(maxlevel) ! absolute wind shear in 1 km layer below/above +         wsb(maxlevel),wsa(maxlevel) ! absolute wind shear in 1 km layer below/above
       CHARACTER*8 vss(maxlevel) ! Vertical sounding significance       CHARACTER*8 vss(maxlevel) ! Vertical sounding significance
 +      CHARACTER*8 vss_missing
 +      LOGICAL reduce ! Set to TRUE if we should skip levels with
 +                     ! vertical sounding significance missing or equal
 +                     ! to 0
  
 C     Variables used for geographical filtering av observations C     Variables used for geographical filtering av observations
       REAL*8 x1,y1,x2,y2       REAL*8 x1,y1,x2,y2
       COMMON /COM_RECTANGLE/  x1,y1,x2,y2       COMMON /COM_RECTANGLE/  x1,y1,x2,y2
 +
 +C     Functions
 +      INTEGER lenstr
 +      CHARACTER*9 ctrim  ! length must be >= longest variable ctrim is used for
 +
 +      IF (obstype.EQ.'sounding-') THEN
 +         reduce = .TRUE.
 +      ELSE
 +         reduce = .FALSE.
 +      END IF
  
       one_bits = CHAR(255)       one_bits = CHAR(255)
-      WRITE(missing9,'(9A)') one_bits,one_bits,one_bits,one_bits, +      WRITE(missing5,'(5A)') one_bits,one_bits,one_bits,one_bits, 
-         one_bits,one_bits,one_bits,one_bits,one_bits+         one_bits 
 +      WRITE(missing8,'(8A)'one_bits,one_bits,one_bits,one_bits
 +         one_bits,one_bits,one_bits,one_bits 
 +      missing9 = missing8 // one_bits 
 +      missing16 = missing8 // missing8 
 +      vss_missing = '       '
  
 C     Initialize all parameters to missing values C     Initialize all parameters to missing values
-      DDDD = missing9+      call_sign = missing9 
 +      flight_number = missing8 
 +      wigos_issuer = missing5 
 +      wigos_issueno = missing5 
 +      wigos_localid = missing16 
 +      wigos_series = rvind
       II = rvind       II = rvind
       iii= rvind       iii= rvind
Line 771: Line 904:
          lo(n) = rvind          lo(n) = rvind
          tp(n) = rvind          tp(n) = rvind
-         vss(n) =       '+         vss(n) = vss_missing
          wsb(n) = rvind          wsb(n) = rvind
          wsa(n) = rvind          wsa(n) = rvind
Line 781: Line 914:
          desc = ktdexp(idx)          desc = ktdexp(idx)
          value = values(idx + (ksub-1)*kxelem)          value = values(idx + (ksub-1)*kxelem)
 +
 +C     Nothing to do if value is missing (note that the missing value
 +C     returned from libbufr might not be exactly equal to rvind)
 +         IF (ABS(value - rvind)/rvind.LE.0.001) THEN
 +            CYCLE
 +         END IF
 +
          IF (desc.EQ.1001) THEN ! WMO block number          IF (desc.EQ.1001) THEN ! WMO block number
             II = value             II = value
          ELSE IF (desc.EQ.1002) THEN ! WMO station number          ELSE IF (desc.EQ.1002) THEN ! WMO station number
             iii = value             iii = value
-         ELSE IF (desc.EQ.1011) THEN  ! Ship or mobile land station identifier +         ELSE IF (desc.EQ.1011.OR.   ! Ship or mobile land station identifier 
-            IF (value.NE.rvind) THEN+     +           desc.EQ.1195) THEN  ! Mobil land station identifier
                cidx = int(value/1000)                cidx = int(value/1000)
-               DDDD = cvals(cidx) ! CCITTIA5 data +               call_sign = cvals(cidx) ! CCITTIA5 data 
-            END IF+               call_sign = ctrim(call_sign,9,missing9) 
 +         ELSE IF (desc.EQ.1006) THEN ! Aircraft flight number, used for dropsondes 
 +            cidx = int(value/1000) 
 +            flight_number = cvals(cidx) ! CCITTIA5 data 
 +            flight_number = ctrim(flight_number,8,missing8) 
 +         ELSE IF (desc.EQ.1125) THEN ! WIGOS identifier series 
 +            wigos_series = value 
 +         ELSE IF (desc.EQ.1126) THEN ! WIGOS issuer of identifier 
 +            i = NINT(value) 
 +            WRITE(wigos_issuer,'(I5)') i 
 +            wigos_issuer = ADJUSTL(wigos_issuer) 
 +         ELSE IF (desc.EQ.1127) THEN ! WIGOS issue number 
 +            i = NINT(value) 
 +            WRITE(wigos_issueno,'(I5)') i 
 +            wigos_issueno = ADJUSTL(wigos_issueno) 
 +         ELSE IF (desc.EQ.1128) THEN  ! WIGOS local identifier 
 +            cidx = int(value/1000) 
 +            wigos_localid = cvals(cidx) ! CCITTIA5 data 
 +            wigos_localid = ctrim(wigos_localid,16,missing16)
          ELSE IF (desc.EQ.2001) THEN ! Type of station          ELSE IF (desc.EQ.2001) THEN ! Type of station
             ix = value             ix = value
Line 802: Line 960:
          ELSE IF (desc.EQ.4005) THEN ! Minute          ELSE IF (desc.EQ.4005) THEN ! Minute
             minute = value             minute = value
-         ELSE IF (desc.EQ.5001) THEN ! Latitude (high accuracy)+C     Seen 5002 and 6002 used for each level in high resolution data 
 +         ELSE IF (desc.EQ.5001 .AND. latitude.EQ.rvind) THEN ! Latitude (high accuracy)
             latitude = value             latitude = value
-         ELSE IF (desc.EQ.5002) THEN ! Latitude (coarse accuracy)+         ELSE IF (desc.EQ.5002 .AND. latitude.EQ.rvind) THEN ! Latitude (coarse accuracy)
             latitude = value             latitude = value
-         ELSE IF (desc.EQ.6001) THEN ! Longitude (high accuracy)+         ELSE IF (desc.EQ.6001 .AND. longitude.EQ.rvind) THEN ! Longitude (high accuracy)
             longitude = value             longitude = value
-         ELSE IF (desc.EQ.6002) THEN ! Longitude (coarse accuracy)+         ELSE IF (desc.EQ.6002 .AND. longitude.EQ.rvind) THEN ! Longitude (coarse accuracy)
             longitude = value             longitude = value
-         ELSE IF (desc.EQ.7001) THEN ! Height of station +         ELSE IF (desc.EQ.7001.OR.  ! Height of station 
-            height = value+               desc.EQ.7030.OR.   ! Height of station ground above mean sea level 
 +               desc.EQ.7031.OR.   ! Height of barometer above mean sea level 
 +               desc.EQ.7007) THEN ! Height (i.e. of release of sonde above mean sea level) 
 +            IF (height.EQ.rvind) THEN 
 +               height = value 
 +            END IF 
 +         ELSE IF (desc.EQ.4086.AND.n.LT.maxlevel) THEN ! Long time period or displacement [second] 
 +C     In WMO template (309052) descriptors 004086 and 008042 comes BEFORE 7004 pressure 
 +            tp(n+1) = value 
 +         ELSE IF (desc.EQ.8042.AND.n.LT.maxlevel) THEN ! Extended vertical sounding significance 
 +            CALL vss_8042(NINT(value),vss(n+1))
          ELSE IF (desc.EQ.7004) THEN ! Pressure          ELSE IF (desc.EQ.7004) THEN ! Pressure
             n = n + 1           ! new level             n = n + 1           ! new level
             IF (n.GT.maxlevel) THEN             IF (n.GT.maxlevel) THEN
 +               n = maxlevel
                WRITE(*,*) 'Too many levels! Skipping rest of message'                WRITE(*,*) 'Too many levels! Skipping rest of message'
                GOTO 110                GOTO 110
             END IF             END IF
             P(n) = value             P(n) = value
-         ELSE IF (desc.EQ.11001) THEN ! Wind direction +C     All following descriptors come after pressure in 309052 (or Hirlam template) 
-            D(n) = value +         ELSE IF (n.GT.0 .AND. n.LE.maxlevel) THEN 
-         ELSE IF (desc.EQ.11002) THEN ! Wind speed +            IF (desc.EQ.11001) THEN ! Wind direction 
-            F(n) = value +               D(n) = value 
-         ELSE IF (desc.EQ.12101) THEN ! Temperature/dry bulb temperature (16 bits) +            ELSE IF (desc.EQ.11002) THEN ! Wind speed 
-            T(n) = value +               F(n) = value 
-         ELSE IF (desc.EQ.12001) THEN ! Temperature/dry bulb temperature (12 bits) +            ELSE IF (desc.EQ.12101) THEN ! Temperature/dry bulb temperature (16 bits) 
-            T(n) = value +               T(n) = value 
-         ELSE IF (desc.EQ.12103) THEN ! Dew-point temperature (16 bits) +            ELSE IF (desc.EQ.12001) THEN ! Temperature/dry bulb temperature (12 bits) 
-            TD(n) = value +               T(n) = value 
-         ELSE IF (desc.EQ.12003) THEN ! Dew-point temperature (12 bits) +            ELSE IF (desc.EQ.12103) THEN ! Dew-point temperature (16 bits) 
-            TD(n) = value +               TD(n) = value 
-         ELSE IF (desc.EQ.10003.AND.value.NE.rvind) THEN ! Geopotential +            ELSE IF (desc.EQ.12003) THEN ! Dew-point temperature (12 bits) 
-            h(n) = value/9.81 +               TD(n) = value 
-         ELSE IF (desc.EQ.10009) THEN ! Geopotential height +            ELSE IF (desc.EQ.10003.AND.value.NE.rvind) THEN ! Geopotential 
-            h(n) = value +               h(n) = value/9.81 
-         ELSE IF (desc.EQ.5015) THEN ! Latitude displacement +            ELSE IF (desc.EQ.10009) THEN ! Geopotential height 
-            la(n) = value +               h(n) = value 
-         ELSE IF (desc.EQ.6015) THEN ! Longitude displacement +            ELSE IF (desc.EQ.5015) THEN ! Latitude displacement 
-            lo(n) = value +               la(n) = value 
-         ELSE IF (desc.EQ.4086) THEN ! Long time period or displacement [second] +            ELSE IF (desc.EQ.6015) THEN ! Longitude displacement 
-            tp(n) = value +               lo(n) = value 
-         ELSE IF (desc.EQ.8001 .AND. value.NE.rvind) THEN ! Vertical sounding significance +            ELSE IF (desc.EQ.8001 .AND. value.NE.rvind) THEN ! Vertical sounding significance 
-C     In HIRLAM templates 008001 comes AFTER 7004 pressure +C     In HIRLAM template (309007) 008001 comes AFTER 7004 pressure 
-            CALL vss_8001(NINT(value),vss(n)) +               CALL vss_8001(NINT(value),vss(n)) 
-         ELSE IF (desc.EQ.8042 .AND. value.NE.rvind) THEN ! Extended vertical sounding significance +            ELSE IF (desc.EQ.11061) THEN ! Absolute wind shear in 1 km layer below 
-C     In WMO templates 008042 comes BEFORE 7004 pressure +               wsb(n) = value 
-            CALL vss_8042(NINT(value),vss(n+1)) +            ELSE IF (desc.EQ.11062) THEN ! Absolute wind shear in 1 km layer above 
-         ELSE IF (desc.EQ.11061) THEN ! Absolute wind shear in 1 km layer below +               wsa(n) = value 
-            wsb(n) = value +            END IF
-         ELSE IF (desc.EQ.11062) THEN ! Absolute wind shear in 1 km layer above +
-            wsa(n) = value+
          END IF          END IF
       END DO       END DO
Line 862: Line 1030:
       END IF       END IF
  
-      WRITE(*,*)+
       IF (II.NE.rvind .AND. iii.NE.rvind) THEN       IF (II.NE.rvind .AND. iii.NE.rvind) THEN
 +         WRITE(*,*)
          WRITE(*,'(A,I5.5)') 'wmonr=',NINT(II)*1000 + NINT(iii)          WRITE(*,'(A,I5.5)') 'wmonr=',NINT(II)*1000 + NINT(iii)
-      ELSE IF (DDDD.NE.missing9) THEN +      ELSE IF (wigos_series.NE.rvind .AND. wigos_issuer.NE.missing5 
-         WRITE(*,'(A,A)') 'DDDD=',DDDD+            .AND. wigos_issueno.NE.missing5 
 +            .AND. wigos_localid.NE.missing16) THEN 
 +         ind = index(wigos_issuer,' ') - 1 
 +         IF (ind.EQ.-1) ind = 5 
 +         ind2 = index(wigos_issueno,' ') - 1 
 +         IF (ind2.EQ.-1) ind2 = 5 
 +         ind3 = index(wigos_localid,' ') - 1 
 +         IF (ind3.EQ.-1) ind3 = 16 
 +         WRITE(*,*) 
 +         WRITE(*,'(A,I1.1,A1,A,A1,A,A1,A)'
 +            'wigosid=',NINT(wigos_series), 
 +            '-',wigos_issuer(1:ind), 
 +            '-',wigos_issueno(1:ind2), 
 +            '-',wigos_localid(1:ind3) 
 +      ELSE IF (call_sign.NE.missing9) THEN 
 +         WRITE(*,*) 
 +         WRITE(*,'(A,A)') 'call_sign=',call_sign(1:lenstr(call_sign,1)) 
 +      ELSE IF (flight_number.NE.missing8) THEN 
 +         WRITE(*,*) 
 +         WRITE(*,'(A,A)') 'aircraft=', 
 +            flight_number(1:lenstr(flight_number,1))
       ELSE       ELSE
          IF (verbose .GT. 1) THEN          IF (verbose .GT. 1) THEN
-            WRITE(*,*) 'Both wmonr and call sign (DDDD)', +            WRITE(*,*) 
-               ' are missing         !!!'+            WRITE(*,*) 'Both wmonr, wigosid, call sign and aircraft
 +               // flight number are missing !!!'
          END IF          END IF
          RETURN          RETURN
Line 886: Line 1076:
          END IF          END IF
       ENDIF       ENDIF
-      IF (NINT(ix).EQ.0) THEN +      IF (ix.NE.rvind) THEN 
-         WRITE(*,'(A,A)') 'type=Automatic' +         IF (NINT(ix).EQ.0) THEN 
-      ELSE IF (NINT(ix).EQ.1) THEN +            WRITE(*,'(A,A)') 'type=Automatic' 
-         WRITE(*,'(A,A)') 'type=Manned' +         ELSE IF (NINT(ix).EQ.1) THEN 
-      ELSE IF (NINT(ix).EQ.2) THEN +            WRITE(*,'(A,A)') 'type=Manned' 
-         WRITE(*,'(A,A)') 'type=Hybrid'+         ELSE IF (NINT(ix).EQ.2) THEN 
 +            WRITE(*,'(A,A)') 'type=Hybrid' 
 +         END IF
       END IF       END IF
       IF (latitude.NE.rvind) THEN       IF (latitude.NE.rvind) THEN
Line 904: Line 1096:
  
       DO n=1,numlevels       DO n=1,numlevels
 +         IF (reduce .AND. vss(n).EQ.vss_missing) CYCLE
          WRITE(*,'(A,I12)'),'n=',n          WRITE(*,'(A,I12)'),'n=',n
 C     The following 3 parameters are not found in TAC TEMP C     The following 3 parameters are not found in TAC TEMP
 +         IF (tp(n).NE.rvind) THEN
 +            WRITE(*,'(A,I12)') 't=',NINT(tp(n))
 +         END IF
          IF (la(n).NE.rvind) THEN          IF (la(n).NE.rvind) THEN
             WRITE(*,'(A,F11.5)') 'la=',la(n)             WRITE(*,'(A,F11.5)') 'la=',la(n)
Line 912: Line 1108:
             WRITE(*,'(A,F11.5)') 'lo=',lo(n)             WRITE(*,'(A,F11.5)') 'lo=',lo(n)
          END IF          END IF
-         IF (tp(n).NE.rvind) THEN +C     Choose to display vss even when it is empty
-            WRITE(*,'(A,I12)') 't=',NINT(tp(n)) +
-         END IF +
-C     Chhose to display vss even when it is empty+
          WRITE(*,'(A,A10)') 'vss=',vss(n)          WRITE(*,'(A,A10)') 'vss=',vss(n)
          IF (P(n).NE.rvind) THEN          IF (P(n).NE.rvind) THEN
Line 921: Line 1114:
          END IF          END IF
          IF (h(n).NE.rvind) THEN          IF (h(n).NE.rvind) THEN
-            WRITE(*,'(A,I11)') 'hh=',NINT(h(n))+            WRITE(*,'(A,I11)') 'gh=',NINT(h(n))
          END IF          END IF
          IF (D(n).NE.rvind) THEN          IF (D(n).NE.rvind) THEN
Line 944: Line 1137:
  
       END SUBROUTINE print_sounding_values       END SUBROUTINE print_sounding_values
 +
 +C     -----------------------------------------------------------------
 +
 +C     Identify height, wind and data quality parameters and print parameter=value to
 +C     screen for the given heights.
 +      SUBROUTINE print_radar_profiler_values(ksub,kxelem,ktdexl,ktdexp,
 +         values,cvals,rectangle,verbose)
 +      IMPLICIT NONE
 +
 +      INTEGER ksub              ! Input: number of subset currently processed
 +      INTEGER kxelem            ! Input: expected (max) number of expanded elements
 +      INTEGER ktdexl            ! Input: number of entries in list of expanded data descriptors
 +      INTEGER ktdexp(*)         ! Input: array containing expanded data descriptors
 +      REAL*8 values(*)          ! Input: expanded data values (one subset)
 +      CHARACTER*80 cvals(*)     ! Input: CCITTIA5 Bufr elements entries (one subset)
 +      LOGICAL rectangle         ! Input: TRUE if observations are wanted for a rectangle only
 +      INTEGER verbose           ! Input: verbose level
 +
 +      REAL*8 rvind              ! missing value for real*8 data
 +      PARAMETER (rvind=1.7E38)
 +
 +      REAL*8 II,iii,ix,year,month,day,hour,minute,
 +         longitude,latitude,height
 +      CHARACTER*9 call_sign,missing9
 +      CHARACTER one_bits
 +      REAL*8 value
 +      INTEGER idx,cidx,desc,n,maxlevel,numlevels,ind
 +      PARAMETER(maxlevel=1000)
 +
 +      REAL*8 HH(maxlevel),D(maxlevel),F(maxlevel),
 +         Q1(maxlevel),WC(maxlevel),Q2(maxlevel)
 +
 +C     Variables used for geographical filtering av observations
 +      REAL*8 x1,y1,x2,y2
 +      COMMON /COM_RECTANGLE/  x1,y1,x2,y2
 +
 +C     Functions
 +      INTEGER lenstr
 +      CHARACTER*9 ctrim  ! length must be >= longest variable ctrim is used for
 +
 +      one_bits = CHAR(255)
 +      WRITE(missing9,'(9A)') one_bits,one_bits,one_bits,one_bits,
 +         one_bits,one_bits,one_bits,one_bits,one_bits
 +
 +C     Initialize all parameters to missing values
 +      call_sign = missing9
 +      II = rvind
 +      iii= rvind
 +      year = rvind
 +      month = rvind
 +      day = rvind
 +      hour = rvind
 +      minute = rvind
 +      latitude = rvind
 +      longitude = rvind
 +      height = rvind
 +      DO n=1,maxlevel
 +         HH(n) = rvind
 +         D(n) = rvind
 +         F(n) = rvind
 +         Q1(n) = rvind
 +         WC(n) = rvind
 +         Q2(n) = rvind
 +      END DO
 +
 +C     Loop through all expanded descriptors
 +      n = 0 ! Numbering the pressure levels
 +      DO idx=1,ktdexl
 +         desc = ktdexp(idx)
 +         value = values(idx + (ksub-1)*kxelem)
 +
 +C     Nothing to do if value is missing (note that the missing value
 +C     returned from libbufr might not be exactly equal to rvind)
 +         IF (ABS(value - rvind)/rvind.LE.0.001) THEN
 +            CYCLE
 +         END IF
 +
 +         IF (desc.EQ.1001) THEN ! WMO block number
 +            II = value
 +         ELSE IF (desc.EQ.1002) THEN ! WMO station number
 +            iii = value
 +         ELSE IF (desc.EQ.1011.OR.   ! Ship or mobile land station identifier
 +               desc.EQ.1195) THEN  ! Mobil land station identifier
 +               cidx = int(value/1000)
 +               call_sign = cvals(cidx) ! CCITTIA5 data
 +               call_sign = ctrim(call_sign,9,missing9)
 +         ELSE IF (desc.EQ.2001) THEN ! Type of station
 +            ix = value
 +         ELSE IF (desc.EQ.4001) THEN ! Year
 +            year = value
 +         ELSE IF (desc.EQ.4002) THEN ! Month
 +            month = value
 +         ELSE IF (desc.EQ.4003) THEN ! Day
 +            day = value
 +         ELSE IF (desc.EQ.4004) THEN ! Hour
 +            hour = value
 +         ELSE IF (desc.EQ.4005) THEN ! Minute
 +            minute = value
 +C     Seen 5002 and 6002 used for each level in high resolution data
 +         ELSE IF (desc.EQ.5001 .AND. latitude.EQ.rvind) THEN ! Latitude (high accuracy)
 +            latitude = value
 +         ELSE IF (desc.EQ.5002 .AND. latitude.EQ.rvind) THEN ! Latitude (coarse accuracy)
 +            latitude = value
 +         ELSE IF (desc.EQ.6001 .AND. longitude.EQ.rvind) THEN ! Longitude (high accuracy)
 +            longitude = value
 +         ELSE IF (desc.EQ.6002 .AND. longitude.EQ.rvind) THEN ! Longitude (coarse accuracy)
 +            longitude = value
 +         ELSE IF (desc.EQ.7001) THEN  ! Height of station
 +            IF (height.EQ.rvind) THEN
 +               height = value
 +            END IF
 +         ELSE IF (desc.EQ.7007) THEN ! Height
 +            n = n + 1           ! new level
 +            IF (n.GT.maxlevel) THEN
 +               n = maxlevel
 +               WRITE(*,*) 'Too many levels! Skipping rest of message'
 +               GOTO 110
 +            END IF
 +            HH(n) = value
 +C     All following descriptors come after 7007 height
 +         ELSE IF (n.GT.0 .AND. n.LE.maxlevel) THEN
 +            IF (desc.EQ.11001) THEN ! Wind direction
 +               D(n) = value
 +            ELSE IF (desc.EQ.11002) THEN ! Wind speed
 +               F(n) = value
 +            ELSE IF (desc.EQ.11006) THEN ! W-component
 +               WC(n) = value
 +            ELSE IF (desc.EQ.33002) THEN ! Quality information, included 2 times per level
 +               IF (ktdexp(idx-1).EQ.11002) THEN
 +                  Q1(n) = value
 +               ELSE
 +                  Q2(n) = value
 +               END IF
 +            END IF
 +         END IF
 +      END DO
 + 110  CONTINUE
 +      numlevels = n
 +
 +      IF (rectangle) THEN
 +         IF (longitude.EQ.rvind .OR. latitude.EQ.rvind
 +            .OR. longitude.LT.x1 .OR. longitude.GT.x2
 +            .OR. latitude.LT.y1 .OR. latitude.GT.y2) RETURN
 +      END IF
 +
 +      IF (II.NE.rvind .AND. iii.NE.rvind) THEN
 +         WRITE(*,*)
 +         WRITE(*,'(A,I5.5)') 'wmonr=',NINT(II)*1000 + NINT(iii)
 +      ELSE IF (call_sign.NE.missing9) THEN
 +         WRITE(*,*)
 +         WRITE(*,'(A,A)') 'call_sign=',call_sign(1:lenstr(call_sign,1))
 +      ELSE
 +         IF (verbose .GT. 1) THEN
 +            WRITE(*,*)
 +            WRITE(*,*) 'Both wmonr and call sign are missing!!!'
 +         END IF
 +         RETURN
 +      END IF
 +
 +      IF (year.NE.rvind.AND.month.NE.rvind.AND.day.NE.rvind
 +         .AND.hour.NE.rvind.AND.minute.NE.rvind) THEN
 +         WRITE(*,900),NINT(year),NINT(month),NINT(day),
 +            NINT(hour),NINT(minute)
 + 900     FORMAT('obstime=',I4,'-',I2.2,'-',I2.2,' ',I2.2,':',I2.2,':00')
 +      ELSE
 +         IF (verbose .GT. 1) THEN
 +            WRITE(*,*) 'obstime is missing!!!'
 +            RETURN
 +         END IF
 +      ENDIF
 +      IF (ix.NE.rvind) THEN
 +         IF (NINT(ix).EQ.0) THEN
 +            WRITE(*,'(A,A)') 'type=Automatic'
 +         ELSE IF (NINT(ix).EQ.1) THEN
 +            WRITE(*,'(A,A)') 'type=Manned'
 +         ELSE IF (NINT(ix).EQ.2) THEN
 +            WRITE(*,'(A,A)') 'type=Hybrid'
 +         END IF
 +      END IF
 +      IF (latitude.NE.rvind) THEN
 +         WRITE(*,'(A,F10.5)') 'lat=',latitude
 +      END IF
 +      IF (longitude.NE.rvind) THEN
 +         WRITE(*,'(A,F10.5)') 'lon=',longitude
 +      END IF
 +      IF (height.NE.rvind) THEN
 +         WRITE(*,'(A,I7)') 'height=',NINT(height)
 +      END IF
 +
 +      DO n=1,numlevels
 +         WRITE(*,'(A,I12)'),'n=',n
 +         IF (HH(n).NE.rvind) THEN
 +            WRITE(*,'(A,F11.1)') 'HH=',HH(n) ! m
 +         END IF
 +         IF (D(n).NE.rvind) THEN
 +            WRITE(*,'(A,I11)') 'DD=',NINT(D(n))
 +         END IF
 +         IF (F(n).NE.rvind) THEN
 +            WRITE(*,'(A,F11.1)') 'FF=',F(n)
 +         END IF
 +         IF (Q1(n).NE.rvind) THEN
 +            WRITE(*,'(A,I11)') 'Q1=',NINT(Q1(n))
 +         END IF
 +         IF (WC(n).NE.rvind) THEN
 +            WRITE(*,'(A,I11)') 'WC=',NINT(WC(n))
 +         END IF
 +         IF (Q2(n).NE.rvind) THEN
 +            WRITE(*,'(A,I11)') 'Q2=',NINT(Q2(n))
 +         END IF
 +      END DO
 +
 +      END SUBROUTINE print_radar_profiler_values
  
 C     ----------------------------------------------------------------- C     -----------------------------------------------------------------
  
       SUBROUTINE print_surface_values(ksub,kxelem,ktdexl,ktdexp,values,       SUBROUTINE print_surface_values(ksub,kxelem,ktdexl,ktdexp,values,
-         cvals,rectangle,verbose)+         cvals,rectangle,metar,verbose)
 C     Identify pressure, temperature etc and print parameter=value to screen C     Identify pressure, temperature etc and print parameter=value to screen
       IMPLICIT NONE       IMPLICIT NONE
Line 959: Line 1364:
       CHARACTER*80 cvals(*)     ! Input: CCITTIA5 Bufr elements entries (one subset)       CHARACTER*80 cvals(*)     ! Input: CCITTIA5 Bufr elements entries (one subset)
       LOGICAL rectangle         ! Input: TRUE if observations are wanted for a rectangle only       LOGICAL rectangle         ! Input: TRUE if observations are wanted for a rectangle only
 +      LOGICAL metar             ! Input: TRUE if metar (data subcategory 5)
       INTEGER verbose           ! Input: verbose level       INTEGER verbose           ! Input: verbose level
  
Line 964: Line 1370:
       PARAMETER (rvind=1.7E38)       PARAMETER (rvind=1.7E38)
  
-      CHARACTER*8 icao_id,missing8,spc8 +      CHARACTER*5 wigos_issuer,wigos_issueno,missing5 
-      CHARACTER*9 DDDD,missing9,spc9 +      CHARACTER*8 icao_id,missing8 
-      CHARACTER*20 name,missing20,spc20+      CHARACTER*9 call_sign,missing9 
 +      CHARACTER*16 wigos_localid,missing16 
 +      CHARACTER*20 name,missing20 
 +      CHARACTER*32 long_name,missing32
 C     Parameters defined in Kvalobs C     Parameters defined in Kvalobs
-      REAL*8 AA,BI,CH,CI,CL,CM,DD,DG,DG_010,DG_1,DI,DW1,DW2, +      REAL*8 AA,BI,CH,CI,CL,CM,DD,DG,DG_010,DG_1,DG_X,DI,DW1,DW2, 
-         E,EM,ES,EV_1,EV_24,FF,FG,FG_010,FG_1,FX,HL, +         EE,ES,EV_1,EV_24,FF,FG,FG_010,FG_1,FG_X,FX,FX_1,FX_X,HL, 
-         HW,HW1,HW2,NH,NN,OT_1,OT_24,PH,PO,PP,PR,PW,PW1,PW2, +         HW,HW1,HW2,HWA,NH,NN,OT_1,OT_24,PH,PO,PP,PR,PW,PW1,PW2,PWA, 
-         RR_1,RR_3,RR_6,RR_12,RR_24,RS,SA,SG,SI, +         QD,QE,QK,QL,QO,QS,QD_24,QE_24,QK_24,QL_24,QO_24,QS_24
-         TA,TAN_12,TAX_12,TD,TGN_12,TW,UU,VV,W1,W2,WW,XIS,ZI,+         RR_1,RR_3,RR_6,RR_12,RR_24,RS,SA,SG,SI,SS_24
 +         TA,TAN_12,TAX_12,TAN,TAX,TD,TGN_12,TW,UU,VV,W1,W2,WW,XIS,ZI,
 C     Other parameters C     Other parameters
-         year,month,day,hour,minute, +         year,month,day,hour,minute,a3,buoy_id5,buoy_id7,ds, 
-         a3,buoy_id,ds,height,hhh,hour_p,II,iii,ix,latitude,longitude,+         height,hhh,hp,hour_p,II,iii,ix,latitude,longitude,
          minute_p,TbTbTb,vert_sign_first,vs,wmo_region_number,          minute_p,TbTbTb,vert_sign_first,vs,wmo_region_number,
-         wmo_region_subarea+         wmo_region_subarea,state_id,national_number, 
 +         wigos_series
       REAL*8 vert_sign(4),CC(4),HS(4),NS(4)       REAL*8 vert_sign(4),CC(4),HS(4),NS(4)
       INTEGER idx,cidx       INTEGER idx,cidx
       INTEGER cloud_type_count  ! Will be increased by one for each 020012       INTEGER cloud_type_count  ! Will be increased by one for each 020012
-                                ! (cloud type) encountered (0 initially) +                                ! (cloud type) encountered (0 initially)
-      INTEGER num_cloud_layers  ! Number of individual cloud layers, +                                ! Not used for metar 
-                                ! set to value of 031001 (delayed +      INTEGER num_cloud_layers  ! Number of individual cloud layers, set 
-                                ! descriptor) if this is met immediately +                                ! to value of 031001 (delayed descriptor 
-                                ! after a 020012 descriptor (-1 initially)+                                ! replication factor) if this is met immediately 
 +                                ! after a 020012 descriptor (-1 initially)
 +                                ! For metar num_cloud_layers is increased 
 +                                ! by one for each new 020011
       LOGICAL bad_cloud_data    ! Set to true if something serious wrong is       LOGICAL bad_cloud_data    ! Set to true if something serious wrong is
                                 ! found in cloud data. No more cloud                                 ! found in cloud data. No more cloud
Line 993: Line 1407:
                                 ! surface') is encountered with a value different                                 ! surface') is encountered with a value different
                                 ! from 0                                 ! from 0
 +      LOGICAL time_of_last_position ! Set to true if 008021 time significance is
 +                                    ! included with value 26
       CHARACTER one_bits       CHARACTER one_bits
       REAL*8 value       REAL*8 value
-      INTEGER desc,i,mm,hh +      INTEGER desc,i,mm,hh,ind,ind2,ind3 
-      INTEGER degree2dir,HStoWMO_HSHS,NNtoWMO_N+      INTEGER degree2dir,NNtoWMO_N
  
 C     Variables used for geographical filtering av observations C     Variables used for geographical filtering av observations
Line 1002: Line 1418:
       REAL*8 x1,y1,x2,y2       REAL*8 x1,y1,x2,y2
       COMMON /COM_RECTANGLE/  x1,y1,x2,y2       COMMON /COM_RECTANGLE/  x1,y1,x2,y2
 +
 +C     Functions
 +      CHARACTER*32 ctrim ! length must be >= longest variable ctrim is used for
 +      INTEGER lenstr
  
       one_bits = CHAR(255)       one_bits = CHAR(255)
 +      WRITE(missing5,'(5A)') one_bits,one_bits,one_bits,one_bits,
 +         one_bits
       WRITE(missing8,'(8A)') one_bits,one_bits,one_bits,one_bits,       WRITE(missing8,'(8A)') one_bits,one_bits,one_bits,one_bits,
          one_bits,one_bits,one_bits,one_bits          one_bits,one_bits,one_bits,one_bits
       missing9 = missing8 // one_bits       missing9 = missing8 // one_bits
 +      missing16 = missing8 // missing8
       missing20 = missing9 // missing9 // one_bits // one_bits       missing20 = missing9 // missing9 // one_bits // one_bits
-      spc8        ' +      missing32 missing16 // missing16
-      spc9 = '         ' +
-      spc20 = '                    '+
  
       cloud_type_count = 0       cloud_type_count = 0
Line 1016: Line 1437:
       num_cloud_layers = -1       num_cloud_layers = -1
       surface_data = .TRUE.       surface_data = .TRUE.
 +      time_of_last_position = .FALSE.
  
 C     Initialize all parameters to missing values C     Initialize all parameters to missing values
Line 1021: Line 1443:
       minute_p = rvind       minute_p = rvind
       icao_id = missing8       icao_id = missing8
-      DDDD = missing9+      call_sign = missing9 
 +      wigos_issuer = missing5 
 +      wigos_issueno = missing5 
 +      wigos_localid = missing16
       name = missing20       name = missing20
 +      long_name = missing32
       AA = rvind       AA = rvind
       BI = rvind       BI = rvind
Line 1033: Line 1459:
       DG_010 = rvind       DG_010 = rvind
       DG_1 = rvind       DG_1 = rvind
 +      DG_X = rvind
       DI = rvind       DI = rvind
-      ds = rvind 
       DW1 = rvind       DW1 = rvind
       DW2 = rvind       DW2 = rvind
 +      EE = rvind
       ES = rvind       ES = rvind
-      E = rvind 
-      EM = rvind 
       EV_1 = rvind       EV_1 = rvind
       EV_24 = rvind       EV_24 = rvind
Line 1046: Line 1471:
       FG_010 = rvind       FG_010 = rvind
       FG_1 = rvind       FG_1 = rvind
 +      FG_X = rvind
       FX = rvind       FX = rvind
 +      FX_1 = rvind
 +      FX_X = rvind
       HL = rvind       HL = rvind
       HW = rvind       HW = rvind
       HW1 = rvind       HW1 = rvind
       HW2 = rvind       HW2 = rvind
 +      HWA = rvind
       NH = rvind       NH = rvind
       NN = rvind       NN = rvind
Line 1063: Line 1492:
       PW1 = rvind       PW1 = rvind
       PW2 = rvind       PW2 = rvind
 +      PWA = rvind
 +      QD = rvind
 +      QE = rvind
 +      QK = rvind
 +      QL = rvind
 +      QO = rvind
 +      QS = rvind
 +      QD_24 = rvind
 +      QE_24 = rvind
 +      QK_24 = rvind
 +      QL_24 = rvind
 +      QO_24 = rvind
 +      QS_24 = rvind
       RR_1 = rvind       RR_1 = rvind
       RR_3 = rvind       RR_3 = rvind
Line 1072: Line 1514:
       SG = rvind       SG = rvind
       SI = rvind       SI = rvind
 +      SS_24 = rvind
       TA = rvind       TA = rvind
       TAN_12 = rvind       TAN_12 = rvind
       TAX_12 = rvind       TAX_12 = rvind
 +      TAN = rvind
 +      TAX = rvind
       TD = rvind       TD = rvind
       TGN_12 = rvind       TGN_12 = rvind
Line 1080: Line 1525:
       UU = rvind       UU = rvind
       VV = rvind       VV = rvind
-      vs = rvind 
       W1 = rvind       W1 = rvind
       W2 = rvind       W2 = rvind
Line 1094: Line 1538:
       longitude = rvind       longitude = rvind
       height = rvind       height = rvind
 +      hp = rvind
       vert_sign_first = rvind       vert_sign_first = rvind
       II = rvind       II = rvind
Line 1103: Line 1548:
       vs = rvind       vs = rvind
       TbTbTb = rvind       TbTbTb = rvind
-      buoy_id = rvind+      buoy_id5 = rvind 
 +      buoy_id7 = rvind
       wmo_region_number = rvind       wmo_region_number = rvind
       wmo_region_subarea = rvind       wmo_region_subarea = rvind
 +      state_id = rvind
 +      national_number = rvind
 +      wigos_series = rvind
  
       DO i=1,4       DO i=1,4
Line 1118: Line 1567:
          desc = ktdexp(idx)          desc = ktdexp(idx)
          value = values(idx + (ksub-1)*kxelem)          value = values(idx + (ksub-1)*kxelem)
 +
 +         IF (ABS(value - rvind)/rvind.LE.0.001) THEN
 +C     Missing value. Only a few descriptors require a reset of
 +C     corresponding parameter in this case. Note that the missing value
 +C     returned from libbufr might not be exactly equal to rvind
 +            IF (desc.EQ.4024) THEN ! Time period or displacement [hour]
 +               hour_p = rvind
 +            ELSE IF (desc.EQ.4025) THEN ! Time period or displacement [minute]
 +               minute_p = rvind
 +C     Delayed descriptor replication factor should never be missing
 +            ELSE IF (desc.EQ.31001) THEN
 +               IF (idx.GT.1 .AND. ktdexp(idx - 1).EQ.20012) THEN
 +                  WRITE(*,*) 'WARNING: delayed descriptor replication'
 +                     // ' factor after 020012 undefined!!!'
 +                  bad_cloud_data = .TRUE.
 +               ELSE
 +                  WRITE(*,*) 'WARNING: delayed descriptor replication'
 +                     // ' factor 31001 undefined!!!'
 +               END IF
 +C     Some counting needed for clouds even for missing values
 +            ELSE IF (desc.EQ.20012 .AND. .NOT.bad_cloud_data) THEN ! Cloud type
 +               cloud_type_count = cloud_type_count + 1
 +               IF (cloud_type_count.GT.3) THEN
 +                  cloud_layer = cloud_type_count - 3
 +               END IF
 +            END IF
 +            CYCLE
 +         END IF
 +
 +C     Continue the loop for non-missing value. For most variables we
 +C     choose to not set the parameter if set before, because if a
 +C     descriptor unexpectedly occurs more than once it is likely that
 +C     the first occurrence is the 'standard' use of the descriptor,
 +C     while the later occurrence(s) might for example be due to data
 +C     required by regional or national reporting practices, added after
 +C     a standard WMO template
          IF (desc.EQ.4024) THEN ! Time period or displacement [hour]          IF (desc.EQ.4024) THEN ! Time period or displacement [hour]
             hour_p = value             hour_p = value
          ELSE IF (desc.EQ.4025) THEN ! Time period or displacement [minute]          ELSE IF (desc.EQ.4025) THEN ! Time period or displacement [minute]
             minute_p = value             minute_p = value
-         ELSE IF (desc.EQ.1001) THEN ! WMO block number +         ELSE IF (desc.EQ.8021) THEN ! Time significance 
-            IF (value.NE.rvind .AND. II.EQ.rvind) THEN +            IF (NINT(value).EQ.26) THEN 
-               II value +               time_of_last_position = .TRUE
-            END IF +            ELSE 
-         ELSE IF (desc.EQ.1002) THEN ! WMO station number +               time_of_last_position .FALSE.
-            IF (value.NE.rvind .AND. iii.EQ.rvind) THEN +
-               iii value+
             END IF             END IF
 +         ELSE IF (desc.EQ.1001 .AND. II.EQ.rvind) THEN ! WMO block number
 +            IF (value.GE.0 .AND. value.LT.100) II = value
 +         ELSE IF (desc.EQ.1002 .AND. iii.EQ.rvind) THEN ! WMO station number
 +            IF (value.GE.0 .AND. value.LT.1000) iii = value
 +         ELSE IF (desc.EQ.1101 .AND. state_id.EQ.rvind) THEN ! WMO member state identifier
 +            IF (value.GE.0 .AND. value.LT.1000) state_id = value
 +         ELSE IF (desc.EQ.1102 .AND. national_number.EQ.rvind) THEN ! National station number
 +            IF (value.GE.0) national_number = value
          ELSE IF (desc.EQ.1015) THEN  ! Station or site name          ELSE IF (desc.EQ.1015) THEN  ! Station or site name
-            IF (value.NE.rvind) THEN +            cidx = int(value/1000) 
-               cidx = int(value/1000) +            name = cvals(cidx)  ! CCITTIA5 data 
-               IF (cvals(cidx).NE.spc20) THEN +            name = ctrim(name,20,missing20) 
-                  name = cvals(cidx) ! CCITTIA5 data +         ELSE IF (desc.EQ.1019) THEN  ! Long station or site name 
-               END IF +            cidx = int(value/1000) 
-            END IF+            long_name = cvals(cidx) ! CCITTIA5 data 
 +            long_name = ctrim(long_name,32,missing32) 
 +         ELSE IF (desc.EQ.1125) THEN ! WIGOS identifier series 
 +            wigos_series = value 
 +         ELSE IF (desc.EQ.1126) THEN ! WIGOS issuer of identifier 
 +            i = NINT(value) 
 +            WRITE(wigos_issuer,'(I5)') i 
 +            wigos_issuer = ADJUSTL(wigos_issuer) 
 +         ELSE IF (desc.EQ.1127) THEN ! WIGOS issue number 
 +            i = NINT(value) 
 +            WRITE(wigos_issueno,'(I5)') i 
 +            wigos_issueno = ADJUSTL(wigos_issueno) 
 +         ELSE IF (desc.EQ.1128) THEN  ! WIGOS local identifier 
 +            cidx = int(value/1000) 
 +            wigos_localid = cvals(cidx) ! CCITTIA5 data 
 +            wigos_localid = ctrim(wigos_localid,16,missing16)
          ELSE IF (desc.EQ.2001) THEN ! Type of station          ELSE IF (desc.EQ.2001) THEN ! Type of station
-            IF (value.NE.rvind .AND. ix.EQ.rvind) THEN+            IF (ix.EQ.rvind) THEN
                ix = value                ix = value
             END IF             END IF
          ELSE IF (desc.EQ.4001) THEN ! Year          ELSE IF (desc.EQ.4001) THEN ! Year
-            IF (value.NE.rvind .AND. year.EQ.rvind) THEN+            IF (year.EQ.rvind.AND..NOT.time_of_last_position) THEN
                year = value                year = value
             END IF             END IF
          ELSE IF (desc.EQ.4002) THEN ! Month          ELSE IF (desc.EQ.4002) THEN ! Month
-            IF (value.NE.rvind .AND. month.EQ.rvind) THEN+            IF (month.EQ.rvind.AND..NOT.time_of_last_position) THEN
                month = value                month = value
             END IF             END IF
          ELSE IF (desc.EQ.4003) THEN ! Day          ELSE IF (desc.EQ.4003) THEN ! Day
-            IF (value.NE.rvind .AND. day.EQ.rvind) THEN+            IF (day.EQ.rvind.AND..NOT.time_of_last_position) THEN
                day = value                day = value
             END IF             END IF
          ELSE IF (desc.EQ.4004) THEN ! Hour          ELSE IF (desc.EQ.4004) THEN ! Hour
-            IF (value.NE.rvind .AND. hour.EQ.rvind) THEN+            IF (hour.EQ.rvind.AND..NOT.time_of_last_position) THEN
                hour = value                hour = value
             END IF             END IF
          ELSE IF (desc.EQ.4005) THEN ! Minute          ELSE IF (desc.EQ.4005) THEN ! Minute
-            IF (value.NE.rvind .AND. minute.EQ.rvind) THEN+            IF (minute.EQ.rvind.AND..NOT.time_of_last_position) THEN
                minute = value                minute = value
             END IF             END IF
-         ELSE IF (desc.EQ.5001) THEN ! Latitude (high accuracy) +         ELSE IF (desc.EQ.5001.OR.  ! Latitude (high accuracy) 
-            IF (value.NE.rvind .AND. latitude.EQ.rvind) THEN+               desc.EQ.5002) THEN ! Latitude (coarse accuracy) 
 +            IF (latitude.EQ.rvind) THEN
                latitude = value                latitude = value
             END IF             END IF
-         ELSE IF (desc.EQ.5002) THEN ! Latitude (coarse accuracy) +         ELSE IF (desc.EQ.6001.OR ! Longitude (high accuracy) 
-            IF (value.NE.rvind .AND. latitude.EQ.rvind) THEN +     +           desc.EQ.6002) THEN ! Longitude (coarse accuracy) 
-               latitude = value +            IF (longitude.EQ.rvind) THEN
-            END IF +
-         ELSE IF (desc.EQ.6001) THEN ! Longitude (high accuracy) +
-            IF (value.NE.rvind .AND. longitude.EQ.rvind) THEN +
-               longitude = value +
-            END IF +
-         ELSE IF (desc.EQ.6002) THEN ! Longitude (coarse accuracy) +
-            IF (value.NE.rvind .AND. longitude.EQ.rvind) THEN+
                longitude = value                longitude = value
             END IF             END IF
-         ELSE IF (desc.EQ.7001) THEN ! Height of station +         ELSE IF (desc.EQ.7001.OR.  ! Height of station 
-            IF (value.NE.rvind .AND. height.EQ.rvind) THEN+               desc.EQ.7030) THEN ! Height of station ground above mean sea level 
 +            IF (height.EQ.rvind) THEN
                height = value                height = value
             END IF             END IF
-         ELSE IF (desc.EQ.7030) THEN ! Height of station ground above mean sea level +         ELSE IF (desc.EQ.7031) THEN ! Hp 
-            IF (value.NE.rvind .AND. height.EQ.rvind) THEN +            IF (hp.EQ.rvind) THEN 
-               height = value+               hp = value
             END IF             END IF
          ELSE IF (desc.EQ.10004) THEN ! Pressure          ELSE IF (desc.EQ.10004) THEN ! Pressure
-            IF (value.NE.rvind .AND. PO.EQ.rvind) THEN+            IF (PO.EQ.rvind) THEN
                PO = value                PO = value
             END IF             END IF
          ELSE IF (desc.EQ.10051) THEN ! Pressure reduced to mean sea level          ELSE IF (desc.EQ.10051) THEN ! Pressure reduced to mean sea level
-            IF (value.NE.rvind .AND. PR.EQ.rvind) THEN+            IF (PR.EQ.rvind) THEN
                PR = value                PR = value
             END IF             END IF
          ELSE IF (desc.EQ.10061) THEN ! 3-hour pressure change          ELSE IF (desc.EQ.10061) THEN ! 3-hour pressure change
-            IF (value.NE.rvind .AND. PP.EQ.rvind) THEN+            IF (PP.EQ.rvind) THEN
                PP = value                PP = value
             END IF             END IF
          ELSE IF (desc.EQ.10063) THEN ! Characteristic of pressure tendency          ELSE IF (desc.EQ.10063) THEN ! Characteristic of pressure tendency
-            IF (value.NE.rvind .AND. AA.EQ.rvind) THEN+            IF (AA.EQ.rvind) THEN
                AA = value                AA = value
             END IF             END IF
-         ELSE IF (desc.EQ.11011) THEN ! Wind direction at 10 m +         ELSE IF (desc.EQ.11011.OR.  ! Wind direction at 10 m 
-            IF (value.NE.rvind .AND. DD.EQ.rvind) THEN+               desc.EQ.11001) THEN ! Wind direction 
 +            IF (DD.EQ.rvind) THEN
                DD = value                DD = value
             END IF             END IF
-         ELSE IF (desc.EQ.11001) THEN ! Wind direction +         ELSE IF (desc.EQ.11012.OR ! Wind speed at 10 m 
-            IF (value.NE.rvind .AND. DD.EQ.rvind) THEN +     +           desc.EQ.11002) THEN ! Wind speed 
-               DD = value +            IF (FF.EQ.rvind) THEN
-            END IF +
-         ELSE IF (desc.EQ.11012) THEN ! Wind speed at 10 m +
-            IF (value.NE.rvind .AND. FF.EQ.rvind) THEN +
-               FF = value +
-            END IF +
-         ELSE IF (desc.EQ.11002) THEN ! Wind speed +
-            IF (value.NE.rvind .AND. FF.EQ.rvind) THEN+
                FF = value                FF = value
             END IF             END IF
          ELSE IF (desc.EQ.11043) THEN ! Maximum wind gust direction          ELSE IF (desc.EQ.11043) THEN ! Maximum wind gust direction
-            IF (value.NE.rvind .AND. minute_p.NE.rvind) THEN+C     DG is treated same way as FG 
 +            IF (minute_p.NE.rvind .AND. hour.NE.rvind) THEN
                mm = NINT(minute_p)                mm = NINT(minute_p)
-               IF ((NINT(hour).EQ.0 .OR. NINT(hour).EQ.6 +               hh = NINT(hour) 
-     +              .ORNINT(hour).EQ.12 .ORNINT(hour).EQ.18+               IF (mm.EQ.-10THEN 
-     +              .AND. mm.EQ.-360) +                  IF (DG_010.EQ.rvind) DG_010 = value 
-                  THEN +               ELSE IF (mm.GE.-70 .ANDmm.LE.-50THEN 
-                  DG = value +                  IF (DG_1.EQ.rvindDG_1 = value 
-               ELSE IF (mm.EQ.-10) THEN +               ELSE IF (mm.EQ.-360 .AND. MOD(hh,6).EQ.0) THEN 
-                  DG_010 = value +                  IF (DG.EQ.rvind) DG = value 
-               ELSE IF (mm.EQ.-60THEN +               ELSE IF (mm.EQ.-180 .AND. MOD(hh,3).EQ.0 
-                  DG_1 = value+                     .AND. MOD(hh,6).NE.0) THEN 
 +                  IF (DG.EQ.rvind) DG = value 
 +               ELSE 
 +C     Actually DG_X is not defined in Kvalobs (but FG_X is!) 
 +                  IF (DG_X.EQ.rvindDG_X = value
                END IF                END IF
             END IF             END IF
          ELSE IF (desc.EQ.11041) THEN ! Maximum wind gust speed          ELSE IF (desc.EQ.11041) THEN ! Maximum wind gust speed
-            IF (value.NE.rvind .AND. minute_p.NE.rvind) THEN+            IF (minute_p.NE.rvind .AND. hour.NE.rvind) THEN
                mm = NINT(minute_p)                mm = NINT(minute_p)
-               IF ((NINT(hour).EQ.0 .OR. NINT(hour).EQ.6 +               hh = NINT(hour) 
-     +              .ORNINT(hour).EQ.12 .ORNINT(hour).EQ.18) +               IF (mm.EQ.-10THEN 
-     +              .AND. mm.EQ.-360) +                  IF (FG_010.EQ.rvind) FG_010 = value 
-                  THEN +               ELSE IF (mm.GE.-70 .ANDmm.LE.-50THEN 
-                  FG = value +                  IF (FG_1.EQ.rvind) FG_1 = value 
-               ELSE IF (mm.EQ.-10) THEN +C     For time periods > 1 hour, we choose to decode this as FG for 
-                  FG_010 = value +C     termins 0,6,12,18 if time period is 6 hours, and for termins 
-               ELSE IF (mm.EQ.-60THEN +C     3,9,15,21 if time period is 3 hours. FG is defined as max wind 
-                  FG_1 = value+C     gust since last synoptic termin (0,6,12,18) and it is unlikely to 
 +    be reported for other termins than 0,3,6,9..
 +               ELSE IF (mm.EQ.-360 .AND. MOD(hh,6).EQ.0) THEN 
 +                  IF (FG.EQ.rvind) FG = value 
 +               ELSE IF (mm.EQ.-180 .AND. MOD(hh,3).EQ.0 
 +                     .AND. MOD(hh,6).NE.0) THEN 
 +                  IF (FG.EQ.rvind) FG = value 
 +               ELSE 
 +C     All other periods are put in FG_X (arbitrary period) 
 +                  IF (FG_X.EQ.rvindFG_X = value
                END IF                END IF
             END IF             END IF
          ELSE IF (desc.EQ.11042) THEN ! Maximum wind speed (10-min mean wind)          ELSE IF (desc.EQ.11042) THEN ! Maximum wind speed (10-min mean wind)
-            IF (value.NE.rvind .AND. FX.EQ.rvind +            IF (minute_p.NE.rvind .AND. hour.NE.rvind) THEN 
-     +           .AND. (NINT(hour).EQ..ORNINT(hour).EQ.6 +    FX is "Vindhastighet, maks10 minutt glidende middel siden 
-               .OR. NINT(hour).EQ.12 .ORNINT(hour).EQ.18) +C     forrige hovedobservasjon, m/s"Assume this is reported for 
-               .AND. NINT(minute_p).EQ.-360+C     termins 0,3,6,9... only 
-     +           FX = value +               mm = NINT(minute_p) 
-         ELSE IF (desc.EQ.12104) THEN ! Dry bulb temperature at 2m (data width 16 bits) +               hh = NINT(hour) 
-            IF (value.NE.rvind .AND. TA.EQ.rvind) THEN +               IF ((mm.EQ.-360 .ANDMOD(hh,6).EQ.0) 
-               TA = value+                  .OR. (mm.EQ.-180 .ANDMOD(hh,3).EQ.0 
 +                  .AND. MOD(hh,6).NE.0) .AND. FX.EQ.rvindTHEN 
 +                  IF (FX.EQ.rvind) FX = value 
 +               ELSE IF (mm.GE.-70 .AND. mm.LE.-50) THEN 
 +                  IF (FX_1.EQ.rvind) FX_1 = value 
 +               ELSE 
 +C     All other periods are put in FX_X (arbitrary period) 
 +                  IF (FX_X.EQ.rvind) FX_X = value 
 +               END IF
             END IF             END IF
-         ELSE IF (desc.EQ.12004THEN ! Dry bulb temperature at 2m (12 bits) +         ELSE IF (desc.EQ.12104.OR. ! Dry bulb temperature at 2m (data width 16 bits) 
-            IF (value.NE.rvind .AND. TA.EQ.rvind) THEN+              desc.EQ.12004.OR.   ! Dry bulb temperature at 2m (12 bits) 
 +     +          desc.EQ.12101.OR  ! Temperature/dry bulb temperature (16 bits) 
 +              desc.EQ.12001) THEN ! Temperature/dry bulb temperature (12 bits) 
 +            IF (TA.EQ.rvind) THEN
                TA = value                TA = value
             END IF             END IF
-         ELSE IF (desc.EQ.12101) THEN ! Temperature/dry bulb temperature (16 bits) +         ELSE IF (desc.EQ.12106.OR ! Dew-point temperature at 2m (16 bits) 
-            IF (value.NE.rvind .AND. TA.EQ.rvind) THEN +     +           desc.EQ.12006.OR  ! Dew-point temperature at 2m (12 bits) 
-               TA = value +     +           desc.EQ.12103.OR  ! Dew-point temperature (16 bits) 
-            END IF +     +           desc.EQ.12003) THEN ! Dew-point temperature (12 bits) 
-         ELSE IF (desc.EQ.12001) THEN ! Temperature/dry bulb temperature (12 bits) +            IF (TD.EQ.rvind) THEN
-            IF (value.NE.rvind .AND. TA.EQ.rvind) THEN +
-               TA = value +
-            END IF +
-         ELSE IF (desc.EQ.12106) THEN ! Dew-point temperature at 2m (16 bits) +
-            IF (value.NE.rvind .AND. TD.EQ.rvind) THEN +
-               TD = value +
-            END IF +
-         ELSE IF (desc.EQ.12006) THEN ! Dew-point temperature at 2m (12 bits) +
-            IF (value.NE.rvind .AND. TD.EQ.rvind) THEN +
-               TD = value +
-            END IF +
-         ELSE IF (desc.EQ.12103) THEN ! Dew-point temperature (16 bits) +
-            IF (value.NE.rvind .AND. TD.EQ.rvind) THEN +
-               TD = value +
-            END IF +
-         ELSE IF (desc.EQ.12003) THEN ! Dew-point temperature (12 bits) +
-            IF (value.NE.rvind .AND. TD.EQ.rvind) THEN+
                TD = value                TD = value
             END IF             END IF
-         ELSE IF (desc.EQ.12113) THEN ! Ground minimum temperature at 2m (data width 16 bits) +         ELSE IF (desc.EQ.12113.OR.  ! Ground minimum temperature at 2m (data width 16 bits) 
-            IF (value.NE.rvind .AND. TGN_12.EQ.rvind) THEN+               desc.EQ.12013) THEN ! Ground minimum temperature at 2m (12 bits) 
 +            IF (TGN_12.EQ.rvind) THEN
                TGN_12 = value                TGN_12 = value
             END IF             END IF
-         ELSE IF (desc.EQ.12013) THEN ! Ground minimum temperature at 2m (12 bits) +         ELSE IF (desc.EQ.12114.OR ! Maximum temperature at 2m, past 12 hours (16 bits) 
-            IF (value.NE.rvind .AND. TGN_12.EQ.rvind) THEN +     +           desc.EQ.12014) THEN ! Maximum temperature at 2m, past 12 hours (12 bits) 
-               TGN_12 = value +            IF (TAX_12.EQ.rvind) THEN
-            END IF +
-         ELSE IF (desc.EQ.12114) THEN ! Maximum temperature at 2m, past 12 hours (16 bits) +
-            IF (value.NE.rvind .AND. TAX_12.EQ.rvind) THEN +
-               TAX_12 = value +
-            END IF +
-         ELSE IF (desc.EQ.12014) THEN ! Maximum temperature at 2m, past 12 hours (12 bits) +
-            IF (value.NE.rvind .AND. TAX_12.EQ.rvind) THEN+
                TAX_12 = value                TAX_12 = value
             END IF             END IF
          ELSE IF (desc.EQ.12111) THEN ! Maximum temperature at height and over period specified          ELSE IF (desc.EQ.12111) THEN ! Maximum temperature at height and over period specified
-            IF (value.NE.rvind .AND. TAX_12.EQ.rvind .AND. idx.GT.2+            IF (TAX_12.EQ.rvind .AND. idx.GT.2
                .AND. ktdexp(idx-1).EQ.4024                .AND. ktdexp(idx-1).EQ.4024
                .AND. NINT(values(idx-1 + (ksub-1)*kxelem)).EQ.0                .AND. NINT(values(idx-1 + (ksub-1)*kxelem)).EQ.0
-               .AND. ktdexp(idx-2).EQ.4024 +               .AND. ktdexp(idx-2).EQ.4024) THEN 
-               .AND. NINT(values(idx-2 + (ksub-1)*kxelem)).EQ.-12)THEN +               IF (NINT(values(idx-2 (ksub-1)*kxelem)).EQ.-12) THEN 
-               TAX_12 = value+                  IF (TAX_12.EQ.rvind) TAX_12 = value 
 +               ELSE IF (NINT(values(idx-2 + (ksub-1)*kxelem)).EQ.-1)THEN 
 +                  IF (TAX.EQ.rvind) TAX = value 
 +               END IF
             END IF             END IF
-C     For TAX_12: do we also need to consider 12021 'Maximum temperature at 2m'? +C     Do we also need to consider 12021 'Maximum temperature at 2m'? 
-         ELSE IF (desc.EQ.12115) THEN ! Minimum temperature at 2m, past 12 hours (16 bits) +         ELSE IF (desc.EQ.12115.OR.  ! Minimum temperature at 2m, past 12 hours (16 bits) 
-            IF (value.NE.rvind .AND. TAN_12.EQ.rvind) THEN +     +           desc.EQ.12015) THEN ! Minimum temperature at 2m, past 12 hours (12 bits) 
-               TAN_12 = value +            IF (TAN_12.EQ.rvind) THEN
-            END IF +
-         ELSE IF (desc.EQ.12015) THEN ! Minimum temperature at 2m, past 12 hours (12 bits) +
-            IF (value.NE.rvind .AND. TAN_12.EQ.rvind) THEN+
                TAN_12 = value                TAN_12 = value
             END IF             END IF
          ELSE IF (desc.EQ.12112) THEN ! Minimum temperature at height and over period specified          ELSE IF (desc.EQ.12112) THEN ! Minimum temperature at height and over period specified
-            IF (value.NE.rvind .AND. TAN_12.EQ.rvind .AND. idx.GT.2+            IF (TAN_12.EQ.rvind .AND. idx.GT.2
                .AND. ktdexp(idx-1).EQ.4024                .AND. ktdexp(idx-1).EQ.4024
                .AND. values(idx-1 + (ksub-1)*kxelem).EQ.0                .AND. values(idx-1 + (ksub-1)*kxelem).EQ.0
-               .AND. ktdexp(idx-2).EQ.4024 +               .AND. ktdexp(idx-2).EQ.4024) THEN 
-               .AND. values(idx-2 + (ksub-1)*kxelem).EQ.-12) THEN +               IF (NINT(values(idx-2 (ksub-1)*kxelem)).EQ.-12) THEN 
-               TAN_12 = value+                  IF (TAN_12.EQ.rvind) TAN_12 = value 
 +               ELSE IF (NINT(values(idx-2 + (ksub-1)*kxelem)).EQ.-1)THEN 
 +                  IF (TAN.EQ.rvind) TAN = value 
 +               END IF
             END IF             END IF
-C     For TAN_12: do we also need to consider 12022 'Minimum temperature at 2m'?+C     Do we also need to consider 12022 'Minimum temperature at 2m'?
          ELSE IF (desc.EQ.13003) THEN ! Relative humidity          ELSE IF (desc.EQ.13003) THEN ! Relative humidity
-            IF (value.NE.rvind .AND. UU.EQ.rvind) THEN+            IF (UU.EQ.rvind) THEN
                UU = value                UU = value
             END IF             END IF
          ELSE IF (desc.EQ.20001) THEN ! Horizontal visibility          ELSE IF (desc.EQ.20001) THEN ! Horizontal visibility
-            IF (value.NE.rvind .AND. VV.EQ.rvind) THEN+            IF (VV.EQ.rvind) THEN
                VV = value                VV = value
             END IF             END IF
          ELSE IF (desc.EQ.20003) THEN ! Present weather          ELSE IF (desc.EQ.20003) THEN ! Present weather
-            IF (value.NE.rvind .AND. WW.EQ.rvind) THEN+            IF (WW.EQ.rvind) THEN
                WW = value                WW = value
             END IF             END IF
          ELSE IF (desc.EQ.20004) THEN ! Past weather (1)          ELSE IF (desc.EQ.20004) THEN ! Past weather (1)
-            IF (value.NE.rvind .AND. W1.EQ.rvind) THEN+            IF (W1.EQ.rvind) THEN
                W1 = value                W1 = value
             END IF             END IF
          ELSE IF (desc.EQ.20005) THEN ! Past weather (2)          ELSE IF (desc.EQ.20005) THEN ! Past weather (2)
-            IF (value.NE.rvind .AND. W2.EQ.rvind) THEN+            IF (W2.EQ.rvind) THEN
                W2 = value                W2 = value
             END IF             END IF
          ELSE IF (desc.EQ.20010) THEN ! Cloud cover (total)          ELSE IF (desc.EQ.20010) THEN ! Cloud cover (total)
-            IF (value.NE.rvind .AND. NN.EQ.rvind) THEN+            IF (NN.EQ.rvind) THEN
                NN = value                NN = value
             END IF             END IF
Line 1353: Line 1853:
 C     number of cloud layers if previous descriptor is cloud C     number of cloud layers if previous descriptor is cloud
 C     type, according to all WMO recommended templates C     type, according to all WMO recommended templates
 +C     (but DNMI metar is an exception!)
             IF (ktdexp(idx - 1).EQ.20012) THEN             IF (ktdexp(idx - 1).EQ.20012) THEN
-               IF (value.EQ.rvind) THEN +               IF (NINT(value).LE.4) THEN 
-                  WRITE(*,*'WARNING: delayed descriptor replication' +                  num_cloud_layers = NINT(value
-     +                 // ' factor after 020012 undefined   !!!'+               ELSE
                   bad_cloud_data = .TRUE.                   bad_cloud_data = .TRUE.
-               ELSE 
-                  num_cloud_layers = NINT(value) 
                END IF                END IF
             END IF             END IF
          ELSE IF (desc.EQ.8002 .AND. .NOT.bad_cloud_data) THEN ! Vertical significance (surface observations)          ELSE IF (desc.EQ.8002 .AND. .NOT.bad_cloud_data) THEN ! Vertical significance (surface observations)
             IF (cloud_type_count.EQ.0) THEN ! First occurrence             IF (cloud_type_count.EQ.0) THEN ! First occurrence
-               IF (value.NE.rvind .AND. vert_sign_first.EQ.rvind) THEN+               IF (vert_sign_first.EQ.rvind) THEN
                   vert_sign_first = value                   vert_sign_first = value
                END IF                END IF
Line 1373: Line 1872:
                cloud_layer = cloud_type_count - 2                cloud_layer = cloud_type_count - 2
                IF (cloud_layer.LE.num_cloud_layers) THEN                IF (cloud_layer.LE.num_cloud_layers) THEN
-                  IF (value.NE.rvind) THEN +                  vert_sign(cloud_layer) = value
-                     vert_sign(cloud_layer) = value +
-                  END IF+
                END IF                END IF
             ELSE                ! rdb-files always have 0 or 4 cloud layers             ELSE                ! rdb-files always have 0 or 4 cloud layers
                cloud_layer = cloud_type_count - 2                cloud_layer = cloud_type_count - 2
                IF (cloud_layer.LT.5) THEN                IF (cloud_layer.LT.5) THEN
-                  IF (value.NE.rvind) THEN +                  vert_sign(cloud_layer) = value
-                     vert_sign(cloud_layer) = value +
-                  END IF+
                END IF                END IF
             END IF             END IF
          ELSE IF (desc.EQ.20011 .AND. .NOT.bad_cloud_data) THEN ! Cloud amount          ELSE IF (desc.EQ.20011 .AND. .NOT.bad_cloud_data) THEN ! Cloud amount
-            IF (cloud_type_count.EQ.0) THEN ! First occurrence +            IF (metar) THEN 
-               IF (value.NE.rvind .AND. NH.EQ.rvind) THEN+               IF (num_cloud_layers.GT.-1) THEN 
 +                  num_cloud_layers = num_cloud_layers + 1 
 +               ELSE 
 +                  num_cloud_layers = 1 
 +               END IF 
 +               NS(num_cloud_layers) = value 
 +            ELSE IF (cloud_type_count.EQ.0) THEN ! First occurrence 
 +               IF (NH.EQ.rvind) THEN
                   NH = value                   NH = value
                END IF                END IF
Line 1396: Line 1898:
                cloud_layer = cloud_type_count - 2                cloud_layer = cloud_type_count - 2
                IF (cloud_layer.LE.num_cloud_layers) THEN                IF (cloud_layer.LE.num_cloud_layers) THEN
-                  IF (value.NE.rvind) THEN +                  NS(cloud_layer) = value
-                     NS(cloud_layer) = value +
-                  END IF+
                END IF                END IF
             ELSE                ! rdb-files always have 0 or 4 cloud layers             ELSE                ! rdb-files always have 0 or 4 cloud layers
                cloud_layer = cloud_type_count - 2                cloud_layer = cloud_type_count - 2
                IF (cloud_layer.LT.5) THEN                IF (cloud_layer.LT.5) THEN
-                  IF (value.NE.rvind) THEN +                  NS(cloud_layer) = value
-                     NS(cloud_layer) = value +
-                  END IF+
                END IF                END IF
             END IF             END IF
          ELSE IF (desc.EQ.20012 .AND. .NOT.bad_cloud_data) THEN ! Cloud type          ELSE IF (desc.EQ.20012 .AND. .NOT.bad_cloud_data) THEN ! Cloud type
-            cloud_type_count = cloud_type_count + 1 +            IF (metar) THEN 
-            IF (cloud_type_count.GT.3) THEN +               CC(num_cloud_layers) = value 
-               cloud_layer = cloud_type_count - 3 +            ELSE    
-               IF (num_cloud_layers .GT.-1) THEN +               cloud_type_count = cloud_type_count + 1 
-                  IF (cloud_layer.LE.num_cloud_layers) THEN +               IF (cloud_type_count.GT.3) THEN 
-                     IF (value.NE.rvind) THEN+                  cloud_layer = cloud_type_count - 3 
 +                  IF (num_cloud_layers .GT.-1) THEN 
 +                     IF (value < 10.0 ! Accept one digit values only 
 +                        .AND. cloud_layer.LE.num_cloud_layers) THEN
                         CC(cloud_layer) = value                         CC(cloud_layer) = value
                      END IF                      END IF
-                  END IF +                  ELSE IF (cloud_layer.LT.5) THEN ! rdb-files always have 0 or 4 cloud layers
-               ELSE IF (cloud_layer.LT.5) THEN ! rdb-files always have 0 or 4 cloud layers +
-                  IF (value.NE.rvind) THEN+
                      CC(cloud_layer) = value                      CC(cloud_layer) = value
                   END IF                   END IF
-               END IF +               ELSE 
-            ELSE +                  IF (cloud_type_count.EQ.1) THEN 
-               IF (cloud_type_count.EQ.1) THEN +                     IF (CL.EQ.rvind) THEN 
-                  IF (value.NE.rvind .AND. CL.EQ.rvind) THEN +                        CL = value 
-                     CL = value +                     END IF 
-                  END IF +                  ELSE IF (cloud_type_count.EQ.2) THEN 
-               ELSE IF (cloud_type_count.EQ.2) THEN +                     IF (CM.EQ.rvind) THEN 
-                  IF (value.NE.rvind .AND. CM.EQ.rvind) THEN +                        CM = value 
-                     CM = value +                     END IF 
-                  END IF +                  ELSE IF (cloud_type_count.EQ.3) THEN 
-               ELSE IF (cloud_type_count.EQ.3) THEN +                     IF (CH.EQ.rvind) THEN 
-                  IF (value.NE.rvind .AND. CH.EQ.rvind) THEN +                        CH = value 
-                     CH = value+                     END IF
                   END IF                   END IF
                END IF                END IF
             END IF             END IF
          ELSE IF (desc.EQ.20013 .AND. .NOT.bad_cloud_data) THEN ! Height of base of cloud          ELSE IF (desc.EQ.20013 .AND. .NOT.bad_cloud_data) THEN ! Height of base of cloud
-            IF (cloud_type_count.EQ.0) THEN ! First occurrence +            IF (metar) THEN 
-               IF (value.NE.rvind .AND. HL.EQ.rvind) THEN+               HS(num_cloud_layers) = value 
 +            ELSE IF (cloud_type_count.EQ.0) THEN ! First occurrence 
 +               IF (HL.EQ.rvind) THEN
                   HL = value                   HL = value
                END IF                END IF
Line 1452: Line 1953:
                cloud_layer = cloud_type_count - 3                cloud_layer = cloud_type_count - 3
                IF (cloud_layer.LE.num_cloud_layers) THEN                IF (cloud_layer.LE.num_cloud_layers) THEN
-                  IF (value.NE.rvind) THEN +                  HS(cloud_layer) = value
-                     HS(cloud_layer) = value +
-                  END IF+
                END IF                END IF
             ELSE ! rdb-files always have 0 or 4 cloud layers             ELSE ! rdb-files always have 0 or 4 cloud layers
-               IF (value.NE.rvind) THEN +               cloud_layer = cloud_type_count - 3 
-                  cloud_layer = cloud_type_count - 3 +               IF (cloud_layer.LT.5) THEN 
-                  IF (cloud_layer.LT.5) THEN +                  HS(cloud_layer) = value
-                     IF (value.NE.rvind) THEN +
-                        HS(cloud_layer) = value +
-                     END IF +
-                  END IF+
                END IF                END IF
             END IF             END IF
          ELSE IF (desc.EQ.13023) THEN ! Total precipitation past 24 hours          ELSE IF (desc.EQ.13023) THEN ! Total precipitation past 24 hours
-            IF (value.NE.rvind .AND. RR_24.EQ.rvind) THEN+            IF (RR_24.EQ.rvind) THEN
                RR_24 = value                RR_24 = value
             END IF             END IF
          ELSE IF (desc.EQ.13022) THEN ! Total precipitation past 12 hours          ELSE IF (desc.EQ.13022) THEN ! Total precipitation past 12 hours
-            IF (value.NE.rvind .AND. RR_12.EQ.rvind) THEN+            IF (RR_12.EQ.rvind) THEN
                RR_12 = value                RR_12 = value
             END IF             END IF
          ELSE IF (desc.EQ.13021) THEN ! Total precipitation past 6 hours          ELSE IF (desc.EQ.13021) THEN ! Total precipitation past 6 hours
-            IF (value.NE.rvind .AND. RR_6.EQ.rvind) THEN+            IF (RR_6.EQ.rvind) THEN
                RR_6 = value                RR_6 = value
             END IF             END IF
          ELSE IF (desc.EQ.13020) THEN ! Total precipitation past 3 hours          ELSE IF (desc.EQ.13020) THEN ! Total precipitation past 3 hours
-            IF (value.NE.rvind .AND. RR_3.EQ.rvind) THEN+            IF (RR_3.EQ.rvind) THEN
                RR_3 = value                RR_3 = value
             END IF             END IF
          ELSE IF (desc.EQ.13019) THEN ! Total precipitation past 1 hour          ELSE IF (desc.EQ.13019) THEN ! Total precipitation past 1 hour
-            IF (value.NE.rvind .AND. RR_1.EQ.rvind) THEN+            IF (RR_1.EQ.rvind) THEN
                RR_1 = value                RR_1 = value
             END IF             END IF
          ELSE IF (desc.EQ.13011) THEN ! Total precipitation/total water equivalent          ELSE IF (desc.EQ.13011) THEN ! Total precipitation/total water equivalent
-            IF (value.NE.rvind .AND. hour_p.NE.rvind) THEN+            IF (hour_p.NE.rvind) THEN
                hh = NINT(hour_p)                hh = NINT(hour_p)
                IF (hh.EQ.-24) THEN                IF (hh.EQ.-24) THEN
Line 1502: Line 1997:
             END IF             END IF
          ELSE IF (desc.EQ.13013) THEN ! Total snow depth          ELSE IF (desc.EQ.13013) THEN ! Total snow depth
-            IF (value.NE.rvind .ANDSA.EQ.rvind) THEN +C     Don't check for SA.EQ.rvind, because SA might earlier have been set to 0 if 
-               SA = value+C     EE < 10, which probably means that 20062 has been wrongly encoded, not 13013 
 +            SA = value 
 +         ELSE IF (desc.EQ.20062) THEN ! State of the ground (with or without snow) 
 +            IF (EE.EQ.rvind) THEN 
 +               EE = value
             END IF             END IF
-         ELSE IF (desc.EQ.20062) THEN ! State of the ground (with or without snow) +            IF (NINT(value).LE.10 .AND. SA.EQ.rvind) THEN 
-            IF (value.NE.rvind) THEN +               SA = 0 
-               IF (NINT(value).LE.10) THEN ! E in TAC (3Ejjj) +            END IF 
-                  E = value +C     Equating 013012 with SS_24 is dubious generally, but this is how 
-                  IF (SA.EQ.rvind) THEN +C     SS_24 is encoded in kvalobs for Norwegian avalanche stations (and 
-                     SA = 0 +C     we have no better kvalobs parameter for depth of fresh snow anyway) 
-                  END IF +         ELSE IF (desc.EQ.13012) THEN ! Depth of fresh snow 
-               ELSE IF (NINT(value).LE.20) THEN ! E' in TAC (4Esss+            IF (SS_24.EQ.rvindTHEN 
-                  EM = value +               SS_24 = value
-               END IF+
             END IF             END IF
          ELSE IF (desc.EQ.14031) THEN ! Total sunshine          ELSE IF (desc.EQ.14031) THEN ! Total sunshine
-            IF (value.NE.rvind .AND. hour_p.NE.rvind) THEN+            IF (hour_p.NE.rvind) THEN
                hh = NINT(hour_p)                hh = NINT(hour_p)
                IF (hh.EQ.-1) THEN                IF (hh.EQ.-1) THEN
Line 1526: Line 2024:
             END IF             END IF
          ELSE IF (desc.EQ.13033) THEN ! Evaporation/evapotranspiration          ELSE IF (desc.EQ.13033) THEN ! Evaporation/evapotranspiration
-            IF (value.NE.rvind .AND. hour_p.NE.rvind) THEN+            IF (hour_p.NE.rvind) THEN
                hh = NINT(hour_p)                hh = NINT(hour_p)
                IF (hh.EQ.-1) THEN                IF (hh.EQ.-1) THEN
Line 1532: Line 2030:
                ELSE IF (hh.EQ.-24) THEN                ELSE IF (hh.EQ.-24) THEN
                   EV_24 = value                   EV_24 = value
 +               END IF
 +            END IF
 +         ELSE IF (desc.EQ.14002) THEN ! Long-wave radiation
 +            IF (hour_p.NE.rvind) THEN
 +               hh = NINT(hour_p)
 +               IF (hh.EQ.-1) THEN
 +                  QL = value
 +               ELSE IF (hh.EQ.-24) THEN
 +                  QL_24 = value
 +               END IF
 +            END IF
 +         ELSE IF (desc.EQ.14004) THEN ! Short-wave radiation
 +            IF (hour_p.NE.rvind) THEN
 +               hh = NINT(hour_p)
 +               IF (hh.EQ.-1) THEN
 +                  QK = value
 +               ELSE IF (hh.EQ.-24) THEN
 +                  QK_24 = value
 +               END IF
 +            END IF
 +         ELSE IF (desc.EQ.14016) THEN ! Net radiation
 +            IF (hour_p.NE.rvind) THEN
 +               hh = NINT(hour_p)
 +               IF (hh.EQ.-1) THEN
 +                  QE = value
 +               ELSE IF (hh.EQ.-24) THEN
 +                  QE_24 = value
 +               END IF
 +            END IF
 +         ELSE IF (desc.EQ.14028) THEN ! Global solar radiation
 +            IF (hour_p.NE.rvind) THEN
 +               hh = NINT(hour_p)
 +               IF (hh.EQ.-1) THEN
 +                  QO = value
 +               ELSE IF (hh.EQ.-24) THEN
 +                  QO_24 = value
 +               END IF
 +            END IF
 +         ELSE IF (desc.EQ.14029) THEN ! Diffuse solar radiation
 +            IF (hour_p.NE.rvind) THEN
 +               hh = NINT(hour_p)
 +               IF (hh.EQ.-1) THEN
 +                  QD = value
 +               ELSE IF (hh.EQ.-24) THEN
 +                  QD_24 = value
 +               END IF
 +            END IF
 +         ELSE IF (desc.EQ.14030) THEN ! Direct solar radiation
 +            IF (hour_p.NE.rvind) THEN
 +               hh = NINT(hour_p)
 +               IF (hh.EQ.-1) THEN
 +                  QS = value
 +               ELSE IF (hh.EQ.-24) THEN
 +                  QS_24 = value
                END IF                END IF
             END IF             END IF
 C     Special for high altitude stations C     Special for high altitude stations
          ELSE IF (desc.EQ.7004) THEN ! Pressure (location class)          ELSE IF (desc.EQ.7004) THEN ! Pressure (location class)
-            IF (value.NE.rvind .AND. a3.EQ.rvind) THEN+            IF (a3.EQ.rvind) THEN
                a3 = value                a3 = value
             END IF             END IF
          ELSE IF (desc.EQ.10009) THEN ! Geopotential height          ELSE IF (desc.EQ.10009) THEN ! Geopotential height
-            IF (value.NE.rvind .AND. hhh.EQ.rvind) THEN+            IF (hhh.EQ.rvind) THEN
                hhh = value                hhh = value
-            END IF 
-         ELSE IF (desc.EQ.10008) THEN ! Geopotential (20 bits) 
-            IF (value.NE.rvind .AND. hhh.EQ.rvind) THEN 
-               hhh = value * 9.8 
-            END IF 
-         ELSE IF (desc.EQ.10003) THEN ! Geopotential (17 bits) 
-            IF (value.NE.rvind .AND. hhh.EQ.rvind) THEN 
-               hhh = value * 9.8 
             END IF             END IF
 C     Special for ship or marine stations C     Special for ship or marine stations
          ELSE IF (desc.EQ.1011) THEN  ! Ship or mobile land station identifier          ELSE IF (desc.EQ.1011) THEN  ! Ship or mobile land station identifier
-            IF (value.NE.rvind) THEN +            cidx = int(value/1000) 
-               cidx = int(value/1000) +            IF (cidx.GT.0) THEN 
-               IF (cvals(cidx).NE.spc9) THEN +               call_sign = cvals(cidx) ! CCITTIA5 data 
-                  DDDD = cvals(cidx) ! CCITTIA5 data +               call_sign = ctrim(call_sign,9,missing9)
-               END IF+
             END IF             END IF
          ELSE IF (desc.EQ.1012) THEN ! Direction of motion of moving observing platform          ELSE IF (desc.EQ.1012) THEN ! Direction of motion of moving observing platform
-            IF (value.NE.rvind .AND. ds.EQ.rvind) THEN+            IF (ds.EQ.rvind) THEN
                ds = value                ds = value
             END IF             END IF
          ELSE IF (desc.EQ.1013) THEN ! Speed of motion of moving observing platform          ELSE IF (desc.EQ.1013) THEN ! Speed of motion of moving observing platform
-            IF (value.NE.rvind .AND. vs.EQ.rvind) THEN+            IF (vs.EQ.rvind) THEN
                vs = value                vs = value
             END IF             END IF
          ELSE IF (desc.EQ.7062) THEN ! Depth below sea/water surface          ELSE IF (desc.EQ.7062) THEN ! Depth below sea/water surface
-            IF (value.NE.rvind) THEN 
 C     Some buoy reports starts with depth 1.5 m, others starts with 0 m C     Some buoy reports starts with depth 1.5 m, others starts with 0 m
 C     then 1.5 m and always have same sea/water temperature for these 2 C     then 1.5 m and always have same sea/water temperature for these 2
 C     levels, so it seems like 0 m should be considered equivalent with 1.5 m C     levels, so it seems like 0 m should be considered equivalent with 1.5 m
-               IF (value.LT.1.6) THEN +            IF (value.LT.1.6) THEN 
-                  surface_data = .TRUE. +               surface_data = .TRUE. 
-               ELSE +            ELSE 
-                  surface_data = .FALSE. +               surface_data = .FALSE.
-               END IF+
             END IF             END IF
-         ELSE IF (desc.EQ.22043) THEN ! Sea/water temperature (15 bits) +         ELSE IF (desc.EQ.22043.OR.  ! Sea/water temperature (15 bits) 
-            IF (value.NE.rvind .AND. TW.EQ.rvind .AND. surface_data)THEN+     +           desc.EQ.22042.OR  ! Sea/water temperature (12 bits) 
 +               desc.EQ.22049) THEN ! Sea-surface temperature (15 bits) 
 +            IF (TW.EQ.rvind .AND. surface_data)THEN
                TW = value                TW = value
             END IF             END IF
-         ELSE IF (desc.EQ.22042) THEN Sea/water temperature (12 bits) +         ELSE IF (desc.EQ.12102.OR.  Wet-bulb temperature (16 bits) 
-            IF (value.NE.rvind .AND. TW.EQ.rvind +               desc.EQ.12005) THEN ! Wet-bulb temperature (12 bits) 
-               .AND. surface_data) THEN +            IF (TbTbTb.EQ.rvind) THEN
-               TW = value +
-            END IF +
-         ELSE IF (desc.EQ.12102) THEN ! Wet-bulb temperature (16 bits) +
-            IF (value.NE.rvind .AND. TbTbTb.EQ.rvind) THEN+
                TbTbTb = value                TbTbTb = value
             END IF             END IF
-         ELSE IF (desc.EQ.12005) THEN ! Wet-bulb temperature (12 bits+         ELSE IF (desc.EQ.22011) THEN !  Period of waves (instrumentally measured
-            IF (value.NE.rvind .AND. TbTbTb.EQ.rvind) THEN +            IF (PWA.EQ.rvind) THEN 
-               TbTbTb = value+               PWA = value
             END IF             END IF
-         ELSE IF (desc.EQ.22011) THEN !  Period of waves (BUFR doesn't distinguish between PW and PWA+         ELSE IF (desc.EQ.22012) THEN !  Period of wind waves (visually measured
-            IF (value.NE.rvind .AND. PW.EQ.rvind) THEN+            IF (PW.EQ.rvind) THEN
                PW = value                PW = value
             END IF             END IF
-         ELSE IF (desc.EQ.22021) THEN ! Heigth of waves (BUFR doesn't distinguish between HW and HWA) +         ELSE IF (desc.EQ.22021) THEN ! Heigth of waves 
-            IF (value.NE.rvind .AND. HW.EQ.rvind) THEN+            IF (HWA.EQ.rvindTHEN 
 +               HWA = value 
 +            END IF 
 +         ELSE IF (desc.EQ.22022) THEN ! Heigth of wind waves 
 +            IF (HW.EQ.rvind) THEN
                HW = value                HW = value
             END IF             END IF
          ELSE IF (desc.EQ.22003) THEN ! Direction of swell waves          ELSE IF (desc.EQ.22003) THEN ! Direction of swell waves
-            IF (value.NE.rvind) THEN +            IF (DW1.EQ.rvind) THEN 
-               IF (DW1.EQ.rvind) THEN +               DW1 = value 
-                  DW1 = value +            ELSE 
-               ELSE +               DW2 = value
-                  DW2 = value +
-               END IF+
             END IF             END IF
          ELSE IF (desc.EQ.22013) THEN ! Period of swell waves          ELSE IF (desc.EQ.22013) THEN ! Period of swell waves
-            IF (value.NE.rvind) THEN +            IF (PW1.EQ.rvind) THEN 
-               IF (PW1.EQ.rvind) THEN +               PW1 = value 
-                  PW1 = value +            ELSE 
-               ELSE +               PW2 = value
-                  PW2 = value +
-               END IF+
             END IF             END IF
          ELSE IF (desc.EQ.22023) THEN ! Height of swell waves          ELSE IF (desc.EQ.22023) THEN ! Height of swell waves
-            IF (value.NE.rvind) THEN +            IF (HW1.EQ.rvind) THEN 
-               IF (HW1.EQ.rvind) THEN +               HW1 = value 
-                  HW1 = value +            ELSE 
-               ELSE +               HW2 = value
-                  HW2 = value +
-               END IF+
             END IF             END IF
          ELSE IF (desc.EQ.22061) THEN ! State of the sea          ELSE IF (desc.EQ.22061) THEN ! State of the sea
-            IF (value.NE.rvind .AND. SG.EQ.rvind) THEN+            IF (SG.EQ.rvind) THEN
                SG = value                SG = value
             END IF             END IF
          ELSE IF (desc.EQ.20033) THEN ! Cause of ice accretion          ELSE IF (desc.EQ.20033) THEN ! Cause of ice accretion
-            IF (value.NE.rvind .AND. XIS.EQ.rvind) THEN+            IF (XIS.EQ.rvind) THEN
                XIS = value                XIS = value
             END IF             END IF
          ELSE IF (desc.EQ.20031) THEN ! Ice deposit (thickness)          ELSE IF (desc.EQ.20031) THEN ! Ice deposit (thickness)
-            IF (value.NE.rvind .AND. ES.EQ.rvind) THEN+            IF (ES.EQ.rvind) THEN
                ES = value                ES = value
             END IF             END IF
          ELSE IF (desc.EQ.20032) THEN ! Rate of ice accretion          ELSE IF (desc.EQ.20032) THEN ! Rate of ice accretion
-            IF (value.NE.rvind .AND. RS.EQ.rvind) THEN+            IF (RS.EQ.rvind) THEN
                RS = value                RS = value
             END IF             END IF
          ELSE IF (desc.EQ.20034) THEN ! Sea ice concentration          ELSE IF (desc.EQ.20034) THEN ! Sea ice concentration
-            IF (value.NE.rvind .AND. CI.EQ.rvind) THEN+            IF (CI.EQ.rvind) THEN
                CI = value                CI = value
             END IF             END IF
          ELSE IF (desc.EQ.20037) THEN ! Ice development          ELSE IF (desc.EQ.20037) THEN ! Ice development
-            IF (value.NE.rvind .AND. SI.EQ.rvind) THEN+            IF (SI.EQ.rvind) THEN
                SI = value                SI = value
             END IF             END IF
          ELSE IF (desc.EQ.20035) THEN ! Amount and type of ice          ELSE IF (desc.EQ.20035) THEN ! Amount and type of ice
-            IF (value.NE.rvind .AND. BI.EQ.rvind) THEN+            IF (BI.EQ.rvind) THEN
                BI = value                BI = value
             END IF             END IF
          ELSE IF (desc.EQ.20038) THEN ! Bearing of ice edge          ELSE IF (desc.EQ.20038) THEN ! Bearing of ice edge
-            IF (value.NE.rvind .AND. DI.EQ.rvind) THEN+            IF (DI.EQ.rvind) THEN
                DI = value                DI = value
             END IF             END IF
          ELSE IF (desc.EQ.20036) THEN ! Ice situation          ELSE IF (desc.EQ.20036) THEN ! Ice situation
-            IF (value.NE.rvind .AND. ZI.EQ.rvind) THEN+            IF (ZI.EQ.rvind) THEN
                ZI = value                ZI = value
             END IF             END IF
          ELSE IF (desc.EQ.1005) THEN ! Buoy/platform identifier          ELSE IF (desc.EQ.1005) THEN ! Buoy/platform identifier
-            IF (value.NE.rvind .AND. buoy_id.EQ.rvind) THEN +            IF (buoy_id5.EQ.rvind) THEN 
-               buoy_id = value+               buoy_id5 = value
             END IF             END IF
          ELSE IF (desc.EQ.1003) THEN ! WMO region number/geographical area          ELSE IF (desc.EQ.1003) THEN ! WMO region number/geographical area
-            IF (value.NE.rvind .AND. wmo_region_number.EQ.rvind) THEN+            IF (wmo_region_number.EQ.rvind) THEN
                wmo_region_number = value                wmo_region_number = value
             END IF             END IF
          ELSE IF (desc.EQ.1020) THEN ! WMO region sub-area          ELSE IF (desc.EQ.1020) THEN ! WMO region sub-area
-            IF (value.NE.rvind .AND. wmo_region_subarea.EQ.rvind) THEN+            IF (wmo_region_subarea.EQ.rvind) THEN
                wmo_region_subarea = value                wmo_region_subarea = value
 +            END IF
 +         ELSE IF (desc.EQ.1087) THEN ! WMO Marine observing platform extended identifier
 +            IF (buoy_id7.EQ.rvind) THEN
 +               buoy_id7 = value
             END IF             END IF
 C     Special for metar C     Special for metar
          ELSE IF (desc.EQ.1063) THEN  ! ICAO location indicator          ELSE IF (desc.EQ.1063) THEN  ! ICAO location indicator
-            IF (value.NE.rvind) THEN +            cidx = int(value/1000) 
-               cidx = int(value/1000) +            icao_id = cvals(cidx) ! CCITTIA5 data 
-               IF (cvals(cidx).NE.spc8) THEN +            icao_id = ctrim(icao_id,8,missing8)
-                  icao_id = cvals(cidx) ! CCITTIA5 data +
-               END IF +
-            END IF+
          ELSE IF (desc.EQ.10052) THEN ! Altimeter setting (QNH)          ELSE IF (desc.EQ.10052) THEN ! Altimeter setting (QNH)
-            IF (value.NE.rvind .AND. PH.EQ.rvind) THEN+            IF (PH.EQ.rvind) THEN
                PH = value                PH = value
             END IF             END IF
Line 1696: Line 2234:
       END IF       END IF
  
-      WRITE(*,*) 
       IF (II.NE.rvind .AND. iii.NE.rvind) THEN       IF (II.NE.rvind .AND. iii.NE.rvind) THEN
 +         WRITE(*,*)
          WRITE(*,'(A,I5.5)') 'wmonr=',NINT(II)*1000 + NINT(iii)          WRITE(*,'(A,I5.5)') 'wmonr=',NINT(II)*1000 + NINT(iii)
-      ELSE IF (DDDD.NE.missing9) THEN +      ELSE IF (wigos_series.NE.rvind .AND. wigos_issuer.NE.missing5 
-         WRITE(*,'(A,A)') 'DDDD=',DDDD +            .AND. wigos_issueno.NE.missing5 
-      ELSE IF (buoy_id.NE.rvind.AND.wmo_region_number.NE.rvind +            .AND. wigos_localid.NE.missing16) THEN 
-            .AND.wmo_region_subarea.NE.rvind) THEN +         ind = index(wigos_issuer,' ') - 1 
-         WRITE(*,'(A,I5)') 'buoy=',NINT(wmo_region_number)*10000 +         IF (ind.EQ.-1) ind = 5 
-            + NINT(wmo_region_subarea)*1000 + NINT(buoy_id) +         ind2 = index(wigos_issueno,' ') - 1 
-      ELSE IF (buoy_id.NE.rvind.AND.buoy_id.GT.1000) THEN+         IF (ind2.EQ.-1) ind2 = 5 
 +         ind3 = index(wigos_localid,' ') - 1 
 +         IF (ind3.EQ.-1) ind3 = 16 
 +         WRITE(*,*) 
 +         WRITE(*,'(A,I1.1,A1,A,A1,A,A1,A)') 
 +            'wigosid=',NINT(wigos_series), 
 +            '-',wigos_issuer(1:ind), 
 +            '-',wigos_issueno(1:ind2), 
 +            '-',wigos_localid(1:ind3) 
 +      ELSE IF (state_id.NE.rvind .AND. national_number.NE.rvind) THEN 
 +         WRITE(*,*) 
 +         WRITE(*,'(A,I3.3,A1,I10.10)') 'nationalnr=',NINT(state_id), 
 +            '_',NINT(national_number) 
 +      ELSE IF (call_sign.NE.missing9) THEN 
 +         ind = index(call_sign,' ') - 1 
 +         IF (ind.EQ.-1) ind = 9 
 +C     Remove trailing NULL characters, which some centres erronously 
 +C     insert 
 +         DO WHILE (IACHAR(call_sign(ind:ind)).EQ.0) 
 +            ind = ind - 1 
 +         END DO 
 +         WRITE(*,*) 
 +         WRITE(*,'(A,A)') 'call_sign=', 
 +            call_sign(1:ind) 
 +      ELSE IF (buoy_id7.NE.rvind) THEN 
 +C     New templates introduced in 2014 for data category 1 use 001087 
 +C     WMO Marine observing platform extended identifier, 7 digits 
 +         WRITE(*,*) 
 +         WRITE(*,'(A,I7)') 'buoy_id=',NINT(buoy_id7
 +      ELSE IF (buoy_id5.NE.rvind) THEN 
 +         WRITE(*,*) 
 +         IF (wmo_region_number.EQ.rvind 
 +            .AND.wmo_region_subarea.EQ.rvind) THEN
 C     Old drau files (wrongly) includes wmo_region_number and C     Old drau files (wrongly) includes wmo_region_number and
-C     wmo_region_subarea in buoy_id +C     wmo_region_subarea in 001005 Buoy/platform identifier. Should we 
-         WRITE(*,'(A,I5)') 'buoy=',NINT(buoy_id)+C     expand this to 7 digits by inserting '00'? 
 +            WRITE(*,'(A,I5)') 'buoy_id=',NINT(buoy_id5) 
 +         ELSE IF (wmo_region_number.EQ.rvind 
 +            .AND.wmo_region_subarea.NE.rvind) THEN 
 +C     Some BUFR BUOYS on GTS have 'missing' value for wmo_region_number, 
 +C     but not for wmo_region_subarea 
 +            WRITE(*,'(A,I6)') 'buoy_id=', 
 +               NINT(wmo_region_subarea)*100000 + NINT(buoy_id5) 
 +         ELSE IF (wmo_region_number.NE.rvind 
 +            .AND.wmo_region_subarea.EQ.rvind) THEN 
 +C     Not easy to know how to display this case, but then I have never 
 +C     seen this in practice 
 +            WRITE(*,'(A,I5)') 'buoy_id=',NINT(buoy_id5) 
 +         ELSE IF (buoy_id5.GT.10000.AND. 
 +               (NINT(buoy_id5) - MOD(NINT(buoy_id5),1000)).EQ. 
 +               NINT(wmo_region_number)*10000 
 +               + NINT(wmo_region_subarea)*1000) THEN 
 +C     If first 2 digits of 5 digit buoy_id equals wmo_region_number and 
 +C     wmo_region_subarea respectively, this is almost certainly an 
 +C     encoding error and we choose to show last 3 digits of buoy_id5 only 
 +           WRITE(*,'(A,I7)') 'buoy_id=',NINT(wmo_region_number)*1000000 
 +               + NINT(wmo_region_subarea)*100000 
 +               + MOD(NINT(buoy_id5),1000) 
 +         ELSE 
 +           WRITE(*,'(A,I7)') 'buoy_id=',NINT(wmo_region_number)*1000000 
 +               + NINT(wmo_region_subarea)*100000 + NINT(buoy_id5) 
 +         END IF
       ELSE       ELSE
          IF (verbose .GT. 1) THEN          IF (verbose .GT. 1) THEN
-            WRITE(*,*) 'Both wmonr, call sign (DDDD) and buoy_id', +            WRITE(*,*) 
-               ' are missing         !!!'+            WRITE(*,*) 'Both wmonr, wigosid, nationalnr, call_sign', 
 +               ' and buoy_id are missing!!!' 
 +C     Example: ISRZ47 EGRR has no proper station identification (except 
 +C     station name and position)
          END IF          END IF
          RETURN          RETURN
Line 1729: Line 2328:
       ENDIF       ENDIF
       IF (icao_id.NE.missing8) THEN       IF (icao_id.NE.missing8) THEN
-         WRITE(*,'(A,A)') 'icao_id=',icao_id+         WRITE(*,'(A,A)') 'icao_id=',icao_id(1:lenstr(icao_id,1))
       END IF       END IF
       IF (name.NE.missing20) THEN       IF (name.NE.missing20) THEN
-         WRITE(*,'(A,A)') 'name=',name+         WRITE(*,'(A,A)') 'name=',name(1:lenstr(name,1))
       END IF       END IF
-      IF (NINT(ix).EQ.0) THEN +      IF (long_name.NE.missing32) THEN 
-         WRITE(*,'(A,A)') 'type=Automatic' +         WRITE(*,'(A,A)') 'name=',long_name(1:lenstr(long_name,1)) 
-      ELSE IF (NINT(ix).EQ.1) THEN +      END IF 
-         WRITE(*,'(A,A)') 'type=Manned' +      IF (ix.NE.rvind) THEN 
-      ELSE IF (NINT(ix).EQ.2) THEN +         IF (NINT(ix).EQ.0) THEN 
-         WRITE(*,'(A,A)') 'type=Hybrid'+            WRITE(*,'(A,A)') 'type=Automatic' 
 +         ELSE IF (NINT(ix).EQ.1) THEN 
 +            WRITE(*,'(A,A)') 'type=Manned' 
 +         ELSE IF (NINT(ix).EQ.2) THEN 
 +            WRITE(*,'(A,A)') 'type=Hybrid' 
 +         END IF
       END IF       END IF
       IF (longitude.NE.rvind) THEN       IF (longitude.NE.rvind) THEN
Line 1750: Line 2354:
                                 ! so display as integer                                 ! so display as integer
          WRITE(*,'(A,I7)') 'height=',NINT(height)          WRITE(*,'(A,I7)') 'height=',NINT(height)
 +      END IF
 +      IF (hp.NE.rvind) THEN
 +         WRITE(*,'(A,F11.1)') 'hp=',hp
       END IF       END IF
       IF (vs.NE.rvind) THEN       IF (vs.NE.rvind) THEN
Line 1756: Line 2363:
       IF (ds.NE.rvind) THEN       IF (ds.NE.rvind) THEN
          WRITE(*,'(A,I11)') 'ds=',NINT(ds)          WRITE(*,'(A,I11)') 'ds=',NINT(ds)
 +      END IF
 +      IF (a3.NE.rvind) THEN     ! Standard isobaric surface for which the
 +                                ! geopotential is reported, no Kvalobs code exists
 +         WRITE(*,'(A,I11)') 'a3=',NINT(a3/100) ! hPa
       END IF       END IF
       IF (hhh.NE.rvind) THEN    ! Geopotential height, no Kvalobs code exists       IF (hhh.NE.rvind) THEN    ! Geopotential height, no Kvalobs code exists
Line 1768: Line 2379:
       IF (FX.NE.rvind) THEN       IF (FX.NE.rvind) THEN
          WRITE(*,'(A,F11.1)') 'FX=',FX          WRITE(*,'(A,F11.1)') 'FX=',FX
 +      END IF
 +      IF (FX_1.NE.rvind) THEN
 +         WRITE(*,'(A,F9.1)') 'FX_1=',FX_1
 +      END IF
 +      IF (FX_X.NE.rvind) THEN
 +         WRITE(*,'(A,F9.1)') 'FX_X=',FX_X
       END IF       END IF
       IF (DG.NE.rvind) THEN       IF (DG.NE.rvind) THEN
Line 1786: Line 2403:
       IF (FG_1.NE.rvind) THEN       IF (FG_1.NE.rvind) THEN
          WRITE(*,'(A,F9.1)') 'FG_1=',FG_1          WRITE(*,'(A,F9.1)') 'FG_1=',FG_1
 +      END IF
 +      IF (DG_X.NE.rvind) THEN
 +         WRITE(*,'(A,F9.1)') 'DG_X=',DG_X
 +      END IF
 +      IF (FG_X.NE.rvind) THEN
 +         WRITE(*,'(A,F9.1)') 'FG_X=',FG_X
       END IF       END IF
       IF (TA.NE.rvind) THEN       IF (TA.NE.rvind) THEN
Line 1798: Line 2421:
       IF (TAN_12.NE.rvind) THEN       IF (TAN_12.NE.rvind) THEN
          WRITE(*,'(A,F7.1)') 'TAN_12=',TAN_12-273.15          WRITE(*,'(A,F7.1)') 'TAN_12=',TAN_12-273.15
 +      END IF
 +      IF (TAX.NE.rvind) THEN
 +         WRITE(*,'(A,F10.1)') 'TAX=',TAX-273.15
 +      END IF
 +      IF (TAN.NE.rvind) THEN
 +         WRITE(*,'(A,F10.1)') 'TAN=',TAN-273.15
       END IF       END IF
       IF (TGN_12.NE.rvind) THEN       IF (TGN_12.NE.rvind) THEN
Line 1826: Line 2455:
          WRITE(*,'(A,F11.1)') 'PP=',PP/100 ! hPa          WRITE(*,'(A,F11.1)') 'PP=',PP/100 ! hPa
       END IF       END IF
-C     Precipitation = -0.1 means "trace(less than 0.05 kg/m2), is +C     Use the BUFR some special values for precipitation, *not* the 
-C     represented as 0 in Kvalobs+C     Kvalobs special valuesSo 'trace(less than 0.05 kg/m2), is 
 +C     showed as -0.1 (not 0 as in Kvalobs)
       IF (RR_24.NE.rvind) THEN       IF (RR_24.NE.rvind) THEN
-         IF (NINT(RR_24*10).EQ.-1) THEN +         WRITE(*,'(A,F8.1)') 'RR_24=',RR_24
-            WRITE(*,'(A,F8.1)') 'RR_24=',0.0 +
-         ELSE +
-            WRITE(*,'(A,F8.1)') 'RR_24=',RR_24 +
-         END IF+
       END IF       END IF
       IF (RR_12.NE.rvind) THEN       IF (RR_12.NE.rvind) THEN
-         IF (NINT(RR_12*10).EQ.-1) THEN +         WRITE(*,'(A,F8.1)') 'RR_12=',RR_12
-            WRITE(*,'(A,F8.1)') 'RR_12=',0.0 +
-         ELSE +
-            WRITE(*,'(A,F8.1)') 'RR_12=',RR_12 +
-         END IF+
       END IF       END IF
       IF (RR_6.NE.rvind) THEN       IF (RR_6.NE.rvind) THEN
-         IF (NINT(RR_6*10).EQ.-1) THEN +         WRITE(*,'(A,F9.1)') 'RR_6=',RR_6
-            WRITE(*,'(A,F9.1)') 'RR_6=',0.0 +
-         ELSE +
-            WRITE(*,'(A,F9.1)') 'RR_6=',RR_6 +
-         END IF+
       END IF       END IF
       IF (RR_3.NE.rvind) THEN       IF (RR_3.NE.rvind) THEN
-         IF (NINT(RR_3*10).EQ.-1) THEN +         WRITE(*,'(A,F9.1)') 'RR_3=',RR_3
-            WRITE(*,'(A,F9.1)') 'RR_3=',0.0 +
-         ELSE +
-            WRITE(*,'(A,F9.1)') 'RR_3=',RR_3 +
-         END IF+
       END IF       END IF
       IF (RR_1.NE.rvind) THEN       IF (RR_1.NE.rvind) THEN
-         IF (NINT(RR_1*10).EQ.-1) THEN +         WRITE(*,'(A,F9.1)') 'RR_1=',RR_1
-            WRITE(*,'(A,F9.1)') 'RR_1=',0.0 +
-         ELSE +
-            WRITE(*,'(A,F9.1)') 'RR_1=',RR_1 +
-         END IF+
       END IF       END IF
       IF (WW.NE.rvind.AND.WW.LT.200) THEN ! 508-511 and w1w1 (in 333 9 group) ignored here       IF (WW.NE.rvind.AND.WW.LT.200) THEN ! 508-511 and w1w1 (in 333 9 group) ignored here
Line 1884: Line 2494:
          END IF          END IF
       END IF       END IF
-      IF (E.NE.rvind) THEN +      IF (EE.NE.rvind) THEN 
-         WRITE(*,'(A,I12)') 'E=',NINT(E)+         WRITE(*,'(A,I11)') 'EE=',NINT(EE)
       END IF       END IF
-      IF (EM.NE.rvind) THEN +C     Use the BUFR some special values for SA, *not* the Kvalobs special values 
-         WRITE(*,'(A,I11)') 'EM=',NINT(EM)-10 +C     So 'trace' is showed as SA=-1, 'Snow cover not continuous' as SA=-2
-      END IF +
-C     SA has some special values in BUFR as well as in Kvalobs+
 C     Note that conversion from synop to BUFR normally will set SA=0 if E < 10 C     Note that conversion from synop to BUFR normally will set SA=0 if E < 10
-c$$$      IF (E.NE.rvind .AND. NINT(E).LE.10 
-c$$$         .AND. (SA.EQ.rvind .OR. NINT(SA).EQ.0) ) THEN 
-c$$$         WRITE(*,'(A,I11)') 'SA=',-1 ! No snow 
       IF (SA.NE.rvind) THEN       IF (SA.NE.rvind) THEN
-         IF (NINT(SA*100).EQ.-1) THEN ! Trace: less than 0.5 cm snow +         WRITE(*,'(A,I11)') 'SA=',NINT(SA*100) 
-            WRITE(*,'(A,I11)') 'SA=',+      END IF 
-         ELSE IF (NINT(SA*100).EQ.-2) THEN ! Snow cover not continuos +      IF (SS_24.NE.rvind) THEN 
-            WRITE(*,'(A,I11)') 'SA=',-1 +         WRITE(*,'(A,I8)') 'SS_24=',NINT(SS_24*100)
-         ELSE IF (NINT(SA*100).EQ.0) THEN ! 0 snow coded as -1 in Kvalobs. Stupid but true +
-            WRITE(*,'(A,I11)') 'SA=',-1 +
-         ELSE +
-            WRITE(*,'(A,I11)') 'SA=',NINT(SA*100) +
-         END IF+
       END IF       END IF
       IF (VV.NE.rvind) THEN       IF (VV.NE.rvind) THEN
Line 1916: Line 2516:
       END IF       END IF
       IF (NH.NE.rvind) THEN       IF (NH.NE.rvind) THEN
-         WRITE(*,'(A,I11)') 'NH=',NNtoWMO_N(NINT(NH))+         WRITE(*,'(A,I11)') 'NH=',NINT(NH)
       END IF       END IF
 C     Convert 020012 Cloud type in BUFR into one digit CL (0513), CM C     Convert 020012 Cloud type in BUFR into one digit CL (0513), CM
Line 1926: Line 2526:
       END IF       END IF
       IF (CM.NE.rvind) THEN       IF (CM.NE.rvind) THEN
-         IF (NINT(CM).GE.20.AND.NINT(CL).LT.30) THEN+         IF (NINT(CM).GE.20.AND.NINT(CM).LT.30) THEN
             WRITE(*,'(A,I11)') 'CM=',NINT(CM) - 20             WRITE(*,'(A,I11)') 'CM=',NINT(CM) - 20
          END IF          END IF
Line 1938: Line 2538:
       DO i=1,num_cloud_layers       DO i=1,num_cloud_layers
          IF (NS(i).NE.rvind) THEN          IF (NS(i).NE.rvind) THEN
-            WRITE(*,'(A,I1,A,I10)') 'NS',i,'=',NNtoWMO_N(NINT(NS(i)))+            WRITE(*,'(A,I1,A,I10)') 'NS',i,'=',NINT(NS(i))
          END IF          END IF
          IF (CC(i).NE.rvind) THEN          IF (CC(i).NE.rvind) THEN
Line 1944: Line 2544:
          END IF          END IF
          IF (HS(i).NE.rvind) THEN          IF (HS(i).NE.rvind) THEN
-            WRITE(*,'(A,I1,A,I10)') 'HS',i,'=',HStoWMO_HSHS(HS(i))+            WRITE(*,'(A,I1,A,I10)') 'HS',i,'=',NINT(HS(i))
          END IF          END IF
       END DO       END DO
       IF (SG.NE.rvind) THEN       IF (SG.NE.rvind) THEN
          WRITE(*,'(A,I11)') 'SG=',NINT(SG)          WRITE(*,'(A,I11)') 'SG=',NINT(SG)
 +      END IF
 +      IF (PWA.NE.rvind) THEN
 +         WRITE(*,'(A,I10)') 'PWA=',NINT(PWA)
       END IF       END IF
       IF (PW.NE.rvind) THEN       IF (PW.NE.rvind) THEN
          WRITE(*,'(A,I11)') 'PW=',NINT(PW)          WRITE(*,'(A,I11)') 'PW=',NINT(PW)
 +      END IF
 +      IF (HWA.NE.rvind) THEN
 +         WRITE(*,'(A,F10.1)') 'HWA=',HWA
       END IF       END IF
       IF (HW.NE.rvind) THEN       IF (HW.NE.rvind) THEN
Line 2003: Line 2609:
       IF (OT_24.NE.rvind) THEN       IF (OT_24.NE.rvind) THEN
          WRITE(*,'(A,I8)') 'OT_24=',NINT(OT_24)          WRITE(*,'(A,I8)') 'OT_24=',NINT(OT_24)
 +      END IF
 +      IF (QE.NE.rvind) THEN
 +         WRITE(*,'(A,F11.2)') 'QE=',QE/3600 ! Wh/m2
 +      END IF
 +      IF (QO.NE.rvind) THEN
 +         WRITE(*,'(A,F11.2)') 'QO=',QO/3600
 +      END IF
 +      IF (QL.NE.rvind) THEN
 +         WRITE(*,'(A,F11.2)') 'QL=',QL/3600
 +      END IF
 +      IF (QK.NE.rvind) THEN
 +         WRITE(*,'(A,F11.2)') 'QK=',QK/3600
 +      END IF
 +      IF (QD.NE.rvind) THEN
 +         WRITE(*,'(A,F11.2)') 'QD=',QD/3600
 +      END IF
 +      IF (QS.NE.rvind) THEN
 +         WRITE(*,'(A,F11.2)') 'QS=',QS/3600
 +      END IF
 +      IF (QE_24.NE.rvind) THEN
 +         WRITE(*,'(A,F8.2)') 'QE_24=',QE_24/3600 ! Wh/m2
 +      END IF
 +      IF (QO_24.NE.rvind) THEN
 +         WRITE(*,'(A,F8.2)') 'QO_24=',QO_24/3600
 +      END IF
 +      IF (QL_24.NE.rvind) THEN
 +         WRITE(*,'(A,F8.2)') 'QL_24=',QL_24/3600
 +      END IF
 +      IF (QK_24.NE.rvind) THEN
 +         WRITE(*,'(A,F8.2)') 'QK_24=',QK_24/3600
 +      END IF
 +      IF (QD_24.NE.rvind) THEN
 +         WRITE(*,'(A,F8.2)') 'QD_24=',QD_24/3600
 +      END IF
 +      IF (QS_24.NE.rvind) THEN
 +         WRITE(*,'(A,F8.2)') 'QS_24=',QS_24/3600
       END IF       END IF
       IF (EV_1.NE.rvind) THEN       IF (EV_1.NE.rvind) THEN
Line 2015: Line 2657:
 C     ----------------------------------------------------------------- C     -----------------------------------------------------------------
  
-C     Convert value of HS (in meter) into WMO code for hshs (table 1677) +      SUBROUTINE print_oceanographic_values(ksub,kxelem,ktdexl,ktdexp, 
-      INTEGER FUNCTION HStoWMO_HSHS(HS)+         values,cvals,rectangle,verbose) 
 +C     Identify pressure, temperature etc and print parameter=value to screen
       IMPLICIT NONE       IMPLICIT NONE
-      REAL*8 HS 
-      INTEGER HSHS 
  
-      IF (NINT(HS).LT.1800) THEN +      INTEGER ksub              ! Input: number of subset currently processed 
-         HSHS=NINT(HS/30)-1 +      INTEGER kxelem            ! Input: expected (max) number of expanded elements 
-      ELSE IF (NINT(HS).LT.10500) THEN +      INTEGER ktdexl            ! Input: number of entries in list of expanded data descriptors 
-         HSHS=NINT((HS-1800)/300)+55 +      INTEGER ktdexp(*)         ! Input: array containing expanded data descriptors 
-      ELSE IF (NINT(HS).LE.21000) THEN +      REAL*8 values(*)          ! Input: expanded data values (one subset) 
-         HSHS=NINT((HS-10500)/1500)+80+      CHARACTER*80 cvals(*)     ! Input: CCITTIA5 Bufr elements entries (one subset) 
 +      LOGICAL rectangle         ! Input: TRUE if observations are wanted for a rectangle only 
 +      INTEGER verbose           ! Input: verbose level 
 + 
 +      REAL*8 rvind              ! missing value for real*8 data 
 +      PARAMETER (rvind=1.7E38) 
 + 
 +C     Parameters defined in Kvalobs 
 +      REAL*8 HW,PW,TW, 
 +C     Other parameters 
 +         year,month,day,hour,minute, 
 +         buoy_id,latitude,longitude,sal, 
 +         wmo_region_number,wmo_region_subarea 
 +      INTEGER idx,cidx,desc,ind,maxlevel,n,numlevels 
 +      PARAMETER(maxlevel=2000) ! Largest number seen was 499 in a bathy 
 +      CHARACTER*9 call_sign,missing9 
 +      CHARACTER one_bits 
 +      REAL*8 value 
 +      REAL*8 d(maxlevel),s(maxlevel),T(maxlevel),v(maxlevel),z(maxlevel) 
 +      REAL*8 w(maxlevel) 
 + 
 +C     Variables used for geographical filtering av observations 
 +C     (--rectangle option set) 
 +      REAL*8 x1,y1,x2,y2 
 +      COMMON /COM_RECTANGLE/  x1,y1,x2,y2 
 + 
 +C     Functions 
 +      CHARACTER*9 ctrim ! length must be >= longest variable ctrim is used for 
 + 
 +      one_bits = CHAR(255) 
 +      WRITE(missing9,'(9A)') one_bits,one_bits,one_bits,one_bits, 
 +         one_bits,one_bits,one_bits,one_bits,one_bits 
 + 
 +C     Initialize all parameters to missing values 
 +      call_sign = missing9 
 +      HW = rvind 
 +      PW = rvind 
 +      TW = rvind 
 +      year = rvind 
 +      month = rvind 
 +      day = rvind 
 +      hour = rvind 
 +      minute = rvind 
 +      latitude = rvind 
 +      longitude = rvind 
 +      buoy_id = rvind 
 +      sal = rvind 
 +      wmo_region_number = rvind 
 +      wmo_region_subarea = rvind 
 +      DO n=1,maxlevel 
 +         z(n) = rvind 
 +         w(n) = rvind 
 +         T(n) = rvind 
 +         s(n) = rvind 
 +         d(n) = rvind 
 +         v(n) = rvind 
 +      END DO 
 + 
 +C     Loop through all expanded descriptors 
 +      n = 0 ! Numbering the subsurface levels 
 +      DO idx=1,ktdexl 
 +         desc = ktdexp(idx) 
 +         value = values(idx + (ksub-1)*kxelem) 
 + 
 +         IF (ABS(value - rvind)/rvind.LE.0.001) THEN 
 +C     Missing value, nothing to do 
 +            CYCLE 
 +         END IF 
 + 
 +C     Continue the loop for non missing values 
 +         IF (desc.EQ.4001) THEN ! Year 
 +            IF (year.EQ.rvind) THEN 
 +               year = value 
 +           END IF 
 +         ELSE IF (desc.EQ.4002) THEN ! Month 
 +            IF (month.EQ.rvind) THEN 
 +               month = value 
 +            END IF 
 +         ELSE IF (desc.EQ.4003) THEN ! Day 
 +            IF (day.EQ.rvind) THEN 
 +               day = value 
 +            END IF 
 +         ELSE IF (desc.EQ.4004) THEN ! Hour 
 +            IF (hour.EQ.rvind) THEN 
 +               hour = value 
 +            END IF 
 +         ELSE IF (desc.EQ.4005) THEN ! Minute 
 +            IF (minute.EQ.rvind) THEN 
 +               minute = value 
 +            END IF 
 +         ELSE IF (desc.EQ.5001.OR.  ! Latitude (high accuracy) 
 +               desc.EQ.5002) THEN ! Latitude (coarse accuracy) 
 +            IF (latitude.EQ.rvind) THEN 
 +               latitude = value 
 +            END IF 
 +         ELSE IF (desc.EQ.6001.OR.  ! Longitude (high accuracy) 
 +               desc.EQ.6002) THEN ! Longitude (coarse accuracy) 
 +            IF (longitude.EQ.rvind) THEN 
 +               longitude = value 
 +            END IF 
 +         ELSE IF (desc.EQ.31001) THEN 
 +C     Delayed descriptor replication factor; this should be number of 
 +C     subsurface levels 
 +            IF (value.EQ.rvind) THEN 
 +               WRITE(*,*) 'WARNING: delayed descriptor replication' 
 +                  // ' factor 31001 undefined!!!' 
 +               RETURN 
 +            END IF 
 +         ELSE IF (desc.EQ.7062) THEN ! Depth below sea/water surface 
 +            n = n + 1           ! new level 
 +            IF (n.GT.maxlevel) THEN 
 +               n = maxlevel 
 +               WRITE(*,*) 'Too many levels! Skipping rest of message' 
 +               GOTO 120 
 +            END IF 
 +            z(n) = value 
 +         ELSE IF (desc.EQ.7065) THEN ! Water pressure 
 +            n = n + 1           ! new level 
 +            IF (n.GT.maxlevel) THEN 
 +               n = maxlevel 
 +               WRITE(*,*) 'Too many levels! Skipping rest of message' 
 +               GOTO 120 
 +            END IF 
 +            w(n) = value 
 +         ELSE IF (desc.EQ.22045.OR.  ! Sea/water temperature (19 bits) 
 +               desc.EQ.22043.OR.   ! Sea/water temperature (15 bits) 
 +               desc.EQ.22042) THEN ! Sea/water temperature (12 bits) 
 +            IF (n.GT.0 .AND. n.LE.maxlevel) THEN 
 +               t(n) = value 
 +            ELSE IF (n.EQ.0 .AND. TW.EQ.rvind) THEN 
 +               TW = value 
 +            END IF 
 +         ELSE IF (desc.EQ.22064.OR.  ! Salinity [part per thousand] (17 bits) 
 +               desc.EQ.22062) THEN ! Salinity [part per thousand] (14 bits) 
 +            IF (n.GT.0 .AND. n.LE.maxlevel) THEN 
 +               s(n) = value 
 +            ELSE IF (n.EQ.0 .AND. sal.EQ.rvind) THEN 
 +               sal = value 
 +            END IF 
 +         ELSE IF (desc.EQ.22004) THEN ! Direction of current 
 +               IF (n.GT.0 .AND. n.LE.maxlevel) THEN 
 +                  d(n) = value 
 +               ELSE IF (n.EQ.0 .AND. verbose.GT.1) THEN 
 +                  WRITE(*,*) 'Find 22004 (dc) before first 7062 (zz)!' 
 +               END IF 
 +         ELSE IF (desc.EQ.22031) THEN ! Speed of current 
 +               IF (n.GT.0 .AND. n.LE.maxlevel) THEN 
 +                  v(n) = value 
 +               ELSE IF (n.EQ.0 .AND. verbose.GT.1) THEN 
 +                  WRITE(*,*) 'Find 22031 (vc) before first 7062 (zz)!' 
 +               END IF 
 +         ELSE IF (desc.EQ.22062) THEN ! Salinity [part per thousand] 
 +            IF (n.GT.0 .AND. n.LE.maxlevel) THEN 
 +               s(n) = value 
 +            ELSE IF (n.EQ.0 .AND. sal.EQ.rvind) THEN 
 +               sal = value 
 +            END IF 
 +         ELSE IF (desc.EQ.22011) THEN !  Period of waves (BUFR doesn't distinguish between PW and PWA) 
 +            IF (PW.EQ.rvind) THEN 
 +               PW = value 
 +            END IF 
 +         ELSE IF (desc.EQ.22021) THEN ! Heigth of waves (BUFR doesn't distinguish between HW and HWA) 
 +            IF (HW.EQ.rvind) THEN 
 +               HW = value 
 +            END IF 
 +         ELSE IF (desc.EQ.1005) THEN ! Buoy/platform identifier 
 +            IF (buoy_id.EQ.rvind) THEN 
 +               buoy_id = value 
 +            END IF 
 +         ELSE IF (desc.EQ.1003) THEN ! WMO region number/geographical area 
 +            IF (wmo_region_number.EQ.rvind) THEN 
 +               wmo_region_number = value 
 +            END IF 
 +         ELSE IF (desc.EQ.1020) THEN ! WMO region sub-area 
 +            IF (wmo_region_subarea.EQ.rvind) THEN 
 +               wmo_region_subarea = value 
 +            END IF 
 +         ELSE IF (desc.EQ.1011) THEN ! Ship or mobile land station identifier 
 +            IF (value.NE.rvind) THEN 
 +               cidx = int(value/1000) 
 +               call_sign = cvals(cidx) ! CCITTIA5 data 
 +               call_sign = ctrim(call_sign,9,missing9) 
 +            END IF 
 +         ELSE IF (desc.EQ.1087) THEN ! WMO marine observing platform extended identifier 
 +            IF (buoy_id.EQ.rvind) THEN 
 +               buoy_id = value 
 +            END IF 
 +         END IF 
 +      END DO 
 + 120  CONTINUE 
 +      numlevels = n 
 + 
 +      IF (rectangle) THEN 
 +         IF (longitude.EQ.rvind .OR. latitude.EQ.rvind 
 +            .OR. longitude.LT.x1 .OR. longitude.GT.x2 
 +            .OR. latitude.LT.y1 .OR. latitude.GT.y2) RETURN 
 +      END IF 
 + 
 +      IF (buoy_id.NE.rvind.AND.wmo_region_number.NE.rvind 
 +         .AND.wmo_region_subarea.NE.rvind) THEN 
 +         WRITE(*,*) 
 +         IF (buoy_id.LT.1000) THEN 
 +            WRITE(*,'(A,I5)') 'buoy_id=',NINT(wmo_region_number)*10000 
 +               + NINT(wmo_region_subarea)*1000 + NINT(buoy_id) 
 +         ELSE 
 +C     This is an error in encoding. We choose to show buoy_id only (and 
 +C     in all cases I have seen of this error, first 2 digits of buoy_id 
 +C     is wmo_region_number and wmo_region_subarea respectively). 
 +            IF (buoy_id.LT.10000) THEN 
 +               WRITE(*,'(A,I4)') 'buoy_id=',NINT(buoy_id) 
 +            ELSE IF (buoy_id.LT.100000) THEN 
 +               WRITE(*,'(A,I5)') 'buoy_id=',NINT(buoy_id) 
 +            ELSE IF (buoy_id.LT.1000000) THEN 
 +               WRITE(*,'(A,I6)') 'buoy_id=',NINT(buoy_id) 
 +            ELSE 
 +               WRITE(*,'(A,I7)') 'buoy_id=',NINT(buoy_id) 
 +            END IF 
 +         END IF 
 +      ELSE IF (buoy_id.NE.rvind.AND.buoy_id.GT.1000) THEN 
 +C     Old drau files (wrongly) includes wmo_region_number and 
 +C     wmo_region_subarea in buoy_id 
 +         WRITE(*,*) 
 +         IF (buoy_id.LT.10000) THEN ! 001005 
 +            WRITE(*,'(A,I5)') 'buoy_id=',NINT(buoy_id) 
 +         ELSE                       ! 001087 
 +            WRITE(*,'(A,I7)') 'buoy_id=',NINT(buoy_id) 
 +         END IF 
 +      ELSE IF (call_sign.NE.missing9) THEN 
 +         ind = index(call_sign,' ') - 1 
 +         IF (ind.EQ.-1) ind = 9 
 +C     Remove trailing NULL characters, which some centres erronously 
 +C     insert 
 +         DO WHILE (IACHAR(call_sign(ind:ind)).EQ.0) 
 +            ind = ind - 1 
 +         END DO 
 +         WRITE(*,*) 
 +         WRITE(*,'(A,A)') 'call_sign=', 
 +            call_sign(1:ind) 
 +      ELSE 
 +         IF (verbose .GT. 1) THEN 
 +            WRITE(*,*) 
 +            WRITE(*,*) 'Both buoy_id and call_sign are missing!!!' 
 +         END IF 
 +         RETURN 
 +      END IF 
 + 
 +      IF (year.NE.rvind.AND.month.NE.rvind.AND.day.NE.rvind 
 +         .AND.hour.NE.rvind.AND.minute.NE.rvind) THEN 
 +         WRITE(*,900),NINT(year),NINT(month),NINT(day), 
 +            NINT(hour),NINT(minute) 
 + 900     FORMAT('obstime=',I4,'-',I2.2,'-',I2.2,' ',I2.2,':',I2.2,':00'
 +      ELSE 
 +         IF (verbose .GT. 1) THEN 
 +            WRITE(*,*) 'obstime is missing!!!' 
 +            RETURN 
 +         END IF 
 +      ENDIF 
 +      IF (longitude.NE.rvind) THEN 
 +         WRITE(*,'(A,F10.5)') 'lon=',longitude 
 +      END IF 
 +      IF (latitude.NE.rvind) THEN 
 +         WRITE(*,'(A,F10.5)') 'lat=',latitude 
 +      END IF 
 +      IF (PW.NE.rvind) THEN 
 +         WRITE(*,'(A,I11)') 'PW=',NINT(PW) 
 +      END IF 
 +      IF (HW.NE.rvind) THEN 
 +         WRITE(*,'(A,F11.1)') 'HW=',HW 
 +      END IF 
 +      IF (TW.NE.rvind) THEN 
 +         WRITE(*,'(A,F11.1)') 'TW=',TW-273.15 
 +      END IF 
 +      IF (sal.NE.rvindTHEN 
 +         WRITE(*,'(A,F11.2)') 'ss=',sal 
 +      END IF 
 + 
 +      DO n=1,numlevels 
 +C     Do not print level if empty (might happen with last levels in 
 +C     compressed messages, or simply due to bad practice. Setting 
 +C     delayed description replication factor = 1 when ought to be 0 is 
 +C     not quite uncommon) 
 +         IF (z(n).EQ.rvind .AND. t(n).EQ.rvind .AND. s(n).EQ.rvind 
 +            .AND. d(n).EQ.rvind .AND. v(n).EQ.rvind 
 +            .AND. w(n).EQ.rvind) THEN 
 +            CYCLE 
 +         END IF 
 +         WRITE(*,'(A,I12)'),'n=',
 +         IF (z(n).NE.rvind) THEN 
 +            WRITE(*,'(A,I11)') 'zz=',NINT(z(n)) 
 +         END IF 
 +         IF (w(n).NE.rvind) THEN 
 +            WRITE(*,'(A,I11)') 'wp=',NINT(w(n)) 
 +         END IF 
 +         IF (t(n).NE.rvind) THEN 
 +            WRITE(*,'(A,F11.2)') 'tt=',t(n)-273.15 
 +         END IF 
 +         IF (s(n).NE.rvind) THEN 
 +            WRITE(*,'(A,F11.2)') 'ss=',s(n) 
 +         END IF 
 +         IF (d(n).NE.rvind) THEN 
 +            WRITE(*,'(A,I11)') 'dc=',NINT(d(n)) 
 +         END IF 
 +         IF (v(n).NE.rvind) THEN 
 +            WRITE(*,'(A,F11.1)') 'vc=',v(n) 
 +         END IF 
 +      END DO 
 + 
 +      END SUBROUTINE print_oceanographic_values 
 + 
 +C     ----------------------------------------------------------------- 
 + 
 +      SUBROUTINE print_amdar_values(ksub,kxelem,ktdexl,ktdexp,values, 
 +         cvals,rectangle,verbose) 
 +C     Identify pressure, temperature etc and print parameter=value to screen 
 +      IMPLICIT NONE 
 + 
 +      INTEGER ksub              ! Input: number of subset currently processed 
 +      INTEGER kxelem            ! Input: expected (max) number of expanded elements 
 +      INTEGER ktdexl            ! Input: number of entries in list of expanded data descriptors 
 +      INTEGER ktdexp(*)         ! Input: array containing expanded data descriptors 
 +      REAL*8 values(*)          ! Input: expanded data values (one subset) 
 +      CHARACTER*80 cvals(*)     ! Input: CCITTIA5 Bufr elements entries (one subset) 
 +      LOGICAL rectangle         ! Input: TRUE if observations are wanted for a rectangle only 
 +      INTEGER verbose           ! Input: verbose level 
 + 
 +      REAL*8 rvind              ! missing value for real*8 data 
 +      PARAMETER (rvind=1.7E38) 
 + 
 +      CHARACTER*8 aircraft,flight_number,missing8 
 +C     Parameters defined in Kvalobs 
 +      REAL*8 DD,FF,TT,PP, 
 +C     Other parameters 
 +         year,month,day,hour,minute,second,latitude,longitude, 
 +         flight_level,phase,osn,mixing_ratio 
 +      CHARACTER*3 cphase,missing3 
 +      INTEGER idx,cidx,ind 
 +      CHARACTER one_bits 
 +      REAL*8 value 
 +      INTEGER desc 
 + 
 +C     Variables used for geographical filtering av observations 
 +C     (--rectangle option set) 
 +      REAL*8 x1,y1,x2,y2 
 +      COMMON /COM_RECTANGLE/  x1,y1,x2,y2 
 + 
 +C     Functions 
 +      INTEGER lenstr 
 +      CHARACTER*8 ctrim ! length must be >= longest variable ctrim is used for 
 +      CHARACTER*3 phase_8004,phase_8009 
 + 
 +      one_bits = CHAR(255) 
 +      WRITE(missing3,'(3A)') one_bits,one_bits,one_bits 
 +      WRITE(missing8,'(8A)') one_bits,one_bits,one_bits,one_bits, 
 +         one_bits,one_bits,one_bits,one_bits 
 + 
 +C     Initialize all parameters to missing values 
 +      aircraft = missing8 
 +      flight_number = missing8 
 +      cphase = missing3 
 +      osn = rvind 
 +      DD = rvind 
 +      FF = rvind 
 +      TT = rvind 
 +      PP = rvind 
 +      year = rvind 
 +      month = rvind 
 +      day = rvind 
 +      hour = rvind 
 +      minute = rvind 
 +      second = rvind 
 +      latitude = rvind 
 +      longitude = rvind 
 +      flight_level = rvind 
 +      phase = rvind 
 +      mixing_ratio = rvind 
 + 
 +C     Loop through all expanded descriptors 
 +      DO idx=1,ktdexl 
 +         desc = ktdexp(idx) 
 +         value = values(idx + (ksub-1)*kxelem) 
 + 
 +         IF (ABS(value - rvind)/rvind.LE.0.001) THEN 
 +C     Missing value, nothing to do 
 +            CYCLE 
 +         END IF 
 + 
 +C     Continue the loop for non missing values 
 +         IF (desc.EQ.1008) THEN ! Aircraft registration number or other identification 
 +            cidx = int(value/1000) 
 +            aircraft = cvals(cidx) ! CCITTIA5 data 
 +            aircraft = ctrim(aircraft,8,missing8) 
 +         ELSE IF (desc.EQ.1006) THEN ! Aircraft flight number 
 +            cidx = int(value/1000) 
 +            flight_number = cvals(cidx) ! CCITTIA5 data 
 +            flight_number = ctrim(flight_number,8,missing8) 
 +         ELSE IF (desc.EQ.1023) THEN ! Observation sequence number 
 +            IF (osn.EQ.rvind) osn = value 
 +         ELSE IF (desc.EQ.4001) THEN ! Year 
 +            IF (year.EQ.rvind) THEN 
 +               year = value 
 +            END IF 
 +         ELSE IF (desc.EQ.4002) THEN ! Month 
 +            IF (month.EQ.rvind) THEN 
 +               month = value 
 +            END IF 
 +         ELSE IF (desc.EQ.4003) THEN ! Day 
 +            IF (day.EQ.rvind) THEN 
 +               day = value 
 +            END IF 
 +         ELSE IF (desc.EQ.4004) THEN ! Hour 
 +            IF (hour.EQ.rvind) THEN 
 +               hour = value 
 +            END IF 
 +         ELSE IF (desc.EQ.4005) THEN ! Minute 
 +            IF (minute.EQ.rvind) THEN 
 +               minute = value 
 +            END IF 
 +         ELSE IF (desc.EQ.4006) THEN ! Second 
 +            IF (second.EQ.rvind) THEN 
 +               second = value 
 +            END IF 
 +         ELSE IF (desc.EQ.5001.OR.  ! Latitude (high accuracy) 
 +               desc.EQ.5002) THEN ! Latitude (coarse accuracy) 
 +            IF (latitude.EQ.rvind) THEN 
 +               latitude = value 
 +            END IF 
 +         ELSE IF (desc.EQ.6001.OR.  ! Longitude (high accuracy) 
 +               desc.EQ.6002) THEN ! Longitude (coarse accuracy) 
 +            IF (longitude.EQ.rvind) THEN 
 +               longitude = value 
 +            END IF 
 +         ELSE IF (desc.EQ.7010.OR.   ! Flight level 
 +               desc.EQ.7002.OR.    ! Height or altitude 
 +               desc.EQ.10070) THEN ! Indicated aircraft altitude 
 +            IF (flight_level.EQ.rvind) THEN 
 +               flight_level = value 
 +            END IF 
 +         ELSE IF (desc.EQ.8009.OR.  ! Detailed phase of aircraft flight 
 +               desc.EQ.8004) THEN ! Phase of aircraft flight 
 +            IF (phase.EQ.rvind) THEN 
 +               phase = value 
 +               cphase = phase_8009(NINT(phase),missing3) 
 +            END IF 
 +         ELSE IF (desc.EQ.8004) THEN ! Phase of aircraft flight 
 +            IF (phase.EQ.rvind) THEN 
 +               phase = value 
 +               cphase = phase_8004(NINT(phase),missing3) 
 +            END IF 
 +         ELSE IF (desc.EQ.12104.OR. ! Dry bulb temperature at 2m (data width 16 bits) 
 +              desc.EQ.12004.OR.   ! Dry bulb temperature at 2m (12 bits) 
 +              desc.EQ.12101.OR.   ! Temperature/dry bulb temperature (16 bits) 
 +              desc.EQ.12001) THEN ! Temperature/dry bulb temperature (12 bits) 
 +            IF (TT.EQ.rvind) THEN 
 +               TT value 
 +            END IF 
 +         ELSE IF (desc.EQ.11011.OR.  ! Wind direction at 10 m 
 +               desc.EQ.11001) THEN ! Wind direction 
 +            IF (DD.EQ.rvind) THEN 
 +               DD = value 
 +            END IF 
 +         ELSE IF (desc.EQ.11012.OR.  ! Wind speed at 10 m 
 +               desc.EQ.11002) THEN ! Wind speed 
 +            IF (FF.EQ.rvind) THEN 
 +               FF = value 
 +            END IF 
 +         ELSE IF (desc.EQ.7004) THEN ! Pressure 
 +            IF (PP.EQ.rvind) THEN 
 +               PP = value 
 +            END IF 
 +         ELSE IF (desc.EQ.13002) THEN ! Mixing ratio 
 +            IF (mixing_ratio.EQ.rvind) THEN 
 +               mixing_ratio = value 
 +            END IF 
 +         END IF 
 +      END DO 
 + 
 +      IF (rectangle) THEN 
 +         IF (longitude.EQ.rvind .OR. latitude.EQ.rvind 
 +            .OR. longitude.LT.x1 .OR. longitude.GT.x2 
 +            .OR. latitude.LT.y1 .OR. latitude.GT.y2) RETURN 
 +      END IF 
 + 
 +      IF (aircraft.NE.missing8) THEN 
 +         WRITE(*,*) 
 +         WRITE(*,'(A,A)') 'aircraft=',aircraft(1:lenstr(aircraft,1)) 
 +      ELSE IF (flight_number.NE.missing8) THEN 
 +         WRITE(*,*) 
 +         WRITE(*,'(A,A)') 'aircraft=', 
 +            flight_number(1:lenstr(flight_number,1)) 
 +      ELSE 
 +         IF (verbose .GT. 1) THEN 
 +            WRITE(*,*) 
 +            WRITE(*,*) 'Aircraft (001008/001006) is missing!!!' 
 +         END IF 
 +         RETURN 
 +      END IF 
 + 
 + 901  FORMAT('obstime=',I4,'-',I2.2,'-',I2.2,' ',I2.2,':',I2.2,':',I2.2) 
 + 902  FORMAT('obstime=',I4,'-',I2.2,'-',I2.2,' ',I2.2,':',I2.2,':00'
 + 
 +      IF (year.NE.rvind.AND.month.NE.rvind.AND.day.NE.rvind 
 +         .AND.hour.NE.rvind.AND.minute.NE.rvind) THEN 
 +         IF (second.NE.rvind) THEN 
 +            WRITE(*,901),NINT(year),NINT(month),NINT(day), 
 +               NINT(hour),NINT(minute),NINT(second) 
 +         ELSE 
 +            WRITE(*,902),NINT(year),NINT(month),NINT(day), 
 +               NINT(hour),NINT(minute) 
 +         END IF 
 +      ELSE IF (verbose .GT. 1) THEN 
 +         WRITE(*,*) 'obstime is missing!!!' 
 +         RETURN 
 +      END IF 
 +      IF (longitude.NE.rvind) THEN 
 +         WRITE(*,'(A,F15.5)') 'lon=',longitude 
 +      END IF 
 +      IF (latitude.NE.rvind) THEN 
 +         WRITE(*,'(A,F15.5)') 'lat=',latitude 
 +      END IF 
 +      IF (osn.NE.rvind) THEN 
 +         WRITE(*,'(A,I12)') 'seqnum=',NINT(osn) 
 +      END IF 
 +      IF (flight_level.NE.rvind) THEN 
 +         WRITE(*,'(A,I6)') 'flight_level=',NINT(flight_level) 
 +      END IF 
 +      IF (phase.NE.rvind) THEN 
 +         WRITE(*,'(A,A3)') 'phase_of_flight=',cphase 
 +      END IF 
 +      IF (DD.NE.rvind) THEN 
 +         WRITE(*,'(A,I16)') 'DD=',NINT(DD) 
 +      END IF 
 +      IF (FF.NE.rvind) THEN 
 +         WRITE(*,'(A,F16.1)') 'FF=',FF 
 +      END IF 
 +      IF (TT.NE.rvind) THEN 
 +         WRITE(*,'(A,F16.1)') 'TT=',TT-273.15 
 +      END IF 
 +      IF (PP.NE.rvindTHEN 
 +         WRITE(*,'(A,F16.1)') 'PP=',PP/100 ! hPa 
 +      END IF 
 +      IF (mixing_ratio.NE.rvindTHEN 
 +         WRITE(*,'(A,F16.2)') 'mr=',mixing_ratio*1000 ! g/kg 
 +      END IF 
 + 
 +      END SUBROUTINE print_amdar_values 
 + 
 +C     ----------------------------------------------------------------- 
 + 
 +C     Remove trailing blanks and nulls from string, returning missing if 
 +C     nothing left 
 +      CHARACTER*(*) FUNCTION ctrim(string,dim,missing) 
 +      IMPLICIT NONE 
 +      CHARACTER*(*) string,missing 
 +      INTEGER dim,ind,ascii 
 + 
 +      ind = dim 
 +      ascii = IACHAR(string(ind:ind)) 
 +      DO WHILE (ind.GT.1 .AND. (ascii.EQ.32 .OR. ascii.EQ.0)) 
 +         ind = ind - 1 
 +         ascii = IACHAR(string(ind:ind)) 
 +      END DO 
 +      IF (ind.EQ.1) THEN 
 +         ascii = IACHAR(string(1:1)) 
 +         IF (ascii.EQ.32 .OR. ascii.EQ.0) THEN 
 +            ctrim = missing 
 +         ELSE 
 +            ctrim = string(1:1) 
 +         END IF 
 +      ELSE IF (ind.GT.1) THEN 
 +         ctrim = string(1:ind) 
 +      ELSE 
 +         ctrim = missing 
 +      END IF 
 + 
 +      RETURN 
 +      END FUNCTION ctrim 
 + 
 + 
 +C     ----------------------------------------------------------------- 
 + 
 +      CHARACTER*3 FUNCTION phase_8004(phase,missing3) 
 +      IMPLICIT NONE 
 +      INTEGER phase 
 +      CHARACTER*3 missing3,indicator(6) 
 + 
 +      DATA indicator/'res','UNS','LVR','LVW','ASC','DES'/ 
 +C                      1                     6 
 + 
 +      IF (phase.LE.1 .OR. phase.GT.6) THEN 
 +         phase_8004 = missing3 
 +      ELSE 
 +         phase_8004 = indicator(phase) 
 +      END IF 
 + 
 +      RETURN 
 +      END FUNCTION phase_8004 
 + 
 +C     ----------------------------------------------------------------- 
 + 
 +      CHARACTER*3 FUNCTION phase_8009(phase,missing3) 
 +      IMPLICIT NONE 
 +      INTEGER phase 
 +      CHARACTER*3 missing3,indicator(15) 
 + 
 +C                      0                         6 
 +      DATA indicator/'LVR','LVW','UNS','LVR','LVW','ASC','DES', 
 +         4*'ASC',4*'DES'/ 
 +C            7-10    11-14 
 + 
 +      IF (phase.LE.0 .OR. phase.GT.14) THEN 
 +         phase_8009 = missing3
       ELSE       ELSE
-         HSHS=89+         phase_8009 indicator(phase + 1)
       END IF       END IF
  
-      HStoWMO_HSHS = HSHS 
       RETURN       RETURN
-      END FUNCTION HStoWMO_HSHS+      END FUNCTION phase_8009
  
 C     ----------------------------------------------------------------- C     -----------------------------------------------------------------
Line 2043: Line 3293:
       IF (NN.EQ.0) THEN       IF (NN.EQ.0) THEN
          N = 0          N = 0
-      ELSE IF (NN.LE.10) THEN  ! 1/10 or less+      ELSE IF (NN.LE.15) THEN  ! 1/10 or less
          N = 1          N = 1
       ELSE IF (NN.LE.30) THEN  ! 2/10 - 3/10       ELSE IF (NN.LE.30) THEN  ! 2/10 - 3/10
Line 2160: Line 3410:
       significance = '        '       significance = '        '
       jj = 8       jj = 8
-      IF (btest(vss,18-15)) THEN +      IF (btest(vss,18-15)) THEN
          significance(jj:jj) = 'r' ! level determined by regional decision          significance(jj:jj) = 'r' ! level determined by regional decision
          jj = jj-1          jj = jj-1
Line 2194: Line 3444:
  
       END SUBROUTINE vss_8042       END SUBROUTINE vss_8042
-      +
 C     ----------------------------------------------------------------- C     -----------------------------------------------------------------
  
Line 2230: Line 3480:
 c c
       character*(*) text       character*(*) text
-      integer       minlen+      integer       k,l,lt,minlen
 c c
       lt=len(text)       lt=len(text)
Line 2244: Line 3494:
       return       return
       end       end
- +</code      
-</file+<code fortran comfilter.f>
- +
- +
-comfilter.f+
-<file>+
 C (C) Copyright 2010, met.no C (C) Copyright 2010, met.no
 C C
Line 2268: Line 3514:
  
 C     Variables used for filtering av observations (--filter option set C     Variables used for filtering av observations (--filter option set
-C     in readbufr or bufrdump)+C     in bufrread or bufrdump)
  
       INTEGER dim1_fid, dim2_fid, dim_fiv       INTEGER dim1_fid, dim2_fid, dim_fiv
Line 2294: Line 3540:
  
       COMMON /COM_FILTERC/ fidformat,fivC       COMMON /COM_FILTERC/ fidformat,fivC
-</file>+</code>
  • bufr.pm/bufrdump.1267198617.txt.gz
  • Last modified: 2022-05-31 09:23:11
  • (external edit)