2013-01-28 22:06:26 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! $Id$
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
|
|
|
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
|
|
|
!> @brief Isostrain (full constraint Taylor assuption) homogenization scheme
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2012-03-09 01:55:28 +05:30
|
|
|
module homogenization_isostrain
|
2013-01-28 22:06:26 +05:30
|
|
|
use prec, only: &
|
|
|
|
pInt
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2010-02-25 23:09:11 +05:30
|
|
|
implicit none
|
2013-01-28 22:06:26 +05:30
|
|
|
private
|
2013-12-12 22:39:59 +05:30
|
|
|
integer(pInt), dimension(:), allocatable, public, protected :: &
|
2012-03-09 01:55:28 +05:30
|
|
|
homogenization_isostrain_sizePostResults
|
2013-12-12 22:39:59 +05:30
|
|
|
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
2012-03-09 01:55:28 +05:30
|
|
|
homogenization_isostrain_sizePostResult
|
2013-11-27 13:34:05 +05:30
|
|
|
|
2013-12-12 22:39:59 +05:30
|
|
|
character(len=64), dimension(:,:), allocatable, target, public :: &
|
2013-01-28 22:06:26 +05:30
|
|
|
homogenization_isostrain_output !< name of each post result output
|
2013-12-12 22:39:59 +05:30
|
|
|
integer(pInt), dimension(:), allocatable, private :: &
|
2013-01-28 22:06:26 +05:30
|
|
|
homogenization_isostrain_Ngrains
|
2013-11-27 17:09:28 +05:30
|
|
|
enum, bind(c)
|
2013-12-12 22:39:59 +05:30
|
|
|
enumerator :: undefined_ID, &
|
|
|
|
nconstituents_ID, &
|
|
|
|
temperature_ID, &
|
|
|
|
ipcoords_ID, &
|
|
|
|
avgdefgrad_ID, &
|
|
|
|
avgfirstpiola_ID
|
2013-11-27 17:09:28 +05:30
|
|
|
end enum
|
2013-12-12 22:39:59 +05:30
|
|
|
enum, bind(c)
|
|
|
|
enumerator :: parallel_ID, &
|
|
|
|
average_ID
|
|
|
|
end enum
|
|
|
|
integer(kind(undefined_ID)), dimension(:,:), allocatable, private :: &
|
2013-11-27 17:09:28 +05:30
|
|
|
homogenization_isostrain_outputID !< ID of each post result output
|
2013-12-12 22:39:59 +05:30
|
|
|
integer(kind(average_ID)), dimension(:), allocatable, private :: &
|
2013-12-18 12:58:01 +05:30
|
|
|
homogenization_isostrain_mapping !< mapping type
|
2013-11-27 17:09:28 +05:30
|
|
|
|
2013-01-28 22:06:26 +05:30
|
|
|
|
|
|
|
public :: &
|
|
|
|
homogenization_isostrain_init, &
|
|
|
|
homogenization_isostrain_partitionDeformation, &
|
|
|
|
homogenization_isostrain_averageStressAndItsTangent, &
|
|
|
|
homogenization_isostrain_postResults
|
2010-02-25 23:09:11 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
contains
|
2013-01-28 22:06:26 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief allocates all neccessary fields, reads information from material configuration file
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2013-12-12 22:39:59 +05:30
|
|
|
subroutine homogenization_isostrain_init(fileUnit)
|
2013-01-28 22:06:26 +05:30
|
|
|
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
2010-02-25 23:09:11 +05:30
|
|
|
use IO
|
|
|
|
use material
|
2013-10-11 21:31:53 +05:30
|
|
|
|
|
|
|
implicit none
|
2013-12-12 22:39:59 +05:30
|
|
|
integer(pInt), intent(in) :: fileUnit
|
2013-10-11 21:31:53 +05:30
|
|
|
integer(pInt), parameter :: MAXNCHUNKS = 2_pInt
|
|
|
|
integer(pInt), dimension(1_pInt+2_pInt*MAXNCHUNKS) :: positions
|
|
|
|
integer(pInt) :: &
|
2013-12-12 22:39:59 +05:30
|
|
|
section = 0_pInt, i, j, output, mySize
|
2013-10-11 21:31:53 +05:30
|
|
|
integer :: &
|
|
|
|
maxNinstance, k ! no pInt (stores a system dependen value from 'count'
|
2013-07-01 12:10:09 +05:30
|
|
|
character(len=65536) :: &
|
|
|
|
tag = '', &
|
2013-12-12 22:39:59 +05:30
|
|
|
line = ''
|
2010-02-25 23:09:11 +05:30
|
|
|
|
2013-10-09 11:42:16 +05:30
|
|
|
write(6,'(/,a)') ' <<<+- homogenization_'//HOMOGENIZATION_ISOSTRAIN_label//' init -+>>>'
|
2013-07-01 12:10:09 +05:30
|
|
|
write(6,'(a)') ' $Id$'
|
|
|
|
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
2012-02-01 00:48:55 +05:30
|
|
|
#include "compilation_info.f90"
|
2013-01-09 03:41:59 +05:30
|
|
|
|
2013-11-27 13:34:05 +05:30
|
|
|
maxNinstance = count(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID)
|
2012-02-21 22:01:37 +05:30
|
|
|
if (maxNinstance == 0) return
|
2010-02-25 23:09:11 +05:30
|
|
|
|
2013-12-12 22:39:59 +05:30
|
|
|
allocate(homogenization_isostrain_sizePostResults(maxNinstance), source=0_pInt)
|
|
|
|
allocate(homogenization_isostrain_sizePostResult(maxval(homogenization_Noutput),maxNinstance), &
|
|
|
|
source=0_pInt)
|
|
|
|
allocate(homogenization_isostrain_Ngrains(maxNinstance), source=0_pInt)
|
|
|
|
allocate(homogenization_isostrain_mapping(maxNinstance), source=average_ID)
|
2013-10-11 21:31:53 +05:30
|
|
|
allocate(homogenization_isostrain_output(maxval(homogenization_Noutput),maxNinstance))
|
|
|
|
homogenization_isostrain_output = ''
|
2013-12-12 22:39:59 +05:30
|
|
|
allocate(homogenization_isostrain_outputID(maxval(homogenization_Noutput),maxNinstance), &
|
|
|
|
source=undefined_ID)
|
2014-03-14 04:50:50 +05:30
|
|
|
|
2013-12-12 22:39:59 +05:30
|
|
|
rewind(fileUnit)
|
2013-12-19 14:19:47 +05:30
|
|
|
do while (trim(line) /= IO_EOF .and. IO_lc(IO_getTag(line,'<','>')) /= material_partHomogenization)! wind forward to <homogenization>
|
2013-12-12 22:39:59 +05:30
|
|
|
line = IO_read(fileUnit)
|
2010-02-25 23:09:11 +05:30
|
|
|
enddo
|
|
|
|
|
2013-12-12 22:39:59 +05:30
|
|
|
do while (trim(line) /= IO_EOF) ! read through sections of homogenization part
|
|
|
|
line = IO_read(fileUnit)
|
2013-01-28 22:06:26 +05:30
|
|
|
if (IO_isBlank(line)) cycle ! skip empty lines
|
2013-12-12 22:39:59 +05:30
|
|
|
if (IO_getTag(line,'<','>') /= '') then ! stop at next part
|
|
|
|
line = IO_read(fileUnit, .true.) ! reset IO_read
|
|
|
|
exit
|
|
|
|
endif
|
2013-01-28 22:06:26 +05:30
|
|
|
if (IO_getTag(line,'[',']') /= '') then ! next section
|
2012-02-13 19:48:07 +05:30
|
|
|
section = section + 1_pInt
|
2013-01-28 22:06:26 +05:30
|
|
|
output = 0_pInt ! reset output counter
|
2013-12-19 14:19:47 +05:30
|
|
|
cycle
|
2010-02-25 23:09:11 +05:30
|
|
|
endif
|
2013-10-09 11:42:16 +05:30
|
|
|
if (section > 0_pInt ) then ! do not short-circuit here (.and. with next if-statement). It's not safe in Fortran
|
2013-11-27 13:34:05 +05:30
|
|
|
if (homogenization_type(section) == HOMOGENIZATION_ISOSTRAIN_ID) then ! one of my sections
|
2013-10-09 11:42:16 +05:30
|
|
|
i = homogenization_typeInstance(section) ! which instance of my type is present homogenization
|
2013-10-11 21:31:53 +05:30
|
|
|
positions = IO_stringPos(line,MAXNCHUNKS)
|
2013-10-09 11:42:16 +05:30
|
|
|
tag = IO_lc(IO_stringValue(line,positions,1_pInt)) ! extract key
|
|
|
|
select case(tag)
|
2013-12-19 14:19:47 +05:30
|
|
|
case('type')
|
2013-10-09 11:42:16 +05:30
|
|
|
case ('(output)')
|
|
|
|
output = output + 1_pInt
|
|
|
|
homogenization_isostrain_output(output,i) = IO_lc(IO_stringValue(line,positions,2_pInt))
|
2013-11-27 17:09:28 +05:30
|
|
|
select case(homogenization_isostrain_output(output,i))
|
2013-12-12 05:12:33 +05:30
|
|
|
case('nconstituents','ngrains')
|
2013-12-12 22:39:59 +05:30
|
|
|
homogenization_isostrain_outputID(output,i) = nconstituents_ID
|
2013-11-27 17:09:28 +05:30
|
|
|
case('temperature')
|
2013-12-13 18:49:17 +05:30
|
|
|
homogenization_isostrain_outputID(output,i) = temperature_ID
|
2013-11-27 17:09:28 +05:30
|
|
|
case('ipcoords')
|
2013-12-13 18:49:17 +05:30
|
|
|
homogenization_isostrain_outputID(output,i) = ipcoords_ID
|
2013-11-27 17:09:28 +05:30
|
|
|
case('avgdefgrad','avgf')
|
2013-12-13 18:49:17 +05:30
|
|
|
homogenization_isostrain_outputID(output,i) = avgdefgrad_ID
|
2013-11-27 17:09:28 +05:30
|
|
|
case('avgp','avgfirstpiola','avg1stpiola')
|
2013-12-13 18:49:17 +05:30
|
|
|
homogenization_isostrain_outputID(output,i) = avgfirstpiola_ID
|
2013-11-27 17:09:28 +05:30
|
|
|
case default
|
2013-12-18 12:58:01 +05:30
|
|
|
call IO_error(105_pInt,ext_msg=IO_stringValue(line,positions,2_pInt)//&
|
|
|
|
' ('//HOMOGENIZATION_isostrain_label//')')
|
|
|
|
end select
|
2013-12-12 05:12:33 +05:30
|
|
|
case ('nconstituents','ngrains')
|
2013-12-19 14:19:47 +05:30
|
|
|
homogenization_isostrain_Ngrains(i) = IO_intValue(line,positions,2_pInt)
|
2013-10-09 11:42:16 +05:30
|
|
|
case ('mapping')
|
2013-11-27 17:09:28 +05:30
|
|
|
select case(IO_lc(IO_stringValue(line,positions,2_pInt)))
|
|
|
|
case ('parallel','sum')
|
2013-12-13 18:49:17 +05:30
|
|
|
homogenization_isostrain_mapping(i) = parallel_ID
|
2013-11-27 17:09:28 +05:30
|
|
|
case ('average','mean','avg')
|
2013-12-13 18:49:17 +05:30
|
|
|
homogenization_isostrain_mapping(i) = average_ID
|
2013-11-27 17:09:28 +05:30
|
|
|
case default
|
2013-12-20 14:06:15 +05:30
|
|
|
call IO_error(211_pInt,ext_msg=trim(tag)//' ('//HOMOGENIZATION_isostrain_label//')')
|
2013-11-27 17:09:28 +05:30
|
|
|
end select
|
2013-12-18 12:58:01 +05:30
|
|
|
case default
|
|
|
|
call IO_error(210_pInt,ext_msg=trim(tag)//' ('//HOMOGENIZATION_isostrain_label//')')
|
2013-10-09 11:42:16 +05:30
|
|
|
end select
|
|
|
|
endif
|
2010-02-25 23:09:11 +05:30
|
|
|
endif
|
|
|
|
enddo
|
|
|
|
|
2013-06-27 00:49:41 +05:30
|
|
|
do k = 1,maxNinstance
|
2010-02-25 23:09:11 +05:30
|
|
|
|
2012-02-21 22:01:37 +05:30
|
|
|
do j = 1_pInt,maxval(homogenization_Noutput)
|
2013-11-27 17:09:28 +05:30
|
|
|
select case(homogenization_isostrain_outputID(j,i))
|
2013-12-12 22:39:59 +05:30
|
|
|
case(nconstituents_ID, temperature_ID)
|
2012-02-21 22:01:37 +05:30
|
|
|
mySize = 1_pInt
|
2013-12-12 22:39:59 +05:30
|
|
|
case(ipcoords_ID)
|
2013-10-19 00:27:28 +05:30
|
|
|
mySize = 3_pInt
|
2013-12-12 22:39:59 +05:30
|
|
|
case(avgdefgrad_ID, avgfirstpiola_ID)
|
2013-10-19 00:27:28 +05:30
|
|
|
mySize = 9_pInt
|
2010-02-25 23:09:11 +05:30
|
|
|
case default
|
2012-02-21 22:01:37 +05:30
|
|
|
mySize = 0_pInt
|
2010-02-25 23:09:11 +05:30
|
|
|
end select
|
|
|
|
|
2013-10-16 18:34:59 +05:30
|
|
|
outputFound: if (mySize > 0_pInt) then
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
homogenization_isostrain_sizePostResult(j,i) = mySize
|
|
|
|
homogenization_isostrain_sizePostResults(i) = &
|
2013-10-16 18:34:59 +05:30
|
|
|
homogenization_isostrain_sizePostResults(i) + mySize
|
|
|
|
endif outputFound
|
2010-02-25 23:09:11 +05:30
|
|
|
enddo
|
|
|
|
enddo
|
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
end subroutine homogenization_isostrain_init
|
2010-02-25 23:09:11 +05:30
|
|
|
|
|
|
|
|
2013-01-28 22:06:26 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief partitions the deformation gradient onto the constituents
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2013-10-16 18:34:59 +05:30
|
|
|
subroutine homogenization_isostrain_partitionDeformation(F,avgF,el)
|
2013-01-28 22:06:26 +05:30
|
|
|
use prec, only: &
|
2013-10-16 18:34:59 +05:30
|
|
|
pReal
|
2013-10-11 21:31:53 +05:30
|
|
|
use mesh, only: &
|
|
|
|
mesh_element
|
2013-01-28 22:06:26 +05:30
|
|
|
use material, only: &
|
2013-10-11 21:31:53 +05:30
|
|
|
homogenization_maxNgrains, &
|
|
|
|
homogenization_Ngrains
|
2013-01-28 22:06:26 +05:30
|
|
|
|
2010-02-25 23:09:11 +05:30
|
|
|
implicit none
|
2013-10-16 18:34:59 +05:30
|
|
|
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(out) :: F !< partioned def grad per grain
|
|
|
|
real(pReal), dimension (3,3), intent(in) :: avgF !< my average def grad
|
2013-10-11 21:31:53 +05:30
|
|
|
integer(pInt), intent(in) :: &
|
|
|
|
el !< element number
|
2014-03-13 11:19:07 +05:30
|
|
|
F=0.0_pReal
|
|
|
|
F(1:3,1:3,1:homogenization_Ngrains(mesh_element(3,el)))= &
|
|
|
|
spread(avgF,3,homogenization_Ngrains(mesh_element(3,el)))
|
2013-10-11 21:31:53 +05:30
|
|
|
|
|
|
|
end subroutine homogenization_isostrain_partitionDeformation
|
2010-02-25 23:09:11 +05:30
|
|
|
|
|
|
|
|
2013-01-28 22:06:26 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief derive average stress and stiffness from constituent quantities
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2013-10-16 18:34:59 +05:30
|
|
|
subroutine homogenization_isostrain_averageStressAndItsTangent(avgP,dAvgPdAvgF,P,dPdF,el)
|
2013-01-28 22:06:26 +05:30
|
|
|
use prec, only: &
|
|
|
|
pReal
|
|
|
|
use mesh, only: &
|
|
|
|
mesh_element
|
2013-10-11 21:31:53 +05:30
|
|
|
use material, only: &
|
|
|
|
homogenization_maxNgrains, &
|
|
|
|
homogenization_Ngrains, &
|
|
|
|
homogenization_typeInstance
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2010-02-25 23:09:11 +05:30
|
|
|
implicit none
|
2013-10-11 21:31:53 +05:30
|
|
|
real(pReal), dimension (3,3), intent(out) :: avgP !< average stress at material point
|
|
|
|
real(pReal), dimension (3,3,3,3), intent(out) :: dAvgPdAvgF !< average stiffness at material point
|
|
|
|
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(in) :: P !< array of current grain stresses
|
|
|
|
real(pReal), dimension (3,3,3,3,homogenization_maxNgrains), intent(in) :: dPdF !< array of current grain stiffnesses
|
2013-10-16 18:34:59 +05:30
|
|
|
integer(pInt), intent(in) :: el !< element number
|
2013-10-11 21:31:53 +05:30
|
|
|
integer(pInt) :: &
|
|
|
|
homID, &
|
|
|
|
Ngrains
|
|
|
|
|
|
|
|
homID = homogenization_typeInstance(mesh_element(3,el))
|
|
|
|
Ngrains = homogenization_Ngrains(mesh_element(3,el))
|
2013-04-30 15:10:06 +05:30
|
|
|
|
|
|
|
select case (homogenization_isostrain_mapping(homID))
|
2013-12-12 22:39:59 +05:30
|
|
|
case (parallel_ID)
|
2013-04-30 15:10:06 +05:30
|
|
|
avgP = sum(P,3)
|
|
|
|
dAvgPdAvgF = sum(dPdF,5)
|
2013-12-12 22:39:59 +05:30
|
|
|
case (average_ID)
|
2013-04-30 15:10:06 +05:30
|
|
|
avgP = sum(P,3) /real(Ngrains,pReal)
|
|
|
|
dAvgPdAvgF = sum(dPdF,5)/real(Ngrains,pReal)
|
|
|
|
end select
|
2010-02-25 23:09:11 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
end subroutine homogenization_isostrain_averageStressAndItsTangent
|
2010-02-25 23:09:11 +05:30
|
|
|
|
|
|
|
|
2013-01-28 22:06:26 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief return array of homogenization results for post file inclusion
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2013-10-19 00:27:28 +05:30
|
|
|
pure function homogenization_isostrain_postResults(ip,el,avgP,avgF)
|
2013-01-28 22:06:26 +05:30
|
|
|
use prec, only: &
|
2013-10-16 18:34:59 +05:30
|
|
|
pReal
|
2013-01-28 22:06:26 +05:30
|
|
|
use mesh, only: &
|
2013-10-19 00:27:28 +05:30
|
|
|
mesh_element, &
|
|
|
|
mesh_ipCoordinates
|
2013-01-28 22:06:26 +05:30
|
|
|
use material, only: &
|
|
|
|
homogenization_typeInstance, &
|
|
|
|
homogenization_Noutput
|
2013-10-19 00:27:28 +05:30
|
|
|
use crystallite, only: &
|
|
|
|
crystallite_temperature
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2010-02-25 23:09:11 +05:30
|
|
|
implicit none
|
2013-10-19 00:27:28 +05:30
|
|
|
integer(pInt), intent(in) :: &
|
|
|
|
ip, & !< integration point number
|
|
|
|
el !< element number
|
|
|
|
real(pReal), dimension(3,3), intent(in) :: &
|
|
|
|
avgP, & !< average stress at material point
|
|
|
|
avgF !< average deformation gradient at material point
|
2013-10-11 21:31:53 +05:30
|
|
|
real(pReal), dimension(homogenization_isostrain_sizePostResults &
|
|
|
|
(homogenization_typeInstance(mesh_element(3,el)))) :: &
|
|
|
|
homogenization_isostrain_postResults
|
|
|
|
|
|
|
|
integer(pInt) :: &
|
|
|
|
homID, &
|
|
|
|
o, c
|
|
|
|
|
2010-02-25 23:09:11 +05:30
|
|
|
c = 0_pInt
|
2013-10-11 21:31:53 +05:30
|
|
|
homID = homogenization_typeInstance(mesh_element(3,el))
|
2010-02-25 23:09:11 +05:30
|
|
|
homogenization_isostrain_postResults = 0.0_pReal
|
|
|
|
|
2013-10-11 21:31:53 +05:30
|
|
|
do o = 1_pInt,homogenization_Noutput(mesh_element(3,el))
|
2013-11-27 17:09:28 +05:30
|
|
|
select case(homogenization_isostrain_outputID(o,homID))
|
2013-12-12 22:39:59 +05:30
|
|
|
case (nconstituents_ID)
|
2012-02-21 22:01:37 +05:30
|
|
|
homogenization_isostrain_postResults(c+1_pInt) = real(homogenization_isostrain_Ngrains(homID),pReal)
|
|
|
|
c = c + 1_pInt
|
2013-12-12 22:39:59 +05:30
|
|
|
case (temperature_ID)
|
2013-10-19 00:27:28 +05:30
|
|
|
homogenization_isostrain_postResults(c+1_pInt) = crystallite_temperature(ip,el)
|
|
|
|
c = c + 1_pInt
|
2013-12-12 22:39:59 +05:30
|
|
|
case (avgdefgrad_ID)
|
2013-10-19 00:27:28 +05:30
|
|
|
homogenization_isostrain_postResults(c+1_pInt:c+9_pInt) = reshape(avgF,[9])
|
|
|
|
c = c + 9_pInt
|
2013-12-12 22:39:59 +05:30
|
|
|
case (avgfirstpiola_ID)
|
2013-10-19 00:27:28 +05:30
|
|
|
homogenization_isostrain_postResults(c+1_pInt:c+9_pInt) = reshape(avgP,[9])
|
|
|
|
c = c + 9_pInt
|
2013-12-12 22:39:59 +05:30
|
|
|
case (ipcoords_ID)
|
2013-10-19 00:27:28 +05:30
|
|
|
homogenization_isostrain_postResults(c+1_pInt:c+3_pInt) = mesh_ipCoordinates(1:3,ip,el) ! current ip coordinates
|
|
|
|
c = c + 3_pInt
|
|
|
|
end select
|
2010-02-25 23:09:11 +05:30
|
|
|
enddo
|
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
end function homogenization_isostrain_postResults
|
2010-02-25 23:09:11 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
end module homogenization_isostrain
|