NCEPLIBS-bufr 11.7.1
rdcmps.f
Go to the documentation of this file.
1C> @file
2C> @author WOOLLEN @date 2000-09-19
3
4C> THIS SUBROUTINE UNCOMPRESSES AND UNPACKS THE NEXT SUBSET
5C> FROM THE INTERNAL COMPRESSED MESSAGE BUFFER (ARRAY MBAY IN MODULE
6C> BITBUF) AND STORES THE UNPACKED SUBSET WITHIN THE INTERNAL
7C> ARRAY VAL(*,LUN) IN MODULE USRINT.
8C>
9C> PROGRAM HISTORY LOG:
10C> 2000-09-19 J. WOOLLEN -- ORIGINAL AUTHOR
11C> 2002-05-14 J. WOOLLEN -- IMPROVED GENERALITY, PREVIOUSLY RDCMPS
12C> WOULD NOT RECOGNIZE COMPRESSED DELAYED
13C> REPLICATION AS A LEGITIMATE DATA STRUCTURE
14C> 2003-11-04 J. ATOR -- ADDED DOCUMENTATION
15C> 2003-11-04 S. BENDER -- ADDED REMARKS/BUFRLIB ROUTINE
16C> INTERDEPENDENCIES
17C> 2003-11-04 D. KEYSER -- MAXJL (MAXIMUM NUMBER OF JUMP/LINK ENTRIES)
18C> INCREASED FROM 15000 TO 16000 (WAS IN
19C> VERIFICATION VERSION); UNIFIED/PORTABLE FOR
20C> WRF; ADDED HISTORY DOCUMENTATION
21C> 2004-08-18 J. ATOR -- INITIALIZE CVAL TO EMPTY BEFORE CALLING UPC;
22C> CORRECT LOGIC FOR WHEN A CHARACTER VALUE IS
23C> THE SAME FOR ALL SUBSETS IN A MESSAGE;
24C> MAXIMUM MESSAGE LENGTH INCREASED FROM
25C> 20,000 TO 50,000 BYTES
26C> 2009-03-23 J. ATOR -- PREVENT OVERFLOW OF CVAL AND CREF FOR
27C> STRINGS LONGER THAN 8 CHARACTERS
28C> 2012-03-02 J. ATOR -- USE FUNCTION UPS
29C> 2012-06-04 J. ATOR -- SET DECODED REAL*8 VALUE TO "MISSING" WHEN
30C> CORRESPONDING CHARACTER FIELD HAS ALL BITS
31C> SET TO 1
32C> 2014-12-10 J. ATOR -- USE MODULES INSTEAD OF COMMON BLOCKS
33C> 2022-05-06 J. WOOLLEN -- USE UP8 FOR 8BYTE INTEGER OPERATION
34C>
35C> USAGE: CALL RDCMPS (LUN)
36C> INPUT ARGUMENT LIST:
37C> LUN - INTEGER: I/O STREAM INDEX INTO INTERNAL MEMORY ARRAYS
38C>
39C> REMARKS:
40C> THIS ROUTINE CALLS: BORT ICBFMS IGETRFEL STRBTM
41C> UPB UP8 UPC UPS USRTPL
42C> THIS ROUTINE IS CALLED BY: READSB
43C> Normally not called by any application
44C> programs.
45C>
46 SUBROUTINE rdcmps(LUN)
47
48 USE modv_bmiss
49 USE modv_mxrst
50
51 USE moda_usrint
52 USE moda_msgcwd
53 USE moda_bitbuf
54 USE moda_tables
55 USE moda_rlccmn
56
57 CHARACTER*128 BORT_STR
58 CHARACTER*8 CREF,CVAL
59 equivalence(cval,rval)
60 real*8 rval,ups
61
62 integer(8) :: ival,lref,ninc,lps
63
64C-----------------------------------------------------------------------
65C Statement function to compute BUFR "missing value" for field
66C of length LBIT bits (all bits "on"):
67
68 lps(lbit) = max(2_8**(lbit)-1,1)
69C-----------------------------------------------------------------------
70
71C SETUP THE SUBSET TEMPLATE
72C -------------------------
73
74 CALL usrtpl(lun,1,1)
75
76C UNCOMPRESS A SUBSET INTO THE VAL ARRAY ACCORDING TO TABLE B
77C -----------------------------------------------------------
78
79 nsbs = nsub(lun)
80
81C Note that we are going to unpack the (NSBS)th subset from within
82C the current BUFR message.
83
84 ibit = mbyt(lun)
85 nrst = 0
86
87C Loop through each element of the subset.
88
89 n = 0
90
911 DO n=n+1,nval(lun)
92 node = inv(n,lun)
93 nrfelm(n,lun) = igetrfel(n,lun)
94 nbit = ibt(node)
95 ityp = itp(node)
96
97C In each of the following code blocks, the "local reference value"
98C for the element is determined first, followed by the 6-bit value
99C which indicates how many bits are used to store the increment
100C (i.e. offset) from this "local reference value". Then, we jump
101C ahead to where this increment is stored for this particular subset,
102C unpack it, and add it to the "local reference value" to determine
103C the final uncompressed value for this element from this subset.
104
105C Note that, if an element has the same final uncompressed value
106C for each subset in the message, then the encoding rules for BUFR
107C compression dictate that the "local reference value" will be equal
108C to this value, the 6-bit increment length indicator will have
109C a value of zero, and the actual increments themselves will be
110C omitted from the message.
111
112 IF(ityp.EQ.1.OR.ityp.EQ.2) THEN
113
114C This is a numeric element.
115
116 CALL up8(lref,nbit,mbay(1,lun),ibit)
117 CALL upb(linc, 6,mbay(1,lun),ibit)
118 jbit = ibit + linc*(nsbs-1)
119 CALL up8(ninc,linc,mbay(1,lun),jbit)
120 IF(ninc.EQ.lps(linc)) THEN
121 ival = lps(nbit)
122 ELSE
123 ival = lref+ninc
124 ENDIF
125 IF(ityp.EQ.1) THEN
126 nbmp=ival; CALL usrtpl(lun,n,nbmp)
127 GOTO 1
128 ENDIF
129 IF(ival.LT.lps(nbit)) val(n,lun) = ups(ival,node)
130 CALL strbtm(n,lun)
131 ibit = ibit + linc*msub(lun)
132 ELSEIF(ityp.EQ.3) THEN
133
134C This is a character element. If there are more than 8
135C characters, then only the first 8 will be unpacked by this
136C routine, and a separate subsequent call to BUFR archive library
137C subroutine READLC will be required to unpack the remainder of
138C the string. In this case, pointers will be saved within
139C COMMON /RLCCMN/ for later use within READLC.
140
141C Unpack the local reference value.
142
143 lelm = nbit/8
144 nchr = min(8,lelm)
145 ibsv = ibit
146 cref = ' '
147 CALL upc(cref,nchr,mbay(1,lun),ibit,.true.)
148 IF(lelm.GT.8) THEN
149 ibit = ibit + (lelm-8)*8
150 nrst = nrst + 1
151 IF(nrst.GT.mxrst) GOTO 900
152 crtag(nrst) = tag(node)
153 ENDIF
154
155C Unpack the increment length indicator. For character elements,
156C this length is in bytes rather than bits.
157
158 CALL upb(linc, 6,mbay(1,lun),ibit)
159 IF(linc.EQ.0) THEN
160 IF(lelm.GT.8) THEN
161 irnch(nrst) = lelm
162 irbit(nrst) = ibsv
163 ENDIF
164 cval = cref
165 ELSE
166 jbit = ibit + linc*(nsbs-1)*8
167 IF(lelm.GT.8) THEN
168 irnch(nrst) = linc
169 irbit(nrst) = jbit
170 ENDIF
171 nchr = min(8,linc)
172 cval = ' '
173 CALL upc(cval,nchr,mbay(1,lun),jbit,.true.)
174 ENDIF
175 IF (lelm.LE.8 .AND. icbfms(cval,nchr).NE.0) THEN
176 val(n,lun) = bmiss
177 ELSE
178 val(n,lun) = rval
179 ENDIF
180 ibit = ibit + 8*linc*msub(lun)
181 ENDIF
182 ENDDO
183
184 RETURN
185900 WRITE(bort_str,'("BUFRLIB: RDCMPS - NUMBER OF LONG CHARACTER ' //
186 . 'STRINGS EXCEEDS THE LIMIT (",I4,")")') mxrst
187 CALL bort(bort_str)
188 END
subroutine bort(STR)
This subroutine calls subroutine errwrt() to log an error message, then calls subroutine bort_exit() ...
Definition: bort.f:23
integer function icbfms(STR, LSTR)
This function provides a handy way to check whether a character string returned from a previous call ...
Definition: icbfms.f:32
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:36
This module contains array and variable declarations used to store BUFR messages internally for multi...
Definition: moda_bitbuf.F:10
integer, dimension(:), allocatable mbyt
Length (in bytes) of current BUFR message for each internal I/O stream.
Definition: moda_bitbuf.F:25
integer, dimension(:,:), allocatable mbay
Current BUFR message for each internal I/O stream.
Definition: moda_bitbuf.F:26
This module contains array and variable declarations used to store the internal jump/link table.
Definition: moda_tables.F:13
integer, dimension(:), allocatable itp
Integer type values corresponding to typ:
Definition: moda_tables.F:141
integer, dimension(:), allocatable ibt
Bit widths corresponding to tag and typ:
Definition: moda_tables.F:138
character *10, dimension(:), allocatable tag
Mnemonics in the jump/link table.
Definition: moda_tables.F:132
This module declares and initializes the BMISS variable.
Definition: modv_BMISS.f90:9
real *8, public bmiss
Current placeholder value to represent "missing" data when reading from or writing to BUFR files; thi...
Definition: modv_BMISS.f90:15
This module declares and initializes the MXRST variable.
Definition: modv_MXRST.f:13
integer mxrst
Maximum number of "long" character strings (greater than 8 bytes) that can be read from a data subset...
Definition: modv_MXRST.f:20
subroutine rdcmps(LUN)
THIS SUBROUTINE UNCOMPRESSES AND UNPACKS THE NEXT SUBSET FROM THE INTERNAL COMPRESSED MESSAGE BUFFER ...
Definition: rdcmps.f:47
subroutine strbtm(N, LUN)
THIS SUBROUTINE STORES INTERNAL INFORMATION IN MODULE BITMAPS IF THE INPUT ELEMENT IS PART OF A BITMA...
Definition: strbtm.f:22
subroutine up8(nval, nbits, ibay, ibit)
THIS SUBROUTINE UNPACKS AND RETURNS AN 8-BYTE INTEGER CONTAINED WITHIN NBITS BITS OF IBAY,...
Definition: up8.f:41
subroutine upb(NVAL, NBITS, IBAY, IBIT)
THIS SUBROUTINE UNPACKS AND RETURNS A BINARY INTEGER CONTAINED WITHIN NBITS BITS OF IBAY,...
Definition: upb.f:50
subroutine upc(CHR, NCHR, IBAY, IBIT, CNVNULL)
THIS SUBROUTINE UNPACKS AND RETURNS A CHARACTER STRING OF LENGTH NCHR CONTAINED WITHIN NCHR BYTES OF ...
Definition: upc.f:50
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:33
subroutine usrtpl(LUN, INVN, NBMP)
THIS SUBROUTINE STORES THE SUBSET TEMPLATE INTO INTERNAL SUBSET ARRAYS IN MODULE USRINT FOR CASES OF ...
Definition: usrtpl.f:52