144 SUBROUTINE ufbrep(LUNIN,USR,I1,I2,IRET,STR)
154 CHARACTER*128 BORT_STR1,BORT_STR2,ERRSTR
157 DATA ifirst1/0/,ifirst2/0/
159 SAVE ifirst1, ifirst2
170 CALL status(lunit,lun,il,im)
173 IF(inode(lun).NE.inv(1,lun))
GOTO 902
175 io = min(max(0,il),1)
176 IF(lunin.NE.lunit) io = 0
180 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
181 errstr = .LE.
'BUFRLIB: UFBREP - 3rd ARG. (INPUT) IS 0, ' //
182 .
'SO RETURN WITH 5th ARG. (IRET) = 0; 6th ARG. (STR) ='
185 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
190 IF(iprt.EQ.-1) ifirst1 = 1
191 IF(io.EQ.0 .OR. ifirst1.EQ.0 .OR. iprt.GE.1)
THEN
192 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
193 errstr = .LE.
'BUFRLIB: UFBREP - 4th ARG. (INPUT) IS 0, ' //
194 .
'SO RETURN WITH 5th ARG. (IRET) = 0; 6th ARG. (STR) ='
197 IF(iprt.EQ.0 .AND. io.EQ.1)
THEN
198 errstr =
'Note: Only the first occurrence of this WARNING ' //
199 .
'message is printed, there may be more. To output all ' //
202 errstr =
'modify your application program to add ' //
203 .
'"CALL OPENBF(0,''QUIET'',1)" prior to the first call ' //
204 .
'to a BUFRLIB routine.'
207 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
230 CALL string(str,lun,i1,io)
235 CALL ufbrp(lun,usr,i1,i2,io,iret)
238 IF(io.EQ.1 .AND. iret.LT.i2)
GOTO 903
243 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
244 errstr =
'BUFRLIB: UFBREP - NO SPECIFIED VALUES READ IN, ' //
245 .
'SO RETURN WITH 5th ARG. (IRET) = 0; 6th ARG. (STR) ='
248 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
252 IF(iprt.EQ.-1) ifirst2 = 1
253 IF(ifirst2.EQ.0 .OR. iprt.GE.1)
THEN
254 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
255 errstr =
'BUFRLIB: UFBREP - NO SPECIFIED VALUES WRITTEN OUT, ' //
256 .
'SO RETURN WITH 5th ARG. (IRET) = 0; 6th ARG. (STR) ='
259 CALL errwrt(
'MAY NOT BE IN THE BUFR TABLE(?)')
261 errstr =
'Note: Only the first occurrence of this WARNING ' //
262 .
'message is printed, there may be more. To output all ' //
265 errstr =
'modify your application program to add ' //
266 .
'"CALL OPENBF(0,''QUIET'',1)" prior to the first call ' //
267 .
'to a BUFRLIB routine.'
270 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
281900
CALL bort(
'BUFRLIB: UFBREP - BUFR FILE IS CLOSED, IT MUST BE'//
283901
CALL bort(
'BUFRLIB: UFBREP - A MESSAGE MUST BE OPEN IN BUFR '//
285902
CALL bort(
'BUFRLIB: UFBREP - LOCATION OF INTERNAL TABLE FOR '//
286 .
'BUFR FILE DOES NOT AGREE WITH EXPECTED LOCATION IN INTERNAL '//
288903
WRITE(bort_str1,
'("BUFRLIB: UFBREP - MNEMONIC STRING READ IN IS'//
290 WRITE(bort_str2,
'(18X,"THE NUMBER OF ''LEVELS'' ACTUALLY '//
291 .
'WRITTEN (",I3,") LESS THAN THE NUMBER REQUESTED (",I3,") - '//
292 .
'INCOMPLETE WRITE")') iret,i2
293 CALL bort2(bort_str1,bort_str2)
subroutine bort2(STR1, STR2)
This subroutine calls subroutine errwrt() to log two error messages, then calls subroutine bort_exit(...
subroutine bort(STR)
This subroutine calls subroutine errwrt() to log an error message, then calls subroutine bort_exit() ...
subroutine errwrt(STR)
This subroutine allows the user to specify a custom location for the logging of error and diagnostic ...
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...
subroutine status(LUNIT, LUN, IL, IM)
This subroutine checks whether a specified Fortran logical unit number is currently connected to the ...
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 ufbrep(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 ufbrp(LUN, USR, I1, I2, IO, IRET)
THIS SUBROUTINE WRITES OR READS SPECIFIED VALUES TO OR FROM THE CURRENT BUFR DATA SUBSET WITHIN INTER...