Skip to content

Commit

Permalink
Github testing 2
Browse files Browse the repository at this point in the history
  • Loading branch information
raback committed Aug 5, 2024
1 parent 9d448df commit 086b7a8
Show file tree
Hide file tree
Showing 2 changed files with 32 additions and 4 deletions.
14 changes: 13 additions & 1 deletion fem/src/CRSMatrix.F90
Original file line number Diff line number Diff line change
Expand Up @@ -3635,10 +3635,15 @@ FUNCTION CRS_IncompleteLU(A,ILUn) RESULT(Status)
FLOOR(ILURows(n+1)*(100.0d0/Rows(n+1)))
CALL Info( 'CRS_IncompleteLU', Message, Level=6 )

IF( InfoActive(25) ) THEN
PRINT *,'ILUValues:',MINVAL(IluValues),MAXVAL(IluValues),SUM(IluValues),SUM(ABS(IluValues))
END IF


WRITE(Message,'(A,I1,A,F8.2)') 'ILU(',ILUn, &
') (Real), Factorization ready at (s): ', CPUTime()-st
CALL Info( 'CRS_IncompleteLU', Message, Level=6 )

Status = .TRUE.
!------------------------------------------------------------------------------

Expand Down Expand Up @@ -3984,6 +3989,13 @@ FUNCTION CRS_ComplexIncompleteLU(A,ILUn) RESULT(Status)
FLOOR(ILURows(n/2+1)*(400.0d0/Rows(n+1)))
CALL Info( 'CRS_ComplexIncompleteLU', Message, Level=6 )


IF( InfoActive(25) ) THEN
PRINT *,'ILUValues(Complex):',MINVAL(ABS(IluValues)),MAXVAL(ABS(IluValues)),SUM(IluValues),SUM(ABS(IluValues))
END IF



WRITE(Message,'(A,I1,A,F8.2)') 'ILU(',ILUn, &
') (Complex), Factorization ready at (s): ', CPUTime()-st
CALL Info( 'CRS_ComplexIncompleteLU', Message, Level=6 )
Expand Down
22 changes: 19 additions & 3 deletions fem/src/IterSolve.F90
Original file line number Diff line number Diff line change
Expand Up @@ -798,13 +798,16 @@ END SUBROUTINE SlavePrecComplex
mvProc = MatvecF
ELSE
IF ( .NOT. ComplexSystem ) THEN
CALL Info('IterSolver','Setting mvproc to CRS_MatrixVectorProd',Level=25)
mvProc = AddrFunc( CRS_MatrixVectorProd )
ELSE
CALL Info('IterSolver','Setting mvproc to CRS_ComplexMatrixVectorProd',Level=25)
mvProc = AddrFunc( CRS_ComplexMatrixVectorProd )
END IF
END IF

IF ( PRESENT(dotF) ) THEN
CALL Info('IterSolver','Setting dotproc to dotF',Level=25)
dotProc = dotF
ELSE
dotProc = 0
Expand Down Expand Up @@ -837,8 +840,10 @@ END SUBROUTINE SlavePrecComplex

CASE (PRECOND_ILUn, PRECOND_ILUT, PRECOND_BILUn )
IF ( .NOT. ComplexSystem ) THEN
CALL Info('IterSolver','Setting pCondProc to CRS_LUPrecondition',Level=25)
pcondProc = AddrFunc( CRS_LUPrecondition )
ELSE
CALL Info('IterSolver','Setting pCondProc to CRS_ComplexLUPrecondition',Level=25)
pcondProc = AddrFunc( CRS_ComplexLUPrecondition )
END IF

Expand Down Expand Up @@ -951,9 +956,17 @@ END SUBROUTINE SlavePrecComplex
END SELECT

IF( Internal ) THEN
IF ( dotProc == 0 ) dotProc = AddrFunc(zdotc)
IF ( normProc == 0 ) normproc = AddrFunc(dznrm2)
IF( HUTI_DBUGLVL == 0) HUTI_DBUGLVL = HUGE( HUTI_DBUGLVL )
IF ( dotProc == 0 ) THEN
CALL Info('IterSolver','Setting dorProc to zdotc',Level=25)
dotProc = AddrFunc(zdotc)
END IF
IF ( normProc == 0 ) THEN
CALL Info('IterSolver','Setting normproc to dznrm2',Level=25)
normproc = AddrFunc(dznrm2)
END IF
IF( HUTI_DBUGLVL == 0) THEN
HUTI_DBUGLVL = HUGE( HUTI_DBUGLVL )
END IF
END IF

END IF
Expand All @@ -972,6 +985,8 @@ END SUBROUTINE SlavePrecComplex
GlobalMatrix => A

IF ( ComplexSystem ) THEN
CALL Info('IterSolver','Allocating stuff for complex linear system',Level=25)

! Associate xC and bC with complex variables
ALLOCATE(xC(HUTI_NDIM), bC(HUTI_NDIM), STAT=astat)
IF (astat /= 0) THEN
Expand All @@ -996,6 +1011,7 @@ END SUBROUTINE SlavePrecComplex
END IF

! Copy result back
CALL Info('IterSolver','Coming back from complex lienar system',Level=25)
DO i=1,HUTI_NDIM
x(2*i-1) = REAL(REAL(xC(i)),dp)
x(2*i) = REAL(AIMAG(xC(i)),dp)
Expand Down

0 comments on commit 086b7a8

Please sign in to comment.