NCEPLIBS-bufr  12.0.0
ardllocf.f
Go to the documentation of this file.
1 C> @file
2 C> @brief Free all dynamically-allocated memory within internal
3 C> Fortran language arrays.
4 C>
5 C> @author J. Ator @date 2014-12-04
6 
7 C> This subroutine frees any memory that was dynamically allocated
8 C> during a previous call to subroutine arallocf().
9 C>
10 C> @author J. Ator @date 2014-12-04
11  SUBROUTINE ardllocf
12 
13  use bufrlib
14 
15  USE moda_usrint
16  USE moda_usrbit
17  USE moda_ival
18  USE moda_msgcwd
19  USE moda_stbfr
20  USE moda_ufbcpl
21  USE moda_sc3bfr
22  USE moda_unptyp
23  USE moda_lushr
24  USE moda_nulbfr
25  USE moda_stcode
26  USE moda_idrdm
27  USE moda_xtab
28  USE moda_msglim
29  USE moda_bitbuf
30  USE moda_mgwa
31  USE moda_mgwb
32  USE moda_bufrmg
33  USE moda_bufrsr
34  USE moda_msgmem
35  USE moda_tababd
36  USE moda_tables
37  USE moda_usrtmp
38  USE moda_ivttmp
39  USE moda_comprx
40  USE moda_comprs
41  USE moda_mstabs
42  USE moda_rdmtb
43  USE moda_nmikrp
44  USE moda_s01cm
45  USE moda_bitmaps
46  USE moda_nrv203
47  USE moda_rlccmn
48  USE moda_h4wlc
49 
50 C-----------------------------------------------------------------------
51 C-----------------------------------------------------------------------
52 
53 C MODA_USRINT arrays.
54 
55  DEALLOCATE( nval )
56  DEALLOCATE( inv )
57  DEALLOCATE( nrfelm )
58  DEALLOCATE( val )
59 
60 C MODA_USRBIT arrays.
61 
62  DEALLOCATE( nbit )
63  DEALLOCATE( mbit )
64 
65 C MODA_IVAL arrays.
66 
67  DEALLOCATE( ival )
68 
69 C MODA_MSGCWD arrays.
70 
71  DEALLOCATE( nmsg )
72  DEALLOCATE( nsub )
73  DEALLOCATE( msub )
74  DEALLOCATE( inode )
75  DEALLOCATE( idate )
76 
77 C MODA_STBFR arrays.
78 
79  DEALLOCATE( iolun )
80  DEALLOCATE( iomsg )
81 
82 C MODA_UFBCPL arrays.
83 
84  DEALLOCATE( luncpy )
85 
86 C MODA_SC3BFR arrays.
87 
88  DEALLOCATE( isc3 )
89  DEALLOCATE( tamnem )
90 
91 C MODA_UNPTYP arrays.
92 
93  DEALLOCATE( msgunp )
94 
95 C MODA_LUSHR arrays.
96 
97  DEALLOCATE( lus )
98 
99 C MODA_NULBFR arrays.
100 
101  DEALLOCATE( null )
102 
103 C MODA_STCODE arrays.
104 
105  DEALLOCATE( iscodes )
106 
107 C MODA_IDRDM arrays.
108 
109  DEALLOCATE( idrdm )
110 
111 C MODA_XTAB arrays.
112 
113  DEALLOCATE( xtab )
114 
115 C MODA_MSGLIM arrays.
116 
117  DEALLOCATE( msglim )
118 
119 C MODA_BITBUF arrays.
120 
121  DEALLOCATE( ibay )
122  DEALLOCATE( mbyt )
123  DEALLOCATE( mbay )
124 
125 C MODA_MGWA arrays.
126 
127  DEALLOCATE( mgwa )
128 
129 C MODA_MGWB arrays.
130 
131  DEALLOCATE( mgwb )
132 
133 C MODA_BUFRMG arrays.
134 
135  DEALLOCATE( msglen )
136  DEALLOCATE( msgtxt )
137 
138 C MODA_BUFRSR arrays.
139 
140  DEALLOCATE( jsr )
141  DEALLOCATE( jbay )
142 
143 C MODA_MSGMEM arrays.
144 
145  DEALLOCATE( msgp )
146  DEALLOCATE( msgs )
147  DEALLOCATE( mdx )
148  DEALLOCATE( ipdxm )
149  DEALLOCATE( ifdxts )
150  DEALLOCATE( icdxts )
151  DEALLOCATE( ipmsgs )
152 
153 C MODA_TABABD arrays.
154 
155  DEALLOCATE( ntba )
156  DEALLOCATE( ntbb )
157  DEALLOCATE( ntbd )
158  DEALLOCATE( mtab )
159  DEALLOCATE( idna )
160  DEALLOCATE( idnb )
161  DEALLOCATE( idnd )
162  DEALLOCATE( taba )
163  DEALLOCATE( tabb )
164  DEALLOCATE( tabd )
165 
166 C MODA_TABLES arrays.
167 
168  DEALLOCATE( tag )
169  DEALLOCATE( typ )
170  DEALLOCATE( knt )
171  DEALLOCATE( jump )
172  DEALLOCATE( link )
173  DEALLOCATE( jmpb )
174  DEALLOCATE( ibt )
175  DEALLOCATE( irf )
176  DEALLOCATE( isc )
177  DEALLOCATE( itp )
178  DEALLOCATE( vali )
179  DEALLOCATE( knti )
180  DEALLOCATE( iseq )
181  DEALLOCATE( jseq )
182 
183 C MODA_USRTMP arrays.
184 
185  DEALLOCATE( iutmp )
186  DEALLOCATE( vutmp )
187 
188 C MODA_IVTTMP arrays.
189 
190  DEALLOCATE( ttmp )
191  DEALLOCATE( itmp )
192  DEALLOCATE( vtmp )
193 
194 C MODA_COMPRX arrays.
195 
196  DEALLOCATE( kmin )
197  DEALLOCATE( kmax )
198  DEALLOCATE( kmis )
199  DEALLOCATE( kbit )
200  DEALLOCATE( ityp )
201  DEALLOCATE( iwid )
202  DEALLOCATE( cstr )
203 
204 C MODA_COMPRS arrays.
205 
206  DEALLOCATE( matx )
207  DEALLOCATE( catx )
208 
209 C MODA_MSTABS arrays.
210 
211  DEALLOCATE( ibfxyn )
212  DEALLOCATE( cbscl )
213  DEALLOCATE( cbsref )
214  DEALLOCATE( cbbw )
215  DEALLOCATE( cbunit )
216  DEALLOCATE( cbmnem )
217  DEALLOCATE( cbelem )
218  DEALLOCATE( idfxyn )
219  DEALLOCATE( cdseq )
220  DEALLOCATE( cdmnem )
221  DEALLOCATE( ndelem )
222  DEALLOCATE( idefxy )
223 
224 C MODA_RDMTB arrays.
225 
226  DEALLOCATE( iefxyn )
227  DEALLOCATE( cmdscb )
228  DEALLOCATE( cmdscd )
229  DEALLOCATE( ceelem )
230 
231 C MODA_NMIKRP arrays.
232 
233  DEALLOCATE( nem )
234  DEALLOCATE( irp )
235  DEALLOCATE( krp )
236 
237 C MODA_S01CM arrays.
238 
239  DEALLOCATE( ivmnem )
240  DEALLOCATE( cmnem )
241 
242 C MODA_BITMAPS arrays.
243 
244  DEALLOCATE( inodtamc )
245  DEALLOCATE( ntco )
246  DEALLOCATE( ctco )
247  DEALLOCATE( inodtco )
248  DEALLOCATE( nbtmse )
249  DEALLOCATE( istbtm )
250  DEALLOCATE( iszbtm )
251  DEALLOCATE( ibtmse )
252 
253 C MODA_NRV203 arrays.
254 
255  DEALLOCATE( tagnrv )
256  DEALLOCATE( inodnrv )
257  DEALLOCATE( nrv )
258  DEALLOCATE( isnrv )
259  DEALLOCATE( ienrv )
260 
261 C MODA_RLCCMN arrays.
262 
263  DEALLOCATE( irnch )
264  DEALLOCATE( irbit )
265  DEALLOCATE( crtag )
266 
267 C MODA_H4WLC arrays.
268 
269  DEALLOCATE( luh4wlc )
270  DEALLOCATE( sth4wlc )
271  DEALLOCATE( chh4wlc )
272 
273 C C language arrays.
274 
275  CALL ardllocc_c
276 
277  RETURN
278  END
subroutine ardllocf
This subroutine frees any memory that was dynamically allocated during a previous call to subroutine ...
Definition: ardllocf.f:12
Wrap C NCEPLIBS-bufr functions so they can be called from within the Fortran part of the library.
Definition: bufrlib.F90:11
This module contains array and variable declarations used to store BUFR messages internally for multi...
integer, dimension(:), allocatable ibay
Current data subset.
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 array and variable declarations used to store bitmaps internally within a data s...
integer, dimension(:), allocatable iszbtm
Size of bitmap (total number of entries, whether "set" (set to a value of 0) or not).
integer, dimension(:,:), allocatable inodtco
Entries within jump/link table which contain Table C operators.
integer, dimension(:), allocatable istbtm
Ordinal position in data subset definition corresponding to the first entry of the bitmap.
integer, dimension(:), allocatable inodtamc
Entries within jump/link table which contain Table A mnemonics.
integer, dimension(:,:), allocatable ibtmse
Ordinal positions in bitmap of bits that were "set" (set to a value of 0); these ordinal positions ca...
integer, dimension(:), allocatable nbtmse
Number of "set" entries (set to a value of 0) in the bitmap.
character *6, dimension(:,:), allocatable ctco
Table C operators corresponding to inodtco.
integer, dimension(:), allocatable ntco
Number of Table C operators (with an XX value of 21 or greater) within the data subset definition of ...
This module contains arrays used to store, for each output I/O stream, a copy of the BUFR message tha...
integer, dimension(:), allocatable msglen
Length (in integers) of BUFR message most recently written to each output I/O stream.
integer, dimension(:,:), allocatable msgtxt
BUFR message most recently written to each output I/O stream.
This module contains arrays and variables needed to store the current position within a BUFR file.
integer, dimension(:), allocatable jsr
Indicator of stack status when entering subroutine rewnbf().
integer, dimension(:), allocatable jbay
BUFR message.
This module contains arrays and variable declarations for the storage of data values needed when writ...
integer(8), dimension(:,:), allocatable matx
Non-character data values for all data subsets in message.
character *(:), dimension(:,:), allocatable catx
Character data values for all data subsets in message.
This module contains arrays and variable declarations for the storage of data values needed when writ...
character *(:), dimension(:), allocatable cstr
Character data value, if corresponding ityp value is set to 3.
integer(8), dimension(:), allocatable kmax
Maximum of each data value across all data subsets in message.
integer, dimension(:), allocatable ityp
Type of each data value:
integer, dimension(:), allocatable iwid
Bit width of underlying data descriptor as defined within Table B for each data value.
integer(8), dimension(:), allocatable kmin
Minimum of each data value across all data subsets in message.
integer, dimension(:), allocatable kbit
Number of bits needed to hold the increments for this data value within each data subset of the messa...
logical, dimension(:), allocatable kmis
"Missing" values flag.
This module contains array and variable declarations needed to store long character strings (greater ...
character *14, dimension(:), allocatable sth4wlc
Table B mnemonics associated with long character strings.
integer, dimension(:), allocatable luh4wlc
I/O stream index into internal arrays for associated output file.
character *120, dimension(:), allocatable chh4wlc
Long character strings.
This module contains a declaration for an array used by subroutine readerme() to read in a new DX dic...
integer, dimension(:), allocatable idrdm
DX BUFR tables message count for each I/O internal stream index.
This module contains a declaration for an array used to pack or unpack all of the values of a BUFR da...
integer(8), dimension(:), allocatable ival
BUFR data subset values.
This module contains arrays which provide working space in several subprograms (usrtpl() and ufbcup()...
character *10, dimension(:), allocatable ttmp
tag array elements for new sections of a growing subset buffer.
real *8, dimension(:), allocatable vtmp
val array elements for new sections of a growing subset buffer.
integer, dimension(:), allocatable itmp
inv array elements for new sections of a growing subset buffer.
This module contains a declaration for an array used by subroutine makestab() to keep track of which ...
integer, dimension(:), allocatable lus
Tracking index for each I/O internal stream index.
This module contains a declaration for an array used by various subroutines and functions to hold a t...
integer, dimension(:), allocatable mgwa
Temporary working copy of BUFR message.
This module contains a declaration for an array used by various subroutines and functions to hold a t...
integer, dimension(:), allocatable mgwb
Temporary working copy of BUFR message.
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.
integer, dimension(:), allocatable idate
Section 1 date-time of message.
integer, dimension(:), allocatable nmsg
Current message pointer within logical unit.
integer, dimension(:), allocatable msub
Total number of data subsets in message.
integer, dimension(:), allocatable nsub
Current subset pointer within message.
This module contains a declaration for an array used to keep track of which logical units should not ...
integer, dimension(:), allocatable msglim
Tracking index for each I/O stream index.
This module contains array and variable declarations used to store the contents of one or more BUFR f...
integer, dimension(:), allocatable msgp
Pointers to the beginning of each message within msgs (up to a maximum of MAXMSG, and where array ele...
integer, dimension(:), allocatable ipmsgs
Pointers to first message within msgs for which each DX BUFR table applies.
integer, dimension(:), allocatable msgs
BUFR messages read from one or more BUFR files.
integer, dimension(:), allocatable icdxts
Number of consecutive messages within mdx which constitute each DX BUFR table, beginning with the cor...
integer, dimension(:), allocatable ifdxts
Pointers to the beginning of each DX BUFR table within mdx.
integer, dimension(:), allocatable mdx
DX BUFR table messages read from one or more BUFR files, for use in decoding the messages in msgs.
integer, dimension(:), allocatable ipdxm
Pointers to the beginning of each message within mdx.
This module contains array and variable declarations used to store master Table B and Table D entries...
integer, dimension(:), allocatable idfxyn
Bit-wise representations of FXY numbers for master Table D.
character, dimension(:,:), allocatable cbunit
Units corresponding to ibfxyn.
character, dimension(:,:), allocatable cbbw
Bit widths corresponding to ibfxyn.
character, dimension(:,:), allocatable cdseq
Sequence names corresponding to idfxyn.
character, dimension(:,:), allocatable cbmnem
Mnemonics corresponding to ibfxyn.
integer, dimension(:), allocatable ndelem
Numbers of child descriptors corresponding to idfxyn.
character, dimension(:,:), allocatable cbelem
Element names corresponding to ibfxyn.
character, dimension(:,:), allocatable cbscl
Scale factors corresponding to ibfxyn.
character, dimension(:,:), allocatable cdmnem
Mnemonics corresponding to idfxyn.
character, dimension(:,:), allocatable cbsref
Reference values corresponding to ibfxyn.
integer, dimension(:), allocatable idefxy
Bit-wise representations of child descriptors corresponding to idfxyn.
integer, dimension(:), allocatable ibfxyn
Bit-wise representations of FXY numbers for master Table B.
This module contains declarations for arrays used by various subroutines to hold information about Ta...
integer, dimension(:,:), allocatable krp
Replication counts corresponding to nem:
integer, dimension(:,:), allocatable irp
Replication indicators corresponding to nem:
character *8, dimension(:,:), allocatable nem
Child mnemonics within Table D sequences.
This module contains array and variable declarations for use with any 2-03-YYY (change reference valu...
integer, dimension(:), allocatable ienrv
End of entry range in jump/link table, within which the corresponding new reference value in nrv will...
character *8, dimension(:), allocatable tagnrv
Table B mnemonic to which the corresponding new reference value in nrv applies.
integer, dimension(:), allocatable isnrv
Start of entry range in jump/link table, within which the corresponding new reference value in nrv wi...
integer *8, dimension(:), allocatable nrv
New reference values corresponding to inodnrv.
integer, dimension(:), allocatable inodnrv
Entries within jump/link table which contain new reference values.
This module contains an array declaration used to store a switch for each internal I/O stream index,...
integer, dimension(:), allocatable null
Output switch for each internal I/O stream index:
This module contains array and variable declarations used to store master Table B and Table D entries...
character *120, dimension(:,:), allocatable ceelem
Element names corresponding to iefxyn.
character *4, dimension(:), allocatable cmdscb
Descriptor codes for Table B elements.
integer, dimension(:,:), allocatable iefxyn
Bit-wise representations of child descriptors of Table D sequences.
character *4, dimension(:), allocatable cmdscd
Descriptor codes for Table D sequences.
This module contains array and variable declarations needed to store information about long character...
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 array and variable declarations used to store custom values for certain mnemonic...
integer, dimension(:), allocatable ivmnem
Custom values for use within Sections 0 and 1 of all future output BUFR messages written to all Fortr...
character *8, dimension(:), allocatable cmnem
Section 0 and 1 mnemonics corresponding to ivmnem.
This module contains an array declaration used to store a switch for each internal I/O stream index,...
character *8, dimension(:), allocatable tamnem
Table A mnemonic most recently read from each internal I/O stream index, if isc3 = 1 for that stream.
integer, dimension(:), allocatable isc3
Section 3 switch for each internal I/O stream index:
This module contains array declarations used to store file and message status indicators for all logi...
integer, dimension(:), allocatable iolun
File status indicators.
integer, dimension(:), allocatable iomsg
Message status indicator corresponding to iolun, denoting whether a BUFR message is currently open wi...
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 DX BUFR tables internally for mult...
integer, dimension(:), allocatable ntba
Number of Table A entries for each internal I/O stream (up to a maximum of MAXTBA,...
character *600, dimension(:,:), allocatable tabd
Table D entries for each internal I/O stream.
character *128, dimension(:,:), allocatable taba
Table A entries for each internal I/O stream.
integer, dimension(:,:), allocatable mtab
Entries within jump/link table corresponding to taba.
integer, dimension(:,:,:), allocatable idna
Message types (in array element 1) and subtypes (in array element 2) corresponding to taba.
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.
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.
This module contains array and variable declarations used to store the internal jump/link table.
integer, dimension(:), allocatable jseq
Temporary storage used in expanding sequences.
integer, dimension(:), allocatable irf
Reference values corresponding to tag and typ:
integer, dimension(:,:), allocatable iseq
Temporary storage used in expanding sequences.
integer, dimension(:), allocatable isc
Scale factors corresponding to tag and typ:
integer, dimension(:), allocatable ibt
Bit widths corresponding to tag and typ:
integer, dimension(:), allocatable knt
Temporary storage used in calculating delayed replication counts.
real *8, dimension(:), allocatable vali
Initialized data values corresponding to typ:
character *3, dimension(:), allocatable typ
Type indicators corresponding to tag:
integer, dimension(:), allocatable jmpb
Jump backward indices corresponding to tag and typ:
character *10, dimension(:), allocatable tag
Mnemonics in the jump/link table.
integer, dimension(:), allocatable jump
Jump forward indices corresponding to tag and typ:
integer, dimension(:), allocatable itp
Integer type values corresponding to typ:
integer, dimension(:), allocatable link
Link indices corresponding to tag, typ and jmpb:
integer, dimension(:), allocatable knti
Initialized replication counts corresponding to typ and jump:
This module contains an array declaration used to store, for each I/O stream index,...
integer, dimension(:), allocatable luncpy
Logical unit numbers used to copy long character strings between BUFR data subsets.
This module contains an array declaration used to store, for each I/O stream index from which a BUFR ...
integer, dimension(:), allocatable msgunp
Flag indicating how to unpack data subsets from BUFR message:
This module contains array declarations for internal storage of pointers to BUFR data subset values.
integer, dimension(:), allocatable nbit
Length (in bits) of each packed data value in data subset.
integer, dimension(:), allocatable mbit
Pointer in data subset to first bit of each packed data value.
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 contains arrays used in subroutine rcstpl() to store subset segments that are being copie...
integer, dimension(:,:), allocatable iutmp
inv array elements for new sections of a growing subset buffer.
real *8, dimension(:,:), allocatable vutmp
val array elements for new sections of a growing subset buffer.
This module contains an array declaration used to track, for each I/O stream index,...
logical, dimension(:), allocatable xtab
Tracking index for each internal I/O stream index.