Program g11bcfe
! G11BCF Example Program Text
! Mark 26.2 Release. NAG Copyright 2017.
! .. Use Statements ..
Use nag_library, Only: g11bcf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Integer :: i, ifail, k, lauxt, maxst, mcells, &
mdim, ncells, ncol, ndim, nrow
Character (1) :: stat
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: auxt(:), stable(:), table(:), wk(:)
Integer, Allocatable :: idim(:), isdim(:), iwk(:), mlevel(:)
! .. Executable Statements ..
Write (nout,*) 'G11BCF Example Program Results'
Write (nout,*)
! Skip heading in data file
Read (nin,*)
! Read in the problem size
Read (nin,*) stat, ncells, ndim
Allocate (table(ncells),idim(ndim),isdim(ndim))
! Read in data
Read (nin,*) table(1:ncells)
Read (nin,*) idim(1:ndim)
Read (nin,*) isdim(1:ndim)
! Calculate MAXST
maxst = 1
Do i = 1, ndim
If (isdim(i)>0) Then
maxst = maxst*idim(i)
End If
End Do
If (stat=='V' .Or. stat=='v') Then
lauxt = maxst
Else
lauxt = 0
End If
Allocate (stable(maxst),mlevel(ndim),auxt(lauxt),iwk(3*ndim),wk(ncells))
! Compute marginal table
ifail = 0
Call g11bcf(stat,table,ncells,ndim,idim,isdim,stable,maxst,mcells,mdim, &
mlevel,auxt,iwk,wk,ifail)
! Display results
Write (nout,*) ' Marginal Table'
Write (nout,*)
ncol = mlevel(mdim)
nrow = mcells/ncol
k = 1
Do i = 1, nrow
Write (nout,99999) stable(k:(k+ncol-1))
k = k + ncol
End Do
99999 Format (10F8.2)
End Program g11bcfe