poicdf(3f) - [M_datapac:CUMULATIVE_DISTRIBUTION] compute the Poisson
cumulative distribution function
SUBROUTINE POICDF(X,Alamba,Cdf)
REAL(kind=wp),intent(in) :: X
REAL(kind=wp),intent(in) :: Alamba
REAL(kind=wp),intent(out) :: Cdf
POICDF(3f) computes the cumulative distribution function value at
the precision value X for the Poisson distribution with
precision tail length parameter = alamba.
The Poisson distribution used herein has mean = ALAMBA and standard
deviation = sqrt(ALAMBA).
This distribution is defined for all discrete non-negative integer
X-- X = 0, 1, 2, ... .
This distribution has the probability function
f(X) = exp(-ALAMBA) * ALAMBA**X / X!
The Poisson distribution is the distribution of the number of events
in the interval (0,ALAMBA) when the waiting time between events is
exponentially distributed with mean = 1 and standard deviation = 1.
X The value at which the cumulative distribution function is
to be evaluated. x should be non-negative and integral-valued.
ALAMBA The value of the tail length parameter. alamba should be
positive. The tail length parameter alamba is not restricted
to only integer values. ALAMBA can be set to any positive
real value --integer or non-integer.
CDF The cumulative distribution function value. For the Poisson
distribution
Even though the input to this cumulative distribution
function subroutine for this discrete distribution should (under
normal circumstances) be a discrete integer value,
X has been specified as REAL so as to conform with the datapac
convention that all input ****data**** (as opposed to sample
size, for example) variables to all datapac subroutines are real.
this convention is based on the belief that
1) a mixture of modes (floating point versus integer) is inconsistent
and an unnecessary complication in a data analysis; and
2) floating point machine arithmetic (as opposed to integer
arithmetic) is the more natural mode for doing data analysis.
Sample program:
program demo_poicdf
!@(#) line plotter graph of cumulative distribution function
use M_datapac, only : poicdf, plott, label
implicit none
real,allocatable :: x(:), y(:)
real :: alamba
integer :: i
call label('poicdf')
x=[(real(i),i=0,100,1)]
if(allocated(y))deallocate(y)
allocate(y(size(x)))
alamba=29.5
do i=1,size(x)
call poicdf(X(i),Alamba,y(i))
enddo
call plott(x,y,size(x))
end program demo_poicdf
Results:
The following is a plot of Y(I) (vertically) versus X(I) (horizontally)
I-----------I-----------I-----------I-----------I
0.1000000E+03 - X
0.9583334E+02 I X
0.9166666E+02 I X
0.8750000E+02 I X
0.8333334E+02 I X
0.7916667E+02 I X
0.7500000E+02 - X
0.7083334E+02 I X
0.6666667E+02 I X
0.6250000E+02 I X
0.5833334E+02 I X
0.5416667E+02 I X
0.5000000E+02 - X
0.4583334E+02 I X
0.4166667E+02 I XX
0.3750000E+02 I XXXX
0.3333334E+02 I X X X X
0.2916667E+02 I X X X X
0.2500000E+02 - X X X X X
0.2083334E+02 I XXX X
0.1666667E+02 I XX
0.1250000E+02 I X
0.8333336E+01 I X
0.4166672E+01 I X
0.0000000E+00 - X
I-----------I-----------I-----------I-----------I
0.1543E-12 0.2500E+00 0.5000E+00 0.7500E+00 0.1000E+01
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) | :: | X | ||||
real(kind=wp) | :: | Alamba | ||||
real(kind=wp) | :: | Cdf |
SUBROUTINE POICDF(X,Alamba,Cdf) REAL(kind=wp) :: X REAL(kind=wp) :: Alamba REAL(kind=wp) :: Cdf REAL(kind=wp) :: del, fintx, gcdf, spchi INTEGER :: i, ievodd, imax, imin, intx, nu DOUBLE PRECISION dx, pi, chi, sum, term, ai, dgcdf DOUBLE PRECISION DSQRT, DEXP DATA pi/3.14159265358979D0/ ! ! CHECK THE INPUT ARGUMENTS FOR ERRORS ! IF ( Alamba<=0.0_wp ) THEN WRITE (G_IO,99001) 99001 FORMAT (' ***** FATAL ERROR--THE SECOND INPUT ARGUMENT TO POICDF(3f) IS NON-POSITIVE *****') WRITE (G_IO,99005) Alamba Cdf = 0.0_wp RETURN ELSEIF ( X<0.0_wp ) THEN WRITE (G_IO,99002) 99002 FORMAT (' ***** NON-FATAL DIAGNOSTIC--THE FIRST INPUT ARGUMENT TO POICDF(3f) IS NEGATIVE *****') WRITE (G_IO,99005) X Cdf = 0.0_wp RETURN ELSE intx = X + 0.0001_wp fintx = intx del = X - fintx IF ( del<0.0_wp ) del = -del IF ( del>0.001_wp ) THEN WRITE (G_IO,99003) 99003 FORMAT (' ***** NON-FATAL DIAGNOSTIC--THE FIRST INPUT ARGUMENT TO POICDF(3f) IS NON-INTEGRAL *****') WRITE (G_IO,99005) X 99004 FORMAT (' ','***** THE VALUE OF THE ARGUMENT IS ',I0,' *****') ENDIF ! !-----START POINT----------------------------------------------------- ! ! EXPRESS THE POISSON CUMULATIVE DISTRIBUTION ! FUNCTION IN TERMS OF THE EQUIVALENT CHI-SQUARED ! CUMULATIVE DISTRIBUTION FUNCTION, ! AND THEN EVALUATE THE LATTER. ! dx = Alamba dx = 2.0D0*dx nu = X + 0.0001_wp nu = 2*(1+nu) ! chi = DSQRT(dx) ievodd = nu - 2*(nu/2) IF ( ievodd==0 ) THEN ! sum = 1.0D0 term = 1.0D0 imin = 2 imax = nu - 2 ELSE ! sum = 0.0D0 term = 1.0_wp/chi imin = 1 imax = nu - 1 ENDIF ! IF ( imin<=imax ) THEN DO i = imin , imax , 2 ai = i term = term*(dx/ai) sum = sum + term ENDDO ENDIF ! sum = sum*DEXP(-dx/2.0D0) IF ( ievodd/=0 ) THEN sum = (DSQRT(2.0D0/pi))*sum spchi = chi CALL NORCDF(spchi,gcdf) dgcdf = gcdf sum = sum + 2.0D0*(1.0D0-dgcdf) ENDIF Cdf = sum ENDIF 99005 FORMAT (' ','***** THE VALUE OF THE ARGUMENT IS ',E15.8,' *****') ! END SUBROUTINE POICDF