152 SUBROUTINE ufbint(LUNIN,USR,I1,I2,IRET,STR)
158 COMMON /usrstr/ nnod,ncon,nods(20),nodc(10),ivls(10),kons(10)
162 CHARACTER*128 bort_str1,bort_str2,errstr
165 DATA ifirst1/0/,ifirst2/0/
167 SAVE ifirst1, ifirst2
178 CALL
status(lunit,lun,il,im)
181 IF(inode(lun).NE.inv(1,lun)) goto 902
183 io = min(max(0,il),1)
184 IF(lunit.NE.lunin) io = 0
188 CALL
errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
189 errstr = .LE.
'BUFRLIB: UFBINT - 3rd ARG. (INPUT) IS 0, ' //
190 .
'SO RETURN WITH 5th ARG. (IRET) = 0; 6th ARG. (STR) ='
193 CALL
errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
198 IF(iprt.EQ.-1) ifirst1 = 1
199 IF(io.EQ.0 .OR. ifirst1.EQ.0 .OR. iprt.GE.1)
THEN
200 CALL
errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
201 errstr = .LE.
'BUFRLIB: UFBINT - 4th ARG. (INPUT) IS 0, ' //
202 .
'SO RETURN WITH 5th ARG. (IRET) = 0; 6th ARG. (STR) ='
205 IF(iprt.EQ.0 .AND. io.EQ.1)
THEN
206 errstr =
'Note: Only the first occurrence of this WARNING ' //
207 .
'message is printed, there may be more. To output all ' //
210 errstr =
'modify your application program to add ' //
211 .
'"CALL OPENBF(0,''QUIET'',1)" prior to the first call ' //
212 .
'to a BUFRLIB routine.'
215 CALL
errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
225 CALL
string(str,lun,i1,io)
241 CALL
ufbrw(lun,usr,i1,i2,io,iret)
246 IF(io.EQ.1 .AND. iret.NE.i2 .AND. iret.GE.0)
THEN
247 CALL
trybump(lunit,lun,usr,i1,i2,io,iret)
248 IF(iret.NE.i2) goto 903
249 ELSEIF(iret.EQ.-1)
THEN
256 CALL
errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
257 errstr =
'BUFRLIB: UFBINT - NO SPECIFIED VALUES READ IN, ' //
258 .
'SO RETURN WITH 5th ARG. (IRET) = 0; 6th ARG. (STR) ='
261 CALL
errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
265 IF(iprt.EQ.-1) ifirst2 = 1
266 IF(ifirst2.EQ.0 .OR. iprt.GE.1)
THEN
267 CALL
errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
268 errstr =
'BUFRLIB: UFBINT - NO SPECIFIED VALUES WRITTEN OUT, ' //
269 .
'SO RETURN WITH 5th ARG. (IRET) = 0; 6th ARG. (STR) ='
272 CALL
errwrt(
'MAY NOT BE IN THE BUFR TABLE(?)')
274 errstr =
'Note: Only the first occurrence of this WARNING ' //
275 .
'message is printed, there may be more. To output all ' //
278 errstr =
'modify your application program to add ' //
279 .
'"CALL OPENBF(0,''QUIET'',1)" prior to the first call ' //
280 .
'to a BUFRLIB routine.'
283 CALL
errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
294 900 CALL
bort(
'BUFRLIB: UFBINT - BUFR FILE IS CLOSED, IT MUST BE'//
296 901 CALL
bort(
'BUFRLIB: UFBINT - A MESSAGE MUST BE OPEN IN BUFR '//
298 902 CALL
bort(
'BUFRLIB: UFBINT - LOCATION OF INTERNAL TABLE FOR '//
299 .
'BUFR FILE DOES NOT AGREE WITH EXPECTED LOCATION IN INTERNAL '//
301 903
WRITE(bort_str1,
'("BUFRLIB: UFBINT - MNEMONIC STRING READ IN IS'//
303 WRITE(bort_str2,
'(18X,"THE NUMBER OF ''LEVELS'' ACTUALLY '//
304 .
'WRITTEN (",I3,") DOES NOT EQUAL THE NUMBER REQUESTED (",I3,")'//
305 .
' - INCOMPLETE WRITE")') iret,i2
306 CALL
bort2(bort_str1,bort_str2)
subroutine ufbrw(LUN, USR, I1, I2, IO, IRET)
THIS SUBROUTINE WRITES OR READS SPECIFIED VALUES TO OR FROM THE CURRENT BUFR DATA SUBSET WITHIN INTER...
subroutine bort2(STR1, STR2)
This subroutine calls subroutine errwrt() to log two error messages, then calls subroutine bort_exit(...
This module declares and initializes the BMISS variable.
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 trybump(LUNIT, LUN, USR, I1, I2, IO, IRET)
THIS SUBROUTINE CHECKS THE FIRST NODE ASSOCIATED WITH A CHARACTER STRING (PARSED INTO ARRAYS IN COMMO...
subroutine status(LUNIT, LUN, IL, IM)
This subroutine checks whether a specified Fortran logical unit number is currently connected to the ...
subroutine errwrt(STR)
This subroutine allows the user to specify a custom location for the logging of error and diagnostic ...
subroutine ufbint(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 bort(STR)
This subroutine calls subroutine errwrt() to log an error message, then calls subroutine bort_exit() ...