GNU Octave 10.1.0
A high-level interpreted language, primarily intended for numerical computations, mostly compatible with Matlab
 
Loading...
Searching...
No Matches
gamlim.f
Go to the documentation of this file.
1*DECK GAMLIM
2 SUBROUTINE gamlim (XMIN, XMAX)
3C***BEGIN PROLOGUE GAMLIM
4C***PURPOSE Compute the minimum and maximum bounds for the argument in
5C the Gamma function.
6C***LIBRARY SLATEC (FNLIB)
7C***CATEGORY C7A, R2
8C***TYPE SINGLE PRECISION (GAMLIM-S, DGAMLM-D)
9C***KEYWORDS COMPLETE GAMMA FUNCTION, FNLIB, LIMITS, SPECIAL FUNCTIONS
10C***AUTHOR Fullerton, W., (LANL)
11C***DESCRIPTION
12C
13C Calculate the minimum and maximum legal bounds for X in GAMMA(X).
14C XMIN and XMAX are not the only bounds, but they are the only non-
15C trivial ones to calculate.
16C
17C Output Arguments --
18C XMIN minimum legal value of X in GAMMA(X). Any smaller value of
19C X might result in underflow.
20C XMAX maximum legal value of X in GAMMA(X). Any larger value will
21C cause overflow.
22C
23C***REFERENCES (NONE)
24C***ROUTINES CALLED R1MACH, XERMSG
25C***REVISION HISTORY (YYMMDD)
26C 770401 DATE WRITTEN
27C 890531 Changed all specific intrinsics to generic. (WRB)
28C 890531 REVISION DATE from Version 3.2
29C 891214 Prologue converted to Version 4.0 format. (BAB)
30C 900315 CALLs to XERROR changed to CALLs to XERMSG. (THJ)
31C***END PROLOGUE GAMLIM
32C***FIRST EXECUTABLE STATEMENT GAMLIM
33 alnsml = log(r1mach(1))
34 xmin = -alnsml
35 DO 10 i=1,10
36 xold = xmin
37 xln = log(xmin)
38 xmin = xmin - xmin*((xmin+0.5)*xln - xmin - 0.2258 + alnsml)
39 1 / (xmin*xln + 0.5)
40 IF (abs(xmin-xold).LT.0.005) GO TO 20
41 10 CONTINUE
42 CALL xermsg ('SLATEC', 'GAMLIM', 'UNABLE TO FIND XMIN', 1, 2)
43C
44 20 xmin = -xmin + 0.01
45C
46 alnbig = log(r1mach(2))
47 xmax = alnbig
48 DO 30 i=1,10
49 xold = xmax
50 xln = log(xmax)
51 xmax = xmax - xmax*((xmax-0.5)*xln - xmax + 0.9189 - alnbig)
52 1 / (xmax*xln - 0.5)
53 IF (abs(xmax-xold).LT.0.005) GO TO 40
54 30 CONTINUE
55 CALL xermsg ('SLATEC', 'GAMLIM', 'UNABLE TO FIND XMAX', 2, 2)
56C
57 40 xmax = xmax - 0.01
58 xmin = max(xmin, -xmax+1.)
59C
60 RETURN
61 END
charNDArray max(char d, const charNDArray &m)
Definition chNDArray.cc:230
subroutine gamlim(xmin, xmax)
Definition gamlim.f:3
octave_int< T > xmin(const octave_int< T > &x, const octave_int< T > &y)
octave_int< T > xmax(const octave_int< T > &x, const octave_int< T > &y)
real function r1mach(i)
Definition r1mach.f:23
subroutine xermsg(librar, subrou, messg, nerr, level)
Definition xermsg.f:3