NCEPLIBS-bufr  12.0.1
readns.f
Go to the documentation of this file.
1 C> @file
2 C> @brief Read the next data subset from a BUFR file that was
3 C> previously opened for reading.
4 C>
5 C> @author J. Woollen @date 1994-01-06
6 
7 C> This subroutine provides a handy way to combine the functionality
8 C> of subroutines readmg() and readsb() within a single subroutine
9 C> call.
10 C>
11 C> Logical unit LUNIT should have already been opened for
12 C> input operations via a previous call to subroutine openbf().
13 C> But once that is done, the application program can immediately call
14 C> this subroutine to read each new data subset from the
15 C> associated BUFR file, and the subroutine will automatically open
16 C> and close each new BUFR message internally as needed, so that
17 C> subsequent calls can immediately be made to any of the various
18 C> [values-reading subroutines](@ref hierarchy).
19 C>
20 C> @param[in] LUNIT -- integer: Fortran logical unit number for
21 C> BUFR file
22 C> @param[out] SUBSET -- character*8: Table A mnemonic for type of
23 C> data subset that was read
24 C> (see [DX BUFR Tables](@ref dfbftab)
25 C> for further information about Table A mnemonics)
26 C> @param[out] JDATE -- integer: Date-time stored within Section 1 of
27 C> BUFR message containing data subset that
28 C> was read, in format of either
29 C> YYMMDDHH or YYYYMMDDHH, depending on the most
30 C> recent call to subroutine datelen()
31 C> @param[out] IRET -- integer: return code
32 C> - 0 = new BUFR data subset was successfully
33 C> read into internal arrays
34 C> - -1 = there are no more BUFR data subsets
35 C> in the file connected to logical unit
36 C> LUNIT
37 C>
38 C> @author J. Woollen @date 1994-01-06
39  RECURSIVE SUBROUTINE readns(LUNIT,SUBSET,JDATE,IRET)
40 
41  USE moda_msgcwd
42  USE moda_tables
43  USE modv_im8b
44 
45  CHARACTER*8 subset
46 
47 C-----------------------------------------------------------------------
48 C-----------------------------------------------------------------------
49 
50 C CHECK FOR I8 INTEGERS
51 C ---------------------
52 
53  IF(im8b) THEN
54  im8b=.false.
55 
56  CALL x84(lunit,my_lunit,1)
57  CALL readns(my_lunit,subset,jdate,iret)
58  CALL x48(jdate,jdate,1)
59  CALL x48(iret,iret,1)
60 
61  im8b=.true.
62  RETURN
63  ENDIF
64 
65 C REFRESH THE SUBSET AND JDATE PARAMETERS
66 C ---------------------------------------
67 
68  CALL status(lunit,lun,il,im)
69  IF(il.EQ.0) GOTO 900
70  IF(il.GT.0) GOTO 901
71  IF(inode(lun).EQ.0) THEN
72  subset = ' '
73  ELSE
74  subset = tag(inode(lun))(1:8)
75  ENDIF
76  jdate = idate(lun)
77 
78 C READ THE NEXT SUBSET IN THE BUFR FILE
79 C -------------------------------------
80 
81 1 CALL readsb(lunit,iret)
82  IF(iret.NE.0) THEN
83  CALL readmg(lunit,subset,jdate,iret)
84  IF(iret.EQ.0) GOTO 1
85  ENDIF
86 
87 C EXITS
88 C -----
89 
90  RETURN
91 900 CALL bort('BUFRLIB: READNS - INPUT BUFR FILE IS CLOSED, IT MUST'//
92  . ' BE OPEN FOR INPUT')
93 901 CALL bort('BUFRLIB: READNS - INPUT BUFR FILE IS OPEN FOR OUTPUT'//
94  . ', IT MUST BE OPEN FOR INPUT')
95  END
subroutine bort(STR)
Log one error message and abort application program.
Definition: bort.f:18
This module contains declarations for arrays used to store information about the current BUFR message...
integer, dimension(:), allocatable inode
Table A mnemonic for type of BUFR message.
integer, dimension(:), allocatable idate
Section 1 date-time of message.
This module contains array and variable declarations used to store the internal jump/link table.
character *10, dimension(:), allocatable tag
Mnemonics in the jump/link table.
This module declares and initializes the IM8B variable.
logical, public im8b
Status indicator to keep track of whether all future calls to BUFRLIB subroutines and functions from ...
recursive subroutine readmg(LUNXX, SUBSET, JDATE, IRET)
Reads the next BUFR message from logical unit ABS(LUNXX) into internal arrays.
Definition: readmg.f:52
recursive subroutine readns(LUNIT, SUBSET, JDATE, IRET)
This subroutine provides a handy way to combine the functionality of subroutines readmg() and readsb(...
Definition: readns.f:40
recursive subroutine readsb(LUNIT, IRET)
Read the next data subset from a BUFR message.
Definition: readsb.f:33
recursive subroutine status(LUNIT, LUN, IL, IM)
Check whether a specified Fortran logical unit number is currently connected to the NCEPLIBS-bufr sof...
Definition: status.f:36
subroutine x48(IIN4, IOUT8, NVAL)
Encode one or more 4-byte integer values as 8-byte integer values.
Definition: x48.F:19
subroutine x84(IIN8, IOUT4, NVAL)
Encode one or more 8-byte integer values as 4-byte integer values.
Definition: x84.F:19