parppf(3f) - [M_datapac:PERCENT_POINT] compute the Pareto percent
point function
SUBROUTINE PARPPF(P,Gamma,Ppf)
REAL(kind=wp),intent(in) :: P
REAL(kind=wp),intent(in) :: Gamma
REAL(kind=wp),intent(out) :: Ppf
PARPPF(3f) computes the percent point function value for the Pareto
distribution with REAL tail length parameter = GAMMA.
The Pareto distribution used herein is defined for all X greater than
or equal to 1, and has the probability density function
f(X) = GAMMA / (X**(GAMMA+1))
Note that the percent point function of a distribution is identically
the same as the inverse cumulative distribution function of the
distribution.
P The value (between 0.0 (inclusively) and 1.0 (exclusively))
at which the percent point function is to be evaluated.
GAMMA The value of the tail length parameter. GAMMA should be
positive.
PPF The percent point function value for the Pareto distribution
Sample program:
program demo_parppf
use M_datapac, only : parppf
implicit none
! call parppf(x,y)
end program demo_parppf
Results:
The original DATAPAC library was written by James Filliben of the
Statistical Engineering Division, National Institute of Standards
and Technology.
John Urban, 2022.05.31
CC0-1.0
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=wp), | intent(in) | :: | P | |||
real(kind=wp), | intent(in) | :: | Gamma | |||
real(kind=wp), | intent(out) | :: | Ppf |
SUBROUTINE PARPPF(P,Gamma,Ppf) REAL(kind=wp),intent(in) :: P REAL(kind=wp),intent(in) :: Gamma REAL(kind=wp),intent(out) :: Ppf !--------------------------------------------------------------------- ! ! CHECK THE INPUT ARGUMENTS FOR ERRORS ! IF ( P<0.0_wp .OR. P>=1.0_wp ) THEN WRITE (G_IO,99001) 99001 FORMAT (' ***** FATAL ERROR--The first input argument to PARPPF(3f) is outside the allowable (0,1) interval *****') WRITE (G_IO,99003) P Ppf = 0.0_wp RETURN ELSEIF ( Gamma<=0.0_wp ) THEN WRITE (G_IO,99002) 99002 FORMAT (' ***** FATAL ERROR--The second input argument to PARPPF(3f) is non-positive *****') WRITE (G_IO,99003) Gamma Ppf = 0.0_wp RETURN ELSE Ppf = (1.0_wp-P)**(-1.0_wp/Gamma) ENDIF 99003 FORMAT (' ','***** The value of the argument is ',E15.8,' *****') END SUBROUTINE PARPPF