NCEPLIBS-bufr  12.0.0
rdcmps.f
Go to the documentation of this file.
1 C> @file
2 C> @brief Read the next compressed BUFR data subset into internal arrays.
3 C>
4 C> @author Woollen @date 2000-09-19
5 
6 C> Read the next compressed BUFR data subset into internal arrays.
7 C>
8 C> This subroutine uncompresses and unpacks the next subset
9 C> from the internal compressed message buffer (array mbay in module
10 C> @ref moda_bitbuf) and stores the unpacked subset within the internal
11 C> array val(*,lun) in module @ref moda_usrint.
12 C>
13 C> @param[in] LUN - integer: File ID.
14 C>
15 C> @author Woollen @date 2000-09-19
16  SUBROUTINE rdcmps(LUN)
17 
18  USE modv_bmiss
19  USE modv_mxrst
20 
21  USE moda_usrint
22  USE moda_msgcwd
23  USE moda_bitbuf
24  USE moda_tables
25  USE moda_rlccmn
26  use moda_stcode
27 
28  CHARACTER*128 BORT_STR
29  CHARACTER*8 CREF,CVAL
30  equivalence(cval,rval)
31  real*8 rval,ups
32 
33  integer(8) :: ival,lref,ninc,lps
34 
35 C-----------------------------------------------------------------------
36 C Statement function to compute BUFR "missing value" for field
37 C of length LBIT bits (all bits "on"):
38 
39  lps(lbit) = max(2_8**(lbit)-1,1)
40 C-----------------------------------------------------------------------
41 
42 C SETUP THE SUBSET TEMPLATE
43 C -------------------------
44 
45  CALL usrtpl(lun,1,1)
46 
47 C UNCOMPRESS A SUBSET INTO THE VAL ARRAY ACCORDING TO TABLE B
48 C -----------------------------------------------------------
49 
50  nsbs = nsub(lun)
51 
52 C Note that we are going to unpack the (NSBS)th subset from within
53 C the current BUFR message.
54 
55  ibit = mbyt(lun)
56  nrst = 0
57 
58 C Loop through each element of the subset.
59 
60  n = 0
61 
62 1 DO n=n+1,nval(lun)
63  node = inv(n,lun)
64  nrfelm(n,lun) = igetrfel(n,lun)
65  nbit = ibt(node)
66  ityp = itp(node)
67 
68 C In each of the following code blocks, the "local reference value"
69 C for the element is determined first, followed by the 6-bit value
70 C which indicates how many bits are used to store the increment
71 C (i.e. offset) from this "local reference value". Then, we jump
72 C ahead to where this increment is stored for this particular subset,
73 C unpack it, and add it to the "local reference value" to determine
74 C the final uncompressed value for this element from this subset.
75 
76 C Note that, if an element has the same final uncompressed value
77 C for each subset in the message, then the encoding rules for BUFR
78 C compression dictate that the "local reference value" will be equal
79 C to this value, the 6-bit increment length indicator will have
80 C a value of zero, and the actual increments themselves will be
81 C omitted from the message.
82 
83  IF(ityp.EQ.1.OR.ityp.EQ.2) THEN
84 
85 C This is a numeric element.
86 
87  CALL up8(lref,nbit,mbay(1,lun),ibit)
88  CALL upb(linc, 6,mbay(1,lun),ibit)
89  jbit = ibit + linc*(nsbs-1)
90  CALL up8(ninc,linc,mbay(1,lun),jbit)
91  IF(ninc.EQ.lps(linc)) THEN
92  ival = lps(nbit)
93  ELSE
94  ival = lref+ninc
95  ENDIF
96  IF(ityp.EQ.1) THEN
97  nbmp=int(ival)
98  CALL usrtpl(lun,n,nbmp)
99  if (iscodes(lun) .ne. 0) return
100  GOTO 1
101  ENDIF
102  IF(ival.LT.lps(nbit)) val(n,lun) = ups(ival,node)
103  CALL strbtm(n,lun)
104  ibit = ibit + linc*msub(lun)
105  ELSEIF(ityp.EQ.3) THEN
106 
107 C This is a character element. If there are more than 8
108 C characters, then only the first 8 will be unpacked by this
109 C routine, and a separate subsequent call to BUFR archive library
110 C subroutine READLC will be required to unpack the remainder of
111 C the string. In this case, pointers will be saved within
112 C COMMON /RLCCMN/ for later use within READLC.
113 
114 C Unpack the local reference value.
115 
116  lelm = nbit/8
117  nchr = min(8,lelm)
118  ibsv = ibit
119  cref = ' '
120  CALL upc(cref,nchr,mbay(1,lun),ibit,.true.)
121  IF(lelm.GT.8) THEN
122  ibit = ibit + (lelm-8)*8
123  nrst = nrst + 1
124  IF(nrst.GT.mxrst) GOTO 900
125  crtag(nrst) = tag(node)
126  ENDIF
127 
128 C Unpack the increment length indicator. For character elements,
129 C this length is in bytes rather than bits.
130 
131  CALL upb(linc, 6,mbay(1,lun),ibit)
132  IF(linc.EQ.0) THEN
133  IF(lelm.GT.8) THEN
134  irnch(nrst) = lelm
135  irbit(nrst) = ibsv
136  ENDIF
137  cval = cref
138  ELSE
139  jbit = ibit + linc*(nsbs-1)*8
140  IF(lelm.GT.8) THEN
141  irnch(nrst) = linc
142  irbit(nrst) = jbit
143  ENDIF
144  nchr = min(8,linc)
145  cval = ' '
146  CALL upc(cval,nchr,mbay(1,lun),jbit,.true.)
147  ENDIF
148  IF (lelm.LE.8 .AND. icbfms(cval,nchr).NE.0) THEN
149  val(n,lun) = bmiss
150  ELSE
151  val(n,lun) = rval
152  ENDIF
153  ibit = ibit + 8*linc*msub(lun)
154  ENDIF
155  ENDDO
156 
157  RETURN
158 900 WRITE(bort_str,'("BUFRLIB: RDCMPS - NUMBER OF LONG CHARACTER ' //
159  . 'STRINGS EXCEEDS THE LIMIT (",I4,")")') mxrst
160  CALL bort(bort_str)
161  END
subroutine bort(STR)
Log one error message and abort application program.
Definition: bort.f:18
recursive function icbfms(STR, LSTR)
This function provides a handy way to check whether a character string returned from a previous call ...
Definition: icbfms.f:25
integer function igetrfel(N, LUN)
This function checks whether the input element refers to a previous element within the same subset vi...
Definition: igetrfel.f:23
This module contains array and variable declarations used to store BUFR messages internally for multi...
integer ibit
Bit pointer within IBAY.
integer, dimension(:,:), allocatable mbay
Current BUFR message for each internal I/O stream.
integer, dimension(:), allocatable mbyt
Length (in bytes) of current BUFR message for each internal I/O stream.
This module contains declarations for arrays used to store information about the current BUFR message...
integer, dimension(:), allocatable msub
Total number of data subsets in message.
integer, dimension(:), allocatable nsub
Current subset pointer within message.
This module contains array and variable declarations needed to store information about long character...
integer nrst
Number of long character strings in data subset.
integer, dimension(:), allocatable irnch
Lengths (in bytes) of long character strings.
integer, dimension(:), allocatable irbit
Pointers in data subset to first bits of long character strings.
character *10, dimension(:), allocatable crtag
Table B mnemonics associated with long character strings.
This module contains an array declaration used to store a status code for each internal I/O stream in...
integer, dimension(:), allocatable iscodes
Abnormal status codes.
This module contains array and variable declarations used to store the internal jump/link table.
integer, dimension(:), allocatable ibt
Bit widths corresponding to tag and typ:
character *10, dimension(:), allocatable tag
Mnemonics in the jump/link table.
integer, dimension(:), allocatable itp
Integer type values corresponding to typ:
This module contains declarations for arrays used to store data values and associated metadata for th...
integer, dimension(:), allocatable nval
Number of data values in BUFR data subset.
real *8, dimension(:,:), allocatable, target val
Data values.
integer, dimension(:,:), allocatable, target inv
Inventory pointer which links each data value to its corresponding node in the internal jump/link tab...
integer, dimension(:,:), allocatable nrfelm
Referenced data value, for data values which refer to a previous data value in the BUFR data subset v...
This module declares and initializes the BMISS variable.
Definition: modules_vars.F90:9
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 MXRST variable.
integer mxrst
Maximum number of "long" character strings (greater than 8 bytes) that can be read from a data subset...
subroutine rdcmps(LUN)
Read the next compressed BUFR data subset into internal arrays.
Definition: rdcmps.f:17
subroutine strbtm(N, LUN)
This subroutine stores internal information in module bitmaps if the input element is part of a bitma...
Definition: strbtm.f:14
subroutine up8(nval, nbits, ibay, ibit)
This subroutine decodes an 8-byte integer value from within a specified number of bits of an integer ...
Definition: up8.f:27
subroutine upb(NVAL, NBITS, IBAY, IBIT)
This subroutine decodes an integer value from within a specified number of bits of an integer array,...
Definition: upb.f:28
subroutine upc(CHR, NCHR, IBAY, IBIT, CNVNULL)
Decode a character string from an integer array.
Definition: upc.f:32
real *8 function ups(IVAL, NODE)
This function unpacks a real*8 user value from a packed BUFR integer by applying the proper scale and...
Definition: ups.f:22
subroutine usrtpl(LUN, INVN, NBMP)
Store the subset template into internal arrays.
Definition: usrtpl.f:22