Merge remote-tracking branch 'origin/development' into YAML-error-message
This commit is contained in:
commit
c8e48090a2
|
@ -503,6 +503,8 @@ subroutine IO_error(error_ID,el,ip,g,instance,ext_msg)
|
||||||
msg = 'Abrupt end of file'
|
msg = 'Abrupt end of file'
|
||||||
case (708)
|
case (708)
|
||||||
msg = '--- expected after YAML file header'
|
msg = '--- expected after YAML file header'
|
||||||
|
case (709)
|
||||||
|
msg = 'Length mismatch'
|
||||||
|
|
||||||
!-------------------------------------------------------------------------------------------------
|
!-------------------------------------------------------------------------------------------------
|
||||||
! errors related to the grid solver
|
! errors related to the grid solver
|
||||||
|
|
|
@ -29,43 +29,45 @@ module YAML_types
|
||||||
procedure :: &
|
procedure :: &
|
||||||
tNode_get_byIndex_asFloat => tNode_get_byIndex_asFloat
|
tNode_get_byIndex_asFloat => tNode_get_byIndex_asFloat
|
||||||
procedure :: &
|
procedure :: &
|
||||||
tNode_get_byIndex_asFloats => tNode_get_byIndex_asFloats
|
tNode_get_byIndex_as1dFloat => tNode_get_byIndex_as1dFloat
|
||||||
procedure :: &
|
procedure :: &
|
||||||
tNode_get_byIndex_asInt => tNode_get_byIndex_asInt
|
tNode_get_byIndex_asInt => tNode_get_byIndex_asInt
|
||||||
procedure :: &
|
procedure :: &
|
||||||
tNode_get_byIndex_asInts => tNode_get_byIndex_asInts
|
tNode_get_byIndex_as1dInt => tNode_get_byIndex_as1dInt
|
||||||
procedure :: &
|
procedure :: &
|
||||||
tNode_get_byIndex_asBool => tNode_get_byIndex_asBool
|
tNode_get_byIndex_asBool => tNode_get_byIndex_asBool
|
||||||
procedure :: &
|
procedure :: &
|
||||||
tNode_get_byIndex_asBools => tNode_get_byIndex_asBools
|
tNode_get_byIndex_as1dBool => tNode_get_byIndex_as1dBool
|
||||||
procedure :: &
|
procedure :: &
|
||||||
tNode_get_byIndex_asString => tNode_get_byIndex_asString
|
tNode_get_byIndex_asString => tNode_get_byIndex_asString
|
||||||
procedure :: &
|
procedure :: &
|
||||||
tNode_get_byIndex_asStrings => tNode_get_byIndex_asStrings
|
tNode_get_byIndex_as1dString => tNode_get_byIndex_as1dString
|
||||||
procedure :: &
|
procedure :: &
|
||||||
tNode_get_byKey => tNode_get_byKey
|
tNode_get_byKey => tNode_get_byKey
|
||||||
procedure :: &
|
procedure :: &
|
||||||
tNode_get_byKey_asFloat => tNode_get_byKey_asFloat
|
tNode_get_byKey_asFloat => tNode_get_byKey_asFloat
|
||||||
procedure :: &
|
procedure :: &
|
||||||
tNode_get_byKey_asFloats => tNode_get_byKey_asFloats
|
tNode_get_byKey_as1dFloat => tNode_get_byKey_as1dFloat
|
||||||
procedure :: &
|
procedure :: &
|
||||||
tNode_get_byKey_asInt => tNode_get_byKey_asInt
|
tNode_get_byKey_asInt => tNode_get_byKey_asInt
|
||||||
procedure :: &
|
procedure :: &
|
||||||
tNode_get_byKey_asInts => tNode_get_byKey_asInts
|
tNode_get_byKey_as1dInt => tNode_get_byKey_as1dInt
|
||||||
procedure :: &
|
procedure :: &
|
||||||
tNode_get_byKey_asBool => tNode_get_byKey_asBool
|
tNode_get_byKey_asBool => tNode_get_byKey_asBool
|
||||||
procedure :: &
|
procedure :: &
|
||||||
tNode_get_byKey_asBools => tNode_get_byKey_asBools
|
tNode_get_byKey_as1dBool => tNode_get_byKey_as1dBool
|
||||||
procedure :: &
|
procedure :: &
|
||||||
tNode_get_byKey_asString => tNode_get_byKey_asString
|
tNode_get_byKey_asString => tNode_get_byKey_asString
|
||||||
procedure :: &
|
procedure :: &
|
||||||
tNode_get_byKey_asStrings => tNode_get_byKey_asStrings
|
tNode_get_byKey_as1dString => tNode_get_byKey_as1dString
|
||||||
procedure :: &
|
procedure :: &
|
||||||
getKey => tNode_get_byIndex_asKey
|
getKey => tNode_get_byIndex_asKey
|
||||||
procedure :: &
|
procedure :: &
|
||||||
getIndex => tNode_get_byKey_asIndex
|
getIndex => tNode_get_byKey_asIndex
|
||||||
procedure :: &
|
procedure :: &
|
||||||
contains => tNode_contains
|
contains => tNode_contains
|
||||||
|
procedure :: &
|
||||||
|
get_as2dFloat => tNode_get_byKey_as2dFloat
|
||||||
|
|
||||||
generic :: &
|
generic :: &
|
||||||
get => tNode_get_byIndex, &
|
get => tNode_get_byIndex, &
|
||||||
|
@ -74,26 +76,26 @@ module YAML_types
|
||||||
get_asFloat => tNode_get_byIndex_asFloat, &
|
get_asFloat => tNode_get_byIndex_asFloat, &
|
||||||
tNode_get_byKey_asFloat
|
tNode_get_byKey_asFloat
|
||||||
generic :: &
|
generic :: &
|
||||||
get_asFloats => tNode_get_byIndex_asFloats, &
|
get_as1dFloat => tNode_get_byIndex_as1dFloat, &
|
||||||
tNode_get_byKey_asFloats
|
tNode_get_byKey_as1dFloat
|
||||||
generic :: &
|
generic :: &
|
||||||
get_asInt => tNode_get_byIndex_asInt, &
|
get_asInt => tNode_get_byIndex_asInt, &
|
||||||
tNode_get_byKey_asInt
|
tNode_get_byKey_asInt
|
||||||
generic :: &
|
generic :: &
|
||||||
get_asInts => tNode_get_byIndex_asInts, &
|
get_as1dInt => tNode_get_byIndex_as1dInt, &
|
||||||
tNode_get_byKey_asInts
|
tNode_get_byKey_as1dInt
|
||||||
generic :: &
|
generic :: &
|
||||||
get_asBool => tNode_get_byIndex_asBool, &
|
get_asBool => tNode_get_byIndex_asBool, &
|
||||||
tNode_get_byKey_asBool
|
tNode_get_byKey_asBool
|
||||||
generic :: &
|
generic :: &
|
||||||
get_asBools => tNode_get_byIndex_asBools, &
|
get_as1dBool => tNode_get_byIndex_as1dBool, &
|
||||||
tNode_get_byKey_asBools
|
tNode_get_byKey_as1dBool
|
||||||
generic :: &
|
generic :: &
|
||||||
get_asString => tNode_get_byIndex_asString, &
|
get_asString => tNode_get_byIndex_asString, &
|
||||||
tNode_get_byKey_asString
|
tNode_get_byKey_asString
|
||||||
generic :: &
|
generic :: &
|
||||||
get_asStrings => tNode_get_byIndex_asStrings, &
|
get_as1dString => tNode_get_byIndex_as1dString, &
|
||||||
tNode_get_byKey_asStrings
|
tNode_get_byKey_as1dString
|
||||||
end type tNode
|
end type tNode
|
||||||
|
|
||||||
|
|
||||||
|
@ -121,13 +123,15 @@ module YAML_types
|
||||||
procedure :: asFormattedString => tList_asFormattedString
|
procedure :: asFormattedString => tList_asFormattedString
|
||||||
procedure :: append => tList_append
|
procedure :: append => tList_append
|
||||||
procedure :: &
|
procedure :: &
|
||||||
asFloats => tList_asFloats
|
as1dFloat => tList_as1dFloat
|
||||||
procedure :: &
|
procedure :: &
|
||||||
asInts => tList_asInts
|
as2dFloat => tList_as2dFloat
|
||||||
procedure :: &
|
procedure :: &
|
||||||
asBools => tList_asBools
|
as1dInt => tList_as1dInt
|
||||||
procedure :: &
|
procedure :: &
|
||||||
asStrings => tList_asStrings
|
as1dBool => tList_as1dBool
|
||||||
|
procedure :: &
|
||||||
|
as1dString => tList_as1dString
|
||||||
final :: tList_finalize
|
final :: tList_finalize
|
||||||
end type tList
|
end type tList
|
||||||
|
|
||||||
|
@ -173,7 +177,7 @@ module YAML_types
|
||||||
|
|
||||||
public :: &
|
public :: &
|
||||||
YAML_types_init, &
|
YAML_types_init, &
|
||||||
output_asStrings, & !ToDo: Hack for GNU. Remove later
|
output_as1dString, & !ToDo: Hack for GNU. Remove later
|
||||||
assignment(=)
|
assignment(=)
|
||||||
|
|
||||||
contains
|
contains
|
||||||
|
@ -195,9 +199,11 @@ end subroutine YAML_types_init
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine selfTest
|
subroutine selfTest
|
||||||
|
|
||||||
class(tNode), pointer :: s1,s2
|
class(tNode), pointer :: s1,s2,s3,s4
|
||||||
allocate(tScalar::s1)
|
allocate(tScalar::s1)
|
||||||
allocate(tScalar::s2)
|
allocate(tScalar::s2)
|
||||||
|
allocate(tScalar::s3)
|
||||||
|
allocate(tScalar::s4)
|
||||||
select type(s1)
|
select type(s1)
|
||||||
class is(tScalar)
|
class is(tScalar)
|
||||||
s1 = '1'
|
s1 = '1'
|
||||||
|
@ -209,7 +215,9 @@ subroutine selfTest
|
||||||
end select
|
end select
|
||||||
|
|
||||||
block
|
block
|
||||||
class(tNode), pointer :: l1, l2, n
|
class(tNode), pointer :: l1, l2, l3, n
|
||||||
|
real(pReal), allocatable, dimension(:,:) :: x
|
||||||
|
|
||||||
select type(s1)
|
select type(s1)
|
||||||
class is(tScalar)
|
class is(tScalar)
|
||||||
s1 = '2'
|
s1 = '2'
|
||||||
|
@ -220,24 +228,47 @@ subroutine selfTest
|
||||||
s2 = '3'
|
s2 = '3'
|
||||||
endselect
|
endselect
|
||||||
|
|
||||||
|
select type(s3)
|
||||||
|
class is(tScalar)
|
||||||
|
s3 = '4'
|
||||||
|
endselect
|
||||||
|
|
||||||
|
select type(s4)
|
||||||
|
class is(tScalar)
|
||||||
|
s4 = '5'
|
||||||
|
endselect
|
||||||
|
|
||||||
|
|
||||||
allocate(tList::l1)
|
allocate(tList::l1)
|
||||||
select type(l1)
|
select type(l1)
|
||||||
class is(tList)
|
class is(tList)
|
||||||
call l1%append(s1)
|
call l1%append(s1)
|
||||||
call l1%append(s2)
|
call l1%append(s2)
|
||||||
n => l1
|
n => l1
|
||||||
if (any(l1%asInts() /= [2,3])) error stop 'tList_asInts'
|
if (any(l1%as1dInt() /= [2,3])) error stop 'tList_as1dInt'
|
||||||
if (any(dNeq(l1%asFloats(),[2.0_pReal,3.0_pReal]))) error stop 'tList_asFloats'
|
if (any(dNeq(l1%as1dFloat(),[2.0_pReal,3.0_pReal]))) error stop 'tList_as1dFloat'
|
||||||
if (n%get_asInt(1) /= 2) error stop 'byIndex_asInt'
|
if (n%get_asInt(1) /= 2) error stop 'byIndex_asInt'
|
||||||
if (dNeq(n%get_asFloat(2),3.0_pReal)) error stop 'byIndex_asFloat'
|
if (dNeq(n%get_asFloat(2),3.0_pReal)) error stop 'byIndex_asFloat'
|
||||||
endselect
|
endselect
|
||||||
|
|
||||||
|
allocate(tList::l3)
|
||||||
|
select type(l3)
|
||||||
|
class is(tList)
|
||||||
|
call l3%append(s3)
|
||||||
|
call l3%append(s4)
|
||||||
|
endselect
|
||||||
|
|
||||||
allocate(tList::l2)
|
allocate(tList::l2)
|
||||||
select type(l2)
|
select type(l2)
|
||||||
class is(tList)
|
class is(tList)
|
||||||
call l2%append(l1)
|
call l2%append(l1)
|
||||||
if (any(l2%get_asInts(1) /= [2,3])) error stop 'byIndex_asInts'
|
if(any(l2%get_as1dInt(1) /= [2,3])) error stop 'byIndex_as1dInt'
|
||||||
if (any(dNeq(l2%get_asFloats(1),[2.0_pReal,3.0_pReal]))) error stop 'byIndex_asFloats'
|
if(any(dNeq(l2%get_as1dFloat(1),[2.0_pReal,3.0_pReal]))) error stop 'byIndex_as1dFloat'
|
||||||
|
call l2%append(l3)
|
||||||
|
x = l2%as2dFloat()
|
||||||
|
if(x(2,1)/= 4.0_pReal) error stop 'byKey_as2dFloat'
|
||||||
|
if(any(dNeq(pack(l2%as2dFloat(),.true.),&
|
||||||
|
[2.0_pReal,4.0_pReal,3.0_pReal,5.0_pReal]))) error stop 'byKey_as2dFloat'
|
||||||
n => l2
|
n => l2
|
||||||
end select
|
end select
|
||||||
deallocate(n)
|
deallocate(n)
|
||||||
|
@ -259,8 +290,8 @@ subroutine selfTest
|
||||||
call l1%append(s2)
|
call l1%append(s2)
|
||||||
n => l1
|
n => l1
|
||||||
|
|
||||||
if (any(l1%asBools() .neqv. [.true., .false.])) error stop 'tList_asBools'
|
if (any(l1%as1dBool() .neqv. [.true., .false.])) error stop 'tList_as1dBool'
|
||||||
if (any(l1%asStrings() /= ['true ','False'])) error stop 'tList_asStrings'
|
if (any(l1%as1dString() /= ['true ','False'])) error stop 'tList_as1dString'
|
||||||
if (n%get_asBool(2)) error stop 'byIndex_asBool'
|
if (n%get_asBool(2)) error stop 'byIndex_asBool'
|
||||||
if (n%get_asString(1) /= 'true') error stop 'byIndex_asString'
|
if (n%get_asString(1) /= 'true') error stop 'byIndex_asString'
|
||||||
end block
|
end block
|
||||||
|
@ -470,13 +501,13 @@ end function tNode_get_byIndex_asString
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief Access by index and convert to float array
|
!> @brief Access by index and convert to float array (1D)
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
function tNode_get_byIndex_asFloats(self,i) result(nodeAsFloats)
|
function tNode_get_byIndex_as1dFloat(self,i) result(nodeAs1dFloat)
|
||||||
|
|
||||||
class(tNode), intent(in), target :: self
|
class(tNode), intent(in), target :: self
|
||||||
integer, intent(in) :: i
|
integer, intent(in) :: i
|
||||||
real(pReal), dimension(:), allocatable :: nodeAsFloats
|
real(pReal), dimension(:), allocatable :: nodeAs1dFloat
|
||||||
|
|
||||||
class(tNode), pointer :: node
|
class(tNode), pointer :: node
|
||||||
class(tList), pointer :: list
|
class(tList), pointer :: list
|
||||||
|
@ -485,22 +516,22 @@ function tNode_get_byIndex_asFloats(self,i) result(nodeAsFloats)
|
||||||
select type(node)
|
select type(node)
|
||||||
class is(tList)
|
class is(tList)
|
||||||
list => node%asList()
|
list => node%asList()
|
||||||
nodeAsFloats = list%asFloats()
|
nodeAs1dFloat = list%as1dFloat()
|
||||||
class default
|
class default
|
||||||
call IO_error(706,ext_msg='Expected list')
|
call IO_error(706,ext_msg='Expected list')
|
||||||
endselect
|
endselect
|
||||||
|
|
||||||
end function tNode_get_byIndex_asFloats
|
end function tNode_get_byIndex_as1dFloat
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief Access by index and convert to int array
|
!> @brief Access by index and convert to int array (1D)
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
function tNode_get_byIndex_asInts(self,i) result(nodeAsInts)
|
function tNode_get_byIndex_as1dInt(self,i) result(nodeAs1dInt)
|
||||||
|
|
||||||
class(tNode), intent(in), target :: self
|
class(tNode), intent(in), target :: self
|
||||||
integer, intent(in) :: i
|
integer, intent(in) :: i
|
||||||
integer, dimension(:), allocatable :: nodeAsInts
|
integer, dimension(:), allocatable :: nodeAs1dInt
|
||||||
|
|
||||||
class(tNode), pointer :: node
|
class(tNode), pointer :: node
|
||||||
class(tList), pointer :: list
|
class(tList), pointer :: list
|
||||||
|
@ -509,22 +540,22 @@ function tNode_get_byIndex_asInts(self,i) result(nodeAsInts)
|
||||||
select type(node)
|
select type(node)
|
||||||
class is(tList)
|
class is(tList)
|
||||||
list => node%asList()
|
list => node%asList()
|
||||||
nodeAsInts = list%asInts()
|
nodeAs1dInt = list%as1dInt()
|
||||||
class default
|
class default
|
||||||
call IO_error(706,ext_msg='Expected list')
|
call IO_error(706,ext_msg='Expected list')
|
||||||
endselect
|
endselect
|
||||||
|
|
||||||
end function tNode_get_byIndex_asInts
|
end function tNode_get_byIndex_as1dInt
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief Access by index and convert to bool array
|
!> @brief Access by index and convert to bool array (1D)
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
function tNode_get_byIndex_asBools(self,i) result(nodeAsBools)
|
function tNode_get_byIndex_as1dBool(self,i) result(nodeAs1dBool)
|
||||||
|
|
||||||
class(tNode), intent(in), target :: self
|
class(tNode), intent(in), target :: self
|
||||||
integer, intent(in) :: i
|
integer, intent(in) :: i
|
||||||
logical, dimension(:), allocatable :: nodeAsBools
|
logical, dimension(:), allocatable :: nodeAs1dBool
|
||||||
|
|
||||||
class(tNode), pointer :: node
|
class(tNode), pointer :: node
|
||||||
class(tList), pointer :: list
|
class(tList), pointer :: list
|
||||||
|
@ -533,22 +564,22 @@ function tNode_get_byIndex_asBools(self,i) result(nodeAsBools)
|
||||||
select type(node)
|
select type(node)
|
||||||
class is(tList)
|
class is(tList)
|
||||||
list => node%asList()
|
list => node%asList()
|
||||||
nodeAsBools = list%asBools()
|
nodeAs1dBool = list%as1dBool()
|
||||||
class default
|
class default
|
||||||
call IO_error(706,ext_msg='Expected list')
|
call IO_error(706,ext_msg='Expected list')
|
||||||
endselect
|
endselect
|
||||||
|
|
||||||
end function tNode_get_byIndex_asBools
|
end function tNode_get_byIndex_as1dBool
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief Access by index and convert to string array
|
!> @brief Access by index and convert to string array (1D)
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
function tNode_get_byIndex_asStrings(self,i) result(nodeAsStrings)
|
function tNode_get_byIndex_as1dString(self,i) result(nodeAs1dString)
|
||||||
|
|
||||||
class(tNode), intent(in), target :: self
|
class(tNode), intent(in), target :: self
|
||||||
integer, intent(in) :: i
|
integer, intent(in) :: i
|
||||||
character(len=:), allocatable, dimension(:) :: nodeAsStrings
|
character(len=:), allocatable, dimension(:) :: nodeAs1dString
|
||||||
|
|
||||||
class(tNode), pointer :: node
|
class(tNode), pointer :: node
|
||||||
type(tList), pointer :: list
|
type(tList), pointer :: list
|
||||||
|
@ -557,12 +588,12 @@ function tNode_get_byIndex_asStrings(self,i) result(nodeAsStrings)
|
||||||
select type(node)
|
select type(node)
|
||||||
class is(tList)
|
class is(tList)
|
||||||
list => node%asList()
|
list => node%asList()
|
||||||
nodeAsStrings = list%asStrings()
|
nodeAs1dString = list%as1dString()
|
||||||
class default
|
class default
|
||||||
call IO_error(706,ext_msg='Expected list')
|
call IO_error(706,ext_msg='Expected list')
|
||||||
endselect
|
endselect
|
||||||
|
|
||||||
end function tNode_get_byIndex_asStrings
|
end function tNode_get_byIndex_as1dString
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
@ -803,16 +834,16 @@ end function tNode_get_byKey_asString
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief Access by key and convert to float array
|
!> @brief Access by key and convert to float array (1D)
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
function tNode_get_byKey_asFloats(self,k,defaultVal,requiredSize) result(nodeAsFloats)
|
function tNode_get_byKey_as1dFloat(self,k,defaultVal,requiredSize) result(nodeAs1dFloat)
|
||||||
|
|
||||||
class(tNode), intent(in), target :: self
|
class(tNode), intent(in), target :: self
|
||||||
character(len=*), intent(in) :: k
|
character(len=*), intent(in) :: k
|
||||||
real(pReal), intent(in), dimension(:), optional :: defaultVal
|
real(pReal), intent(in), dimension(:), optional :: defaultVal
|
||||||
integer, intent(in), optional :: requiredSize
|
integer, intent(in), optional :: requiredSize
|
||||||
|
|
||||||
real(pReal), dimension(:), allocatable :: nodeAsFloats
|
real(pReal), dimension(:), allocatable :: nodeAs1dFloat
|
||||||
|
|
||||||
class(tNode), pointer :: node
|
class(tNode), pointer :: node
|
||||||
type(tList), pointer :: list
|
type(tList), pointer :: list
|
||||||
|
@ -822,33 +853,65 @@ function tNode_get_byKey_asFloats(self,k,defaultVal,requiredSize) result(nodeAsF
|
||||||
select type(self)
|
select type(self)
|
||||||
class is(tList)
|
class is(tList)
|
||||||
list => node%asList()
|
list => node%asList()
|
||||||
nodeAsFloats = list%asFloats()
|
nodeAs1dFloat = list%as1dFloat()
|
||||||
class default
|
class default
|
||||||
call IO_error(706,ext_msg='Expected list for key '//k)
|
call IO_error(706,ext_msg='Expected 1D list for key '//k)
|
||||||
endselect
|
endselect
|
||||||
elseif (present(defaultVal)) then
|
elseif (present(defaultVal)) then
|
||||||
nodeAsFloats = defaultVal
|
nodeAs1dFloat = defaultVal
|
||||||
else
|
else
|
||||||
call IO_error(143,ext_msg=k)
|
call IO_error(143,ext_msg=k)
|
||||||
endif
|
endif
|
||||||
|
|
||||||
if (present(requiredSize)) then
|
if (present(requiredSize)) then
|
||||||
if (requiredSize /= size(nodeAsFloats)) call IO_error(146,ext_msg=k)
|
if (requiredSize /= size(nodeAs1dFloat)) call IO_error(146,ext_msg=k)
|
||||||
endif
|
endif
|
||||||
|
|
||||||
end function tNode_get_byKey_asFloats
|
end function tNode_get_byKey_as1dFloat
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief Access by key and convert to int array
|
!> @brief Access by key and convert to float array (2D)
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
function tNode_get_byKey_asInts(self,k,defaultVal,requiredSize) result(nodeAsInts)
|
function tNode_get_byKey_as2dFloat(self,k,defaultVal) result(nodeAs2dFloat)
|
||||||
|
|
||||||
|
class(tNode), intent(in), target :: self
|
||||||
|
character(len=*), intent(in) :: k
|
||||||
|
real(pReal), intent(in), dimension(:,:), optional :: defaultVal
|
||||||
|
|
||||||
|
real(pReal), dimension(:,:), allocatable :: nodeAs2dFloat
|
||||||
|
|
||||||
|
class(tNode), pointer :: node
|
||||||
|
type(tList), pointer :: rows
|
||||||
|
|
||||||
|
if(self%contains(k)) then
|
||||||
|
node => self%get(k)
|
||||||
|
select type(node)
|
||||||
|
class is(tList)
|
||||||
|
rows => node%asList()
|
||||||
|
nodeAs2dFloat = rows%as2dFloat()
|
||||||
|
class default
|
||||||
|
call IO_error(706,ext_msg='Expected 2D list for key '//k)
|
||||||
|
endselect
|
||||||
|
elseif(present(defaultVal)) then
|
||||||
|
nodeAs2dFloat = defaultVal
|
||||||
|
else
|
||||||
|
call IO_error(143,ext_msg=k)
|
||||||
|
endif
|
||||||
|
|
||||||
|
end function tNode_get_byKey_as2dFloat
|
||||||
|
|
||||||
|
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
!> @brief Access by key and convert to int array (1D)
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
function tNode_get_byKey_as1dInt(self,k,defaultVal,requiredSize) result(nodeAs1dInt)
|
||||||
|
|
||||||
class(tNode), intent(in), target :: self
|
class(tNode), intent(in), target :: self
|
||||||
character(len=*), intent(in) :: k
|
character(len=*), intent(in) :: k
|
||||||
integer, dimension(:), intent(in), optional :: defaultVal
|
integer, dimension(:), intent(in), optional :: defaultVal
|
||||||
integer, intent(in), optional :: requiredSize
|
integer, intent(in), optional :: requiredSize
|
||||||
integer, dimension(:), allocatable :: nodeAsInts
|
integer, dimension(:), allocatable :: nodeAs1dInt
|
||||||
|
|
||||||
class(tNode), pointer :: node
|
class(tNode), pointer :: node
|
||||||
type(tList), pointer :: list
|
type(tList), pointer :: list
|
||||||
|
@ -858,32 +921,32 @@ function tNode_get_byKey_asInts(self,k,defaultVal,requiredSize) result(nodeAsInt
|
||||||
select type(node)
|
select type(node)
|
||||||
class is(tList)
|
class is(tList)
|
||||||
list => node%asList()
|
list => node%asList()
|
||||||
nodeAsInts = list%asInts()
|
nodeAs1dInt = list%as1dInt()
|
||||||
class default
|
class default
|
||||||
call IO_error(706,ext_msg='Expected list for key '//k)
|
call IO_error(706,ext_msg='Expected list for key '//k)
|
||||||
endselect
|
endselect
|
||||||
elseif (present(defaultVal)) then
|
elseif (present(defaultVal)) then
|
||||||
nodeAsInts = defaultVal
|
nodeAs1dInt = defaultVal
|
||||||
else
|
else
|
||||||
call IO_error(143,ext_msg=k)
|
call IO_error(143,ext_msg=k)
|
||||||
endif
|
endif
|
||||||
|
|
||||||
if (present(requiredSize)) then
|
if (present(requiredSize)) then
|
||||||
if (requiredSize /= size(nodeAsInts)) call IO_error(146,ext_msg=k)
|
if (requiredSize /= size(nodeAs1dInt)) call IO_error(146,ext_msg=k)
|
||||||
endif
|
endif
|
||||||
|
|
||||||
end function tNode_get_byKey_asInts
|
end function tNode_get_byKey_as1dInt
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief Access by key and convert to bool array
|
!> @brief Access by key and convert to bool array (1D)
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
function tNode_get_byKey_asBools(self,k,defaultVal) result(nodeAsBools)
|
function tNode_get_byKey_as1dBool(self,k,defaultVal) result(nodeAs1dBool)
|
||||||
|
|
||||||
class(tNode), intent(in), target :: self
|
class(tNode), intent(in), target :: self
|
||||||
character(len=*), intent(in) :: k
|
character(len=*), intent(in) :: k
|
||||||
logical, dimension(:), intent(in), optional :: defaultVal
|
logical, dimension(:), intent(in), optional :: defaultVal
|
||||||
logical, dimension(:), allocatable :: nodeAsBools
|
logical, dimension(:), allocatable :: nodeAs1dBool
|
||||||
|
|
||||||
class(tNode), pointer :: node
|
class(tNode), pointer :: node
|
||||||
type(tList), pointer :: list
|
type(tList), pointer :: list
|
||||||
|
@ -893,28 +956,28 @@ function tNode_get_byKey_asBools(self,k,defaultVal) result(nodeAsBools)
|
||||||
select type(node)
|
select type(node)
|
||||||
class is(tList)
|
class is(tList)
|
||||||
list => node%asList()
|
list => node%asList()
|
||||||
nodeAsBools = list%asBools()
|
nodeAs1dBool = list%as1dBool()
|
||||||
class default
|
class default
|
||||||
call IO_error(706,ext_msg='Expected list for key '//k)
|
call IO_error(706,ext_msg='Expected list for key '//k)
|
||||||
endselect
|
endselect
|
||||||
elseif (present(defaultVal)) then
|
elseif (present(defaultVal)) then
|
||||||
nodeAsBools = defaultVal
|
nodeAs1dBool = defaultVal
|
||||||
else
|
else
|
||||||
call IO_error(143,ext_msg=k)
|
call IO_error(143,ext_msg=k)
|
||||||
endif
|
endif
|
||||||
|
|
||||||
end function tNode_get_byKey_asBools
|
end function tNode_get_byKey_as1dBool
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief Access by key and convert to string array
|
!> @brief Access by key and convert to string array (1D)
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
function tNode_get_byKey_asStrings(self,k,defaultVal) result(nodeAsStrings)
|
function tNode_get_byKey_as1dString(self,k,defaultVal) result(nodeAs1dString)
|
||||||
|
|
||||||
class(tNode), intent(in), target :: self
|
class(tNode), intent(in), target :: self
|
||||||
character(len=*), intent(in) :: k
|
character(len=*), intent(in) :: k
|
||||||
character(len=*), intent(in), dimension(:), optional :: defaultVal
|
character(len=*), intent(in), dimension(:), optional :: defaultVal
|
||||||
character(len=:), allocatable, dimension(:) :: nodeAsStrings
|
character(len=:), allocatable, dimension(:) :: nodeAs1dString
|
||||||
|
|
||||||
class(tNode), pointer :: node
|
class(tNode), pointer :: node
|
||||||
type(tList), pointer :: list
|
type(tList), pointer :: list
|
||||||
|
@ -924,23 +987,23 @@ function tNode_get_byKey_asStrings(self,k,defaultVal) result(nodeAsStrings)
|
||||||
select type(node)
|
select type(node)
|
||||||
class is(tList)
|
class is(tList)
|
||||||
list => node%asList()
|
list => node%asList()
|
||||||
nodeAsStrings = list%asStrings()
|
nodeAs1dString = list%as1dString()
|
||||||
class default
|
class default
|
||||||
call IO_error(706,ext_msg='Expected list for key '//k)
|
call IO_error(706,ext_msg='Expected list for key '//k)
|
||||||
endselect
|
endselect
|
||||||
elseif (present(defaultVal)) then
|
elseif (present(defaultVal)) then
|
||||||
nodeAsStrings = defaultVal
|
nodeAs1dString = defaultVal
|
||||||
else
|
else
|
||||||
call IO_error(143,ext_msg=k)
|
call IO_error(143,ext_msg=k)
|
||||||
endif
|
endif
|
||||||
|
|
||||||
end function tNode_get_byKey_asStrings
|
end function tNode_get_byKey_as1dString
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief Returns string output array (hack for GNU)
|
!> @brief Returns string output array (1D) (hack for GNU)
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
function output_asStrings(self) result(output) !ToDo: SR: Remove whenever GNU works
|
function output_as1dString(self) result(output) !ToDo: SR: Remove whenever GNU works
|
||||||
|
|
||||||
class(tNode), pointer,intent(in) :: self
|
class(tNode), pointer,intent(in) :: self
|
||||||
character(len=pStringLen), allocatable, dimension(:) :: output
|
character(len=pStringLen), allocatable, dimension(:) :: output
|
||||||
|
@ -954,7 +1017,7 @@ function output_asStrings(self) result(output) !ToDo: SR: Rem
|
||||||
output(o) = output_list%get_asString(o)
|
output(o) = output_list%get_asString(o)
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
end function output_asStrings
|
end function output_as1dString
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
@ -1112,81 +1175,107 @@ end function tScalar_asString
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief Convert to float array
|
!> @brief Convert to float array (1D)
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
function tList_asFloats(self)
|
function tList_as1dFloat(self)
|
||||||
|
|
||||||
class(tList), intent(in), target :: self
|
class(tList), intent(in), target :: self
|
||||||
real(pReal), dimension(:), allocatable :: tList_asFloats
|
real(pReal), dimension(:), allocatable :: tList_as1dFloat
|
||||||
|
|
||||||
integer :: i
|
integer :: i
|
||||||
type(tItem), pointer :: item
|
type(tItem), pointer :: item
|
||||||
type(tScalar), pointer :: scalar
|
type(tScalar), pointer :: scalar
|
||||||
|
|
||||||
allocate(tList_asFloats(self%length))
|
allocate(tList_as1dFloat(self%length))
|
||||||
item => self%first
|
item => self%first
|
||||||
do i = 1, self%length
|
do i = 1, self%length
|
||||||
scalar => item%node%asScalar()
|
scalar => item%node%asScalar()
|
||||||
tList_asFloats(i) = scalar%asFloat()
|
tList_as1dFloat(i) = scalar%asFloat()
|
||||||
item => item%next
|
item => item%next
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
end function tList_asFloats
|
end function tList_as1dFloat
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief Convert to int array
|
!> @brief Convert to float array (2D)
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
function tList_asInts(self)
|
function tList_as2dFloat(self)
|
||||||
|
|
||||||
class(tList), intent(in), target :: self
|
class(tList), intent(in), target :: self
|
||||||
integer, dimension(:), allocatable :: tList_asInts
|
real(pReal), dimension(:,:), allocatable :: tList_as2dFloat
|
||||||
|
|
||||||
|
integer :: i
|
||||||
|
class(tNode), pointer :: row
|
||||||
|
type(tList), pointer :: row_data
|
||||||
|
|
||||||
|
row => self%get(1)
|
||||||
|
row_data => row%asList()
|
||||||
|
allocate(tList_as2dFloat(self%length,row_data%length))
|
||||||
|
|
||||||
|
do i=1,self%length
|
||||||
|
row => self%get(i)
|
||||||
|
row_data => row%asList()
|
||||||
|
if(row_data%length /= size(tList_as2dFloat,2)) call IO_error(709,ext_msg='Varying number of columns')
|
||||||
|
tList_as2dFloat(i,:) = self%get_as1dFloat(i)
|
||||||
|
enddo
|
||||||
|
|
||||||
|
end function tList_as2dFloat
|
||||||
|
|
||||||
|
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
!> @brief Convert to int array (1D)
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
function tList_as1dInt(self)
|
||||||
|
|
||||||
|
class(tList), intent(in), target :: self
|
||||||
|
integer, dimension(:), allocatable :: tList_as1dInt
|
||||||
|
|
||||||
integer :: i
|
integer :: i
|
||||||
type(tItem), pointer :: item
|
type(tItem), pointer :: item
|
||||||
type(tScalar), pointer :: scalar
|
type(tScalar), pointer :: scalar
|
||||||
|
|
||||||
allocate(tList_asInts(self%length))
|
allocate(tList_as1dInt(self%length))
|
||||||
item => self%first
|
item => self%first
|
||||||
do i = 1, self%length
|
do i = 1, self%length
|
||||||
scalar => item%node%asScalar()
|
scalar => item%node%asScalar()
|
||||||
tList_asInts(i) = scalar%asInt()
|
tList_as1dInt(i) = scalar%asInt()
|
||||||
item => item%next
|
item => item%next
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
end function tList_asInts
|
end function tList_as1dInt
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief Convert to bool array
|
!> @brief Convert to bool array (1D)
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
function tList_asBools(self)
|
function tList_as1dBool(self)
|
||||||
|
|
||||||
class(tList), intent(in), target :: self
|
class(tList), intent(in), target :: self
|
||||||
logical, dimension(:), allocatable :: tList_asBools
|
logical, dimension(:), allocatable :: tList_as1dBool
|
||||||
|
|
||||||
integer :: i
|
integer :: i
|
||||||
type(tItem), pointer :: item
|
type(tItem), pointer :: item
|
||||||
type(tScalar), pointer :: scalar
|
type(tScalar), pointer :: scalar
|
||||||
|
|
||||||
allocate(tList_asBools(self%length))
|
allocate(tList_as1dBool(self%length))
|
||||||
item => self%first
|
item => self%first
|
||||||
do i = 1, self%length
|
do i = 1, self%length
|
||||||
scalar => item%node%asScalar()
|
scalar => item%node%asScalar()
|
||||||
tList_asBools(i) = scalar%asBool()
|
tList_as1dBool(i) = scalar%asBool()
|
||||||
item => item%next
|
item => item%next
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
end function tList_asBools
|
end function tList_as1dBool
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief Convert to string array
|
!> @brief Convert to string array (1D)
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
function tList_asStrings(self)
|
function tList_as1dString(self)
|
||||||
|
|
||||||
class(tList), intent(in), target :: self
|
class(tList), intent(in), target :: self
|
||||||
character(len=:), allocatable, dimension(:) :: tList_asStrings
|
character(len=:), allocatable, dimension(:) :: tList_as1dString
|
||||||
|
|
||||||
integer :: i,len_max
|
integer :: i,len_max
|
||||||
type(tItem), pointer :: item
|
type(tItem), pointer :: item
|
||||||
|
@ -1200,15 +1289,15 @@ function tList_asStrings(self)
|
||||||
item => item%next
|
item => item%next
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
allocate(character(len=len_max) :: tList_asStrings(self%length))
|
allocate(character(len=len_max) :: tList_as1dString(self%length))
|
||||||
item => self%first
|
item => self%first
|
||||||
do i = 1, self%length
|
do i = 1, self%length
|
||||||
scalar => item%node%asScalar()
|
scalar => item%node%asScalar()
|
||||||
tList_asStrings(i) = scalar%asString()
|
tList_as1dString(i) = scalar%asString()
|
||||||
item => item%next
|
item => item%next
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
end function tList_asStrings
|
end function tList_as1dString
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
|
|
@ -219,7 +219,7 @@ program DAMASK_grid
|
||||||
loadCases(l)%stress%mask = transpose(reshape(temp_maskVector,[3,3]))
|
loadCases(l)%stress%mask = transpose(reshape(temp_maskVector,[3,3]))
|
||||||
loadCases(l)%stress%values = math_9to33(temp_valueVector)
|
loadCases(l)%stress%values = math_9to33(temp_valueVector)
|
||||||
end select
|
end select
|
||||||
call loadCases(l)%rot%fromAxisAngle(step_mech%get_asFloats('R',defaultVal = real([0.0,0.0,1.0,0.0],pReal)),degrees=.true.)
|
call loadCases(l)%rot%fromAxisAngle(step_mech%get_as1dFloat('R',defaultVal = real([0.0,0.0,1.0,0.0],pReal)),degrees=.true.)
|
||||||
enddo readMech
|
enddo readMech
|
||||||
if (.not. allocated(loadCases(l)%deformation%myType)) call IO_error(error_ID=837,ext_msg = 'L/dot_F/F missing')
|
if (.not. allocated(loadCases(l)%deformation%myType)) call IO_error(error_ID=837,ext_msg = 'L/dot_F/F missing')
|
||||||
|
|
||||||
|
|
|
@ -48,9 +48,9 @@ module subroutine damage_init()
|
||||||
if (configHomogenization%contains('damage')) then
|
if (configHomogenization%contains('damage')) then
|
||||||
configHomogenizationDamage => configHomogenization%get('damage')
|
configHomogenizationDamage => configHomogenization%get('damage')
|
||||||
#if defined (__GFORTRAN__)
|
#if defined (__GFORTRAN__)
|
||||||
prm%output = output_asStrings(configHomogenizationDamage)
|
prm%output = output_as1dString(configHomogenizationDamage)
|
||||||
#else
|
#else
|
||||||
prm%output = configHomogenizationDamage%get_asStrings('output',defaultVal=emptyStringArray)
|
prm%output = configHomogenizationDamage%get_as1dString('output',defaultVal=emptyStringArray)
|
||||||
#endif
|
#endif
|
||||||
else
|
else
|
||||||
prm%output = emptyStringArray
|
prm%output = emptyStringArray
|
||||||
|
|
|
@ -145,20 +145,20 @@ module subroutine mechanical_RGC_init(num_homogMech)
|
||||||
dst => dependentState(ho))
|
dst => dependentState(ho))
|
||||||
|
|
||||||
#if defined (__GFORTRAN__)
|
#if defined (__GFORTRAN__)
|
||||||
prm%output = output_asStrings(homogMech)
|
prm%output = output_as1dString(homogMech)
|
||||||
#else
|
#else
|
||||||
prm%output = homogMech%get_asStrings('output',defaultVal=emptyStringArray)
|
prm%output = homogMech%get_as1dString('output',defaultVal=emptyStringArray)
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
prm%N_constituents = homogMech%get_asInts('cluster_size',requiredSize=3)
|
prm%N_constituents = homogMech%get_as1dInt('cluster_size',requiredSize=3)
|
||||||
if (homogenization_Nconstituents(ho) /= product(prm%N_constituents)) &
|
if (homogenization_Nconstituents(ho) /= product(prm%N_constituents)) &
|
||||||
call IO_error(211,ext_msg='N_constituents (mechanical_RGC)')
|
call IO_error(211,ext_msg='N_constituents (mechanical_RGC)')
|
||||||
|
|
||||||
prm%xi_alpha = homogMech%get_asFloat('xi_alpha')
|
prm%xi_alpha = homogMech%get_asFloat('xi_alpha')
|
||||||
prm%c_alpha = homogMech%get_asFloat('c_alpha')
|
prm%c_alpha = homogMech%get_asFloat('c_alpha')
|
||||||
|
|
||||||
prm%D_alpha = homogMech%get_asFloats('D_alpha', requiredSize=3)
|
prm%D_alpha = homogMech%get_as1dFloat('D_alpha', requiredSize=3)
|
||||||
prm%a_g = homogMech%get_asFloats('a_g', requiredSize=3)
|
prm%a_g = homogMech%get_as1dFloat('a_g', requiredSize=3)
|
||||||
|
|
||||||
Nmaterialpoints = count(material_homogenizationAt == ho)
|
Nmaterialpoints = count(material_homogenizationAt == ho)
|
||||||
nIntFaceTot = 3*( (prm%N_constituents(1)-1)*prm%N_constituents(2)*prm%N_constituents(3) &
|
nIntFaceTot = 3*( (prm%N_constituents(1)-1)*prm%N_constituents(2)*prm%N_constituents(3) &
|
||||||
|
|
|
@ -51,9 +51,9 @@ module subroutine thermal_init()
|
||||||
if (configHomogenization%contains('thermal')) then
|
if (configHomogenization%contains('thermal')) then
|
||||||
configHomogenizationThermal => configHomogenization%get('thermal')
|
configHomogenizationThermal => configHomogenization%get('thermal')
|
||||||
#if defined (__GFORTRAN__)
|
#if defined (__GFORTRAN__)
|
||||||
prm%output = output_asStrings(configHomogenizationThermal)
|
prm%output = output_as1dString(configHomogenizationThermal)
|
||||||
#else
|
#else
|
||||||
prm%output = configHomogenizationThermal%get_asStrings('output',defaultVal=emptyStringArray)
|
prm%output = configHomogenizationThermal%get_as1dString('output',defaultVal=emptyStringArray)
|
||||||
#endif
|
#endif
|
||||||
else
|
else
|
||||||
prm%output = emptyStringArray
|
prm%output = emptyStringArray
|
||||||
|
|
|
@ -64,14 +64,14 @@ module function anisobrittle_init() result(mySources)
|
||||||
associate(prm => param(p))
|
associate(prm => param(p))
|
||||||
src => sources%get(1)
|
src => sources%get(1)
|
||||||
|
|
||||||
N_cl = src%get_asInts('N_cl',defaultVal=emptyIntArray)
|
N_cl = src%get_as1dInt('N_cl',defaultVal=emptyIntArray)
|
||||||
prm%sum_N_cl = sum(abs(N_cl))
|
prm%sum_N_cl = sum(abs(N_cl))
|
||||||
|
|
||||||
prm%q = src%get_asFloat('q')
|
prm%q = src%get_asFloat('q')
|
||||||
prm%dot_o = src%get_asFloat('dot_o')
|
prm%dot_o = src%get_asFloat('dot_o')
|
||||||
|
|
||||||
prm%s_crit = src%get_asFloats('s_crit', requiredSize=size(N_cl))
|
prm%s_crit = src%get_as1dFloat('s_crit', requiredSize=size(N_cl))
|
||||||
prm%g_crit = src%get_asFloats('g_crit', requiredSize=size(N_cl))
|
prm%g_crit = src%get_as1dFloat('g_crit', requiredSize=size(N_cl))
|
||||||
|
|
||||||
prm%cleavage_systems = lattice_SchmidMatrix_cleavage(N_cl,phase%get_asString('lattice'),&
|
prm%cleavage_systems = lattice_SchmidMatrix_cleavage(N_cl,phase%get_asString('lattice'),&
|
||||||
phase%get_asFloat('c/a',defaultVal=0.0_pReal))
|
phase%get_asFloat('c/a',defaultVal=0.0_pReal))
|
||||||
|
@ -81,9 +81,9 @@ module function anisobrittle_init() result(mySources)
|
||||||
prm%g_crit = math_expand(prm%g_crit,N_cl)
|
prm%g_crit = math_expand(prm%g_crit,N_cl)
|
||||||
|
|
||||||
#if defined (__GFORTRAN__)
|
#if defined (__GFORTRAN__)
|
||||||
prm%output = output_asStrings(src)
|
prm%output = output_as1dString(src)
|
||||||
#else
|
#else
|
||||||
prm%output = src%get_asStrings('output',defaultVal=emptyStringArray)
|
prm%output = src%get_as1dString('output',defaultVal=emptyStringArray)
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
! sanity checks
|
! sanity checks
|
||||||
|
|
|
@ -61,17 +61,17 @@ module function anisoductile_init() result(mySources)
|
||||||
associate(prm => param(p))
|
associate(prm => param(p))
|
||||||
src => sources%get(1)
|
src => sources%get(1)
|
||||||
|
|
||||||
N_sl = pl%get_asInts('N_sl',defaultVal=emptyIntArray)
|
N_sl = pl%get_as1dInt('N_sl',defaultVal=emptyIntArray)
|
||||||
prm%q = src%get_asFloat('q')
|
prm%q = src%get_asFloat('q')
|
||||||
prm%gamma_crit = src%get_asFloats('gamma_crit',requiredSize=size(N_sl))
|
prm%gamma_crit = src%get_as1dFloat('gamma_crit',requiredSize=size(N_sl))
|
||||||
|
|
||||||
! expand: family => system
|
! expand: family => system
|
||||||
prm%gamma_crit = math_expand(prm%gamma_crit,N_sl)
|
prm%gamma_crit = math_expand(prm%gamma_crit,N_sl)
|
||||||
|
|
||||||
#if defined (__GFORTRAN__)
|
#if defined (__GFORTRAN__)
|
||||||
prm%output = output_asStrings(src)
|
prm%output = output_as1dString(src)
|
||||||
#else
|
#else
|
||||||
prm%output = src%get_asStrings('output',defaultVal=emptyStringArray)
|
prm%output = src%get_as1dString('output',defaultVal=emptyStringArray)
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
! sanity checks
|
! sanity checks
|
||||||
|
|
|
@ -56,9 +56,9 @@ module function isobrittle_init() result(mySources)
|
||||||
prm%W_crit = src%get_asFloat('W_crit')
|
prm%W_crit = src%get_asFloat('W_crit')
|
||||||
|
|
||||||
#if defined (__GFORTRAN__)
|
#if defined (__GFORTRAN__)
|
||||||
prm%output = output_asStrings(src)
|
prm%output = output_as1dString(src)
|
||||||
#else
|
#else
|
||||||
prm%output = src%get_asStrings('output',defaultVal=emptyStringArray)
|
prm%output = src%get_as1dString('output',defaultVal=emptyStringArray)
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
! sanity checks
|
! sanity checks
|
||||||
|
|
|
@ -59,9 +59,9 @@ module function isoductile_init() result(mySources)
|
||||||
prm%gamma_crit = src%get_asFloat('gamma_crit')
|
prm%gamma_crit = src%get_asFloat('gamma_crit')
|
||||||
|
|
||||||
#if defined (__GFORTRAN__)
|
#if defined (__GFORTRAN__)
|
||||||
prm%output = output_asStrings(src)
|
prm%output = output_as1dString(src)
|
||||||
#else
|
#else
|
||||||
prm%output = src%get_asStrings('output',defaultVal=emptyStringArray)
|
prm%output = src%get_as1dString('output',defaultVal=emptyStringArray)
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
! sanity checks
|
! sanity checks
|
||||||
|
|
|
@ -249,9 +249,9 @@ module subroutine mechanical_init(materials,phases)
|
||||||
phase => phases%get(ph)
|
phase => phases%get(ph)
|
||||||
mech => phase%get('mechanical')
|
mech => phase%get('mechanical')
|
||||||
#if defined(__GFORTRAN__)
|
#if defined(__GFORTRAN__)
|
||||||
output_constituent(ph)%label = output_asStrings(mech)
|
output_constituent(ph)%label = output_as1dString(mech)
|
||||||
#else
|
#else
|
||||||
output_constituent(ph)%label = mech%get_asStrings('output',defaultVal=emptyStringArray)
|
output_constituent(ph)%label = mech%get_as1dString('output',defaultVal=emptyStringArray)
|
||||||
#endif
|
#endif
|
||||||
elastic => mech%get('elastic')
|
elastic => mech%get('elastic')
|
||||||
if(elastic%get_asString('type') == 'hooke') then
|
if(elastic%get_asString('type') == 'hooke') then
|
||||||
|
@ -288,7 +288,7 @@ module subroutine mechanical_init(materials,phases)
|
||||||
ph = material_phaseAt(co,el)
|
ph = material_phaseAt(co,el)
|
||||||
me = material_phaseMemberAt(co,ip,el)
|
me = material_phaseMemberAt(co,ip,el)
|
||||||
|
|
||||||
call material_orientation0(co,ph,me)%fromQuaternion(constituent%get_asFloats('O',requiredSize=4))
|
call material_orientation0(co,ph,me)%fromQuaternion(constituent%get_as1dFloat('O',requiredSize=4))
|
||||||
|
|
||||||
phase_mechanical_Fp0(ph)%data(1:3,1:3,me) = material_orientation0(co,ph,me)%asMatrix() ! Fp reflects initial orientation (see 10.1016/j.actamat.2006.01.005)
|
phase_mechanical_Fp0(ph)%data(1:3,1:3,me) = material_orientation0(co,ph,me)%asMatrix() ! Fp reflects initial orientation (see 10.1016/j.actamat.2006.01.005)
|
||||||
phase_mechanical_Fp0(ph)%data(1:3,1:3,me) = phase_mechanical_Fp0(ph)%data(1:3,1:3,me) &
|
phase_mechanical_Fp0(ph)%data(1:3,1:3,me) = phase_mechanical_Fp0(ph)%data(1:3,1:3,me) &
|
||||||
|
|
|
@ -71,7 +71,7 @@ module function kinematics_slipplane_opening_init() result(myKinematics)
|
||||||
|
|
||||||
prm%dot_o = kinematic_type%get_asFloat('dot_o')
|
prm%dot_o = kinematic_type%get_asFloat('dot_o')
|
||||||
prm%q = kinematic_type%get_asFloat('q')
|
prm%q = kinematic_type%get_asFloat('q')
|
||||||
N_sl = pl%get_asInts('N_sl')
|
N_sl = pl%get_as1dInt('N_sl')
|
||||||
prm%sum_N_sl = sum(abs(N_sl))
|
prm%sum_N_sl = sum(abs(N_sl))
|
||||||
|
|
||||||
d = lattice_slip_direction (N_sl,phase%get_asString('lattice'),&
|
d = lattice_slip_direction (N_sl,phase%get_asString('lattice'),&
|
||||||
|
@ -88,7 +88,7 @@ module function kinematics_slipplane_opening_init() result(myKinematics)
|
||||||
prm%P_n(1:3,1:3,i) = math_outer(n(1:3,i), n(1:3,i))
|
prm%P_n(1:3,1:3,i) = math_outer(n(1:3,i), n(1:3,i))
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
prm%g_crit = kinematic_type%get_asFloats('g_crit',requiredSize=size(N_sl))
|
prm%g_crit = kinematic_type%get_as1dFloat('g_crit',requiredSize=size(N_sl))
|
||||||
|
|
||||||
! expand: family => system
|
! expand: family => system
|
||||||
prm%g_crit = math_expand(prm%g_crit,N_sl)
|
prm%g_crit = math_expand(prm%g_crit,N_sl)
|
||||||
|
|
|
@ -60,11 +60,11 @@ module function thermalexpansion_init(kinematics_length) result(myKinematics)
|
||||||
prm%T_ref = kinematic_type%get_asFloat('T_ref', defaultVal=0.0_pReal)
|
prm%T_ref = kinematic_type%get_asFloat('T_ref', defaultVal=0.0_pReal)
|
||||||
|
|
||||||
! read up to three parameters (constant, linear, quadratic with T)
|
! read up to three parameters (constant, linear, quadratic with T)
|
||||||
temp = kinematic_type%get_asFloats('A_11')
|
temp = kinematic_type%get_as1dFloat('A_11')
|
||||||
prm%A(1,1,1:size(temp)) = temp
|
prm%A(1,1,1:size(temp)) = temp
|
||||||
temp = kinematic_type%get_asFloats('A_22',defaultVal=[(0.0_pReal, i=1,size(temp))],requiredSize=size(temp))
|
temp = kinematic_type%get_as1dFloat('A_22',defaultVal=[(0.0_pReal, i=1,size(temp))],requiredSize=size(temp))
|
||||||
prm%A(2,2,1:size(temp)) = temp
|
prm%A(2,2,1:size(temp)) = temp
|
||||||
temp = kinematic_type%get_asFloats('A_33',defaultVal=[(0.0_pReal, i=1,size(temp))],requiredSize=size(temp))
|
temp = kinematic_type%get_as1dFloat('A_33',defaultVal=[(0.0_pReal, i=1,size(temp))],requiredSize=size(temp))
|
||||||
prm%A(3,3,1:size(temp)) = temp
|
prm%A(3,3,1:size(temp)) = temp
|
||||||
do i=1, size(prm%A,3)
|
do i=1, size(prm%A,3)
|
||||||
prm%A(1:3,1:3,i) = lattice_applyLatticeSymmetry33(prm%A(1:3,1:3,i),&
|
prm%A(1:3,1:3,i) = lattice_applyLatticeSymmetry33(prm%A(1:3,1:3,i),&
|
||||||
|
|
|
@ -124,9 +124,9 @@ module function plastic_dislotungsten_init() result(myPlasticity)
|
||||||
pl => mech%get('plastic')
|
pl => mech%get('plastic')
|
||||||
|
|
||||||
#if defined (__GFORTRAN__)
|
#if defined (__GFORTRAN__)
|
||||||
prm%output = output_asStrings(pl)
|
prm%output = output_as1dString(pl)
|
||||||
#else
|
#else
|
||||||
prm%output = pl%get_asStrings('output',defaultVal=emptyStringArray)
|
prm%output = pl%get_as1dString('output',defaultVal=emptyStringArray)
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
! This data is read in already in lattice
|
! This data is read in already in lattice
|
||||||
|
@ -134,14 +134,14 @@ module function plastic_dislotungsten_init() result(myPlasticity)
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! slip related parameters
|
! slip related parameters
|
||||||
N_sl = pl%get_asInts('N_sl',defaultVal=emptyIntArray)
|
N_sl = pl%get_as1dInt('N_sl',defaultVal=emptyIntArray)
|
||||||
prm%sum_N_sl = sum(abs(N_sl))
|
prm%sum_N_sl = sum(abs(N_sl))
|
||||||
slipActive: if (prm%sum_N_sl > 0) then
|
slipActive: if (prm%sum_N_sl > 0) then
|
||||||
prm%P_sl = lattice_SchmidMatrix_slip(N_sl,phase%get_asString('lattice'),&
|
prm%P_sl = lattice_SchmidMatrix_slip(N_sl,phase%get_asString('lattice'),&
|
||||||
phase%get_asFloat('c/a',defaultVal=0.0_pReal))
|
phase%get_asFloat('c/a',defaultVal=0.0_pReal))
|
||||||
|
|
||||||
if(trim(phase%get_asString('lattice')) == 'cI') then
|
if(trim(phase%get_asString('lattice')) == 'cI') then
|
||||||
a = pl%get_asFloats('a_nonSchmid',defaultVal = emptyRealArray)
|
a = pl%get_as1dFloat('a_nonSchmid',defaultVal = emptyRealArray)
|
||||||
prm%nonSchmid_pos = lattice_nonSchmidMatrix(N_sl,a,+1)
|
prm%nonSchmid_pos = lattice_nonSchmidMatrix(N_sl,a,+1)
|
||||||
prm%nonSchmid_neg = lattice_nonSchmidMatrix(N_sl,a,-1)
|
prm%nonSchmid_neg = lattice_nonSchmidMatrix(N_sl,a,-1)
|
||||||
else
|
else
|
||||||
|
@ -149,28 +149,28 @@ module function plastic_dislotungsten_init() result(myPlasticity)
|
||||||
prm%nonSchmid_neg = prm%P_sl
|
prm%nonSchmid_neg = prm%P_sl
|
||||||
endif
|
endif
|
||||||
|
|
||||||
prm%h_sl_sl = lattice_interaction_SlipBySlip(N_sl,pl%get_asFloats('h_sl_sl'), &
|
prm%h_sl_sl = lattice_interaction_SlipBySlip(N_sl,pl%get_as1dFloat('h_sl_sl'), &
|
||||||
phase%get_asString('lattice'))
|
phase%get_asString('lattice'))
|
||||||
prm%forestProjection = lattice_forestProjection_edge(N_sl,phase%get_asString('lattice'),&
|
prm%forestProjection = lattice_forestProjection_edge(N_sl,phase%get_asString('lattice'),&
|
||||||
phase%get_asFloat('c/a',defaultVal=0.0_pReal))
|
phase%get_asFloat('c/a',defaultVal=0.0_pReal))
|
||||||
prm%forestProjection = transpose(prm%forestProjection)
|
prm%forestProjection = transpose(prm%forestProjection)
|
||||||
|
|
||||||
rho_mob_0 = pl%get_asFloats('rho_mob_0', requiredSize=size(N_sl))
|
rho_mob_0 = pl%get_as1dFloat('rho_mob_0', requiredSize=size(N_sl))
|
||||||
rho_dip_0 = pl%get_asFloats('rho_dip_0', requiredSize=size(N_sl))
|
rho_dip_0 = pl%get_as1dFloat('rho_dip_0', requiredSize=size(N_sl))
|
||||||
prm%v_0 = pl%get_asFloats('v_0', requiredSize=size(N_sl))
|
prm%v_0 = pl%get_as1dFloat('v_0', requiredSize=size(N_sl))
|
||||||
prm%b_sl = pl%get_asFloats('b_sl', requiredSize=size(N_sl))
|
prm%b_sl = pl%get_as1dFloat('b_sl', requiredSize=size(N_sl))
|
||||||
prm%Q_s = pl%get_asFloats('Q_s', requiredSize=size(N_sl))
|
prm%Q_s = pl%get_as1dFloat('Q_s', requiredSize=size(N_sl))
|
||||||
|
|
||||||
prm%i_sl = pl%get_asFloats('i_sl', requiredSize=size(N_sl))
|
prm%i_sl = pl%get_as1dFloat('i_sl', requiredSize=size(N_sl))
|
||||||
prm%tau_Peierls = pl%get_asFloats('tau_Peierls', requiredSize=size(N_sl))
|
prm%tau_Peierls = pl%get_as1dFloat('tau_Peierls', requiredSize=size(N_sl))
|
||||||
prm%p = pl%get_asFloats('p_sl', requiredSize=size(N_sl), &
|
prm%p = pl%get_as1dFloat('p_sl', requiredSize=size(N_sl), &
|
||||||
defaultVal=[(1.0_pReal,i=1,size(N_sl))])
|
defaultVal=[(1.0_pReal,i=1,size(N_sl))])
|
||||||
prm%q = pl%get_asFloats('q_sl', requiredSize=size(N_sl), &
|
prm%q = pl%get_as1dFloat('q_sl', requiredSize=size(N_sl), &
|
||||||
defaultVal=[(1.0_pReal,i=1,size(N_sl))])
|
defaultVal=[(1.0_pReal,i=1,size(N_sl))])
|
||||||
prm%h = pl%get_asFloats('h', requiredSize=size(N_sl))
|
prm%h = pl%get_as1dFloat('h', requiredSize=size(N_sl))
|
||||||
prm%w = pl%get_asFloats('w', requiredSize=size(N_sl))
|
prm%w = pl%get_as1dFloat('w', requiredSize=size(N_sl))
|
||||||
prm%omega = pl%get_asFloats('omega', requiredSize=size(N_sl))
|
prm%omega = pl%get_as1dFloat('omega', requiredSize=size(N_sl))
|
||||||
prm%B = pl%get_asFloats('B', requiredSize=size(N_sl))
|
prm%B = pl%get_as1dFloat('B', requiredSize=size(N_sl))
|
||||||
|
|
||||||
prm%D = pl%get_asFloat('D')
|
prm%D = pl%get_asFloat('D')
|
||||||
prm%D_0 = pl%get_asFloat('D_0')
|
prm%D_0 = pl%get_asFloat('D_0')
|
||||||
|
|
|
@ -177,9 +177,9 @@ module function plastic_dislotwin_init() result(myPlasticity)
|
||||||
pl => mech%get('plastic')
|
pl => mech%get('plastic')
|
||||||
|
|
||||||
#if defined (__GFORTRAN__)
|
#if defined (__GFORTRAN__)
|
||||||
prm%output = output_asStrings(pl)
|
prm%output = output_as1dString(pl)
|
||||||
#else
|
#else
|
||||||
prm%output = pl%get_asStrings('output',defaultVal=emptyStringArray)
|
prm%output = pl%get_as1dString('output',defaultVal=emptyStringArray)
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
! This data is read in already in lattice
|
! This data is read in already in lattice
|
||||||
|
@ -189,12 +189,12 @@ module function plastic_dislotwin_init() result(myPlasticity)
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! slip related parameters
|
! slip related parameters
|
||||||
N_sl = pl%get_asInts('N_sl',defaultVal=emptyIntArray)
|
N_sl = pl%get_as1dInt('N_sl',defaultVal=emptyIntArray)
|
||||||
prm%sum_N_sl = sum(abs(N_sl))
|
prm%sum_N_sl = sum(abs(N_sl))
|
||||||
slipActive: if (prm%sum_N_sl > 0) then
|
slipActive: if (prm%sum_N_sl > 0) then
|
||||||
prm%P_sl = lattice_SchmidMatrix_slip(N_sl,phase%get_asString('lattice'),&
|
prm%P_sl = lattice_SchmidMatrix_slip(N_sl,phase%get_asString('lattice'),&
|
||||||
phase%get_asFloat('c/a',defaultVal=0.0_pReal))
|
phase%get_asFloat('c/a',defaultVal=0.0_pReal))
|
||||||
prm%h_sl_sl = lattice_interaction_SlipBySlip(N_sl,pl%get_asFloats('h_sl_sl'), &
|
prm%h_sl_sl = lattice_interaction_SlipBySlip(N_sl,pl%get_as1dFloat('h_sl_sl'), &
|
||||||
phase%get_asString('lattice'))
|
phase%get_asString('lattice'))
|
||||||
prm%forestProjection = lattice_forestProjection_edge(N_sl,phase%get_asString('lattice'),&
|
prm%forestProjection = lattice_forestProjection_edge(N_sl,phase%get_asString('lattice'),&
|
||||||
phase%get_asFloat('c/a',defaultVal=0.0_pReal))
|
phase%get_asFloat('c/a',defaultVal=0.0_pReal))
|
||||||
|
@ -205,16 +205,16 @@ module function plastic_dislotwin_init() result(myPlasticity)
|
||||||
prm%fccTwinTransNucleation = lattice_structure(ph) == lattice_FCC_ID .and. (N_sl(1) == 12)
|
prm%fccTwinTransNucleation = lattice_structure(ph) == lattice_FCC_ID .and. (N_sl(1) == 12)
|
||||||
if(prm%fccTwinTransNucleation) prm%fcc_twinNucleationSlipPair = lattice_FCC_TWINNUCLEATIONSLIPPAIR
|
if(prm%fccTwinTransNucleation) prm%fcc_twinNucleationSlipPair = lattice_FCC_TWINNUCLEATIONSLIPPAIR
|
||||||
|
|
||||||
rho_mob_0 = pl%get_asFloats('rho_mob_0', requiredSize=size(N_sl))
|
rho_mob_0 = pl%get_as1dFloat('rho_mob_0', requiredSize=size(N_sl))
|
||||||
rho_dip_0 = pl%get_asFloats('rho_dip_0', requiredSize=size(N_sl))
|
rho_dip_0 = pl%get_as1dFloat('rho_dip_0', requiredSize=size(N_sl))
|
||||||
prm%v_0 = pl%get_asFloats('v_0', requiredSize=size(N_sl))
|
prm%v_0 = pl%get_as1dFloat('v_0', requiredSize=size(N_sl))
|
||||||
prm%b_sl = pl%get_asFloats('b_sl', requiredSize=size(N_sl))
|
prm%b_sl = pl%get_as1dFloat('b_sl', requiredSize=size(N_sl))
|
||||||
prm%Q_s = pl%get_asFloats('Q_s', requiredSize=size(N_sl))
|
prm%Q_s = pl%get_as1dFloat('Q_s', requiredSize=size(N_sl))
|
||||||
prm%i_sl = pl%get_asFloats('i_sl', requiredSize=size(N_sl))
|
prm%i_sl = pl%get_as1dFloat('i_sl', requiredSize=size(N_sl))
|
||||||
prm%p = pl%get_asFloats('p_sl', requiredSize=size(N_sl))
|
prm%p = pl%get_as1dFloat('p_sl', requiredSize=size(N_sl))
|
||||||
prm%q = pl%get_asFloats('q_sl', requiredSize=size(N_sl))
|
prm%q = pl%get_as1dFloat('q_sl', requiredSize=size(N_sl))
|
||||||
prm%tau_0 = pl%get_asFloats('tau_0', requiredSize=size(N_sl))
|
prm%tau_0 = pl%get_as1dFloat('tau_0', requiredSize=size(N_sl))
|
||||||
prm%B = pl%get_asFloats('B', requiredSize=size(N_sl), &
|
prm%B = pl%get_as1dFloat('B', requiredSize=size(N_sl), &
|
||||||
defaultVal=[(0.0_pReal, i=1,size(N_sl))])
|
defaultVal=[(0.0_pReal, i=1,size(N_sl))])
|
||||||
|
|
||||||
prm%D_a = pl%get_asFloat('D_a')
|
prm%D_a = pl%get_asFloat('D_a')
|
||||||
|
@ -265,18 +265,18 @@ module function plastic_dislotwin_init() result(myPlasticity)
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! twin related parameters
|
! twin related parameters
|
||||||
N_tw = pl%get_asInts('N_tw', defaultVal=emptyIntArray)
|
N_tw = pl%get_as1dInt('N_tw', defaultVal=emptyIntArray)
|
||||||
prm%sum_N_tw = sum(abs(N_tw))
|
prm%sum_N_tw = sum(abs(N_tw))
|
||||||
twinActive: if (prm%sum_N_tw > 0) then
|
twinActive: if (prm%sum_N_tw > 0) then
|
||||||
prm%P_tw = lattice_SchmidMatrix_twin(N_tw,phase%get_asString('lattice'),&
|
prm%P_tw = lattice_SchmidMatrix_twin(N_tw,phase%get_asString('lattice'),&
|
||||||
phase%get_asFloat('c/a',defaultVal=0.0_pReal))
|
phase%get_asFloat('c/a',defaultVal=0.0_pReal))
|
||||||
prm%h_tw_tw = lattice_interaction_TwinByTwin(N_tw,&
|
prm%h_tw_tw = lattice_interaction_TwinByTwin(N_tw,&
|
||||||
pl%get_asFloats('h_tw_tw'), &
|
pl%get_as1dFloat('h_tw_tw'), &
|
||||||
phase%get_asString('lattice'))
|
phase%get_asString('lattice'))
|
||||||
|
|
||||||
prm%b_tw = pl%get_asFloats('b_tw', requiredSize=size(N_tw))
|
prm%b_tw = pl%get_as1dFloat('b_tw', requiredSize=size(N_tw))
|
||||||
prm%t_tw = pl%get_asFloats('t_tw', requiredSize=size(N_tw))
|
prm%t_tw = pl%get_as1dFloat('t_tw', requiredSize=size(N_tw))
|
||||||
prm%r = pl%get_asFloats('p_tw', requiredSize=size(N_tw))
|
prm%r = pl%get_as1dFloat('p_tw', requiredSize=size(N_tw))
|
||||||
|
|
||||||
prm%x_c_tw = pl%get_asFloat('x_c_tw')
|
prm%x_c_tw = pl%get_asFloat('x_c_tw')
|
||||||
prm%L_tw = pl%get_asFloat('L_tw')
|
prm%L_tw = pl%get_asFloat('L_tw')
|
||||||
|
@ -289,7 +289,7 @@ module function plastic_dislotwin_init() result(myPlasticity)
|
||||||
phase%get_asFloat('c/a',defaultVal=0.0_pReal))
|
phase%get_asFloat('c/a',defaultVal=0.0_pReal))
|
||||||
|
|
||||||
if (.not. prm%fccTwinTransNucleation) then
|
if (.not. prm%fccTwinTransNucleation) then
|
||||||
prm%dot_N_0_tw = pl%get_asFloats('dot_N_0_tw')
|
prm%dot_N_0_tw = pl%get_as1dFloat('dot_N_0_tw')
|
||||||
prm%dot_N_0_tw = math_expand(prm%dot_N_0_tw,N_tw)
|
prm%dot_N_0_tw = math_expand(prm%dot_N_0_tw,N_tw)
|
||||||
endif
|
endif
|
||||||
|
|
||||||
|
@ -315,10 +315,10 @@ module function plastic_dislotwin_init() result(myPlasticity)
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! transformation related parameters
|
! transformation related parameters
|
||||||
N_tr = pl%get_asInts('N_tr', defaultVal=emptyIntArray)
|
N_tr = pl%get_as1dInt('N_tr', defaultVal=emptyIntArray)
|
||||||
prm%sum_N_tr = sum(abs(N_tr))
|
prm%sum_N_tr = sum(abs(N_tr))
|
||||||
transActive: if (prm%sum_N_tr > 0) then
|
transActive: if (prm%sum_N_tr > 0) then
|
||||||
prm%b_tr = pl%get_asFloats('b_tr')
|
prm%b_tr = pl%get_as1dFloat('b_tr')
|
||||||
prm%b_tr = math_expand(prm%b_tr,N_tr)
|
prm%b_tr = math_expand(prm%b_tr,N_tr)
|
||||||
|
|
||||||
prm%h = pl%get_asFloat('h', defaultVal=0.0_pReal) ! ToDo: How to handle that???
|
prm%h = pl%get_asFloat('h', defaultVal=0.0_pReal) ! ToDo: How to handle that???
|
||||||
|
@ -327,7 +327,7 @@ module function plastic_dislotwin_init() result(myPlasticity)
|
||||||
prm%x_c_tr = pl%get_asFloat('x_c_tr', defaultVal=0.0_pReal) ! ToDo: How to handle that???
|
prm%x_c_tr = pl%get_asFloat('x_c_tr', defaultVal=0.0_pReal) ! ToDo: How to handle that???
|
||||||
prm%L_tr = pl%get_asFloat('L_tr')
|
prm%L_tr = pl%get_asFloat('L_tr')
|
||||||
|
|
||||||
prm%h_tr_tr = lattice_interaction_TransByTrans(N_tr,pl%get_asFloats('h_tr_tr'), &
|
prm%h_tr_tr = lattice_interaction_TransByTrans(N_tr,pl%get_as1dFloat('h_tr_tr'), &
|
||||||
phase%get_asString('lattice'))
|
phase%get_asString('lattice'))
|
||||||
|
|
||||||
prm%C66_tr = lattice_C66_trans(N_tr,prm%C66,pl%get_asString('lattice_tr'), &
|
prm%C66_tr = lattice_C66_trans(N_tr,prm%C66,pl%get_asString('lattice_tr'), &
|
||||||
|
@ -341,12 +341,12 @@ module function plastic_dislotwin_init() result(myPlasticity)
|
||||||
pl%get_asFloat('a_cF', defaultVal=0.0_pReal))
|
pl%get_asFloat('a_cF', defaultVal=0.0_pReal))
|
||||||
|
|
||||||
if (lattice_structure(ph) /= lattice_FCC_ID) then
|
if (lattice_structure(ph) /= lattice_FCC_ID) then
|
||||||
prm%dot_N_0_tr = pl%get_asFloats('dot_N_0_tr')
|
prm%dot_N_0_tr = pl%get_as1dFloat('dot_N_0_tr')
|
||||||
prm%dot_N_0_tr = math_expand(prm%dot_N_0_tr,N_tr)
|
prm%dot_N_0_tr = math_expand(prm%dot_N_0_tr,N_tr)
|
||||||
endif
|
endif
|
||||||
prm%t_tr = pl%get_asFloats('t_tr')
|
prm%t_tr = pl%get_as1dFloat('t_tr')
|
||||||
prm%t_tr = math_expand(prm%t_tr,N_tr)
|
prm%t_tr = math_expand(prm%t_tr,N_tr)
|
||||||
prm%s = pl%get_asFloats('p_tr',defaultVal=[0.0_pReal])
|
prm%s = pl%get_as1dFloat('p_tr',defaultVal=[0.0_pReal])
|
||||||
prm%s = math_expand(prm%s,N_tr)
|
prm%s = math_expand(prm%s,N_tr)
|
||||||
|
|
||||||
! sanity checks
|
! sanity checks
|
||||||
|
@ -392,14 +392,14 @@ module function plastic_dislotwin_init() result(myPlasticity)
|
||||||
|
|
||||||
slipAndTwinActive: if (prm%sum_N_sl * prm%sum_N_tw > 0) then
|
slipAndTwinActive: if (prm%sum_N_sl * prm%sum_N_tw > 0) then
|
||||||
prm%h_sl_tw = lattice_interaction_SlipByTwin(N_sl,N_tw,&
|
prm%h_sl_tw = lattice_interaction_SlipByTwin(N_sl,N_tw,&
|
||||||
pl%get_asFloats('h_sl_tw'), &
|
pl%get_as1dFloat('h_sl_tw'), &
|
||||||
phase%get_asString('lattice'))
|
phase%get_asString('lattice'))
|
||||||
if (prm%fccTwinTransNucleation .and. size(N_tw) /= 1) extmsg = trim(extmsg)//' interaction_sliptwin'
|
if (prm%fccTwinTransNucleation .and. size(N_tw) /= 1) extmsg = trim(extmsg)//' interaction_sliptwin'
|
||||||
endif slipAndTwinActive
|
endif slipAndTwinActive
|
||||||
|
|
||||||
slipAndTransActive: if (prm%sum_N_sl * prm%sum_N_tr > 0) then
|
slipAndTransActive: if (prm%sum_N_sl * prm%sum_N_tr > 0) then
|
||||||
prm%h_sl_tr = lattice_interaction_SlipByTrans(N_sl,N_tr,&
|
prm%h_sl_tr = lattice_interaction_SlipByTrans(N_sl,N_tr,&
|
||||||
pl%get_asFloats('h_sl_tr'), &
|
pl%get_as1dFloat('h_sl_tr'), &
|
||||||
phase%get_asString('lattice'))
|
phase%get_asString('lattice'))
|
||||||
if (prm%fccTwinTransNucleation .and. size(N_tr) /= 1) extmsg = trim(extmsg)//' interaction_sliptrans'
|
if (prm%fccTwinTransNucleation .and. size(N_tr) /= 1) extmsg = trim(extmsg)//' interaction_sliptrans'
|
||||||
endif slipAndTransActive
|
endif slipAndTransActive
|
||||||
|
|
|
@ -89,9 +89,9 @@ module function plastic_isotropic_init() result(myPlasticity)
|
||||||
pl => mech%get('plastic')
|
pl => mech%get('plastic')
|
||||||
|
|
||||||
#if defined (__GFORTRAN__)
|
#if defined (__GFORTRAN__)
|
||||||
prm%output = output_asStrings(pl)
|
prm%output = output_as1dString(pl)
|
||||||
#else
|
#else
|
||||||
prm%output = pl%get_asStrings('output',defaultVal=emptyStringArray)
|
prm%output = pl%get_as1dString('output',defaultVal=emptyStringArray)
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
xi_0 = pl%get_asFloat('xi_0')
|
xi_0 = pl%get_asFloat('xi_0')
|
||||||
|
|
|
@ -102,21 +102,21 @@ module function plastic_kinehardening_init() result(myPlasticity)
|
||||||
pl => mech%get('plastic')
|
pl => mech%get('plastic')
|
||||||
|
|
||||||
#if defined (__GFORTRAN__)
|
#if defined (__GFORTRAN__)
|
||||||
prm%output = output_asStrings(pl)
|
prm%output = output_as1dString(pl)
|
||||||
#else
|
#else
|
||||||
prm%output = pl%get_asStrings('output',defaultVal=emptyStringArray)
|
prm%output = pl%get_as1dString('output',defaultVal=emptyStringArray)
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! slip related parameters
|
! slip related parameters
|
||||||
N_sl = pl%get_asInts('N_sl',defaultVal=emptyIntArray)
|
N_sl = pl%get_as1dInt('N_sl',defaultVal=emptyIntArray)
|
||||||
prm%sum_N_sl = sum(abs(N_sl))
|
prm%sum_N_sl = sum(abs(N_sl))
|
||||||
slipActive: if (prm%sum_N_sl > 0) then
|
slipActive: if (prm%sum_N_sl > 0) then
|
||||||
prm%P = lattice_SchmidMatrix_slip(N_sl,phase%get_asString('lattice'),&
|
prm%P = lattice_SchmidMatrix_slip(N_sl,phase%get_asString('lattice'),&
|
||||||
phase%get_asFloat('c/a',defaultVal=0.0_pReal))
|
phase%get_asFloat('c/a',defaultVal=0.0_pReal))
|
||||||
|
|
||||||
if(trim(phase%get_asString('lattice')) == 'cI') then
|
if(trim(phase%get_asString('lattice')) == 'cI') then
|
||||||
a = pl%get_asFloats('a_nonSchmid',defaultVal = emptyRealArray)
|
a = pl%get_as1dFloat('a_nonSchmid',defaultVal = emptyRealArray)
|
||||||
if(size(a) > 0) prm%nonSchmidActive = .true.
|
if(size(a) > 0) prm%nonSchmidActive = .true.
|
||||||
prm%nonSchmid_pos = lattice_nonSchmidMatrix(N_sl,a,+1)
|
prm%nonSchmid_pos = lattice_nonSchmidMatrix(N_sl,a,+1)
|
||||||
prm%nonSchmid_neg = lattice_nonSchmidMatrix(N_sl,a,-1)
|
prm%nonSchmid_neg = lattice_nonSchmidMatrix(N_sl,a,-1)
|
||||||
|
@ -125,16 +125,16 @@ module function plastic_kinehardening_init() result(myPlasticity)
|
||||||
prm%nonSchmid_neg = prm%P
|
prm%nonSchmid_neg = prm%P
|
||||||
endif
|
endif
|
||||||
prm%interaction_SlipSlip = lattice_interaction_SlipBySlip(N_sl, &
|
prm%interaction_SlipSlip = lattice_interaction_SlipBySlip(N_sl, &
|
||||||
pl%get_asFloats('h_sl_sl'), &
|
pl%get_as1dFloat('h_sl_sl'), &
|
||||||
phase%get_asString('lattice'))
|
phase%get_asString('lattice'))
|
||||||
|
|
||||||
xi_0 = pl%get_asFloats('xi_0', requiredSize=size(N_sl))
|
xi_0 = pl%get_as1dFloat('xi_0', requiredSize=size(N_sl))
|
||||||
prm%xi_inf_f = pl%get_asFloats('xi_inf_f', requiredSize=size(N_sl))
|
prm%xi_inf_f = pl%get_as1dFloat('xi_inf_f', requiredSize=size(N_sl))
|
||||||
prm%xi_inf_b = pl%get_asFloats('xi_inf_b', requiredSize=size(N_sl))
|
prm%xi_inf_b = pl%get_as1dFloat('xi_inf_b', requiredSize=size(N_sl))
|
||||||
prm%h_0_f = pl%get_asFloats('h_0_f', requiredSize=size(N_sl))
|
prm%h_0_f = pl%get_as1dFloat('h_0_f', requiredSize=size(N_sl))
|
||||||
prm%h_inf_f = pl%get_asFloats('h_inf_f', requiredSize=size(N_sl))
|
prm%h_inf_f = pl%get_as1dFloat('h_inf_f', requiredSize=size(N_sl))
|
||||||
prm%h_0_b = pl%get_asFloats('h_0_b', requiredSize=size(N_sl))
|
prm%h_0_b = pl%get_as1dFloat('h_0_b', requiredSize=size(N_sl))
|
||||||
prm%h_inf_b = pl%get_asFloats('h_inf_b', requiredSize=size(N_sl))
|
prm%h_inf_b = pl%get_as1dFloat('h_inf_b', requiredSize=size(N_sl))
|
||||||
|
|
||||||
prm%dot_gamma_0 = pl%get_asFloat('dot_gamma_0')
|
prm%dot_gamma_0 = pl%get_asFloat('dot_gamma_0')
|
||||||
prm%n = pl%get_asFloat('n')
|
prm%n = pl%get_asFloat('n')
|
||||||
|
|
|
@ -233,9 +233,9 @@ module function plastic_nonlocal_init() result(myPlasticity)
|
||||||
phase_localPlasticity(ph) = .not. pl%contains('nonlocal')
|
phase_localPlasticity(ph) = .not. pl%contains('nonlocal')
|
||||||
|
|
||||||
#if defined (__GFORTRAN__)
|
#if defined (__GFORTRAN__)
|
||||||
prm%output = output_asStrings(pl)
|
prm%output = output_as1dString(pl)
|
||||||
#else
|
#else
|
||||||
prm%output = pl%get_asStrings('output',defaultVal=emptyStringArray)
|
prm%output = pl%get_as1dString('output',defaultVal=emptyStringArray)
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
prm%atol_rho = pl%get_asFloat('atol_rho',defaultVal=1.0e4_pReal)
|
prm%atol_rho = pl%get_asFloat('atol_rho',defaultVal=1.0e4_pReal)
|
||||||
|
@ -244,14 +244,14 @@ module function plastic_nonlocal_init() result(myPlasticity)
|
||||||
prm%mu = lattice_mu(ph)
|
prm%mu = lattice_mu(ph)
|
||||||
prm%nu = lattice_nu(ph)
|
prm%nu = lattice_nu(ph)
|
||||||
|
|
||||||
ini%N_sl = pl%get_asInts('N_sl',defaultVal=emptyIntArray)
|
ini%N_sl = pl%get_as1dInt('N_sl',defaultVal=emptyIntArray)
|
||||||
prm%sum_N_sl = sum(abs(ini%N_sl))
|
prm%sum_N_sl = sum(abs(ini%N_sl))
|
||||||
slipActive: if (prm%sum_N_sl > 0) then
|
slipActive: if (prm%sum_N_sl > 0) then
|
||||||
prm%Schmid = lattice_SchmidMatrix_slip(ini%N_sl,phase%get_asString('lattice'),&
|
prm%Schmid = lattice_SchmidMatrix_slip(ini%N_sl,phase%get_asString('lattice'),&
|
||||||
phase%get_asFloat('c/a',defaultVal=0.0_pReal))
|
phase%get_asFloat('c/a',defaultVal=0.0_pReal))
|
||||||
|
|
||||||
if(trim(phase%get_asString('lattice')) == 'cI') then
|
if(trim(phase%get_asString('lattice')) == 'cI') then
|
||||||
a = pl%get_asFloats('a_nonSchmid',defaultVal = emptyRealArray)
|
a = pl%get_as1dFloat('a_nonSchmid',defaultVal = emptyRealArray)
|
||||||
if(size(a) > 0) prm%nonSchmidActive = .true.
|
if(size(a) > 0) prm%nonSchmidActive = .true.
|
||||||
prm%nonSchmid_pos = lattice_nonSchmidMatrix(ini%N_sl,a,+1)
|
prm%nonSchmid_pos = lattice_nonSchmidMatrix(ini%N_sl,a,+1)
|
||||||
prm%nonSchmid_neg = lattice_nonSchmidMatrix(ini%N_sl,a,-1)
|
prm%nonSchmid_neg = lattice_nonSchmidMatrix(ini%N_sl,a,-1)
|
||||||
|
@ -261,7 +261,7 @@ module function plastic_nonlocal_init() result(myPlasticity)
|
||||||
endif
|
endif
|
||||||
|
|
||||||
prm%h_sl_sl = lattice_interaction_SlipBySlip(ini%N_sl, &
|
prm%h_sl_sl = lattice_interaction_SlipBySlip(ini%N_sl, &
|
||||||
pl%get_asFloats('h_sl_sl'), &
|
pl%get_as1dFloat('h_sl_sl'), &
|
||||||
phase%get_asString('lattice'))
|
phase%get_asString('lattice'))
|
||||||
|
|
||||||
prm%forestProjection_edge = lattice_forestProjection_edge (ini%N_sl,phase%get_asString('lattice'),&
|
prm%forestProjection_edge = lattice_forestProjection_edge (ini%N_sl,phase%get_asString('lattice'),&
|
||||||
|
@ -286,29 +286,29 @@ module function plastic_nonlocal_init() result(myPlasticity)
|
||||||
enddo
|
enddo
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
ini%rho_u_ed_pos_0 = pl%get_asFloats('rho_u_ed_pos_0', requiredSize=size(ini%N_sl))
|
ini%rho_u_ed_pos_0 = pl%get_as1dFloat('rho_u_ed_pos_0', requiredSize=size(ini%N_sl))
|
||||||
ini%rho_u_ed_neg_0 = pl%get_asFloats('rho_u_ed_neg_0', requiredSize=size(ini%N_sl))
|
ini%rho_u_ed_neg_0 = pl%get_as1dFloat('rho_u_ed_neg_0', requiredSize=size(ini%N_sl))
|
||||||
ini%rho_u_sc_pos_0 = pl%get_asFloats('rho_u_sc_pos_0', requiredSize=size(ini%N_sl))
|
ini%rho_u_sc_pos_0 = pl%get_as1dFloat('rho_u_sc_pos_0', requiredSize=size(ini%N_sl))
|
||||||
ini%rho_u_sc_neg_0 = pl%get_asFloats('rho_u_sc_neg_0', requiredSize=size(ini%N_sl))
|
ini%rho_u_sc_neg_0 = pl%get_as1dFloat('rho_u_sc_neg_0', requiredSize=size(ini%N_sl))
|
||||||
ini%rho_d_ed_0 = pl%get_asFloats('rho_d_ed_0', requiredSize=size(ini%N_sl))
|
ini%rho_d_ed_0 = pl%get_as1dFloat('rho_d_ed_0', requiredSize=size(ini%N_sl))
|
||||||
ini%rho_d_sc_0 = pl%get_asFloats('rho_d_sc_0', requiredSize=size(ini%N_sl))
|
ini%rho_d_sc_0 = pl%get_as1dFloat('rho_d_sc_0', requiredSize=size(ini%N_sl))
|
||||||
|
|
||||||
prm%i_sl = pl%get_asFloats('i_sl', requiredSize=size(ini%N_sl))
|
prm%i_sl = pl%get_as1dFloat('i_sl', requiredSize=size(ini%N_sl))
|
||||||
prm%b_sl = pl%get_asFloats('b_sl', requiredSize=size(ini%N_sl))
|
prm%b_sl = pl%get_as1dFloat('b_sl', requiredSize=size(ini%N_sl))
|
||||||
|
|
||||||
prm%i_sl = math_expand(prm%i_sl,ini%N_sl)
|
prm%i_sl = math_expand(prm%i_sl,ini%N_sl)
|
||||||
prm%b_sl = math_expand(prm%b_sl,ini%N_sl)
|
prm%b_sl = math_expand(prm%b_sl,ini%N_sl)
|
||||||
|
|
||||||
prm%d_ed = pl%get_asFloats('d_ed', requiredSize=size(ini%N_sl))
|
prm%d_ed = pl%get_as1dFloat('d_ed', requiredSize=size(ini%N_sl))
|
||||||
prm%d_sc = pl%get_asFloats('d_sc', requiredSize=size(ini%N_sl))
|
prm%d_sc = pl%get_as1dFloat('d_sc', requiredSize=size(ini%N_sl))
|
||||||
prm%d_ed = math_expand(prm%d_ed,ini%N_sl)
|
prm%d_ed = math_expand(prm%d_ed,ini%N_sl)
|
||||||
prm%d_sc = math_expand(prm%d_sc,ini%N_sl)
|
prm%d_sc = math_expand(prm%d_sc,ini%N_sl)
|
||||||
allocate(prm%minDipoleHeight(prm%sum_N_sl,2))
|
allocate(prm%minDipoleHeight(prm%sum_N_sl,2))
|
||||||
prm%minDipoleHeight(:,1) = prm%d_ed
|
prm%minDipoleHeight(:,1) = prm%d_ed
|
||||||
prm%minDipoleHeight(:,2) = prm%d_sc
|
prm%minDipoleHeight(:,2) = prm%d_sc
|
||||||
|
|
||||||
prm%tau_Peierls_ed = pl%get_asFloats('tau_Peierls_ed', requiredSize=size(ini%N_sl))
|
prm%tau_Peierls_ed = pl%get_as1dFloat('tau_Peierls_ed', requiredSize=size(ini%N_sl))
|
||||||
prm%tau_Peierls_sc = pl%get_asFloats('tau_Peierls_sc', requiredSize=size(ini%N_sl))
|
prm%tau_Peierls_sc = pl%get_as1dFloat('tau_Peierls_sc', requiredSize=size(ini%N_sl))
|
||||||
prm%tau_Peierls_ed = math_expand(prm%tau_Peierls_ed,ini%N_sl)
|
prm%tau_Peierls_ed = math_expand(prm%tau_Peierls_ed,ini%N_sl)
|
||||||
prm%tau_Peierls_sc = math_expand(prm%tau_Peierls_sc,ini%N_sl)
|
prm%tau_Peierls_sc = math_expand(prm%tau_Peierls_sc,ini%N_sl)
|
||||||
allocate(prm%peierlsstress(prm%sum_N_sl,2))
|
allocate(prm%peierlsstress(prm%sum_N_sl,2))
|
||||||
|
|
|
@ -112,14 +112,14 @@ module function plastic_phenopowerlaw_init() result(myPlasticity)
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! slip related parameters
|
! slip related parameters
|
||||||
N_sl = pl%get_asInts('N_sl',defaultVal=emptyIntArray)
|
N_sl = pl%get_as1dInt('N_sl',defaultVal=emptyIntArray)
|
||||||
prm%sum_N_sl = sum(abs(N_sl))
|
prm%sum_N_sl = sum(abs(N_sl))
|
||||||
slipActive: if (prm%sum_N_sl > 0) then
|
slipActive: if (prm%sum_N_sl > 0) then
|
||||||
prm%P_sl = lattice_SchmidMatrix_slip(N_sl,phase%get_asString('lattice'),&
|
prm%P_sl = lattice_SchmidMatrix_slip(N_sl,phase%get_asString('lattice'),&
|
||||||
phase%get_asFloat('c/a',defaultVal=0.0_pReal))
|
phase%get_asFloat('c/a',defaultVal=0.0_pReal))
|
||||||
|
|
||||||
if(phase%get_asString('lattice') == 'cI') then
|
if(phase%get_asString('lattice') == 'cI') then
|
||||||
a = pl%get_asFloats('a_nonSchmid',defaultVal=emptyRealArray)
|
a = pl%get_as1dFloat('a_nonSchmid',defaultVal=emptyRealArray)
|
||||||
if(size(a) > 0) prm%nonSchmidActive = .true.
|
if(size(a) > 0) prm%nonSchmidActive = .true.
|
||||||
prm%nonSchmid_pos = lattice_nonSchmidMatrix(N_sl,a,+1)
|
prm%nonSchmid_pos = lattice_nonSchmidMatrix(N_sl,a,+1)
|
||||||
prm%nonSchmid_neg = lattice_nonSchmidMatrix(N_sl,a,-1)
|
prm%nonSchmid_neg = lattice_nonSchmidMatrix(N_sl,a,-1)
|
||||||
|
@ -128,12 +128,12 @@ module function plastic_phenopowerlaw_init() result(myPlasticity)
|
||||||
prm%nonSchmid_neg = prm%P_sl
|
prm%nonSchmid_neg = prm%P_sl
|
||||||
endif
|
endif
|
||||||
prm%h_sl_sl = lattice_interaction_SlipBySlip(N_sl, &
|
prm%h_sl_sl = lattice_interaction_SlipBySlip(N_sl, &
|
||||||
pl%get_asFloats('h_sl_sl'), &
|
pl%get_as1dFloat('h_sl_sl'), &
|
||||||
phase%get_asString('lattice'))
|
phase%get_asString('lattice'))
|
||||||
|
|
||||||
xi_0_sl = pl%get_asFloats('xi_0_sl', requiredSize=size(N_sl))
|
xi_0_sl = pl%get_as1dFloat('xi_0_sl', requiredSize=size(N_sl))
|
||||||
prm%xi_inf_sl = pl%get_asFloats('xi_inf_sl', requiredSize=size(N_sl))
|
prm%xi_inf_sl = pl%get_as1dFloat('xi_inf_sl', requiredSize=size(N_sl))
|
||||||
prm%h_int = pl%get_asFloats('h_int', requiredSize=size(N_sl), &
|
prm%h_int = pl%get_as1dFloat('h_int', requiredSize=size(N_sl), &
|
||||||
defaultVal=[(0.0_pReal,i=1,size(N_sl))])
|
defaultVal=[(0.0_pReal,i=1,size(N_sl))])
|
||||||
|
|
||||||
prm%dot_gamma_0_sl = pl%get_asFloat('dot_gamma_0_sl')
|
prm%dot_gamma_0_sl = pl%get_asFloat('dot_gamma_0_sl')
|
||||||
|
@ -161,18 +161,18 @@ module function plastic_phenopowerlaw_init() result(myPlasticity)
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! twin related parameters
|
! twin related parameters
|
||||||
N_tw = pl%get_asInts('N_tw', defaultVal=emptyIntArray)
|
N_tw = pl%get_as1dInt('N_tw', defaultVal=emptyIntArray)
|
||||||
prm%sum_N_tw = sum(abs(N_tw))
|
prm%sum_N_tw = sum(abs(N_tw))
|
||||||
twinActive: if (prm%sum_N_tw > 0) then
|
twinActive: if (prm%sum_N_tw > 0) then
|
||||||
prm%P_tw = lattice_SchmidMatrix_twin(N_tw,phase%get_asString('lattice'),&
|
prm%P_tw = lattice_SchmidMatrix_twin(N_tw,phase%get_asString('lattice'),&
|
||||||
phase%get_asFloat('c/a',defaultVal=0.0_pReal))
|
phase%get_asFloat('c/a',defaultVal=0.0_pReal))
|
||||||
prm%h_tw_tw = lattice_interaction_TwinByTwin(N_tw,&
|
prm%h_tw_tw = lattice_interaction_TwinByTwin(N_tw,&
|
||||||
pl%get_asFloats('h_tw_tw'), &
|
pl%get_as1dFloat('h_tw_tw'), &
|
||||||
phase%get_asString('lattice'))
|
phase%get_asString('lattice'))
|
||||||
prm%gamma_tw_char = lattice_characteristicShear_twin(N_tw,phase%get_asString('lattice'),&
|
prm%gamma_tw_char = lattice_characteristicShear_twin(N_tw,phase%get_asString('lattice'),&
|
||||||
phase%get_asFloat('c/a',defaultVal=0.0_pReal))
|
phase%get_asFloat('c/a',defaultVal=0.0_pReal))
|
||||||
|
|
||||||
xi_0_tw = pl%get_asFloats('xi_0_tw',requiredSize=size(N_tw))
|
xi_0_tw = pl%get_as1dFloat('xi_0_tw',requiredSize=size(N_tw))
|
||||||
|
|
||||||
prm%c_1 = pl%get_asFloat('c_1',defaultVal=0.0_pReal)
|
prm%c_1 = pl%get_asFloat('c_1',defaultVal=0.0_pReal)
|
||||||
prm%c_2 = pl%get_asFloat('c_2',defaultVal=1.0_pReal)
|
prm%c_2 = pl%get_asFloat('c_2',defaultVal=1.0_pReal)
|
||||||
|
@ -201,10 +201,10 @@ module function plastic_phenopowerlaw_init() result(myPlasticity)
|
||||||
slipAndTwinActive: if (prm%sum_N_sl > 0 .and. prm%sum_N_tw > 0) then
|
slipAndTwinActive: if (prm%sum_N_sl > 0 .and. prm%sum_N_tw > 0) then
|
||||||
prm%h_0_tw_sl = pl%get_asFloat('h_0_tw_sl')
|
prm%h_0_tw_sl = pl%get_asFloat('h_0_tw_sl')
|
||||||
prm%h_sl_tw = lattice_interaction_SlipByTwin(N_sl,N_tw,&
|
prm%h_sl_tw = lattice_interaction_SlipByTwin(N_sl,N_tw,&
|
||||||
pl%get_asFloats('h_sl_tw'), &
|
pl%get_as1dFloat('h_sl_tw'), &
|
||||||
phase%get_asString('lattice'))
|
phase%get_asString('lattice'))
|
||||||
prm%h_tw_sl = lattice_interaction_TwinBySlip(N_tw,N_sl,&
|
prm%h_tw_sl = lattice_interaction_TwinBySlip(N_tw,N_sl,&
|
||||||
pl%get_asFloats('h_tw_sl'), &
|
pl%get_as1dFloat('h_tw_sl'), &
|
||||||
phase%get_asString('lattice'))
|
phase%get_asString('lattice'))
|
||||||
else slipAndTwinActive
|
else slipAndTwinActive
|
||||||
allocate(prm%h_sl_tw(prm%sum_N_sl,prm%sum_N_tw)) ! at least one dimension is 0
|
allocate(prm%h_sl_tw(prm%sum_N_sl,prm%sum_N_tw)) ! at least one dimension is 0
|
||||||
|
@ -216,9 +216,9 @@ module function plastic_phenopowerlaw_init() result(myPlasticity)
|
||||||
! output pararameters
|
! output pararameters
|
||||||
|
|
||||||
#if defined (__GFORTRAN__)
|
#if defined (__GFORTRAN__)
|
||||||
prm%output = output_asStrings(pl)
|
prm%output = output_as1dString(pl)
|
||||||
#else
|
#else
|
||||||
prm%output = pl%get_asStrings('output',defaultVal=emptyStringArray)
|
prm%output = pl%get_as1dString('output',defaultVal=emptyStringArray)
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
|
|
@ -62,10 +62,10 @@ module function externalheat_init(source_length) result(mySources)
|
||||||
associate(prm => param(ph))
|
associate(prm => param(ph))
|
||||||
src => sources%get(so)
|
src => sources%get(so)
|
||||||
|
|
||||||
prm%t_n = src%get_asFloats('t_n')
|
prm%t_n = src%get_as1dFloat('t_n')
|
||||||
prm%nIntervals = size(prm%t_n) - 1
|
prm%nIntervals = size(prm%t_n) - 1
|
||||||
|
|
||||||
prm%f_T = src%get_asFloats('f_T',requiredSize = size(prm%t_n))
|
prm%f_T = src%get_as1dFloat('f_T',requiredSize = size(prm%t_n))
|
||||||
|
|
||||||
Nmembers = count(material_phaseAt2 == ph)
|
Nmembers = count(material_phaseAt2 == ph)
|
||||||
call phase_allocateState(thermalState(ph)%p(so),Nmembers,1,1,0)
|
call phase_allocateState(thermalState(ph)%p(so),Nmembers,1,1,0)
|
||||||
|
|
Loading…
Reference in New Issue