2009-08-31 20:39:15 +05:30
|
|
|
!* 'Id'
|
2008-03-15 03:02:57 +05:30
|
|
|
!##############################################################
|
|
|
|
MODULE FEsolving
|
|
|
|
!##############################################################
|
|
|
|
|
2008-04-07 20:24:29 +05:30
|
|
|
use prec, only: pInt,pReal
|
2008-03-15 03:02:57 +05:30
|
|
|
implicit none
|
|
|
|
|
2009-10-12 21:31:49 +05:30
|
|
|
integer(pInt) cycleCounter, theInc
|
|
|
|
real(pReal) theTime, theDelta
|
2009-08-11 22:01:57 +05:30
|
|
|
logical :: lastIncConverged = .false.,outdatedByNewInc = .false.,outdatedFFN1 = .false.,terminallyIll = .false.
|
2009-01-20 00:40:58 +05:30
|
|
|
logical :: symmetricSolver = .false.
|
2009-03-04 17:18:54 +05:30
|
|
|
logical :: parallelExecution = .true.
|
2009-10-12 21:31:49 +05:30
|
|
|
logical :: lastMode = .true., cutBack = .false.
|
|
|
|
logical, dimension(:,:), allocatable :: calcMode
|
2009-05-07 21:57:36 +05:30
|
|
|
integer(pInt), dimension(:,:), allocatable :: FEsolving_execIP
|
|
|
|
integer(pInt), dimension(2) :: FEsolving_execElem
|
2009-01-20 00:40:58 +05:30
|
|
|
|
|
|
|
|
|
|
|
CONTAINS
|
|
|
|
|
|
|
|
!***********************************************************
|
|
|
|
! determine wether a symmetric solver is used
|
|
|
|
!***********************************************************
|
2009-03-04 17:18:54 +05:30
|
|
|
subroutine FE_init()
|
2009-01-20 00:40:58 +05:30
|
|
|
|
|
|
|
use prec, only: pInt
|
|
|
|
use IO
|
|
|
|
implicit none
|
|
|
|
|
2009-03-04 17:18:54 +05:30
|
|
|
integer(pInt), parameter :: fileunit = 222
|
2009-05-07 21:57:36 +05:30
|
|
|
integer(pInt), parameter :: maxNchunks = 2
|
|
|
|
integer(pInt), dimension(1+2*maxNchunks) :: positions
|
2009-03-04 17:18:54 +05:30
|
|
|
character(len=1024) line
|
|
|
|
|
2009-06-18 19:58:02 +05:30
|
|
|
write(6,*)
|
|
|
|
write(6,*) '<<<+- FEsolving init -+>>>'
|
2009-08-31 20:39:15 +05:30
|
|
|
write(6,*) '$Id$'
|
2009-06-18 19:58:02 +05:30
|
|
|
write(6,*)
|
|
|
|
|
2009-03-04 17:18:54 +05:30
|
|
|
if (IO_open_inputFile(fileunit)) then
|
2009-01-20 00:40:58 +05:30
|
|
|
|
2009-03-04 17:18:54 +05:30
|
|
|
rewind(fileunit)
|
|
|
|
do
|
|
|
|
read (fileunit,'(a1024)',END=100) line
|
2009-05-07 21:57:36 +05:30
|
|
|
positions = IO_stringPos(line,1)
|
|
|
|
if( IO_lc(IO_stringValue(line,positions,1)) == 'solver' ) then
|
2009-03-04 17:18:54 +05:30
|
|
|
read (fileunit,'(a1024)',END=100) line ! Garbage line
|
2009-05-07 21:57:36 +05:30
|
|
|
positions = IO_stringPos(line,2)
|
|
|
|
symmetricSolver = (IO_intValue(line,positions,2) /= 1_pInt)
|
2009-03-04 17:18:54 +05:30
|
|
|
exit
|
2009-01-20 00:40:58 +05:30
|
|
|
endif
|
2009-03-04 17:18:54 +05:30
|
|
|
enddo
|
|
|
|
else
|
2010-02-18 13:59:57 +05:30
|
|
|
call IO_error(101) ! cannot open input file
|
2009-03-04 17:18:54 +05:30
|
|
|
endif
|
|
|
|
|
|
|
|
100 close(fileunit)
|
2009-06-18 19:58:02 +05:30
|
|
|
|
2009-03-04 17:18:54 +05:30
|
|
|
return
|
2009-01-20 00:40:58 +05:30
|
|
|
|
|
|
|
end subroutine
|
2008-03-15 03:02:57 +05:30
|
|
|
|
|
|
|
END MODULE FEsolving
|