phase out mesh_elem and theMesh

This commit is contained in:
Martin Diehl 2019-06-07 06:18:42 +02:00
parent d07cdf85de
commit 2a35a78d93
5 changed files with 49 additions and 92 deletions

View File

@ -344,7 +344,7 @@ subroutine CPFEM_general(mode, parallelExecution, ffn, ffn1, temperature_inp, dt
!* If no parallel execution is required, there is no need to collect FEM input !* If no parallel execution is required, there is no need to collect FEM input
if (.not. parallelExecution) then if (.not. parallelExecution) then
chosenThermal1: select case (thermal_type(mesh_element(3,elCP))) chosenThermal1: select case (thermal_type(material_homogenizationAt(elCP)))
case (THERMAL_conduction_ID) chosenThermal1 case (THERMAL_conduction_ID) chosenThermal1
temperature(material_homogenizationAt(elCP))%p(thermalMapping(material_homogenizationAt(elCP))%p(ip,elCP)) = & temperature(material_homogenizationAt(elCP))%p(thermalMapping(material_homogenizationAt(elCP))%p(ip,elCP)) = &
temperature_inp temperature_inp
@ -357,7 +357,7 @@ subroutine CPFEM_general(mode, parallelExecution, ffn, ffn1, temperature_inp, dt
if (rnd < 0.5_pReal) rnd = rnd - 1.0_pReal if (rnd < 0.5_pReal) rnd = rnd - 1.0_pReal
CPFEM_cs(1:6,ip,elCP) = rnd * CPFEM_odd_stress CPFEM_cs(1:6,ip,elCP) = rnd * CPFEM_odd_stress
CPFEM_dcsde(1:6,1:6,ip,elCP) = CPFEM_odd_jacobian * math_identity2nd(6) CPFEM_dcsde(1:6,1:6,ip,elCP) = CPFEM_odd_jacobian * math_identity2nd(6)
chosenThermal2: select case (thermal_type(mesh_element(3,elCP))) chosenThermal2: select case (thermal_type(material_homogenizationAt(elCP)))
case (THERMAL_conduction_ID) chosenThermal2 case (THERMAL_conduction_ID) chosenThermal2
temperature(material_homogenizationAt(elCP))%p(thermalMapping(material_homogenizationAt(elCP))%p(ip,elCP)) = & temperature(material_homogenizationAt(elCP))%p(thermalMapping(material_homogenizationAt(elCP))%p(ip,elCP)) = &
temperature_inp temperature_inp

View File

@ -30,6 +30,13 @@
module DAMASK_interface module DAMASK_interface
use prec use prec
#if __INTEL_COMPILER >= 1800
use, intrinsic :: iso_fortran_env, only: &
compiler_version, &
compiler_options
#endif
use ifport, only: &
CHDIR
implicit none implicit none
private private
@ -47,15 +54,7 @@ contains
!> @brief reports and sets working directory !> @brief reports and sets working directory
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine DAMASK_interface_init subroutine DAMASK_interface_init
#if __INTEL_COMPILER >= 1800
use, intrinsic :: iso_fortran_env, only: &
compiler_version, &
compiler_options
#endif
use ifport, only: &
CHDIR
implicit none
integer, dimension(8) :: & integer, dimension(8) :: &
dateAndTime dateAndTime
integer :: ierr integer :: ierr
@ -99,7 +98,6 @@ end subroutine DAMASK_interface_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
function getSolverJobName() function getSolverJobName()
implicit none
character(1024) :: getSolverJobName, inputName character(1024) :: getSolverJobName, inputName
character(len=*), parameter :: pathSep = achar(47)//achar(92) ! forward and backward slash character(len=*), parameter :: pathSep = achar(47)//achar(92) ! forward and backward slash
integer :: extPos integer :: extPos
@ -131,46 +129,11 @@ subroutine hypela2(d,g,e,de,s,t,dt,ngens,m,nn,kcus,matus,ndi,nshear,disp, &
strechn1,eigvn1,ncrd,itel,ndeg,ndm,nnode, & strechn1,eigvn1,ncrd,itel,ndeg,ndm,nnode, &
jtype,lclass,ifr,ifu) jtype,lclass,ifr,ifu)
use prec use prec
use numerics, only: & use numerics
!$ DAMASK_NumThreadsInt, & use FEsolving
numerics_unitlength, & use debug
usePingPong use mesh
use FEsolving, only: & use CPFEM
calcMode, &
terminallyIll, &
symmetricSolver
use debug, only: &
debug_level, &
debug_LEVELBASIC, &
debug_MARC, &
debug_info, &
debug_reset
use mesh, only: &
theMesh, &
mesh_FEasCP, &
mesh_element, &
mesh_node0, &
mesh_node, &
mesh_cellnode, &
mesh_build_cellnodes, &
mesh_build_ipCoordinates
use CPFEM, only: &
CPFEM_general, &
CPFEM_init_done, &
CPFEM_initAll, &
CPFEM_CALCRESULTS, &
CPFEM_AGERESULTS, &
CPFEM_COLLECT, &
CPFEM_RESTOREJACOBIAN, &
CPFEM_BACKUPJACOBIAN, &
cycleCounter, &
theInc, &
theTime, &
theDelta, &
lastIncConverged, &
outdatedByNewInc, &
outdatedFFN1, &
lastLovl
implicit none implicit none
!$ include "omp_lib.h" ! the openMP function library !$ include "omp_lib.h" ! the openMP function library
@ -318,7 +281,7 @@ subroutine hypela2(d,g,e,de,s,t,dt,ngens,m,nn,kcus,matus,ndi,nshear,disp, &
lastIncConverged = .false. ! reset flag lastIncConverged = .false. ! reset flag
endif endif
do node = 1,theMesh%elem%nNodes do node = 1,theMesh%elem%nNodes
CPnodeID = mesh_element(4+node,cp_en) !CPnodeID = mesh_element(4+node,cp_en)
!mesh_node(1:ndeg,CPnodeID) = mesh_node0(1:ndeg,CPnodeID) + numerics_unitlength * dispt(1:ndeg,node) !mesh_node(1:ndeg,CPnodeID) = mesh_node0(1:ndeg,CPnodeID) + numerics_unitlength * dispt(1:ndeg,node)
enddo enddo
endif endif
@ -371,10 +334,8 @@ end subroutine hypela2
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine flux(f,ts,n,time) subroutine flux(f,ts,n,time)
use prec use prec
use thermal_conduction, only: & use thermal_conduction
thermal_conduction_getSourceAndItsTangent use mesh
use mesh, only: &
mesh_FEasCP
implicit none implicit none
real(pReal), dimension(6), intent(in) :: & real(pReal), dimension(6), intent(in) :: &
@ -397,8 +358,7 @@ subroutine flux(f,ts,n,time)
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine uedinc(inc,incsub) subroutine uedinc(inc,incsub)
use prec use prec
use CPFEM, only: & use CPFEM
CPFEM_results
implicit none implicit none
integer, intent(in) :: inc, incsub integer, intent(in) :: inc, incsub
@ -415,13 +375,9 @@ end subroutine uedinc
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine plotv(v,s,sp,etot,eplas,ecreep,t,m,nn,layer,ndi,nshear,jpltcd) subroutine plotv(v,s,sp,etot,eplas,ecreep,t,m,nn,layer,ndi,nshear,jpltcd)
use prec use prec
use mesh, only: & use mesh
mesh_FEasCP use IO
use IO, only: & use homogenization
IO_error
use homogenization, only: &
materialpoint_results,&
materialpoint_sizeResults
implicit none implicit none
integer, intent(in) :: & integer, intent(in) :: &

View File

@ -364,7 +364,7 @@ subroutine crystallite_init
call IO_write_jobFile(FILEUNIT,'outputCrystallite') call IO_write_jobFile(FILEUNIT,'outputCrystallite')
do r = 1,size(config_crystallite) do r = 1,size(config_crystallite)
if (any(microstructure_crystallite(mesh_element(4,:)) == r)) then if (any(microstructure_crystallite(material_microstructureAt(:)) == r)) then
write(FILEUNIT,'(/,a,/)') '['//trim(crystallite_name(r))//']' write(FILEUNIT,'(/,a,/)') '['//trim(crystallite_name(r))//']'
do o = 1,crystallite_Noutput(r) do o = 1,crystallite_Noutput(r)
write(FILEUNIT,'(a,i4)') trim(crystallite_output(o,r))//char(9),crystallite_sizePostResult(o,r) write(FILEUNIT,'(a,i4)') trim(crystallite_output(o,r))//char(9),crystallite_sizePostResult(o,r)
@ -884,7 +884,7 @@ function crystallite_postResults(ipc, ip, el)
ip, & !< integration point index ip, & !< integration point index
ipc !< grain index ipc !< grain index
real(pReal), dimension(1+crystallite_sizePostResults(microstructure_crystallite(mesh_element(4,el))) + & real(pReal), dimension(1+crystallite_sizePostResults(microstructure_crystallite(material_microstructureAt(el))) + &
1+plasticState(material_phase(ipc,ip,el))%sizePostResults + & 1+plasticState(material_phase(ipc,ip,el))%sizePostResults + &
sum(sourceState(material_phase(ipc,ip,el))%p(:)%sizePostResults)) :: & sum(sourceState(material_phase(ipc,ip,el))%p(:)%sizePostResults)) :: &
crystallite_postResults crystallite_postResults
@ -896,7 +896,7 @@ function crystallite_postResults(ipc, ip, el)
n n
type(rotation) :: rot type(rotation) :: rot
crystID = microstructure_crystallite(mesh_element(4,el)) crystID = microstructure_crystallite(material_microstructureAt(el))
crystallite_postResults = 0.0_pReal crystallite_postResults = 0.0_pReal
crystallite_postResults(1) = real(crystallite_sizePostResults(crystID),pReal) ! header-like information (length) crystallite_postResults(1) = real(crystallite_sizePostResults(crystID),pReal) ! header-like information (length)

View File

@ -18,6 +18,7 @@ module material
use debug use debug
use mesh use mesh
use numerics use numerics
use discretization
implicit none implicit none
private private
@ -339,11 +340,11 @@ subroutine material_init
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
! new mappings ! new mappings
allocate(material_homogenizationAt,source=theMesh%homogenizationAt) allocate(material_homogenizationAt,source=theMesh%homogenizationAt)
allocate(material_homogenizationMemberAt(theMesh%elem%nIPs,theMesh%Nelems),source=0) allocate(material_homogenizationMemberAt(discretization_nIP,discretization_nElem),source=0)
allocate(CounterHomogenization(size(config_homogenization)),source=0) allocate(CounterHomogenization(size(config_homogenization)),source=0)
do e = 1, theMesh%Nelems do e = 1, discretization_nElem
do i = 1, theMesh%elem%nIPs do i = 1, discretization_nIP
CounterHomogenization(material_homogenizationAt(e)) = & CounterHomogenization(material_homogenizationAt(e)) = &
CounterHomogenization(material_homogenizationAt(e)) + 1 CounterHomogenization(material_homogenizationAt(e)) + 1
material_homogenizationMemberAt(i,e) = CounterHomogenization(material_homogenizationAt(e)) material_homogenizationMemberAt(i,e) = CounterHomogenization(material_homogenizationAt(e))
@ -351,12 +352,12 @@ subroutine material_init
enddo enddo
allocate(material_phaseAt(homogenization_maxNgrains,theMesh%Nelems), source=material_phase(:,1,:)) allocate(material_phaseAt(homogenization_maxNgrains,discretization_nElem), source=material_phase(:,1,:))
allocate(material_phaseMemberAt(homogenization_maxNgrains,theMesh%elem%nIPs,theMesh%Nelems),source=0) allocate(material_phaseMemberAt(homogenization_maxNgrains,discretization_nIP,discretization_nElem),source=0)
allocate(CounterPhase(size(config_phase)),source=0) allocate(CounterPhase(size(config_phase)),source=0)
do e = 1, theMesh%Nelems do e = 1, discretization_nElem
do i = 1, theMesh%elem%nIPs do i = 1, discretization_nIP
do c = 1, homogenization_maxNgrains do c = 1, homogenization_maxNgrains
CounterPhase(material_phaseAt(c,e)) = & CounterPhase(material_phaseAt(c,e)) = &
CounterPhase(material_phaseAt(c,e)) + 1 CounterPhase(material_phaseAt(c,e)) + 1
@ -377,18 +378,18 @@ subroutine material_init
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
! BEGIN DEPRECATED ! BEGIN DEPRECATED
allocate(phaseAt ( homogenization_maxNgrains,theMesh%elem%nIPs,theMesh%Nelems),source=0) allocate(phaseAt ( homogenization_maxNgrains,discretization_nIP,discretization_nElem),source=0)
allocate(phasememberAt ( homogenization_maxNgrains,theMesh%elem%nIPs,theMesh%Nelems),source=0) allocate(phasememberAt ( homogenization_maxNgrains,discretization_nIP,discretization_nElem),source=0)
allocate(mappingHomogenization (2, theMesh%elem%nIPs,theMesh%Nelems),source=0) allocate(mappingHomogenization (2, discretization_nIP,discretization_nElem),source=0)
allocate(mappingHomogenizationConst( theMesh%elem%nIPs,theMesh%Nelems),source=1) allocate(mappingHomogenizationConst( discretization_nIP,discretization_nElem),source=1)
CounterHomogenization=0 CounterHomogenization=0
CounterPhase =0 CounterPhase =0
do e = 1,theMesh%Nelems do e = 1,discretization_nElem
myHomog = theMesh%homogenizationAt(e) myHomog = theMesh%homogenizationAt(e)
do i = 1, theMesh%elem%nIPs do i = 1, discretization_nIP
CounterHomogenization(myHomog) = CounterHomogenization(myHomog) + 1 CounterHomogenization(myHomog) = CounterHomogenization(myHomog) + 1
mappingHomogenization(1:2,i,e) = [CounterHomogenization(myHomog),huge(1)] mappingHomogenization(1:2,i,e) = [CounterHomogenization(myHomog),huge(1)]
do g = 1,homogenization_Ngrains(myHomog) do g = 1,homogenization_Ngrains(myHomog)
@ -524,7 +525,7 @@ subroutine material_parseMicrostructure
if(any(theMesh%microstructureAt > size(config_microstructure))) & if(any(theMesh%microstructureAt > size(config_microstructure))) &
call IO_error(155,ext_msg='More microstructures in geometry than sections in material.config') call IO_error(155,ext_msg='More microstructures in geometry than sections in material.config')
forall (e = 1:theMesh%Nelems) & forall (e = 1:discretization_nElem) &
microstructure_active(theMesh%microstructureAt(e)) = .true. ! current microstructure used in model? Elementwise view, maximum N operations for N elements microstructure_active(theMesh%microstructureAt(e)) = .true. ! current microstructure used in model? Elementwise view, maximum N operations for N elements
do m=1, size(config_microstructure) do m=1, size(config_microstructure)
@ -872,12 +873,12 @@ subroutine material_populateGrains
integer :: e,i,c,homog,micro integer :: e,i,c,homog,micro
allocate(material_phase(homogenization_maxNgrains,theMesh%elem%nIPs,theMesh%Nelems), source=0) allocate(material_phase(homogenization_maxNgrains,discretization_nIP,discretization_nElem), source=0)
allocate(material_texture(homogenization_maxNgrains,theMesh%elem%nIPs,theMesh%Nelems), source=0) allocate(material_texture(homogenization_maxNgrains,discretization_nIP,discretization_nElem), source=0)
allocate(material_EulerAngles(3,homogenization_maxNgrains,theMesh%elem%nIPs,theMesh%Nelems),source=0.0_pReal) allocate(material_EulerAngles(3,homogenization_maxNgrains,discretization_nIP,discretization_nElem),source=0.0_pReal)
do e = 1, theMesh%Nelems do e = 1, discretization_nElem
do i = 1, theMesh%elem%nIPs do i = 1, discretization_nIP
homog = theMesh%homogenizationAt(e) homog = theMesh%homogenizationAt(e)
micro = theMesh%microstructureAt(e) micro = theMesh%microstructureAt(e)
do c = 1, homogenization_Ngrains(homog) do c = 1, homogenization_Ngrains(homog)

View File

@ -665,7 +665,7 @@ subroutine plastic_nonlocal_init
enddo enddo
allocate(compatibility(2,maxval(totalNslip),maxval(totalNslip),theMesh%elem%nIPneighbors,theMesh%elem%nIPs,theMesh%nElems), & allocate(compatibility(2,maxval(totalNslip),maxval(totalNslip),theMesh%elem%nIPneighbors,discretization_nIP,discretization_nElem), &
source=0.0_pReal) source=0.0_pReal)
! BEGIN DEPRECATED---------------------------------------------------------------------------------- ! BEGIN DEPRECATED----------------------------------------------------------------------------------
@ -763,8 +763,8 @@ subroutine plastic_nonlocal_init
if (prm%rhoSglRandom > 0.0_pReal) then if (prm%rhoSglRandom > 0.0_pReal) then
! get the total volume of the instance ! get the total volume of the instance
do e = 1,theMesh%nElems do e = 1,discretization_nElem
do i = 1,theMesh%elem%nIPs do i = 1,discretization_nIP
if (material_phase(1,i,e) == phase) volume(phasememberAt(1,i,e)) = IPvolume(i,e) if (material_phase(1,i,e) == phase) volume(phasememberAt(1,i,e)) = IPvolume(i,e)
enddo enddo
enddo enddo
@ -1433,7 +1433,7 @@ subroutine plastic_nonlocal_dotState(Mp, Fe, Fp, Temperature, &
timestep !< substepped crystallite time increment timestep !< substepped crystallite time increment
real(pReal), dimension(3,3), intent(in) ::& real(pReal), dimension(3,3), intent(in) ::&
Mp !< MandelStress Mp !< MandelStress
real(pReal), dimension(3,3,homogenization_maxNgrains,theMesh%elem%nIPs,theMesh%nElems), intent(in) :: & real(pReal), dimension(3,3,homogenization_maxNgrains,discretization_nIP,discretization_nElem), intent(in) :: &
Fe, & !< elastic deformation gradient Fe, & !< elastic deformation gradient
Fp !< plastic deformation gradient Fp !< plastic deformation gradient
@ -1886,7 +1886,7 @@ subroutine plastic_nonlocal_updateCompatibility(orientation,i,e)
integer, intent(in) :: & integer, intent(in) :: &
i, & i, &
e e
type(rotation), dimension(1,theMesh%elem%nIPs,theMesh%nElems), intent(in) :: & type(rotation), dimension(1,discretization_nIP,discretization_nElem), intent(in) :: &
orientation ! crystal orientation in quaternions orientation ! crystal orientation in quaternions
integer :: & integer :: &