restructured restarting capabilities

This commit is contained in:
Krishna Komerla 2011-11-07 11:04:57 +00:00
parent 583abf7ee6
commit 49c0b8a3fd
4 changed files with 44 additions and 30 deletions

View File

@ -51,6 +51,7 @@ program DAMASK_spectral
use math
use mesh, only: mesh_ipCenterOfGravity
use CPFEM, only: CPFEM_general, CPFEM_initAll
use FEsolving, only: restartWrite
use numerics, only: err_div_tol, err_stress_tol, err_stress_tolrel , rotation_tol,&
itmax, memory_efficient, DAMASK_NumThreadsInt,&
fftw_planner_flag, fftw_timelimit
@ -62,7 +63,7 @@ program DAMASK_spectral
real(pReal), dimension(9) :: valueVector ! stores information temporarily from loadcase file
integer(pInt), parameter :: maxNchunksLoadcase = &
(1_pInt + 9_pInt)*3_pInt + & ! deformation, rotation, and stress
(1_pInt + 1_pInt)*4_pInt + & ! time, (log)incs, temp, and frequency
(1_pInt + 1_pInt)*5_pInt + & ! time, (log)incs, temp, restartfrequency, and outputfrequency
1_pInt ! dropguessing
integer(pInt), dimension (1 + maxNchunksLoadcase*2) :: posLoadcase
integer(pInt), parameter :: maxNchunksGeom = 7_pInt ! 4 identifiers, 3 values
@ -79,7 +80,8 @@ program DAMASK_spectral
real(pReal), dimension(:), allocatable :: bc_timeIncrement, & ! length of increment
bc_temperature ! isothermal starting conditions
integer(pInt), dimension(:), allocatable :: bc_steps, & ! number of steps
bc_frequency, & ! frequency of result writes
bc_outputfrequency, & ! frequency of result writes
bc_restartfrequency, & ! frequency of result writes
bc_logscale ! linear/logaritmic time step flag
logical, dimension(:), allocatable :: bc_followFormerTrajectory,& ! follow trajectory of former loadcase
bc_velGradApplied ! decide wether velocity gradient or fdot is given
@ -189,7 +191,8 @@ program DAMASK_spectral
allocate (bc_temperature(N_Loadcases)); bc_temperature = 300.0_pReal
allocate (bc_steps(N_Loadcases)); bc_steps = 0_pInt
allocate (bc_logscale(N_Loadcases)); bc_logscale = 0_pInt
allocate (bc_frequency(N_Loadcases)); bc_frequency = 1_pInt
allocate (bc_outputfrequency(N_Loadcases)); bc_outputfrequency = 1_pInt
allocate (bc_restartfrequency(N_Loadcases)); bc_restartfrequency = 1_pInt
allocate (bc_followFormerTrajectory(N_Loadcases)); bc_followFormerTrajectory = .true.
allocate (bc_rotation(3,3,N_Loadcases)); bc_rotation = 0.0_pReal
@ -230,8 +233,10 @@ program DAMASK_spectral
case('logincs','logsteps') ! true, if log scale
bc_steps(loadcase) = IO_intValue(line,posLoadcase,j+1)
bc_logscale(loadcase) = 1_pInt
case('f','freq','frequency') ! frequency of result writings
bc_frequency(loadcase) = IO_intValue(line,posLoadcase,j+1)
case('f','freq','frequency','outputfreq') ! frequency of result writings
bc_outputfrequency(loadcase) = IO_intValue(line,posLoadcase,j+1)
case('r','restart','restartwrite') ! frequency of writing restart information
bc_restartfrequency(loadcase) = IO_intValue(line,posLoadcase,j+1)
case('guessreset','dropguessing')
bc_followFormerTrajectory(loadcase) = .false. ! do not continue to predict deformation along former trajectory
case('euler') ! rotation of loadcase given in euler angles
@ -407,9 +412,13 @@ program DAMASK_spectral
!$OMP CRITICAL (write2out)
print '(a,i5)','Increments: ',bc_steps(loadcase)
!$OMP END CRITICAL (write2out)
if (bc_frequency(loadcase) < 1_pInt) call IO_error(error_ID=36,ext_msg=loadcase_string) ! non-positive result frequency
if (bc_outputfrequency(loadcase) < 1_pInt) call IO_error(error_ID=36,ext_msg=loadcase_string) ! non-positive result frequency
!$OMP CRITICAL (write2out)
print '(a,i5)','Freq. of Output: ',bc_frequency(loadcase)
print '(a,i5)','Freq. of Restults Output: ',bc_outputfrequency(loadcase)
!$OMP END CRITICAL (write2out)
if (bc_restartfrequency(loadcase) < 1_pInt) call IO_error(error_ID=39,ext_msg=loadcase_string) ! non-positive result frequency
!$OMP CRITICAL (write2out)
print '(a,i5)','Freq. of Restart Information Output: ',bc_restartfrequency(loadcase)
!$OMP END CRITICAL (write2out)
enddo
@ -527,7 +536,7 @@ program DAMASK_spectral
write(538), 'materialpoint_sizeResults', materialpoint_sizeResults
write(538), 'loadcases', N_Loadcases
write(538), 'logscale', bc_logscale ! one entry per loadcase (0: linear, 1: log)
write(538), 'frequencies', bc_frequency ! one entry per loadcase
write(538), 'frequencies', bc_outputfrequency ! one entry per loadcase
write(538), 'times', bc_timeIncrement ! one entry per loadcase
bc_steps(1)= bc_steps(1) + 1_pInt
write(538), 'increments', bc_steps ! one entry per loadcase ToDo: rename keyword to steps
@ -565,6 +574,11 @@ program DAMASK_spectral
! loop oper steps defined in input file for current loadcase
do step = 1, bc_steps(loadcase)
!*************************************************************
if (mod(step,bc_restartFrequency(loadcase))==0_pInt) then ! setting restart parameter for FEsolving
restartWrite = .true.
else
restartWrite = .false.
endif
if (bc_logscale(loadcase) == 1_pInt) then ! loglinear scale
if (loadcase == 1_pInt) then ! 1st loadcase of loglinear scale
if (step == 1_pInt) then ! 1st step of 1st loadcase of loglinear scale
@ -778,8 +792,8 @@ program DAMASK_spectral
c_prev = math_rotate_forward3x3x3x3(c_current*wgt,bc_rotation(1:3,1:3,loadcase)) ! calculate stiffness for next step
!ToDo: Incfluence for next loadcase
if (mod(step,bc_frequency(loadcase)) == 0_pInt) then ! at output frequency
write(538), materialpoint_results(:,1,:) ! write result to file
if (mod(totalStepsCounter,bc_outputfrequency(loadcase)) == 0_pInt) then ! at output frequency
write(538), materialpoint_results(:,1,:) ! write result to file
endif
totalStepsCounter = totalStepsCounter + 1_pInt
!$OMP CRITICAL (write2out)

View File

@ -27,9 +27,9 @@ MODULE DAMASK_interface
character(len=64), parameter :: FEsolver = 'Spectral'
character(len=5), parameter :: InputFileExtension = '.geom'
character(len=4), parameter :: LogFileExtension = '.log' !until now, we don't have a log file. But IO.f90 requires it
logical :: restart_Write_Interface, restart_Read_Interface
logical :: restartReadFlag
character(len=1024) :: geometryParameter,loadcaseParameter
integer(pInt) :: restartParameter
integer(pInt) :: restartReadStep
CONTAINS
!********************************************************************
@ -45,8 +45,7 @@ subroutine DAMASK_interface_init()
start = 0_pInt
length= 0_pInt
restart_Write_Interface =.true.
restart_Read_Interface = .false.
restartReadFlag = .false.
call get_command(commandLine)
@ -60,7 +59,7 @@ subroutine DAMASK_interface_init()
if (index(commandLine,'--geometry',.true.)>0) then ! again, now searching for --geometry'
start = index(commandLine,'--geometry',.true.) + 11_pInt
endif
if(start==3_pInt) stop 'No Geometry specified, terminating DAMASK'! Could not find valid keyword. Functions from IO.f90 are not available
if(start==3_pInt) stop 'No Geometry specified, terminating DAMASK'! Could not find valid keyword (position 0 +3). Functions from IO.f90 are not available
length = index(commandLine(start:len(commandLine)),' ',.false.)
call get_command(commandLine) ! may contain capitals
@ -72,14 +71,14 @@ subroutine DAMASK_interface_init()
if(64<iachar(commandLine(i:i)) .and. iachar(commandLine(i:i))<91) commandLine(i:i) =achar(iachar(commandLine(i:i))+32)
enddo
start = index(commandLine,'-l',.true.) + 3_pInt ! search for '-l' and jump forward to given name
start = index(commandLine,'-l',.true.) + 3_pInt ! search for '-l' and jump forward iby 3 to given name
if (index(commandLine,'--load',.true.)>0) then ! if '--load' is found, use that (contains '-l')
start = index(commandLine,'--load',.true.) + 7_pInt
endif
if (index(commandLine,'--loadcase',.true.)>0) then ! again, now searching for --loadcase'
start = index(commandLine,'--loadcase',.true.) + 11_pInt
endif
if(start==3_pInt) stop 'No Loadcase specified, terminating DAMASK'! Could not find valid keyword functions from IO.f90 are not available
if(start==3_pInt) stop 'No Loadcase specified, terminating DAMASK'! Could not find valid keyword (position 0 +3). Functions from IO.f90 are not available
length = index(commandLine(start:len(commandLine)),' ',.false.)
call get_command(commandLine) ! may contain capitals
@ -96,14 +95,14 @@ subroutine DAMASK_interface_init()
endif
length = index(commandLine(start:len(commandLine)),' ',.false.)
if(start/=3_pInt) then
read(commandLine(start:start+length),'(I12)') restartParameter
if (restartParameter>0) then
restart_Read_Interface = .true.
else
restart_Write_Interface =.false.
endif
restartReadStep = 0_pInt
if(start/=3_pInt) then ! found -r
read(commandLine(start:start+length),'(I12)') restartReadStep
restartReadFlag = .true.
endif
if(restartReadStep<1_pInt .and. RestartReadFlag .eq. .true.) stop 'Invalid Restart Parameter, terminating DAMASK' ! Functions from IO.f90 are not available
!$OMP CRITICAL (write2out)
write(6,*)
write(6,*) '<<<+- DAMASK_spectral_interface init -+>>>'
@ -111,11 +110,10 @@ subroutine DAMASK_interface_init()
write(6,*)
write(6,*) 'Geometry Parameter: ', trim(geometryParameter)
write(6,*) 'Loadcase Parameter: ', trim(loadcaseParameter)
write(6,*) 'Restart Write: ', restart_Write_Interface
if (restart_Read_Interface) then
write(6,*) 'Restart Read: ', restartParameter
if (restartReadFlag) then
write(6,*) 'Restart Read: ', restartReadFlag
else
write(6,'(a,I5)') ' Restart Read at Step: ', restart_Read_Interface
write(6,'(a,I5)') ' Restart Read at Step: ', restartReadStep
endif
write(6,*)
!$OMP END CRITICAL (write2out)

View File

@ -62,8 +62,8 @@
FEmodelGeometry = getModelName()
if (IO_open_inputFile(fileunit,FEmodelGeometry)) then
if(trim(FEsolver)=='Spectral') then
restartWrite = restart_Write_Interface
restartRead = restart_Read_Interface
restartWrite = .true.
restartRead = restartReadFlag
else
rewind(fileunit)
do

View File

@ -1150,6 +1150,8 @@ endfunction
msg = 'incomplete loadcase'
case (38)
msg = 'mixed boundary conditions allow rotation'
case (39)
msg = 'non-positive restart frequency in spectral loadcase'
case (40)
msg = 'path rectification error'
case (41)