63 CHARACTER*128 BORT_STR
73 CALL status(lunin,lin,il,im)
79 CALL status(lunot,lot,il,im)
83 IF(inode(lin).NE.inode(lot))
THEN
84 IF( (
tag(inode(lin)).NE.
tag(inode(lot))) .OR.
85 . (
iok2cpy(lin,lot).NE.1) )
GOTO 906
92 IF(nsub(lin).EQ.msub(lin))
THEN
100 CALL mesgbc(-lunin,mest,icmp)
118 ELSE IF(icmp.EQ.0)
THEN
127 CALL upb(nbyt,16,
mbay(1,lin),ibit)
128 IF (nbyt.GT.65530)
THEN
133 IF ( (nsub(lin).EQ.0) .AND. (msub(lin).EQ.1) )
THEN
138 CALL getlens(
mbay(1,lin),4,len0,len1,len2,len3,len4,l5)
149 IF(lunot.GT.0)
CALL cpyupd(lunot,lin,lot,nbyt)
151 nsub(lin) = nsub(lin) + 1
160900
CALL bort(
'BUFRLIB: COPYSB - INPUT BUFR FILE IS CLOSED, IT '//
161 .
'MUST BE OPEN FOR INPUT')
162901
CALL bort(
'BUFRLIB: COPYSB - INPUT BUFR FILE IS OPEN FOR '//
163 .
'OUTPUT, IT MUST BE OPEN FOR INPUT')
164902
CALL bort(
'BUFRLIB: COPYSB - A MESSAGE MUST BE OPEN IN INPUT '//
165 .
'BUFR FILE, NONE ARE')
166903
CALL bort(
'BUFRLIB: COPYSB - OUTPUT BUFR FILE IS CLOSED, IT '//
167 .
'MUST BE OPEN FOR OUTPUT')
168904
CALL bort(
'BUFRLIB: COPYSB - OUTPUT BUFR FILE IS OPEN FOR '//
169 .
'INPUT, IT MUST BE OPEN FOR OUTPUT')
170905
CALL bort(
'BUFRLIB: COPYSB - A MESSAGE MUST BE OPEN IN OUTPUT '//
171 .
'BUFR FILE, NONE ARE')
172906
CALL bort(
'BUFRLIB: COPYSB - INPUT AND OUTPUT BUFR FILES MUST '//
173 .
'HAVE THE SAME INTERNAL TABLES, THEY ARE DIFFERENT HERE')
174907
WRITE(bort_str,
'("BUFRLIB: COPYSB - INVALID COMPRESSION '//
175 .
'INDICATOR (ICMP=",I3," RETURNED FROM BUFR ARCHIVE LIBRARY '//
176 .
'ROUTINE MESGBC")') icmp
subroutine bort(STR)
This subroutine calls subroutine errwrt() to log an error message, then calls subroutine bort_exit() ...
subroutine cmpmsg(CF)
This subroutine is used to specify whether BUFR messages output by future calls to message-writing su...
subroutine copysb(LUNIN, LUNOT, IRET)
This subroutine copies a BUFR data subset from one Fortran logical unit to another.
subroutine cpyupd(LUNIT, LIN, LUN, IBYT)
THIS SUBROUTINE COPIES A SUBSET FROM ONE MESSAGE BUFFER (ARRAY MBAY IN MODULE BITBUF) TO ANOTHER AND/...
subroutine getlens(MBAY, LL, LEN0, LEN1, LEN2, LEN3, LEN4, LEN5)
This subroutine reads the lengths of all of the individual sections of a given BUFR message,...
integer function iok2cpy(LUI, LUO)
This function determines whether a BUFR message, or a data subset from within a BUFR message,...
subroutine mesgbc(LUNIN, MESGTYP, ICOMP)
THIS SUBROUTINE EXAMINES A BUFR MESSAGE AND RETURNS BOTH THE MESSAGE TYPE FROM SECTION 1 AND A MESSAG...
This module contains array and variable declarations used to store BUFR messages internally for multi...
integer, dimension(:), allocatable mbyt
Length (in bytes) of current BUFR message for each internal I/O stream.
integer, dimension(:,:), allocatable mbay
Current BUFR message for each internal I/O stream.
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.
subroutine readsb(LUNIT, IRET)
This subroutine reads the next data subset from a BUFR message into internal arrays.
subroutine status(LUNIT, LUN, IL, IM)
This subroutine checks whether a specified Fortran logical unit number is currently connected to the ...
subroutine ufbcpy(LUBIN, LUBOT)
THIS SUBROUTINE COPIES A COMPLETE SUBSET BUFFER, UNPACKED INTO INTERNAL MEMORY FROM LOGICAL UNIT LUBI...
subroutine upb(NVAL, NBITS, IBAY, IBIT)
THIS SUBROUTINE UNPACKS AND RETURNS A BINARY INTEGER CONTAINED WITHIN NBITS BITS OF IBAY,...
subroutine writsb(LUNIT)
This subroutine writes a complete data subset into a BUFR message, for eventual output to logical uni...