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-01-07 18:26:45 +05:30
! - start program with mpie_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
!********************************************************************
2010-06-08 15:38:15 +05:30
program mpie_spectral
2010-06-10 20:21:10 +05:30
!********************************************************************
2010-06-08 15:38:15 +05:30
use mpie_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-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 , &
itmax , fast_execution , mpieNumThreadsInt
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-01-07 18:26:45 +05:30
include 'fftw3.f' !header file for fftw3 (declaring variables). Library files are also needed
2010-06-10 20:21:10 +05:30
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
integer ( pInt ) , parameter :: maxNchunksInput = 24 ! 4 identifiers, 18 values for the matrices and 2 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
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 ) unit , N_l , N_s , N_t , N_n ! 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
real ( pReal ) timeinc
real ( pReal ) , dimension ( : , : , : ) , allocatable :: bc_velocityGrad , &
bc_stress ! velocity gradient and stress BC
real ( pReal ) , dimension ( : ) , allocatable :: bc_timeIncrement ! length of increment
2010-09-22 17:34:43 +05:30
integer ( pInt ) N_Loadcases , steps
integer ( pInt ) , dimension ( : ) , allocatable :: bc_steps ! number of steps
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 , 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
2010-09-22 17:34:43 +05:30
integer ( pInt ) homog , prodnn
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 , &
mask_stress , mask_defgrad
2011-01-07 18:26:45 +05:30
real ( pReal ) , dimension ( 3 , 3 , 3 ) :: temp333_Real
2010-09-22 17:34:43 +05:30
real ( pReal ) , dimension ( 3 , 3 , 3 , 3 ) :: dPdF , c0 , s0
2010-10-20 14:29:00 +05:30
real ( pReal ) , dimension ( 6 ) :: cstress ! cauchy stress in Mandel notation
2011-02-07 20:05:42 +05:30
real ( pReal ) , dimension ( 6 , 6 ) :: dsde , c066 , s066 ! Mandel notation of 4th order tensors
2010-10-20 14:29:00 +05:30
real ( pReal ) , dimension ( : , : , : ) , allocatable :: ddefgrad
2011-01-31 22:37:42 +05:30
real ( pReal ) , dimension ( : , : , : , : , : ) , allocatable :: pstress_field , defgrad , defgradold
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
2010-09-01 13:35:11 +05:30
complex ( pReal ) , dimension ( : , : , : , : , : ) , allocatable :: workfft
complex ( pReal ) , dimension ( 3 , 3 ) :: temp33_Complex
2010-10-20 14:29:00 +05:30
real ( pReal ) , dimension ( 3 , 3 ) :: xinormdyad
2010-09-01 13:35:11 +05:30
real ( pReal ) , dimension ( : , : , : , : , : , : , : ) , allocatable :: gamma_hat
integer ( pInt ) , dimension ( 3 ) :: k_s
2011-02-07 20:05:42 +05:30
real ( pReal ) , dimension ( 3 ) :: xi , xi_middle
2010-09-01 13:35:11 +05:30
integer * 8 , dimension ( 2 , 3 , 3 ) :: plan_fft
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-02-07 20:05:42 +05:30
! loop variables, convergence etc.
real ( pReal ) guessmode , err_div , err_stress , err_defgrad , sigma0
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-02-07 20:05:42 +05:30
integer ( pInt ) loadcase , ielem , iter , calcmode , CPFEM_mode , ierr
logical errmatinv
2010-09-01 13:35:11 +05:30
2010-09-24 18:57:53 +05:30
real ( pReal ) temperature ! not used, but needed for call to CPFEM_general
2011-02-07 20:05:42 +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-01-12 22:32:42 +05:30
!$ call omp_set_num_threads(mpieNumThreadsInt) ! set number of threads for parallel execution set by MPIE_NUM_THREADS
2010-06-10 21:02:06 +05:30
bc_maskvector = ''
2010-06-10 20:21:10 +05:30
unit = 234_pInt
2010-10-27 22:45:49 +05:30
ones = 1.0_pReal ; zeroes = 0.0_pReal
2010-10-13 21:34:44 +05:30
2010-10-27 22:45:49 +05:30
N_l = 0_pInt ; N_s = 0_pInt
N_t = 0_pInt ; N_n = 0_pInt
2011-01-31 22:37:42 +05:30
gotResolution = . false . ; gotDimension = . false . ; gotHomogenization = . false .
2011-01-07 18:26:45 +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
temperature = 30 0.0_pReal
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 ( )
2010-07-01 20:50:06 +05:30
print * , 'Loadcase: ' , trim ( path )
print * , 'Workingdir: ' , trim ( getSolverWorkingDirectoryName ( ) )
2010-06-10 20:21:10 +05:30
2010-07-02 19:40:36 +05:30
if ( . not . IO_open_file ( unit , path ) ) call IO_error ( 45 , ext_msg = path )
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 ) ) )
2010-06-10 20:21:10 +05:30
case ( 'l' , 'velocitygrad' )
N_l = N_l + 1
case ( 's' , 'stress' )
N_s = N_s + 1
case ( 't' , 'time' , 'delta' )
N_t = N_t + 1
case ( 'n' , 'incs' , 'increments' , 'steps' )
N_n = N_n + 1
end select
enddo ! count all identifiers to allocate memory and do sanity check
if ( ( N_l / = N_s ) . or . ( N_s / = N_t ) . or . ( N_t / = N_n ) ) & ! sanity check
2010-10-27 22:45:49 +05:30
call IO_error ( 46 , ext_msg = path ) ! error message for incomplete input file
2010-06-10 20:21:10 +05:30
enddo
2010-06-10 14:20:04 +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
101 N_Loadcases = N_l
2011-01-07 18:26:45 +05:30
! allocate memory depending on lines in input 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
allocate ( bc_velocityGrad ( 3 , 3 , N_Loadcases ) ) ; bc_velocityGrad = 0.0_pReal
allocate ( bc_stress ( 3 , 3 , N_Loadcases ) ) ; bc_stress = 0.0_pReal
allocate ( bc_mask ( 3 , 3 , 2 , N_Loadcases ) ) ; bc_mask = . false .
allocate ( bc_timeIncrement ( N_Loadcases ) ) ; bc_timeIncrement = 0.0_pReal
allocate ( bc_steps ( N_Loadcases ) ) ; bc_steps = 0_pInt
2010-06-10 20:21:10 +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
i = 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
2010-06-10 14:20:04 +05:30
if ( IO_isBlank ( line ) ) cycle ! skip empty lines
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
i = i + 1
2010-10-27 22:45:49 +05:30
posInput = IO_stringPos ( line , maxNchunksInput ) ! ToDo: Add error message for case that information is not complete
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 ) ) )
2010-06-10 20:21:10 +05:30
case ( 'l' , 'velocitygrad' )
valuevector = 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
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
2010-10-20 14:29:00 +05:30
if ( bc_maskvector ( k ) ) valuevector ( k ) = IO_floatValue ( line , posInput , j + k ) ! assign values for the velocity gradient matrix
2010-06-10 20:21:10 +05:30
enddo
2011-01-31 22:37:42 +05:30
bc_mask ( : , : , 1 , i ) = transpose ( reshape ( bc_maskvector , ( / 3 , 3 / ) ) )
bc_velocityGrad ( : , : , i ) = math_transpose3x3 ( reshape ( valuevector , ( / 3 , 3 / ) ) )
2010-06-10 20:21:10 +05:30
case ( 's' , 'stress' )
valuevector = 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
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-01-31 22:37:42 +05:30
bc_mask ( : , : , 2 , i ) = transpose ( reshape ( bc_maskvector , ( / 3 , 3 / ) ) )
bc_stress ( : , : , i ) = math_transpose3x3 ( reshape ( valuevector , ( / 3 , 3 / ) ) )
2010-06-10 20:21:10 +05:30
case ( 't' , 'time' , 'delta' ) ! increment time
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
bc_timeIncrement ( i ) = IO_floatValue ( line , posInput , j + 1 )
2010-06-10 21:02:06 +05:30
case ( 'n' , 'incs' , 'increments' , 'steps' ) ! bc_steps
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
bc_steps ( i ) = IO_intValue ( line , posInput , j + 1 )
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 )
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 , N_Loadcases
2010-09-07 22:07:55 +05:30
if ( any ( bc_mask ( : , : , 1 , i ) == bc_mask ( : , : , 2 , i ) ) ) call IO_error ( 47 , i ) ! bc_mask consistency
2011-02-07 20:05:42 +05:30
print '(a,/,3(3(f12.6,x)/))' , 'L' , math_transpose3x3 ( bc_velocityGrad ( : , : , i ) )
2011-01-31 22:37:42 +05:30
print '(a,/,3(3(f12.6,x)/))' , 'bc_stress' , math_transpose3x3 ( bc_stress ( : , : , i ) )
2011-02-07 20:05:42 +05:30
print '(a,/,3(3(l,x)/))' , 'bc_mask for velocitygrad' , transpose ( bc_mask ( : , : , 1 , i ) )
print '(a,/,3(3(l,x)/))' , 'bc_mask for stress' , transpose ( bc_mask ( : , : , 2 , i ) )
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
print * , 'time' , bc_timeIncrement ( i )
print * , 'incs' , bc_steps ( i )
2010-06-10 20:21:10 +05:30
print * , ''
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
2010-06-25 17:01:05 +05:30
path = getSolverJobName ( )
2010-07-01 20:50:06 +05:30
print * , 'JobName: ' , trim ( path )
2010-07-02 19:40:36 +05:30
if ( . not . IO_open_file ( unit , trim ( path ) / / InputFileExtension ) ) call IO_error ( 101 , ext_msg = path )
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 )
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-20 14:29:00 +05:30
print '(a,/,i4,i4,i4)' , 'resolution a b c' , resolution
2011-01-07 18:26:45 +05:30
print '(a,/,f6.1,f6.1,f6.1)' , 'dimension x y z' , geomdimension
2010-07-02 19:40:36 +05:30
print * , 'homogenization' , homog
2010-10-20 14:29:00 +05:30
2011-02-07 20:05:42 +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
2010-07-05 21:31:36 +05:30
prodnn = resolution ( 1 ) * resolution ( 2 ) * resolution ( 3 )
2011-02-07 20:05:42 +05:30
wgt = 1.0_pReal / real ( prodnn , pReal )
2010-10-13 21:34:44 +05:30
defgradAim = math_I3
defgradAimOld = math_I3
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-01-07 18:26:45 +05:30
call CPFEM_initAll ( temperature , 1_pInt , 1_pInt )
2010-09-07 22:07:55 +05:30
ielem = 0_pInt
2011-01-07 18:26:45 +05:30
c066 = 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 )
2010-09-22 17:34:43 +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
2010-09-01 13:35:11 +05:30
call CPFEM_general ( 2 , math_I3 , math_I3 , temperature , 0.0_pReal , ielem , 1_pInt , cstress , dsde , pstress , dPdF )
2010-10-20 14:29:00 +05:30
c066 = c066 + dsde
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-02-07 20:05:42 +05:30
c066 = c066 * wgt
c0 = math_mandel66to3333 ( c066 )
call math_invert ( 6 , c066 , s066 , i , errmatinv )
s0 = math_mandel66to3333 ( s066 )
2010-10-20 14:29:00 +05:30
2011-02-07 20:05:42 +05:30
!calculation of calculate gamma_hat field in the case of fast execution (needs a lot of memory)
if ( fast_execution ) then
allocate ( gamma_hat ( resolution ( 1 ) / 2 + 1 , resolution ( 2 ) , resolution ( 3 ) , 3 , 3 , 3 , 3 ) ) ; gamma_hat = 0.0_pReal
do k = 1 , resolution ( 3 )
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
if ( j > resolution ( 2 ) / 2 + 1 ) k_s ( 2 ) = k_s ( 2 ) - resolution ( 2 )
do i = 1 , resolution ( 1 ) / 2 + 1
k_s ( 1 ) = i - 1
xi ( 3 ) = 0.0_pReal !for the 2D case
if ( resolution ( 3 ) > 1 ) xi ( 3 ) = real ( k_s ( 3 ) , pReal ) / geomdimension ( 3 ) !3D case
xi ( 2 ) = real ( k_s ( 2 ) , pReal ) / geomdimension ( 2 )
xi ( 1 ) = real ( k_s ( 1 ) , pReal ) / geomdimension ( 1 )
if ( any ( xi / = 0.0_pReal ) ) then
do l = 1 , 3 ; do m = 1 , 3
xinormdyad ( l , m ) = xi ( l ) * xi ( m ) / sum ( xi ** 2 )
enddo ; enddo
else
xinormdyad = 0.0_pReal
endif
temp33_Real = math_mul3333xx33 ( c0 , xinormdyad )
temp33_Real = math_inv3x3 ( temp33_Real )
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.5 * temp33_Real ( l , n ) + 0.5 * temp33_Real ( n , l ) ) * &
( 0.5 * xinormdyad ( m , p ) + 0.5 * xinormdyad ( p , m ) )
enddo ; enddo ; enddo ; enddo
enddo ; enddo ; enddo
else ! or allocate just one fourth order tensor
allocate ( gamma_hat ( 1 , 1 , 1 , 3 , 3 , 3 , 3 ) ) ; gamma_hat = 0.0_pReal
endif
2010-10-20 14:29:00 +05:30
2011-02-07 20:05:42 +05:30
! calculate xi for the calculation of divergence in Fourier space (middle frequency)
xi_middle ( 3 ) = 0.0_pReal
if ( resolution ( 3 ) > 1 ) xi_middle ( 3 ) = real ( resolution ( 3 ) / 2 , pReal ) / geomdimension ( 3 ) !3D case
xi_middle ( 2 ) = real ( resolution ( 2 ) / 2 , pReal ) / geomdimension ( 2 )
xi_middle ( 1 ) = real ( resolution ( 1 ) / 2 , pReal ) / geomdimension ( 1 )
! Initialization of fftw (see manual on fftw.org for more details)
allocate ( workfft ( resolution ( 1 ) / 2 + 1 , resolution ( 2 ) , resolution ( 3 ) , 3 , 3 ) ) ; workfft = 0.0_pReal
allocate ( ddefgrad ( resolution ( 1 ) , resolution ( 2 ) , resolution ( 3 ) ) ) ; ddefgrad = 0.0_pReal
allocate ( pstress_field ( resolution ( 1 ) , resolution ( 2 ) , resolution ( 3 ) , 3 , 3 ) ) ; pstress_field = 0.0_pReal
call dfftw_init_threads ( ierr ) !toDo: add error code
call dfftw_plan_with_nthreads ( mpieNumThreadsInt )
! Do r2c Transform r2c in one step
call dfftw_plan_many_dft_r2c ( plan_fft ( 1 , 1 , 1 ) , 3 , ( / resolution ( 1 ) , resolution ( 2 ) , resolution ( 3 ) / ) , 9 , &
pstress_field ( : , : , : , : , : ) , ( / resolution ( 1 ) , resolution ( 2 ) , resolution ( 3 ) / ) , 1 , prodnn , workfft ( : , : , : , : , : ) , &
( / resolution ( 1 ) / 2 + 1 , resolution ( 2 ) , resolution ( 3 ) / ) , 1 , ( resolution ( 1 ) / 2 + 1 ) * resolution ( 2 ) * resolution ( 3 ) , FFTW_PATIENT )
do m = 1 , 3 ; do n = 1 , 3 ! do the back transform for each single component (saves memory)
call dfftw_plan_dft_c2r ( plan_fft ( 2 , m , n ) , 3 , ( / resolution ( 1 ) , resolution ( 2 ) , resolution ( 3 ) / ) , &
workfft ( : , : , : , m , n ) , ddefgrad ( : , : , : ) , FFTW_PATIENT )
enddo ; enddo
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 ( ) ) &
/ / '_' / / trim ( getLoadcase ( ) ) &
/ / '.spectralOut' , form = 'UNFORMATTED' )
2011-01-12 22:32:42 +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-01-12 22:32:42 +05:30
write ( 538 ) , 'increments' , sum ( bc_steps )
write ( 538 ) , 'eoh'
2011-01-07 18:26:45 +05:30
write ( 538 ) materialpoint_results ( : , 1 , : )
2011-01-12 22:32:42 +05:30
write ( 538 ) materialpoint_results ( : , 1 , : ) !to be conform with t16 Marc format
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
!*************************************************************
!Loop over loadcases defined in the loadcase file
do loadcase = 1 , N_Loadcases
!*************************************************************
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
timeinc = bc_timeIncrement ( loadcase ) / bc_steps ( loadcase )
2010-09-24 18:57:53 +05:30
guessmode = 0.0_pReal ! change of load case, homogeneous guess for the first step
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 ) )
2010-10-20 14:29:00 +05:30
damper = ones / 10
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
do steps = 1 , bc_steps ( loadcase )
!*************************************************************
2010-10-13 21:34:44 +05:30
temp33_Real = defgradAim
defgradAim = defgradAim & ! update macroscopic displacement gradient (defgrad BC)
+ guessmode * mask_stress * ( defgradAim - defgradAimOld ) &
+ math_mul33x33 ( bc_velocityGrad ( : , : , loadcase ) , defgradAim ) * timeinc
defgradAimOld = temp33_Real
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 )
2010-09-01 13:35:11 +05:30
temp33_Real = defgrad ( i , j , k , : , : )
2010-10-13 21:34:44 +05:30
defgrad ( i , j , k , : , : ) = defgrad ( i , j , k , : , : ) & ! old fluctuations as guess for new step, no fluctuations for new loadcase
2010-09-22 17:34:43 +05:30
+ guessmode * ( defgrad ( i , j , k , : , : ) - defgradold ( i , j , k , : , : ) ) &
+ ( 1.0_pReal - guessmode ) * math_mul33x33 ( bc_velocityGrad ( : , : , loadcase ) , defgradold ( i , j , k , : , : ) ) * timeinc
2010-09-07 22:07:55 +05:30
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
if ( all ( bc_mask ( : , : , 1 , loadcase ) ) ) then
calcmode = 1_pInt ! if no stress BC is given (calmode 0 is not needed)
else
calcmode = 0_pInt ! start calculation of BC fulfillment
endif
CPFEM_mode = 1_pInt ! winding forward
2010-07-02 22:45:53 +05:30
iter = 0_pInt
2011-01-31 22:37:42 +05:30
err_div = 2_pReal * err_div_tol ! go into loop
defgradAimCorr = 0.0_pReal ! reset damping calculation
2010-10-20 14:29:00 +05:30
damper = damper * 0.9_pReal
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-01-31 22:37:42 +05:30
do while ( iter < itmax . and . &
2010-10-13 21:34:44 +05:30
( err_div > err_div_tol . or . &
2010-10-27 22:45:49 +05:30
err_stress > err_stress_tol . or . &
err_defgrad > err_defgrad_tol ) )
2011-02-07 20:05:42 +05:30
iter = iter + 1_pInt
print * , ' '
2010-10-27 22:45:49 +05:30
print '(3(A,I5.5,tr2))' , ' Loadcase = ' , loadcase , ' Step = ' , steps , 'Iteration = ' , iter
2011-01-31 22:37:42 +05:30
cstress_av = 0.0_pReal
2010-10-13 21:34:44 +05:30
!*************************************************************
2010-10-20 14:29:00 +05:30
! adjust defgrad to fulfill BCs
2011-01-31 22:37:42 +05:30
select case ( calcmode )
2010-10-20 14:29:00 +05:30
case ( 0 )
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 )
ielem = ielem + 1
call CPFEM_general ( 3 , defgradold ( i , j , k , : , : ) , defgrad ( i , j , k , : , : ) , &
temperature , timeinc , ielem , 1_pInt , &
cstress , dsde , pstress , dPdF )
enddo ; enddo ; enddo
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,
defgradold ( i , j , k , : , : ) , defgrad ( i , j , k , : , : ) , & ! others get 2 (saves winding forward effort)
temperature , timeinc , ielem , 1_pInt , &
cstress , dsde , pstress , dPdF )
CPFEM_mode = 2_pInt
2011-01-07 18:26:45 +05:30
pstress_field ( 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-01-31 22:37:42 +05:30
cstress_av = cstress_av * wgt
2010-10-20 14:29:00 +05:30
do m = 1 , 3 ; do n = 1 , 3
2011-01-31 22:37:42 +05:30
pstress_av ( m , n ) = sum ( pstress_field ( : , : , : , m , n ) ) * wgt
2010-10-20 14:29:00 +05:30
defgrad_av ( m , n ) = sum ( defgrad ( : , : , : , m , n ) ) * wgt
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 ) ) ) )
err_stress_tol = maxval ( abs ( pstress_av ) ) * err_stress_tolrel
print * , 'Correcting deformation gradient to fullfill BCs'
defgradAimCorrPrev = defgradAimCorr
defgradAimCorr = - mask_stress * math_mul3333xx33 ( s0 , ( mask_stress * ( pstress_av - bc_stress ( : , : , loadcase ) ) ) )
do m = 1 , 3 ; do n = 1 , 3 ! calculate damper (correction is far to strong)
if ( sign ( 1.0_pReal , defgradAimCorr ( m , n ) ) / = sign ( 1.0_pReal , defgradAimCorrPrev ( m , n ) ) ) then
damper ( m , n ) = max ( 0.01_pReal , damper ( m , n ) * 0.8 )
2010-10-13 21:34:44 +05:30
else
2010-10-20 14:29:00 +05:30
damper ( m , n ) = min ( 1.0_pReal , damper ( m , n ) * 1.2 )
2010-10-13 21:34:44 +05:30
endif
2010-10-20 14:29:00 +05:30
enddo ; enddo
defgradAimCorr = mask_Stress * ( damper * defgradAimCorr )
defgradAim = defgradAim + defgradAimCorr
2010-10-13 21:34:44 +05:30
2010-10-20 14:29:00 +05:30
do m = 1 , 3 ; do n = 1 , 3
defgrad ( : , : , : , m , n ) = defgrad ( : , : , : , m , n ) + ( defgradAim ( m , n ) - defgrad_av ( m , n ) ) !anticipated target minus current state
enddo ; enddo
err_div = 2 * err_div_tol
err_defgrad = maxval ( abs ( mask_defgrad * ( defgrad_av - defgradAim ) ) )
2011-01-31 22:37:42 +05:30
print '(a,/,3(3(f12.7,x)/))' , ' Deformation Gradient: ' , math_transpose3x3 ( defgrad_av )
2011-02-07 20:05:42 +05:30
print '(a,/,3(3(f10.4,x)/))' , ' Cauchy Stress [MPa]: ' , math_transpose3x3 ( cstress_av ) / 1.e6
print '(2(a,E8.2))' , ' error stress ' , err_stress , ' Tol. = ' , err_stress_tol
2010-10-27 22:45:49 +05:30
print '(2(a,E8.2))' , ' error deformation gradient ' , err_defgrad , ' Tol. = ' , err_defgrad_tol * 0.8
2010-10-20 14:29:00 +05:30
if ( err_stress < err_stress_tol * 0.8 ) then
2011-01-31 22:37:42 +05:30
calcmode = 1_pInt
2010-10-20 14:29:00 +05:30
endif
! 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
2010-10-20 14:29:00 +05:30
call CPFEM_general ( 3 , defgradold ( i , j , k , : , : ) , defgrad ( i , j , k , : , : ) , &
temperature , timeinc , ielem , 1_pInt , &
cstress , dsde , pstress , dPdF )
enddo ; enddo ; enddo
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
2010-10-20 14:29:00 +05:30
call CPFEM_general ( 2 , &
defgradold ( i , j , k , : , : ) , defgrad ( i , j , k , : , : ) , &
temperature , timeinc , ielem , 1_pInt , &
cstress , dsde , pstress , dPdF )
pstress_field ( 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
do m = 1 , 3 ; do n = 1 , 3
pstress_av ( m , n ) = sum ( pstress_field ( : , : , : , m , n ) ) * wgt
enddo ; enddo
2010-10-20 14:29:00 +05:30
print * , 'Calculating equilibrium using spectral method'
err_div = 0.0_pReal ; sigma0 = 0.0_pReal
2011-02-07 20:05:42 +05:30
call dfftw_execute_dft_r2c ( plan_fft ( 1 , 1 , 1 ) , pstress_field , workfft ) ! FFT of pstress
do m = 1 , 3
sigma0 = max ( sigma0 , sum ( abs ( workfft ( 1 , 1 , 1 , m , : ) ) ) ) ! L infinity Norm of stress tensor
enddo
err_div = ( maxval ( abs ( math_mul33x3_complex ( workfft ( resolution ( 1 ) / 2 + 1 , resolution ( 2 ) / 2 + 1 , resolution ( 3 ) / 2 + 1 , : , : ) , xi_middle ) ) ) ) ! L infinity Norm of div(stress)
err_div = err_div / sigma0 !weighting of error
if ( fast_execution ) then ! fast execution with stored gamma_hat
2010-10-20 14:29:00 +05:30
do k = 1 , resolution ( 3 ) ; do j = 1 , resolution ( 2 ) ; do i = 1 , resolution ( 1 ) / 2 + 1
temp33_Complex = 0.0_pReal
2010-10-13 21:34:44 +05:30
do m = 1 , 3 ; do n = 1 , 3
2010-10-20 14:29:00 +05:30
temp33_Complex ( m , n ) = sum ( gamma_hat ( i , j , k , m , n , : , : ) * workfft ( i , j , k , : , : ) )
2010-10-13 21:34:44 +05:30
enddo ; enddo
2010-10-20 14:29:00 +05:30
workfft ( i , j , k , : , : ) = temp33_Complex ( : , : )
2011-02-07 20:05:42 +05:30
enddo ; enddo ; enddo
else ! memory saving version, in-time calculation of gamma_hat
do k = 1 , resolution ( 3 )
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
if ( j > resolution ( 2 ) / 2 + 1 ) k_s ( 2 ) = k_s ( 2 ) - resolution ( 2 )
do i = 1 , resolution ( 1 ) / 2 + 1
k_s ( 1 ) = i - 1
xi ( 3 ) = 0.0_pReal !for the 2D case
if ( resolution ( 3 ) > 1 ) xi ( 3 ) = real ( k_s ( 3 ) , pReal ) / geomdimension ( 3 ) !3D case
xi ( 2 ) = real ( k_s ( 2 ) , pReal ) / geomdimension ( 2 )
xi ( 1 ) = real ( k_s ( 1 ) , pReal ) / geomdimension ( 1 )
if ( any ( xi ( : ) / = 0.0_pReal ) ) then
do l = 1 , 3 ; do m = 1 , 3
xinormdyad ( l , m ) = xi ( l ) * xi ( m ) / sum ( xi ** 2 )
enddo ; enddo
else
xinormdyad = 0.0_pReal
endif
temp33_Real = math_mul3333xx33 ( c0 , xinormdyad )
temp33_Real = math_inv3x3 ( temp33_Real )
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.5 * temp33_Real ( l , n ) + 0.5 * temp33_Real ( n , l ) ) * &
( 0.5 * xinormdyad ( m , p ) + 0.5 * xinormdyad ( p , m ) )
enddo ; enddo ; enddo ; enddo
temp33_Complex = 0.0_pReal
do m = 1 , 3 ; do n = 1 , 3
temp33_Complex ( m , n ) = sum ( gamma_hat ( 1 , 1 , 1 , m , n , : , : ) * workfft ( i , j , k , : , : ) )
enddo ; enddo
workfft ( i , j , k , : , : ) = temp33_Complex ( : , : )
enddo
enddo
enddo
endif
2010-10-13 21:34:44 +05:30
2011-02-07 20:05:42 +05:30
workfft ( 1 , 1 , 1 , : , : ) = defgrad_av - math_I3 !zero frequency
2010-10-20 14:29:00 +05:30
do m = 1 , 3 ; do n = 1 , 3
2011-02-07 20:05:42 +05:30
call dfftw_execute_dft_c2r ( plan_fft ( 2 , m , n ) , workfft ( : , : , : , m , n ) , ddefgrad ( : , : , : ) )
defgrad ( : , : , : , m , n ) = defgrad ( : , : , : , m , n ) + ddefgrad * wgt
defgrad_av ( m , n ) = sum ( defgrad ( : , : , : , m , n ) ) * wgt
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
err_stress = maxval ( abs ( mask_stress * ( pstress_av - bc_stress ( : , : , loadcase ) ) ) )
err_stress_tol = maxval ( abs ( pstress_av ) ) * err_stress_tolrel !accecpt relativ error specified
2010-10-27 22:45:49 +05:30
err_defgrad = maxval ( abs ( mask_defgrad * ( defgrad_av - defgradAim ) ) )
2011-02-07 20:05:42 +05:30
print '(2(a,E8.2))' , ' error divergence ' , err_div , ' Tol. = ' , err_div_tol
print '(2(a,E8.2))' , ' error stress ' , err_stress , ' Tol. = ' , err_stress_tol
2010-10-27 22:45:49 +05:30
print '(2(a,E8.2))' , ' error deformation gradient ' , err_defgrad , ' Tol. = ' , err_defgrad_tol
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
damper = damper * 0.9_pReal
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-01-07 18:26:45 +05:30
write ( 538 ) materialpoint_results ( : , 1 , : ) !write to output file
2010-10-27 22:45:49 +05:30
2011-01-07 18:26:45 +05:30
print '(a,x,f12.7)' , ' Determinant of Deformation Aim:' , math_det3x3 ( defgradAim )
2011-02-07 20:05:42 +05:30
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
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-01-07 18:26:45 +05:30
close ( 538 )
do i = 1 , 2 ; do m = 1 , 3 ; do n = 1 , 3
call dfftw_destroy_plan ( plan_fft ( i , m , n ) )
enddo ; enddo ; enddo
2010-09-01 13:35:11 +05:30
2010-06-10 20:21:10 +05:30
end program mpie_spectral
!********************************************************************
! 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
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
end subroutine