OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
slartg.f90
Go to the documentation of this file.
1!> \brief \b SLARTG generates a plane rotation with real cosine and real sine.
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!
17!> \par Purpose:
18! =============
19!>
20!> \verbatim
21!>
22!> SLARTG generates a plane rotation so that
23!>
24!> [ C S ] . [ F ] = [ R ]
25!> [ -S C ] [ G ] [ 0 ]
26!>
27!> where C**2 + S**2 = 1.
28!>
29!> The mathematical formulas used for C and S are
30!> R = sign(F) * sqrt(F**2 + G**2)
31!> C = F / R
32!> S = G / R
33!> Hence C >= 0. The algorithm used to compute these quantities
34!> incorporates scaling to avoid overflow or underflow in computing the
35!> square root of the sum of squares.
36!>
37!> This version is discontinuous in R at F = 0 but it returns the same
38!> C and S as SLARTG for complex inputs (F,0) and (G,0).
39!>
40!> This is a more accurate version of the BLAS1 routine SROTG,
41!> with the following other differences:
42!> F and G are unchanged on return.
43!> If G=0, then C=1 and S=0.
44!> If F=0 and (G .ne. 0), then C=0 and S=sign(1,G) without doing any
45!> floating point operations (saves work in SBDSQR when
46!> there are zeros on the diagonal).
47!>
48!> If F exceeds G in magnitude, C will be positive.
49!>
50!> Below, wp=>sp stands for single precision from LA_CONSTANTS module.
51!> \endverbatim
52!
53! Arguments:
54! ==========
55!
56!> \param[in] F
57!> \verbatim
58!> F is REAL(wp)
59!> The first component of vector to be rotated.
60!> \endverbatim
61!>
62!> \param[in] G
63!> \verbatim
64!> G is REAL(wp)
65!> The second component of vector to be rotated.
66!> \endverbatim
67!>
68!> \param[out] C
69!> \verbatim
70!> C is REAL(wp)
71!> The cosine of the rotation.
72!> \endverbatim
73!>
74!> \param[out] S
75!> \verbatim
76!> S is REAL(wp)
77!> The sine of the rotation.
78!> \endverbatim
79!>
80!> \param[out] R
81!> \verbatim
82!> R is REAL(wp)
83!> The nonzero component of the rotated vector.
84!> \endverbatim
85!
86! Authors:
87! ========
88!
89!> \author Edward Anderson, Lockheed Martin
90!
91!> \date July 2016
92!
93!> \ingroup OTHERauxiliary
94!
95!> \par Contributors:
96! ==================
97!>
98!> Weslley Pereira, University of Colorado Denver, USA
99!
100!> \par Further Details:
101! =====================
102!>
103!> \verbatim
104!>
105!> Anderson E. (2017)
106!> Algorithm 978: Safe Scaling in the Level 1 BLAS
107!> ACM Trans Math Softw 44:1--28
108!> https://doi.org/10.1145/3061665
109!>
110!> \endverbatim
111!
112subroutine slartg( f, g, c, s, r )
113 use la_constants, &
114 only: wp=>sp, zero=>szero, half=>shalf, one=>sone, &
115 rtmin=>srtmin, rtmax=>srtmax, safmin=>ssafmin, safmax=>ssafmax
116!
117! -- LAPACK auxiliary routine --
118! -- LAPACK is a software package provided by Univ. of Tennessee, --
119! -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
120! February 2021
121!
122! .. Scalar Arguments ..
123 real(wp) :: c, f, g, r, s
124! ..
125! .. Local Scalars ..
126 real(wp) :: d, f1, fs, g1, gs, p, u, uu
127! ..
128! .. Intrinsic Functions ..
129 intrinsic :: abs, sign, sqrt
130! ..
131! .. Executable Statements ..
132!
133 f1 = abs( f )
134 g1 = abs( g )
135 if( g == zero ) then
136 c = one
137 s = zero
138 r = f
139 else if( f == zero ) then
140 c = zero
141 s = sign( one, g )
142 r = g1
143 else if( f1 > rtmin .and. f1 < rtmax .and. &
144 g1 > rtmin .and. g1 < rtmax ) then
145 d = sqrt( f*f + g*g )
146 p = one / d
147 c = f1*p
148 s = g*sign( p, f )
149 r = sign( d, f )
150 else
151 u = min( safmax, max( safmin, f1, g1 ) )
152 uu = one / u
153 fs = f*uu
154 gs = g*uu
155 d = sqrt( fs*fs + gs*gs )
156 p = one / d
157 c = abs( fs )*p
158 s = gs*sign( p, f )
159 r = sign( d, f )*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:113
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21
LA_CONSTANTS is a module for the scaling constants for the compiled Fortran single and double precisi...
real(sp), parameter srtmax
real(sp), parameter sone
real(sp), parameter shalf
real(sp), parameter srtmin
integer, parameter sp
real(sp), parameter ssafmin
real(sp), parameter ssafmax
real(sp), parameter szero