2011-04-07 12:50:28 +05:30
! Copyright 2011 Max-Planck-Institut für Eisenforschung GmbH
2011-04-04 19:39:54 +05:30
!
! This file is part of DAMASK,
2011-04-07 12:50:28 +05:30
! the Düsseldorf Advanced MAterial Simulation Kit.
2011-04-04 19:39:54 +05:30
!
! 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/>.
!
!##############################################################
2010-06-08 15:40:57 +05:30
!* $Id$
2010-06-08 15:38:15 +05:30
!********************************************************************
! Material subroutine for BVP solution using spectral method
!
! written by P. Eisenlohr,
! F. Roters,
! L. Hantcherli,
2011-02-07 20:05:42 +05:30
! W.A. Counts,
! D.D. Tjahjanto,
! C. Kords,
! M. Diehl,
2010-06-08 15:38:15 +05:30
! R. Lebensohn
!
! MPI fuer Eisenforschung, Duesseldorf
!
!********************************************************************
! Usage:
2011-05-11 22:08:45 +05:30
! - start program with DAMASK_spectral PathToGeomFile/NameOfGeom.geom
2010-06-08 15:38:15 +05:30
! PathToLoadFile/NameOfLoadFile.load
2011-02-07 20:05:42 +05:30
! - PathToGeomFile will be the working directory
2010-06-08 15:38:15 +05:30
! - make sure the file "material.config" exists in the working
2011-02-07 20:05:42 +05:30
! directory. For further configuration use "numerics.config"
2010-06-10 20:21:10 +05:30
!********************************************************************
2011-05-11 22:08:45 +05:30
program DAMASK_spectral
2010-06-10 20:21:10 +05:30
!********************************************************************
2010-06-08 15:38:15 +05:30
2011-05-11 22:31:03 +05:30
use DAMASK_interface
2010-06-10 20:21:10 +05:30
use prec , only : pInt , pReal
use IO
2010-07-05 21:31:36 +05:30
use math
2011-05-26 14:53:13 +05:30
use mesh , only : mesh_ipCenterOfGravity
2011-01-07 18:26:45 +05:30
use CPFEM , only : CPFEM_general , CPFEM_initAll
2011-02-07 20:05:42 +05:30
use numerics , only : err_div_tol , err_stress_tol , err_stress_tolrel , err_defgrad_tol , &
2011-07-29 21:27:39 +05:30
relevantStrain , itmax , memory_efficient , DAMASK_NumThreadsInt
2010-10-27 22:45:49 +05:30
use homogenization , only : materialpoint_sizeResults , materialpoint_results
2011-01-07 18:26:45 +05:30
!$ use OMP_LIB ! the openMP function library
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
2010-06-08 15:38:15 +05:30
implicit none
2011-05-11 22:08:45 +05:30
include 'include/fftw3.f' ! header file for fftw3 (declaring variables). Library files are also needed
2011-07-07 15:33:55 +05:30
! compile FFTW 3.2.2 with ./configure --enable-threads
2011-01-07 18:26:45 +05:30
! variables to read from loadcase and geom file
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
real ( pReal ) , dimension ( 9 ) :: valuevector ! stores information temporarily from loadcase file
2011-06-15 23:18:14 +05:30
integer ( pInt ) , parameter :: maxNchunksInput = 26 ! 5 identifiers, 18 values for the matrices and 3 scalars
2010-06-25 17:01:05 +05:30
integer ( pInt ) , dimension ( 1 + maxNchunksInput * 2 ) :: posInput
2011-01-07 18:26:45 +05:30
integer ( pInt ) , parameter :: maxNchunksGeom = 7 ! 4 identifiers, 3 values
integer ( pInt ) , dimension ( 1 + 2 * maxNchunksGeom ) :: posGeom
2011-08-02 19:28:28 +05:30
integer ( pInt ) unit , N_l , N_s , N_t , N_n , N_freq , N_Fdot , N_temperature ! numbers of identifiers
2010-09-22 17:34:43 +05:30
character ( len = 1024 ) path , line
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
logical gotResolution , gotDimension , gotHomogenization
logical , dimension ( 9 ) :: bc_maskvector
2010-07-02 19:40:36 +05:30
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
! variables storing information from loadcase file
2011-07-25 22:00:21 +05:30
real ( pReal ) time , time0 , timeinc ! elapsed time, begin of interval, time interval
real ( pReal ) , dimension ( : , : , : ) , allocatable :: bc_deformation , & ! applied velocity gradient or time derivative of deformation gradient
bc_stress ! stress BC (if applicable)
2011-08-02 19:28:28 +05:30
real ( pReal ) , dimension ( : ) , allocatable :: bc_timeIncrement , & ! length of increment
bc_temperature ! isothermal starting conditions
2011-07-25 22:00:21 +05:30
integer ( pInt ) N_Loadcases , step ! ToDo: rename?
integer ( pInt ) , dimension ( : ) , allocatable :: bc_steps , & ! number of steps
bc_frequency , & ! frequency of result writes
bc_logscale ! linear/logaritmic time step flag
logical , dimension ( : ) , allocatable :: followFormerTrajectory , & ! follow trajectory of former loadcase
velGradApplied ! decide wether velocity gradient or fdot is given
logical , dimension ( : , : , : , : ) , allocatable :: bc_mask ! mask of boundary conditions
2010-07-01 20:50:06 +05:30
2011-01-07 18:26:45 +05:30
! variables storing information from geom file
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
real ( pReal ) wgt
2011-01-07 18:26:45 +05:30
real ( pReal ) , dimension ( 3 ) :: geomdimension
2011-02-09 23:17:28 +05:30
integer ( pInt ) homog
2010-09-22 17:34:43 +05:30
integer ( pInt ) , dimension ( 3 ) :: resolution
2010-07-01 20:50:06 +05:30
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
! stress etc.
2010-10-13 21:34:44 +05:30
real ( pReal ) , dimension ( 3 , 3 ) :: ones , zeroes , temp33_Real , damper , &
2010-10-20 14:29:00 +05:30
pstress , pstress_av , cstress_av , defgrad_av , &
2010-10-13 21:34:44 +05:30
defgradAim , defgradAimOld , defgradAimCorr , defgradAimCorrPrev , &
2011-07-14 15:07:31 +05:30
mask_stress , mask_defgrad , deltaF
2011-08-10 21:32:13 +05:30
real ( pReal ) , dimension ( 3 , 3 , 3 , 3 ) :: dPdF , c_current , s_current , c0_reference ! ToDo
real ( pReal ) , dimension ( 6 ) :: cstress , stress_res , delta_defgrad ! cauchy stress, residuum_stress, change of defgrad in Mandel notation
real ( pReal ) , dimension ( 6 , 6 ) :: dsde , c_current66 , s_current66 ! Mandel notation of 4th order tensors
real ( pReal ) , dimension ( 9 , 9 ) :: s_current99 , c_current99
2011-02-09 23:17:28 +05:30
real ( pReal ) , dimension ( : , : , : , : , : ) , allocatable :: workfft , defgrad , defgradold
2011-05-24 21:27:59 +05:30
real ( pReal ) , dimension ( : , : , : , : ) , allocatable :: coordinates
2011-08-02 19:28:28 +05:30
real ( pReal ) , dimension ( : , : , : ) , allocatable :: temperature
2011-08-10 21:32:13 +05:30
real ( pReal ) , dimension ( : , : ) , allocatable :: s_reduced , c_reduced
logical , dimension ( 6 ) :: mask_stress6
logical , dimension ( 9 ) :: mask_stress9
integer ( pInt ) size_reduced
2010-10-20 14:29:00 +05:30
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
! variables storing information for spectral method
2011-02-09 23:17:28 +05:30
complex ( pReal ) :: img
2010-09-01 13:35:11 +05:30
complex ( pReal ) , dimension ( 3 , 3 ) :: temp33_Complex
2011-07-07 20:57:35 +05:30
real ( pReal ) , dimension ( 3 , 3 ) :: xiDyad
2010-09-01 13:35:11 +05:30
real ( pReal ) , dimension ( : , : , : , : , : , : , : ) , allocatable :: gamma_hat
2011-07-07 15:33:55 +05:30
real ( pReal ) , dimension ( : , : , : , : ) , allocatable :: xi
2011-02-09 23:17:28 +05:30
integer ( pInt ) , dimension ( 3 ) :: k_s
integer * 8 , dimension ( 2 ) :: plan_fft
2011-02-07 20:05:42 +05:30
! loop variables, convergence etc.
2011-07-25 22:00:21 +05:30
real ( pReal ) guessmode , err_div , err_stress , err_defgrad , p_hat_avg
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
integer ( pInt ) i , j , k , l , m , n , p
2011-07-25 22:00:21 +05:30
integer ( pInt ) loadcase , ielem , iter , calcmode , CPFEM_mode , ierr , not_converged_counter
2011-02-07 20:05:42 +05:30
logical errmatinv
2011-07-25 22:00:21 +05:30
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
!Initializing
2011-06-06 20:50:28 +05:30
!$ call omp_set_num_threads(DAMASK_NumThreadsInt) ! set number of threads for parallel execution set by DAMASK_NUM_THREADS
2011-01-12 22:32:42 +05:30
2011-06-06 20:50:28 +05:30
bc_maskvector = . false .
2010-06-10 20:21:10 +05:30
unit = 234_pInt
2011-06-06 20:50:28 +05:30
ones = 1.0_pReal ; zeroes = 0.0_pReal
2011-02-09 23:17:28 +05:30
img = cmplx ( 0.0 , 1.0 )
2011-06-15 23:18:14 +05:30
N_l = 0_pInt
N_s = 0_pInt
N_t = 0_pInt
2011-08-02 19:28:28 +05:30
N_temperature = 0_pInt
2011-07-06 18:40:18 +05:30
time = 0.0_pReal
2011-06-15 23:18:14 +05:30
N_n = 0_pInt
2011-07-13 22:03:12 +05:30
N_freq = 0_pInt
N_Fdot = 0_pInt
2011-07-25 22:00:21 +05:30
not_converged_counter = 0_pInt
2011-01-31 22:37:42 +05:30
gotResolution = . false . ; gotDimension = . false . ; gotHomogenization = . false .
2011-06-15 23:18:14 +05:30
resolution = 1_pInt
geomdimension = 0.0_pReal
2010-10-13 21:34:44 +05:30
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
2010-09-22 17:34:43 +05:30
if ( IargC ( ) / = 2 ) call IO_error ( 102 ) ! check for correct number of given arguments
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
2010-09-01 13:35:11 +05:30
! Reading the loadcase file and assign variables
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
path = getLoadcaseName ( )
2011-02-21 20:07:38 +05:30
print '(a,/,a)' , 'Loadcase: ' , trim ( path )
print '(a,/,a)' , 'Workingdir: ' , trim ( getSolverWorkingDirectoryName ( ) )
print '(a,/,a)' , 'SolverJobName: ' , trim ( getSolverJobName ( ) )
2010-06-10 20:21:10 +05:30
2011-07-14 15:07:31 +05:30
if ( . not . IO_open_file ( unit , path ) ) call IO_error ( 30 , ext_msg = path )
2011-02-09 23:17:28 +05:30
2010-06-10 20:21:10 +05:30
rewind ( unit )
do
2010-07-02 19:40:36 +05:30
read ( unit , '(a1024)' , END = 101 ) line
2010-06-10 20:21:10 +05:30
if ( IO_isBlank ( line ) ) cycle ! skip empty lines
2010-06-25 17:01:05 +05:30
posInput = IO_stringPos ( line , maxNchunksInput )
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
do i = 1 , maxNchunksInput , 1
2010-06-25 17:01:05 +05:30
select case ( IO_lc ( IO_stringValue ( line , posInput , i ) ) )
2011-07-13 22:03:12 +05:30
case ( 'l' , 'velocitygrad' )
2010-06-10 20:21:10 +05:30
N_l = N_l + 1
2011-07-13 22:03:12 +05:30
case ( 'fdot' )
N_Fdot = N_Fdot + 1
case ( 's' , 'stress' , 'pk1' , 'piolakirchhoff' )
2010-06-10 20:21:10 +05:30
N_s = N_s + 1
2011-07-13 22:03:12 +05:30
case ( 't' , 'time' , 'delta' )
2010-06-10 20:21:10 +05:30
N_t = N_t + 1
2011-07-13 22:03:12 +05:30
case ( 'n' , 'incs' , 'increments' , 'steps' , 'logincs' , 'logsteps' )
2010-06-10 20:21:10 +05:30
N_n = N_n + 1
2011-07-13 22:03:12 +05:30
case ( 'f' , 'freq' , 'frequency' )
N_freq = N_freq + 1
2011-08-02 19:28:28 +05:30
case ( 'temp' , 'temperature' )
N_temperature = N_temperature + 1
2010-06-10 20:21:10 +05:30
end select
enddo ! count all identifiers to allocate memory and do sanity check
enddo
2010-06-10 14:20:04 +05:30
2011-07-13 22:03:12 +05:30
101 N_Loadcases = N_n
2011-08-03 23:27:28 +05:30
if ( ( N_l + N_Fdot / = N_n ) . or . ( N_n / = N_t ) ) & ! sanity check
call IO_error ( 31 , ext_msg = path ) ! error message for incomplete inp !ToDo:change message
2011-07-06 18:40:18 +05:30
2011-01-07 18:26:45 +05:30
! allocate memory depending on lines in input file
2011-07-13 22:03:12 +05:30
allocate ( bc_deformation ( 3 , 3 , N_Loadcases ) ) ; bc_deformation = 0.0_pReal
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
allocate ( bc_stress ( 3 , 3 , N_Loadcases ) ) ; bc_stress = 0.0_pReal
allocate ( bc_mask ( 3 , 3 , 2 , N_Loadcases ) ) ; bc_mask = . false .
2011-07-13 22:03:12 +05:30
allocate ( velGradApplied ( N_Loadcases ) ) ; velGradApplied = . false .
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
allocate ( bc_timeIncrement ( N_Loadcases ) ) ; bc_timeIncrement = 0.0_pReal
2011-08-03 23:27:28 +05:30
allocate ( bc_temperature ( N_Loadcases ) ) ; bc_temperature = 30 0.0_pReal
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
allocate ( bc_steps ( N_Loadcases ) ) ; bc_steps = 0_pInt
2011-08-02 19:28:28 +05:30
2011-07-25 22:00:21 +05:30
allocate ( bc_logscale ( N_Loadcases ) ) ; bc_logscale = 0_pInt
2011-06-15 23:18:14 +05:30
allocate ( bc_frequency ( N_Loadcases ) ) ; bc_frequency = 1_pInt
2011-07-25 22:00:21 +05:30
allocate ( followFormerTrajectory ( N_Loadcases ) ) ; followFormerTrajectory = . true .
2010-06-10 20:21:10 +05:30
rewind ( unit )
2011-07-14 15:07:31 +05:30
loadcase = 0_pInt
2010-06-10 20:21:10 +05:30
do
2010-07-02 19:40:36 +05:30
read ( unit , '(a1024)' , END = 200 ) line
2011-07-14 15:07:31 +05:30
if ( IO_isBlank ( line ) ) cycle ! skip empty lines
loadcase = loadcase + 1
2011-02-21 20:07:38 +05:30
posInput = IO_stringPos ( line , maxNchunksInput )
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
do j = 1 , maxNchunksInput , 2
select case ( IO_lc ( IO_stringValue ( line , posInput , j ) ) )
2011-07-14 15:07:31 +05:30
case ( 'fdot' ) ! assign values for the deformation BC matrix (in case of given fdot)
2010-06-10 20:21:10 +05:30
valuevector = 0.0_pReal
2011-06-06 20:50:28 +05:30
forall ( k = 1 : 9 ) bc_maskvector ( k ) = IO_stringValue ( line , posInput , j + k ) / = '*'
2010-06-10 20:21:10 +05:30
do k = 1 , 9
2011-07-14 15:07:31 +05:30
if ( bc_maskvector ( k ) ) valuevector ( k ) = IO_floatValue ( line , posInput , j + k )
2010-06-10 20:21:10 +05:30
enddo
2011-07-14 15:07:31 +05:30
bc_mask ( : , : , 1 , loadcase ) = transpose ( reshape ( bc_maskvector , ( / 3 , 3 / ) ) )
bc_deformation ( : , : , loadcase ) = math_transpose3x3 ( reshape ( valuevector , ( / 3 , 3 / ) ) )
case ( 'l' , 'velocitygrad' ) ! assign values for the deformation BC matrix (in case of given L)
velGradApplied ( loadcase ) = . true . ! in case of given L, set flag to true
2011-07-13 22:03:12 +05:30
valuevector = 0.0_pReal
forall ( k = 1 : 9 ) bc_maskvector ( k ) = IO_stringValue ( line , posInput , j + k ) / = '*'
do k = 1 , 9
2011-07-14 15:07:31 +05:30
if ( bc_maskvector ( k ) ) valuevector ( k ) = IO_floatValue ( line , posInput , j + k )
2011-07-13 22:03:12 +05:30
enddo
2011-07-14 15:07:31 +05:30
bc_mask ( : , : , 1 , loadcase ) = transpose ( reshape ( bc_maskvector , ( / 3 , 3 / ) ) )
bc_deformation ( : , : , loadcase ) = math_transpose3x3 ( reshape ( valuevector , ( / 3 , 3 / ) ) )
2011-07-13 22:03:12 +05:30
case ( 's' , 'stress' , 'pk1' , 'piolakirchhoff' )
2010-06-10 20:21:10 +05:30
valuevector = 0.0_pReal
2011-06-06 20:50:28 +05:30
forall ( k = 1 : 9 ) bc_maskvector ( k ) = IO_stringValue ( line , posInput , j + k ) / = '*'
2010-06-10 20:21:10 +05:30
do k = 1 , 9
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
if ( bc_maskvector ( k ) ) valuevector ( k ) = IO_floatValue ( line , posInput , j + k ) ! assign values for the bc_stress matrix
2010-06-10 20:21:10 +05:30
enddo
2011-07-14 15:07:31 +05:30
bc_mask ( : , : , 2 , loadcase ) = transpose ( reshape ( bc_maskvector , ( / 3 , 3 / ) ) )
bc_stress ( : , : , loadcase ) = math_transpose3x3 ( reshape ( valuevector , ( / 3 , 3 / ) ) )
2010-06-10 20:21:10 +05:30
case ( 't' , 'time' , 'delta' ) ! increment time
2011-07-14 15:07:31 +05:30
bc_timeIncrement ( loadcase ) = IO_floatValue ( line , posInput , j + 1 )
2011-08-02 19:28:28 +05:30
case ( 'temp' , 'temperature' ) ! starting temperature
2011-08-03 23:27:28 +05:30
bc_temperature ( loadcase ) = IO_floatValue ( line , posInput , j + 1 )
2010-06-10 21:02:06 +05:30
case ( 'n' , 'incs' , 'increments' , 'steps' ) ! bc_steps
2011-07-14 15:07:31 +05:30
bc_steps ( loadcase ) = IO_intValue ( line , posInput , j + 1 )
2011-07-13 22:03:12 +05:30
case ( 'logincs' , 'logsteps' ) ! true, if log scale
2011-07-14 15:07:31 +05:30
bc_steps ( loadcase ) = IO_intValue ( line , posInput , j + 1 )
2011-07-25 22:00:21 +05:30
bc_logscale ( loadcase ) = 1_pInt
2011-07-07 20:57:35 +05:30
case ( 'f' , 'freq' , 'frequency' ) ! frequency of result writings
2011-07-14 15:07:31 +05:30
bc_frequency ( loadcase ) = IO_intValue ( line , posInput , j + 1 )
case ( 'guessreset' , 'dropguessing' )
2011-07-25 22:00:21 +05:30
followFormerTrajectory ( loadcase ) = . false . ! do not continue to predict deformation along former trajectory
2010-06-10 20:21:10 +05:30
end select
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
enddo ; enddo
2010-06-10 20:21:10 +05:30
200 close ( unit )
2011-07-14 15:07:31 +05:30
2011-07-25 22:00:21 +05:30
if ( followFormerTrajectory ( 1 ) ) then
call IO_warning ( 33 ) ! cannot guess along trajectory for first step of first loadcase
followFormerTrajectory ( 1 ) = . false .
2011-07-14 15:07:31 +05:30
endif
2011-07-06 18:40:18 +05:30
2011-07-14 15:07:31 +05:30
do loadcase = 1 , N_Loadcases ! consistency checks and output
print * , '------------------------------------------------------'
print '(a,i5)' , 'Loadcase:' , loadcase
2011-07-25 22:00:21 +05:30
if ( . not . followFormerTrajectory ( loadcase ) ) &
2011-07-14 15:07:31 +05:30
print '(a)' , 'drop guessing along trajectory'
2011-08-10 21:32:13 +05:30
if ( any ( bc_mask ( : , : , 1 , loadcase ) . eqv . bc_mask ( : , : , 2 , loadcase ) ) ) & ! exclusive or masking only
2011-07-29 21:27:39 +05:30
call IO_error ( 31 , loadcase )
2011-07-14 15:07:31 +05:30
if ( velGradApplied ( loadcase ) ) then
2011-07-13 22:03:12 +05:30
do j = 1 , 3
2011-08-01 15:41:32 +05:30
if ( any ( bc_mask ( j , : , 1 , loadcase ) . eqv . . true . ) . and . &
any ( bc_mask ( j , : , 1 , loadcase ) . eqv . . false . ) ) call IO_error ( 32 , loadcase ) ! each line should be either fully or not at all defined
2011-07-13 22:03:12 +05:30
enddo
2011-07-14 15:07:31 +05:30
print '(a,/,3(3(f12.6,x)/))' , 'L:' , math_transpose3x3 ( bc_deformation ( : , : , loadcase ) )
print '(a,/,3(3(l,x)/))' , 'bc_mask for L:' , transpose ( bc_mask ( : , : , 1 , loadcase ) )
2011-07-13 22:03:12 +05:30
else
2011-07-14 15:07:31 +05:30
print '(a,/,3(3(f12.6,x)/))' , 'Fdot:' , math_transpose3x3 ( bc_deformation ( : , : , loadcase ) )
print '(a,/,3(3(l,x)/))' , 'bc_mask for Fdot:' , transpose ( bc_mask ( : , : , 1 , loadcase ) )
2011-07-13 22:03:12 +05:30
endif
2011-07-29 21:27:39 +05:30
print '(a,/,3(3(f12.6,x)/))' , 'bc_stress/MPa:' , math_transpose3x3 ( bc_stress ( : , : , loadcase ) ) * 1e-6
2011-07-14 15:07:31 +05:30
print '(a,/,3(3(l,x)/))' , 'bc_mask for stress:' , transpose ( bc_mask ( : , : , 2 , loadcase ) )
if ( bc_timeIncrement ( loadcase ) < 0.0_pReal ) call IO_error ( 34 , loadcase ) ! negative time increment
2011-08-03 23:27:28 +05:30
print '(a,f12.6)' , 'temperature: ' , bc_temperature ( loadcase )
2011-07-14 15:07:31 +05:30
print '(a,f12.6)' , 'time: ' , bc_timeIncrement ( loadcase )
if ( bc_steps ( loadcase ) < 1_pInt ) call IO_error ( 35 , loadcase ) ! non-positive increment count
print '(a,i6)' , 'incs: ' , bc_steps ( loadcase )
if ( bc_frequency ( loadcase ) < 1_pInt ) call IO_error ( 36 , loadcase ) ! non-positive result frequency
print '(a,i6)' , 'freq: ' , bc_frequency ( loadcase )
2010-06-10 20:21:10 +05:30
enddo
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
2011-01-07 18:26:45 +05:30
!read header of geom file to get the information needed before the complete geom file is intepretated by mesh.f90
2011-02-21 20:07:38 +05:30
path = getModelName ( )
2011-07-14 15:07:31 +05:30
print * , '------------------------------------------------------'
2011-02-21 20:07:38 +05:30
print '(a,a)' , 'GeomName: ' , trim ( path )
if ( . not . IO_open_file ( unit , trim ( path ) / / InputFileExtension ) ) call IO_error ( 101 , ext_msg = trim ( path ) / / InputFileExtension )
2010-06-25 17:01:05 +05:30
rewind ( unit )
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
do
2010-07-02 19:40:36 +05:30
read ( unit , '(a1024)' , END = 100 ) line
2010-06-25 17:01:05 +05:30
if ( IO_isBlank ( line ) ) cycle ! skip empty lines
2011-01-07 18:26:45 +05:30
posGeom = IO_stringPos ( line , maxNchunksGeom )
2010-06-25 17:01:05 +05:30
2011-01-07 18:26:45 +05:30
select case ( IO_lc ( IO_StringValue ( line , posGeom , 1 ) ) )
2010-06-25 17:01:05 +05:30
case ( 'dimension' )
2010-09-22 17:34:43 +05:30
gotDimension = . true .
do i = 2 , 6 , 2
2011-01-07 18:26:45 +05:30
select case ( IO_lc ( IO_stringValue ( line , posGeom , i ) ) )
2010-09-22 17:34:43 +05:30
case ( 'x' )
2011-01-07 18:26:45 +05:30
geomdimension ( 1 ) = IO_floatValue ( line , posGeom , i + 1 )
2010-09-22 17:34:43 +05:30
case ( 'y' )
2011-01-07 18:26:45 +05:30
geomdimension ( 2 ) = IO_floatValue ( line , posGeom , i + 1 )
2010-09-22 17:34:43 +05:30
case ( 'z' )
2011-01-07 18:26:45 +05:30
geomdimension ( 3 ) = IO_floatValue ( line , posGeom , i + 1 )
2010-09-22 17:34:43 +05:30
end select
enddo
2010-06-25 17:01:05 +05:30
case ( 'homogenization' )
2010-09-22 17:34:43 +05:30
gotHomogenization = . true .
2011-01-07 18:26:45 +05:30
homog = IO_intValue ( line , posGeom , 2 )
2010-06-25 17:01:05 +05:30
case ( 'resolution' )
2010-09-22 17:34:43 +05:30
gotResolution = . true .
do i = 2 , 6 , 2
2011-01-07 18:26:45 +05:30
select case ( IO_lc ( IO_stringValue ( line , posGeom , i ) ) )
2010-09-22 17:34:43 +05:30
case ( 'a' )
2011-01-07 18:26:45 +05:30
resolution ( 1 ) = IO_intValue ( line , posGeom , i + 1 )
2010-09-22 17:34:43 +05:30
case ( 'b' )
2011-01-07 18:26:45 +05:30
resolution ( 2 ) = IO_intValue ( line , posGeom , i + 1 )
2010-09-22 17:34:43 +05:30
case ( 'c' )
2011-01-07 18:26:45 +05:30
resolution ( 3 ) = IO_intValue ( line , posGeom , i + 1 )
2010-09-22 17:34:43 +05:30
end select
enddo
2010-06-25 17:01:05 +05:30
end select
if ( gotDimension . and . gotHomogenization . and . gotResolution ) exit
enddo
2010-07-01 20:50:06 +05:30
100 close ( unit )
2011-02-14 22:51:31 +05:30
2011-08-01 15:41:32 +05:30
if ( mod ( resolution ( 1 ) , 2_pInt ) / = 0_pInt . or . &
mod ( resolution ( 2 ) , 2_pInt ) / = 0_pInt . or . &
( mod ( resolution ( 3 ) , 2_pInt ) / = 0_pInt . and . resolution ( 3 ) / = 1_pInt ) ) call IO_error ( 103 )
2011-02-14 22:51:31 +05:30
2011-02-21 20:07:38 +05:30
print '(a,/,i4,i4,i4)' , 'resolution a b c:' , resolution
2011-05-11 22:08:45 +05:30
print '(a,/,f8.4,f8.5,f8.5)' , 'dimension x y z:' , geomdimension
2011-02-21 20:07:38 +05:30
print '(a,i4)' , 'homogenization: ' , homog
2010-10-20 14:29:00 +05:30
2011-08-03 23:27:28 +05:30
allocate ( defgrad ( resolution ( 1 ) , resolution ( 2 ) , resolution ( 3 ) , 3 , 3 ) ) ; defgrad = 0.0_pReal
allocate ( defgradold ( resolution ( 1 ) , resolution ( 2 ) , resolution ( 3 ) , 3 , 3 ) ) ; defgradold = 0.0_pReal
allocate ( coordinates ( 3 , resolution ( 1 ) , resolution ( 2 ) , resolution ( 3 ) ) ) ; coordinates = 0.0_pReal
allocate ( temperature ( resolution ( 1 ) , resolution ( 2 ) , resolution ( 3 ) ) ) ; temperature = bc_temperature ( 1 ) ! start out isothermally
2011-08-10 23:15:37 +05:30
allocate ( xi ( 3 , resolution ( 1 ) / 2 + 1 , resolution ( 2 ) , resolution ( 3 ) ) ) ; xi = 0.0_pReal
2011-07-25 22:00:21 +05:30
2011-02-09 23:17:28 +05:30
wgt = 1.0_pReal / real ( resolution ( 1 ) * resolution ( 2 ) * resolution ( 3 ) , pReal )
2011-04-06 15:28:17 +05:30
defgradAim = math_I3
2010-10-13 21:34:44 +05:30
defgradAimOld = math_I3
2011-04-06 15:28:17 +05:30
defgrad_av = math_I3
2011-02-07 20:05:42 +05:30
2010-10-13 21:34:44 +05:30
! Initialization of CPFEM_general (= constitutive law) and of deformation gradient field
2011-08-02 19:28:28 +05:30
call CPFEM_initAll ( bc_temperature ( 1 ) , 1_pInt , 1_pInt )
2010-09-07 22:07:55 +05:30
ielem = 0_pInt
2011-08-10 21:32:13 +05:30
c_current = 0.0_pReal
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
do k = 1 , resolution ( 3 ) ; do j = 1 , resolution ( 2 ) ; do i = 1 , resolution ( 1 )
2011-08-10 21:32:13 +05:30
defgradold ( i , j , k , : , : ) = math_I3 ! no deformation at the beginning
2010-09-06 15:30:59 +05:30
defgrad ( i , j , k , : , : ) = math_I3
2011-01-07 18:26:45 +05:30
ielem = ielem + 1
2011-07-07 20:57:35 +05:30
coordinates ( 1 : 3 , i , j , k ) = mesh_ipCenterOfGravity ( 1 : 3 , 1 , ielem ) ! set to initial coordinates ToDo: SHOULD BE UPDATED TO CURRENT POSITION IN FUTURE REVISIONS!!!
2011-08-02 19:28:28 +05:30
call CPFEM_general ( 2 , coordinates ( 1 : 3 , i , j , k ) , math_I3 , math_I3 , temperature ( i , j , k ) , 0.0_pReal , ielem , 1_pInt , cstress , dsde , pstress , dPdF )
2011-08-10 21:32:13 +05:30
c_current = c_current + dPdF
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
enddo ; enddo ; enddo
2011-08-10 21:32:13 +05:30
c0_reference = c_current * wgt ! linear reference material stiffness
2011-07-07 15:33:55 +05:30
2011-07-07 20:57:35 +05:30
do k = 1 , resolution ( 3 ) ! calculation of discrete angular frequencies, ordered as in FFTW (wrap around)
2011-07-07 15:33:55 +05:30
k_s ( 3 ) = k - 1
if ( k > resolution ( 3 ) / 2 + 1 ) k_s ( 3 ) = k_s ( 3 ) - resolution ( 3 )
do j = 1 , resolution ( 2 )
k_s ( 2 ) = j - 1
2011-08-10 23:15:37 +05:30
if ( j > resolution ( 2 ) / 2 + 1 ) k_s ( 2 ) = k_s ( 2 ) - resolution ( 2 )
do i = 1 , resolution ( 1 ) / 2 + 1
2011-07-07 15:33:55 +05:30
k_s ( 1 ) = i - 1
2011-08-10 23:15:37 +05:30
xi ( 3 , i , j , k ) = 0.0_pReal ! 2D case
2011-07-25 22:00:21 +05:30
if ( resolution ( 3 ) > 1 ) xi ( 3 , i , j , k ) = real ( k_s ( 3 ) , pReal ) / geomdimension ( 3 ) ! 3D case
xi ( 2 , i , j , k ) = real ( k_s ( 2 ) , pReal ) / geomdimension ( 2 )
xi ( 1 , i , j , k ) = real ( k_s ( 1 ) , pReal ) / geomdimension ( 1 )
2011-07-07 15:33:55 +05:30
enddo ; enddo ; enddo
2010-10-20 14:29:00 +05:30
2011-04-06 15:28:17 +05:30
if ( memory_efficient ) then ! allocate just single fourth order tensor
2011-02-21 20:07:38 +05:30
allocate ( gamma_hat ( 1 , 1 , 1 , 3 , 3 , 3 , 3 ) ) ; gamma_hat = 0.0_pReal
2011-04-06 15:28:17 +05:30
else ! precalculation of gamma_hat field
2011-02-07 20:05:42 +05:30
allocate ( gamma_hat ( resolution ( 1 ) / 2 + 1 , resolution ( 2 ) , resolution ( 3 ) , 3 , 3 , 3 , 3 ) ) ; gamma_hat = 0.0_pReal
2011-07-07 15:33:55 +05:30
do k = 1 , resolution ( 3 ) ; do j = 1 , resolution ( 2 ) ; do i = 1 , resolution ( 1 ) / 2 + 1
if ( any ( xi ( : , i , j , k ) / = 0.0_pReal ) ) then
do l = 1 , 3 ; do m = 1 , 3
2011-07-07 20:57:35 +05:30
xiDyad ( l , m ) = xi ( l , i , j , k ) * xi ( m , i , j , k )
2011-07-07 15:33:55 +05:30
enddo ; enddo
2011-08-10 21:32:13 +05:30
temp33_Real = math_inv3x3 ( math_mul3333xx33 ( c0_reference , xiDyad ) )
2011-07-07 15:33:55 +05:30
else
2011-07-07 20:57:35 +05:30
xiDyad = 0.0_pReal
2011-07-07 15:33:55 +05:30
temp33_Real = 0.0_pReal
endif
do l = 1 , 3 ; do m = 1 , 3 ; do n = 1 , 3 ; do p = 1 , 3
gamma_hat ( i , j , k , l , m , n , p ) = - 0.25 * ( temp33_Real ( l , n ) + temp33_Real ( n , l ) ) * &
2011-07-07 20:57:35 +05:30
( xiDyad ( m , p ) + xiDyad ( p , m ) )
2011-07-07 15:33:55 +05:30
enddo ; enddo ; enddo ; enddo
2011-02-07 20:05:42 +05:30
enddo ; enddo ; enddo
endif
2011-07-07 15:33:55 +05:30
2011-02-09 23:17:28 +05:30
allocate ( workfft ( resolution ( 1 ) + 2 , resolution ( 2 ) , resolution ( 3 ) , 3 , 3 ) ) ; workfft = 0.0_pReal
2011-07-25 22:00:21 +05:30
! Initialization of fftw (see manual on fftw.org for more details)
2011-08-10 21:32:13 +05:30
if ( DAMASK_NumThreadsInt > 0_pInt ) then
call dfftw_init_threads ( ierr )
if ( ierr == 0_pInt ) call IO_error ( 104 , ierr )
call dfftw_plan_with_nthreads ( DAMASK_NumThreadsInt )
endif
2011-07-25 22:00:21 +05:30
2011-02-09 23:17:28 +05:30
call dfftw_plan_many_dft_r2c ( plan_fft ( 1 ) , 3 , ( / resolution ( 1 ) , resolution ( 2 ) , resolution ( 3 ) / ) , 9 , &
workfft , ( / resolution ( 1 ) + 2 , resolution ( 2 ) , resolution ( 3 ) / ) , 1 , ( resolution ( 1 ) + 2 ) * resolution ( 2 ) * resolution ( 3 ) , &
workfft , ( / resolution ( 1 ) / 2 + 1 , resolution ( 2 ) , resolution ( 3 ) / ) , 1 , ( resolution ( 1 ) / 2 + 1 ) * resolution ( 2 ) * resolution ( 3 ) , FFTW_PATIENT )
call dfftw_plan_many_dft_c2r ( plan_fft ( 2 ) , 3 , ( / resolution ( 1 ) , resolution ( 2 ) , resolution ( 3 ) / ) , 9 , &
workfft , ( / resolution ( 1 ) / 2 + 1 , resolution ( 2 ) , resolution ( 3 ) / ) , 1 , ( resolution ( 1 ) / 2 + 1 ) * resolution ( 2 ) * resolution ( 3 ) , &
workfft , ( / resolution ( 1 ) + 2 , resolution ( 2 ) , resolution ( 3 ) / ) , 1 , ( resolution ( 1 ) + 2 ) * resolution ( 2 ) * resolution ( 3 ) , FFTW_PATIENT )
2011-02-07 20:05:42 +05:30
2011-01-07 18:26:45 +05:30
! write header of output file
2011-02-07 20:05:42 +05:30
open ( 538 , file = trim ( getSolverWorkingDirectoryName ( ) ) / / trim ( getSolverJobName ( ) ) &
/ / '.spectralOut' , form = 'UNFORMATTED' )
2011-06-15 23:18:14 +05:30
write ( 538 ) , 'load' , trim ( getLoadcaseName ( ) )
write ( 538 ) , 'workingdir' , trim ( getSolverWorkingDirectoryName ( ) )
write ( 538 ) , 'geometry' , trim ( getSolverJobName ( ) ) / / InputFileExtension
write ( 538 ) , 'resolution' , resolution
write ( 538 ) , 'dimension' , geomdimension
2011-01-07 18:26:45 +05:30
write ( 538 ) , 'materialpoint_sizeResults' , materialpoint_sizeResults
2011-06-15 23:18:14 +05:30
write ( 538 ) , 'loadcases' , N_Loadcases
2011-07-25 22:00:21 +05:30
write ( 538 ) , 'logscale' , bc_logscale ! one entry per loadcase (0: linear, 1: log)
2011-06-15 23:18:14 +05:30
write ( 538 ) , 'frequencies' , bc_frequency ! one entry per loadcase
write ( 538 ) , 'times' , bc_timeIncrement ! one entry per loadcase
bc_steps ( 1 ) = bc_steps ( 1 ) + 1 ! +1 to store initial situation
write ( 538 ) , 'increments' , bc_steps ! one entry per loadcase
bc_steps ( 1 ) = bc_steps ( 1 ) - 1 ! re-adjust for correct looping
write ( 538 ) , 'eoh' ! end of header
2011-07-06 18:40:18 +05:30
2011-04-06 15:28:17 +05:30
write ( 538 ) materialpoint_results ( : , 1 , : ) ! initial (non-deformed) results
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
! Initialization done
2010-09-06 15:30:59 +05:30
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
!*************************************************************
2011-04-06 15:28:17 +05:30
! Loop over loadcases defined in the loadcase file
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
do loadcase = 1 , N_Loadcases
!*************************************************************
2011-07-13 22:03:12 +05:30
time0 = time ! loadcase start time
2011-07-25 22:00:21 +05:30
if ( followFormerTrajectory ( loadcase ) ) then
2011-07-13 22:03:12 +05:30
guessmode = 1.0_pReal
else
guessmode = 0.0_pReal ! change of load case, homogeneous guess for the first step
2011-07-29 21:27:39 +05:30
damper = 1.0_pReal
2011-07-13 22:03:12 +05:30
endif
2011-07-06 18:40:18 +05:30
2010-10-13 21:34:44 +05:30
mask_defgrad = merge ( ones , zeroes , bc_mask ( : , : , 1 , loadcase ) )
mask_stress = merge ( ones , zeroes , bc_mask ( : , : , 2 , loadcase ) )
2011-08-10 21:32:13 +05:30
2011-07-14 15:07:31 +05:30
deltaF = bc_deformation ( : , : , loadcase ) ! only valid for given fDot. will be overwritten later in case L is given
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
!*************************************************************
! loop oper steps defined in input file for current loadcase
2011-06-15 23:18:14 +05:30
do step = 1 , bc_steps ( loadcase )
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
!*************************************************************
2011-07-25 22:00:21 +05:30
if ( bc_logscale ( loadcase ) == 1_pInt ) then ! loglinear scale
2011-07-13 22:03:12 +05:30
if ( loadcase == 1_pInt ) then ! 1st loadcase of loglinear scale
if ( step == 1_pInt ) then ! 1st step of 1st loadcase of loglinear scale
2011-07-06 18:40:18 +05:30
timeinc = bc_timeIncrement ( 1 ) * ( 2.0 ** ( 1 - bc_steps ( 1 ) ) ) ! assume 1st step is equal to 2nd
else ! not-1st step of 1st loadcase of loglinear scale
timeinc = bc_timeIncrement ( 1 ) * ( 2.0 ** ( step - ( 1 + bc_steps ( 1 ) ) ) )
endif
else ! not-1st loadcase of loglinear scale
2011-08-02 19:28:28 +05:30
timeinc = time0 * ( ( ( 1.0_pReal + bc_timeIncrement ( loadcase ) / time0 ) ** ( float ( step ) / ( bc_steps ( loadcase ) ) ) ) &
- ( ( 1.0_pReal + bc_timeIncrement ( loadcase ) / time0 ) ** ( float ( ( step - 1 ) ) / ( bc_steps ( loadcase ) ) ) ) )
2011-07-06 18:40:18 +05:30
endif
else ! linear scale
timeinc = bc_timeIncrement ( loadcase ) / bc_steps ( loadcase )
endif
time = time + timeinc
2011-07-13 22:03:12 +05:30
! update macroscopic deformation gradient (defgrad BC)
2011-07-14 15:07:31 +05:30
if ( velGradApplied ( loadcase ) ) & ! calculate deltaF from given L and current F
deltaF = math_mul33x33 ( bc_deformation ( : , : , loadcase ) , defgradAim )
temp33_Real = defgradAim
defgradAim = defgradAim &
+ guessmode * mask_stress * ( defgradAim - defgradAimOld ) &
+ mask_defgrad * deltaF * timeinc
2011-07-13 22:03:12 +05:30
defgradAimOld = temp33_Real
2011-07-14 15:07:31 +05:30
2011-07-13 22:03:12 +05:30
! update local deformation gradient
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
do k = 1 , resolution ( 3 ) ; do j = 1 , resolution ( 2 ) ; do i = 1 , resolution ( 1 )
2011-07-14 15:07:31 +05:30
temp33_Real = defgrad ( i , j , k , : , : )
2011-08-10 23:15:37 +05:30
if ( velGradApplied ( loadcase ) ) & ! using velocity gradient to calculate new deformation gradient (if not guessing)
2011-07-14 15:07:31 +05:30
deltaF = math_mul33x33 ( bc_deformation ( : , : , loadcase ) , defgradold ( i , j , k , : , : ) )
2011-08-03 13:24:32 +05:30
defgrad ( i , j , k , : , : ) = defgrad ( i , j , k , : , : ) & ! decide if guessing along former trajectory or apply homogeneous addon (addon only for applied deformation)
+ guessmode * ( defgrad ( i , j , k , : , : ) - defgradold ( i , j , k , : , : ) ) &
+ ( 1.0_pReal - guessmode ) * mask_defgrad * deltaF * timeinc
defgradold ( i , j , k , : , : ) = temp33_Real
2010-07-13 20:59:26 +05:30
enddo ; enddo ; enddo
2010-07-02 22:45:53 +05:30
2011-01-31 22:37:42 +05:30
guessmode = 1.0_pReal ! keep guessing along former trajectory during same loadcase
2011-07-13 22:03:12 +05:30
2011-07-25 22:00:21 +05:30
if ( all ( bc_mask ( : , : , 1 , loadcase ) ) ) then
2011-01-31 22:37:42 +05:30
calcmode = 1_pInt ! if no stress BC is given (calmode 0 is not needed)
else
calcmode = 0_pInt ! start calculation of BC fulfillment
endif
2011-07-13 22:03:12 +05:30
2011-01-31 22:37:42 +05:30
CPFEM_mode = 1_pInt ! winding forward
2010-07-02 22:45:53 +05:30
iter = 0_pInt
2011-07-14 15:07:31 +05:30
err_div = 2.0_pReal * err_div_tol ! go into loop
2011-01-07 18:26:45 +05:30
added fftw3 as fft(library will not versioned, should be in a linkable folder) , did some corrections on the code, splitted main file up (allows use of makefile), added makefile
changes on mpie_spectral.f90:
new structure, changed variable names, now using defgrad instead of disgrad, cleaned up, removed augmented Lagrange.
ToDo: Implement Augmented Lagrange again (but then a working version), implement Large strain, think about complex-to real-transform backwards, try to implement MP-support
2010-08-27 22:09:38 +05:30
!*************************************************************
2010-10-13 21:34:44 +05:30
! convergence loop
2011-04-06 15:28:17 +05:30
do while ( iter < itmax . and . &
2011-06-06 20:50:28 +05:30
( err_div > err_div_tol . or . &
err_stress > err_stress_tol . or . &
2011-04-06 15:28:17 +05:30
err_defgrad > err_defgrad_tol ) )
2011-02-07 20:05:42 +05:30
iter = iter + 1_pInt
2011-07-25 22:00:21 +05:30
if ( iter == itmax ) not_converged_counter = not_converged_counter + 1
2011-02-07 20:05:42 +05:30
print * , ' '
2011-07-06 18:40:18 +05:30
print '(3(A,I5.5,tr2))' , ' Loadcase = ' , loadcase , ' Step = ' , step , ' Iteration = ' , iter
2011-01-31 22:37:42 +05:30
cstress_av = 0.0_pReal
2011-07-07 15:33:55 +05:30
workfft = 0.0_pReal ! needed because of the padding for FFTW
2010-10-13 21:34:44 +05:30
!*************************************************************
2010-10-20 14:29:00 +05:30
! adjust defgrad to fulfill BCs
2011-04-06 15:28:17 +05:30
select case ( calcmode )
case ( 0 )
print * , 'Update Stress Field (constitutive evaluation P(F))'
2010-10-20 14:29:00 +05:30
ielem = 0_pInt
do k = 1 , resolution ( 3 ) ; do j = 1 , resolution ( 2 ) ; do i = 1 , resolution ( 1 )
ielem = ielem + 1
2011-06-06 20:50:28 +05:30
call CPFEM_general ( 3 , & ! collect cycle
coordinates ( 1 : 3 , i , j , k ) , defgradold ( i , j , k , : , : ) , defgrad ( i , j , k , : , : ) , &
2011-08-02 19:28:28 +05:30
temperature ( i , j , k ) , timeinc , ielem , 1_pInt , &
2010-10-20 14:29:00 +05:30
cstress , dsde , pstress , dPdF )
enddo ; enddo ; enddo
2011-02-09 23:17:28 +05:30
2011-08-10 21:32:13 +05:30
c_current = 0.0_pReal
2011-01-07 18:26:45 +05:30
ielem = 0_pInt
2010-10-20 14:29:00 +05:30
do k = 1 , resolution ( 3 ) ; do j = 1 , resolution ( 2 ) ; do i = 1 , resolution ( 1 )
2011-01-07 18:26:45 +05:30
ielem = ielem + 1_pInt
2010-10-20 14:29:00 +05:30
call CPFEM_general ( CPFEM_mode , & ! first element in first iteration retains CPFEM_mode 1,
2011-05-26 14:53:13 +05:30
coordinates ( 1 : 3 , i , j , k ) , &
2010-10-20 14:29:00 +05:30
defgradold ( i , j , k , : , : ) , defgrad ( i , j , k , : , : ) , & ! others get 2 (saves winding forward effort)
2011-08-02 19:28:28 +05:30
temperature ( i , j , k ) , timeinc , ielem , 1_pInt , &
2010-10-20 14:29:00 +05:30
cstress , dsde , pstress , dPdF )
CPFEM_mode = 2_pInt
2011-07-13 22:03:12 +05:30
workfft ( i , j , k , : , : ) = pstress ! build up average P-K stress
2011-06-06 20:50:28 +05:30
cstress_av = cstress_av + math_mandel6to33 ( cstress ) ! build up average Cauchy stress
2011-08-10 21:32:13 +05:30
c_current = c_current + dPdF
2010-10-20 14:29:00 +05:30
enddo ; enddo ; enddo
2011-08-10 21:32:13 +05:30
c_current = c_current * wgt
2011-01-31 22:37:42 +05:30
cstress_av = cstress_av * wgt
2011-06-06 20:50:28 +05:30
do n = 1 , 3 ; do m = 1 , 3
2011-08-10 21:32:13 +05:30
pstress_av ( m , n ) = sum ( workfft ( 1 : resolution ( 1 ) , : , : , m , n ) ) * wgt
defgrad_av ( m , n ) = sum ( defgrad ( : , : , : , m , n ) ) * wgt
2010-10-20 14:29:00 +05:30
enddo ; enddo
2011-02-07 20:05:42 +05:30
2010-10-20 14:29:00 +05:30
err_stress = maxval ( abs ( mask_stress * ( pstress_av - bc_stress ( : , : , loadcase ) ) ) )
2011-08-10 23:15:37 +05:30
err_stress_tol = maxval ( abs ( pstress_av ) ) * 0.8 * err_stress_tolrel
2011-08-10 21:32:13 +05:30
2011-08-10 23:15:37 +05:30
call math_invert ( 9 , math_plain3333to99 ( c_current ) , s_current99 , i , errmatinv )
if ( errmatinv ) then
print * , 'using symmetric compliance'
pause !maybe we don't need it. Code below is not working
!mask_stress6 = math_Plain33to6_logical(bc_mask(:,:,2,loadcase))
!if the symmetrized stiffness is not used at all, the allocate terms only needed at the beginning of a load case
size_reduced = count ( mask_stress6 )
allocate ( c_reduced ( size_reduced , size_reduced ) ) ; c_reduced = 0.0_pReal
allocate ( s_reduced ( size_reduced , size_reduced ) ) ; s_reduced = 0.0_pReal
! c_current66 = math_Plain3333to66(c_current)
2011-08-10 21:32:13 +05:30
k = 0_pInt
2011-08-10 23:15:37 +05:30
do n = 1 , 6
if ( mask_stress6 ( n ) ) then
2011-08-10 21:32:13 +05:30
k = k + 1_pInt
j = 0_pInt
2011-08-10 23:15:37 +05:30
do m = 1 , 6
if ( mask_stress6 ( m ) ) then
2011-08-10 21:32:13 +05:30
j = j + 1_pInt
2011-08-10 23:15:37 +05:30
c_reduced ( k , j ) = c_current66 ( n , m )
2011-08-10 21:32:13 +05:30
endif
enddo
endif
enddo
call math_invert ( size_reduced , c_reduced , s_reduced , i , errmatinv )
if ( errmatinv ) call IO_error ( 800 )
2011-08-10 23:15:37 +05:30
s_current66 = 0.0_pReal
k = 0_pInt
do n = 1 , 6
if ( mask_stress6 ( n ) ) then
k = k + 1_pInt
j = 0_pInt
do m = 1 , 6
if ( mask_stress6 ( m ) ) then
j = j + 1_pInt
s_current66 ( n , m ) = s_reduced ( k , j )
endif
enddo
endif
enddo
! s_current = math_Plain66to3333(s_current66)
else
mask_stress9 = reshape ( bc_mask ( : , : , 2 , loadcase ) , ( / 9 / ) )
size_reduced = count ( mask_stress9 )
allocate ( c_reduced ( size_reduced , size_reduced ) ) ; c_reduced = 0.0_pReal
allocate ( s_reduced ( size_reduced , size_reduced ) ) ; s_reduced = 0.0_pReal
c_current99 = math_Plain3333to99 ( c_current )
k = 0_pInt ! build reduced stiffness
do n = 1 , 9
if ( mask_stress9 ( n ) ) then
k = k + 1_pInt
j = 0_pInt
do m = 1 , 9
if ( mask_stress9 ( m ) ) then
j = j + 1_pInt
c_reduced ( k , j ) = c_current99 ( n , m )
endif ; enddo ; endif ; enddo
call math_invert ( size_reduced , c_reduced , s_reduced , i , errmatinv ) ! invert reduced stiffness
if ( errmatinv ) call IO_error ( 800 )
s_current99 = 0.0_pReal ! build full compliance
2011-08-10 21:32:13 +05:30
k = 0_pInt
do n = 1 , 9
if ( mask_stress9 ( n ) ) then
k = k + 1_pInt
j = 0_pInt
do m = 1 , 9
if ( mask_stress9 ( m ) ) then
j = j + 1_pInt
s_current99 ( n , m ) = s_reduced ( k , j )
2011-08-10 23:15:37 +05:30
endif ; enddo ; endif ; enddo
2011-08-10 21:32:13 +05:30
s_current = math_Plain99to3333 ( s_current99 )
endif
2011-08-10 23:15:37 +05:30
2011-08-10 21:32:13 +05:30
deallocate ( c_reduced )
deallocate ( s_reduced )
2010-10-20 14:29:00 +05:30
print * , 'Correcting deformation gradient to fullfill BCs'
2011-08-10 21:32:13 +05:30
defgradAimCorr = - math_mul3333xx33 ( s_current , ( ( pstress_av - bc_stress ( : , : , loadcase ) ) ) ) ! residual on given stress components
2011-08-10 23:15:37 +05:30
defgradAim = defgradAim + defgradAimCorr
2010-10-13 21:34:44 +05:30
2011-04-06 15:28:17 +05:30
do m = 1 , 3 ; do n = 1 , 3
2011-08-10 23:15:37 +05:30
defgrad ( : , : , : , m , n ) = defgrad ( : , : , : , m , n ) + defgradAim ( m , n ) - defgrad_av ( m , n ) ! anticipated target minus current state
2010-10-20 14:29:00 +05:30
enddo ; enddo
2011-07-13 22:03:12 +05:30
err_div = 2.0_pReal * err_div_tol
2011-04-06 15:28:17 +05:30
err_defgrad = maxval ( abs ( mask_defgrad * ( defgrad_av - defgradAim ) ) )
print '(a,/,3(3(f12.7,x)/))' , ' Deformation Gradient:' , math_transpose3x3 ( defgrad_av )
2011-07-13 22:03:12 +05:30
print '(a,/,3(3(f10.4,x)/))' , ' Piola-Kirchhoff Stress / MPa: ' , math_transpose3x3 ( pstress_av ) / 1.e6
2011-07-29 21:27:39 +05:30
print '(2(a,E8.2))' , ' error stress: ' , err_stress , ' Tol. = ' , err_stress_tol
2011-07-13 22:03:12 +05:30
print '(2(a,E8.2))' , ' error deformation gradient: ' , err_defgrad , ' Tol. = ' , err_defgrad_tol
2011-07-29 21:27:39 +05:30
if ( err_stress < err_stress_tol ) then
2011-01-31 22:37:42 +05:30
calcmode = 1_pInt
2010-10-20 14:29:00 +05:30
endif
2011-04-06 15:28:17 +05:30
! Using the spectral method to calculate the change of deformation gradient, check divergence of stress field in fourier space
2011-02-07 20:05:42 +05:30
case ( 1 )
2010-10-20 14:29:00 +05:30
print * , 'Update Stress Field (constitutive evaluation P(F))'
ielem = 0_pInt
do k = 1 , resolution ( 3 ) ; do j = 1 , resolution ( 2 ) ; do i = 1 , resolution ( 1 )
2011-02-07 20:05:42 +05:30
ielem = ielem + 1_pInt
2011-05-24 21:27:59 +05:30
call CPFEM_general ( 3 , coordinates ( 1 : 3 , i , j , k ) , defgradold ( i , j , k , : , : ) , defgrad ( i , j , k , : , : ) , &
2011-08-02 19:28:28 +05:30
temperature ( i , j , k ) , timeinc , ielem , 1_pInt , &
2010-10-20 14:29:00 +05:30
cstress , dsde , pstress , dPdF )
enddo ; enddo ; enddo
2011-08-10 21:32:13 +05:30
ielem = 0_pInt
2011-08-10 23:15:37 +05:30
2010-10-20 14:29:00 +05:30
do k = 1 , resolution ( 3 ) ; do j = 1 , resolution ( 2 ) ; do i = 1 , resolution ( 1 )
2011-02-07 20:05:42 +05:30
ielem = ielem + 1_pInt
2011-04-06 15:28:17 +05:30
call CPFEM_general ( CPFEM_mode , & ! first element in first iteration retains CPFEM_mode 1,
2011-05-26 14:53:13 +05:30
coordinates ( 1 : 3 , i , j , k ) , &
2010-10-20 14:29:00 +05:30
defgradold ( i , j , k , : , : ) , defgrad ( i , j , k , : , : ) , &
2011-08-02 19:28:28 +05:30
temperature ( i , j , k ) , timeinc , ielem , 1_pInt , &
2010-10-20 14:29:00 +05:30
cstress , dsde , pstress , dPdF )
2011-02-21 20:07:38 +05:30
CPFEM_mode = 2_pInt
2011-07-25 22:00:21 +05:30
workfft ( i , j , k , : , : ) = pstress
2011-01-31 22:37:42 +05:30
cstress_av = cstress_av + math_mandel6to33 ( cstress )
2010-10-20 14:29:00 +05:30
enddo ; enddo ; enddo
2011-02-07 20:05:42 +05:30
cstress_av = cstress_av * wgt
2011-06-06 20:50:28 +05:30
do n = 1 , 3 ; do m = 1 , 3
pstress_av ( m , n ) = sum ( workfft ( 1 : resolution ( 1 ) , 1 : resolution ( 2 ) , 1 : resolution ( 3 ) , m , n ) ) * wgt
2011-02-07 20:05:42 +05:30
enddo ; enddo
2010-10-20 14:29:00 +05:30
print * , 'Calculating equilibrium using spectral method'
2011-07-25 22:00:21 +05:30
err_div = 0.0_pReal
p_hat_avg = 0.0_pReal
2011-04-06 15:28:17 +05:30
call dfftw_execute_dft_r2c ( plan_fft ( 1 ) , workfft , workfft ) ! FFT of pstress
2011-07-25 22:00:21 +05:30
do m = 1 , 3 ! L infinity norm of stress tensor
p_hat_avg = max ( p_hat_avg , sum ( abs ( workfft ( 1 , 1 , 1 , : , m ) ) ) ) ! ignore imaginary part as it is always zero (Nyquist freq for real only input)
enddo
do k = 1 , resolution ( 3 ) ; do j = 1 , resolution ( 2 ) ; do i = 1 , resolution ( 1 ) / 2 + 1
err_div = max ( err_div , maxval ( abs ( math_mul33x3_complex ( workfft ( i * 2 - 1 , j , k , : , : ) + & ! maximum of L infinity norm of div(stress), Suquet 2001
2011-08-10 23:15:37 +05:30
workfft ( i * 2 , j , k , : , : ) * img , xi ( : , i , j , k ) * minval ( geomdimension ) ) ) ) )
2011-07-25 22:00:21 +05:30
enddo ; enddo ; enddo
2011-08-10 23:15:37 +05:30
err_div = err_div / p_hat_avg !weigthting of error by average stress (L infinity norm)
2011-02-09 23:17:28 +05:30
2011-08-10 23:15:37 +05:30
if ( memory_efficient ) then ! memory saving version, on-the-fly calculation of gamma_hat
2011-07-07 15:33:55 +05:30
do k = 1 , resolution ( 3 ) ; do j = 1 , resolution ( 2 ) ; do i = 1 , resolution ( 1 ) / 2 + 1
if ( any ( xi ( : , i , j , k ) / = 0.0_pReal ) ) then
do l = 1 , 3 ; do m = 1 , 3
2011-07-07 20:57:35 +05:30
xiDyad ( l , m ) = xi ( l , i , j , k ) * xi ( m , i , j , k )
2011-07-07 15:33:55 +05:30
enddo ; enddo
2011-08-10 21:32:13 +05:30
temp33_Real = math_inv3x3 ( math_mul3333xx33 ( c0_reference , xiDyad ) )
2011-07-07 15:33:55 +05:30
else
2011-07-07 20:57:35 +05:30
xiDyad = 0.0_pReal
2011-07-07 15:33:55 +05:30
temp33_Real = 0.0_pReal
endif
do l = 1 , 3 ; do m = 1 , 3 ; do n = 1 , 3 ; do p = 1 , 3
gamma_hat ( 1 , 1 , 1 , l , m , n , p ) = - 0.25_pReal * ( temp33_Real ( l , n ) + temp33_Real ( n , l ) ) * &
2011-07-07 20:57:35 +05:30
( xiDyad ( m , p ) + xiDyad ( p , m ) )
2011-07-07 15:33:55 +05:30
enddo ; enddo ; enddo ; enddo
do m = 1 , 3 ; do n = 1 , 3
temp33_Complex ( m , n ) = sum ( gamma_hat ( 1 , 1 , 1 , m , n , : , : ) * ( workfft ( i * 2 - 1 , j , k , : , : ) &
+ workfft ( i * 2 , j , k , : , : ) * img ) )
enddo ; enddo
2011-07-07 20:57:35 +05:30
workfft ( i * 2 - 1 , j , k , : , : ) = real ( temp33_Complex ) ! change of average strain
2011-07-07 15:33:55 +05:30
workfft ( i * 2 , j , k , : , : ) = aimag ( temp33_Complex )
2011-02-09 23:17:28 +05:30
enddo ; enddo ; enddo
2011-04-06 15:28:17 +05:30
else ! use precalculated gamma-operator
2011-02-21 20:07:38 +05:30
do k = 1 , resolution ( 3 ) ; do j = 1 , resolution ( 2 ) ; do i = 1 , resolution ( 1 ) / 2 + 1
do m = 1 , 3 ; do n = 1 , 3
2011-04-06 15:28:17 +05:30
temp33_Complex ( m , n ) = sum ( gamma_hat ( i , j , k , m , n , : , : ) * ( workfft ( i * 2 - 1 , j , k , : , : ) &
2011-02-21 20:07:38 +05:30
+ workfft ( i * 2 , j , k , : , : ) * img ) )
enddo ; enddo
2011-07-25 22:00:21 +05:30
workfft ( i * 2 - 1 , j , k , : , : ) = real ( temp33_Complex ) ! change of average strain
2011-02-21 20:07:38 +05:30
workfft ( i * 2 , j , k , : , : ) = aimag ( temp33_Complex )
enddo ; enddo ; enddo
2011-02-07 20:05:42 +05:30
endif
2010-10-13 21:34:44 +05:30
2011-04-06 15:28:17 +05:30
workfft ( 1 , 1 , 1 , : , : ) = defgrad_av - math_I3 ! zero frequency (real part)
workfft ( 2 , 1 , 1 , : , : ) = 0.0_pReal ! zero frequency (imaginary part)
2011-02-09 23:17:28 +05:30
call dfftw_execute_dft_c2r ( plan_fft ( 2 ) , workfft , workfft )
defgrad = defgrad + workfft ( 1 : resolution ( 1 ) , : , : , : , : ) * wgt
2010-10-20 14:29:00 +05:30
do m = 1 , 3 ; do n = 1 , 3
2011-02-07 20:05:42 +05:30
defgrad_av ( m , n ) = sum ( defgrad ( : , : , : , m , n ) ) * wgt
2011-08-10 23:15:37 +05:30
defgrad ( : , : , : , m , n ) = defgrad ( : , : , : , m , n ) + ( defgradAim ( m , n ) - defgrad_av ( m , n ) ) ! anticipated target minus current state
2010-10-20 14:29:00 +05:30
enddo ; enddo
2011-02-09 23:17:28 +05:30
2010-10-20 14:29:00 +05:30
err_stress = maxval ( abs ( mask_stress * ( pstress_av - bc_stress ( : , : , loadcase ) ) ) )
2011-04-06 15:28:17 +05:30
err_stress_tol = maxval ( abs ( pstress_av ) ) * err_stress_tolrel ! accecpt relative error specified
2010-10-27 22:45:49 +05:30
err_defgrad = maxval ( abs ( mask_defgrad * ( defgrad_av - defgradAim ) ) )
2011-02-09 23:17:28 +05:30
2011-08-10 23:15:37 +05:30
print '(2(a,E13.8))' , ' error divergence: ' , err_div , ' Tol. = ' , err_div_tol
print '(2(a,E13.8))' , ' error stress: ' , err_stress , ' Tol. = ' , err_stress_tol
print '(2(a,E13.8))' , ' error deformation gradient: ' , err_defgrad , ' Tol. = ' , err_defgrad_tol
2011-08-03 13:24:32 +05:30
!ToDo: usefull .and. for err_div?
2011-01-07 18:26:45 +05:30
if ( ( err_stress > err_stress_tol . or . err_defgrad > err_defgrad_tol ) . and . err_div < err_div_tol ) then ! change to calculation of BCs, reset damper etc.
2011-02-07 20:05:42 +05:30
calcmode = 0_pInt
2010-10-20 14:29:00 +05:30
defgradAimCorr = 0.0_pReal
2011-08-10 21:32:13 +05:30
damper = 1.0_pReal
2010-10-20 14:29:00 +05:30
endif
end select
2010-10-13 21:34:44 +05:30
enddo ! end looping when convergency is achieved
2010-10-27 22:45:49 +05:30
2011-06-15 23:18:14 +05:30
if ( mod ( step , bc_frequency ( loadcase ) ) == 0_pInt ) & ! at output frequency
write ( 538 ) materialpoint_results ( : , 1 , : ) ! write result to file
2011-07-25 22:00:21 +05:30
print '(A)' , '------------------------------------------------------------'
2011-02-21 20:07:38 +05:30
print '(a,x,f12.7)' , ' Determinant of Deformation Aim: ' , math_det3x3 ( defgradAim )
print '(a,/,3(3(f12.7,x)/))' , ' Deformation Aim: ' , math_transpose3x3 ( defgradAim )
print '(a,/,3(3(f12.7,x)/))' , ' Deformation Gradient:' , math_transpose3x3 ( defgrad_av )
print '(a,/,3(3(f10.4,x)/))' , ' Cauchy Stress / MPa: ' , math_transpose3x3 ( cstress_av ) / 1.e6
2011-07-13 22:03:12 +05:30
print '(a,/,3(3(f10.4,x)/))' , ' Piola-Kirchhoff Stress / MPa: ' , math_transpose3x3 ( pstress_av ) / 1.e6
2010-09-22 14:21:34 +05:30
print '(A)' , '************************************************************'
2010-09-06 15:30:59 +05:30
enddo ! end looping over steps in current loadcase
enddo ! end looping over loadcases
2011-07-25 22:00:21 +05:30
print '(a,i10,a)' , 'A Total of ' , not_converged_counter , ' Steps did not converge!'
2011-01-07 18:26:45 +05:30
close ( 538 )
2011-02-09 23:17:28 +05:30
call dfftw_destroy_plan ( plan_fft ( 1 ) ) ; call dfftw_destroy_plan ( plan_fft ( 2 ) )
2011-05-11 22:08:45 +05:30
end program DAMASK_spectral
2010-06-10 20:21:10 +05:30
!********************************************************************
! quit subroutine to satisfy IO_error
!
!********************************************************************
2010-06-08 15:38:15 +05:30
subroutine quit ( id )
use prec
implicit none
integer ( pInt ) id
stop
2011-05-24 21:27:59 +05:30
end subroutine