File: test_sunlinsol.f90

package info (click to toggle)
sundials 6.4.1%2Bdfsg1-3
  • links: PTS, VCS
  • area: main
  • in suites: bookworm
  • size: 79,368 kB
  • sloc: ansic: 218,700; f90: 62,503; cpp: 61,511; fortran: 5,166; python: 4,642; sh: 4,114; makefile: 562; perl: 123
file content (353 lines) | stat: -rw-r--r-- 10,381 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
! -----------------------------------------------------------------
! Programmer(s): Cody J. Balos @ LLNL
! -----------------------------------------------------------------
! Acknowledgements: These testing routines are based on
! test_sunlinsol.c written by David Gardner @ LLNL and Daniel
! R. Reynolds @ SMU.
! -----------------------------------------------------------------
! SUNDIALS Copyright Start
! Copyright (c) 2002-2022, Lawrence Livermore National Security
! and Southern Methodist University.
! All rights reserved.
!
! See the top-level LICENSE and NOTICE files for details.
!
! SPDX-License-Identifier: BSD-3-Clause
! SUNDIALS Copyright End
! -----------------------------------------------------------------
! These test functions are designed to check the SWIG generated
! Fortran interface to a SUNLinearSolver module implementation.
! -----------------------------------------------------------------

module test_sunlinsol
  use, intrinsic :: iso_c_binding
  use fsundials_nvector_mod
  use fsundials_matrix_mod
  use fsundials_types_mod
  use test_utilities

  implicit none

  ! check_vector routine is provided by implementation specific tests
  integer(C_INT), external :: check_vector

contains

  integer(C_INT) function Test_FSUNLinSolGetType(S, mysunid, myid) result(failure)
    use, intrinsic :: iso_c_binding
    use fsundials_linearsolver_mod

    implicit none

    type(SUNLinearSolver), pointer :: S
    integer(SUNLinearSolver_Type)  :: mysunid, sunid
    integer(C_INT)                 :: myid

    sunid = FSUNLinSolGetType(S)
    if (sunid /= mysunid) then
      failure = 1
      write(*,*) ">>> FAILED test -- FSUNLinSolGetType, Proc", myid
    else if (myid == 0) then
      failure = 0
      write(*,*) "    PASSED test -- FSUNLinSolGetType"
    end if
  end function Test_FSUNLinSolGetType


  integer(C_INT) function Test_FSUNLinSolLastFlag(S, myid) result(failure)
    use, intrinsic :: iso_c_binding
    use fsundials_linearsolver_mod

    implicit none

    type(SUNLinearSolver), pointer :: S
    integer(C_INT)                 :: myid
    integer(C_LONG)                :: lastflag

    failure = 0

    ! the only way to fail this test is if the function is NULL,
    ! which will cause a seg-fault
    lastflag = FSUNLinSolLastFlag(S)
    if (myid == 0) then
      write(*,'(A,I0,A)') "     PASSED test -- FSUNLinSolLastFlag (", lastflag, ")"
    end if
  end function Test_FSUNLinSolLastFlag


  integer(C_INT) function Test_FSUNLinSolSpace(S, myid) result(failure)
    use, intrinsic :: iso_c_binding
    use fsundials_linearsolver_mod

    implicit none

    type(SUNLinearSolver), pointer :: S
    integer(C_INT)                 :: myid
    integer(C_LONG)                :: lenrw(1), leniw(1)

    failure = 0

    ! call FSUNLinSolSpace (failure based on output flag)
    failure = FSUNLinSolSpace(S, lenrw, leniw)
    if (failure /= 0) then
      write(*,*) ">>> FAILED test -- FSUNLinSolSpace, Proc ", myid
    else if (myid == 0) then
      write(*,'(A,I0,A,I0)') "     PASSED test -- FSUNLinSolSpace, lenrw = ", &
        lenrw, " leniw = ",  leniw
    end if

  end function Test_FSUNLinSolSpace


  integer(C_INT) function Test_FSUNLinSolNumIters(S, myid) result(failure)
    use, intrinsic :: iso_c_binding
    use fsundials_linearsolver_mod

    implicit none

    type(SUNLinearSolver), pointer :: S
    integer(C_INT)                 :: myid
    integer(C_INT)                 :: numiters

    failure = 0

    ! the only way to fail this test is if the function is NULL (segfault will happen)
    numiters = FSUNLinSolNumIters(S)

    if (myid == 0) then
      write(*,'(A,I0,A)') "     PASSED test -- FSUNLinSolNumIters (", numiters, ")"
    end if

  end function Test_FSUNLinSolNumIters


  integer(C_INT) function Test_FSUNLinSolResNorm(S, myid) result(failure)
    use, intrinsic :: iso_c_binding
    use fsundials_linearsolver_mod

    implicit none

    type(SUNLinearSolver), pointer :: S
    integer(C_INT)                 :: myid
    real(C_DOUBLE)                 :: resnorm

    failure = 0

    resnorm = FSUNLinSolResNorm(S)

    if (resnorm < ZERO) then
      write(*,'(A,E14.7,A,I0)') &
        ">>> FAILED test -- FSUNLinSolSolve returned ", resnorm, ", Proc ", myid
    else if (myid == 0) then
      write(*,*) "    PASSED test -- FSUNLinSolResNorm "
    end if

  end function Test_FSUNLinSolResNorm


  integer(C_INT) function Test_FSUNLinSolResid(S, myid) result(failure)
    use, intrinsic :: iso_c_binding
    use fsundials_nvector_mod
    use fsundials_linearsolver_mod

    implicit none

    type(SUNLinearSolver), pointer :: S
    integer(C_INT)                 :: myid
    type(N_Vector),        pointer :: resid

    failure = 0

    resid => FSUNLinSolResid(S)

    if (.not. associated(resid)) then
      write(*,*) ">>> FAILED test -- FSUNLinSolResid returned NULL N_Vector, Proc ", myid
    else if (myid == 0) then
      write(*,*) "    PASSED test -- FSUNLinSolResid "
    end if

  end function Test_FSUNLinSolResid


  integer(C_INT) function Test_FSUNLinSolSetATimes(S, ATdata, ATimes, myid) &
    result(failure)
    use, intrinsic :: iso_c_binding
    use fsundials_linearsolver_mod

    implicit none

    type(SUNLinearSolver), pointer :: S
    type(C_PTR)                    :: ATdata
    type(C_FUNPTR)                 :: ATimes
    integer(C_INT)                 :: myid

    failure = 0

    ! try calling SetATimes routine: should pass/fail based on expected input
    failure = FSUNLinSolSetATimes(S, ATdata, ATimes);

    if (failure /= 0) then
      write(*,'(A,I0,A,I0)') &
        ">>> FAILED test -- FSUNLinSolSetATimes returned ", failure, ", Proc ", myid
      failure = 1
    else if (myid == 0) then
      write(*,*) "    PASSED test -- FSUNLinSolSetATimes "
    end if

  end function Test_FSUNLinSolSetATimes


  integer(C_INT) function Test_FSUNLinSolSetPreconditioner(S, Pdata, PSetup, PSolve, myid) &
    result(failure)
    use, intrinsic :: iso_c_binding
    use fsundials_linearsolver_mod

    implicit none

    type(SUNLinearSolver), pointer :: S
    type(C_PTR)                    :: Pdata
    type(C_FUNPTR)                 :: PSetup, PSolve
    integer(C_INT)                 :: myid

    ! try calling SetPreconditioner routine: should pass/fail based on expected input
    failure = FSUNLinSolSetPreconditioner(S, Pdata, PSetup, PSolve);

    if (failure /= 0) then
      write(*,'(A,I0,A,I0)') &
        ">>> FAILED test -- FSUNLinSolSetPreconditioner returned ", failure, ", Proc ", myid
      failure = 1
    else if (myid == 0) then
      write(*,*) "    PASSED test -- FSUNLinSolSetPreconditioner "
    end if

  end function Test_FSUNLinSolSetPreconditioner


  integer(C_INT) function Test_FSUNLinSolSetScalingVectors(S, s1, s2, myid) &
    result(failure)
    use, intrinsic :: iso_c_binding
    use fsundials_linearsolver_mod
    use fsundials_nvector_mod

    implicit none

    type(SUNLinearSolver) :: S
    type(N_Vector)        :: s1, s2
    integer(C_INT)        :: myid

    failure = 0

    ! try calling SetScalingVectors routine: should pass/fail based on expected input
    failure = FSUNLinSolSetScalingVectors(S, s1, s2)

    if (failure /= 0) then
      write(*,'(A,I0,A,I0)') &
        ">>> FAILED test -- FSUNLinSolSetScalingVectors returned ", failure, ", Proc ", myid
      failure = 1
    else if (myid == 0) then
      write(*,*) "    PASSED test -- FSUNLinSolSetScalingVectors "
    end if

  end function Test_FSUNLinSolSetScalingVectors


  integer(C_INT) function Test_FSUNLinSolInitialize(S, myid) result(failure)
    use, intrinsic :: iso_c_binding
    use fsundials_linearsolver_mod

    implicit none

    type(SUNLinearSolver) :: S
    integer(C_INT)        :: myid

    failure = 0

    failure = FSUNLinSolInitialize(S)

    if (failure /= 0) then
      write(*,'(A,I0,A,I0)') &
        ">>> FAILED test -- FSUNLinSolInitialize returned ", failure, ", Proc ", myid
      failure = 1
    else if (myid == 0) then
      write(*,*) "    PASSED test -- FSUNLinSolInitialize "
    end if

  end function Test_FSUNLinSolInitialize

  integer(C_INT) function Test_FSUNLinSolSetup(S, A, myid) result(failure)
    use, intrinsic :: iso_c_binding
    use fsundials_matrix_mod
    use fsundials_linearsolver_mod

    implicit none

    type(SUNLinearSolver) :: S
    type(SUNMatrix)       :: A
    integer(C_INT)        :: myid

    failure = 0

    failure = FSUNLinSolSetup(S, A)

    if (failure /= 0) then
      write(*,'(A,I0,A,I0)') &
        ">>> FAILED test -- FSUNLinSolSetup returned ", failure, ", Proc ", myid
      failure = 1
    else if (myid == 0) then
      write(*,*) "    PASSED test -- FSUNLinSolSetup "
    end if

  end function Test_FSUNLinSolSetup

  ! ----------------------------------------------------------------------
  ! FSUNLinSolSolve Test
  !
  ! This test must follow Test_FSUNLinSolSetup.  Also, x must be the
  ! solution to the linear system A*x = b (for the original A matrix);
  ! while the 'A' that is supplied to this function should have been
  ! 'setup' by the Test_FSUNLinSolSetup() function prior to this call.
  ! ----------------------------------------------------------------------
  integer(C_INT) function Test_FSUNLinSolSolve(S, A, x, b, tol, myid) result(failure)
    use, intrinsic :: iso_c_binding
    use fsundials_nvector_mod
    use fsundials_matrix_mod
    use fsundials_linearsolver_mod

    implicit none

    type(SUNLinearSolver)   :: S
    type(SUNMatrix)         :: A
    type(N_Vector)          :: x, b
    type(N_Vector), pointer :: y
    real(C_DOUBLE)          :: tol
    integer(C_INT)          :: myid

    failure = 0

    ! clone to create solution vector
    y => FN_VClone(x)
    call FN_VConst(ZERO, y)

    ! perform solve
    failure = FSUNLinSolSolve(S, A, y, b, tol)
    if (failure /= 0) then
      write(*,'(A,I0,A,I0)') &
        ">>> FAILED test -- FSUNLinSolSolve returned ", failure, ", Proc ", myid
      return
    end if

    ! Check solution, and copy y into x for return
    failure = check_vector(x, y, 10.0d0*tol)
    call FN_VScale(ONE, y, x)

    if (failure /= 0) then
      write(*,*) ">>> FAILED test -- FSUNLinSolSolve check, Proc ", myid
    else if (myid == 0) then
      write(*,*) "    PASSED test -- FSUNLinSolSolve"
    end if

    call FN_VDestroy(y)

  end function Test_FSUNLinSolSolve

end module