ev2ppf(3f) - [M_datapac:PERCENT_POINT] compute the extreme value type 2
(Frechet) percent point function
SUBROUTINE EV2PPF(P,Gamma,Ppf)
REAL(kind=wp),intent(in) :: P
REAL(kind=wp),intent(in) :: Gamma
REAL(kind=wp),intent(out) :: Ppf
EV2PPF(3f) computes the percent point function value for the extreme
value type 2 distribution with REAL tail length parameter
= GAMMA.
The extreme value type 2 distribution used herein is defined for all
non-negative X, and has the probability density function
f(X) = GAMMA * (X**(-GAMMA-1)) * exp(-(X**(-GAMMA)))
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 (exclusively) 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 extreme value type
2 distribution with tail length parameter value = GAMMA.
Sample program:
program demo_ev2ppf
use M_datapac, only : ev2ppf
implicit none
! call ev2ppf(x,y)
end program demo_ev2ppf
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 EV2PPF(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 THE EV2PPF SUBROU& &TINE 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 THE EV2PPF SUBROU& &TINE IS NON-POSITIVE *****') WRITE (G_IO,99003) Gamma Ppf = 0.0_wp RETURN ELSE ! !-----START POINT----------------------------------------------------- ! Ppf = (-LOG(P))**(-1.0_wp/Gamma) ENDIF 99003 FORMAT (' ','***** THE VALUE OF THE ARGUMENT IS ',E15.8,' *****') ! END SUBROUTINE EV2PPF