Merge branch '30_parsePhasePartOnce' into 19-NewStylePhenopowerlaw

This commit is contained in:
Martin Diehl 2018-06-19 23:10:06 +02:00
commit 7aa8cac164
3 changed files with 25 additions and 19 deletions

View File

@ -268,7 +268,8 @@ subroutine crystallite_init
do c = 1_pInt, material_Ncrystallite do c = 1_pInt, material_Ncrystallite
str = crystalliteConfig(c)%getStrings('(output)')!,defaultVal=[]) if (crystalliteConfig(c)%keyExists('output') )then
str = crystalliteConfig(c)%getStrings('(output)')
do o = 1_pInt, size(str) do o = 1_pInt, size(str)
crystallite_output(o,c) = str(o) crystallite_output(o,c) = str(o)
outputName: select case(str(o)) outputName: select case(str(o))
@ -319,7 +320,8 @@ subroutine crystallite_init
case default outputName case default outputName
call IO_error(105_pInt,ext_msg=tag//' (Crystallite)') call IO_error(105_pInt,ext_msg=tag//' (Crystallite)')
end select outputName end select outputName
enddo enddo
endif
enddo enddo

View File

@ -147,7 +147,6 @@ integer(pInt) function count(this,key)
class(tPartitionedStringList), intent(in) :: this class(tPartitionedStringList), intent(in) :: this
character(len=*), intent(in) :: key character(len=*), intent(in) :: key
type(tPartitionedStringList), pointer :: item type(tPartitionedStringList), pointer :: item
integer(pInt) :: i
count = 0_pInt count = 0_pInt
@ -326,9 +325,7 @@ function getStrings(this,key,defaultVal,raw)
cumulative = (key(1:1) == '(' .and. key(len_trim(key):len_trim(key)) == ')') cumulative = (key(1:1) == '(' .and. key(len_trim(key):len_trim(key)) == ')')
split = merge(.not. raw,.true.,present(raw)) split = merge(.not. raw,.true.,present(raw))
found = present(defaultVal) found = .false.
if (present(defaultVal)) getStrings = defaultVal
item => this%next item => this%next
do while (associated(item)) do while (associated(item))
@ -363,8 +360,13 @@ function getStrings(this,key,defaultVal,raw)
item => item%next item => item%next
end do end do
if (present(defaultVal) .and. .not. found) then
getStrings = defaultVal
found = .true.
endif
if (.not. found) call IO_error(140_pInt,ext_msg=key) if (.not. found) call IO_error(140_pInt,ext_msg=key)
end function
end function getStrings
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
@ -388,13 +390,9 @@ function getInts(this,key,defaultVal)
cumulative cumulative
cumulative = (key(1:1) == '(' .and. key(len_trim(key):len_trim(key)) == ')') cumulative = (key(1:1) == '(' .and. key(len_trim(key):len_trim(key)) == ')')
found = present(defaultVal) found = .false.
if (present(defaultVal)) then
getInts = defaultVal
else
allocate(getInts(0)) allocate(getInts(0))
endif
item => this%next item => this%next
do while (associated(item)) do while (associated(item))
@ -412,6 +410,10 @@ function getInts(this,key,defaultVal)
item => item%next item => item%next
end do end do
if (present(defaultVal) .and. .not. found) then
getInts = defaultVal
found = .true.
endif
if (.not. found) call IO_error(140_pInt,ext_msg=key) if (.not. found) call IO_error(140_pInt,ext_msg=key)
end function getInts end function getInts
@ -438,13 +440,9 @@ function getFloats(this,key,defaultVal)
cumulative cumulative
cumulative = (key(1:1) == '(' .and. key(len_trim(key):len_trim(key)) == ')') cumulative = (key(1:1) == '(' .and. key(len_trim(key):len_trim(key)) == ')')
found = present(defaultVal) found = .false.
if (present(defaultVal)) then
getFloats = defaultVal
else
allocate(getFloats(0)) allocate(getFloats(0))
endif
item => this%next item => this%next
do while (associated(item)) do while (associated(item))
@ -462,6 +460,10 @@ function getFloats(this,key,defaultVal)
item => item%next item => item%next
end do end do
if (present(defaultVal) .and. .not. found) then
getFloats = defaultVal
found = .true.
endif
if (.not. found) call IO_error(140_pInt,ext_msg=key) if (.not. found) call IO_error(140_pInt,ext_msg=key)
end function getFloats end function getFloats

View File

@ -1,6 +1,7 @@
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @author Philip Eisenlohr, Michigan State University !> @author Philip Eisenlohr, Michigan State University
!> @author Zhuowen Zhao, Michigan State University !> @author Zhuowen Zhao, Michigan State University
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
!> @brief Introducing Voce-type kinematic hardening rule into crystal plasticity !> @brief Introducing Voce-type kinematic hardening rule into crystal plasticity
!! formulation using a power law fitting !! formulation using a power law fitting
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
@ -231,6 +232,7 @@ subroutine plastic_kinehardening_init(fileUnit)
allocate(param(instance)%nonSchmidCoeff(Nchunks_nonSchmid), source=0.0_pReal) allocate(param(instance)%nonSchmidCoeff(Nchunks_nonSchmid), source=0.0_pReal)
if(allocated(tempPerSlip)) deallocate(tempPerSlip) if(allocated(tempPerSlip)) deallocate(tempPerSlip)
allocate(tempPerSlip(Nchunks_SlipFamilies)) allocate(tempPerSlip(Nchunks_SlipFamilies))
allocate(param(instance)%outputID(0))
endif endif
cycle ! skip to next line cycle ! skip to next line
endif endif