NCEPLIBS-bufr  12.0.0
upc.f
Go to the documentation of this file.
1 C> @file
2 C> @brief Decode a character string from an integer array.
3 C>
4 C> @author J. Woollen @date 1994-01-06
5 
6 C> Decode a character string from an integer array.
7 C>
8 C> This subroutine decodes a character string from within a specified
9 C> number of bytes of an integer array, starting at the bit immediately
10 C> after a specified bit within the array.
11 C>
12 C> @remarks
13 C> - This subroutine is the logical inverse of subroutine pkc().
14 C> - On input, there is no requirement that IBIT must point to the first
15 C> bit of a byte within IBAY. In other words, the NCHR characters to
16 C> be decoded do not necessarily need to be aligned on byte boundaries
17 C> within IBAY.
18 C>
19 C> @param[out] CHR - character*(*): Decoded string.
20 C> @param[in] NCHR - integer: Number of bytes of IBAY from within
21 C> which to decode CHR (i.e. the number of characters in CHR).
22 C> @param[in] IBAY - integer(*): Array from which to decode CHR.
23 C> @param[inout] IBIT - integer: Bit pointer within IBAY
24 C> - On input, IBIT points to the bit within IBAY after which to begin
25 C> decoding CHR.
26 C> - On output, IBIT points to the last bit of IBAY which was decoded.
27 C> @param[in] CNVNULL - logical: .true. if null characters in IBAY
28 C> should be converted to blanks within CHR; .false. otherwise
29 C>
30 C> @author J. Woollen @date 1994-01-06
31  SUBROUTINE upc(CHR,NCHR,IBAY,IBIT,CNVNULL)
32 
33  COMMON /hrdwrd/ nbytw,nbitw,iord(8)
34 
35  CHARACTER*(*) CHR
36  CHARACTER*8 CVAL
37  dimension ibay(*),ival(2)
38  equivalence(cval,ival)
39 
40  LOGICAL CNVNULL
41 
42 C----------------------------------------------------------------------
43 C----------------------------------------------------------------------
44 
45  lb = iord(nbytw)
46  cval = ' '
47 
48  numchr = min(nchr,len(chr))
49  DO i=1,numchr
50  CALL upb(ival(1),8,ibay,ibit)
51  IF((ival(1).EQ.0).AND.(cnvnull)) THEN
52  chr(i:i) = ' '
53  ELSE
54  chr(i:i) = cval(lb:lb)
55  ENDIF
56  ENDDO
57 
58  RETURN
59  END
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