improved on enums (introduced them for output in j2), fixed wrong recursion depth bug in IO, fixed a bug in reading in for none, j2, phenopowerlaw
This commit is contained in:
parent
7885ebaf8f
commit
95d6430b09
|
@ -133,7 +133,7 @@ recursive function IO_read(fileUnit,reset) result(line)
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
! reset case
|
||||
if(present(reset)) then; if (reset .eqv. .true.) then ! do not short circuit here
|
||||
do while (stack > 0_pInt) ! can go back to former file
|
||||
do while (stack > 1_pInt) ! can go back to former file
|
||||
close(unitOn(stack))
|
||||
stack = stack-1_pInt
|
||||
enddo
|
||||
|
|
|
@ -31,28 +31,28 @@ module constitutive_j2
|
|||
pReal,&
|
||||
pInt
|
||||
use lattice, only: &
|
||||
LATTICE_iso_ID
|
||||
LATTICE_undefined_ID
|
||||
|
||||
implicit none
|
||||
private
|
||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
||||
constitutive_j2_sizeDotState, & !< number of dotStates
|
||||
constitutive_j2_sizeState, & !< total number of microstructural variables
|
||||
constitutive_j2_sizePostResults !< cumulative size of post results
|
||||
|
||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
||||
constitutive_j2_sizePostResult !< size of each post result output
|
||||
|
||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
||||
constitutive_j2_output !< name of each post result output
|
||||
|
||||
integer(kind(LATTICE_iso_ID)), dimension(:), allocatable, public :: &
|
||||
integer(kind(LATTICE_undefined_ID)), dimension(:), allocatable, public :: &
|
||||
constitutive_j2_structureID !< ID of the lattice structure
|
||||
|
||||
integer(pInt), dimension(:), allocatable, private :: &
|
||||
integer(pInt), dimension(:), allocatable, private :: &
|
||||
constitutive_j2_Noutput !< number of outputs per instance
|
||||
|
||||
real(pReal), dimension(:), allocatable, private :: &
|
||||
real(pReal), dimension(:), allocatable, private :: &
|
||||
constitutive_j2_fTaylor, & !< Taylor factor
|
||||
constitutive_j2_tau0, & !< initial plastic stress
|
||||
constitutive_j2_gdot0, & !< reference velocity
|
||||
|
@ -71,8 +71,15 @@ module constitutive_j2
|
|||
constitutive_j2_tausat_SinhFitC, & !< fitting parameter for normalized strain rate vs. stress function
|
||||
constitutive_j2_tausat_SinhFitD !< fitting parameter for normalized strain rate vs. stress function
|
||||
|
||||
real(pReal), dimension(:,:,:), allocatable, private :: &
|
||||
real(pReal), dimension(:,:,:), allocatable, private :: &
|
||||
constitutive_j2_Cslip_66
|
||||
enum, bind(c)
|
||||
enumerator :: undefined_ID, &
|
||||
flowstress_ID, &
|
||||
strainrate_ID
|
||||
end enum
|
||||
integer(kind(undefined_ID)), dimension(:,:), allocatable, private :: &
|
||||
constitutive_j2_outputID !< ID of each post result output
|
||||
|
||||
public :: &
|
||||
constitutive_j2_init, &
|
||||
|
@ -90,7 +97,7 @@ contains
|
|||
!> @brief module initialization
|
||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine constitutive_j2_init(myFile)
|
||||
subroutine constitutive_j2_init(fileUnit)
|
||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
||||
use math, only: &
|
||||
math_Mandel3333to66, &
|
||||
|
@ -104,7 +111,8 @@ subroutine constitutive_j2_init(myFile)
|
|||
IO_stringValue, &
|
||||
IO_floatValue, &
|
||||
IO_error, &
|
||||
IO_timeStamp
|
||||
IO_timeStamp, &
|
||||
IO_EOF
|
||||
use material
|
||||
use debug, only: &
|
||||
debug_level, &
|
||||
|
@ -113,7 +121,7 @@ subroutine constitutive_j2_init(myFile)
|
|||
use lattice
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: myFile
|
||||
integer(pInt), intent(in) :: fileUnit
|
||||
|
||||
integer(pInt), parameter :: MAXNCHUNKS = 7_pInt
|
||||
|
||||
|
@ -136,58 +144,42 @@ subroutine constitutive_j2_init(myFile)
|
|||
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) &
|
||||
write(6,'(a16,1x,i5,/)') '# instances:',maxNinstance
|
||||
|
||||
allocate(constitutive_j2_sizeDotState(maxNinstance))
|
||||
constitutive_j2_sizeDotState = 0_pInt
|
||||
allocate(constitutive_j2_sizeState(maxNinstance))
|
||||
constitutive_j2_sizeState = 0_pInt
|
||||
allocate(constitutive_j2_sizePostResults(maxNinstance))
|
||||
constitutive_j2_sizePostResults = 0_pInt
|
||||
allocate(constitutive_j2_sizePostResult(maxval(phase_Noutput), maxNinstance))
|
||||
constitutive_j2_sizePostResult = 0_pInt
|
||||
allocate(constitutive_j2_sizeDotState(maxNinstance), source=0_pInt)
|
||||
allocate(constitutive_j2_sizeState(maxNinstance), source=0_pInt)
|
||||
allocate(constitutive_j2_sizePostResults(maxNinstance), source=0_pInt)
|
||||
allocate(constitutive_j2_sizePostResult(maxval(phase_Noutput), maxNinstance),source=0_pInt)
|
||||
allocate(constitutive_j2_output(maxval(phase_Noutput), maxNinstance))
|
||||
constitutive_j2_output = ''
|
||||
allocate(constitutive_j2_Noutput(maxNinstance))
|
||||
constitutive_j2_Noutput = 0_pInt
|
||||
allocate(constitutive_j2_structureID(maxNinstance))
|
||||
constitutive_j2_structureID = -1
|
||||
allocate(constitutive_j2_Cslip_66(6,6,maxNinstance))
|
||||
constitutive_j2_Cslip_66 = 0.0_pReal
|
||||
allocate(constitutive_j2_fTaylor(maxNinstance))
|
||||
constitutive_j2_fTaylor = 0.0_pReal
|
||||
allocate(constitutive_j2_tau0(maxNinstance))
|
||||
constitutive_j2_tau0 = 0.0_pReal
|
||||
allocate(constitutive_j2_gdot0(maxNinstance))
|
||||
constitutive_j2_gdot0 = 0.0_pReal
|
||||
allocate(constitutive_j2_n(maxNinstance))
|
||||
constitutive_j2_n = 0.0_pReal
|
||||
allocate(constitutive_j2_h0(maxNinstance))
|
||||
constitutive_j2_h0 = 0.0_pReal
|
||||
allocate(constitutive_j2_h0_slopeLnRate(maxNinstance))
|
||||
constitutive_j2_h0_slopeLnRate = 0.0_pReal
|
||||
allocate(constitutive_j2_tausat(maxNinstance))
|
||||
constitutive_j2_tausat = 0.0_pReal
|
||||
allocate(constitutive_j2_a(maxNinstance))
|
||||
constitutive_j2_a = 0.0_pReal
|
||||
allocate(constitutive_j2_aTolResistance(maxNinstance))
|
||||
constitutive_j2_aTolResistance = 0.0_pReal
|
||||
allocate(constitutive_j2_tausat_SinhFitA(maxNinstance))
|
||||
constitutive_j2_tausat_SinhFitA = 0.0_pReal
|
||||
allocate(constitutive_j2_tausat_SinhFitB(maxNinstance))
|
||||
constitutive_j2_tausat_SinhFitB = 0.0_pReal
|
||||
allocate(constitutive_j2_tausat_SinhFitC(maxNinstance))
|
||||
constitutive_j2_tausat_SinhFitC = 0.0_pReal
|
||||
allocate(constitutive_j2_tausat_SinhFitD(maxNinstance))
|
||||
constitutive_j2_tausat_SinhFitD = 0.0_pReal
|
||||
allocate(constitutive_j2_outputID(maxval(phase_Noutput),maxNinstance), source=undefined_ID)
|
||||
allocate(constitutive_j2_Noutput(maxNinstance), source=0_pInt)
|
||||
allocate(constitutive_j2_structureID(maxNinstance), source=LATTICE_undefined_ID)
|
||||
allocate(constitutive_j2_Cslip_66(6,6,maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_j2_fTaylor(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_j2_tau0(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_j2_gdot0(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_j2_n(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_j2_h0(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_j2_h0_slopeLnRate(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_j2_tausat(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_j2_a(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_j2_aTolResistance(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_j2_tausat_SinhFitA(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_j2_tausat_SinhFitB(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_j2_tausat_SinhFitC(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_j2_tausat_SinhFitD(maxNinstance), source=0.0_pReal)
|
||||
|
||||
rewind(myFile)
|
||||
do while (trim(line) /= '#EOF#' .and. IO_lc(IO_getTag(line,'<','>')) /= 'phase') ! wind forward to <phase>
|
||||
line = IO_read(myFile)
|
||||
rewind(fileUnit)
|
||||
do while (trim(line) /= IO_EOF .and. IO_lc(IO_getTag(line,'<','>')) /= 'phase') ! wind forward to <phase>
|
||||
line = IO_read(fileUnit)
|
||||
enddo
|
||||
|
||||
do while (trim(line) /= '#EOF#') ! read through sections of phase part
|
||||
line = IO_read(myFile)
|
||||
do while (trim(line) /= IO_EOF) ! read through sections of phase part
|
||||
line = IO_read(fileUnit)
|
||||
if (IO_isBlank(line)) cycle ! skip empty lines
|
||||
if (IO_getTag(line,'<','>') /= '') exit ! stop at next part
|
||||
if (IO_getTag(line,'<','>') /= '') then ! stop at next part
|
||||
line = IO_read(fileUnit, .true.) ! reset IO_read
|
||||
exit
|
||||
endif
|
||||
if (IO_getTag(line,'[',']') /= '') then ! next section
|
||||
section = section + 1_pInt ! advance section counter
|
||||
cycle ! skip to next line
|
||||
|
@ -203,7 +195,13 @@ subroutine constitutive_j2_init(myFile)
|
|||
case ('(output)')
|
||||
constitutive_j2_Noutput(i) = constitutive_j2_Noutput(i) + 1_pInt
|
||||
constitutive_j2_output(constitutive_j2_Noutput(i),i) = &
|
||||
IO_lc(IO_stringValue(line,positions,2_pInt))
|
||||
IO_lc(IO_stringValue(line,positions,2_pInt))
|
||||
select case(IO_lc(IO_stringValue(line,positions,2_pInt)))
|
||||
case ('flowstress')
|
||||
constitutive_j2_outputID(constitutive_j2_Noutput(i),i) = flowstress_ID
|
||||
case ('strainrate')
|
||||
constitutive_j2_outputID(constitutive_j2_Noutput(i),i) = strainrate_ID
|
||||
end select
|
||||
case ('lattice_structure')
|
||||
structure = IO_lc(IO_stringValue(line,positions,2_pInt))
|
||||
select case(structure(1:3))
|
||||
|
@ -288,10 +286,8 @@ subroutine constitutive_j2_init(myFile)
|
|||
|
||||
instancesLoop: do i = 1_pInt,maxNinstance
|
||||
outputsLoop: do o = 1_pInt,constitutive_j2_Noutput(i)
|
||||
select case(constitutive_j2_output(o,i))
|
||||
case('flowstress')
|
||||
mySize = 1_pInt
|
||||
case('strainrate')
|
||||
select case(constitutive_j2_outputID(o,i))
|
||||
case(flowstress_ID,strainrate_ID)
|
||||
mySize = 1_pInt
|
||||
case default
|
||||
call IO_error(212_pInt,ext_msg=constitutive_j2_output(o,i)//' ('//PLASTICITY_J2_label//')')
|
||||
|
@ -583,11 +579,11 @@ pure function constitutive_j2_postResults(Tstar_v,state,ipc,ip,el)
|
|||
constitutive_j2_postResults = 0.0_pReal
|
||||
|
||||
outputsLoop: do o = 1_pInt,phase_Noutput(material_phase(ipc,ip,el))
|
||||
select case(constitutive_j2_output(o,matID))
|
||||
case ('flowstress')
|
||||
select case(constitutive_j2_outputID(o,matID))
|
||||
case (flowstress_ID)
|
||||
constitutive_j2_postResults(c+1_pInt) = state(ipc,ip,el)%p(1)
|
||||
c = c + 1_pInt
|
||||
case ('strainrate')
|
||||
case (strainrate_ID)
|
||||
constitutive_j2_postResults(c+1_pInt) = &
|
||||
constitutive_j2_gdot0(matID) * ( sqrt(1.5_pReal) * norm_Tstar_dev &
|
||||
/ &!----------------------------------------------------------------------------------
|
||||
|
|
|
@ -28,22 +28,22 @@ module constitutive_none
|
|||
pReal, &
|
||||
pInt
|
||||
use lattice, only: &
|
||||
LATTICE_iso_ID
|
||||
LATTICE_undefined_ID
|
||||
|
||||
implicit none
|
||||
private
|
||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
||||
constitutive_none_sizeDotState, &
|
||||
constitutive_none_sizeState, &
|
||||
constitutive_none_sizePostResults
|
||||
|
||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
||||
constitutive_none_sizePostResult !< size of each post result output
|
||||
|
||||
integer(kind(LATTICE_iso_ID)), dimension(:), allocatable, public :: &
|
||||
integer(kind(LATTICE_undefined_ID)), dimension(:), allocatable, public :: &
|
||||
constitutive_none_structureID !< ID of the lattice structure
|
||||
|
||||
real(pReal), dimension(:,:,:), allocatable, private :: &
|
||||
real(pReal), dimension(:,:,:), allocatable, private :: &
|
||||
constitutive_none_Cslip_66
|
||||
|
||||
public :: &
|
||||
|
@ -57,7 +57,7 @@ contains
|
|||
!> @brief module initialization
|
||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine constitutive_none_init(myFile)
|
||||
subroutine constitutive_none_init(fileUnit)
|
||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
||||
use math, only: &
|
||||
math_Mandel3333to66, &
|
||||
|
@ -71,7 +71,8 @@ subroutine constitutive_none_init(myFile)
|
|||
IO_stringValue, &
|
||||
IO_floatValue, &
|
||||
IO_error, &
|
||||
IO_timeStamp
|
||||
IO_timeStamp, &
|
||||
IO_EOF
|
||||
use material
|
||||
use debug, only: &
|
||||
debug_level, &
|
||||
|
@ -80,7 +81,7 @@ subroutine constitutive_none_init(myFile)
|
|||
use lattice
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: myFile
|
||||
integer(pInt), intent(in) :: fileUnit
|
||||
|
||||
integer(pInt), parameter :: MAXNCHUNKS = 7_pInt
|
||||
|
||||
|
@ -103,27 +104,24 @@ subroutine constitutive_none_init(myFile)
|
|||
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) &
|
||||
write(6,'(a16,1x,i5,/)') '# instances:',maxNinstance
|
||||
|
||||
allocate(constitutive_none_sizeDotState(maxNinstance))
|
||||
constitutive_none_sizeDotState = 0_pInt
|
||||
allocate(constitutive_none_sizeState(maxNinstance))
|
||||
constitutive_none_sizeState = 0_pInt
|
||||
allocate(constitutive_none_sizePostResults(maxNinstance))
|
||||
constitutive_none_sizePostResults = 0_pInt
|
||||
allocate(constitutive_none_structureID(maxNinstance))
|
||||
constitutive_none_structureID = -1
|
||||
allocate(constitutive_none_Cslip_66(6,6,maxNinstance))
|
||||
constitutive_none_Cslip_66 = 0.0_pReal
|
||||
allocate(constitutive_none_sizeDotState(maxNinstance), source=0_pInt)
|
||||
allocate(constitutive_none_sizeState(maxNinstance), source=0_pInt)
|
||||
allocate(constitutive_none_sizePostResults(maxNinstance), source=0_pInt)
|
||||
allocate(constitutive_none_structureID(maxNinstance), source=LATTICE_undefined_ID)
|
||||
allocate(constitutive_none_Cslip_66(6,6,maxNinstance), source=0.0_pReal)
|
||||
|
||||
rewind(myFile)
|
||||
|
||||
do while (trim(line) /= '#EOF#' .and. IO_lc(IO_getTag(line,'<','>')) /= 'phase') ! wind forward to <phase>
|
||||
line = IO_read(myFile)
|
||||
rewind(fileUnit)
|
||||
do while (trim(line) /= IO_EOF .and. IO_lc(IO_getTag(line,'<','>')) /= 'phase') ! wind forward to <phase>
|
||||
line = IO_read(fileUnit)
|
||||
enddo
|
||||
|
||||
do while (trim(line) /= '#EOF#') ! read through sections of phase part
|
||||
line = IO_read(myFile)
|
||||
do while (trim(line) /= IO_EOF) ! read through sections of phase part
|
||||
line = IO_read(fileUnit)
|
||||
if (IO_isBlank(line)) cycle ! skip empty lines
|
||||
if (IO_getTag(line,'<','>') /= '') exit ! stop at next part
|
||||
if (IO_getTag(line,'<','>') /= '') then ! stop at next part
|
||||
line = IO_read(fileUnit, .true.) ! reset IO_read
|
||||
exit
|
||||
endif
|
||||
if (IO_getTag(line,'[',']') /= '') then ! next section
|
||||
section = section + 1_pInt ! advance section counter
|
||||
cycle
|
||||
|
|
|
@ -29,35 +29,35 @@ module constitutive_phenopowerlaw
|
|||
pReal,&
|
||||
pInt
|
||||
use lattice, only: &
|
||||
LATTICE_iso_ID
|
||||
LATTICE_undefined_ID
|
||||
|
||||
implicit none
|
||||
private
|
||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
||||
constitutive_phenopowerlaw_sizeDotState, &
|
||||
constitutive_phenopowerlaw_sizeState, &
|
||||
constitutive_phenopowerlaw_sizePostResults, & !< cumulative size of post results
|
||||
constitutive_phenopowerlaw_structure
|
||||
|
||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
||||
constitutive_phenopowerlaw_sizePostResult !< size of each post result output
|
||||
|
||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
||||
constitutive_phenopowerlaw_output !< name of each post result output
|
||||
|
||||
integer(kind(LATTICE_iso_ID)), dimension(:), allocatable, public :: &
|
||||
integer(kind(LATTICE_undefined_ID)), dimension(:), allocatable, public :: &
|
||||
constitutive_phenopowerlaw_structureID !< ID of the lattice structure
|
||||
|
||||
integer(pInt), dimension(:), allocatable, private :: &
|
||||
integer(pInt), dimension(:), allocatable, private :: &
|
||||
constitutive_phenopowerlaw_Noutput, & !< number of outputs per instance of this constitution
|
||||
constitutive_phenopowerlaw_totalNslip, & !< no. of slip system used in simulation
|
||||
constitutive_phenopowerlaw_totalNtwin !< no. of twin system used in simulation
|
||||
|
||||
integer(pInt), dimension(:,:), allocatable, private :: &
|
||||
integer(pInt), dimension(:,:), allocatable, private :: &
|
||||
constitutive_phenopowerlaw_Nslip, & !< active number of slip systems per family (input parameter, per family)
|
||||
constitutive_phenopowerlaw_Ntwin !< active number of twin systems per family (input parameter, per family)
|
||||
|
||||
real(pReal), dimension(:), allocatable, private :: &
|
||||
real(pReal), dimension(:), allocatable, private :: &
|
||||
constitutive_phenopowerlaw_CoverA, & !< c/a of the crystal (input parameter)
|
||||
constitutive_phenopowerlaw_gdot0_slip, & !< reference shear strain rate for slip (input parameter)
|
||||
constitutive_phenopowerlaw_gdot0_twin, & !< reference shear strain rate for twin (input parameter)
|
||||
|
@ -78,7 +78,7 @@ module constitutive_phenopowerlaw
|
|||
constitutive_phenopowerlaw_aTolShear, &
|
||||
constitutive_phenopowerlaw_aTolTwinfrac
|
||||
|
||||
real(pReal), dimension(:,:), allocatable, private :: &
|
||||
real(pReal), dimension(:,:), allocatable, private :: &
|
||||
constitutive_phenopowerlaw_tau0_slip, & !< initial critical shear stress for slip (input parameter, per family)
|
||||
constitutive_phenopowerlaw_tau0_twin, & !< initial critical shear stress for twin (input parameter, per family)
|
||||
constitutive_phenopowerlaw_tausat_slip, & !< maximum critical shear stress for slip (input parameter, per family)
|
||||
|
@ -89,14 +89,15 @@ module constitutive_phenopowerlaw
|
|||
constitutive_phenopowerlaw_interaction_TwinSlip, & !< interaction factors twin - slip (input parameter)
|
||||
constitutive_phenopowerlaw_interaction_TwinTwin !< interaction factors twin - twin (input parameter)
|
||||
|
||||
real(pReal), dimension(:,:,:), allocatable, private :: &
|
||||
real(pReal), dimension(:,:,:), allocatable, private :: &
|
||||
constitutive_phenopowerlaw_hardeningMatrix_SlipSlip, &
|
||||
constitutive_phenopowerlaw_hardeningMatrix_SlipTwin, &
|
||||
constitutive_phenopowerlaw_hardeningMatrix_TwinSlip, &
|
||||
constitutive_phenopowerlaw_hardeningMatrix_TwinTwin, &
|
||||
constitutive_phenopowerlaw_Cslip_66
|
||||
enum, bind(c)
|
||||
enumerator :: resistance_slip_ID, &
|
||||
enumerator :: undefined_ID, &
|
||||
resistance_slip_ID, &
|
||||
accumulatedshear_slip_ID, &
|
||||
shearrate_slip_ID, &
|
||||
resolvedstress_slip_ID, &
|
||||
|
@ -107,7 +108,7 @@ module constitutive_phenopowerlaw
|
|||
resolvedstress_twin_ID, &
|
||||
totalvolfrac_ID
|
||||
end enum
|
||||
integer(kind(resistance_slip_ID)), dimension(:,:), allocatable, private :: &
|
||||
integer(kind(undefined_ID)), dimension(:,:), allocatable, private :: &
|
||||
constitutive_phenopowerlaw_outputID !< ID of each post result output
|
||||
|
||||
public :: &
|
||||
|
@ -126,7 +127,7 @@ contains
|
|||
!> @brief module initialization
|
||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine constitutive_phenopowerlaw_init(myFile)
|
||||
subroutine constitutive_phenopowerlaw_init(fileUnit)
|
||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
||||
use prec, only: &
|
||||
tol_math_check
|
||||
|
@ -142,7 +143,7 @@ subroutine constitutive_phenopowerlaw_init(myFile)
|
|||
use lattice
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: myFile
|
||||
integer(pInt), intent(in) :: fileUnit
|
||||
|
||||
integer(pInt), parameter :: MAXNCHUNKS = LATTICE_maxNinteraction + 1_pInt
|
||||
integer(pInt), dimension(1_pInt+2_pInt*MAXNCHUNKS) :: positions
|
||||
|
@ -179,93 +180,63 @@ subroutine constitutive_phenopowerlaw_init(myFile)
|
|||
Nchunks_TwinTwin = lattice_maxNinteraction
|
||||
Nchunks_nonSchmid = lattice_maxNnonSchmid
|
||||
|
||||
allocate(constitutive_phenopowerlaw_sizeDotState(maxNinstance))
|
||||
constitutive_phenopowerlaw_sizeDotState = 0_pInt
|
||||
allocate(constitutive_phenopowerlaw_sizeState(maxNinstance))
|
||||
constitutive_phenopowerlaw_sizeState = 0_pInt
|
||||
allocate(constitutive_phenopowerlaw_sizePostResults(maxNinstance))
|
||||
constitutive_phenopowerlaw_sizePostResults = 0_pInt
|
||||
allocate(constitutive_phenopowerlaw_sizePostResult(maxval(phase_Noutput),maxNinstance))
|
||||
constitutive_phenopowerlaw_sizePostResult = 0_pInt
|
||||
allocate(constitutive_phenopowerlaw_sizeDotState(maxNinstance), source=0_pInt)
|
||||
allocate(constitutive_phenopowerlaw_sizeState(maxNinstance), source=0_pInt)
|
||||
allocate(constitutive_phenopowerlaw_sizePostResults(maxNinstance), source=0_pInt)
|
||||
allocate(constitutive_phenopowerlaw_sizePostResult(maxval(phase_Noutput),maxNinstance), &
|
||||
source=0_pInt)
|
||||
allocate(constitutive_phenopowerlaw_output(maxval(phase_Noutput),maxNinstance))
|
||||
constitutive_phenopowerlaw_output = ''
|
||||
allocate(constitutive_phenopowerlaw_outputID(maxval(phase_Noutput),maxNinstance))
|
||||
constitutive_phenopowerlaw_outputID = -1
|
||||
allocate(constitutive_phenopowerlaw_Noutput(maxNinstance))
|
||||
constitutive_phenopowerlaw_Noutput = 0_pInt
|
||||
allocate(constitutive_phenopowerlaw_structureID(maxNinstance))
|
||||
constitutive_phenopowerlaw_structureID = -1
|
||||
allocate(constitutive_phenopowerlaw_structure(maxNinstance))
|
||||
constitutive_phenopowerlaw_structure = 0_pInt
|
||||
allocate(constitutive_phenopowerlaw_Nslip(lattice_maxNslipFamily,maxNinstance))
|
||||
constitutive_phenopowerlaw_Nslip = 0_pInt
|
||||
allocate(constitutive_phenopowerlaw_Ntwin(lattice_maxNtwinFamily,maxNinstance))
|
||||
constitutive_phenopowerlaw_Ntwin = 0_pInt
|
||||
allocate(constitutive_phenopowerlaw_totalNslip(maxNinstance))
|
||||
constitutive_phenopowerlaw_totalNslip = 0_pInt
|
||||
allocate(constitutive_phenopowerlaw_totalNtwin(maxNinstance))
|
||||
constitutive_phenopowerlaw_totalNtwin = 0_pInt
|
||||
allocate(constitutive_phenopowerlaw_CoverA(maxNinstance))
|
||||
constitutive_phenopowerlaw_CoverA = 0.0_pReal
|
||||
allocate(constitutive_phenopowerlaw_Cslip_66(6,6,maxNinstance))
|
||||
constitutive_phenopowerlaw_Cslip_66 = 0.0_pReal
|
||||
allocate(constitutive_phenopowerlaw_gdot0_slip(maxNinstance))
|
||||
constitutive_phenopowerlaw_gdot0_slip = 0.0_pReal
|
||||
allocate(constitutive_phenopowerlaw_n_slip(maxNinstance))
|
||||
constitutive_phenopowerlaw_n_slip = 0.0_pReal
|
||||
allocate(constitutive_phenopowerlaw_tau0_slip(lattice_maxNslipFamily,maxNinstance))
|
||||
constitutive_phenopowerlaw_tau0_slip = 0.0_pReal
|
||||
allocate(constitutive_phenopowerlaw_tausat_slip(lattice_maxNslipFamily,maxNinstance))
|
||||
constitutive_phenopowerlaw_tausat_slip = 0.0_pReal
|
||||
allocate(constitutive_phenopowerlaw_gdot0_twin(maxNinstance))
|
||||
constitutive_phenopowerlaw_gdot0_twin = 0.0_pReal
|
||||
allocate(constitutive_phenopowerlaw_n_twin(maxNinstance))
|
||||
constitutive_phenopowerlaw_n_twin = 0.0_pReal
|
||||
allocate(constitutive_phenopowerlaw_tau0_twin(lattice_maxNtwinFamily,maxNinstance))
|
||||
constitutive_phenopowerlaw_tau0_twin = 0.0_pReal
|
||||
allocate(constitutive_phenopowerlaw_spr(maxNinstance))
|
||||
constitutive_phenopowerlaw_spr = 0.0_pReal
|
||||
allocate(constitutive_phenopowerlaw_twinB(maxNinstance))
|
||||
constitutive_phenopowerlaw_twinB = 0.0_pReal
|
||||
allocate(constitutive_phenopowerlaw_twinC(maxNinstance))
|
||||
constitutive_phenopowerlaw_twinC = 0.0_pReal
|
||||
allocate(constitutive_phenopowerlaw_twinD(maxNinstance))
|
||||
constitutive_phenopowerlaw_twinD = 0.0_pReal
|
||||
allocate(constitutive_phenopowerlaw_twinE(maxNinstance))
|
||||
constitutive_phenopowerlaw_twinE = 0.0_pReal
|
||||
allocate(constitutive_phenopowerlaw_h0_SlipSlip(maxNinstance))
|
||||
constitutive_phenopowerlaw_h0_SlipSlip = 0.0_pReal
|
||||
allocate(constitutive_phenopowerlaw_h0_SlipTwin(maxNinstance))
|
||||
constitutive_phenopowerlaw_h0_SlipTwin = 0.0_pReal
|
||||
allocate(constitutive_phenopowerlaw_h0_TwinSlip(maxNinstance))
|
||||
constitutive_phenopowerlaw_h0_TwinSlip = 0.0_pReal
|
||||
allocate(constitutive_phenopowerlaw_h0_TwinTwin(maxNinstance))
|
||||
constitutive_phenopowerlaw_h0_TwinTwin = 0.0_pReal
|
||||
allocate(constitutive_phenopowerlaw_interaction_SlipSlip(lattice_maxNinteraction,maxNinstance))
|
||||
constitutive_phenopowerlaw_interaction_SlipSlip = 0.0_pReal
|
||||
allocate(constitutive_phenopowerlaw_interaction_SlipTwin(lattice_maxNinteraction,maxNinstance))
|
||||
constitutive_phenopowerlaw_interaction_SlipTwin = 0.0_pReal
|
||||
allocate(constitutive_phenopowerlaw_interaction_TwinSlip(lattice_maxNinteraction,maxNinstance))
|
||||
constitutive_phenopowerlaw_interaction_TwinSlip = 0.0_pReal
|
||||
allocate(constitutive_phenopowerlaw_interaction_TwinTwin(lattice_maxNinteraction,maxNinstance))
|
||||
constitutive_phenopowerlaw_interaction_TwinTwin = 0.0_pReal
|
||||
allocate(constitutive_phenopowerlaw_a_slip(maxNinstance))
|
||||
constitutive_phenopowerlaw_a_slip = 0.0_pReal
|
||||
allocate(constitutive_phenopowerlaw_aTolResistance(maxNinstance))
|
||||
constitutive_phenopowerlaw_aTolResistance = 0.0_pReal
|
||||
allocate(constitutive_phenopowerlaw_aTolShear(maxNinstance))
|
||||
constitutive_phenopowerlaw_aTolShear = 0.0_pReal
|
||||
allocate(constitutive_phenopowerlaw_aTolTwinfrac(maxNinstance))
|
||||
constitutive_phenopowerlaw_aTolTwinfrac = 0.0_pReal
|
||||
allocate(constitutive_phenopowerlaw_nonSchmidCoeff(lattice_maxNnonSchmid,maxNinstance))
|
||||
constitutive_phenopowerlaw_nonSchmidCoeff = 0.0_pReal
|
||||
allocate(constitutive_phenopowerlaw_outputID(maxval(phase_Noutput),maxNinstance),source=undefined_ID)
|
||||
allocate(constitutive_phenopowerlaw_Noutput(maxNinstance), source=0_pInt)
|
||||
allocate(constitutive_phenopowerlaw_structureID(maxNinstance), source=LATTICE_undefined_ID)
|
||||
allocate(constitutive_phenopowerlaw_structure(maxNinstance), source=0_pInt)
|
||||
allocate(constitutive_phenopowerlaw_Nslip(lattice_maxNslipFamily,maxNinstance), source=0_pInt)
|
||||
allocate(constitutive_phenopowerlaw_Ntwin(lattice_maxNtwinFamily,maxNinstance), source=0_pInt)
|
||||
allocate(constitutive_phenopowerlaw_totalNslip(maxNinstance), source=0_pInt)
|
||||
allocate(constitutive_phenopowerlaw_totalNtwin(maxNinstance), source=0_pInt)
|
||||
allocate(constitutive_phenopowerlaw_CoverA(maxNinstance) , source=0.0_pReal)
|
||||
allocate(constitutive_phenopowerlaw_Cslip_66(6,6,maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_phenopowerlaw_gdot0_slip(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_phenopowerlaw_n_slip(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_phenopowerlaw_tau0_slip(lattice_maxNslipFamily,maxNinstance), &
|
||||
source=0.0_pReal)
|
||||
allocate(constitutive_phenopowerlaw_tausat_slip(lattice_maxNslipFamily,maxNinstance), &
|
||||
source=0.0_pReal)
|
||||
allocate(constitutive_phenopowerlaw_gdot0_twin(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_phenopowerlaw_n_twin(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_phenopowerlaw_tau0_twin(lattice_maxNtwinFamily,maxNinstance), &
|
||||
source=0.0_pReal)
|
||||
allocate(constitutive_phenopowerlaw_spr(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_phenopowerlaw_twinB(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_phenopowerlaw_twinC(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_phenopowerlaw_twinD(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_phenopowerlaw_twinE(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_phenopowerlaw_h0_SlipSlip(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_phenopowerlaw_h0_SlipTwin(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_phenopowerlaw_h0_TwinSlip(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_phenopowerlaw_h0_TwinTwin(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_phenopowerlaw_interaction_SlipSlip(lattice_maxNinteraction,maxNinstance), &
|
||||
source=0.0_pReal)
|
||||
allocate(constitutive_phenopowerlaw_interaction_SlipTwin(lattice_maxNinteraction,maxNinstance), &
|
||||
source=0.0_pReal)
|
||||
allocate(constitutive_phenopowerlaw_interaction_TwinSlip(lattice_maxNinteraction,maxNinstance), &
|
||||
source=0.0_pReal)
|
||||
allocate(constitutive_phenopowerlaw_interaction_TwinTwin(lattice_maxNinteraction,maxNinstance), &
|
||||
source=0.0_pReal)
|
||||
allocate(constitutive_phenopowerlaw_a_slip(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_phenopowerlaw_aTolResistance(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_phenopowerlaw_aTolShear(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_phenopowerlaw_aTolTwinfrac(maxNinstance), source=0.0_pReal)
|
||||
allocate(constitutive_phenopowerlaw_nonSchmidCoeff(lattice_maxNnonSchmid,maxNinstance), &
|
||||
source=0.0_pReal)
|
||||
|
||||
rewind(myFile)
|
||||
rewind(fileUnit)
|
||||
do while (trim(line) /= '#EOF#' .and. IO_lc(IO_getTag(line,'<','>')) /= 'phase') ! wind forward to <phase>
|
||||
line = IO_read(myFile)
|
||||
line = IO_read(fileUnit)
|
||||
enddo
|
||||
do while (trim(line) /= '#EOF#') ! read through sections of phase part
|
||||
line = IO_read(myFile)
|
||||
line = IO_read(fileUnit)
|
||||
if (IO_isBlank(line)) cycle ! skip empty lines
|
||||
if (IO_getTag(line,'<','>') /= '') exit ! stop at next part
|
||||
if (IO_getTag(line,'[',']') /= '') then ! next section
|
||||
|
|
|
@ -691,7 +691,8 @@ module lattice
|
|||
20,20,20,20,20,20, 19,19,19,19,19,19, 18,18,18,18,18,18, 17,17,17,17,17,16 &
|
||||
],pInt),[lattice_hex_Ntwin,lattice_hex_Ntwin],order=[2,1]) !< Twin--slip interaction types for hex (isotropic, 16 in total)
|
||||
enum, bind(c)
|
||||
enumerator :: LATTICE_iso_ID, &
|
||||
enumerator :: LATTICE_undefined_ID, &
|
||||
LATTICE_iso_ID, &
|
||||
LATTICE_fcc_ID, &
|
||||
LATTICE_bcc_ID, &
|
||||
LATTICE_hex_ID, &
|
||||
|
@ -710,6 +711,7 @@ module lattice
|
|||
lattice_symmetryType, &
|
||||
lattice_symmetrizeC66, &
|
||||
lattice_configNchunks, &
|
||||
LATTICE_undefined_ID, &
|
||||
LATTICE_iso_ID, &
|
||||
LATTICE_fcc_ID, &
|
||||
LATTICE_bcc_ID, &
|
||||
|
|
Loading…
Reference in New Issue