NCEPLIBS-bufr  12.0.0
ufbcpy.f
Go to the documentation of this file.
1 C> @file
2 C> @brief Copy a BUFR data subset.
3 C>
4 C> @author J. Woollen @date 1994-01-06
5 
6 C> Copy a BUFR data subset.
7 C>
8 C> This subroutine copies a BUFR data subset from one Fortran logical
9 C> unit to another.
10 C>
11 C> It is similar to subroutine copysb(), except that here a
12 C> BUFR data subset should have already been read into internal arrays
13 C> for logical unit LUBIN via a previous call to one of the
14 C> [subset-reading subroutines](@ref hierarchy), whereas copysb()
15 C> only requires that a BUFR message should have already been read
16 C> into internal arrays via a previous call to one of the
17 C> [message-reading subroutines](@ref hierarchy).
18 C>
19 C> For logical unit LUBOT, a BUFR message should already be open
20 C> for output within internal arrays via a previous call to one of
21 C> the [message-writing subroutines](@ref hierarchy).
22 C>
23 C> The [DX BUFR Table information](@ref dfbftab) associated with
24 C> each of the logical units LUBIN and LUBOT must contain identical
25 C> definitions for the data subset to be copied.
26 C>
27 C> @param[in] LUBIN - integer: Fortran logical unit number for
28 C> source BUFR file.
29 C> @param[in] LUBOT - integer: Fortran logical unit number for
30 C> target BUFR file.
31 C>
32 C> @author J. Woollen @date 1994-01-06
33  RECURSIVE SUBROUTINE ufbcpy(LUBIN,LUBOT)
34 
35  USE modv_im8b
36 
37  USE moda_usrint
38  USE moda_msgcwd
39  USE moda_ufbcpl
40  USE moda_tables
41 
42 C----------------------------------------------------------------------
43 C----------------------------------------------------------------------
44 
45 C CHECK FOR I8 INTEGERS
46 C ---------------------
47 
48  IF(im8b) THEN
49  im8b=.false.
50 
51  CALL x84(lubin,my_lubin,1)
52  CALL x84(lubot,my_lubot,1)
53  CALL ufbcpy(my_lubin,my_lubot)
54 
55  im8b=.true.
56  RETURN
57  ENDIF
58 
59 C CHECK THE FILE STATUSES AND I-NODE
60 C ----------------------------------
61 
62  CALL status(lubin,lui,il,im)
63  IF(il.EQ.0) GOTO 900
64  IF(il.GT.0) GOTO 901
65  IF(im.EQ.0) GOTO 902
66  IF(inode(lui).NE.inv(1,lui)) GOTO 903
67 
68  CALL status(lubot,luo,il,im)
69  IF(il.EQ.0) GOTO 904
70  IF(il.LT.0) GOTO 905
71  IF(im.EQ.0) GOTO 906
72 
73  IF(inode(lui).NE.inode(luo)) THEN
74  IF( (tag(inode(lui)).NE.tag(inode(luo))) .OR.
75  . (iok2cpy(lui,luo).NE.1) ) GOTO 907
76  ENDIF
77 
78 C EVERYTHING OKAY COPY USER ARRAY FROM LUI TO LUO
79 C -----------------------------------------------
80 
81  nval(luo) = nval(lui)
82 
83  DO n=1,nval(lui)
84  inv(n,luo) = inv(n,lui)
85  nrfelm(n,luo) = nrfelm(n,lui)
86  val(n,luo) = val(n,lui)
87  ENDDO
88 
89  luncpy(luo)=lubin
90 
91 C EXITS
92 C -----
93 
94  RETURN
95 900 CALL bort('BUFRLIB: UFBCPY - INPUT BUFR FILE IS CLOSED, IT MUST'//
96  . ' BE OPEN FOR INPUT')
97 901 CALL bort('BUFRLIB: UFBCPY - INPUT BUFR FILE IS OPEN FOR '//
98  . 'OUTPUT, IT MUST BE OPEN FOR INPUT')
99 902 CALL bort('BUFRLIB: UFBCPY - A MESSAGE MUST BE OPEN IN INPUT '//
100  . 'BUFR FILE, NONE ARE')
101 903 CALL bort('BUFRLIB: UFBCPY - LOCATION OF INTERNAL TABLE FOR '//
102  . 'INPUT BUFR FILE DOES NOT AGREE WITH EXPECTED LOCATION IN '//
103  . 'INTERNAL SUBSET ARRAY')
104 904 CALL bort('BUFRLIB: UFBCPY - OUTPUT BUFR FILE IS CLOSED, IT '//
105  . 'MUST BE OPEN FOR OUTPUT')
106 905 CALL bort('BUFRLIB: UFBCPY - OUTPUT BUFR FILE IS OPEN FOR '//
107  . 'INPUT, IT MUST BE OPEN FOR OUTPUT')
108 906 CALL bort('BUFRLIB: UFBCPY - A MESSAGE MUST BE OPEN IN OUTPUT '//
109  . 'BUFR FILE, NONE ARE')
110 907 CALL bort('BUFRLIB: UFBCPY - INPUT AND OUTPUT BUFR FILES MUST '//
111  . 'HAVE THE SAME INTERNAL TABLES, THEY ARE DIFFERENT HERE')
112  END
subroutine bort(STR)
Log one error message and abort application program.
Definition: bort.f:18
integer function iok2cpy(LUI, LUO)
This function determines whether a BUFR message, or a data subset from within a BUFR message,...
Definition: iok2cpy.f:28
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.
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 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 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 ufbcpy(LUBIN, LUBOT)
Copy a BUFR data subset.
Definition: ufbcpy.f:34
subroutine x84(IIN8, IOUT4, NVAL)
Encode one or more 8-byte integer values as 4-byte integer values.
Definition: x84.F:19