2012-08-25 17:16:36 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! $Id$
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
|
|
|
!> Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
2013-02-27 00:31:31 +05:30
|
|
|
!> @brief triggering reading in of restart information when doing a restart
|
2013-06-11 22:05:04 +05:30
|
|
|
!> @todo Descriptions for public variables needed
|
2012-08-25 17:16:36 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2012-03-09 01:55:28 +05:30
|
|
|
module FEsolving
|
2012-03-20 23:31:31 +05:30
|
|
|
use prec, only: &
|
|
|
|
pInt, &
|
|
|
|
pReal
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2008-03-15 03:02:57 +05:30
|
|
|
implicit none
|
2012-03-20 23:31:31 +05:30
|
|
|
private
|
2013-06-11 22:05:04 +05:30
|
|
|
integer(pInt), public :: & !< needs description
|
|
|
|
cycleCounter = 0_pInt, & !< needs description
|
|
|
|
theInc = -1_pInt, & !< needs description
|
2013-08-08 18:23:03 +05:30
|
|
|
restartInc = 1_pInt, & !< needs description
|
|
|
|
lastLovl = 0_pInt, & !< lovl in previous call to marc hypela2
|
|
|
|
lastStep = 0_pInt !< kstep in previous call to abaqus umat
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2012-03-20 23:31:31 +05:30
|
|
|
real(pReal), public :: &
|
2013-06-11 22:05:04 +05:30
|
|
|
theTime = 0.0_pReal, & !< needs description
|
|
|
|
theDelta = 0.0_pReal !< needs description
|
|
|
|
|
2012-03-20 23:31:31 +05:30
|
|
|
logical, public :: &
|
2013-06-11 22:05:04 +05:30
|
|
|
outdatedFFN1 = .false., & !< needs description
|
2012-08-25 17:16:36 +05:30
|
|
|
symmetricSolver = .false., & !< use a symmetric solver (FEM)
|
|
|
|
restartWrite = .false., & !< write current state to enable restart
|
|
|
|
restartRead = .false., & !< restart information to continue calculation from saved state
|
|
|
|
terminallyIll = .false., & !< at least one material point is terminally ill
|
2013-06-11 22:05:04 +05:30
|
|
|
lastIncConverged = .false., & !< needs description
|
|
|
|
outdatedByNewInc = .false. !< needs description
|
2012-03-20 23:31:31 +05:30
|
|
|
|
|
|
|
integer(pInt), dimension(:,:), allocatable, public :: &
|
2014-05-22 20:54:12 +05:30
|
|
|
FEsolving_execIP !< for ping-pong scheme always range to max IP, otherwise one specific IP
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2012-03-20 23:31:31 +05:30
|
|
|
integer(pInt), dimension(2), public :: &
|
2014-05-22 20:54:12 +05:30
|
|
|
FEsolving_execElem !< for ping-pong scheme always whole range, otherwise one specific element
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2012-03-20 23:31:31 +05:30
|
|
|
character(len=1024), public :: &
|
2013-06-11 22:05:04 +05:30
|
|
|
modelName !< needs description
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2012-03-20 23:31:31 +05:30
|
|
|
logical, dimension(:,:), allocatable, public :: &
|
2013-06-11 22:05:04 +05:30
|
|
|
calcMode !< needs description
|
2012-03-21 23:34:52 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
public :: FE_init
|
2008-03-15 03:02:57 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
contains
|
2009-01-20 00:40:58 +05:30
|
|
|
|
2013-02-11 15:14:17 +05:30
|
|
|
|
2012-08-25 17:16:36 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief determine whether a symmetric solver is used and whether restart is requested
|
2013-02-27 00:31:31 +05:30
|
|
|
!> @details restart information is found in input file in case of FEM solvers, in case of spectal
|
|
|
|
!> solver the information is provided by the interface module
|
2012-08-25 17:16:36 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2012-03-09 01:55:28 +05:30
|
|
|
subroutine FE_init
|
2013-02-27 00:31:31 +05:30
|
|
|
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
2012-03-20 23:31:31 +05:30
|
|
|
use debug, only: &
|
2012-07-05 15:24:50 +05:30
|
|
|
debug_level, &
|
2012-03-20 23:31:31 +05:30
|
|
|
debug_FEsolving, &
|
|
|
|
debug_levelBasic
|
|
|
|
use IO, only: &
|
|
|
|
IO_stringPos, &
|
|
|
|
IO_stringValue, &
|
|
|
|
IO_intValue, &
|
|
|
|
IO_lc, &
|
2012-06-15 21:40:21 +05:30
|
|
|
#ifndef Spectral
|
2014-06-06 06:08:29 +05:30
|
|
|
#ifndef FEM
|
2012-06-15 21:40:21 +05:30
|
|
|
IO_open_inputFile, &
|
2012-03-20 23:31:31 +05:30
|
|
|
IO_open_logFile, &
|
2014-06-06 06:08:29 +05:30
|
|
|
#endif
|
2012-06-15 21:40:21 +05:30
|
|
|
#endif
|
2013-02-25 22:04:59 +05:30
|
|
|
IO_warning, &
|
|
|
|
IO_timeStamp
|
2011-11-04 01:02:11 +05:30
|
|
|
use DAMASK_interface
|
2009-01-20 00:40:58 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
implicit none
|
2013-02-11 15:14:17 +05:30
|
|
|
#ifndef Spectral
|
2014-06-06 06:08:29 +05:30
|
|
|
#ifndef FEM
|
2012-03-20 23:31:31 +05:30
|
|
|
integer(pInt), parameter :: &
|
2013-12-11 22:19:20 +05:30
|
|
|
FILEUNIT = 222_pInt, &
|
2012-03-20 23:31:31 +05:30
|
|
|
maxNchunks = 6_pInt
|
2012-02-14 17:47:47 +05:30
|
|
|
integer(pInt) :: j
|
2012-03-09 01:55:28 +05:30
|
|
|
character(len=64) :: tag
|
2012-06-15 21:40:21 +05:30
|
|
|
character(len=1024) :: line
|
|
|
|
integer(pInt), dimension(1_pInt+2_pInt*maxNchunks) :: positions
|
2014-06-06 06:08:29 +05:30
|
|
|
#endif
|
2012-06-15 21:40:21 +05:30
|
|
|
#endif
|
2013-02-11 15:14:17 +05:30
|
|
|
|
|
|
|
write(6,'(/,a)') ' <<<+- FEsolving init -+>>>'
|
|
|
|
write(6,'(a)') ' $Id$'
|
2014-05-15 14:22:16 +05:30
|
|
|
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
2012-08-06 18:13:05 +05:30
|
|
|
#include "compilation_info.f90"
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2012-06-15 21:40:21 +05:30
|
|
|
modelName = getSolverJobName()
|
2012-06-20 18:19:46 +05:30
|
|
|
#ifdef Spectral
|
2012-06-18 14:57:36 +05:30
|
|
|
restartInc = spectralRestartInc
|
2012-06-15 21:40:21 +05:30
|
|
|
if(restartInc <= 0_pInt) then
|
|
|
|
call IO_warning(warning_ID=34_pInt)
|
|
|
|
restartInc = 1_pInt
|
|
|
|
endif
|
2012-08-25 17:16:36 +05:30
|
|
|
restartRead = restartInc > 1_pInt ! only read in if "true" restart requested
|
2014-06-06 06:08:29 +05:30
|
|
|
#elif defined FEM
|
|
|
|
restartInc = FEMRestartInc
|
|
|
|
if(restartInc <= 0_pInt) then
|
|
|
|
call IO_warning(warning_ID=34_pInt)
|
|
|
|
restartInc = 1_pInt
|
|
|
|
endif
|
|
|
|
restartRead = restartInc > 1_pInt
|
2012-06-15 21:40:21 +05:30
|
|
|
#else
|
2013-12-11 22:19:20 +05:30
|
|
|
call IO_open_inputFile(FILEUNIT,modelName)
|
|
|
|
rewind(FILEUNIT)
|
2012-06-15 21:40:21 +05:30
|
|
|
do
|
2013-12-11 22:19:20 +05:30
|
|
|
read (FILEUNIT,'(a1024)',END=100) line
|
2012-06-15 21:40:21 +05:30
|
|
|
positions = IO_stringPos(line,maxNchunks)
|
2012-08-25 17:16:36 +05:30
|
|
|
tag = IO_lc(IO_stringValue(line,positions,1_pInt)) ! extract key
|
2012-06-15 21:40:21 +05:30
|
|
|
select case(tag)
|
|
|
|
case ('solver')
|
2013-12-11 22:19:20 +05:30
|
|
|
read (FILEUNIT,'(a1024)',END=100) line ! next line
|
2012-06-15 21:40:21 +05:30
|
|
|
positions = IO_stringPos(line,maxNchunks)
|
|
|
|
symmetricSolver = (IO_intValue(line,positions,2_pInt) /= 1_pInt)
|
|
|
|
case ('restart')
|
2013-12-11 22:19:20 +05:30
|
|
|
read (FILEUNIT,'(a1024)',END=100) line ! next line
|
2012-06-15 21:40:21 +05:30
|
|
|
positions = IO_stringPos(line,maxNchunks)
|
|
|
|
restartWrite = iand(IO_intValue(line,positions,1_pInt),1_pInt) > 0_pInt
|
|
|
|
restartRead = iand(IO_intValue(line,positions,1_pInt),2_pInt) > 0_pInt
|
|
|
|
case ('*restart')
|
|
|
|
do j=2_pInt,positions(1)
|
|
|
|
restartWrite = (IO_lc(IO_StringValue(line,positions,j)) == 'write') .or. restartWrite
|
|
|
|
restartRead = (IO_lc(IO_StringValue(line,positions,j)) == 'read') .or. restartRead
|
|
|
|
enddo
|
|
|
|
if(restartWrite) then
|
2012-02-16 00:28:38 +05:30
|
|
|
do j=2_pInt,positions(1)
|
2012-06-15 21:40:21 +05:30
|
|
|
restartWrite = (IO_lc(IO_StringValue(line,positions,j)) /= 'frequency=0') .and. restartWrite
|
2012-02-13 23:11:27 +05:30
|
|
|
enddo
|
2012-06-15 21:40:21 +05:30
|
|
|
endif
|
|
|
|
end select
|
|
|
|
enddo
|
2013-12-11 22:19:20 +05:30
|
|
|
100 close(FILEUNIT)
|
2012-06-15 21:40:21 +05:30
|
|
|
|
2011-05-28 15:14:43 +05:30
|
|
|
if (restartRead) then
|
2013-04-30 15:19:30 +05:30
|
|
|
#ifdef Marc4DAMASK
|
2013-12-11 22:19:20 +05:30
|
|
|
call IO_open_logFile(FILEUNIT)
|
|
|
|
rewind(FILEUNIT)
|
2012-06-15 21:40:21 +05:30
|
|
|
do
|
2013-12-11 22:19:20 +05:30
|
|
|
read (FILEUNIT,'(a1024)',END=200) line
|
2012-06-15 21:40:21 +05:30
|
|
|
positions = IO_stringPos(line,maxNchunks)
|
|
|
|
if ( IO_lc(IO_stringValue(line,positions,1_pInt)) == 'restart' .and. &
|
|
|
|
IO_lc(IO_stringValue(line,positions,2_pInt)) == 'file' .and. &
|
|
|
|
IO_lc(IO_stringValue(line,positions,3_pInt)) == 'job' .and. &
|
|
|
|
IO_lc(IO_stringValue(line,positions,4_pInt)) == 'id' ) &
|
|
|
|
modelName = IO_StringValue(line,positions,6_pInt)
|
|
|
|
enddo
|
|
|
|
#else
|
2013-12-11 22:19:20 +05:30
|
|
|
call IO_open_inputFile(FILEUNIT,modelName)
|
|
|
|
rewind(FILEUNIT)
|
2012-06-15 21:40:21 +05:30
|
|
|
do
|
2013-12-11 22:19:20 +05:30
|
|
|
read (FILEUNIT,'(a1024)',END=200) line
|
2012-06-15 21:40:21 +05:30
|
|
|
positions = IO_stringPos(line,maxNchunks)
|
|
|
|
if ( IO_lc(IO_stringValue(line,positions,1_pInt))=='*heading') then
|
2013-12-11 22:19:20 +05:30
|
|
|
read (FILEUNIT,'(a1024)',END=200) line
|
2011-05-28 15:14:43 +05:30
|
|
|
positions = IO_stringPos(line,maxNchunks)
|
2012-06-15 21:40:21 +05:30
|
|
|
modelName = IO_StringValue(line,positions,1_pInt)
|
|
|
|
endif
|
|
|
|
enddo
|
|
|
|
#endif
|
2013-12-11 22:19:20 +05:30
|
|
|
200 close(FILEUNIT)
|
2010-11-03 20:09:18 +05:30
|
|
|
endif
|
2013-02-11 15:14:17 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! the following array are allocated by mesh.f90 and need to be deallocated in case of regridding
|
2012-08-06 18:13:05 +05:30
|
|
|
if (allocated(calcMode)) deallocate(calcMode)
|
|
|
|
if (allocated(FEsolving_execIP)) deallocate(FEsolving_execIP)
|
2012-06-15 21:40:21 +05:30
|
|
|
#endif
|
2012-07-05 15:24:50 +05:30
|
|
|
if (iand(debug_level(debug_FEsolving),debug_levelBasic) /= 0_pInt) then
|
2014-07-23 18:56:05 +05:30
|
|
|
write(6,'(a20,l1)') 'restart writing: ', restartWrite
|
|
|
|
write(6,'(a20,l1)') 'restart reading: ', restartRead
|
2013-07-01 12:10:09 +05:30
|
|
|
if (restartRead) write(6,'(a,/)') 'restart Job: '//trim(modelName)
|
2011-03-21 16:01:17 +05:30
|
|
|
endif
|
2009-01-20 00:40:58 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
end subroutine FE_init
|
2008-03-15 03:02:57 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
end module FEsolving
|