Program g12aafe
! G12AAF Example Program Text
! Mark 26.2 Release. NAG Copyright 2017.
! .. Use Statements ..
Use nag_library, Only: g12aaf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Integer :: i, ifail, lifreq, n, nd
Character (1) :: freq
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: p(:), psig(:), t(:), tp(:)
Integer, Allocatable :: ic(:), ifreq(:), iwk(:)
! .. Executable Statements ..
Write (nout,*) 'G12AAF Example Program Results'
Write (nout,*)
! Skip heading in data file
Read (nin,*)
! Read in the problem size
Read (nin,*) n, freq
If (freq=='F' .Or. freq=='f') Then
lifreq = n
Else
lifreq = 0
End If
Allocate (p(n),psig(n),t(n),tp(n),ic(n),ifreq(lifreq),iwk(n))
! Read in the data
If (lifreq==0) Then
Read (nin,*)(t(i),ic(i),i=1,n)
Else
Read (nin,*)(t(i),ic(i),ifreq(i),i=1,n)
End If
! Calculate Kaplan-Meier statistic
ifail = 0
Call g12aaf(n,t,ic,freq,ifreq,nd,tp,p,psig,iwk,ifail)
! Display the results
Write (nout,*) ' Time Survival Standard'
Write (nout,*) ' probability deviation'
Write (nout,*)
Write (nout,99999)(tp(i),p(i),psig(i),i=1,nd)
99999 Format (1X,F6.1,F10.3,2X,F10.3)
End Program g12aafe