115 RECURSIVE SUBROUTINE ufbrep(LUNIN,USR,I1,I2,IRET,STR)
127 CHARACTER*128 bort_str1,bort_str2,errstr
130 DATA ifirst1/0/,ifirst2/0/
132 SAVE ifirst1, ifirst2
143 CALL x84(lunin,my_lunin,1)
146 CALL ufbrep(my_lunin,usr,my_i1,my_i2,iret,str)
147 CALL x48(iret,iret,1)
159 CALL status(lunit,lun,il,im)
162 IF(
inode(lun).NE.
inv(1,lun))
GOTO 902
164 io = min(max(0,il),1)
165 IF(lunin.NE.lunit) io = 0
169 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
170 errstr = .LE.
'BUFRLIB: UFBREP - 3rd ARG. (INPUT) IS 0, ' //
171 .
'SO RETURN WITH 5th ARG. (IRET) = 0; 6th ARG. (STR) ='
174 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
179 IF(iprt.EQ.-1) ifirst1 = 1
180 IF(io.EQ.0 .OR. ifirst1.EQ.0 .OR. iprt.GE.1)
THEN
181 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
182 errstr = .LE.
'BUFRLIB: UFBREP - 4th ARG. (INPUT) IS 0, ' //
183 .
'SO RETURN WITH 5th ARG. (IRET) = 0; 6th ARG. (STR) ='
186 IF(iprt.EQ.0 .AND. io.EQ.1)
THEN
187 errstr =
'Note: Only the first occurrence of this WARNING ' //
188 .
'message is printed, there may be more. To output all ' //
191 errstr =
'modify your application program to add ' //
192 .
'"CALL OPENBF(0,''QUIET'',1)" prior to the first call ' //
193 .
'to a BUFRLIB routine.'
196 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
219 CALL string(str,lun,i1,io)
224 CALL ufbrp(lun,usr,i1,i2,io,iret)
227 IF(io.EQ.1 .AND. iret.LT.i2)
GOTO 903
232 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
233 errstr =
'BUFRLIB: UFBREP - NO SPECIFIED VALUES READ IN, ' //
234 .
'SO RETURN WITH 5th ARG. (IRET) = 0; 6th ARG. (STR) ='
237 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
241 IF(iprt.EQ.-1) ifirst2 = 1
242 IF(ifirst2.EQ.0 .OR. iprt.GE.1)
THEN
243 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
244 errstr =
'BUFRLIB: UFBREP - NO SPECIFIED VALUES WRITTEN OUT, ' //
245 .
'SO RETURN WITH 5th ARG. (IRET) = 0; 6th ARG. (STR) ='
248 CALL errwrt(
'MAY NOT BE IN THE BUFR TABLE(?)')
250 errstr =
'Note: Only the first occurrence of this WARNING ' //
251 .
'message is printed, there may be more. To output all ' //
254 errstr =
'modify your application program to add ' //
255 .
'"CALL OPENBF(0,''QUIET'',1)" prior to the first call ' //
256 .
'to a BUFRLIB routine.'
259 CALL errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
270 900
CALL bort(
'BUFRLIB: UFBREP - BUFR FILE IS CLOSED, IT MUST BE'//
272 901
CALL bort(
'BUFRLIB: UFBREP - A MESSAGE MUST BE OPEN IN BUFR '//
274 902
CALL bort(
'BUFRLIB: UFBREP - LOCATION OF INTERNAL TABLE FOR '//
275 .
'BUFR FILE DOES NOT AGREE WITH EXPECTED LOCATION IN INTERNAL '//
277 903
WRITE(bort_str1,
'("BUFRLIB: UFBREP - MNEMONIC STRING READ IN IS'//
279 WRITE(bort_str2,
'(18X,"THE NUMBER OF ''LEVELS'' ACTUALLY '//
280 .
'WRITTEN (",I3,") LESS THAN THE NUMBER REQUESTED (",I3,") - '//
281 .
'INCOMPLETE WRITE")') iret,i2
282 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 ...
recursive subroutine ufbrep(LUNIN, USR, I1, I2, IRET, STR)
Read/write one or more data values from/to a data subset.
subroutine ufbrp(LUN, USR, I1, I2, IO, IRET)
This subroutine writes or reads specified data values to or from the current BUFR data subset within ...
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.