2013-03-22 23:05:05 +05:30
! Copyright 2011-13 Max-Planck-Institut für Eisenforschung GmbH
!
! This file is part of DAMASK,
! the Düsseldorf Advanced MAterial Simulation Kit.
!
! DAMASK is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! DAMASK is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with DAMASK. If not, see <http://www.gnu.org/licenses/>.
!
2012-07-30 19:36:22 +05:30
!--------------------------------------------------------------------------------------------------
2012-10-24 17:01:40 +05:30
! $Id$
2012-07-30 19:36:22 +05:30
!--------------------------------------------------------------------------------------------------
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
!> @brief Driver controlling inner and outer load case looping of the various spectral solvers
2013-02-23 05:54:30 +05:30
!> @details doing cutbacking, forwarding in case of restart, reporting statistics, writing
!> results
2012-07-30 19:36:22 +05:30
!--------------------------------------------------------------------------------------------------
2012-07-24 22:37:10 +05:30
program DAMASK_spectral_Driver
2012-12-15 21:51:10 +05:30
use , intrinsic :: &
iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran >4.6 at the moment)
2013-02-23 05:54:30 +05:30
use prec , only : &
pInt , &
pReal
2012-07-20 21:03:13 +05:30
use DAMASK_interface , only : &
DAMASK_interface_init , &
loadCaseFile , &
geometryFile , &
getSolverWorkingDirectoryName , &
getSolverJobName , &
appendToOutFile
2012-07-19 22:54:56 +05:30
use IO , only : &
2013-06-27 00:49:00 +05:30
IO_read , &
2012-07-20 21:03:13 +05:30
IO_isBlank , &
IO_open_file , &
IO_stringPos , &
IO_stringValue , &
IO_floatValue , &
IO_intValue , &
IO_error , &
IO_lc , &
IO_read_jobBinaryFile , &
2012-08-31 01:56:28 +05:30
IO_write_jobBinaryFile , &
2013-01-10 19:03:43 +05:30
IO_intOut , &
2013-05-08 21:22:29 +05:30
IO_warning , &
IO_timeStamp
use debug , only : &
debug_level , &
debug_spectral , &
debug_levelBasic
2012-10-24 17:01:40 +05:30
use math ! need to include the whole module for FFTW
2012-07-20 21:03:13 +05:30
use CPFEM , only : &
CPFEM_initAll
2012-07-19 22:54:56 +05:30
use FEsolving , only : &
restartWrite , &
restartInc
2012-07-20 21:03:13 +05:30
use numerics , only : &
2012-10-02 20:56:56 +05:30
maxCutBack , &
2012-07-25 19:31:39 +05:30
rotation_tol , &
2012-12-14 20:48:04 +05:30
mySpectralSolver , &
regridMode
2012-07-19 22:54:56 +05:30
use homogenization , only : &
materialpoint_sizeResults , &
materialpoint_results
2012-08-03 14:55:48 +05:30
use DAMASK_spectral_Utilities , only : &
2013-05-08 21:22:29 +05:30
grid , &
geomSize , &
2012-10-02 20:56:56 +05:30
tBoundaryCondition , &
tSolutionState , &
cutBack
2012-07-24 22:37:10 +05:30
use DAMASK_spectral_SolverBasic
2012-08-29 00:49:47 +05:30
#ifdef PETSc
2012-08-14 22:28:23 +05:30
use DAMASK_spectral_SolverBasicPETSC
2012-08-06 14:23:12 +05:30
use DAMASK_spectral_SolverAL
2013-07-24 18:36:16 +05:30
use DAMASK_spectral_SolverPolarisation
2012-08-29 00:49:47 +05:30
#endif
2013-02-20 20:07:12 +05:30
2012-07-19 22:54:56 +05:30
implicit none
2012-10-02 20:56:56 +05:30
type tLoadCase
2012-10-19 14:14:21 +05:30
real ( pReal ) , dimension ( 3 , 3 ) :: rotation = math_I3 !< rotation of BC
type ( tBoundaryCondition ) :: P , & !< stress BC
deformation !< deformation BC (Fdot or L)
real ( pReal ) :: time = 0.0_pReal , & !< length of increment
2013-07-26 21:55:37 +05:30
temperature = 30 0.0_pReal , & !< isothermal starting conditions
density = 0.0_pReal !< density
2012-10-19 14:14:21 +05:30
integer ( pInt ) :: incs = 0_pInt , & !< number of increments
outputfrequency = 1_pInt , & !< frequency of result writes
restartfrequency = 0_pInt , & !< frequency of restart writes
2013-01-09 03:24:25 +05:30
logscale = 0_pInt !< linear/logarithmic time inc flag
2012-10-19 14:14:21 +05:30
logical :: followFormerTrajectory = . true . !< follow trajectory of former loadcase
2012-10-02 20:56:56 +05:30
end type tLoadCase
2012-07-23 15:42:31 +05:30
2012-07-20 21:03:13 +05:30
!--------------------------------------------------------------------------------------------------
! variables related to information from load case and geom file
2012-11-09 03:03:58 +05:30
real ( pReal ) , dimension ( 9 ) :: temp_valueVector = 0.0_pReal !< temporarily from loadcase file when reading in tensors (initialize to 0.0)
logical , dimension ( 9 ) :: temp_maskVector = . false . !< temporarily from loadcase file when reading in tensors
2012-12-15 21:51:10 +05:30
integer ( pInt ) , parameter :: maxNchunks = ( 1_pInt + 9_pInt ) * 3_pInt + & ! deformation, rotation, and stress
( 1_pInt + 1_pInt ) * 5_pInt + & ! time, (log)incs, temp, restartfrequency, and outputfrequency
1_pInt , & ! dropguessing
myUnit = 234_pInt !< file unit, DAMASK IO does not support newunit feature
integer ( pInt ) , dimension ( 1_pInt + maxNchunks * 2_pInt ) :: positions ! this is longer than needed for geometry parsing
2012-07-20 21:03:13 +05:30
integer ( pInt ) :: &
2013-02-23 05:54:30 +05:30
N_t = 0_pInt , & !< # of time indicators found in load case file
N_n = 0_pInt , & !< # of increment specifiers found in load case file
2013-05-13 15:14:23 +05:30
N_def = 0_pInt !< # of rate of deformation specifiers found in load case file
2013-06-27 00:49:00 +05:30
character ( len = 65536 ) :: &
2012-07-20 21:03:13 +05:30
line
2012-07-19 22:54:56 +05:30
!--------------------------------------------------------------------------------------------------
! loop variables, convergence etc.
2012-12-15 21:51:10 +05:30
real ( pReal ) , dimension ( 3 , 3 ) , parameter :: &
ones = 1.0_pReal , &
zeros = 0.0_pReal
2013-01-08 03:12:00 +05:30
integer ( pInt ) , parameter :: &
subStepFactor = 2_pInt !< for each substep, divide the last time increment by 2.0
2012-12-15 21:51:10 +05:30
real ( pReal ) :: &
time = 0.0_pReal , & !< elapsed time
time0 = 0.0_pReal , & !< begin of interval
timeinc = 1.0_pReal , & !< current time interval
2013-05-13 15:14:23 +05:30
timeIncOld = 0.0_pReal , & !< previous time interval
remainingLoadCaseTime = 0.0_pReal !< remaining time of current load case
2012-12-15 21:51:10 +05:30
logical :: &
guess !< guess along former trajectory
integer ( pInt ) :: &
i , j , k , l , &
errorID , &
cutBackLevel = 0_pInt , & !< cut back level \f$ t = \frac{t_{inc}}{2^l} \f$
stepFraction = 0_pInt !< fraction of current time interval
integer ( pInt ) :: &
currentLoadcase = 0_pInt , & !< current load case
inc , & !< current increment in current load case
totalIncsCounter = 0_pInt , & !< total No. of increments
convergedCounter = 0_pInt , & !< No. of converged increments
notConvergedCounter = 0_pInt , & !< No. of non-converged increments
resUnit = 0_pInt , & !< file unit for results writing
statUnit = 0_pInt , & !< file unit for statistics output
lastRestartWritten = 0_pInt !< total increment No. at which last restart information was written
2012-07-23 15:42:31 +05:30
character ( len = 6 ) :: loadcase_string
2012-12-15 21:51:10 +05:30
character ( len = 1024 ) :: incInfo !< string parsed to solution with information about current load case
type ( tLoadCase ) , allocatable , dimension ( : ) :: loadCases !< array of all load cases
2012-10-02 20:56:56 +05:30
type ( tSolutionState ) solres
2013-02-20 20:07:12 +05:30
external :: quit
2012-08-03 14:55:48 +05:30
!--------------------------------------------------------------------------------------------------
! init DAMASK (all modules)
2012-07-30 19:36:22 +05:30
call CPFEM_initAll ( temperature = 30 0.0_pReal , element = 1_pInt , IP = 1_pInt )
2013-05-08 21:22:29 +05:30
write ( 6 , '(/,a)' ) ' <<<+- DAMASK_spectral_driver init -+>>>'
write ( 6 , '(a)' ) ' $Id$'
write ( 6 , '(a15,a)' ) ' Current time: ' , IO_timeStamp ( )
2012-07-19 22:54:56 +05:30
#include "compilation_info.f90"
2012-10-24 17:01:40 +05:30
2012-07-19 22:54:56 +05:30
!--------------------------------------------------------------------------------------------------
2012-08-03 14:55:48 +05:30
! reading basic information from load case file and allocate data structure containing load cases
2012-07-19 22:54:56 +05:30
call IO_open_file ( myUnit , trim ( loadCaseFile ) )
rewind ( myUnit )
do
2013-06-27 00:49:00 +05:30
line = IO_read ( myUnit )
if ( trim ( line ) == '#EOF#' ) exit
2012-07-19 22:54:56 +05:30
if ( IO_isBlank ( line ) ) cycle ! skip empty lines
2012-12-15 21:51:10 +05:30
positions = IO_stringPos ( line , maxNchunks )
2013-06-27 00:49:00 +05:30
do i = 1_pInt , positions ( 1 ) ! reading compulsory parameters for loadcase
2013-02-23 05:54:30 +05:30
select case ( IO_lc ( IO_stringValue ( line , positions , i ) ) )
2013-05-13 15:14:23 +05:30
case ( 'l' , 'velocitygrad' , 'velgrad' , 'velocitygradient' , 'fdot' , 'dotf' , 'f' )
N_def = N_def + 1_pInt
2013-02-23 05:54:30 +05:30
case ( 't' , 'time' , 'delta' )
N_t = N_t + 1_pInt
case ( 'n' , 'incs' , 'increments' , 'steps' , 'logincs' , 'logincrements' , 'logsteps' )
N_n = N_n + 1_pInt
end select
2012-07-19 22:54:56 +05:30
enddo ! count all identifiers to allocate memory and do sanity check
enddo
2013-06-27 00:49:00 +05:30
if ( ( N_def / = N_n ) . or . ( N_n / = N_t ) ) & ! sanity check
call IO_error ( error_ID = 837_pInt , ext_msg = trim ( loadCaseFile ) ) ! error message for incomplete loadcase
2012-12-15 21:51:10 +05:30
allocate ( loadCases ( N_n ) ) ! array of load cases
2012-08-03 14:55:48 +05:30
loadCases % P % myType = 'p'
2012-07-19 22:54:56 +05:30
2012-10-24 17:01:40 +05:30
!--------------------------------------------------------------------------------------------------
2012-07-19 22:54:56 +05:30
! reading the load case and assign values to the allocated data structure
rewind ( myUnit )
do
2013-06-27 00:49:00 +05:30
line = IO_read ( myUnit )
if ( trim ( line ) == '#EOF#' ) exit
2012-07-19 22:54:56 +05:30
if ( IO_isBlank ( line ) ) cycle ! skip empty lines
2012-08-03 14:55:48 +05:30
currentLoadCase = currentLoadCase + 1_pInt
2012-12-15 21:51:10 +05:30
positions = IO_stringPos ( line , maxNchunks )
2013-02-06 22:15:34 +05:30
do i = 1_pInt , positions ( 1 )
2012-07-20 21:03:13 +05:30
select case ( IO_lc ( IO_stringValue ( line , positions , i ) ) )
2013-05-13 15:14:23 +05:30
case ( 'fdot' , 'dotf' , 'l' , 'velocitygrad' , 'velgrad' , 'velocitygradient' , 'f' ) ! assign values for the deformation BC matrix
2012-11-09 02:05:31 +05:30
temp_valueVector = 0.0_pReal
2012-11-29 18:56:17 +05:30
if ( IO_lc ( IO_stringValue ( line , positions , i ) ) == 'fdot' . or . & ! in case of Fdot, set type to fdot
IO_lc ( IO_stringValue ( line , positions , i ) ) == 'dotf' ) then
2012-08-03 14:55:48 +05:30
loadCases ( currentLoadCase ) % deformation % myType = 'fdot'
2013-05-13 15:14:23 +05:30
else if ( IO_lc ( IO_stringValue ( line , positions , i ) ) == 'f' ) then
loadCases ( currentLoadCase ) % deformation % myType = 'f'
2012-11-29 18:56:17 +05:30
else
loadCases ( currentLoadCase ) % deformation % myType = 'l'
2012-08-03 14:55:48 +05:30
endif
2013-02-06 22:15:34 +05:30
do j = 1_pInt , 9_pInt
temp_maskVector ( j ) = IO_stringValue ( line , positions , i + j ) / = '*' ! true if not a *
enddo
2012-12-15 21:51:10 +05:30
do j = 1_pInt , 9_pInt
if ( temp_maskVector ( j ) ) temp_valueVector ( j ) = IO_floatValue ( line , positions , i + j ) ! read value where applicable
2012-07-19 22:54:56 +05:30
enddo
2012-12-15 21:51:10 +05:30
loadCases ( currentLoadCase ) % deformation % maskLogical = & ! logical mask in 3x3 notation
transpose ( reshape ( temp_maskVector , [ 3 , 3 ] ) )
loadCases ( currentLoadCase ) % deformation % maskFloat = & ! float (1.0/0.0) mask in 3x3 notation
merge ( ones , zeros , loadCases ( currentLoadCase ) % deformation % maskLogical )
loadCases ( currentLoadCase ) % deformation % values = math_plain9to33 ( temp_valueVector ) ! values in 3x3 notation
2013-01-24 00:03:46 +05:30
case ( 'p' , 'pk1' , 'piolakirchhoff' , 'stress' , 's' )
2012-07-19 22:54:56 +05:30
temp_valueVector = 0.0_pReal
2013-02-06 22:15:34 +05:30
do j = 1_pInt , 9_pInt
2013-05-13 15:14:23 +05:30
temp_maskVector ( j ) = IO_stringValue ( line , positions , i + j ) / = '*' ! true if not an asterisk
2013-02-06 22:15:34 +05:30
enddo
2012-07-20 21:03:13 +05:30
do j = 1_pInt , 9_pInt
2012-12-15 21:51:10 +05:30
if ( temp_maskVector ( j ) ) temp_valueVector ( j ) = IO_floatValue ( line , positions , i + j ) ! read value where applicable
2012-07-19 22:54:56 +05:30
enddo
2012-08-03 14:55:48 +05:30
loadCases ( currentLoadCase ) % P % maskLogical = transpose ( reshape ( temp_maskVector , [ 3 , 3 ] ) )
2012-10-19 14:14:21 +05:30
loadCases ( currentLoadCase ) % P % maskFloat = merge ( ones , zeros , &
2012-08-03 14:55:48 +05:30
loadCases ( currentLoadCase ) % P % maskLogical )
loadCases ( currentLoadCase ) % P % values = math_plain9to33 ( temp_valueVector )
2012-07-19 22:54:56 +05:30
case ( 't' , 'time' , 'delta' ) ! increment time
2012-08-03 14:55:48 +05:30
loadCases ( currentLoadCase ) % time = IO_floatValue ( line , positions , i + 1_pInt )
2012-07-19 22:54:56 +05:30
case ( 'temp' , 'temperature' ) ! starting temperature
2012-08-03 14:55:48 +05:30
loadCases ( currentLoadCase ) % temperature = IO_floatValue ( line , positions , i + 1_pInt )
2013-07-26 21:55:37 +05:30
case ( 'den' , 'density' ) ! starting density
loadCases ( currentLoadCase ) % density = IO_floatValue ( line , positions , i + 1_pInt )
2012-07-19 22:54:56 +05:30
case ( 'n' , 'incs' , 'increments' , 'steps' ) ! number of increments
2012-08-03 14:55:48 +05:30
loadCases ( currentLoadCase ) % incs = IO_intValue ( line , positions , i + 1_pInt )
2012-07-19 22:54:56 +05:30
case ( 'logincs' , 'logincrements' , 'logsteps' ) ! number of increments (switch to log time scaling)
2012-08-03 14:55:48 +05:30
loadCases ( currentLoadCase ) % incs = IO_intValue ( line , positions , i + 1_pInt )
loadCases ( currentLoadCase ) % logscale = 1_pInt
2013-02-23 05:54:30 +05:30
case ( 'freq' , 'frequency' , 'outputfreq' ) ! frequency of result writings
2012-08-03 14:55:48 +05:30
loadCases ( currentLoadCase ) % outputfrequency = IO_intValue ( line , positions , i + 1_pInt )
2012-07-19 22:54:56 +05:30
case ( 'r' , 'restart' , 'restartwrite' ) ! frequency of writing restart information
2012-12-15 21:51:10 +05:30
loadCases ( currentLoadCase ) % restartfrequency = &
max ( 0_pInt , IO_intValue ( line , positions , i + 1_pInt ) )
2012-07-19 22:54:56 +05:30
case ( 'guessreset' , 'dropguessing' )
2012-10-24 17:01:40 +05:30
loadCases ( currentLoadCase ) % followFormerTrajectory = . false . ! do not continue to predict deformation along former trajectory
2012-08-03 14:55:48 +05:30
case ( 'euler' ) ! rotation of currentLoadCase given in euler angles
2012-11-09 03:03:58 +05:30
temp_valueVector = 0.0_pReal
2012-11-28 20:34:05 +05:30
l = 1_pInt ! assuming values given in degrees
k = 1_pInt ! assuming keyword indicating degree/radians present
2012-07-20 21:03:13 +05:30
select case ( IO_lc ( IO_stringValue ( line , positions , i + 1_pInt ) ) )
2012-07-19 22:54:56 +05:30
case ( 'deg' , 'degree' )
2012-11-28 20:34:05 +05:30
case ( 'rad' , 'radian' ) ! don't convert from degree to radian
l = 0_pInt
case default
k = 0_pInt
2012-07-19 22:54:56 +05:30
end select
2013-02-06 22:15:34 +05:30
do j = 1_pInt , 3_pInt
temp_valueVector ( j ) = IO_floatValue ( line , positions , i + k + j )
enddo
2012-11-28 20:34:05 +05:30
if ( l == 1_pInt ) temp_valueVector ( 1 : 3 ) = temp_valueVector ( 1 : 3 ) * inRad ! convert to rad
2012-09-06 19:35:28 +05:30
loadCases ( currentLoadCase ) % rotation = math_EulerToR ( temp_valueVector ( 1 : 3 ) ) ! convert rad Eulers to rotation matrix
2012-08-03 14:55:48 +05:30
case ( 'rotation' , 'rot' ) ! assign values for the rotation of currentLoadCase matrix
2012-07-19 22:54:56 +05:30
temp_valueVector = 0.0_pReal
2013-02-06 22:15:34 +05:30
do j = 1_pInt , 9_pInt
temp_valueVector ( j ) = IO_floatValue ( line , positions , i + j )
enddo
2012-08-03 14:55:48 +05:30
loadCases ( currentLoadCase ) % rotation = math_plain9to33 ( temp_valueVector )
2012-07-19 22:54:56 +05:30
end select
enddo ; enddo
2013-06-27 00:49:00 +05:30
close ( myUnit )
2012-08-03 14:55:48 +05:30
2012-07-19 22:54:56 +05:30
!--------------------------------------------------------------------------------------------------
! consistency checks and output of load case
2012-10-24 17:01:40 +05:30
loadCases ( 1 ) % followFormerTrajectory = . false . ! cannot guess along trajectory for first inc of first currentLoadCase
2012-07-19 22:54:56 +05:30
errorID = 0_pInt
2012-08-03 14:55:48 +05:30
checkLoadcases : do currentLoadCase = 1_pInt , size ( loadCases )
write ( loadcase_string , '(i6)' ) currentLoadCase
2012-10-02 20:56:56 +05:30
write ( 6 , '(1x,a,i6)' ) 'load case: ' , currentLoadCase
2012-10-24 17:01:40 +05:30
if ( . not . loadCases ( currentLoadCase ) % followFormerTrajectory ) &
write ( 6 , '(2x,a)' ) 'drop guessing along trajectory'
2012-08-03 14:55:48 +05:30
if ( loadCases ( currentLoadCase ) % deformation % myType == 'l' ) then
2012-07-19 22:54:56 +05:30
do j = 1_pInt , 3_pInt
2012-08-03 14:55:48 +05:30
if ( any ( loadCases ( currentLoadCase ) % deformation % maskLogical ( j , 1 : 3 ) . eqv . . true . ) . and . &
2012-10-24 17:01:40 +05:30
any ( loadCases ( currentLoadCase ) % deformation % maskLogical ( j , 1 : 3 ) . eqv . . false . ) ) &
errorID = 832_pInt ! each row should be either fully or not at all defined
2012-07-19 22:54:56 +05:30
enddo
2012-08-03 14:55:48 +05:30
write ( 6 , '(2x,a)' ) 'velocity gradient:'
2013-05-13 15:14:23 +05:30
else if ( loadCases ( currentLoadCase ) % deformation % myType == 'f' ) then
write ( 6 , '(2x,a)' ) 'deformation gradient at end of load case:'
2012-07-19 22:54:56 +05:30
else
2012-08-03 14:55:48 +05:30
write ( 6 , '(2x,a)' ) 'deformation gradient rate:'
2012-07-19 22:54:56 +05:30
endif
2012-10-24 17:01:40 +05:30
write ( 6 , '(3(3(3x,f12.7,1x)/))' , advance = 'no' ) &
merge ( math_transpose33 ( loadCases ( currentLoadCase ) % deformation % values ) , &
2012-12-15 21:51:10 +05:30
reshape ( spread ( huge ( 1.0_pReal ) , 1 , 9 ) , [ 3 , 3 ] ) , & ! print *** (huge) for undefined
2012-10-24 17:01:40 +05:30
transpose ( loadCases ( currentLoadCase ) % deformation % maskLogical ) )
if ( any ( loadCases ( currentLoadCase ) % P % maskLogical . eqv . &
loadCases ( currentLoadCase ) % deformation % maskLogical ) ) errorID = 831_pInt ! exclusive or masking only
if ( any ( loadCases ( currentLoadCase ) % P % maskLogical . and . &
transpose ( loadCases ( currentLoadCase ) % P % maskLogical ) . and . &
reshape ( [ . false . , . true . , . true . , . true . , . false . , . true . , . true . , . true . , . false . ] , [ 3 , 3 ] ) ) ) &
errorID = 838_pInt ! no rotation is allowed by stress BC
2012-10-02 20:56:56 +05:30
write ( 6 , '(2x,a,/,3(3(3x,f12.7,1x)/))' , advance = 'no' ) 'stress / GPa:' , &
2012-10-24 17:01:40 +05:30
1e-9_pReal * merge ( math_transpose33 ( loadCases ( currentLoadCase ) % P % values ) , &
reshape ( spread ( huge ( 1.0_pReal ) , 1 , 9 ) , [ 3 , 3 ] ) , &
transpose ( loadCases ( currentLoadCase ) % P % maskLogical ) )
if ( any ( abs ( math_mul33x33 ( loadCases ( currentLoadCase ) % rotation , &
math_transpose33 ( loadCases ( currentLoadCase ) % rotation ) ) - math_I3 ) > &
reshape ( spread ( rotation_tol , 1 , 9 ) , [ 3 , 3 ] ) ) &
. or . abs ( math_det33 ( loadCases ( currentLoadCase ) % rotation ) ) > &
1.0_pReal + rotation_tol ) errorID = 846_pInt ! given rotation matrix contains strain
2012-08-03 14:55:48 +05:30
if ( any ( loadCases ( currentLoadCase ) % rotation / = math_I3 ) ) &
2012-10-02 20:56:56 +05:30
write ( 6 , '(2x,a,/,3(3(3x,f12.7,1x)/))' , advance = 'no' ) 'rotation of loadframe:' , &
2012-10-24 17:01:40 +05:30
math_transpose33 ( loadCases ( currentLoadCase ) % rotation )
2012-08-03 14:55:48 +05:30
write ( 6 , '(2x,a,f12.6)' ) 'temperature:' , loadCases ( currentLoadCase ) % temperature
2013-07-26 21:55:37 +05:30
write ( 6 , '(2x,a,f12.6)' ) 'density: ' , loadCases ( currentLoadCase ) % density
2012-10-24 17:01:40 +05:30
if ( loadCases ( currentLoadCase ) % time < 0.0_pReal ) errorID = 834_pInt ! negative time increment
2012-08-03 14:55:48 +05:30
write ( 6 , '(2x,a,f12.6)' ) 'time: ' , loadCases ( currentLoadCase ) % time
2012-10-24 17:01:40 +05:30
if ( loadCases ( currentLoadCase ) % incs < 1_pInt ) errorID = 835_pInt ! non-positive incs count
2012-08-03 14:55:48 +05:30
write ( 6 , '(2x,a,i5)' ) 'increments: ' , loadCases ( currentLoadCase ) % incs
2012-10-24 17:01:40 +05:30
if ( loadCases ( currentLoadCase ) % outputfrequency < 1_pInt ) errorID = 836_pInt ! non-positive result frequency
write ( 6 , '(2x,a,i5)' ) 'output frequency: ' , &
loadCases ( currentLoadCase ) % outputfrequency
write ( 6 , '(2x,a,i5,/)' ) 'restart frequency: ' , &
loadCases ( currentLoadCase ) % restartfrequency
2012-12-15 21:51:10 +05:30
if ( errorID > 0_pInt ) call IO_error ( error_ID = errorID , ext_msg = loadcase_string ) ! exit with error message
2012-07-24 22:37:10 +05:30
enddo checkLoadcases
2012-07-20 21:03:13 +05:30
2012-12-15 21:51:10 +05:30
!--------------------------------------------------------------------------------------------------
! doing initialization depending on selected solver
2012-08-03 14:55:48 +05:30
select case ( myspectralsolver )
case ( DAMASK_spectral_SolverBasic_label )
2013-01-09 23:38:08 +05:30
call basic_init ( loadCases ( 1 ) % temperature )
2012-08-29 00:49:47 +05:30
#ifdef PETSc
2012-10-02 20:56:56 +05:30
case ( DAMASK_spectral_SolverBasicPETSc_label )
2013-01-09 23:38:08 +05:30
call basicPETSc_init ( loadCases ( 1 ) % temperature )
2012-08-06 14:23:12 +05:30
case ( DAMASK_spectral_SolverAL_label )
2013-05-08 21:22:29 +05:30
if ( iand ( debug_level ( debug_spectral ) , debug_levelBasic ) / = 0 ) &
call IO_warning ( 42_pInt , ext_msg = 'debug Divergence' )
2013-01-09 23:38:08 +05:30
call AL_init ( loadCases ( 1 ) % temperature )
2013-07-24 18:36:16 +05:30
case ( DAMASK_spectral_SolverPolarisation_label )
if ( iand ( debug_level ( debug_spectral ) , debug_levelBasic ) / = 0 ) &
call IO_warning ( 42_pInt , ext_msg = 'debug Divergence' )
call Polarisation_init ( loadCases ( 1 ) % temperature )
2012-08-29 00:49:47 +05:30
#endif
case default
call IO_error ( error_ID = 891 , ext_msg = trim ( myspectralsolver ) )
2012-08-03 14:55:48 +05:30
end select
2012-08-29 00:49:47 +05:30
2012-07-20 21:03:13 +05:30
!--------------------------------------------------------------------------------------------------
! write header of output file
2012-12-15 21:51:10 +05:30
if ( appendToOutFile ) then ! after restart, append to existing results file
2012-10-19 14:14:21 +05:30
open ( newunit = resUnit , file = trim ( getSolverWorkingDirectoryName ( ) ) / / trim ( getSolverJobName ( ) ) / / &
2012-10-24 17:01:40 +05:30
'.spectralOut' , form = 'UNFORMATTED' , position = 'APPEND' , status = 'OLD' )
2013-04-25 19:33:54 +05:30
! '.spectralOut',access='STREAM', position='APPEND', status='OLD')
2012-10-19 14:14:21 +05:30
open ( newunit = statUnit , file = trim ( getSolverWorkingDirectoryName ( ) ) / / trim ( getSolverJobName ( ) ) / / &
2012-10-24 17:01:40 +05:30
'.sta' , form = 'FORMATTED' , position = 'APPEND' , status = 'OLD' )
2012-12-15 21:51:10 +05:30
else ! open new files ...
2012-10-19 14:14:21 +05:30
open ( newunit = resUnit , file = trim ( getSolverWorkingDirectoryName ( ) ) / / trim ( getSolverJobName ( ) ) / / &
2012-10-24 17:01:40 +05:30
'.spectralOut' , form = 'UNFORMATTED' , status = 'REPLACE' )
2013-04-25 19:33:54 +05:30
! '.spectralOut',access='STREAM',status='REPLACE')
2012-12-15 21:51:10 +05:30
write ( resUnit ) 'load' , trim ( loadCaseFile ) ! ... and write header
2012-10-19 14:14:21 +05:30
write ( resUnit ) 'workingdir' , trim ( getSolverWorkingDirectoryName ( ) )
write ( resUnit ) 'geometry' , trim ( geometryFile )
2013-05-08 21:22:29 +05:30
!write(resUnit) 'grid', grid
!write(resUnit) 'size', geomSize
write ( resUnit ) 'resolution' , grid
write ( resUnit ) 'dimension' , geomSize
2012-10-19 14:14:21 +05:30
write ( resUnit ) 'materialpoint_sizeResults' , materialpoint_sizeResults
write ( resUnit ) 'loadcases' , size ( loadCases )
2012-10-24 17:01:40 +05:30
write ( resUnit ) 'frequencies' , loadCases % outputfrequency ! one entry per currentLoadCase
write ( resUnit ) 'times' , loadCases % time ! one entry per currentLoadCase
2012-10-19 14:14:21 +05:30
write ( resUnit ) 'logscales' , loadCases % logscale
2012-10-24 17:01:40 +05:30
write ( resUnit ) 'increments' , loadCases % incs ! one entry per currentLoadCase
write ( resUnit ) 'startingIncrement' , restartInc - 1_pInt ! start with writing out the previous inc
write ( resUnit ) 'eoh' ! end of header
2013-07-01 12:10:09 +05:30
write ( resUnit ) materialpoint_results ! initial (non-deformed or read-in) results
2012-10-24 17:01:40 +05:30
open ( newunit = statUnit , file = trim ( getSolverWorkingDirectoryName ( ) ) / / trim ( getSolverJobName ( ) ) / / &
'.sta' , form = 'FORMATTED' , status = 'REPLACE' )
2012-12-15 21:51:10 +05:30
write ( statUnit , '(a)' ) 'Increment Time CutbackLevel Converged IterationsNeeded' ! statistics file
2013-05-08 21:22:29 +05:30
if ( iand ( debug_level ( debug_spectral ) , debug_levelBasic ) / = 0 ) &
write ( 6 , '(/,a)' ) ' header of result file written out'
2013-01-10 03:49:32 +05:30
flush ( 6 )
2012-07-20 21:03:13 +05:30
endif
2013-02-23 05:54:30 +05:30
2012-08-03 14:55:48 +05:30
!--------------------------------------------------------------------------------------------------
! loopping over loadcases
loadCaseLooping : do currentLoadCase = 1_pInt , size ( loadCases )
time0 = time ! currentLoadCase start time
if ( loadCases ( currentLoadCase ) % followFormerTrajectory ) then
2012-11-09 01:02:00 +05:30
guess = . true .
2012-07-19 22:54:56 +05:30
else
2012-11-09 01:02:00 +05:30
guess = . false . ! change of load case, homogeneous guess for the first inc
2012-07-19 22:54:56 +05:30
endif
2012-08-03 14:55:48 +05:30
!--------------------------------------------------------------------------------------------------
! loop oper incs defined in input file for current currentLoadCase
incLooping : do inc = 1_pInt , loadCases ( currentLoadCase ) % incs
2012-07-19 22:54:56 +05:30
totalIncsCounter = totalIncsCounter + 1_pInt
!--------------------------------------------------------------------------------------------------
! forwarding time
2013-05-13 15:14:23 +05:30
timeIncOld = timeinc
2012-10-02 20:56:56 +05:30
if ( loadCases ( currentLoadCase ) % logscale == 0_pInt ) then ! linear scale
timeinc = loadCases ( currentLoadCase ) % time / loadCases ( currentLoadCase ) % incs ! only valid for given linear time scale. will be overwritten later in case loglinear scale is used
2012-07-19 22:54:56 +05:30
else
2012-10-02 20:56:56 +05:30
if ( currentLoadCase == 1_pInt ) then ! 1st currentLoadCase of logarithmic scale
2012-08-03 14:55:48 +05:30
if ( inc == 1_pInt ) then ! 1st inc of 1st currentLoadCase of logarithmic scale
2012-10-02 20:56:56 +05:30
timeinc = loadCases ( 1 ) % time * ( 2.0_pReal ** real ( 1_pInt - loadCases ( 1 ) % incs , pReal ) ) ! assume 1st inc is equal to 2nd
2012-08-03 14:55:48 +05:30
else ! not-1st inc of 1st currentLoadCase of logarithmic scale
timeinc = loadCases ( 1 ) % time * ( 2.0_pReal ** real ( inc - 1_pInt - loadCases ( 1 ) % incs , pReal ) )
2012-07-19 22:54:56 +05:30
endif
2012-08-03 14:55:48 +05:30
else ! not-1st currentLoadCase of logarithmic scale
2012-12-15 21:51:10 +05:30
timeinc = time0 * &
( ( 1.0_pReal + loadCases ( currentLoadCase ) % time / time0 ) ** ( real ( inc , pReal ) / &
real ( loadCases ( currentLoadCase ) % incs , pReal ) ) &
- ( 1.0_pReal + loadCases ( currentLoadCase ) % time / time0 ) ** ( real ( ( inc - 1_pInt ) , pReal ) / &
real ( loadCases ( currentLoadCase ) % incs , pReal ) ) )
2012-07-19 22:54:56 +05:30
endif
endif
2012-12-15 21:51:10 +05:30
timeinc = timeinc / 2.0_pReal ** real ( cutBackLevel , pReal ) ! depending on cut back level, decrease time step
2012-07-19 22:54:56 +05:30
2013-01-29 15:58:01 +05:30
forwarding : if ( totalIncsCounter > = restartInc ) then
2012-10-02 20:56:56 +05:30
stepFraction = 0_pInt
2013-02-23 05:54:30 +05:30
2012-07-19 22:54:56 +05:30
!--------------------------------------------------------------------------------------------------
2012-12-15 21:51:10 +05:30
! loop over sub incs
2013-01-08 03:12:00 +05:30
subIncLooping : do while ( stepFraction / subStepFactor ** cutBackLevel < 1_pInt )
2012-12-15 21:51:10 +05:30
time = time + timeinc ! forward time
2012-10-02 20:56:56 +05:30
stepFraction = stepFraction + 1_pInt
2013-05-13 15:14:23 +05:30
remainingLoadCaseTime = time0 - time + loadCases ( currentLoadCase ) % time + timeInc
2012-12-15 21:51:10 +05:30
!--------------------------------------------------------------------------------------------------
! report begin of new increment
2013-01-10 03:49:32 +05:30
write ( 6 , '(/,a)' ) ' ###########################################################################'
write ( 6 , '(1x,a,es12.5' / / &
2012-10-02 20:56:56 +05:30
',a,' / / IO_intOut ( inc ) / / ',a,' / / IO_intOut ( loadCases ( currentLoadCase ) % incs ) / / &
2013-01-08 03:12:00 +05:30
',a,' / / IO_intOut ( stepFraction ) / / ',a,' / / IO_intOut ( subStepFactor ** cutBackLevel ) / / &
2012-10-02 20:56:56 +05:30
',a,' / / IO_intOut ( currentLoadCase ) / / ',a,' / / IO_intOut ( size ( loadCases ) ) / / ')' ) &
2012-10-24 17:01:40 +05:30
'Time' , time , &
's: Increment ' , inc , '/' , loadCases ( currentLoadCase ) % incs , &
2013-01-08 03:12:00 +05:30
'-' , stepFraction , '/' , subStepFactor ** cutBackLevel , &
2012-10-24 17:01:40 +05:30
' of load case ' , currentLoadCase , '/' , size ( loadCases )
2013-01-10 03:49:32 +05:30
flush ( 6 )
2013-01-10 19:03:43 +05:30
write ( incInfo , '(a,' / / IO_intOut ( totalIncsCounter ) / / ',a,' / / IO_intOut ( sum ( loadCases % incs ) ) / / &
2013-01-08 03:12:00 +05:30
',a,' / / IO_intOut ( stepFraction ) / / ',a,' / / IO_intOut ( subStepFactor ** cutBackLevel ) / / ')' ) &
2013-01-10 19:03:43 +05:30
'Increment ' , totalIncsCounter , '/' , sum ( loadCases % incs ) , &
2013-01-08 03:12:00 +05:30
'-' , stepFraction , '/' , subStepFactor ** cutBackLevel
2012-10-02 20:56:56 +05:30
select case ( myspectralsolver )
2012-12-15 21:51:10 +05:30
!--------------------------------------------------------------------------------------------------
! calculate solution
2012-10-02 20:56:56 +05:30
case ( DAMASK_spectral_SolverBasic_label )
solres = basic_solution ( &
2013-05-13 15:14:23 +05:30
incInfo , guess , timeinc , timeIncOld , remainingLoadCaseTime , &
2013-01-09 23:38:08 +05:30
P_BC = loadCases ( currentLoadCase ) % P , &
F_BC = loadCases ( currentLoadCase ) % deformation , &
temperature_bc = loadCases ( currentLoadCase ) % temperature , &
rotation_BC = loadCases ( currentLoadCase ) % rotation )
2012-08-29 00:49:47 +05:30
#ifdef PETSc
2012-10-02 20:56:56 +05:30
case ( DAMASK_spectral_SolverBasicPETSC_label )
solres = BasicPETSC_solution ( &
2013-05-13 15:14:23 +05:30
incInfo , guess , timeinc , timeIncOld , remainingLoadCaseTime , &
2013-01-09 23:38:08 +05:30
P_BC = loadCases ( currentLoadCase ) % P , &
F_BC = loadCases ( currentLoadCase ) % deformation , &
temperature_bc = loadCases ( currentLoadCase ) % temperature , &
2013-07-26 21:55:37 +05:30
rotation_BC = loadCases ( currentLoadCase ) % rotation , &
density = loadCases ( currentLoadCase ) % density )
2012-10-02 20:56:56 +05:30
case ( DAMASK_spectral_SolverAL_label )
solres = AL_solution ( &
2013-05-13 15:14:23 +05:30
incInfo , guess , timeinc , timeIncOld , remainingLoadCaseTime , &
2013-01-09 23:38:08 +05:30
P_BC = loadCases ( currentLoadCase ) % P , &
F_BC = loadCases ( currentLoadCase ) % deformation , &
temperature_bc = loadCases ( currentLoadCase ) % temperature , &
2013-07-26 21:55:37 +05:30
rotation_BC = loadCases ( currentLoadCase ) % rotation , &
density = loadCases ( currentLoadCase ) % density )
2013-07-24 18:36:16 +05:30
case ( DAMASK_spectral_SolverPolarisation_label )
solres = Polarisation_solution ( &
incInfo , guess , timeinc , timeIncOld , remainingLoadCaseTime , &
P_BC = loadCases ( currentLoadCase ) % P , &
F_BC = loadCases ( currentLoadCase ) % deformation , &
temperature_bc = loadCases ( currentLoadCase ) % temperature , &
2013-07-26 21:55:37 +05:30
rotation_BC = loadCases ( currentLoadCase ) % rotation , &
density = loadCases ( currentLoadCase ) % density )
2012-08-29 00:49:47 +05:30
#endif
2012-10-02 20:56:56 +05:30
end select
2013-02-23 05:54:30 +05:30
2012-12-15 21:51:10 +05:30
!--------------------------------------------------------------------------------------------------
! check solution
2013-04-26 14:43:39 +05:30
cutBack = . False .
2012-10-02 20:56:56 +05:30
if ( solres % termIll . or . . not . solres % converged ) then ! no solution found
if ( cutBackLevel < maxCutBack ) then ! do cut back
2013-01-18 17:00:52 +05:30
write ( 6 , '(/,a)' ) ' cut back detected'
2012-10-02 20:56:56 +05:30
cutBack = . True .
2013-01-08 03:12:00 +05:30
stepFraction = ( stepFraction - 1_pInt ) * subStepFactor ! adjust to new denominator
2012-10-02 20:56:56 +05:30
cutBackLevel = cutBackLevel + 1_pInt
2012-12-15 21:51:10 +05:30
time = time - timeinc ! rewind time
2013-05-13 15:14:23 +05:30
timeIncOld = timeinc
2012-10-02 20:56:56 +05:30
timeinc = timeinc / 2.0_pReal
elseif ( solres % termIll ) then ! material point model cannot find a solution
2013-01-08 03:12:00 +05:30
if ( regridMode > 0_pInt ) call quit ( - 1_pInt * ( lastRestartWritten + 1_pInt ) ) ! regrid requested (mode 1 or 2)
2012-12-15 21:51:10 +05:30
call IO_error ( 850_pInt ) ! no regrid (give up)
2012-10-02 20:56:56 +05:30
else
2013-01-08 03:12:00 +05:30
if ( regridMode == 2_pInt ) call quit ( - 1_pInt * ( lastRestartWritten + 1_pInt ) ) ! regrid also if BVP solver do not converge
2012-12-15 21:51:10 +05:30
guess = . true . ! continue from non-converged solution and start guessing after accepted (sub)inc
2012-10-02 20:56:56 +05:30
endif
else
2012-11-09 01:02:00 +05:30
guess = . true . ! start guessing after first converged (sub)inc
2012-10-02 20:56:56 +05:30
endif
2013-04-26 18:53:36 +05:30
if ( . not . cutBack ) &
write ( statUnit , * ) totalIncsCounter , time , cutBackLevel , &
solres % converged , solres % iterationsNeeded ! write statistics about accepted solution
2012-10-02 20:56:56 +05:30
enddo subIncLooping
2012-12-15 21:51:10 +05:30
cutBackLevel = max ( 0_pInt , cutBackLevel - 1_pInt ) ! try half number of subincs next inc
if ( solres % converged ) then ! report converged inc
2012-07-19 22:54:56 +05:30
convergedCounter = convergedCounter + 1_pInt
2013-02-23 05:54:30 +05:30
write ( 6 , '(/,a,' / / IO_intOut ( totalIncsCounter ) / / ',a)' ) &
2013-01-10 03:49:32 +05:30
' increment ' , totalIncsCounter , ' converged'
2012-07-20 21:03:13 +05:30
else
2013-02-23 05:54:30 +05:30
write ( 6 , '(/,a,' / / IO_intOut ( totalIncsCounter ) / / ',a)' ) & ! report non-converged inc
2013-01-10 03:49:32 +05:30
' increment ' , totalIncsCounter , ' NOT converged'
2012-07-20 21:03:13 +05:30
notConvergedCounter = notConvergedCounter + 1_pInt
2013-02-23 05:54:30 +05:30
endif ; flush ( 6 )
2012-07-19 22:54:56 +05:30
2012-10-02 20:56:56 +05:30
if ( mod ( inc , loadCases ( currentLoadCase ) % outputFrequency ) == 0_pInt ) then ! at output frequency
2013-01-10 03:49:32 +05:30
write ( 6 , '(1/,a)' ) ' ... writing results to file ......................................'
2012-12-15 21:51:10 +05:30
write ( resUnit ) materialpoint_results ! write result to file
2012-07-19 22:54:56 +05:30
endif
2013-06-11 22:05:04 +05:30
if ( loadCases ( currentLoadCase ) % restartFrequency > 0_pInt . and . & ! at frequency of writing restart information set restart parameter for FEsolving
mod ( inc , loadCases ( currentLoadCase ) % restartFrequency ) == 0_pInt ) then ! ToDo first call to CPFEM_general will write?
2012-10-24 17:01:40 +05:30
restartWrite = . true .
2012-12-14 20:48:04 +05:30
lastRestartWritten = inc
2012-10-24 17:01:40 +05:30
endif
2013-01-29 15:58:01 +05:30
else forwarding
2012-10-24 17:01:40 +05:30
time = time + timeinc
2012-11-09 01:02:00 +05:30
guess = . true .
2013-01-29 15:58:01 +05:30
endif forwarding
2012-07-20 21:03:13 +05:30
2012-07-24 22:37:10 +05:30
enddo incLooping
enddo loadCaseLooping
2012-08-03 14:55:48 +05:30
2012-07-25 19:31:39 +05:30
select case ( myspectralsolver )
case ( DAMASK_spectral_SolverBasic_label )
call basic_destroy ( )
2012-08-29 00:49:47 +05:30
#ifdef PETSc
2012-08-14 22:28:23 +05:30
case ( DAMASK_spectral_SolverBasicPETSC_label )
call BasicPETSC_destroy ( )
2012-08-06 14:23:12 +05:30
case ( DAMASK_spectral_SolverAL_label )
call AL_destroy ( )
2013-07-24 18:36:16 +05:30
case ( DAMASK_spectral_SolverPolarisation_label )
call Polarisation_destroy ( )
2012-08-29 00:49:47 +05:30
#endif
2012-08-03 14:55:48 +05:30
end select
2012-12-15 21:51:10 +05:30
!--------------------------------------------------------------------------------------------------
2013-02-23 05:54:30 +05:30
! report summary of whole calculation
2013-08-08 14:43:29 +05:30
write ( 6 , '(/,a)' ) ' ###########################################################################'
2013-01-10 03:49:32 +05:30
write ( 6 , '(1x,i6.6,a,i6.6,a,f5.1,a)' ) convergedCounter , ' out of ' , &
2012-07-20 21:03:13 +05:30
notConvergedCounter + convergedCounter , ' (' , &
real ( convergedCounter , pReal ) / &
real ( notConvergedCounter + convergedCounter , pReal ) * 10 0.0_pReal , &
' %) increments converged!'
2012-10-19 14:14:21 +05:30
close ( resUnit )
2012-12-15 21:51:10 +05:30
if ( notConvergedCounter > 0_pInt ) call quit ( 3_pInt ) ! error if some are not converged
call quit ( 0_pInt ) ! no complains ;)
2012-07-20 21:03:13 +05:30
2012-07-24 22:37:10 +05:30
end program DAMASK_spectral_Driver
2012-07-20 21:03:13 +05:30
2013-02-23 05:54:30 +05:30
!--------------------------------------------------------------------------------------------------
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
!> @brief quit subroutine to mimic behavior of FEM solvers
!> @details exits the Spectral solver and reports time and duration. Exit code 0 signals
!> everything went fine. Exit code 1 signals an error, message according to IO_error. Exit code
!> 2 signals request for regridding, increment of last saved restart information is written to
!> stderr. Exit code 3 signals no severe problems, but some increments did not converge
!--------------------------------------------------------------------------------------------------
2013-02-19 20:24:34 +05:30
subroutine quit ( stop_id )
use prec , only : &
pInt
implicit none
integer ( pInt ) , intent ( in ) :: stop_id
integer , dimension ( 8 ) :: dateAndTime ! type default integer
call date_and_time ( values = dateAndTime )
write ( 6 , '(/,a)' ) 'DAMASK terminated on:'
write ( 6 , '(a,2(i2.2,a),i4.4)' ) 'Date: ' , dateAndTime ( 3 ) , '/' , &
dateAndTime ( 2 ) , '/' , &
dateAndTime ( 1 )
write ( 6 , '(a,2(i2.2,a),i2.2)' ) 'Time: ' , dateAndTime ( 5 ) , ':' , &
dateAndTime ( 6 ) , ':' , &
dateAndTime ( 7 )
if ( stop_id == 0_pInt ) stop 0 ! normal termination
if ( stop_id < 0_pInt ) then ! trigger regridding
write ( 0 , '(a,i6)' ) 'restart at ' , stop_id * ( - 1_pInt )
stop 2
endif
2013-02-23 05:54:30 +05:30
if ( stop_id == 3_pInt ) stop 3 ! not all incs converged
2013-02-19 20:24:34 +05:30
stop 1 ! error (message from IO_error)
2013-02-23 05:54:30 +05:30
end subroutine quit