lamppf(3f) - [M_datapac:PERCENT_POINT] compute the Tukey-Lambda percent
point function
SUBROUTINE LAMPPF(P,Alamba,Ppf)
REAL(kind=wp),intent(in) :: Alamba
REAL(kind=wp),intent(in) :: P
REAL(kind=wp),intent(out) :: Ppf
LAMPPF(3f) computes the percent point function value for the (Tukey)
lambda distribution with tail length parameter value = ALAMBA.
In general, the probability density function for this distribution
is not simple.
The percent point function for this distribution is
g(P) = ((P**ALAMBA)-((1-P)**ALAMBA))/ALAMBA
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 and 1.0) at which the percent point
function is to be evaluated.
If ALAMBA is positive, then P should be between 0.0 and 1.0,
inclusively.
If ALAMBA is non-positive, then P should be between 0.0 and
1.0, exclusively.
ALAMBA The value of lambda (the tail length parameter).
PPF The percent point function value ppf for the Tukey lambda
distribution
Sample program:
program demo_lamppf
!@(#) line plotter graph of function
use M_datapac, only : lamppf, plott, label
implicit none
integer,parameter :: n=200
real :: x(n), y(n)
real :: alamba
integer :: i
alamba=3.3333
call label('lamppf')
x=[(real(i)/real(n+1),i=1,n)]
do i=1,n
call lamppf(x(i),alamba,y(i))
enddo
call plott(x,y,n)
end program demo_lamppf
Results:
The following is a plot of Y(I) (vertically) versus X(I) (horizontally)
I-----------I-----------I-----------I-----------I
0.9950249E+00 - XXX
0.9537728E+00 I XXX
0.9125207E+00 I XXX
0.8712686E+00 I XXXX
0.8300166E+00 I XXX
0.7887645E+00 I XXX
0.7475125E+00 - XXX
0.7062603E+00 I XXX
0.6650083E+00 I XX
0.6237562E+00 I XX
0.5825042E+00 I XX
0.5412520E+00 I XX
0.5000000E+00 - XXX
0.4587479E+00 I XX
0.4174958E+00 I XX
0.3762438E+00 I XX
0.3349917E+00 I XX
0.2937396E+00 I XXX
0.2524875E+00 - XXX
0.2112355E+00 I XXX
0.1699834E+00 I XXX
0.1287313E+00 I XXXX
0.8747923E-01 I XXX
0.4622716E-01 I XXX
0.4975124E-02 - XXX
I-----------I-----------I-----------I-----------I
-0.2951E+00 -0.1475E+00 0.0000E+00 0.1475E+00 0.2951E+00
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
lamran(3f) - [M_datapac:RANDOM] generate Tukey-Lambda random numbers
SUBROUTINE LAMRAN(N,Alamba,Iseed,X)
INTEGER,intent(in) :: N
REAL(kind=wp),intent(in) :: Alamba
INTEGER,intent(inout) :: Iseed
REAL(kind=wp),intent(out) :: X(:)
LAMRAN(3f) generates a random sample of size N from the (Tukey)
lambda distribution with tail length parameter value = ALAMBA.
In general, the probability density function for this distribution
is not simple. the percent point function for this distribution is
g(P) = ((P**ALAMBA)-((1-P)**ALAMBA))/ALAMBA
N The desired integer number of random numbers to be generated.
ALAMBA The value of LAMBDA (the tail length parameter).
ISEED An integer seed value. Should be set to a non-negative value
to start a new sequence of values. Will be set to -1 on return
to indicate the next call should continue the current random
sequence walk.
X A vector (of dimension at least N) into which the generated
random sample of size N from the (Tukey) lambda distribution
will be placed.
Sample program:
program demo_lamran
use m_datapac, only : lamran, plott, label, plotxt, sort
implicit none
integer,parameter :: n=400
real :: x(n)
integer :: iseed
real :: gamma
call label('lamran')
gamma=3.4
iseed=12345
call lamran(n,gamma,iseed,x)
call plotxt(x,n)
call sort(x,n,x) ! sort to show distribution
call plotxt(x,n)
end program demo_lamran
Results:
THE FOLLOWING IS A PLOT OF X(I) (VERTICALLY) VERSUS I (HORIZONTALLY
I-----------I-----------I-----------I-----------I
0.2940770E+00 - XX X X X
0.2701390E+00 I XXX X X X X X X
0.2462010E+00 I X XX X X X X
0.2222630E+00 I X XX X X X X X X X X
0.1983251E+00 I XX XX XX X X
0.1743871E+00 I XX X XX X X X X X X X XX XXXX
0.1504491E+00 - X X XX X X X XX X X
0.1265111E+00 I X X XXX X X X XX XX XX X X
0.1025732E+00 I X XX XXX XX XXXX XX X X XXXX
0.7863519E-01 I X XX XXXXX X X X X XXX X X XX
0.5469720E-01 I X XXX X X XX X X XX X XX X
0.3075922E-01 I X XXX X XXXX XXX XX XXX X XX XX X
0.6821245E-02 - XXXX X XX X X X X XX XX XX XX X X
-0.1711673E-01 I X X X XX X XX XX X XX X X XX
-0.4105473E-01 I XX X X XXXXXX XXXX XX X X X XXX
-0.6499270E-01 I X XX X X X XX XXXX X XX X
-0.8893067E-01 I X X X XX X X XX X X XX X X X
-0.1128686E+00 I X X X X X X X X XX
-0.1368066E+00 - XX X X X X X XXX X X X
-0.1607446E+00 I X XX X X X X X XX X X
-0.1846826E+00 I X X XX XXX X X X X X X X X X
-0.2086205E+00 I X XX X X X X X XX XXX
-0.2325585E+00 I X X X X X X
-0.2564965E+00 I XX X X X
-0.2804345E+00 - X X X X X X X
I-----------I-----------I-----------I-----------I
0.1000E+01 0.1008E+03 0.2005E+03 0.3002E+03 0.4000E+03
THE FOLLOWING IS A PLOT OF X(I) (VERTICALLY) VERSUS I (HORIZONTALLY
I-----------I-----------I-----------I-----------I
0.2940770E+00 - X
0.2701390E+00 I XX
0.2462010E+00 I XX
0.2222630E+00 I XX
0.1983251E+00 I XX
0.1743871E+00 I XXX
0.1504491E+00 - XXX
0.1265111E+00 I XXX
0.1025732E+00 I XXXX
0.7863519E-01 I XXXX
0.5469720E-01 I XXX
0.3075922E-01 I XXXX
0.6821245E-02 - XXXX
-0.1711673E-01 I XXXX
-0.4105473E-01 I XXXX
-0.6499270E-01 I XXX
-0.8893067E-01 I XXX
-0.1128686E+00 I XX
-0.1368066E+00 - XXX
-0.1607446E+00 I XXX
-0.1846826E+00 I XXX
-0.2086205E+00 I XXX
-0.2325585E+00 I X
-0.2564965E+00 I X
-0.2804345E+00 - XX
I-----------I-----------I-----------I-----------I
0.1000E+01 0.1008E+03 0.2005E+03 0.3002E+03 0.4000E+03
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) | :: | Alamba | |||
real(kind=wp), | intent(out) | :: | Ppf |
SUBROUTINE LAMPPF(P,Alamba,Ppf) REAL(kind=wp),intent(in) :: Alamba REAL(kind=wp),intent(in) :: P REAL(kind=wp),intent(out) :: Ppf !--------------------------------------------------------------------- ! ! CHECK THE INPUT ARGUMENTS FOR ERRORS ! IF ( Alamba>0.0_wp .OR. P>0.0_wp ) THEN IF ( Alamba>0.0_wp .OR. P<1.0_wp ) THEN IF ( Alamba<=0.0_wp .OR. P>=0.0_wp ) THEN IF ( Alamba<=0.0_wp .OR. P<=1.0_wp ) THEN IF ( -0.001_wp<Alamba .AND. Alamba<0.001_wp ) THEN Ppf = LOG(P/(1.0_wp-P)) RETURN ELSE Ppf = (P**Alamba-(1.0_wp-P)**Alamba)/Alamba GOTO 99999 ENDIF ENDIF ENDIF ENDIF ENDIF WRITE (G_IO,99001) 99001 FORMAT (' ***** FATAL ERROR--The first input argument to LAMPPF(3f) is outside the allowable (0,1) interval *****') WRITE (G_IO,99002) P 99002 FORMAT (' ***** The value of the argument is ',E15.8,' *****') RETURN ! 99999 END SUBROUTINE LAMPPF