Report Typos and Errors    
Semi-Lagrangian Library
Modular library for kinetic and gyrokinetic simulations of plasmas in fusion energy devices.
sll_m_uzawa_iterator.F90
Go to the documentation of this file.
2 #include "sll_working_precision.h"
3 
6 
9 
12 
13  implicit none
14 
15  public :: sll_t_uzawa_iterator
16 
17  private
19  class(sll_t_linear_solver_abstract), pointer :: solver_k
20  class(sll_t_linear_operator_abstract), pointer :: operator_l
21  class(sll_t_linear_operator_abstract), pointer :: operator_lt
22  sll_int32 :: n_total0
23  sll_int32 :: n_total1
24 
25 
26  contains
27  procedure :: create => create_uzawa_iterator
28  procedure :: set_guess => set_guess_uzawa_iterator
29  procedure :: check_convergence => check_convergence_uzawa_iterator
30  procedure :: read_from_file => read_from_file_uzawa_iterator
31  procedure :: set_verbose => set_verbose_uzawa_iterator
32  procedure :: solve_real => solve_uzawa_iterator
33  procedure :: print_info => print_info_uzawa_iterator
34  procedure :: free => free_uzawa_iterator
35 
36  end type sll_t_uzawa_iterator
37 
38 
39 contains
40 
41  subroutine create_uzawa_iterator( self, solver_k, operator_l, operator_lt )
42  class(sll_t_uzawa_iterator), intent( inout ) :: self
43  class(sll_t_linear_solver_abstract), target :: solver_k
44  class(sll_t_linear_operator_abstract), target :: operator_l
45  class(sll_t_linear_operator_abstract), target :: operator_lt
46 
47  self%solver_k => solver_k
48  self%operator_l => operator_l
49  self%operator_lt => operator_lt
50 
51  self%n_total0 = operator_l%n_global_cols
52  self%n_total1 = operator_l%n_global_rows
53 
54  self%n_rows = solver_k%n_rows
55  self%n_cols = solver_k%n_cols
56 
57  allocate(self%x_0(self%n_total0))
58  self%x_0 = 0.0_f64
59 
60  end subroutine create_uzawa_iterator
61 
62  subroutine free_uzawa_iterator( self )
63  class(sll_t_uzawa_iterator), intent( inout ) :: self
64 
65  deallocate (self%x_0)
66  self%solver_k => null()
67  self%operator_l => null()
68  self%operator_lt => null()
69 
70  end subroutine free_uzawa_iterator
71 
72 
73  subroutine solve_uzawa_iterator(self, rhs, unknown)
74  class(sll_t_uzawa_iterator), intent( inout ) :: self
75  sll_real64, intent( in ) :: rhs(:)
76  sll_real64, intent( out ) :: unknown(:)
77  !local variables
78  sll_real64 :: rhs1(self%n_total1)
79  sll_real64 :: x0(self%n_total0)
80  sll_int32 :: itr_used
81  sll_real64 :: res
82  logical :: flag
83 
84  x0 = self%x_0
85  call self%operator_l%dot(x0, rhs1)
86  rhs1 = rhs - rhs1
87  call self%solver_k%solve(rhs1, unknown)
88 
89  call uzawa_iterator(self, unknown, x0, itr_used, res)
90 
91  self%x_0 = x0
92 
93  call self%check_convergence( i_iteration=itr_used, &
94  & flag=flag, &
95  & r_err=res)
96 
97  end subroutine solve_uzawa_iterator
98 
99 
100  subroutine uzawa_iterator(self, x1, x0, niterx, res)
101  class(sll_t_uzawa_iterator), intent( in ) :: self
102  sll_real64, intent(inout) :: x1(:)
103  sll_real64, intent(inout) :: x0(:)
104  sll_int32, intent(out) :: niterx
105  sll_real64, intent(out) :: res
106  !local variables
107  sll_int32 :: k
108  sll_real64 :: alpha, beta
109  sll_real64 :: a0(self%n_total0), p0(self%n_total0), r0(self%n_total0)
110  sll_real64 :: a1(self%n_total1), p1(self%n_total1)
111 
112 
113  call self%operator_lt%dot(x1, r0)
114  p0=r0
115  niterx = 1
116  do k = 1, self%n_maxiter
117 
118 
119  call self%operator_l%dot(p0, a1)
120  call self%solver_k%solve(a1, p1)
121  call self%operator_lt%dot(p1, a0)
122 
123  alpha = sum(p0*a0)/sum(p0*r0)
124 
125  x0 = x0 + alpha * p0
126  r0 = r0 - alpha * a0
127  x1 = x1 - alpha * p1
128 
129  res = sqrt(sum(r0*r0)/real(self%n_total0,f64))
130  if(self%verbose) print*, 'residuum', res
131  if( res <= self%atol ) exit
132 
133  if(sqrt(sum(p0*p0)/real(self%n_total0,f64)) < self%atol) then
134  print*, 'error uzawa iterator: search direction too small '
135  else
136  beta = sum(r0*a0)/sum(p0*a0)
137  p0 = r0 - beta*p0
138  end if
139 
140  niterx = k + 1
141  end do
142 
143  return
144 
145  end subroutine uzawa_iterator
146 
147 
148  subroutine print_info_uzawa_iterator( self )
149  class(sll_t_uzawa_iterator), intent(in) :: self
150 
151  print *, ">>>> uzawa_iterator"
152  print *, "* verbose : ", self%verbose
153  print *, "* atol : ", self%atol
154  print *, "* n_maxiter : ", self%n_maxiter
155  print *, "<<<< "
156 
157  end subroutine print_info_uzawa_iterator
158 
159  subroutine set_guess_uzawa_iterator(self, x_0)
160  class(sll_t_uzawa_iterator), intent(inout) :: self
161  sll_real64,dimension(:), intent(in) :: x_0
162 
163  self%x_0 = x_0
164 
165  end subroutine set_guess_uzawa_iterator
166 
167  ! ............................................
168  subroutine check_convergence_uzawa_iterator(self, i_iteration, flag, r_err, arr_err)
169  class(sll_t_uzawa_iterator), intent(in) :: self
170  ! local
171  sll_int32, intent(in) :: i_iteration
172  logical, intent(inout) :: flag
173  sll_real64, optional, intent(in) :: r_err
174  sll_real64, dimension(:), optional, intent(in) :: arr_err
175 
176  ! ...
177  if (self%verbose) then
178  if (present(r_err)) then
179  if (i_iteration <= self%n_maxiter) then
180  print*, '* uzawa_iterator: convergence after', i_iteration, 'iterations. Error ', r_err
181  else
182  print *, '* uzawa_iterator: Warning - max iterations', self%n_maxiter, 'achieved without convergence. Error', r_err
183  end if
184  end if
185  end if
186  !...
187 
188  end subroutine check_convergence_uzawa_iterator
189 
190  subroutine read_from_file_uzawa_iterator( self, filename )
191  class(sll_t_uzawa_iterator), intent(inout) :: self
192  character(len=*) , intent(in) :: filename
193 
194  end subroutine read_from_file_uzawa_iterator
195 
196  subroutine set_verbose_uzawa_iterator( self, verbose )
197  class(sll_t_uzawa_iterator), intent(inout) :: self
198  logical , intent(in) :: verbose
199 
200  call self%set_verbose_abstract(verbose)
201 
202  end subroutine set_verbose_uzawa_iterator
203 
204 
205 end module sll_m_uzawa_iterator
module for abstract linear operator
module for abstract linear solver
module for abstract iterative linear solvers
subroutine solve_uzawa_iterator(self, rhs, unknown)
subroutine set_verbose_uzawa_iterator(self, verbose)
subroutine set_guess_uzawa_iterator(self, x_0)
subroutine read_from_file_uzawa_iterator(self, filename)
subroutine uzawa_iterator(self, x1, x0, niterx, res)
subroutine free_uzawa_iterator(self)
subroutine print_info_uzawa_iterator(self)
subroutine check_convergence_uzawa_iterator(self, i_iteration, flag, r_err, arr_err)
subroutine create_uzawa_iterator(self, solver_k, operator_l, operator_lt)
    Report Typos and Errors