reworked crystallite part to allow for flexible user output
--> new "crystallite" part in config file --> new "crystallite" option for microstructures --> new output file "...job.outputCrystallite" to be used in conjunction with marc_addUserOutput for meaningful naming of User Defined Vars.
This commit is contained in:
parent
538faecf45
commit
8c8ed34356
|
@ -959,11 +959,15 @@ endfunction
|
|||
msg = 'No homogenization specified via State Variable 2'
|
||||
case (120)
|
||||
msg = 'No microstructure specified via State Variable 3'
|
||||
case (125)
|
||||
msg = 'No entries in config part'
|
||||
case (130)
|
||||
msg = 'Homogenization index out of bounds'
|
||||
case (140)
|
||||
msg = 'Microstructure index out of bounds'
|
||||
case (150)
|
||||
msg = 'Crystallite index out of bounds'
|
||||
case (155)
|
||||
msg = 'Phase index out of bounds'
|
||||
case (160)
|
||||
msg = 'Texture index out of bounds'
|
||||
|
|
|
@ -98,7 +98,7 @@ subroutine constitutive_init()
|
|||
write(fileunit,'(a)') '['//trim(phase_name(p))//']'
|
||||
write(fileunit,*)
|
||||
if (knownConstitution) then
|
||||
write(fileunit,'(a)') '#'//char(9)//'constitution'//char(9)//trim(phase_constitution(p))
|
||||
write(fileunit,'(a)') '(constitution)'//char(9)//trim(phase_constitution(p))
|
||||
do e = 1,phase_Noutput(p)
|
||||
write(fileunit,'(a,i4)') trim(thisOutput(e,i))//char(9),thisSize(e,i)
|
||||
enddo
|
||||
|
|
|
@ -19,8 +19,12 @@ implicit none
|
|||
! ****************************************************************
|
||||
! *** General variables for the crystallite calculation ***
|
||||
! ****************************************************************
|
||||
integer(pInt), parameter :: crystallite_Nresults = 14_pInt ! phaseID, volume, Euler angles, def gradient
|
||||
|
||||
integer(pInt) crystallite_maxSizePostResults
|
||||
integer(pInt), dimension(:), allocatable :: crystallite_sizePostResults
|
||||
integer(pInt), dimension(:,:), allocatable :: crystallite_sizePostResult
|
||||
character(len=64), dimension(:,:), allocatable :: crystallite_output ! name of each post result output
|
||||
|
||||
real(pReal), dimension (:,:,:), allocatable :: &
|
||||
crystallite_dt, & ! requested time increment of each grain
|
||||
crystallite_subdt, & ! substepped time increment of each grain
|
||||
|
@ -73,104 +77,185 @@ CONTAINS
|
|||
! allocate and initialize per grain variables
|
||||
!********************************************************************
|
||||
subroutine crystallite_init(Temperature)
|
||||
|
||||
!*** variables and functions from other modules ***!
|
||||
use prec, only: pInt, &
|
||||
pReal
|
||||
use debug, only: debug_info, &
|
||||
debug_reset
|
||||
use math, only: math_I3, &
|
||||
math_EulerToR
|
||||
use FEsolving, only: FEsolving_execElem, &
|
||||
FEsolving_execIP
|
||||
use mesh, only: mesh_element, &
|
||||
mesh_NcpElems, &
|
||||
mesh_maxNips, &
|
||||
mesh_maxNipNeighbors
|
||||
use material, only: homogenization_Ngrains, &
|
||||
homogenization_maxNgrains, &
|
||||
material_EulerAngles, &
|
||||
material_phase, &
|
||||
phase_localConstitution
|
||||
implicit none
|
||||
|
||||
!*** input variables ***!
|
||||
real(pReal) Temperature
|
||||
|
||||
!*** variables and functions from other modules ***!
|
||||
use prec, only: pInt, &
|
||||
pReal
|
||||
use debug, only: debug_info, &
|
||||
debug_reset
|
||||
use math, only: math_I3, &
|
||||
math_EulerToR
|
||||
use FEsolving, only: FEsolving_execElem, &
|
||||
FEsolving_execIP
|
||||
use mesh, only: mesh_element, &
|
||||
mesh_NcpElems, &
|
||||
mesh_maxNips, &
|
||||
mesh_maxNipNeighbors
|
||||
use IO
|
||||
use material
|
||||
|
||||
!*** output variables ***!
|
||||
implicit none
|
||||
integer(pInt), parameter :: file = 200
|
||||
|
||||
!*** local variables ***!
|
||||
integer(pInt) g, & ! grain number
|
||||
i, & ! integration point number
|
||||
e, & ! element number
|
||||
gMax, & ! maximum number of grains
|
||||
iMax, & ! maximum number of integration points
|
||||
eMax, & ! maximum number of elements
|
||||
nMax, & ! maximum number of ip neighbors
|
||||
myNgrains
|
||||
!*** input variables ***!
|
||||
real(pReal) Temperature
|
||||
|
||||
!*** output variables ***!
|
||||
|
||||
!*** local variables ***!
|
||||
integer(pInt), parameter :: maxNchunks = 2
|
||||
integer(pInt), dimension(1+2*maxNchunks) :: positions
|
||||
integer(pInt) g, & ! grain number
|
||||
i, & ! integration point number
|
||||
e, & ! element number
|
||||
gMax, & ! maximum number of grains
|
||||
iMax, & ! maximum number of integration points
|
||||
eMax, & ! maximum number of elements
|
||||
nMax, & ! maximum number of ip neighbors
|
||||
myNgrains, & ! number of grains in current IP
|
||||
myCrystallite ! crystallite of current elem
|
||||
integer(pInt) section, j,p, output, mySize
|
||||
character(len=64) tag
|
||||
character(len=1024) line
|
||||
|
||||
gMax = homogenization_maxNgrains
|
||||
iMax = mesh_maxNips
|
||||
eMax = mesh_NcpElems
|
||||
nMax = mesh_maxNipNeighbors
|
||||
|
||||
allocate(crystallite_Temperature(gMax,iMax,eMax)); crystallite_Temperature = Temperature
|
||||
allocate(crystallite_P(3,3,gMax,iMax,eMax)); crystallite_P = 0.0_pReal
|
||||
allocate(crystallite_Fe(3,3,gMax,iMax,eMax)); crystallite_Fe = 0.0_pReal
|
||||
allocate(crystallite_Fp(3,3,gMax,iMax,eMax)); crystallite_Fp = 0.0_pReal
|
||||
allocate(crystallite_invFp(3,3,gMax,iMax,eMax)); crystallite_invFp = 0.0_pReal
|
||||
allocate(crystallite_Lp(3,3,gMax,iMax,eMax)); crystallite_Lp = 0.0_pReal
|
||||
allocate(crystallite_Tstar_v(6,gMax,iMax,eMax)); crystallite_Tstar_v = 0.0_pReal
|
||||
allocate(crystallite_F0(3,3,gMax,iMax,eMax)); crystallite_F0 = 0.0_pReal
|
||||
allocate(crystallite_Fp0(3,3,gMax,iMax,eMax)); crystallite_Fp0 = 0.0_pReal
|
||||
allocate(crystallite_Lp0(3,3,gMax,iMax,eMax)); crystallite_Lp0 = 0.0_pReal
|
||||
allocate(crystallite_Tstar0_v(6,gMax,iMax,eMax)); crystallite_Tstar0_v = 0.0_pReal
|
||||
allocate(crystallite_partionedTemperature0(gMax,iMax,eMax)); crystallite_partionedTemperature0 = 0.0_pReal
|
||||
allocate(crystallite_partionedF(3,3,gMax,iMax,eMax)); crystallite_partionedF = 0.0_pReal
|
||||
allocate(crystallite_partionedF0(3,3,gMax,iMax,eMax)); crystallite_partionedF0 = 0.0_pReal
|
||||
allocate(crystallite_partionedFp0(3,3,gMax,iMax,eMax)); crystallite_partionedFp0 = 0.0_pReal
|
||||
allocate(crystallite_partionedLp0(3,3,gMax,iMax,eMax)); crystallite_partionedLp0 = 0.0_pReal
|
||||
allocate(crystallite_partionedTstar0_v(6,gMax,iMax,eMax)); crystallite_partionedTstar0_v = 0.0_pReal
|
||||
allocate(crystallite_subTemperature0(gMax,iMax,eMax)); crystallite_subTemperature0 = 0.0_pReal
|
||||
allocate(crystallite_subF(3,3,gMax,iMax,eMax)); crystallite_subF = 0.0_pReal
|
||||
allocate(crystallite_subF0(3,3,gMax,iMax,eMax)); crystallite_subF0 = 0.0_pReal
|
||||
allocate(crystallite_subFp0(3,3,gMax,iMax,eMax)); crystallite_subFp0 = 0.0_pReal
|
||||
allocate(crystallite_subLp0(3,3,gMax,iMax,eMax)); crystallite_subLp0 = 0.0_pReal
|
||||
allocate(crystallite_R(3,3,gMax,iMax,eMax)); crystallite_R = 0.0_pReal
|
||||
allocate(crystallite_eulerangles(3,gMax,iMax,eMax)); crystallite_eulerangles = 0.0_pReal
|
||||
allocate(crystallite_misorientation(4,nMax,gMax,iMax,eMax)); crystallite_misorientation = 0.0_pReal
|
||||
allocate(crystallite_subTstar0_v(6,gMax,iMax,eMax)); crystallite_subTstar0_v = 0.0_pReal
|
||||
allocate(crystallite_dPdF(3,3,3,3,gMax,iMax,eMax)); crystallite_dPdF = 0.0_pReal
|
||||
allocate(crystallite_fallbackdPdF(3,3,3,3,gMax,iMax,eMax)); crystallite_fallbackdPdF = 0.0_pReal
|
||||
allocate(crystallite_dt(gMax,iMax,eMax)); crystallite_dt = 0.0_pReal
|
||||
allocate(crystallite_subdt(gMax,iMax,eMax)); crystallite_subdt = 0.0_pReal
|
||||
allocate(crystallite_subFrac(gMax,iMax,eMax)); crystallite_subFrac = 0.0_pReal
|
||||
allocate(crystallite_subStep(gMax,iMax,eMax)); crystallite_subStep = 0.0_pReal
|
||||
allocate(crystallite_localConstitution(gMax,iMax,eMax)); crystallite_localConstitution = .true.
|
||||
allocate(crystallite_requested(gMax,iMax,eMax)); crystallite_requested = .false.
|
||||
allocate(crystallite_converged(gMax,iMax,eMax)); crystallite_converged = .true.
|
||||
allocate(crystallite_stateConverged(gMax,iMax,eMax)); crystallite_stateConverged = .false.
|
||||
allocate(crystallite_temperatureConverged(gMax,iMax,eMax)); crystallite_temperatureConverged = .false.
|
||||
allocate(crystallite_todo(gMax,iMax,eMax)); crystallite_todo = .true.
|
||||
|
||||
gMax = homogenization_maxNgrains
|
||||
iMax = mesh_maxNips
|
||||
eMax = mesh_NcpElems
|
||||
nMax = mesh_maxNipNeighbors
|
||||
allocate(crystallite_output(maxval(crystallite_Noutput), &
|
||||
material_Ncrystallite)) ; crystallite_output = ''
|
||||
allocate(crystallite_sizePostResults(material_Ncrystallite)) ; crystallite_sizePostResults = 0_pInt
|
||||
allocate(crystallite_sizePostResult(maxval(crystallite_Noutput), &
|
||||
material_Ncrystallite)) ; crystallite_sizePostResult = 0_pInt
|
||||
|
||||
if(.not. IO_open_file(file,material_configFile)) call IO_error (100) ! corrupt config file
|
||||
line = ''
|
||||
section = 0
|
||||
|
||||
do while (IO_lc(IO_getTag(line,'<','>')) /= material_partCrystallite) ! wind forward to <crystallite>
|
||||
read(file,'(a1024)',END=100) line
|
||||
enddo
|
||||
|
||||
allocate(crystallite_Temperature(gMax,iMax,eMax)); crystallite_Temperature = Temperature
|
||||
allocate(crystallite_P(3,3,gMax,iMax,eMax)); crystallite_P = 0.0_pReal
|
||||
allocate(crystallite_Fe(3,3,gMax,iMax,eMax)); crystallite_Fe = 0.0_pReal
|
||||
allocate(crystallite_Fp(3,3,gMax,iMax,eMax)); crystallite_Fp = 0.0_pReal
|
||||
allocate(crystallite_invFp(3,3,gMax,iMax,eMax)); crystallite_invFp = 0.0_pReal
|
||||
allocate(crystallite_Lp(3,3,gMax,iMax,eMax)); crystallite_Lp = 0.0_pReal
|
||||
allocate(crystallite_Tstar_v(6,gMax,iMax,eMax)); crystallite_Tstar_v = 0.0_pReal
|
||||
allocate(crystallite_F0(3,3,gMax,iMax,eMax)); crystallite_F0 = 0.0_pReal
|
||||
allocate(crystallite_Fp0(3,3,gMax,iMax,eMax)); crystallite_Fp0 = 0.0_pReal
|
||||
allocate(crystallite_Lp0(3,3,gMax,iMax,eMax)); crystallite_Lp0 = 0.0_pReal
|
||||
allocate(crystallite_Tstar0_v(6,gMax,iMax,eMax)); crystallite_Tstar0_v = 0.0_pReal
|
||||
allocate(crystallite_partionedTemperature0(gMax,iMax,eMax)); crystallite_partionedTemperature0 = 0.0_pReal
|
||||
allocate(crystallite_partionedF(3,3,gMax,iMax,eMax)); crystallite_partionedF = 0.0_pReal
|
||||
allocate(crystallite_partionedF0(3,3,gMax,iMax,eMax)); crystallite_partionedF0 = 0.0_pReal
|
||||
allocate(crystallite_partionedFp0(3,3,gMax,iMax,eMax)); crystallite_partionedFp0 = 0.0_pReal
|
||||
allocate(crystallite_partionedLp0(3,3,gMax,iMax,eMax)); crystallite_partionedLp0 = 0.0_pReal
|
||||
allocate(crystallite_partionedTstar0_v(6,gMax,iMax,eMax)); crystallite_partionedTstar0_v = 0.0_pReal
|
||||
allocate(crystallite_subTemperature0(gMax,iMax,eMax)); crystallite_subTemperature0 = 0.0_pReal
|
||||
allocate(crystallite_subF(3,3,gMax,iMax,eMax)); crystallite_subF = 0.0_pReal
|
||||
allocate(crystallite_subF0(3,3,gMax,iMax,eMax)); crystallite_subF0 = 0.0_pReal
|
||||
allocate(crystallite_subFp0(3,3,gMax,iMax,eMax)); crystallite_subFp0 = 0.0_pReal
|
||||
allocate(crystallite_subLp0(3,3,gMax,iMax,eMax)); crystallite_subLp0 = 0.0_pReal
|
||||
allocate(crystallite_R(3,3,gMax,iMax,eMax)); crystallite_R = 0.0_pReal
|
||||
allocate(crystallite_eulerangles(3,gMax,iMax,eMax)); crystallite_eulerangles = 0.0_pReal
|
||||
allocate(crystallite_misorientation(4,nMax,gMax,iMax,eMax)); crystallite_misorientation = 0.0_pReal
|
||||
allocate(crystallite_subTstar0_v(6,gMax,iMax,eMax)); crystallite_subTstar0_v = 0.0_pReal
|
||||
allocate(crystallite_dPdF(3,3,3,3,gMax,iMax,eMax)); crystallite_dPdF = 0.0_pReal
|
||||
allocate(crystallite_fallbackdPdF(3,3,3,3,gMax,iMax,eMax)); crystallite_fallbackdPdF = 0.0_pReal
|
||||
allocate(crystallite_dt(gMax,iMax,eMax)); crystallite_dt = 0.0_pReal
|
||||
allocate(crystallite_subdt(gMax,iMax,eMax)); crystallite_subdt = 0.0_pReal
|
||||
allocate(crystallite_subFrac(gMax,iMax,eMax)); crystallite_subFrac = 0.0_pReal
|
||||
allocate(crystallite_subStep(gMax,iMax,eMax)); crystallite_subStep = 0.0_pReal
|
||||
allocate(crystallite_localConstitution(gMax,iMax,eMax)); crystallite_localConstitution = .true.
|
||||
allocate(crystallite_requested(gMax,iMax,eMax)); crystallite_requested = .false.
|
||||
allocate(crystallite_converged(gMax,iMax,eMax)); crystallite_converged = .true.
|
||||
allocate(crystallite_stateConverged(gMax,iMax,eMax)); crystallite_stateConverged = .false.
|
||||
allocate(crystallite_temperatureConverged(gMax,iMax,eMax)); crystallite_temperatureConverged = .false.
|
||||
allocate(crystallite_todo(gMax,iMax,eMax)); crystallite_todo = .true.
|
||||
do ! read thru sections of phase part
|
||||
read(file,'(a1024)',END=100) line
|
||||
if (IO_isBlank(line)) cycle ! skip empty lines
|
||||
if (IO_getTag(line,'<','>') /= '') exit ! stop at next part
|
||||
if (IO_getTag(line,'[',']') /= '') then ! next section
|
||||
section = section + 1
|
||||
output = 0 ! reset output counter
|
||||
endif
|
||||
if (section > 0) then
|
||||
positions = IO_stringPos(line,maxNchunks)
|
||||
tag = IO_lc(IO_stringValue(line,positions,1)) ! extract key
|
||||
select case(tag)
|
||||
case ('(output)')
|
||||
output = output + 1
|
||||
crystallite_output(output,section) = IO_lc(IO_stringValue(line,positions,2))
|
||||
end select
|
||||
endif
|
||||
enddo
|
||||
|
||||
!$OMP PARALLEL DO
|
||||
do e = FEsolving_execElem(1),FEsolving_execElem(2) ! iterate over all cp elements
|
||||
myNgrains = homogenization_Ngrains(mesh_element(3,e))
|
||||
do i = FEsolving_execIP(1,e),FEsolving_execIP(2,e) ! iterate over IPs of this element
|
||||
do g = 1,myNgrains
|
||||
crystallite_partionedTemperature0(g,i,e) = Temperature ! isothermal assumption
|
||||
crystallite_Fp0(:,:,g,i,e) = math_EulerToR(material_EulerAngles(:,g,i,e)) ! plastic def gradient reflects init orientation
|
||||
crystallite_Fe(:,:,g,i,e) = transpose(crystallite_Fp0(:,:,g,i,e))
|
||||
crystallite_F0(:,:,g,i,e) = math_I3
|
||||
crystallite_partionedFp0(:,:,g,i,e) = crystallite_Fp0(:,:,g,i,e)
|
||||
crystallite_partionedF0(:,:,g,i,e) = crystallite_F0(:,:,g,i,e)
|
||||
crystallite_partionedF(:,:,g,i,e) = crystallite_F0(:,:,g,i,e)
|
||||
crystallite_requested(g,i,e) = .true.
|
||||
crystallite_localConstitution(g,i,e) = phase_localConstitution(material_phase(g,i,e))
|
||||
enddo
|
||||
enddo
|
||||
enddo
|
||||
!$OMPEND PARALLEL DO
|
||||
100 close(file)
|
||||
do i = 1,material_Ncrystallite ! sanity checks
|
||||
enddo
|
||||
|
||||
do i = 1,material_Ncrystallite
|
||||
do j = 1,crystallite_Noutput(i)
|
||||
select case(crystallite_output(j,i))
|
||||
case('phase')
|
||||
mySize = 1
|
||||
case('volume')
|
||||
mySize = 1
|
||||
case('orientation')
|
||||
mySize = 3
|
||||
case('defgrad')
|
||||
mySize = 9
|
||||
case default
|
||||
mySize = 0
|
||||
end select
|
||||
|
||||
if (mySize > 0_pInt) then ! any meaningful output found
|
||||
crystallite_sizePostResult(j,i) = mySize
|
||||
crystallite_sizePostResults(i) = crystallite_sizePostResults(i) + mySize
|
||||
endif
|
||||
enddo
|
||||
enddo
|
||||
crystallite_maxSizePostResults = maxval(crystallite_sizePostResults)
|
||||
|
||||
! write description file for crystallite output
|
||||
|
||||
if(.not. IO_open_jobFile(file,'outputCrystallite')) call IO_error (50) ! problems in writing file
|
||||
|
||||
do p = 1,material_Ncrystallite
|
||||
write(file,*)
|
||||
write(file,'(a)') '['//trim(crystallite_name(p))//']'
|
||||
write(file,*)
|
||||
do e = 1,crystallite_Noutput(p)
|
||||
write(file,'(a,i4)') trim(crystallite_output(e,p))//char(9),crystallite_sizePostResult(e,p)
|
||||
enddo
|
||||
enddo
|
||||
|
||||
close(file)
|
||||
|
||||
|
||||
!$OMP PARALLEL DO
|
||||
do e = FEsolving_execElem(1),FEsolving_execElem(2) ! iterate over all cp elements
|
||||
myNgrains = homogenization_Ngrains(mesh_element(3,e)) ! look up homogenization-->grainCount
|
||||
do i = FEsolving_execIP(1,e),FEsolving_execIP(2,e) ! iterate over IPs of this element
|
||||
do g = 1,myNgrains
|
||||
crystallite_partionedTemperature0(g,i,e) = Temperature ! isothermal assumption
|
||||
crystallite_Fp0(:,:,g,i,e) = math_EulerToR(material_EulerAngles(:,g,i,e)) ! plastic def gradient reflects init orientation
|
||||
crystallite_Fe(:,:,g,i,e) = transpose(crystallite_Fp0(:,:,g,i,e))
|
||||
crystallite_F0(:,:,g,i,e) = math_I3
|
||||
crystallite_partionedFp0(:,:,g,i,e) = crystallite_Fp0(:,:,g,i,e)
|
||||
crystallite_partionedF0(:,:,g,i,e) = crystallite_F0(:,:,g,i,e)
|
||||
crystallite_partionedF(:,:,g,i,e) = crystallite_F0(:,:,g,i,e)
|
||||
crystallite_requested(g,i,e) = .true.
|
||||
crystallite_localConstitution(g,i,e) = phase_localConstitution(material_phase(g,i,e))
|
||||
enddo
|
||||
enddo
|
||||
enddo
|
||||
!$OMPEND PARALLEL DO
|
||||
|
||||
call crystallite_orientations()
|
||||
call crystallite_stressAndItsTangent(.true.) ! request elastic answers
|
||||
|
@ -182,8 +267,6 @@ subroutine crystallite_init(Temperature)
|
|||
write(6,*) '<<<+- crystallite init -+>>>'
|
||||
write(6,*) '$Id$'
|
||||
write(6,*)
|
||||
write(6,'(a35,x,7(i5,x))') 'crystallite_Nresults: ', crystallite_Nresults
|
||||
write(6,*)
|
||||
write(6,'(a35,x,7(i5,x))') 'crystallite_Temperature: ', shape(crystallite_Temperature)
|
||||
write(6,'(a35,x,7(i5,x))') 'crystallite_Fe: ', shape(crystallite_Fe)
|
||||
write(6,'(a35,x,7(i5,x))') 'crystallite_Fp: ', shape(crystallite_Fp)
|
||||
|
@ -221,6 +304,8 @@ subroutine crystallite_init(Temperature)
|
|||
write(6,'(a35,x,7(i5,x))') 'crystallite_converged: ', shape(crystallite_converged)
|
||||
write(6,'(a35,x,7(i5,x))') 'crystallite_stateConverged: ', shape(crystallite_stateConverged)
|
||||
write(6,'(a35,x,7(i5,x))') 'crystallite_temperatureConverged: ', shape(crystallite_temperatureConverged)
|
||||
write(6,'(a35,x,7(i5,x))') 'crystallite_sizePostResults: ', shape(crystallite_sizePostResults)
|
||||
write(6,'(a35,x,7(i5,x))') 'crystallite_sizePostResult: ', shape(crystallite_sizePostResult)
|
||||
write(6,*)
|
||||
write(6,*) 'Number of nonlocal grains: ',count(.not. crystallite_localConstitution)
|
||||
call flush(6)
|
||||
|
@ -1505,7 +1590,10 @@ function crystallite_postResults(&
|
|||
!*** variables and functions from other modules ***!
|
||||
use prec, only: pInt, &
|
||||
pReal
|
||||
use material, only: material_phase, &
|
||||
use mesh, only: mesh_element
|
||||
use material, only: microstructure_crystallite, &
|
||||
crystallite_Noutput, &
|
||||
material_phase, &
|
||||
material_volume
|
||||
use constitutive, only: constitutive_sizePostResults, &
|
||||
constitutive_postResults
|
||||
|
@ -1519,29 +1607,37 @@ function crystallite_postResults(&
|
|||
real(pReal), intent(in):: dt ! time increment
|
||||
|
||||
!*** output variables ***!
|
||||
real(pReal), dimension(1+crystallite_Nresults + 1+constitutive_sizePostResults(g,i,e)) :: crystallite_postResults
|
||||
real(pReal), dimension(1+crystallite_sizePostResults(microstructure_crystallite(mesh_element(4,e)))+ &
|
||||
1+constitutive_sizePostResults(g,i,e)) :: crystallite_postResults
|
||||
|
||||
!*** local variables ***!
|
||||
real(pReal), dimension(3,3) :: U, R
|
||||
integer(pInt) k,l,c
|
||||
logical error
|
||||
integer(pInt) k,l,o,c,crystID
|
||||
logical error
|
||||
|
||||
c = 0_pInt
|
||||
crystallite_postResults(c+1) = crystallite_Nresults; c = c+1_pInt ! size of (hardwired) results
|
||||
if (crystallite_Nresults >= 2) then
|
||||
crystallite_postResults(c+1) = material_phase(g,i,e)
|
||||
crystallite_postResults(c+2) = material_volume(g,i,e)
|
||||
c = c+2_pInt
|
||||
endif
|
||||
if (crystallite_Nresults >= 5) then
|
||||
crystallite_postResults(c+1:c+3) = crystallite_eulerangles(:,g,i,e) ! grain orientation
|
||||
c = c+3_pInt
|
||||
endif
|
||||
if (crystallite_Nresults >= 14) then ! deformation gradient 11,12,13,21,...
|
||||
forall (k=0:2,l=0:2) crystallite_postResults(c+1+k*3+l) = crystallite_partionedF(k+1,l+1,g,i,e)
|
||||
c = c+9_pInt
|
||||
endif
|
||||
crystID = microstructure_crystallite(mesh_element(4,e))
|
||||
|
||||
crystallite_postResults = 0.0_pReal
|
||||
c = 0_pInt
|
||||
crystallite_postResults(c+1) = crystallite_sizePostResults(crystID); c = c+1_pInt ! size of results from cryst
|
||||
|
||||
do o = 1,crystallite_Noutput(crystID)
|
||||
select case(crystallite_output(o,crystID))
|
||||
case ('phase')
|
||||
crystallite_postResults(c+1) = material_phase(g,i,e) ! phaseID of grain
|
||||
c = c + 1_pInt
|
||||
case ('volume')
|
||||
crystallite_postResults(c+1) = material_volume(g,i,e) ! grain volume (not fraction but absolute, right?)
|
||||
c = c + 1_pInt
|
||||
case ('orientation')
|
||||
crystallite_postResults(c+1:c+3) = crystallite_eulerangles(:,g,i,e) ! grain orientation
|
||||
c = c + 3_pInt
|
||||
case ('defgrad')
|
||||
forall (k=0:2,l=0:2) crystallite_postResults(c+1+k*3+l) = crystallite_partionedF(k+1,l+1,g,i,e)
|
||||
c = c+9_pInt
|
||||
end select
|
||||
enddo
|
||||
|
||||
crystallite_postResults(c+1) = constitutive_sizePostResults(g,i,e); c = c+1_pInt ! size of constitutive results
|
||||
crystallite_postResults(c+1:c+constitutive_sizePostResults(g,i,e)) = &
|
||||
constitutive_postResults(crystallite_Tstar_v(:,g,i,e), crystallite_subTstar0_v(:,g,i,e), crystallite_Fe, crystallite_Fp, &
|
||||
|
|
|
@ -59,7 +59,7 @@ subroutine homogenization_init(Temperature)
|
|||
use mesh, only: mesh_maxNips,mesh_NcpElems,mesh_element,FE_Nips
|
||||
use material
|
||||
use constitutive, only: constitutive_maxSizePostResults
|
||||
use crystallite, only: crystallite_Nresults
|
||||
use crystallite, only: crystallite_maxSizePostResults
|
||||
use homogenization_isostrain
|
||||
use homogenization_RGC ! RGC homogenization added <<<updated 31.07.2009>>>
|
||||
|
||||
|
@ -99,7 +99,8 @@ subroutine homogenization_init(Temperature)
|
|||
write(fileunit,'(a)') '['//trim(homogenization_name(p))//']'
|
||||
write(fileunit,*)
|
||||
if (knownHomogenization) then
|
||||
write(fileunit,'(a)') '#'//char(9)//'homogenization'//char(9)//trim(homogenization_type(p))
|
||||
write(fileunit,'(a)') '(type)'//char(9)//trim(homogenization_type(p))
|
||||
write(fileunit,'(a,i)') '(ngrains)'//char(9),homogenization_Ngrains(p)
|
||||
do e = 1,homogenization_Noutput(p)
|
||||
write(fileunit,'(a,i4)') trim(thisOutput(e,i))//char(9),thisSize(e,i)
|
||||
enddo
|
||||
|
@ -168,8 +169,9 @@ subroutine homogenization_init(Temperature)
|
|||
homogenization_maxSizePostResults = maxval(homogenization_sizePostResults)
|
||||
|
||||
materialpoint_sizeResults = 1+ 1+homogenization_maxSizePostResults + & ! grain count, homogSize, homogResult
|
||||
homogenization_maxNgrains*(1+crystallite_Nresults+1+constitutive_maxSizePostResults)
|
||||
allocate(materialpoint_results( materialpoint_sizeResults, mesh_maxNips,mesh_NcpElems))
|
||||
homogenization_maxNgrains*(1+crystallite_maxSizePostResults+ & ! results count, cryst results
|
||||
1+constitutive_maxSizePostResults) ! results count, constitutive results
|
||||
allocate(materialpoint_results(materialpoint_sizeResults, mesh_maxNips,mesh_NcpElems))
|
||||
|
||||
|
||||
! *** Output to MARC output file ***
|
||||
|
@ -505,17 +507,18 @@ subroutine materialpoint_postResults(dt)
|
|||
|
||||
use FEsolving, only: FEsolving_execElem, FEsolving_execIP
|
||||
use mesh, only: mesh_element
|
||||
use material, only: homogenization_Ngrains
|
||||
use material, only: homogenization_Ngrains, microstructure_crystallite
|
||||
use constitutive, only: constitutive_sizePostResults, constitutive_postResults
|
||||
use crystallite, only: crystallite_Nresults, crystallite_postResults
|
||||
use crystallite, only: crystallite_sizePostResults, crystallite_postResults
|
||||
implicit none
|
||||
|
||||
real(pReal), intent(in) :: dt
|
||||
integer(pInt) g,i,e,c,d,myNgrains
|
||||
integer(pInt) g,i,e,c,d,myNgrains,myCrystallite
|
||||
|
||||
!$OMP PARALLEL DO
|
||||
do e = FEsolving_execElem(1),FEsolving_execElem(2) ! iterate over elements to be processed
|
||||
myNgrains = homogenization_Ngrains(mesh_element(3,e))
|
||||
myCrystallite = microstructure_crystallite(mesh_element(4,e))
|
||||
do i = FEsolving_execIP(1,e),FEsolving_execIP(2,e) ! iterate over IPs of this element to be processed
|
||||
c = 0_pInt
|
||||
materialpoint_results(c+1,i,e) = myNgrains; c = c+1_pInt ! tell number of grains at materialpoint
|
||||
|
@ -526,7 +529,7 @@ subroutine materialpoint_postResults(dt)
|
|||
homogenization_postResults(i,e); c = c+d
|
||||
endif
|
||||
do g = 1,myNgrains ! loop over all grains
|
||||
d = 1+crystallite_Nresults + 1+constitutive_sizePostResults(g,i,e)
|
||||
d = 1+crystallite_sizePostResults(myCrystallite) + 1+constitutive_sizePostResults(g,i,e)
|
||||
materialpoint_results(c+1:c+d,i,e) = & ! tell crystallite results
|
||||
crystallite_postResults(dt,g,i,e); c = c+d
|
||||
enddo
|
||||
|
|
|
@ -1,320 +1,320 @@
|
|||
!* $Id$
|
||||
!*****************************************************
|
||||
!* Module: HOMOGENIZATION_ISOSTRAIN *
|
||||
!*****************************************************
|
||||
!* contains: *
|
||||
!*****************************************************
|
||||
|
||||
! [isostrain]
|
||||
! type isostrain
|
||||
! Ngrains 6
|
||||
! (output) Ngrains
|
||||
|
||||
MODULE homogenization_isostrain
|
||||
|
||||
!*** Include other modules ***
|
||||
use prec, only: pReal,pInt
|
||||
implicit none
|
||||
|
||||
character (len=*), parameter :: homogenization_isostrain_label = 'isostrain'
|
||||
|
||||
integer(pInt), dimension(:), allocatable :: homogenization_isostrain_sizeState, &
|
||||
homogenization_isostrain_Ngrains
|
||||
integer(pInt), dimension(:), allocatable :: homogenization_isostrain_sizePostResults
|
||||
integer(pInt), dimension(:,:), allocatable,target :: homogenization_isostrain_sizePostResult
|
||||
character(len=64), dimension(:,:), allocatable,target :: homogenization_isostrain_output ! name of each post result output
|
||||
|
||||
|
||||
CONTAINS
|
||||
!****************************************
|
||||
!* - homogenization_isostrain_init
|
||||
!* - homogenization_isostrain_stateInit
|
||||
!* - homogenization_isostrain_deformationPartititon
|
||||
!* - homogenization_isostrain_stateUpdate
|
||||
!* - homogenization_isostrain_averageStressAndItsTangent
|
||||
!* - homogenization_isostrain_postResults
|
||||
!****************************************
|
||||
|
||||
|
||||
!**************************************
|
||||
!* Module initialization *
|
||||
!**************************************
|
||||
subroutine homogenization_isostrain_init(&
|
||||
file & ! file pointer to material configuration
|
||||
)
|
||||
|
||||
use prec, only: pInt, pReal
|
||||
use math, only: math_Mandel3333to66, math_Voigt66to3333
|
||||
use IO
|
||||
use material
|
||||
integer(pInt), intent(in) :: file
|
||||
integer(pInt), parameter :: maxNchunks = 2
|
||||
integer(pInt), dimension(1+2*maxNchunks) :: positions
|
||||
integer(pInt) section, maxNinstance, i,j,k,l, output, mySize
|
||||
character(len=64) tag
|
||||
character(len=1024) line
|
||||
|
||||
write(6,*)
|
||||
write(6,'(a20,a20,a12)') '<<<+- homogenization',homogenization_isostrain_label,' init -+>>>'
|
||||
write(6,*) '$Id$'
|
||||
write(6,*)
|
||||
|
||||
maxNinstance = count(homogenization_type == homogenization_isostrain_label)
|
||||
if (maxNinstance == 0) return
|
||||
|
||||
allocate(homogenization_isostrain_sizeState(maxNinstance)) ; homogenization_isostrain_sizeState = 0_pInt
|
||||
allocate(homogenization_isostrain_sizePostResults(maxNinstance)); homogenization_isostrain_sizePostResults = 0_pInt
|
||||
allocate(homogenization_isostrain_sizePostResult(maxval(homogenization_Noutput), &
|
||||
maxNinstance)); homogenization_isostrain_sizePostResult = 0_pInt
|
||||
allocate(homogenization_isostrain_Ngrains(maxNinstance)); homogenization_isostrain_Ngrains = 0_pInt
|
||||
allocate(homogenization_isostrain_output(maxval(homogenization_Noutput), &
|
||||
maxNinstance)) ; homogenization_isostrain_output = ''
|
||||
|
||||
rewind(file)
|
||||
line = ''
|
||||
section = 0
|
||||
|
||||
do while (IO_lc(IO_getTag(line,'<','>')) /= material_partHomogenization) ! wind forward to <homogenization>
|
||||
read(file,'(a1024)',END=100) line
|
||||
enddo
|
||||
|
||||
do ! read thru sections of phase part
|
||||
read(file,'(a1024)',END=100) line
|
||||
if (IO_isBlank(line)) cycle ! skip empty lines
|
||||
if (IO_getTag(line,'<','>') /= '') exit ! stop at next part
|
||||
if (IO_getTag(line,'[',']') /= '') then ! next section
|
||||
section = section + 1
|
||||
output = 0 ! reset output counter
|
||||
endif
|
||||
if (section > 0 .and. homogenization_type(section) == homogenization_isostrain_label) then ! one of my sections
|
||||
i = homogenization_typeInstance(section) ! which instance of my type is present homogenization
|
||||
positions = IO_stringPos(line,maxNchunks)
|
||||
tag = IO_lc(IO_stringValue(line,positions,1)) ! extract key
|
||||
select case(tag)
|
||||
case ('(output)')
|
||||
output = output + 1
|
||||
homogenization_isostrain_output(output,i) = IO_lc(IO_stringValue(line,positions,2))
|
||||
case ('ngrains')
|
||||
homogenization_isostrain_Ngrains(i) = IO_intValue(line,positions,2)
|
||||
end select
|
||||
endif
|
||||
enddo
|
||||
|
||||
100 do i = 1,maxNinstance ! sanity checks
|
||||
enddo
|
||||
|
||||
do i = 1,maxNinstance
|
||||
homogenization_isostrain_sizeState(i) = 0_pInt
|
||||
|
||||
do j = 1,maxval(homogenization_Noutput)
|
||||
select case(homogenization_isostrain_output(j,i))
|
||||
case('ngrains')
|
||||
mySize = 1
|
||||
case default
|
||||
mySize = 0
|
||||
end select
|
||||
|
||||
if (mySize > 0_pInt) then ! any meaningful output found
|
||||
homogenization_isostrain_sizePostResult(j,i) = mySize
|
||||
homogenization_isostrain_sizePostResults(i) = &
|
||||
homogenization_isostrain_sizePostResults(i) + mySize
|
||||
endif
|
||||
enddo
|
||||
enddo
|
||||
|
||||
return
|
||||
|
||||
endsubroutine
|
||||
|
||||
|
||||
!*********************************************************************
|
||||
!* initial homogenization state *
|
||||
!*********************************************************************
|
||||
function homogenization_isostrain_stateInit(myInstance)
|
||||
use prec, only: pReal,pInt
|
||||
implicit none
|
||||
|
||||
!* Definition of variables
|
||||
integer(pInt), intent(in) :: myInstance
|
||||
real(pReal), dimension(homogenization_isostrain_sizeState(myInstance)) :: &
|
||||
homogenization_isostrain_stateInit ! modified <<<updated 31.07.2009>>>
|
||||
|
||||
homogenization_isostrain_stateInit = 0.0_pReal
|
||||
|
||||
return
|
||||
|
||||
endfunction
|
||||
|
||||
|
||||
!********************************************************************
|
||||
! partition material point def grad onto constituents
|
||||
!********************************************************************
|
||||
subroutine homogenization_isostrain_partitionDeformation(&
|
||||
F, & ! partioned def grad per grain
|
||||
!
|
||||
F0, & ! initial partioned def grad per grain
|
||||
avgF, & ! my average def grad
|
||||
state, & ! my state
|
||||
ip, & ! my integration point
|
||||
el & ! my element
|
||||
)
|
||||
use prec, only: pReal,pInt,p_vec
|
||||
use mesh, only: mesh_element,mesh_NcpElems,mesh_maxNips
|
||||
use material, only: homogenization_maxNgrains,homogenization_Ngrains
|
||||
implicit none
|
||||
|
||||
!* Definition of variables
|
||||
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(out) :: F
|
||||
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(in) :: F0
|
||||
real(pReal), dimension (3,3), intent(in) :: avgF
|
||||
type(p_vec), intent(in) :: state
|
||||
integer(pInt), intent(in) :: ip,el
|
||||
integer(pInt) homID, i
|
||||
|
||||
! homID = homogenization_typeInstance(mesh_element(3,el))
|
||||
forall (i = 1:homogenization_Ngrains(mesh_element(3,el))) &
|
||||
F(:,:,i) = avgF
|
||||
|
||||
return
|
||||
|
||||
endsubroutine
|
||||
|
||||
|
||||
!********************************************************************
|
||||
! update the internal state of the homogenization scheme
|
||||
! and tell whether "done" and "happy" with result
|
||||
!********************************************************************
|
||||
function homogenization_isostrain_updateState(&
|
||||
state, & ! my state
|
||||
!
|
||||
P, & ! array of current grain stresses
|
||||
dPdF, & ! array of current grain stiffnesses
|
||||
ip, & ! my integration point
|
||||
el & ! my element
|
||||
)
|
||||
|
||||
use prec, only: pReal,pInt,p_vec
|
||||
use mesh, only: mesh_element,mesh_NcpElems,mesh_maxNips
|
||||
use material, only: homogenization_maxNgrains
|
||||
implicit none
|
||||
|
||||
!* Definition of variables
|
||||
type(p_vec), intent(inout) :: state
|
||||
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(in) :: P
|
||||
real(pReal), dimension (3,3,3,3,homogenization_maxNgrains), intent(in) :: dPdF
|
||||
integer(pInt), intent(in) :: ip,el
|
||||
! integer(pInt) homID
|
||||
logical, dimension(2) :: homogenization_isostrain_updateState
|
||||
|
||||
! homID = homogenization_typeInstance(mesh_element(3,el))
|
||||
homogenization_isostrain_updateState = .true. ! homogenization at material point converged (done and happy)
|
||||
|
||||
return
|
||||
|
||||
endfunction
|
||||
|
||||
|
||||
!********************************************************************
|
||||
! derive average stress and stiffness from constituent quantities
|
||||
!********************************************************************
|
||||
subroutine homogenization_isostrain_averageStressAndItsTangent(&
|
||||
avgP, & ! average stress at material point
|
||||
dAvgPdAvgF, & ! average stiffness at material point
|
||||
!
|
||||
P, & ! array of current grain stresses
|
||||
dPdF, & ! array of current grain stiffnesses
|
||||
ip, & ! my integration point
|
||||
el & ! my element
|
||||
)
|
||||
|
||||
use prec, only: pReal,pInt,p_vec
|
||||
use mesh, only: mesh_element,mesh_NcpElems,mesh_maxNips
|
||||
use material, only: homogenization_maxNgrains, homogenization_Ngrains
|
||||
implicit none
|
||||
|
||||
!* Definition of variables
|
||||
real(pReal), dimension (3,3), intent(out) :: avgP
|
||||
real(pReal), dimension (3,3,3,3), intent(out) :: dAvgPdAvgF
|
||||
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(in) :: P
|
||||
real(pReal), dimension (3,3,3,3,homogenization_maxNgrains), intent(in) :: dPdF
|
||||
integer(pInt), intent(in) :: ip,el
|
||||
logical homogenization_isostrain_stateUpdate
|
||||
integer(pInt) homID, i, Ngrains
|
||||
|
||||
! homID = homogenization_typeInstance(mesh_element(3,el))
|
||||
Ngrains = homogenization_Ngrains(mesh_element(3,el))
|
||||
avgP = sum(P,3)/dble(Ngrains)
|
||||
dAvgPdAvgF = sum(dPdF,5)/dble(Ngrains)
|
||||
|
||||
return
|
||||
|
||||
endsubroutine
|
||||
|
||||
|
||||
!********************************************************************
|
||||
! derive average stress and stiffness from constituent quantities
|
||||
!********************************************************************
|
||||
function homogenization_isostrain_averageTemperature(&
|
||||
Temperature, & ! temperature
|
||||
ip, & ! my integration point
|
||||
el & ! my element
|
||||
)
|
||||
|
||||
use prec, only: pReal,pInt,p_vec
|
||||
use mesh, only: mesh_element,mesh_NcpElems,mesh_maxNips
|
||||
use material, only: homogenization_maxNgrains, homogenization_Ngrains
|
||||
implicit none
|
||||
|
||||
!* Definition of variables
|
||||
real(pReal), dimension (homogenization_maxNgrains), intent(in) :: Temperature
|
||||
integer(pInt), intent(in) :: ip,el
|
||||
real(pReal) homogenization_isostrain_averageTemperature
|
||||
integer(pInt) homID, i, Ngrains
|
||||
|
||||
! homID = homogenization_typeInstance(mesh_element(3,el))
|
||||
Ngrains = homogenization_Ngrains(mesh_element(3,el))
|
||||
homogenization_isostrain_averageTemperature = sum(Temperature(1:Ngrains))/dble(Ngrains)
|
||||
|
||||
return
|
||||
|
||||
endfunction
|
||||
|
||||
|
||||
!********************************************************************
|
||||
! return array of homogenization results for post file inclusion
|
||||
!********************************************************************
|
||||
pure function homogenization_isostrain_postResults(&
|
||||
state, & ! my state
|
||||
ip, & ! my integration point
|
||||
el & ! my element
|
||||
)
|
||||
|
||||
use prec, only: pReal,pInt,p_vec
|
||||
use mesh, only: mesh_element
|
||||
use material, only: homogenization_typeInstance,homogenization_Noutput
|
||||
implicit none
|
||||
|
||||
!* Definition of variables
|
||||
type(p_vec), intent(in) :: state
|
||||
integer(pInt), intent(in) :: ip,el
|
||||
integer(pInt) homID,o,c
|
||||
real(pReal), dimension(homogenization_isostrain_sizePostResults(homogenization_typeInstance(mesh_element(3,el)))) :: &
|
||||
homogenization_isostrain_postResults
|
||||
|
||||
homID = homogenization_typeInstance(mesh_element(3,el))
|
||||
c = 0_pInt
|
||||
homogenization_isostrain_postResults = 0.0_pReal
|
||||
|
||||
do o = 1,homogenization_Noutput(mesh_element(3,el))
|
||||
select case(homogenization_isostrain_output(o,homID))
|
||||
case ('ngrains')
|
||||
homogenization_isostrain_postResults(c+1) = homogenization_isostrain_Ngrains(homID)
|
||||
c = c + 1
|
||||
end select
|
||||
enddo
|
||||
|
||||
return
|
||||
|
||||
endfunction
|
||||
|
||||
END MODULE
|
||||
!* $Id$
|
||||
!*****************************************************
|
||||
!* Module: HOMOGENIZATION_ISOSTRAIN *
|
||||
!*****************************************************
|
||||
!* contains: *
|
||||
!*****************************************************
|
||||
|
||||
! [isostrain]
|
||||
! type isostrain
|
||||
! Ngrains 6
|
||||
! (output) Ngrains
|
||||
|
||||
MODULE homogenization_isostrain
|
||||
|
||||
!*** Include other modules ***
|
||||
use prec, only: pReal,pInt
|
||||
implicit none
|
||||
|
||||
character (len=*), parameter :: homogenization_isostrain_label = 'isostrain'
|
||||
|
||||
integer(pInt), dimension(:), allocatable :: homogenization_isostrain_sizeState, &
|
||||
homogenization_isostrain_Ngrains
|
||||
integer(pInt), dimension(:), allocatable :: homogenization_isostrain_sizePostResults
|
||||
integer(pInt), dimension(:,:), allocatable,target :: homogenization_isostrain_sizePostResult
|
||||
character(len=64), dimension(:,:), allocatable,target :: homogenization_isostrain_output ! name of each post result output
|
||||
|
||||
|
||||
CONTAINS
|
||||
!****************************************
|
||||
!* - homogenization_isostrain_init
|
||||
!* - homogenization_isostrain_stateInit
|
||||
!* - homogenization_isostrain_deformationPartititon
|
||||
!* - homogenization_isostrain_stateUpdate
|
||||
!* - homogenization_isostrain_averageStressAndItsTangent
|
||||
!* - homogenization_isostrain_postResults
|
||||
!****************************************
|
||||
|
||||
|
||||
!**************************************
|
||||
!* Module initialization *
|
||||
!**************************************
|
||||
subroutine homogenization_isostrain_init(&
|
||||
file & ! file pointer to material configuration
|
||||
)
|
||||
|
||||
use prec, only: pInt, pReal
|
||||
use math, only: math_Mandel3333to66, math_Voigt66to3333
|
||||
use IO
|
||||
use material
|
||||
integer(pInt), intent(in) :: file
|
||||
integer(pInt), parameter :: maxNchunks = 2
|
||||
integer(pInt), dimension(1+2*maxNchunks) :: positions
|
||||
integer(pInt) section, maxNinstance, i,j,k,l, output, mySize
|
||||
character(len=64) tag
|
||||
character(len=1024) line
|
||||
|
||||
write(6,*)
|
||||
write(6,'(a20,a20,a12)') '<<<+- homogenization',homogenization_isostrain_label,' init -+>>>'
|
||||
write(6,*) '$Id$'
|
||||
write(6,*)
|
||||
|
||||
maxNinstance = count(homogenization_type == homogenization_isostrain_label)
|
||||
if (maxNinstance == 0) return
|
||||
|
||||
allocate(homogenization_isostrain_sizeState(maxNinstance)) ; homogenization_isostrain_sizeState = 0_pInt
|
||||
allocate(homogenization_isostrain_sizePostResults(maxNinstance)); homogenization_isostrain_sizePostResults = 0_pInt
|
||||
allocate(homogenization_isostrain_sizePostResult(maxval(homogenization_Noutput), &
|
||||
maxNinstance)); homogenization_isostrain_sizePostResult = 0_pInt
|
||||
allocate(homogenization_isostrain_Ngrains(maxNinstance)); homogenization_isostrain_Ngrains = 0_pInt
|
||||
allocate(homogenization_isostrain_output(maxval(homogenization_Noutput), &
|
||||
maxNinstance)) ; homogenization_isostrain_output = ''
|
||||
|
||||
rewind(file)
|
||||
line = ''
|
||||
section = 0
|
||||
|
||||
do while (IO_lc(IO_getTag(line,'<','>')) /= material_partHomogenization) ! wind forward to <homogenization>
|
||||
read(file,'(a1024)',END=100) line
|
||||
enddo
|
||||
|
||||
do ! read thru sections of phase part
|
||||
read(file,'(a1024)',END=100) line
|
||||
if (IO_isBlank(line)) cycle ! skip empty lines
|
||||
if (IO_getTag(line,'<','>') /= '') exit ! stop at next part
|
||||
if (IO_getTag(line,'[',']') /= '') then ! next section
|
||||
section = section + 1
|
||||
output = 0 ! reset output counter
|
||||
endif
|
||||
if (section > 0 .and. homogenization_type(section) == homogenization_isostrain_label) then ! one of my sections
|
||||
i = homogenization_typeInstance(section) ! which instance of my type is present homogenization
|
||||
positions = IO_stringPos(line,maxNchunks)
|
||||
tag = IO_lc(IO_stringValue(line,positions,1)) ! extract key
|
||||
select case(tag)
|
||||
case ('(output)')
|
||||
output = output + 1
|
||||
homogenization_isostrain_output(output,i) = IO_lc(IO_stringValue(line,positions,2))
|
||||
case ('ngrains')
|
||||
homogenization_isostrain_Ngrains(i) = IO_intValue(line,positions,2)
|
||||
end select
|
||||
endif
|
||||
enddo
|
||||
|
||||
100 do i = 1,maxNinstance ! sanity checks
|
||||
enddo
|
||||
|
||||
do i = 1,maxNinstance
|
||||
homogenization_isostrain_sizeState(i) = 0_pInt
|
||||
|
||||
do j = 1,maxval(homogenization_Noutput)
|
||||
select case(homogenization_isostrain_output(j,i))
|
||||
case('ngrains')
|
||||
mySize = 1
|
||||
case default
|
||||
mySize = 0
|
||||
end select
|
||||
|
||||
if (mySize > 0_pInt) then ! any meaningful output found
|
||||
homogenization_isostrain_sizePostResult(j,i) = mySize
|
||||
homogenization_isostrain_sizePostResults(i) = &
|
||||
homogenization_isostrain_sizePostResults(i) + mySize
|
||||
endif
|
||||
enddo
|
||||
enddo
|
||||
|
||||
return
|
||||
|
||||
endsubroutine
|
||||
|
||||
|
||||
!*********************************************************************
|
||||
!* initial homogenization state *
|
||||
!*********************************************************************
|
||||
function homogenization_isostrain_stateInit(myInstance)
|
||||
use prec, only: pReal,pInt
|
||||
implicit none
|
||||
|
||||
!* Definition of variables
|
||||
integer(pInt), intent(in) :: myInstance
|
||||
real(pReal), dimension(homogenization_isostrain_sizeState(myInstance)) :: &
|
||||
homogenization_isostrain_stateInit ! modified <<<updated 31.07.2009>>>
|
||||
|
||||
homogenization_isostrain_stateInit = 0.0_pReal
|
||||
|
||||
return
|
||||
|
||||
endfunction
|
||||
|
||||
|
||||
!********************************************************************
|
||||
! partition material point def grad onto constituents
|
||||
!********************************************************************
|
||||
subroutine homogenization_isostrain_partitionDeformation(&
|
||||
F, & ! partioned def grad per grain
|
||||
!
|
||||
F0, & ! initial partioned def grad per grain
|
||||
avgF, & ! my average def grad
|
||||
state, & ! my state
|
||||
ip, & ! my integration point
|
||||
el & ! my element
|
||||
)
|
||||
use prec, only: pReal,pInt,p_vec
|
||||
use mesh, only: mesh_element,mesh_NcpElems,mesh_maxNips
|
||||
use material, only: homogenization_maxNgrains,homogenization_Ngrains
|
||||
implicit none
|
||||
|
||||
!* Definition of variables
|
||||
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(out) :: F
|
||||
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(in) :: F0
|
||||
real(pReal), dimension (3,3), intent(in) :: avgF
|
||||
type(p_vec), intent(in) :: state
|
||||
integer(pInt), intent(in) :: ip,el
|
||||
integer(pInt) homID, i
|
||||
|
||||
! homID = homogenization_typeInstance(mesh_element(3,el))
|
||||
forall (i = 1:homogenization_Ngrains(mesh_element(3,el))) &
|
||||
F(:,:,i) = avgF
|
||||
|
||||
return
|
||||
|
||||
endsubroutine
|
||||
|
||||
|
||||
!********************************************************************
|
||||
! update the internal state of the homogenization scheme
|
||||
! and tell whether "done" and "happy" with result
|
||||
!********************************************************************
|
||||
function homogenization_isostrain_updateState(&
|
||||
state, & ! my state
|
||||
!
|
||||
P, & ! array of current grain stresses
|
||||
dPdF, & ! array of current grain stiffnesses
|
||||
ip, & ! my integration point
|
||||
el & ! my element
|
||||
)
|
||||
|
||||
use prec, only: pReal,pInt,p_vec
|
||||
use mesh, only: mesh_element,mesh_NcpElems,mesh_maxNips
|
||||
use material, only: homogenization_maxNgrains
|
||||
implicit none
|
||||
|
||||
!* Definition of variables
|
||||
type(p_vec), intent(inout) :: state
|
||||
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(in) :: P
|
||||
real(pReal), dimension (3,3,3,3,homogenization_maxNgrains), intent(in) :: dPdF
|
||||
integer(pInt), intent(in) :: ip,el
|
||||
! integer(pInt) homID
|
||||
logical, dimension(2) :: homogenization_isostrain_updateState
|
||||
|
||||
! homID = homogenization_typeInstance(mesh_element(3,el))
|
||||
homogenization_isostrain_updateState = .true. ! homogenization at material point converged (done and happy)
|
||||
|
||||
return
|
||||
|
||||
endfunction
|
||||
|
||||
|
||||
!********************************************************************
|
||||
! derive average stress and stiffness from constituent quantities
|
||||
!********************************************************************
|
||||
subroutine homogenization_isostrain_averageStressAndItsTangent(&
|
||||
avgP, & ! average stress at material point
|
||||
dAvgPdAvgF, & ! average stiffness at material point
|
||||
!
|
||||
P, & ! array of current grain stresses
|
||||
dPdF, & ! array of current grain stiffnesses
|
||||
ip, & ! my integration point
|
||||
el & ! my element
|
||||
)
|
||||
|
||||
use prec, only: pReal,pInt,p_vec
|
||||
use mesh, only: mesh_element,mesh_NcpElems,mesh_maxNips
|
||||
use material, only: homogenization_maxNgrains, homogenization_Ngrains
|
||||
implicit none
|
||||
|
||||
!* Definition of variables
|
||||
real(pReal), dimension (3,3), intent(out) :: avgP
|
||||
real(pReal), dimension (3,3,3,3), intent(out) :: dAvgPdAvgF
|
||||
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(in) :: P
|
||||
real(pReal), dimension (3,3,3,3,homogenization_maxNgrains), intent(in) :: dPdF
|
||||
integer(pInt), intent(in) :: ip,el
|
||||
logical homogenization_isostrain_stateUpdate
|
||||
integer(pInt) homID, i, Ngrains
|
||||
|
||||
! homID = homogenization_typeInstance(mesh_element(3,el))
|
||||
Ngrains = homogenization_Ngrains(mesh_element(3,el))
|
||||
avgP = sum(P,3)/dble(Ngrains)
|
||||
dAvgPdAvgF = sum(dPdF,5)/dble(Ngrains)
|
||||
|
||||
return
|
||||
|
||||
endsubroutine
|
||||
|
||||
|
||||
!********************************************************************
|
||||
! derive average stress and stiffness from constituent quantities
|
||||
!********************************************************************
|
||||
function homogenization_isostrain_averageTemperature(&
|
||||
Temperature, & ! temperature
|
||||
ip, & ! my integration point
|
||||
el & ! my element
|
||||
)
|
||||
|
||||
use prec, only: pReal,pInt,p_vec
|
||||
use mesh, only: mesh_element,mesh_NcpElems,mesh_maxNips
|
||||
use material, only: homogenization_maxNgrains, homogenization_Ngrains
|
||||
implicit none
|
||||
|
||||
!* Definition of variables
|
||||
real(pReal), dimension (homogenization_maxNgrains), intent(in) :: Temperature
|
||||
integer(pInt), intent(in) :: ip,el
|
||||
real(pReal) homogenization_isostrain_averageTemperature
|
||||
integer(pInt) homID, i, Ngrains
|
||||
|
||||
! homID = homogenization_typeInstance(mesh_element(3,el))
|
||||
Ngrains = homogenization_Ngrains(mesh_element(3,el))
|
||||
homogenization_isostrain_averageTemperature = sum(Temperature(1:Ngrains))/dble(Ngrains)
|
||||
|
||||
return
|
||||
|
||||
endfunction
|
||||
|
||||
|
||||
!********************************************************************
|
||||
! return array of homogenization results for post file inclusion
|
||||
!********************************************************************
|
||||
pure function homogenization_isostrain_postResults(&
|
||||
state, & ! my state
|
||||
ip, & ! my integration point
|
||||
el & ! my element
|
||||
)
|
||||
|
||||
use prec, only: pReal,pInt,p_vec
|
||||
use mesh, only: mesh_element
|
||||
use material, only: homogenization_typeInstance,homogenization_Noutput
|
||||
implicit none
|
||||
|
||||
!* Definition of variables
|
||||
type(p_vec), intent(in) :: state
|
||||
integer(pInt), intent(in) :: ip,el
|
||||
integer(pInt) homID,o,c
|
||||
real(pReal), dimension(homogenization_isostrain_sizePostResults(homogenization_typeInstance(mesh_element(3,el)))) :: &
|
||||
homogenization_isostrain_postResults
|
||||
|
||||
homID = homogenization_typeInstance(mesh_element(3,el))
|
||||
c = 0_pInt
|
||||
homogenization_isostrain_postResults = 0.0_pReal
|
||||
|
||||
do o = 1,homogenization_Noutput(mesh_element(3,el))
|
||||
select case(homogenization_isostrain_output(o,homID))
|
||||
case ('ngrains')
|
||||
homogenization_isostrain_postResults(c+1) = homogenization_isostrain_Ngrains(homID)
|
||||
c = c + 1
|
||||
end select
|
||||
enddo
|
||||
|
||||
return
|
||||
|
||||
endfunction
|
||||
|
||||
END MODULE
|
||||
|
|
|
@ -1,8 +1,17 @@
|
|||
#####################
|
||||
# $Id$
|
||||
#####################
|
||||
|
||||
#-------------------#
|
||||
<global>
|
||||
#-------------------#
|
||||
|
||||
[crystallite]
|
||||
results 14
|
||||
|
||||
#-------------------#
|
||||
<homogenization>
|
||||
#####################
|
||||
#-------------------#
|
||||
|
||||
[SX]
|
||||
type isostrain
|
||||
|
@ -23,28 +32,42 @@ overproportionality 1.0e+1 1.0e+1 1.0e+1 # typical range between 0.1 (very lar
|
|||
type isostrain
|
||||
Ngrains 2
|
||||
|
||||
#####################
|
||||
#-------------------#
|
||||
<microstructure>
|
||||
#####################
|
||||
#-------------------#
|
||||
|
||||
[Aluminum_Poly]
|
||||
/elementhomogeneous/ # put this flag to set ips identical in one element (something like reduced integration)
|
||||
crystallite 1
|
||||
(constituent) phase 3 texture 1 fraction 1.0
|
||||
|
||||
[Aluminum_001]
|
||||
crystallite 1
|
||||
(constituent) phase 3 texture 2 fraction 1.0
|
||||
|
||||
[Aluminum_j2]
|
||||
crystallite 1
|
||||
(constituent) phase 1 texture 1 fraction 1.0
|
||||
|
||||
[DP_Steel]
|
||||
/elementhomogeneous/
|
||||
(constituent) phase 1 texture 1 fraction 0.82
|
||||
crystallite 1
|
||||
(constituent) phase 1 texture 1 fraction 0.82
|
||||
(constituent) phase 2 texture 1 fraction 0.18
|
||||
|
||||
#####################
|
||||
#-------------------#
|
||||
<crystallite>
|
||||
#-------------------#
|
||||
|
||||
[all]
|
||||
(output) phase
|
||||
(output) volume
|
||||
(output) orientation
|
||||
(output) defgrad
|
||||
|
||||
#-------------------#
|
||||
<phase>
|
||||
#####################
|
||||
#-------------------#
|
||||
|
||||
[Aluminum_J2isotropic]
|
||||
|
||||
|
@ -320,9 +343,9 @@ Cthresholdtwin 1.0 # Adj. parameter controlling slip threshold stress
|
|||
interactionSlipTwin 0.0 1.0 # Dislocation interaction coefficients
|
||||
interactionTwinTwin 0.0 1.0 # Dislocation interaction coefficients
|
||||
|
||||
#####################
|
||||
#-------------------#
|
||||
<texture>
|
||||
#####################
|
||||
#-------------------#
|
||||
|
||||
[Rolling]
|
||||
hybridIA DP_EBSD.linearODF
|
||||
|
|
|
@ -15,6 +15,7 @@ implicit none
|
|||
character(len=64), parameter :: material_configFile = 'material.config'
|
||||
character(len=32), parameter :: material_partHomogenization = 'homogenization'
|
||||
character(len=32), parameter :: material_partMicrostructure = 'microstructure'
|
||||
character(len=32), parameter :: material_partCrystallite = 'crystallite'
|
||||
character(len=32), parameter :: material_partPhase = 'phase'
|
||||
character(len=32), parameter :: material_partTexture = 'texture'
|
||||
|
||||
|
@ -25,6 +26,7 @@ character(len=32), parameter :: material_partTexture = 'texture'
|
|||
!* Number of materials
|
||||
integer(pInt) material_Nhomogenization, & ! number of homogenizations
|
||||
material_Nmicrostructure, & ! number of microstructures
|
||||
material_Ncrystallite, & ! number of crystallite settings
|
||||
material_Nphase, & ! number of phases
|
||||
material_Ntexture, & ! number of textures
|
||||
microstructure_maxNconstituents, & ! max number of constituents in any phase
|
||||
|
@ -34,6 +36,7 @@ integer(pInt) material_Nhomogenization, &
|
|||
character(len=64), dimension(:), allocatable :: homogenization_name, & ! name of each homogenization
|
||||
homogenization_type, & ! type of each homogenization
|
||||
microstructure_name, & ! name of each microstructure
|
||||
crystallite_name, & ! name of each crystallite setting
|
||||
phase_name, & ! name of each phase
|
||||
phase_constitution, & ! constitution of each phase
|
||||
texture_name ! name of each texture
|
||||
|
@ -42,6 +45,7 @@ integer(pInt), dimension(:), allocatable :: homogenization_Ngrains, &
|
|||
homogenization_typeInstance, & ! instance of particular type of each homogenization
|
||||
homogenization_Noutput, & ! number of '(output)' items per homogenization
|
||||
microstructure_Nconstituents, & ! number of constituents in each microstructure
|
||||
crystallite_Noutput, & ! number of '(output)' items per crystallite setting
|
||||
phase_constitutionInstance, & ! instance of particular constitution of each phase
|
||||
phase_Noutput, & ! number of '(output)' items per phase
|
||||
texture_symmetry, & ! number of symmetric orientations per texture
|
||||
|
@ -51,6 +55,7 @@ logical, dimension(:), allocatable :: homogenization_active, &
|
|||
microstructure_active, & !
|
||||
microstructure_elemhomo, & ! flag to indicate homogeneous microstructure distribution over element's IPs
|
||||
phase_localConstitution ! flags phases with local constitutive law
|
||||
integer(pInt), dimension(:), allocatable :: microstructure_crystallite ! crystallite setting ID of each microstructure
|
||||
integer(pInt), dimension(:,:), allocatable :: microstructure_phase, & ! phase IDs of each microstructure
|
||||
microstructure_texture ! texture IDs of each microstructure
|
||||
real(pReal), dimension(:,:), allocatable :: microstructure_fraction ! vol fraction of each constituent in microstructure
|
||||
|
@ -84,13 +89,20 @@ subroutine material_init()
|
|||
if(.not. IO_open_file(fileunit,material_configFile)) call IO_error(100) ! cannot open config file
|
||||
call material_parseHomogenization(fileunit,material_partHomogenization)
|
||||
call material_parseMicrostructure(fileunit,material_partMicrostructure)
|
||||
call material_parseCrystallite(fileunit,material_partCrystallite)
|
||||
call material_parseTexture(fileunit,material_partTexture)
|
||||
call material_parsePhase(fileunit,material_partPhase)
|
||||
close(fileunit)
|
||||
write(6,*) '<<<+- done -+>>>'; call flush(6)
|
||||
|
||||
write(6,*) 'material_Nmicrostructure',material_Nmicrostructure
|
||||
write(6,*) 'microstructure_crystallite',microstructure_crystallite
|
||||
write(6,*) 'material_Ncrystallite',material_Ncrystallite
|
||||
do i = 1,material_Nmicrostructure
|
||||
if (microstructure_crystallite(i) < 1 .or. &
|
||||
microstructure_crystallite(i) > material_Ncrystallite) call IO_error(150,i)
|
||||
if (minval(microstructure_phase(1:microstructure_Nconstituents(i),i)) < 1 .or. &
|
||||
maxval(microstructure_phase(1:microstructure_Nconstituents(i),i)) > material_Nphase) call IO_error(150,i)
|
||||
maxval(microstructure_phase(1:microstructure_Nconstituents(i),i)) > material_Nphase) call IO_error(155,i)
|
||||
if (minval(microstructure_texture(1:microstructure_Nconstituents(i),i)) < 1 .or. &
|
||||
maxval(microstructure_texture(1:microstructure_Nconstituents(i),i)) > material_Ntexture) call IO_error(160,i)
|
||||
if (abs(sum(microstructure_fraction(:,i)) - 1.0_pReal) >= 1.0e-10_pReal) then
|
||||
|
@ -106,9 +118,12 @@ subroutine material_init()
|
|||
write (6,'(x,a32,x,a16,x,i4)') homogenization_name(i),homogenization_type(i),homogenization_Ngrains(i)
|
||||
enddo
|
||||
write (6,*)
|
||||
write (6,'(a32,x,a12,x,a13)') 'microstructure ','constituents','homogeneous'
|
||||
write (6,'(a32,x,a11,x,a12,x,a13)') 'microstructure ','crystallite','constituents','homogeneous'
|
||||
do i = 1,material_Nmicrostructure
|
||||
write (6,'(a32,4x,i4,8x,l)') microstructure_name(i),microstructure_Nconstituents(i),microstructure_elemhomo(i)
|
||||
write (6,'(a32,4x,i4,8x,i4,8x,l)') microstructure_name(i), &
|
||||
microstructure_crystallite(i), &
|
||||
microstructure_Nconstituents(i), &
|
||||
microstructure_elemhomo(i)
|
||||
if (microstructure_Nconstituents(i) > 0_pInt) then
|
||||
do j = 1,microstructure_Nconstituents(i)
|
||||
write (6,'(a1,x,a32,x,a32,x,f6.4)') '>',phase_name(microstructure_phase(j,i)),&
|
||||
|
@ -143,6 +158,7 @@ subroutine material_parseHomogenization(file,myPart)
|
|||
|
||||
Nsections = IO_countSections(file,myPart)
|
||||
material_Nhomogenization = Nsections
|
||||
if (Nsections < 1_pInt) call IO_error(125,ext_msg=myPart)
|
||||
|
||||
allocate(homogenization_name(Nsections)); homogenization_name = ''
|
||||
allocate(homogenization_type(Nsections)); homogenization_type = ''
|
||||
|
@ -211,7 +227,10 @@ subroutine material_parseMicrostructure(file,myPart)
|
|||
|
||||
Nsections = IO_countSections(file,myPart)
|
||||
material_Nmicrostructure = Nsections
|
||||
allocate(microstructure_name(Nsections)); microstructure_name = ''
|
||||
if (Nsections < 1_pInt) call IO_error(125,ext_msg=myPart)
|
||||
|
||||
allocate(microstructure_name(Nsections)); microstructure_name = ''
|
||||
allocate(microstructure_crystallite(Nsections)); microstructure_crystallite = 0_pInt
|
||||
allocate(microstructure_Nconstituents(Nsections))
|
||||
allocate(microstructure_active(Nsections))
|
||||
allocate(microstructure_elemhomo(Nsections))
|
||||
|
@ -247,6 +266,8 @@ subroutine material_parseMicrostructure(file,myPart)
|
|||
positions = IO_stringPos(line,maxNchunks)
|
||||
tag = IO_lc(IO_stringValue(line,positions,1)) ! extract key
|
||||
select case(tag)
|
||||
case ('crystallite')
|
||||
microstructure_crystallite(section) = IO_intValue(line,positions,2)
|
||||
case ('(constituent)')
|
||||
constituent = constituent + 1
|
||||
do i=2,6,2
|
||||
|
@ -269,6 +290,53 @@ subroutine material_parseMicrostructure(file,myPart)
|
|||
endsubroutine
|
||||
|
||||
|
||||
!*********************************************************************
|
||||
subroutine material_parseCrystallite(file,myPart)
|
||||
!*********************************************************************
|
||||
|
||||
use prec, only: pInt
|
||||
use IO
|
||||
use mesh, only: mesh_element
|
||||
implicit none
|
||||
|
||||
character(len=*), intent(in) :: myPart
|
||||
integer(pInt), intent(in) :: file
|
||||
integer(pInt) Nsections, section
|
||||
character(len=64) tag
|
||||
character(len=1024) line
|
||||
|
||||
Nsections = IO_countSections(file,myPart)
|
||||
material_Ncrystallite = Nsections
|
||||
if (Nsections < 1_pInt) call IO_error(125,ext_msg=myPart)
|
||||
|
||||
allocate(crystallite_name(Nsections)); crystallite_name = ''
|
||||
allocate(crystallite_Noutput(Nsections)); crystallite_Noutput = 0_pInt
|
||||
|
||||
crystallite_Noutput = IO_countTagInPart(file,myPart,'(output)',Nsections)
|
||||
|
||||
rewind(file)
|
||||
line = ''
|
||||
section = 0
|
||||
|
||||
do while (IO_lc(IO_getTag(line,'<','>')) /= myPart) ! wind forward to myPart
|
||||
read(file,'(a1024)',END=100) line
|
||||
enddo
|
||||
|
||||
do
|
||||
read(file,'(a1024)',END=100) line
|
||||
if (IO_isBlank(line)) cycle ! skip empty lines
|
||||
if (IO_getTag(line,'<','>') /= '') exit ! stop at next part
|
||||
if (IO_getTag(line,'[',']') /= '') then ! next section
|
||||
section = section + 1
|
||||
crystallite_name(section) = IO_getTag(line,'[',']')
|
||||
endif
|
||||
enddo
|
||||
|
||||
100 return
|
||||
|
||||
endsubroutine
|
||||
|
||||
|
||||
!*********************************************************************
|
||||
subroutine material_parsePhase(file,myPart)
|
||||
!*********************************************************************
|
||||
|
@ -287,6 +355,8 @@ subroutine material_parsePhase(file,myPart)
|
|||
|
||||
Nsections = IO_countSections(file,myPart)
|
||||
material_Nphase = Nsections
|
||||
if (Nsections < 1_pInt) call IO_error(125,ext_msg=myPart)
|
||||
|
||||
allocate(phase_name(Nsections)); phase_name = ''
|
||||
allocate(phase_constitution(Nsections)); phase_constitution = ''
|
||||
allocate(phase_constitutionInstance(Nsections)); phase_constitutionInstance = 0_pInt
|
||||
|
@ -351,6 +421,8 @@ subroutine material_parseTexture(file,myPart)
|
|||
|
||||
Nsections = IO_countSections(file,myPart)
|
||||
material_Ntexture = Nsections
|
||||
if (Nsections < 1_pInt) call IO_error(125,ext_msg=myPart)
|
||||
|
||||
allocate(texture_name(Nsections)); texture_name = ''
|
||||
allocate(texture_ODFfile(Nsections)); texture_ODFfile = ''
|
||||
allocate(texture_symmetry(Nsections)); texture_symmetry = 1_pInt
|
||||
|
|
|
@ -1,4 +1,4 @@
|
|||
!* $Id: mpie_cpfem_abaqus.f 431 2009-10-13 06:55:15Z MPIE\f.roters $
|
||||
!* $Id$
|
||||
!********************************************************************
|
||||
! Material subroutine for Abaqus
|
||||
!
|
||||
|
@ -25,7 +25,7 @@ subroutine mpie_cpfem_init ()
|
|||
!$OMP CRITICAL (write2out)
|
||||
write(6,*)
|
||||
write(6,*) '<<<+- mpie_cpfem_abaqus_exp init -+>>>'
|
||||
write(6,*) '$Id: mpie_cpfem_abaqus.f 431 2009-10-13 06:55:15Z MPIE\f.roters $'
|
||||
write(6,*) '$Id$'
|
||||
write(6,*)
|
||||
call flush(6)
|
||||
!$OMP END CRITICAL (write2out)
|
||||
|
|
|
@ -43,7 +43,7 @@ real(pReal) relevantStrain, & ! strain
|
|||
volDiscrPow_RGC ! powerlaw penalty for volume discrepancy
|
||||
|
||||
!* Random seeding parameters: added <<<updated 27.08.2009>>>
|
||||
integer(pInt) fixedSeed ! fixed seeding for pseudo-random number generator
|
||||
integer(pInt) fixedSeed ! fixed seeding for pseudo-random number generator
|
||||
|
||||
CONTAINS
|
||||
|
||||
|
|
|
@ -1,8 +1,8 @@
|
|||
$Id$
|
||||
Things to be implemented into the code
|
||||
|
||||
# make OpenMP parallelization work again
|
||||
# define set of test problems with known solution
|
||||
$Id$
|
||||
Things to be implemented into the code
|
||||
|
||||
# make OpenMP parallelization work again
|
||||
# define set of test problems with known solution
|
||||
|
||||
# check out
|
||||
@phdthesis{Bal98,
|
||||
|
|
Loading…
Reference in New Issue