Program e04ne_t1w_fe
! E04NE_T1W_F Example Program Text
! Mark 30.2 Release. NAG Copyright 2024.
! .. Use Statements ..
Use iso_c_binding, Only: c_ptr
Use nagad_library, Only: e04nc_t1w_f, e04ne_t1w_f, e04wb_t1w_f, &
nagad_t1w_set_derivative, nagad_t1w_w_rtype, &
x10aa_t1w_f, x10ab_t1w_f, Assignment (=)
Use nag_library, Only: nag_wp, x04caf
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: lcwsav = 1, liwsav = 610, &
llwsav = 120, lrwsav = 475, nin = 5, &
nout = 6
! .. Local Scalars ..
Type (c_ptr) :: ad_handle
Type (nagad_t1w_w_rtype) :: obj
Integer :: i, ifail, inform, iter, k, lda, ldc, &
liwork, lwork, m, n, nclin, sdc
! .. Local Arrays ..
Type (nagad_t1w_w_rtype), Allocatable :: a(:,:), b(:), bl(:), bu(:), &
c(:,:), clamda(:), cvec(:), &
rwsav(:), work(:), x(:)
Real (Kind=nag_wp), Allocatable :: a_r(:,:), bl_r(:), bu_r(:), b_r(:), &
c_r(:,:), db(:), dbl(:), dbu(:), &
x_r(:)
Integer, Allocatable :: istate(:), iwork(:), iwsav(:), kx(:)
Logical, Allocatable :: lwsav(:)
Character (80), Allocatable :: cwsav(:)
! .. Intrinsic Procedures ..
Intrinsic :: max
! .. Executable Statements ..
Write (nout,*) 'E04NE_T1W_F Example Program Results'
! Skip heading in data file
Read (nin,*)
Read (nin,*) m, n, nclin
liwork = n
ldc = max(1,nclin)
lda = max(1,m)
If (nclin>0) Then
sdc = n
Else
sdc = 1
End If
! This particular example problem is of type LS1, so we allocate
! A(LDA,N), CVEC(1), B(M) and define LWORK as below
If (nclin>0) Then
lwork = 2*n**2 + 9*n + 6*nclin
Else
lwork = 9*n
End If
Allocate (istate(n+nclin),kx(n),iwork(liwork),c_r(ldc,sdc), &
bl_r(n+nclin),bu_r(n+nclin),cvec(1),x_r(n),a_r(lda,n),b_r(m), &
clamda(n+nclin),work(lwork),iwsav(liwsav),lwsav(llwsav),cwsav(lcwsav), &
rwsav(lrwsav))
Read (nin,*)(a_r(i,1:n),i=1,m)
Read (nin,*) b_r(1:m)
Read (nin,*)(c_r(i,1:sdc),i=1,nclin)
Read (nin,*) bl_r(1:(n+nclin))
Read (nin,*) bu_r(1:(n+nclin))
Read (nin,*) x_r(1:n)
! Create AD configuration data object
ifail = 0
Call x10aa_t1w_f(ad_handle,ifail)
Allocate (a(lda,n),b(m),c(ldc,sdc),bl(n+nclin),bu(n+nclin),x(n))
Allocate (db(m),dbl(n+nclin),dbu(n+nclin))
Do i = 1, m + 2*(n+nclin)
istate = 0
a = a_r
b = b_r
c = c_r
bl = bl_r
bu = bu_r
If (i<=m) Then
k = i
Call nagad_t1w_set_derivative(b(k),1.0_nag_wp)
Else If (i<=m+n+nclin) Then
k = i - m
Call nagad_t1w_set_derivative(bl(k),1.0_nag_wp)
Else
k = i - m - n - nclin
Call nagad_t1w_set_derivative(bu(k),1.0_nag_wp)
End If
x = x_r
! Initialise E04NE
ifail = 0
Call e04wb_t1w_f('E04NCA',cwsav,lcwsav,lwsav,llwsav,iwsav,liwsav, &
rwsav,lrwsav,ifail)
If (i==m+2*(n+nclin)) Then
! Set option via string
Call e04ne_t1w_f('Print Level = 1',lwsav,iwsav,rwsav,inform)
End If
! Solve the problem
obj = 0.0_nag_wp
ifail = 0
Call e04nc_t1w_f(ad_handle,m,n,nclin,ldc,lda,c,bl,bu,cvec,istate,kx,x, &
a,b,iter,obj,clamda,iwork,liwork,work,lwork,lwsav,iwsav,rwsav,ifail)
If (i<=m) Then
db(k) = obj%tangent
Else If (i<=m+n+nclin) Then
dbl(k) = obj%tangent
Else
dbu(k) = obj%tangent
End If
End Do
Write (nout,*)
Write (nout,*) ' Derivatives calculated: First order tangents'
Write (nout,*) ' Computational mode : algorithmic'
Write (nout,*)
Call x04caf('General',' ',m,1,db,m,' dobj/db',ifail)
Write (nout,*)
Call x04caf('General',' ',n+nclin,1,dbl,n+nclin,' dobj/dbl',ifail)
Write (nout,*)
Call x04caf('General',' ',n+nclin,1,dbu,n+nclin,' dobj/dbu',ifail)
! Remove computational data object
Call x10ab_t1w_f(ad_handle,ifail)
End Program e04ne_t1w_fe