NCEPLIBS-bufr  12.0.0
newwin.f
Go to the documentation of this file.
1 C> @file
2 C> @brief Computes the ending index of the window.
3 C>
4 C> @author J. Woollen @date 1994-01-06
5 
6 C> Given an index within the internal jump/link table which
7 C> points to the start of an "rpc" window (which is the iteration of an 8-bit
8 C> or 16-bit delayed replication sequence), this subroutine computes
9 C> the ending index of the window. Alternatively, if the given index
10 C> points to the start of a "sub" window (which is the first node of a
11 C> subset), then the subroutine returns the index of the last node.
12 C>
13 C> @note See the docblock in bufr archive library subroutine getwin() for an
14 C> explanation of "windows" within the context of a bufr data subset.
15 C>
16 C> @param[in] LUN - integer: i/o stream index into internal memory arrays.
17 C> @param[in] IWIN - integer: starting index of window iteration.
18 C> @param[out] JWIN - integer: ending index of window iteration.
19 C>
20 C> @author J. Woollen @date 1994-01-06
21  SUBROUTINE newwin(LUN,IWIN,JWIN)
22 
23  USE moda_usrint
24 
25  CHARACTER*128 BORT_STR
26 
27 C----------------------------------------------------------------------
28 C----------------------------------------------------------------------
29 
30  IF(iwin.EQ.1) THEN
31 
32 C This is a "SUB" (subset) node, so return JWIN as pointing to
33 C the last value of the entire subset.
34 
35  jwin = nval(lun)
36  GOTO 100
37  ENDIF
38 
39 C Confirm that IWIN points to an RPC node and then compute JWIN.
40 
41  node = inv(iwin,lun)
42  IF(lstjpb(node,lun,'RPC').NE.node) GOTO 900
43  jwin = iwin+nint(val(iwin,lun))
44 
45 C EXITS
46 C -----
47 
48 100 RETURN
49 900 WRITE(bort_str,'("BUFRLIB: NEWWIN - LSTJPB FOR NODE",I6,'//
50  . '" (LSTJPB=",I5,") DOES NOT EQUAL VALUE OF NODE, NOT RPC '//
51  . '(IWIN =",I8,")")') node,lstjpb(node,lun,'RPC'),iwin
52  CALL bort(bort_str)
53  END
subroutine bort(STR)
Log one error message and abort application program.
Definition: bort.f:18
function lstjpb(NODE, LUN, JBTYP)
This function searches backwards, beginning from a given node within the jump/link table,...
Definition: lstjpb.f:30
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...
subroutine newwin(LUN, IWIN, JWIN)
Given an index within the internal jump/link table which points to the start of an "rpc" window (whic...
Definition: newwin.f:22