FrontISTR  5.7.0
Large-scale structural analysis program with finit element method
hecmw_precond_DIAG_nn.f90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
2 ! Copyright (c) 2019 FrontISTR Commons
3 ! This software is released under the MIT License, see LICENSE.txt
4 !-------------------------------------------------------------------------------
5 
6 !C
7 !C***
8 !C*** module hecmw_precond_DIAG_nn
9 !C***
10 !C
12  use hecmw_util
13 
14  private
15 
19 
20  integer(kind=kint) :: N
21  real(kind=kreal), pointer :: alu(:) => null()
22 
23  logical, save :: INITIALIZED = .false.
24 
25 contains
26 
27  subroutine hecmw_precond_diag_nn_setup(hecMAT)
29  implicit none
30  type(hecmwst_matrix), intent(inout) :: hecmat
31  integer(kind=kint ) :: np,ndof,ndof2
32  real (kind=kreal) :: sigma_diag
33  real(kind=kreal), pointer:: d(:)
34 
35  real (kind=kreal):: alutmp(hecmat%NDOF,hecmat%NDOF), pw(hecmat%NDOF)
36  integer(kind=kint ):: i, j, k, ii
37 
38  if (initialized) then
39  if (hecmat%Iarray(98) == 0 .and. hecmat%Iarray(97) == 0) return
41  endif
42 
43  n = hecmat%N
44  ndof = hecmat%NDOF
45  ndof2 = ndof*ndof
46  np = hecmat%NP
47  d => hecmat%D
48  sigma_diag = hecmw_mat_get_sigma_diag(hecmat)
49 
50  allocate(alu(ndof2*np))
51  alu = 0.d0
52 
53  do ii= 1, n
54  do i = 1, ndof2
55  alu(ndof2*(ii-1)+i)=d(ndof2*(ii-1)+i)
56  end do
57  enddo
58 
59  !$omp parallel default(none),private(ii,ALUtmp,k,i,j,PW),shared(N,NDOF,NDOF2,ALU,SIGMA_DIAG)
60  !$omp do
61  do ii= 1, n
62 
63  do i = 1, ndof
64  do j = 1, ndof
65  alutmp(i,j) = alu(ndof2*(ii-1)+(i-1)*ndof+j)
66  if (i==j) alutmp(i,j)=alutmp(i,j)*sigma_diag
67  end do
68  end do
69  do k= 1, ndof
70  alutmp(k,k)= 1.d0/alutmp(k,k)
71  do i= k+1, ndof
72  alutmp(i,k)= alutmp(i,k) * alutmp(k,k)
73  do j= k+1, ndof
74  pw(j)= alutmp(i,j) - alutmp(i,k)*alutmp(k,j)
75  enddo
76  do j= k+1, ndof
77  alutmp(i,j)= pw(j)
78  enddo
79  enddo
80  enddo
81  do i = 1, ndof
82  do j = 1, ndof
83  alu(ndof2*(ii-1)+(i-1)*ndof+j)= alutmp(i,j)
84  end do
85  end do
86  enddo
87  !$omp end do
88  !$omp end parallel
89  initialized = .true.
90  hecmat%Iarray(98) = 0 ! symbolic setup done
91  hecmat%Iarray(97) = 0 ! numerical setup done
92 
93  end subroutine hecmw_precond_diag_nn_setup
94 
95  subroutine hecmw_precond_diag_nn_apply(WW,NDOF)
96  implicit none
97  real(kind=kreal), intent(inout) :: ww(:)
98  integer(kind=kint) :: i,j,k,ndof
99  real(kind=kreal) :: x(ndof)
100 
101  !C
102  !C== Block SCALING
103  !$omp parallel default(none),private(i,j,k,X),shared(N,WW,ALU,NDOF)
104  !$omp do
105  do i= 1, n
106  do j=1,ndof
107  x(j)=ww(ndof*(i-1)+j)
108  end do
109  do j=2,ndof
110  do k = 1,j-1
111  x(j)=x(j)-alu(ndof*ndof*(i-1)+ndof*(j-1)+k )*x(k)
112  end do
113  end do
114  do j=ndof,1,-1
115  do k = ndof,j+1,-1
116  x(j)=x(j)-alu(ndof*ndof*(i-1)+ndof*(j-1)+k )*x(k)
117  end do
118  x(j)=alu(ndof*ndof*(i-1)+(ndof+1)*(j-1)+1 )*x(j)
119  end do
120  do j=1,ndof
121  ww(ndof*(i-1)+j)=x(j)
122  end do
123 
124  enddo
125  !$omp end do
126  !$omp end parallel
127 
128  end subroutine hecmw_precond_diag_nn_apply
129 
130  subroutine hecmw_precond_diag_nn_clear()
131  implicit none
132  if (associated(alu)) deallocate(alu)
133  nullify(alu)
134  initialized = .false.
135  end subroutine hecmw_precond_diag_nn_clear
136 
137 end module hecmw_precond_diag_nn
hecmw_precond_diag_nn::hecmw_precond_diag_nn_clear
subroutine, public hecmw_precond_diag_nn_clear()
Definition: hecmw_precond_DIAG_nn.f90:131
hecmw_precond_diag_nn
Definition: hecmw_precond_DIAG_nn.f90:11
hecmw_precond_diag_nn::hecmw_precond_diag_nn_setup
subroutine, public hecmw_precond_diag_nn_setup(hecMAT)
Definition: hecmw_precond_DIAG_nn.f90:28
hecmw_precond_diag_nn::hecmw_precond_diag_nn_apply
subroutine, public hecmw_precond_diag_nn_apply(WW, NDOF)
Definition: hecmw_precond_DIAG_nn.f90:96
hecmw_util
I/O and Utility.
Definition: hecmw_util_f.F90:7
hecmw_util::kreal
integer(kind=4), parameter kreal
Definition: hecmw_util_f.F90:16
hecmw_matrix_misc::hecmw_mat_get_sigma_diag
real(kind=kreal) function, public hecmw_mat_get_sigma_diag(hecMAT)
Definition: hecmw_matrix_misc.f90:694
hecmw_matrix_misc
Definition: hecmw_matrix_misc.f90:6
hecmw_util::hecmwst_matrix
Definition: hecmw_util_f.F90:444