general polishing
This commit is contained in:
parent
77a0cfd7a2
commit
19df6f8a71
|
@ -318,7 +318,7 @@ subroutine show(this)
|
||||||
do while (associated(item%next))
|
do while (associated(item%next))
|
||||||
write(6,'(a)') ' '//trim(item%string%val)
|
write(6,'(a)') ' '//trim(item%string%val)
|
||||||
item => item%next
|
item => item%next
|
||||||
end do
|
enddo
|
||||||
|
|
||||||
end subroutine show
|
end subroutine show
|
||||||
|
|
||||||
|
@ -391,7 +391,7 @@ logical function keyExists(this,key)
|
||||||
do while (associated(item%next) .and. .not. keyExists)
|
do while (associated(item%next) .and. .not. keyExists)
|
||||||
keyExists = trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)
|
keyExists = trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)
|
||||||
item => item%next
|
item => item%next
|
||||||
end do
|
enddo
|
||||||
|
|
||||||
end function keyExists
|
end function keyExists
|
||||||
|
|
||||||
|
@ -417,7 +417,7 @@ integer(pInt) function countKeys(this,key)
|
||||||
if (trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)) &
|
if (trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)) &
|
||||||
countKeys = countKeys + 1_pInt
|
countKeys = countKeys + 1_pInt
|
||||||
item => item%next
|
item => item%next
|
||||||
end do
|
enddo
|
||||||
|
|
||||||
end function countKeys
|
end function countKeys
|
||||||
|
|
||||||
|
@ -451,7 +451,7 @@ real(pReal) function getFloat(this,key,defaultVal)
|
||||||
getFloat = IO_FloatValue(item%string%val,item%string%pos,2)
|
getFloat = IO_FloatValue(item%string%val,item%string%pos,2)
|
||||||
endif
|
endif
|
||||||
item => item%next
|
item => item%next
|
||||||
end do
|
enddo
|
||||||
|
|
||||||
if (.not. found) call IO_error(140_pInt,ext_msg=key)
|
if (.not. found) call IO_error(140_pInt,ext_msg=key)
|
||||||
|
|
||||||
|
@ -487,7 +487,7 @@ integer(pInt) function getInt(this,key,defaultVal)
|
||||||
getInt = IO_IntValue(item%string%val,item%string%pos,2)
|
getInt = IO_IntValue(item%string%val,item%string%pos,2)
|
||||||
endif
|
endif
|
||||||
item => item%next
|
item => item%next
|
||||||
end do
|
enddo
|
||||||
|
|
||||||
if (.not. found) call IO_error(140_pInt,ext_msg=key)
|
if (.not. found) call IO_error(140_pInt,ext_msg=key)
|
||||||
|
|
||||||
|
@ -538,7 +538,7 @@ character(len=65536) function getString(this,key,defaultVal,raw)
|
||||||
endif
|
endif
|
||||||
endif
|
endif
|
||||||
item => item%next
|
item => item%next
|
||||||
end do
|
enddo
|
||||||
|
|
||||||
if (.not. found) call IO_error(140_pInt,ext_msg=key)
|
if (.not. found) call IO_error(140_pInt,ext_msg=key)
|
||||||
|
|
||||||
|
@ -584,7 +584,7 @@ function getFloats(this,key,defaultVal,requiredShape,requiredSize)
|
||||||
enddo
|
enddo
|
||||||
endif
|
endif
|
||||||
item => item%next
|
item => item%next
|
||||||
end do
|
enddo
|
||||||
|
|
||||||
if (.not. found) then
|
if (.not. found) then
|
||||||
if (present(defaultVal)) then; getFloats = defaultVal; else; call IO_error(140_pInt,ext_msg=key); endif
|
if (present(defaultVal)) then; getFloats = defaultVal; else; call IO_error(140_pInt,ext_msg=key); endif
|
||||||
|
@ -635,7 +635,7 @@ function getInts(this,key,defaultVal,requiredShape,requiredSize)
|
||||||
enddo
|
enddo
|
||||||
endif
|
endif
|
||||||
item => item%next
|
item => item%next
|
||||||
end do
|
enddo
|
||||||
|
|
||||||
if (.not. found) then
|
if (.not. found) then
|
||||||
if (present(defaultVal)) then; getInts = defaultVal; else; call IO_error(140_pInt,ext_msg=key); endif
|
if (present(defaultVal)) then; getInts = defaultVal; else; call IO_error(140_pInt,ext_msg=key); endif
|
||||||
|
@ -712,7 +712,7 @@ function getStrings(this,key,defaultVal,requiredShape,raw)
|
||||||
endif notAllocated
|
endif notAllocated
|
||||||
endif
|
endif
|
||||||
item => item%next
|
item => item%next
|
||||||
end do
|
enddo
|
||||||
|
|
||||||
if (.not. found) then
|
if (.not. found) then
|
||||||
if (present(defaultVal)) then; getStrings = defaultVal; else; call IO_error(140_pInt,ext_msg=key); endif
|
if (present(defaultVal)) then; getStrings = defaultVal; else; call IO_error(140_pInt,ext_msg=key); endif
|
||||||
|
|
|
@ -189,7 +189,7 @@ subroutine plastic_disloUCLA_init()
|
||||||
allocate(dependentState(Ninstance))
|
allocate(dependentState(Ninstance))
|
||||||
|
|
||||||
|
|
||||||
do p = 1_pInt, size(phase_plasticityInstance)
|
do p = 1_pInt, size(phase_plasticity)
|
||||||
if (phase_plasticity(p) /= PLASTICITY_DISLOUCLA_ID) cycle
|
if (phase_plasticity(p) /= PLASTICITY_DISLOUCLA_ID) cycle
|
||||||
associate(prm => param(phase_plasticityInstance(p)), &
|
associate(prm => param(phase_plasticityInstance(p)), &
|
||||||
dot => dotState(phase_plasticityInstance(p)), &
|
dot => dotState(phase_plasticityInstance(p)), &
|
||||||
|
@ -325,7 +325,7 @@ subroutine plastic_disloUCLA_init()
|
||||||
prm%outputID = [prm%outputID, outputID]
|
prm%outputID = [prm%outputID, outputID]
|
||||||
endif
|
endif
|
||||||
|
|
||||||
end do
|
enddo
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! allocate state arrays
|
! allocate state arrays
|
||||||
|
|
|
@ -91,7 +91,7 @@ subroutine plastic_isotropic_init()
|
||||||
debug_levelExtensive, &
|
debug_levelExtensive, &
|
||||||
#endif
|
#endif
|
||||||
debug_level, &
|
debug_level, &
|
||||||
debug_constitutive,&
|
debug_constitutive, &
|
||||||
debug_levelBasic
|
debug_levelBasic
|
||||||
use IO, only: &
|
use IO, only: &
|
||||||
IO_error, &
|
IO_error, &
|
||||||
|
@ -148,7 +148,7 @@ subroutine plastic_isotropic_init()
|
||||||
allocate(state(Ninstance))
|
allocate(state(Ninstance))
|
||||||
allocate(dotState(Ninstance))
|
allocate(dotState(Ninstance))
|
||||||
|
|
||||||
do p = 1_pInt, size(phase_plasticityInstance)
|
do p = 1_pInt, size(phase_plasticity)
|
||||||
if (phase_plasticity(p) /= PLASTICITY_ISOTROPIC_ID) cycle
|
if (phase_plasticity(p) /= PLASTICITY_ISOTROPIC_ID) cycle
|
||||||
associate(prm => param(phase_plasticityInstance(p)), &
|
associate(prm => param(phase_plasticityInstance(p)), &
|
||||||
dot => dotState(phase_plasticityInstance(p)), &
|
dot => dotState(phase_plasticityInstance(p)), &
|
||||||
|
@ -217,7 +217,7 @@ subroutine plastic_isotropic_init()
|
||||||
prm%outputID = [prm%outputID, outputID]
|
prm%outputID = [prm%outputID, outputID]
|
||||||
endif
|
endif
|
||||||
|
|
||||||
end do
|
enddo
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! allocate state arrays
|
! allocate state arrays
|
||||||
|
|
|
@ -1,7 +1,8 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
||||||
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
||||||
!> @brief material subroutine for purely elastic material
|
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
|
||||||
|
!> @brief Dummy plasticity for purely elastic material
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module plastic_none
|
module plastic_none
|
||||||
|
|
||||||
|
@ -13,7 +14,6 @@ module plastic_none
|
||||||
|
|
||||||
contains
|
contains
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief module initialization
|
!> @brief module initialization
|
||||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||||
|
@ -32,52 +32,40 @@ subroutine plastic_none_init
|
||||||
debug_levelBasic
|
debug_levelBasic
|
||||||
use IO, only: &
|
use IO, only: &
|
||||||
IO_timeStamp
|
IO_timeStamp
|
||||||
use numerics, only: &
|
|
||||||
numerics_integrator
|
|
||||||
use material, only: &
|
use material, only: &
|
||||||
phase_plasticity, &
|
phase_plasticity, &
|
||||||
|
material_allocatePlasticState, &
|
||||||
PLASTICITY_NONE_label, &
|
PLASTICITY_NONE_label, &
|
||||||
|
PLASTICITY_NONE_ID, &
|
||||||
material_phase, &
|
material_phase, &
|
||||||
plasticState, &
|
plasticState
|
||||||
PLASTICITY_none_ID
|
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
|
|
||||||
integer(pInt) :: &
|
integer(pInt) :: &
|
||||||
maxNinstance, &
|
Ninstance, &
|
||||||
phase, &
|
p, &
|
||||||
NofMyPhase
|
NipcMyPhase
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- plastic_'//PLASTICITY_NONE_label//' init -+>>>'
|
write(6,'(/,a)') ' <<<+- plastic_'//PLASTICITY_NONE_label//' init -+>>>'
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
||||||
#include "compilation_info.f90"
|
#include "compilation_info.f90"
|
||||||
|
|
||||||
maxNinstance = int(count(phase_plasticity == PLASTICITY_none_ID),pInt)
|
Ninstance = int(count(phase_plasticity == PLASTICITY_NONE_ID),pInt)
|
||||||
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) &
|
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) &
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',maxNinstance
|
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
||||||
|
|
||||||
initializeInstances: do phase = 1_pInt, size(phase_plasticity)
|
do p = 1_pInt, size(phase_plasticity)
|
||||||
if (phase_plasticity(phase) == PLASTICITY_none_ID) then
|
if (phase_plasticity(p) /= PLASTICITY_NONE_ID) cycle
|
||||||
NofMyPhase=count(material_phase==phase)
|
|
||||||
|
|
||||||
allocate(plasticState(phase)%aTolState (0_pInt))
|
!--------------------------------------------------------------------------------------------------
|
||||||
allocate(plasticState(phase)%state0 (0_pInt,NofMyPhase))
|
! allocate state arrays
|
||||||
allocate(plasticState(phase)%partionedState0 (0_pInt,NofMyPhase))
|
NipcMyPhase = count(material_phase == p)
|
||||||
allocate(plasticState(phase)%subState0 (0_pInt,NofMyPhase))
|
|
||||||
allocate(plasticState(phase)%state (0_pInt,NofMyPhase))
|
|
||||||
|
|
||||||
allocate(plasticState(phase)%dotState (0_pInt,NofMyPhase))
|
call material_allocatePlasticState(p,NipcMyPhase,0_pInt,0_pInt,0_pInt, &
|
||||||
allocate(plasticState(phase)%deltaState (0_pInt,NofMyPhase))
|
0_pInt,0_pInt,0_pInt)
|
||||||
if (any(numerics_integrator == 1_pInt)) then
|
plasticState(p)%sizePostResults = 0_pInt
|
||||||
allocate(plasticState(phase)%previousDotState (0_pInt,NofMyPhase))
|
|
||||||
allocate(plasticState(phase)%previousDotState2(0_pInt,NofMyPhase))
|
enddo
|
||||||
endif
|
|
||||||
if (any(numerics_integrator == 4_pInt)) &
|
|
||||||
allocate(plasticState(phase)%RK4dotState (0_pInt,NofMyPhase))
|
|
||||||
if (any(numerics_integrator == 5_pInt)) &
|
|
||||||
allocate(plasticState(phase)%RKCK45dotState (6,0_pInt,NofMyPhase))
|
|
||||||
endif
|
|
||||||
enddo initializeInstances
|
|
||||||
|
|
||||||
end subroutine plastic_none_init
|
end subroutine plastic_none_init
|
||||||
|
|
||||||
|
|
|
@ -171,7 +171,7 @@ subroutine plastic_phenopowerlaw_init
|
||||||
allocate(state(Ninstance))
|
allocate(state(Ninstance))
|
||||||
allocate(dotState(Ninstance))
|
allocate(dotState(Ninstance))
|
||||||
|
|
||||||
do p = 1_pInt, size(phase_plasticityInstance)
|
do p = 1_pInt, size(phase_plasticity)
|
||||||
if (phase_plasticity(p) /= PLASTICITY_PHENOPOWERLAW_ID) cycle
|
if (phase_plasticity(p) /= PLASTICITY_PHENOPOWERLAW_ID) cycle
|
||||||
associate(prm => param(phase_plasticityInstance(p)), &
|
associate(prm => param(phase_plasticityInstance(p)), &
|
||||||
dot => dotState(phase_plasticityInstance(p)), &
|
dot => dotState(phase_plasticityInstance(p)), &
|
||||||
|
@ -336,7 +336,7 @@ subroutine plastic_phenopowerlaw_init
|
||||||
prm%outputID = [prm%outputID, outputID]
|
prm%outputID = [prm%outputID, outputID]
|
||||||
endif
|
endif
|
||||||
|
|
||||||
end do
|
enddo
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! allocate state arrays
|
! allocate state arrays
|
||||||
|
|
Loading…
Reference in New Issue