shorter names

need to prefix 'pass' to avoid name clashes that result in errors during
compilation
This commit is contained in:
Martin Diehl 2021-04-06 12:05:47 +02:00
parent 49804c6e44
commit d56f1acf36
6 changed files with 54 additions and 54 deletions

View File

@ -2,7 +2,7 @@
!> @author Martin Diehl, KU Leuven !> @author Martin Diehl, KU Leuven
!> @brief Dummy homogenization scheme for 1 constituent per material point !> @brief Dummy homogenization scheme for 1 constituent per material point
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
submodule(homogenization:damage) pass submodule(homogenization:damage) damage_pass
contains contains
@ -11,4 +11,4 @@ module subroutine pass_init
end subroutine pass_init end subroutine pass_init
end submodule pass end submodule damage_pass

View File

@ -7,51 +7,51 @@ submodule(homogenization) mechanical
interface interface
module subroutine mechanical_pass_init module subroutine pass_init
end subroutine mechanical_pass_init end subroutine pass_init
module subroutine mechanical_isostrain_init module subroutine isostrain_init
end subroutine mechanical_isostrain_init end subroutine isostrain_init
module subroutine mechanical_RGC_init(num_homogMech) module subroutine RGC_init(num_homogMech)
class(tNode), pointer, intent(in) :: & class(tNode), pointer, intent(in) :: &
num_homogMech !< pointer to mechanical homogenization numerics data num_homogMech !< pointer to mechanical homogenization numerics data
end subroutine mechanical_RGC_init end subroutine RGC_init
module subroutine mechanical_isostrain_partitionDeformation(F,avgF) module subroutine isostrain_partitionDeformation(F,avgF)
real(pReal), dimension (:,:,:), intent(out) :: F !< partitioned deformation gradient real(pReal), dimension (:,:,:), intent(out) :: F !< partitioned deformation gradient
real(pReal), dimension (3,3), intent(in) :: avgF !< average deformation gradient at material point real(pReal), dimension (3,3), intent(in) :: avgF !< average deformation gradient at material point
end subroutine mechanical_isostrain_partitionDeformation end subroutine isostrain_partitionDeformation
module subroutine mechanical_RGC_partitionDeformation(F,avgF,ce) module subroutine RGC_partitionDeformation(F,avgF,ce)
real(pReal), dimension (:,:,:), intent(out) :: F !< partitioned deformation gradient real(pReal), dimension (:,:,:), intent(out) :: F !< partitioned deformation gradient
real(pReal), dimension (3,3), intent(in) :: avgF !< average deformation gradient at material point real(pReal), dimension (3,3), intent(in) :: avgF !< average deformation gradient at material point
integer, intent(in) :: & integer, intent(in) :: &
ce ce
end subroutine mechanical_RGC_partitionDeformation end subroutine RGC_partitionDeformation
module subroutine mechanical_isostrain_averageStressAndItsTangent(avgP,dAvgPdAvgF,P,dPdF,ho) module subroutine isostrain_averageStressAndItsTangent(avgP,dAvgPdAvgF,P,dPdF,ho)
real(pReal), dimension (3,3), intent(out) :: avgP !< average stress at material point real(pReal), dimension (3,3), intent(out) :: avgP !< average stress at material point
real(pReal), dimension (3,3,3,3), intent(out) :: dAvgPdAvgF !< average stiffness at material point real(pReal), dimension (3,3,3,3), intent(out) :: dAvgPdAvgF !< average stiffness at material point
real(pReal), dimension (:,:,:), intent(in) :: P !< partitioned stresses real(pReal), dimension (:,:,:), intent(in) :: P !< partitioned stresses
real(pReal), dimension (:,:,:,:,:), intent(in) :: dPdF !< partitioned stiffnesses real(pReal), dimension (:,:,:,:,:), intent(in) :: dPdF !< partitioned stiffnesses
integer, intent(in) :: ho integer, intent(in) :: ho
end subroutine mechanical_isostrain_averageStressAndItsTangent end subroutine isostrain_averageStressAndItsTangent
module subroutine mechanical_RGC_averageStressAndItsTangent(avgP,dAvgPdAvgF,P,dPdF,ho) module subroutine RGC_averageStressAndItsTangent(avgP,dAvgPdAvgF,P,dPdF,ho)
real(pReal), dimension (3,3), intent(out) :: avgP !< average stress at material point real(pReal), dimension (3,3), intent(out) :: avgP !< average stress at material point
real(pReal), dimension (3,3,3,3), intent(out) :: dAvgPdAvgF !< average stiffness at material point real(pReal), dimension (3,3,3,3), intent(out) :: dAvgPdAvgF !< average stiffness at material point
real(pReal), dimension (:,:,:), intent(in) :: P !< partitioned stresses real(pReal), dimension (:,:,:), intent(in) :: P !< partitioned stresses
real(pReal), dimension (:,:,:,:,:), intent(in) :: dPdF !< partitioned stiffnesses real(pReal), dimension (:,:,:,:,:), intent(in) :: dPdF !< partitioned stiffnesses
integer, intent(in) :: ho integer, intent(in) :: ho
end subroutine mechanical_RGC_averageStressAndItsTangent end subroutine RGC_averageStressAndItsTangent
module function mechanical_RGC_updateState(P,F,avgF,dt,dPdF,ce) result(doneAndHappy) module function RGC_updateState(P,F,avgF,dt,dPdF,ce) result(doneAndHappy)
logical, dimension(2) :: doneAndHappy logical, dimension(2) :: doneAndHappy
real(pReal), dimension(:,:,:), intent(in) :: & real(pReal), dimension(:,:,:), intent(in) :: &
P,& !< partitioned stresses P,& !< partitioned stresses
@ -61,13 +61,13 @@ submodule(homogenization) mechanical
real(pReal), intent(in) :: dt !< time increment real(pReal), intent(in) :: dt !< time increment
integer, intent(in) :: & integer, intent(in) :: &
ce !< cell ce !< cell
end function mechanical_RGC_updateState end function RGC_updateState
module subroutine mechanical_RGC_results(ho,group) module subroutine RGC_results(ho,group)
integer, intent(in) :: ho !< homogenization type integer, intent(in) :: ho !< homogenization type
character(len=*), intent(in) :: group !< group name in HDF5 file character(len=*), intent(in) :: group !< group name in HDF5 file
end subroutine mechanical_RGC_results end subroutine RGC_results
end interface end interface
@ -92,9 +92,9 @@ module subroutine mechanical_init(num_homog)
allocate(homogenization_P(3,3,discretization_nIPs*discretization_Nelems), source=0.0_pReal) allocate(homogenization_P(3,3,discretization_nIPs*discretization_Nelems), source=0.0_pReal)
num_homogMech => num_homog%get('mech',defaultVal=emptyDict) num_homogMech => num_homog%get('mech',defaultVal=emptyDict)
if (any(homogenization_type == HOMOGENIZATION_NONE_ID)) call mechanical_pass_init if (any(homogenization_type == HOMOGENIZATION_NONE_ID)) call pass_init
if (any(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID)) call mechanical_isostrain_init if (any(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID)) call isostrain_init
if (any(homogenization_type == HOMOGENIZATION_RGC_ID)) call mechanical_RGC_init(num_homogMech) if (any(homogenization_type == HOMOGENIZATION_RGC_ID)) call RGC_init(num_homogMech)
end subroutine mechanical_init end subroutine mechanical_init
@ -119,10 +119,10 @@ module subroutine mechanical_partition(subF,ce)
Fs(1:3,1:3,1) = subF Fs(1:3,1:3,1) = subF
case (HOMOGENIZATION_ISOSTRAIN_ID) chosenHomogenization case (HOMOGENIZATION_ISOSTRAIN_ID) chosenHomogenization
call mechanical_isostrain_partitionDeformation(Fs,subF) call isostrain_partitionDeformation(Fs,subF)
case (HOMOGENIZATION_RGC_ID) chosenHomogenization case (HOMOGENIZATION_RGC_ID) chosenHomogenization
call mechanical_RGC_partitionDeformation(Fs,subF,ce) call RGC_partitionDeformation(Fs,subF,ce)
end select chosenHomogenization end select chosenHomogenization
@ -158,7 +158,7 @@ module subroutine mechanical_homogenize(dt,ce)
dPdFs(:,:,:,:,co) = phase_mechanical_dPdF(dt,co,ce) dPdFs(:,:,:,:,co) = phase_mechanical_dPdF(dt,co,ce)
Ps(:,:,co) = phase_mechanical_getP(co,ce) Ps(:,:,co) = phase_mechanical_getP(co,ce)
enddo enddo
call mechanical_isostrain_averageStressAndItsTangent(& call isostrain_averageStressAndItsTangent(&
homogenization_P(1:3,1:3,ce), & homogenization_P(1:3,1:3,ce), &
homogenization_dPdF(1:3,1:3,1:3,1:3,ce),& homogenization_dPdF(1:3,1:3,1:3,1:3,ce),&
Ps,dPdFs, & Ps,dPdFs, &
@ -169,7 +169,7 @@ module subroutine mechanical_homogenize(dt,ce)
dPdFs(:,:,:,:,co) = phase_mechanical_dPdF(dt,co,ce) dPdFs(:,:,:,:,co) = phase_mechanical_dPdF(dt,co,ce)
Ps(:,:,co) = phase_mechanical_getP(co,ce) Ps(:,:,co) = phase_mechanical_getP(co,ce)
enddo enddo
call mechanical_RGC_averageStressAndItsTangent(& call RGC_averageStressAndItsTangent(&
homogenization_P(1:3,1:3,ce), & homogenization_P(1:3,1:3,ce), &
homogenization_dPdF(1:3,1:3,1:3,1:3,ce),& homogenization_dPdF(1:3,1:3,1:3,1:3,ce),&
Ps,dPdFs, & Ps,dPdFs, &
@ -206,7 +206,7 @@ module function mechanical_updateState(subdt,subF,ce) result(doneAndHappy)
Fs(:,:,co) = phase_mechanical_getF(co,ce) Fs(:,:,co) = phase_mechanical_getF(co,ce)
Ps(:,:,co) = phase_mechanical_getP(co,ce) Ps(:,:,co) = phase_mechanical_getP(co,ce)
enddo enddo
doneAndHappy = mechanical_RGC_updateState(Ps,Fs,subF,subdt,dPdFs,ce) doneAndHappy = RGC_updateState(Ps,Fs,subF,subdt,dPdFs,ce)
else else
doneAndHappy = .true. doneAndHappy = .true.
endif endif
@ -230,7 +230,7 @@ module subroutine mechanical_results(group_base,ho)
select case(homogenization_type(ho)) select case(homogenization_type(ho))
case(HOMOGENIZATION_rgc_ID) case(HOMOGENIZATION_rgc_ID)
call mechanical_RGC_results(ho,group) call RGC_results(ho,group)
end select end select

View File

@ -71,7 +71,7 @@ contains
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief allocates all necessary fields, reads information from material configuration file !> @brief allocates all necessary fields, reads information from material configuration file
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module subroutine mechanical_RGC_init(num_homogMech) module subroutine RGC_init(num_homogMech)
class(tNode), pointer, intent(in) :: & class(tNode), pointer, intent(in) :: &
num_homogMech !< pointer to mechanical homogenization numerics data num_homogMech !< pointer to mechanical homogenization numerics data
@ -152,7 +152,7 @@ module subroutine mechanical_RGC_init(num_homogMech)
prm%N_constituents = homogMech%get_as1dInt('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 (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')
@ -187,13 +187,13 @@ module subroutine mechanical_RGC_init(num_homogMech)
enddo enddo
end subroutine mechanical_RGC_init end subroutine RGC_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief partitions the deformation gradient onto the constituents !> @brief partitions the deformation gradient onto the constituents
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module subroutine mechanical_RGC_partitionDeformation(F,avgF,ce) module subroutine RGC_partitionDeformation(F,avgF,ce)
real(pReal), dimension (:,:,:), intent(out) :: F !< partitioned F per grain real(pReal), dimension (:,:,:), intent(out) :: F !< partitioned F per grain
@ -227,14 +227,14 @@ module subroutine mechanical_RGC_partitionDeformation(F,avgF,ce)
end associate end associate
end subroutine mechanical_RGC_partitionDeformation end subroutine RGC_partitionDeformation
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief update the internal state of the homogenization scheme and tell whether "done" and !> @brief update the internal state of the homogenization scheme and tell whether "done" and
! "happy" with result ! "happy" with result
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module function mechanical_RGC_updateState(P,F,avgF,dt,dPdF,ce) result(doneAndHappy) module function RGC_updateState(P,F,avgF,dt,dPdF,ce) result(doneAndHappy)
logical, dimension(2) :: doneAndHappy logical, dimension(2) :: doneAndHappy
real(pReal), dimension(:,:,:), intent(in) :: & real(pReal), dimension(:,:,:), intent(in) :: &
P,& !< partitioned stresses P,& !< partitioned stresses
@ -697,13 +697,13 @@ module function mechanical_RGC_updateState(P,F,avgF,dt,dPdF,ce) result(doneAndHa
end subroutine grainDeformation end subroutine grainDeformation
end function mechanical_RGC_updateState end function RGC_updateState
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief derive average stress and stiffness from constituent quantities !> @brief derive average stress and stiffness from constituent quantities
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module subroutine mechanical_RGC_averageStressAndItsTangent(avgP,dAvgPdAvgF,P,dPdF,ho) module subroutine RGC_averageStressAndItsTangent(avgP,dAvgPdAvgF,P,dPdF,ho)
real(pReal), dimension (3,3), intent(out) :: avgP !< average stress at material point real(pReal), dimension (3,3), intent(out) :: avgP !< average stress at material point
real(pReal), dimension (3,3,3,3), intent(out) :: dAvgPdAvgF !< average stiffness at material point real(pReal), dimension (3,3,3,3), intent(out) :: dAvgPdAvgF !< average stiffness at material point
@ -715,13 +715,13 @@ module subroutine mechanical_RGC_averageStressAndItsTangent(avgP,dAvgPdAvgF,P,dP
avgP = sum(P,3) /real(product(param(ho)%N_constituents),pReal) avgP = sum(P,3) /real(product(param(ho)%N_constituents),pReal)
dAvgPdAvgF = sum(dPdF,5)/real(product(param(ho)%N_constituents),pReal) dAvgPdAvgF = sum(dPdF,5)/real(product(param(ho)%N_constituents),pReal)
end subroutine mechanical_RGC_averageStressAndItsTangent end subroutine RGC_averageStressAndItsTangent
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief writes results to HDF5 output file !> @brief writes results to HDF5 output file
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module subroutine mechanical_RGC_results(ho,group) module subroutine RGC_results(ho,group)
integer, intent(in) :: ho integer, intent(in) :: ho
character(len=*), intent(in) :: group character(len=*), intent(in) :: group
@ -747,7 +747,7 @@ module subroutine mechanical_RGC_results(ho,group)
enddo outputsLoop enddo outputsLoop
end associate end associate
end subroutine mechanical_RGC_results end subroutine RGC_results
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------

View File

@ -26,7 +26,7 @@ contains
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief allocates all neccessary fields, reads information from material configuration file !> @brief allocates all neccessary fields, reads information from material configuration file
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module subroutine mechanical_isostrain_init module subroutine isostrain_init
integer :: & integer :: &
h, & h, &
@ -56,7 +56,7 @@ module subroutine mechanical_isostrain_init
case ('avg') case ('avg')
prm%mapping = average_ID prm%mapping = average_ID
case default case default
call IO_error(211,ext_msg='sum'//' (mechanical_isostrain)') call IO_error(211,ext_msg='sum'//' (isostrain)')
end select end select
Nmaterialpoints = count(material_homogenizationAt == h) Nmaterialpoints = count(material_homogenizationAt == h)
@ -68,13 +68,13 @@ module subroutine mechanical_isostrain_init
enddo enddo
end subroutine mechanical_isostrain_init end subroutine isostrain_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief partitions the deformation gradient onto the constituents !> @brief partitions the deformation gradient onto the constituents
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module subroutine mechanical_isostrain_partitionDeformation(F,avgF) module subroutine isostrain_partitionDeformation(F,avgF)
real(pReal), dimension (:,:,:), intent(out) :: F !< partitioned deformation gradient real(pReal), dimension (:,:,:), intent(out) :: F !< partitioned deformation gradient
@ -82,13 +82,13 @@ module subroutine mechanical_isostrain_partitionDeformation(F,avgF)
F = spread(avgF,3,size(F,3)) F = spread(avgF,3,size(F,3))
end subroutine mechanical_isostrain_partitionDeformation end subroutine isostrain_partitionDeformation
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief derive average stress and stiffness from constituent quantities !> @brief derive average stress and stiffness from constituent quantities
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module subroutine mechanical_isostrain_averageStressAndItsTangent(avgP,dAvgPdAvgF,P,dPdF,ho) module subroutine isostrain_averageStressAndItsTangent(avgP,dAvgPdAvgF,P,dPdF,ho)
real(pReal), dimension (3,3), intent(out) :: avgP !< average stress at material point real(pReal), dimension (3,3), intent(out) :: avgP !< average stress at material point
real(pReal), dimension (3,3,3,3), intent(out) :: dAvgPdAvgF !< average stiffness at material point real(pReal), dimension (3,3,3,3), intent(out) :: dAvgPdAvgF !< average stiffness at material point
@ -110,6 +110,6 @@ module subroutine mechanical_isostrain_averageStressAndItsTangent(avgP,dAvgPdAvg
end associate end associate
end subroutine mechanical_isostrain_averageStressAndItsTangent end subroutine isostrain_averageStressAndItsTangent
end submodule isostrain end submodule isostrain

View File

@ -4,14 +4,14 @@
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH !> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
!> @brief dummy homogenization homogenization scheme for 1 constituent per material point !> @brief dummy homogenization homogenization scheme for 1 constituent per material point
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
submodule(homogenization:mechanical) none submodule(homogenization:mechanical) mechanical_pass
contains contains
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief allocates all necessary fields, reads information from material configuration file !> @brief allocates all necessary fields, reads information from material configuration file
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module subroutine mechanical_pass_init module subroutine pass_init
integer :: & integer :: &
Ninstances, & Ninstances, &
@ -27,7 +27,7 @@ module subroutine mechanical_pass_init
if(homogenization_type(h) /= HOMOGENIZATION_NONE_ID) cycle if(homogenization_type(h) /= HOMOGENIZATION_NONE_ID) cycle
if(homogenization_Nconstituents(h) /= 1) & if(homogenization_Nconstituents(h) /= 1) &
call IO_error(211,ext_msg='N_constituents (mechanical_pass)') call IO_error(211,ext_msg='N_constituents (pass)')
Nmaterialpoints = count(material_homogenizationAt == h) Nmaterialpoints = count(material_homogenizationAt == h)
homogState(h)%sizeState = 0 homogState(h)%sizeState = 0
@ -36,6 +36,6 @@ module subroutine mechanical_pass_init
enddo enddo
end subroutine mechanical_pass_init end subroutine pass_init
end submodule none end submodule mechanical_pass

View File

@ -2,7 +2,7 @@
!> @author Martin Diehl, KU Leuven !> @author Martin Diehl, KU Leuven
!> @brief Dummy homogenization scheme for 1 constituent per material point !> @brief Dummy homogenization scheme for 1 constituent per material point
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
submodule(homogenization:thermal) pass submodule(homogenization:thermal) thermal_pass
contains contains
@ -11,4 +11,4 @@ module subroutine pass_init
end subroutine pass_init end subroutine pass_init
end submodule pass end submodule thermal_pass