115 RECURSIVE SUBROUTINE ufbstp(LUNIN,USR,I1,I2,IRET,STR)
126 CHARACTER*128 bort_str1,bort_str2,errstr
129 DATA ifirst1/0/,ifirst2/0/
131 SAVE ifirst1, ifirst2
142 CALL x84(lunin,my_lunin,1)
145 CALL ufbstp(my_lunin,usr,my_i1,my_i2,iret,str)
146 CALL x48(iret,iret,1)
158 CALL status(lunit,lun,il,im)
161 IF(
inode(lun).NE.
inv(1,lun))
GOTO 902
163 io = min(max(0,il),1)
164 IF(lunin.NE.lunit) io = 0
168 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
169 errstr = .LE.
'BUFRLIB: UFBSTP - 3rd ARG. (INPUT) IS 0, ' //
170 .
'SO RETURN WITH 5th ARG. (IRET) = 0; 6th ARG. (STR) ='
173 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
178 IF(iprt.EQ.-1) ifirst1 = 1
179 IF(io.EQ.0 .OR. ifirst1.EQ.0 .OR. iprt.GE.1)
THEN
180 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
181 errstr = .LE.
'BUFRLIB: UFBSTP - 4th ARG. (INPUT) IS 0, ' //
182 .
'SO RETURN WITH 5th ARG. (IRET) = 0; 6th ARG. (STR) ='
185 IF(iprt.EQ.0 .AND. io.EQ.1)
THEN
186 errstr =
'Note: Only the first occurrence of this WARNING ' //
187 .
'message is printed, there may be more. To output all ' //
190 errstr =
'modify your application program to add ' //
191 .
'"CALL OPENBF(0,''QUIET'',1)" prior to the first call ' //
192 .
'to a BUFRLIB routine.'
195 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
216 CALL string(str,lun,i1,io)
221 CALL ufbsp(lun,usr,i1,i2,io,iret)
223 IF(io.EQ.1 .AND. iret.NE.i2)
GOTO 903
228 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
229 errstr =
'BUFRLIB: UFBSTP - NO SPECIFIED VALUES READ IN, ' //
230 .
'SO RETURN WITH 5th ARG. (IRET) = 0; 6th ARG. (STR) ='
233 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
237 IF(iprt.EQ.-1) ifirst2 = 1
238 IF(ifirst2.EQ.0 .OR. iprt.GE.1)
THEN
239 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
240 errstr =
'BUFRLIB: UFBSTP - NO SPECIFIED VALUES WRITTEN OUT, ' //
241 .
'SO RETURN WITH 5th ARG. (IRET) = 0; 6th ARG. (STR) ='
244 CALL errwrt(
'MAY NOT BE IN THE BUFR TABLE(?)')
246 errstr =
'Note: Only the first occurrence of this WARNING ' //
247 .
'message is printed, there may be more. To output all ' //
250 errstr =
'modify your application program to add ' //
251 .
'"CALL OPENBF(0,''QUIET'',1)" prior to the first call ' //
252 .
'to a BUFRLIB routine.'
255 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
266 900
CALL bort(
'BUFRLIB: UFBSTP - BUFR FILE IS CLOSED, IT MUST BE'//
268 901
CALL bort(
'BUFRLIB: UFBSTP - A MESSAGE MUST BE OPEN IN BUFR '//
270 902
CALL bort(
'BUFRLIB: UFBSTP - LOCATION OF INTERNAL TABLE FOR '//
271 .
'BUFR FILE DOES NOT AGREE WITH EXPECTED LOCATION IN INTERNAL '//
273 903
WRITE(bort_str1,
'("BUFRLIB: UFBSTP - MNEMONIC STRING READ IN IS'//
275 WRITE(bort_str2,
'(18X,"THE NUMBER OF ''LEVELS'' ACTUALLY '//
276 .
'WRITTEN (",I3,") DOES NOT EQUAL THE NUMBER REQUESTED (",I3,")'//
277 .
' - INCOMPLETE WRITE")') iret,i2
278 CALL bort2(bort_str1,bort_str2)
subroutine bort2(STR1, STR2)
Log two error messages and abort application program.
subroutine bort(STR)
Log one error message and abort application program.
subroutine errwrt(STR)
This subroutine allows the user to specify a custom location for the logging of error and diagnostic ...
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.
This module contains declarations for arrays used to store data values and associated metadata for th...
integer, dimension(:,:), allocatable, target inv
Inventory pointer which links each data value to its corresponding node in the internal jump/link tab...
This module declares and initializes the BMISS variable.
real *8, public bmiss
Current placeholder value to represent "missing" data when reading from or writing to BUFR files; thi...
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 status(LUNIT, LUN, IL, IM)
Check whether a specified Fortran logical unit number is currently connected to the NCEPLIBS-bufr sof...
subroutine string(STR, LUN, I1, IO)
This subroutine checks to see if a user-specified character string is in the string cache (arrays in ...
subroutine ufbsp(LUN, USR, I1, I2, IO, IRET)
This subroutine writes or reads specified values to or from the current BUFR data subset within inter...
recursive subroutine ufbstp(LUNIN, USR, I1, I2, IRET, STR)
This subroutine reads or writes one or more data values from or to the BUFR data subset that is curre...
subroutine x48(IIN4, IOUT8, NVAL)
Encode one or more 4-byte integer values as 8-byte integer values.
subroutine x84(IIN8, IOUT4, NVAL)
Encode one or more 8-byte integer values as 4-byte integer values.