From d2dee587039a296e7b6af9c4efaceeb4a0e4186d Mon Sep 17 00:00:00 2001
From: Pratheek Shanthraj
Date: Tue, 23 Sep 2014 10:42:57 +0000
Subject: [PATCH] removed obsolete thermal and damage modules
---
code/constitutive_damage.f90 | 222 ----------------------------------
code/constitutive_thermal.f90 | 202 -------------------------------
2 files changed, 424 deletions(-)
delete mode 100644 code/constitutive_damage.f90
delete mode 100644 code/constitutive_thermal.f90
diff --git a/code/constitutive_damage.f90 b/code/constitutive_damage.f90
deleted file mode 100644
index dc9016965..000000000
--- a/code/constitutive_damage.f90
+++ /dev/null
@@ -1,222 +0,0 @@
-!--------------------------------------------------------------------------------------------------
-! $Id: constitutive_damage.f90 3205 2014-06-17 06:54:49Z MPIE\m.diehl $
-!--------------------------------------------------------------------------------------------------
-!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
-!> @author Luv Sharma, Max-Planck-Institut für Eisenforschung GmbH
-!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
-!> @brief damage internal microstructure state
-!--------------------------------------------------------------------------------------------------
-module constitutive_damage
- use prec, only: &
- pInt, &
- pReal
-
- implicit none
- private
- integer(pInt), public, protected :: &
- constitutive_damage_maxSizePostResults, &
- constitutive_damage_maxSizeDotState
-
- public :: &
- constitutive_damage_init, &
- constitutive_damage_microstructure, &
- constitutive_damage_collectDotState, &
- constitutive_damage_postResults
-
-contains
-
-
-!--------------------------------------------------------------------------------------------------
-!> @brief allocates arrays pointing to array of the various constitutive modules
-!--------------------------------------------------------------------------------------------------
-subroutine constitutive_damage_init
-
- use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
- use IO, only: &
- IO_open_file, &
- IO_open_jobFile_stat, &
- IO_write_jobFile, &
- IO_timeStamp
- use mesh, only: &
- mesh_maxNips, &
- mesh_NcpElems, &
- mesh_element, &
- FE_Nips, &
- FE_geomtype
- use material, only: &
- material_phase, &
- material_Nphase, &
- material_localFileExt, &
- material_configFile, &
- phase_name, &
- phase_damage, &
- phase_damageInstance, &
- phase_Noutput, &
- homogenization_Ngrains, &
- homogenization_maxNgrains, &
- damageState, &
- LOCAL_DAMAGE_NONE_ID, &
- LOCAL_DAMAGE_NONE_label, &
- LOCAL_DAMAGE_BRITTLE_ID, &
- LOCAL_DAMAGE_BRITTLE_label
-use damage_none
-use damage_brittle
-
- implicit none
- integer(pInt), parameter :: FILEUNIT = 200_pInt
- integer(pInt) :: &
- e, & !< grain number
- ph, &
- instance
-
- integer(pInt), dimension(:,:), pointer :: thisSize
- logical :: knownDamage
- character(len=64), dimension(:,:), pointer :: thisOutput
- character(len=32) :: outputName !< name of output, intermediate fix until HDF5 output is ready
-
-!--------------------------------------------------------------------------------------------------
-! parse plasticities from config file
- if (.not. IO_open_jobFile_stat(FILEUNIT,material_localFileExt)) & ! no local material configuration present...
- call IO_open_file(FILEUNIT,material_configFile) ! ... open material.config file
- if (any(phase_damage == LOCAL_DAMAGE_NONE_ID)) call damage_none_init(FILEUNIT)
- if (any(phase_damage == LOCAL_DAMAGE_BRITTLE_ID)) call damage_brittle_init(FILEUNIT)
- close(FILEUNIT)
-
- write(6,'(/,a)') ' <<<+- constitutive_damage init -+>>>'
- write(6,'(a)') ' $Id: constitutive_damage.f90 3205 2014-06-17 06:54:49Z MPIE\m.diehl $'
- write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
-#include "compilation_info.f90"
-
-!--------------------------------------------------------------------------------------------------
-! write description file for constitutive phase output
- call IO_write_jobFile(FILEUNIT,'outputDamage')
- do ph = 1_pInt,material_Nphase
- instance = phase_damageInstance(ph) ! which instance of a plasticity is present phase
- knownDamage = .true.
- select case(phase_damage(ph)) ! split per constititution
- case (LOCAL_DAMAGE_none_ID)
- outputName = LOCAL_DAMAGE_NONE_label
- thisOutput => null()
- thisSize => null()
- case (LOCAL_DAMAGE_BRITTLE_ID)
- outputName = LOCAL_DAMAGE_BRITTLE_label
- thisOutput => damage_brittle_output
- thisSize => damage_brittle_sizePostResult
- case default
- knownDamage = .false.
- end select
- write(FILEUNIT,'(/,a,/)') '['//trim(phase_name(ph))//']'
- if (knownDamage) then
- write(FILEUNIT,'(a)') '(damage)'//char(9)//trim(outputName)
- if (phase_damage(ph) /= LOCAL_DAMAGE_none_ID) then
- do e = 1_pInt,phase_Noutput(ph)
- write(FILEUNIT,'(a,i4)') trim(thisOutput(e,instance))//char(9),thisSize(e,instance)
- enddo
- endif
- endif
- enddo
- close(FILEUNIT)
-
-!--------------------------------------------------------------------------------------------------
-! allocation of states
- constitutive_damage_maxSizePostResults = 0_pInt
- constitutive_damage_maxSizeDotState = 0_pInt
- PhaseLoop:do ph = 1_pInt,material_Nphase ! loop over phases
- constitutive_damage_maxSizeDotState = max(constitutive_damage_maxSizeDotState, damageState(ph)%sizeDotState)
- constitutive_damage_maxSizePostResults = max(constitutive_damage_maxSizePostResults, damageState(ph)%sizePostResults)
- enddo PhaseLoop
-
-end subroutine constitutive_damage_init
-
-
-!--------------------------------------------------------------------------------------------------
-!> @brief calls microstructure function of the different constitutive models
-!--------------------------------------------------------------------------------------------------
-subroutine constitutive_damage_microstructure(Tstar_v, Fe, ipc, ip, el)
- use material, only: &
- material_phase, &
- LOCAL_DAMAGE_BRITTLE_ID, &
- phase_damage
- use damage_brittle, only: &
- damage_brittle_microstructure
-
- implicit none
- integer(pInt), intent(in) :: &
- ipc, & !< grain number
- ip, & !< integration point number
- el !< element number
- real(pReal), intent(in), dimension(6) :: &
- Tstar_v !< 2nd Piola Kirchhoff stress tensor (Mandel)
- real(pReal), intent(in), dimension(3,3) :: &
- Fe
-
- select case (phase_damage(material_phase(ipc,ip,el)))
- case (LOCAL_DAMAGE_BRITTLE_ID)
- call damage_brittle_microstructure(Tstar_v, Fe, ipc, ip, el)
-
- end select
-
-end subroutine constitutive_damage_microstructure
-
-
-!--------------------------------------------------------------------------------------------------
-!> @brief contains the constitutive equation for calculating the rate of change of microstructure
-!--------------------------------------------------------------------------------------------------
-subroutine constitutive_damage_collectDotState(Tstar_v, Fe, Lp, ipc, ip, el)
- use material, only: &
- material_phase, &
- LOCAL_DAMAGE_BRITTLE_ID, &
- phase_damage
- use damage_brittle, only: &
- damage_brittle_dotState
-
- implicit none
- integer(pInt), intent(in) :: &
- ipc, & !< grain number
- ip, & !< integration point number
- el !< element number
- real(pReal), intent(in), dimension(6) :: &
- Tstar_v !< 2nd Piola Kirchhoff stress tensor (Mandel)
- real(pReal), intent(in), dimension(3,3) :: &
- Lp, &
- Fe
-
- select case (phase_damage(material_phase(ipc,ip,el)))
- case (LOCAL_DAMAGE_BRITTLE_ID)
- call damage_brittle_dotState(Tstar_v, Fe, Lp, ipc, ip, el)
-
- end select
-
-end subroutine constitutive_damage_collectDotState
-
-!--------------------------------------------------------------------------------------------------
-!> @brief returns array of constitutive results
-!--------------------------------------------------------------------------------------------------
-function constitutive_damage_postResults(ipc, ip, el)
- use material, only: &
- damageState, &
- material_phase, &
- LOCAL_DAMAGE_BRITTLE_ID, &
- phase_damage
- use damage_brittle, only: &
- damage_brittle_postResults
-
- implicit none
- integer(pInt), intent(in) :: &
- ipc, & !< grain number
- ip, & !< integration point number
- el !< element number
- real(pReal), dimension(damageState(material_phase(ipc,ip,el))%sizePostResults) :: &
- constitutive_damage_postResults
-
- constitutive_damage_postResults = 0.0_pReal
-
- select case (phase_damage(material_phase(ipc,ip,el)))
- case (LOCAL_DAMAGE_BRITTLE_ID)
- constitutive_damage_postResults = damage_brittle_postResults(ipc, ip, el)
- end select
-
-end function constitutive_damage_postResults
-
-
-end module constitutive_damage
diff --git a/code/constitutive_thermal.f90 b/code/constitutive_thermal.f90
deleted file mode 100644
index feb09ad80..000000000
--- a/code/constitutive_thermal.f90
+++ /dev/null
@@ -1,202 +0,0 @@
-!--------------------------------------------------------------------------------------------------
-! $Id: constitutive_thermal.f90 3205 2014-06-17 06:54:49Z MPIE\m.diehl $
-!--------------------------------------------------------------------------------------------------
-!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
-!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
-!> @brief thermal internal microstructure state
-!--------------------------------------------------------------------------------------------------
-module constitutive_thermal
- use prec, only: &
- pInt, &
- pReal
-
- implicit none
- private
- integer(pInt), public, protected :: &
- constitutive_thermal_maxSizePostResults, &
- constitutive_thermal_maxSizeDotState
- public :: &
- constitutive_thermal_init, &
- constitutive_thermal_microstructure, &
- constitutive_thermal_collectDotState, &
- constitutive_thermal_postResults
-
-contains
-
-
-!--------------------------------------------------------------------------------------------------
-!> @brief allocates arrays pointing to array of the various constitutive modules
-!--------------------------------------------------------------------------------------------------
-subroutine constitutive_thermal_init
-
- use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
- use IO, only: &
- IO_open_file, &
- IO_open_jobFile_stat, &
- IO_write_jobFile, &
- IO_timeStamp
- use mesh, only: &
- mesh_maxNips, &
- mesh_NcpElems, &
- mesh_element, &
- FE_Nips, &
- FE_geomtype
- use material, only: &
- material_phase, &
- material_Nphase, &
- material_localFileExt, &
- material_configFile, &
- phase_name, &
- phase_thermal, &
- phase_thermalInstance, &
- phase_Noutput, &
- LOCAL_THERMAL_none_ID, &
- LOCAL_THERMAL_none_label, &
- LOCAL_THERMAL_heatgen_ID, &
- LOCAL_THERMAL_heatgen_label, &
- homogenization_Ngrains, &
- homogenization_maxNgrains, &
- thermalState
- use thermal_none
-
- implicit none
- integer(pInt), parameter :: FILEUNIT = 200_pInt
- integer(pInt) :: &
- e, & !< grain number
- ph, & !< phase
- instance
-
- integer(pInt), dimension(:,:), pointer :: thisSize
- logical :: knownThermal
- character(len=64), dimension(:,:), pointer :: thisOutput
- character(len=32) :: outputName !< name of output, intermediate fix until HDF5 output is ready
-
-!--------------------------------------------------------------------------------------------------
-! parse from config file
- if (.not. IO_open_jobFile_stat(FILEUNIT,material_localFileExt)) & ! no local material configuration present...
- call IO_open_file(FILEUNIT,material_configFile) ! ... open material.config file
- if (any(phase_thermal == LOCAL_THERMAL_none_ID)) call thermal_none_init(FILEUNIT)
-! if (any(phase_thermal == LOCAL_THERMAL_HEATGEN_ID)) call thermal_heatgen_init(FILEUNIT)
- close(FILEUNIT)
-
- write(6,'(/,a)') ' <<<+- constitutive_thermal init -+>>>'
- write(6,'(a)') ' $Id: constitutive_thermal.f90 3205 2014-06-17 06:54:49Z MPIE\m.diehl $'
- write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
-#include "compilation_info.f90"
-
-!--------------------------------------------------------------------------------------------------
-! write description file for constitutive phase output
- call IO_write_jobFile(FILEUNIT,'outputThermal')
- do ph = 1_pInt,material_Nphase
- instance = phase_thermalInstance(ph) ! which instance is present phase
- knownThermal = .true.
- select case(phase_thermal(ph)) ! split per constititution
- case (LOCAL_THERMAL_none_ID)
- outputName = LOCAL_THERMAL_NONE_label
- thisOutput => null()
- thisSize => null()
- case (LOCAL_THERMAL_heatgen_ID)
- outputName = LOCAL_THERMAL_HEATGEN_label
- thisOutput => null()
- thisSize => null()
- case default
- knownThermal = .false.
- end select
- write(FILEUNIT,'(/,a,/)') '['//trim(phase_name(ph))//']'
- if (knownThermal) then
- write(FILEUNIT,'(a)') '(thermal)'//char(9)//trim(outputName)
- if (phase_thermal(ph) /= LOCAL_THERMAL_none_ID) then
- do e = 1_pInt,phase_Noutput(ph)
- write(FILEUNIT,'(a,i4)') trim(thisOutput(e,instance))//char(9),thisSize(e,instance)
- enddo
- endif
- endif
- enddo
- close(FILEUNIT)
-
-!--------------------------------------------------------------------------------------------------
-! allocation of states
- constitutive_thermal_maxSizePostResults = 0_pInt
- constitutive_thermal_maxSizeDotState = 0_pInt
-
- PhaseLoop:do ph = 1_pInt,material_Nphase ! loop over phases
- constitutive_thermal_maxSizeDotState = max(constitutive_thermal_maxSizeDotState, thermalState(ph)%sizeDotState)
- constitutive_thermal_maxSizePostResults = max(constitutive_thermal_maxSizePostResults, thermalState(ph)%sizePostResults)
- enddo PhaseLoop
-
-end subroutine constitutive_thermal_init
-
-
-!--------------------------------------------------------------------------------------------------
-!> @brief calls microstructure function of the different constitutive models
-!--------------------------------------------------------------------------------------------------
-subroutine constitutive_thermal_microstructure(Tstar_v, Lp, ipc, ip, el)
- use material, only: &
- material_phase, &
- phase_thermal
-
- implicit none
- integer(pInt), intent(in) :: &
- ipc, & !< grain number
- ip, & !< integration point number
- el !< element number
- real(pReal), intent(in), dimension(6) :: &
- Tstar_v !< 2nd Piola Kirchhoff stress tensor (Mandel)
- real(pReal), intent(in), dimension(3,3) :: &
- Lp
-
-
-end subroutine constitutive_thermal_microstructure
-
-
-!--------------------------------------------------------------------------------------------------
-!> @brief contains the constitutive equation for calculating the rate of change of microstructure
-!--------------------------------------------------------------------------------------------------
-subroutine constitutive_thermal_collectDotState(Tstar_v, Lp, ipc, ip, el)
- use material, only: &
- material_phase, &
- LOCAL_THERMAL_none_ID, &
- LOCAL_THERMAL_HEATGEN_ID, &
- phase_thermal
-
- implicit none
- integer(pInt), intent(in) :: &
- ipc, & !< grain number
- ip, & !< integration point number
- el !< element number
- real(pReal), intent(in), dimension(6) :: &
- Tstar_v !< 2nd Piola Kirchhoff stress tensor (Mandel)
- real(pReal), intent(in), dimension(3,3) :: &
- Lp
-
- select case (phase_thermal(material_phase(ipc,ip,el)))
- case (LOCAL_THERMAL_HEATGEN_ID)
-! call thermal_adiabatic_dotState(Tstar_v, Lp, ipc, ip, el)
- end select
-
-end subroutine constitutive_thermal_collectDotState
-
-!--------------------------------------------------------------------------------------------------
-!> @brief returns array of constitutive results
-!--------------------------------------------------------------------------------------------------
-function constitutive_thermal_postResults(ipc, ip, el)
- use material, only: &
- thermalState, &
- material_phase, &
- phase_thermal
-
- implicit none
- integer(pInt), intent(in) :: &
- ipc, & !< grain number
- ip, & !< integration point number
- el !< element number
- real(pReal), dimension(thermalState(material_phase(ipc,ip,el))%sizePostResults) :: &
- constitutive_thermal_postResults
-
- constitutive_thermal_postResults = 0.0_pReal
-
-
-end function constitutive_thermal_postResults
-
-
-end module constitutive_thermal