NCEPLIBS-bufr  12.0.0
nxtwin.f
Go to the documentation of this file.
1 C> @file
2 C> @brief Computes the start and end indices of the next window.
3 C>
4 C> @author J. Woollen @date 1994-01-06
5 
6 C> Given indices within the internal jump/link table which
7 C> point to the start and end of an "rpc" window (which is an iteration of
8 C> an 8-bit or 16-bit delayed replication sequence), this subroutine
9 C> computes the start and end indices of the next window.
10 C>
11 C> @note See getwin() for an explanation of "windows" within the
12 C> context of a bufr data subset.
13 C>
14 C> @param[in] LUN - integer: i/o stream index into internal memory arrays.
15 C> @param[inout] IWIN - integer:
16 C> - on input, contains starting index of current window iteration.
17 C> - on output, contains starting index of next window iteration.
18 C> @param[inout] JWIN - integer:
19 C> - on input, contains ending index of current window iteration.
20 C> - on output, contains ending index of next window iteration.
21 C>
22 C> @author J. Woollen @date 1994-01-06
23  SUBROUTINE nxtwin(LUN,IWIN,JWIN)
24 
25  USE moda_usrint
26 
27  CHARACTER*128 BORT_STR
28 
29 C----------------------------------------------------------------------
30 C----------------------------------------------------------------------
31 
32  IF(jwin.EQ.nval(lun)) THEN
33  iwin = 0
34  GOTO 100
35  ENDIF
36 
37 C FIND THE NEXT SEQUENTIAL WINDOW
38 C -------------------------------
39 
40  node = inv(iwin,lun)
41  IF(lstjpb(node,lun,'RPC').NE.node) GOTO 900
42  IF(val(jwin,lun).EQ.0) THEN
43  iwin = 0
44  ELSE
45  iwin = jwin
46  jwin = iwin+nint(val(iwin,lun))
47  ENDIF
48 
49 C EXITS
50 C -----
51 
52 100 RETURN
53 900 WRITE(bort_str,'("BUFRLIB: NXTWIN - LSTJPB FOR NODE",I6," '//
54  . '(LSTJPB=",I5,") DOES NOT EQUAL VALUE OF NODE, NOT RPC (IWIN '//
55  . '=",I8,")")') node,lstjpb(node,lun,'RPC'),iwin
56  CALL bort(bort_str)
57  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 nxtwin(LUN, IWIN, JWIN)
Given indices within the internal jump/link table which point to the start and end of an "rpc" window...
Definition: nxtwin.f:24