27 SUBROUTINE stntbi ( N, LUN, NUMB, NEMO, CELSQ )
31 CHARACTER*(*) NUMB, NEMO, CELSQ
36 CALL nenubd ( nemo, numb, lun )
38 IF ( numb(1:1) .EQ.
'0')
THEN
40 tabb(n,lun)( 1: 6) = numb(1:6)
41 tabb(n,lun)( 7:14) = nemo(1:8)
42 tabb(n,lun)(16:70) = celsq(1:55)
44 ELSE IF ( numb(1:1) .EQ.
'3')
THEN
46 tabd(n,lun)( 1: 6) = numb(1:6)
47 tabd(n,lun)( 7:14) = nemo(1:8)
48 tabd(n,lun)(16:70) = celsq(1:55)
function ifxy(ADSC)
This function converts an FXY value from its 6 character representation to its bit-wise (integer) rep...
This module contains array and variable declarations used to store DX BUFR tables internally for mult...
integer, dimension(:,:), allocatable idnb
Bit-wise representations of the FXY values corresponding to tabb.
character *128, dimension(:,:), allocatable tabb
Table B entries for each internal I/O stream.
integer, dimension(:), allocatable ntbd
Number of Table D entries for each internal I/O stream (up to a maximum of MAXTBD,...
integer, dimension(:), allocatable ntbb
Number of Table B entries for each internal I/O stream (up to a maximum of MAXTBB,...
integer, dimension(:,:), allocatable idnd
Bit-wise representations of the FXY values corresponding to tabd.
character *600, dimension(:,:), allocatable tabd
Table D entries for each internal I/O stream.
subroutine nenubd(NEMO, NUMB, LUN)
THIS SUBROUTINE CHECKS A MNEMONIC AND FXY VALUE PAIR THAT WERE READ FROM A USER-SUPPLIED BUFR DICTION...
subroutine stntbi(N, LUN, NUMB, NEMO, CELSQ)
THIS SUBROUTINE STORES A NEW ENTRY WITHIN INTERNAL BUFR TABLE B OR D, DEPENDING ON THE VALUE OF NUMB.