HP MLIB User's Guide Vol. 1 7th Ed.
Chapter 2 Basic Vector Operations 113
Generate linear ramp SRAMP/DRAMP/IRAMP
Indexing Conventions” in the introduction to this
chapter.
Output x Array of length lenx = (n−1)×|incx|+1 containing the
n-vector x. If n ≤ 0, then x is not referenced. Otherwise,
the specified linear ramp function replaces the input.
Notes The result is unspecified if incx = 0.
Fortran
Equivalent
SUBROUTINE SRAMP (N, X1,DX, X,INCX)
REAL*4 X1,DX,X(*)
IF ( N .LE. 0 ) RETURN
IX = 1
INCXA = ABS ( INCX )
DO 10 I = 1, N
X(IX) = X1 + (I-1) * DX
IX = IX + INCXA
10 CONTINUE
RETURN
END
Example Generate the linear ramp x with initial value 0 and slope π/9, where x is a
vector 10 elements long stored in a one-dimensional array X of dimension 20.
INTEGER*4 N,INCX
REAL*8 A,H,PI,X(20)
PARAMETER ( PI = 3.14159265358979323846D0 )
N = 10
INCX = 1
A = 0.0D0
H = PI / (N-1)
CALL DRAMP (N,A,H,X,INCX)