DAMASK_EICMD/src/FEsolving.f90

66 lines
2.6 KiB
Fortran
Raw Normal View History

!--------------------------------------------------------------------------------------------------
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
!> Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
!> @brief holds some global variables and gets extra information for commercial FEM
!--------------------------------------------------------------------------------------------------
module FEsolving
2019-06-11 19:46:10 +05:30
use prec
use IO
use DAMASK_interface
implicit none
private
logical, public :: &
2019-06-11 19:46:10 +05:30
terminallyIll = .false. !< at least one material point is terminally ill
2019-06-11 19:46:10 +05:30
integer, dimension(:,:), allocatable, public :: &
FEsolving_execIP !< for ping-pong scheme always range to max IP, otherwise one specific IP
integer, dimension(2), public :: &
2019-06-11 19:46:10 +05:30
FEsolving_execElem !< for ping-pong scheme always whole range, otherwise one specific element
#if defined(Marc4DAMASK) || defined(Abaqus)
logical, public, protected :: &
2019-10-24 17:26:48 +05:30
symmetricSolver = .false. !< use a symmetric FEM solver
2019-06-11 19:46:10 +05:30
logical, dimension(:,:), allocatable, public :: &
calcMode !< do calculation or simply collect when using ping pong scheme
2019-06-11 19:46:10 +05:30
public :: FE_init
#endif
contains
2009-01-20 00:40:58 +05:30
#if defined(Marc4DAMASK) || defined(Abaqus)
!--------------------------------------------------------------------------------------------------
!> @brief determine whether a symmetric solver is used
!--------------------------------------------------------------------------------------------------
subroutine FE_init
2019-06-11 19:46:10 +05:30
write(6,'(/,a)') ' <<<+- FEsolving init -+>>>'
2019-10-24 17:26:48 +05:30
#if defined(Marc4DAMASK)
block
integer, parameter :: FILEUNIT = 222
character(len=pStringLen) :: line
integer, allocatable, dimension(:) :: chunkPos
call IO_open_inputFile(FILEUNIT)
rewind(FILEUNIT)
do
read (FILEUNIT,'(a256)',END=100) line
chunkPos = IO_stringPos(line)
if(IO_lc(IO_stringValue(line,chunkPos,1)) == 'solver') then
read (FILEUNIT,'(a256)',END=100) line ! next line
2019-06-11 19:46:10 +05:30
chunkPos = IO_stringPos(line)
symmetricSolver = (IO_intValue(line,chunkPos,2) /= 1)
2019-10-24 17:26:48 +05:30
endif
enddo
100 close(FILEUNIT)
end block
#endif
end subroutine FE_init
#endif
2019-10-24 17:26:48 +05:30
end module FEsolving