NCEPLIBS-bufr  12.0.0
ufbcup.f
Go to the documentation of this file.
1 C> @file
2 C> @brief Copy unique elements of a data subset.
3 C>
4 C> @author Woollen @date 1994-01-06
5 
6 C> Copy unique elements of a data subset.
7 C>
8 C> This subroutine makes one copy of each unique element in an input
9 C> subset buffer into the identical mnemonic slot in the output subset
10 C> buffer.
11 C>
12 C> Before this subroutine is called:
13 C> - The input file must be opened for input with openbf().
14 C> - a message must be read, as with readmg().
15 C> - a subset of data loaded into memory, as with readsb().
16 C> - the output file must be opened for output with openbf().
17 C> - a message must be created in the output file, as with openmg().
18 C>
19 C> After this subroutine is called, writsb() must be called on the output
20 C> file to write the subset to file.
21 C>
22 C> @param[in] LUBIN - integer: fortran logical unit number for input BUFR
23 C> file.
24 C> @param[in] LUBOT - integer: fortran logical unit number for output
25 C> BUFR file.
26 C>
27 C> @author Woollen @date 1994-01-06
28  RECURSIVE SUBROUTINE ufbcup(LUBIN,LUBOT)
29 
30  USE modv_im8b
31 
32  USE moda_usrint
33  USE moda_msgcwd
34  USE moda_tables
35  USE moda_ivttmp
36 
37  CHARACTER*10 tago
38 
39 C----------------------------------------------------------------------
40 C----------------------------------------------------------------------
41 
42 C CHECK FOR I8 INTEGERS
43 C ---------------------
44 
45  IF(im8b) THEN
46  im8b=.false.
47 
48  CALL x84(lubin,my_lubin,1)
49  CALL x84(lubot,my_lubot,1)
50  CALL ufbcup(my_lubin,my_lubot)
51 
52  im8b=.true.
53  RETURN
54  ENDIF
55 
56 C CHECK THE FILE STATUSES AND I-NODE
57 C ----------------------------------
58 
59  CALL status(lubin,lui,il,im)
60  IF(il.EQ.0) GOTO 900
61  IF(il.GT.0) GOTO 901
62  IF(im.EQ.0) GOTO 902
63  IF(inode(lui).NE.inv(1,lui)) GOTO 903
64 
65  CALL status(lubot,luo,il,im)
66  IF(il.EQ.0) GOTO 904
67  IF(il.LT.0) GOTO 905
68  IF(im.EQ.0) GOTO 906
69 
70 C MAKE A LIST OF UNIQUE TAGS IN INPUT BUFFER
71 C ------------------------------------------
72 
73  ntag = 0
74 
75  DO 5 ni=1,nval(lui)
76  nin = inv(ni,lui)
77  IF(itp(nin).GE.2) THEN
78  DO nv=1,ntag
79  IF(ttmp(nv).EQ.tag(nin)) GOTO 5
80  ENDDO
81  ntag = ntag+1
82  itmp(ntag) = ni
83  ttmp(ntag) = tag(nin)
84  ENDIF
85 5 ENDDO
86 
87  IF(ntag.EQ.0) GOTO 907
88 
89 C GIVEN A LIST MAKE ONE COPY OF COMMON ELEMENTS TO OUTPUT BUFFER
90 C --------------------------------------------------------------
91 
92  DO 10 nv=1,ntag
93  ni = itmp(nv)
94  DO no=1,nval(luo)
95  tago = tag(inv(no,luo))
96  IF(ttmp(nv).EQ.tago) THEN
97  val(no,luo) = val(ni,lui)
98  GOTO 10
99  ENDIF
100  ENDDO
101 10 ENDDO
102 
103 C EXITS
104 C -----
105 
106  RETURN
107 900 CALL bort('BUFRLIB: UFBCUP - INPUT BUFR FILE IS CLOSED, IT '//
108  . 'MUST BE OPEN FOR INPUT')
109 901 CALL bort('BUFRLIB: UFBCUP - INPUT BUFR FILE IS OPEN FOR '//
110  . 'OUTPUT, IT MUST BE OPEN FOR INPUT')
111 902 CALL bort('BUFRLIB: UFBCUP - A MESSAGE MUST BE OPEN IN INPUT '//
112  . 'BUFR FILE, NONE ARE')
113 903 CALL bort('BUFRLIB: UFBCUP - LOCATION OF INTERNAL TABLE FOR '//
114  . 'INPUT BUFR FILE DOES NOT AGREE WITH EXPECTED LOCATION IN '//
115  . 'INTERNAL SUBSET ARRAY')
116 904 CALL bort('BUFRLIB: UFBCUP - OUTPUT BUFR FILE IS CLOSED, IT '//
117  . 'MUST BE OPEN FOR OUTPUT')
118 905 CALL bort('BUFRLIB: UFBCUP - OUTPUT BUFR FILE IS OPEN FOR '//
119  . 'INPUT, IT MUST BE OPEN FOR OUTPUT')
120 906 CALL bort('BUFRLIB: UFBCUP - A MESSAGE MUST BE OPEN IN OUTPUT '//
121  . 'BUFR FILE, NONE ARE')
122 907 CALL bort('BUFRLIB: UFBCUP - THERE ARE NO ELEMENTS (TAGS) IN '//
123  . 'INPUT SUBSET BUFFER')
124  END
subroutine bort(STR)
Log one error message and abort application program.
Definition: bort.f:18
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.
integer, dimension(:), allocatable itmp
inv array elements for new sections of a growing subset buffer.
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.
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.
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...
This module declares and initializes the IM8B variable.
logical, public im8b
Status indicator to keep track of whether all future calls to BUFRLIB subroutines and functions from ...
recursive subroutine status(LUNIT, LUN, IL, IM)
Check whether a specified Fortran logical unit number is currently connected to the NCEPLIBS-bufr sof...
Definition: status.f:36
recursive subroutine ufbcup(LUBIN, LUBOT)
Copy unique elements of a data subset.
Definition: ufbcup.f:29
subroutine x84(IIN8, IOUT4, NVAL)
Encode one or more 8-byte integer values as 4-byte integer values.
Definition: x84.F:19