LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
slartg.f90
Go to the documentation of this file.
1
2!
3! =========== DOCUMENTATION ===========
4!
5! Online html documentation available at
6! http://www.netlib.org/lapack/explore-html/
7!
8! Definition:
9! ===========
10!
11! SUBROUTINE SLARTG( F, G, C, S, R )
12!
13! .. Scalar Arguments ..
14! REAL(wp) C, F, G, R, S
15! ..
16!
18! =============
50!
51! Arguments:
52! ==========
53!
83!
84! Authors:
85! ========
86!
88!
90!
92!
94! ==================
97!
99! =====================
109!
110subroutine slartg( f, g, c, s, r )
111 use la_constants, &
112 only: wp=>sp, zero=>szero, half=>shalf, one=>sone, &
113 safmin=>ssafmin, safmax=>ssafmax
114!
115! -- LAPACK auxiliary routine --
116! -- LAPACK is a software package provided by Univ. of Tennessee, --
117! -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
118! February 2021
119!
120! .. Scalar Arguments ..
121 real(wp) :: c, f, g, r, s
122! ..
123! .. Local Scalars ..
124 real(wp) :: d, f1, fs, g1, gs, u, rtmin, rtmax
125! ..
126! .. Intrinsic Functions ..
127 intrinsic :: abs, sign, sqrt
128! ..
129! .. Constants ..
130 rtmin = sqrt( safmin )
131 rtmax = sqrt( safmax/2 )
132! ..
133! .. Executable Statements ..
134!
135 f1 = abs( f )
136 g1 = abs( g )
137 if( g == zero ) then
138 c = one
139 s = zero
140 r = f
141 else if( f == zero ) then
142 c = zero
143 s = sign( one, g )
144 r = g1
145 else if( f1 > rtmin .and. f1 < rtmax .and. &
146 g1 > rtmin .and. g1 < rtmax ) then
147 d = sqrt( f*f + g*g )
148 c = f1 / d
149 r = sign( d, f )
150 s = g / r
151 else
152 u = min( safmax, max( safmin, f1, g1 ) )
153 fs = f / u
154 gs = g / u
155 d = sqrt( fs*fs + gs*gs )
156 c = abs( fs ) / d
157 r = sign( d, f )
158 s = gs / r
159 r = r*u
160 end if
161 return
162end subroutine
subroutine slartg(f, g, c, s, r)
SLARTG generates a plane rotation with real cosine and real sine.
Definition slartg.f90:111
real(sp), parameter sone
real(sp), parameter shalf
integer, parameter sp
real(sp), parameter ssafmin
real(sp), parameter ssafmax
real(sp), parameter szero
LA_CONSTANTS is a module for the scaling constants for the compiled Fortran single and double precisi...