general cleaning

This commit is contained in:
Martin Diehl 2019-03-09 01:07:26 +01:00
parent 60feb96afd
commit 0d08659b2a
17 changed files with 43 additions and 147 deletions

View File

@ -1,4 +1,4 @@
#!/usr/bin/env python2.7
#!/usr/bin/env python3
# -*- coding: UTF-8 no BOM -*-
import os,sys

View File

@ -446,7 +446,7 @@ subroutine setSIGUSR1(signal) bind(C)
integer(C_INT), value :: signal
SIGUSR1 = .true.
write(6,*) 'received signal ',signal, 'set SIGUSR1'
write(6,'(a,i2.2,a)') ' received signal ',signal, ', set SIGUSR1'
end subroutine setSIGUSR1
@ -461,7 +461,7 @@ subroutine setSIGUSR2(signal) bind(C)
integer(C_INT), value :: signal
SIGUSR2 = .true.
write(6,*) 'received signal ',signal, 'set SIGUSR2'
write(6,'(a,i2.2,a)') ' received signal ',signal, ', set SIGUSR2'
end subroutine setSIGUSR2

View File

@ -494,24 +494,12 @@ end subroutine utilities_indexActiveSet
!> @brief cleans up
!--------------------------------------------------------------------------------------------------
subroutine utilities_destroy()
!use material, only: &
! homogenization_Ngrains
!implicit none
!PetscInt :: homog, cryst, grain, phase
!PetscErrorCode :: ierr
!call PetscViewerHDF5PopGroup(resUnit, ierr); CHKERRQ(ierr)
!call VecDestroy(coordinatesVec,ierr); CHKERRQ(ierr)
!do homog = 1, material_Nhomogenization
! call VecDestroy(homogenizationResultsVec(homog),ierr);CHKERRQ(ierr)
! do cryst = 1, material_Ncrystallite; do grain = 1, homogenization_Ngrains(homog)
! call VecDestroy(crystalliteResultsVec(cryst,grain),ierr);CHKERRQ(ierr)
! enddo; enddo
! do phase = 1, material_Nphase; do grain = 1, homogenization_Ngrains(homog)
! call VecDestroy(phaseResultsVec(phase,grain),ierr);CHKERRQ(ierr)
! enddo; enddo
!enddo
!call PetscViewerDestroy(resUnit, ierr); CHKERRQ(ierr)
end subroutine utilities_destroy

View File

@ -59,21 +59,11 @@ module config
microstructure_name, & !< name of each microstructure
texture_name !< name of each texture
! ToDo: make private, no one needs to know that
character(len=*), parameter, public :: &
MATERIAL_partHomogenization = 'homogenization', & !< keyword for homogenization part
MATERIAL_partCrystallite = 'crystallite', & !< keyword for crystallite part
MATERIAL_partPhase = 'phase', & !< keyword for phase part
MATERIAL_partMicrostructure = 'microstructure' !< keyword for microstructure part
character(len=*), parameter, private :: &
MATERIAL_partTexture = 'texture' !< keyword for texture part
! ToDo: Remove, use size(config_phase) etc
integer(pInt), public, protected :: &
material_Nphase, & !< number of phases
material_Nhomogenization, & !< number of homogenizations
material_Nmicrostructure, & !< number of microstructures
material_Ncrystallite !< number of crystallite settings
material_Nhomogenization !< number of homogenizations
public :: &
config_init, &
@ -126,40 +116,38 @@ subroutine config_init()
part = IO_lc(IO_getTag(line,'<','>'))
select case (trim(part))
case (trim(material_partPhase))
case (trim('phase'))
call parseFile(phase_name,config_phase,line,fileContent(i+1:))
if (iand(myDebug,debug_levelBasic) /= 0_pInt) write(6,'(a)') ' Phase parsed'; flush(6)
if (iand(myDebug,debug_levelBasic) /= 0) write(6,'(a)') ' Phase parsed'; flush(6)
case (trim(material_partMicrostructure))
case (trim('microstructure'))
call parseFile(microstructure_name,config_microstructure,line,fileContent(i+1:))
if (iand(myDebug,debug_levelBasic) /= 0_pInt) write(6,'(a)') ' Microstructure parsed'; flush(6)
if (iand(myDebug,debug_levelBasic) /= 0) write(6,'(a)') ' Microstructure parsed'; flush(6)
case (trim(material_partCrystallite))
case (trim('crystallite'))
call parseFile(crystallite_name,config_crystallite,line,fileContent(i+1:))
if (iand(myDebug,debug_levelBasic) /= 0_pInt) write(6,'(a)') ' Crystallite parsed'; flush(6)
if (iand(myDebug,debug_levelBasic) /= 0) write(6,'(a)') ' Crystallite parsed'; flush(6)
case (trim(material_partHomogenization))
case (trim('homogenization'))
call parseFile(homogenization_name,config_homogenization,line,fileContent(i+1:))
if (iand(myDebug,debug_levelBasic) /= 0_pInt) write(6,'(a)') ' Homogenization parsed'; flush(6)
if (iand(myDebug,debug_levelBasic) /= 0) write(6,'(a)') ' Homogenization parsed'; flush(6)
case (trim(material_partTexture))
case (trim('texture'))
call parseFile(texture_name,config_texture,line,fileContent(i+1:))
if (iand(myDebug,debug_levelBasic) /= 0_pInt) write(6,'(a)') ' Texture parsed'; flush(6)
if (iand(myDebug,debug_levelBasic) /= 0) write(6,'(a)') ' Texture parsed'; flush(6)
end select
enddo
material_Nhomogenization = size(config_homogenization)
material_Nmicrostructure = size(config_microstructure)
material_Ncrystallite = size(config_crystallite)
material_Nphase = size(config_phase)
if (material_Nhomogenization < 1_pInt) call IO_error(160_pInt,ext_msg=material_partHomogenization)
if (material_Nmicrostructure < 1_pInt) call IO_error(160_pInt,ext_msg=material_partMicrostructure)
if (material_Ncrystallite < 1_pInt) call IO_error(160_pInt,ext_msg=material_partCrystallite)
if (material_Nphase < 1_pInt) call IO_error(160_pInt,ext_msg=material_partPhase)
if (size(config_texture) < 1_pInt) call IO_error(160_pInt,ext_msg=material_partTexture)
if (material_Nhomogenization < 1) call IO_error(160_pInt,ext_msg='<homogenization>')
if (size(config_microstructure) < 1) call IO_error(160_pInt,ext_msg='<microstructure>')
if (size(config_crystallite) < 1) call IO_error(160_pInt,ext_msg='<crystallite>')
if (material_Nphase < 1) call IO_error(160_pInt,ext_msg='<phase>')
if (size(config_texture) < 1) call IO_error(160_pInt,ext_msg='<texture>')
end subroutine config_init

View File

@ -114,11 +114,6 @@ contains
!> @details reads in material parameters, allocates arrays, and does sanity checks
!--------------------------------------------------------------------------------------------------
subroutine plastic_disloUCLA_init()
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
use, intrinsic :: iso_fortran_env, only: &
compiler_version, &
compiler_options
#endif
use prec, only: &
pStringLen
use debug, only: &
@ -128,8 +123,7 @@ subroutine plastic_disloUCLA_init()
use math, only: &
math_expand
use IO, only: &
IO_error, &
IO_timeStamp
IO_error
use material, only: &
phase_plasticity, &
phase_plasticityInstance, &
@ -140,7 +134,6 @@ subroutine plastic_disloUCLA_init()
material_phase, &
plasticState
use config, only: &
MATERIAL_partPhase, &
config_phase
use lattice
@ -167,8 +160,6 @@ subroutine plastic_disloUCLA_init()
write(6,'(/,a)') ' <<<+- plastic_'//PLASTICITY_DISLOUCLA_label//' init -+>>>'
write(6,'(/,a)') ' Cereceda et al., International Journal of Plasticity 78, 2016, 242-256'
write(6,'(/,a)') ' http://dx.doi.org/10.1016/j.ijplas.2015.09.002'
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
#include "compilation_info.f90"
Ninstance = int(count(phase_plasticity == PLASTICITY_DISLOUCLA_ID),pInt)
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) &

View File

@ -182,11 +182,6 @@ contains
!> @details reads in material parameters, allocates arrays, and does sanity checks
!--------------------------------------------------------------------------------------------------
subroutine plastic_dislotwin_init
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
use, intrinsic :: iso_fortran_env, only: &
compiler_version, &
compiler_options
#endif
use prec, only: &
pStringLen, &
dEq0, &
@ -200,9 +195,7 @@ subroutine plastic_dislotwin_init
math_expand,&
PI
use IO, only: &
IO_warning, &
IO_error, &
IO_timeStamp
IO_error
use material, only: &
phase_plasticity, &
phase_plasticityInstance, &
@ -213,7 +206,6 @@ subroutine plastic_dislotwin_init
material_phase, &
plasticState
use config, only: &
MATERIAL_partPhase, &
config_phase
use lattice
@ -244,10 +236,8 @@ subroutine plastic_dislotwin_init
write(6,'(a)') ' https://doi.org/10.1016/j.commatsci.2006.04.014'
write(6,'(/,a)') ' Wong et al., Acta Materialia, 118:140151, 2016'
write(6,'(a,/)') ' https://doi.org/10.1016/j.actamat.2016.07.032'
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
#include "compilation_info.f90"
Ninstance = int(count(phase_plasticity == PLASTICITY_DISLOTWIN_ID),pInt)
Ninstance = count(phase_plasticity == PLASTICITY_DISLOTWIN_ID)
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) &
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance

View File

@ -76,12 +76,7 @@ contains
!> @brief module initialization
!> @details reads in material parameters, allocates arrays, and does sanity checks
!--------------------------------------------------------------------------------------------------
subroutine plastic_isotropic_init()
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
use, intrinsic :: iso_fortran_env, only: &
compiler_version, &
compiler_options
#endif
subroutine plastic_isotropic_init
use prec, only: &
pStringLen
use debug, only: &
@ -95,8 +90,7 @@ subroutine plastic_isotropic_init()
debug_constitutive, &
debug_levelBasic
use IO, only: &
IO_error, &
IO_timeStamp
IO_error
use material, only: &
#ifdef DEBUG
phasememberAt, &
@ -110,7 +104,6 @@ subroutine plastic_isotropic_init()
material_phase, &
plasticState
use config, only: &
MATERIAL_partPhase, &
config_phase
use lattice
@ -134,10 +127,8 @@ subroutine plastic_isotropic_init()
write(6,'(/,a)') ' <<<+- plastic_'//PLASTICITY_ISOTROPIC_label//' init -+>>>'
write(6,'(/,a)') ' Maiti and Eisenlohr, Scripta Materialia, 145:37-40, 2018'
write(6,'(/,a)') ' https://doi.org/10.1016/j.scriptamat.2017.09.047'
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
#include "compilation_info.f90"
Ninstance = int(count(phase_plasticity == PLASTICITY_ISOTROPIC_ID),pInt)
Ninstance = count(phase_plasticity == PLASTICITY_ISOTROPIC_ID)
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) &
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance

View File

@ -95,11 +95,6 @@ contains
!> @details reads in material parameters, allocates arrays, and does sanity checks
!--------------------------------------------------------------------------------------------------
subroutine plastic_kinehardening_init
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
use, intrinsic :: iso_fortran_env, only: &
compiler_version, &
compiler_options
#endif
use prec, only: &
dEq0, &
pStringLen
@ -116,8 +111,7 @@ subroutine plastic_kinehardening_init
use math, only: &
math_expand
use IO, only: &
IO_error, &
IO_timeStamp
IO_error
use material, only: &
#ifdef DEBUG
phasememberAt, &
@ -131,7 +125,6 @@ subroutine plastic_kinehardening_init
material_phase, &
plasticState
use config, only: &
MATERIAL_partPhase, &
config_phase
use lattice
@ -156,11 +149,9 @@ subroutine plastic_kinehardening_init
outputs
write(6,'(/,a)') ' <<<+- plastic_'//PLASTICITY_KINEHARDENING_label//' init -+>>>'
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
#include "compilation_info.f90"
Ninstance = int(count(phase_plasticity == PLASTICITY_KINEHARDENING_ID),pInt)
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) &
Ninstance = count(phase_plasticity == PLASTICITY_KINEHARDENING_ID)
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
allocate(plastic_kinehardening_sizePostResult(maxval(phase_Noutput),Ninstance),source=0_pInt)

View File

@ -107,11 +107,6 @@ contains
!> @details reads in material parameters, allocates arrays, and does sanity checks
!--------------------------------------------------------------------------------------------------
subroutine plastic_phenopowerlaw_init
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
use, intrinsic :: iso_fortran_env, only: &
compiler_version, &
compiler_options
#endif
use prec, only: &
pStringLen
use debug, only: &
@ -121,8 +116,7 @@ subroutine plastic_phenopowerlaw_init
use math, only: &
math_expand
use IO, only: &
IO_error, &
IO_timeStamp
IO_error
use material, only: &
phase_plasticity, &
phase_plasticityInstance, &
@ -133,7 +127,6 @@ subroutine plastic_phenopowerlaw_init
material_phase, &
plasticState
use config, only: &
MATERIAL_partPhase, &
config_phase
use lattice
@ -158,14 +151,12 @@ subroutine plastic_phenopowerlaw_init
outputs
write(6,'(/,a)') ' <<<+- plastic_'//PLASTICITY_PHENOPOWERLAW_label//' init -+>>>'
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
#include "compilation_info.f90"
Ninstance = int(count(phase_plasticity == PLASTICITY_PHENOPOWERLAW_ID),pInt)
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) &
Ninstance = count(phase_plasticity == PLASTICITY_PHENOPOWERLAW_ID)
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
allocate(plastic_phenopowerlaw_sizePostResult(maxval(phase_Noutput),Ninstance),source=0_pInt)
allocate(plastic_phenopowerlaw_sizePostResult(maxval(phase_Noutput),Ninstance),source=0)
allocate(plastic_phenopowerlaw_output(maxval(phase_Noutput),Ninstance))
plastic_phenopowerlaw_output = ''

View File

@ -63,11 +63,6 @@ contains
!> @details reads in material parameters, allocates arrays, and does sanity checks
!--------------------------------------------------------------------------------------------------
subroutine source_damage_anisoBrittle_init
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
use, intrinsic :: iso_fortran_env, only: &
compiler_version, &
compiler_options
#endif
use prec, only: &
pStringLen
use debug, only: &
@ -89,8 +84,7 @@ subroutine source_damage_anisoBrittle_init
sourceState
use config, only: &
config_phase, &
material_Nphase, &
MATERIAL_partPhase
material_Nphase
use lattice, only: &
lattice_maxNcleavageFamily
@ -109,7 +103,6 @@ subroutine source_damage_anisoBrittle_init
outputs
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ANISOBRITTLE_LABEL//' init -+>>>'
#include "compilation_info.f90"
Ninstance = int(count(phase_source == SOURCE_damage_anisoBrittle_ID),pInt)
if (Ninstance == 0_pInt) return

View File

@ -62,11 +62,6 @@ contains
!> @details reads in material parameters, allocates arrays, and does sanity checks
!--------------------------------------------------------------------------------------------------
subroutine source_damage_anisoDuctile_init
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
use, intrinsic :: iso_fortran_env, only: &
compiler_version, &
compiler_options
#endif
use prec, only: &
pStringLen
use debug, only: &
@ -75,7 +70,7 @@ subroutine source_damage_anisoDuctile_init
debug_levelBasic
use IO, only: &
IO_error
use math, only: &
use math, only: &
math_expand
use material, only: &
material_allocateSourceState, &
@ -88,8 +83,7 @@ subroutine source_damage_anisoDuctile_init
sourceState
use config, only: &
config_phase, &
material_Nphase, &
MATERIAL_partPhase
material_Nphase
use lattice, only: &
lattice_maxNslipFamily
@ -109,9 +103,8 @@ subroutine source_damage_anisoDuctile_init
outputs
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ANISODUCTILE_LABEL//' init -+>>>'
#include "compilation_info.f90"
Ninstance = int(count(phase_source == SOURCE_damage_anisoDuctile_ID),pInt)
Ninstance = count(phase_source == SOURCE_damage_anisoDuctile_ID)
if (Ninstance == 0_pInt) return
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) &

View File

@ -53,11 +53,6 @@ contains
!> @details reads in material parameters, allocates arrays, and does sanity checks
!--------------------------------------------------------------------------------------------------
subroutine source_damage_isoBrittle_init
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
use, intrinsic :: iso_fortran_env, only: &
compiler_version, &
compiler_options
#endif
use prec, only: &
pStringLen
use debug, only: &
@ -77,8 +72,7 @@ subroutine source_damage_isoBrittle_init
sourceState
use config, only: &
config_phase, &
material_Nphase, &
MATERIAL_partPhase
material_Nphase
implicit none
@ -94,7 +88,6 @@ subroutine source_damage_isoBrittle_init
outputs
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ISOBRITTLE_LABEL//' init -+>>>'
#include "compilation_info.f90"
Ninstance = int(count(phase_source == SOURCE_damage_isoBrittle_ID),pInt)
if (Ninstance == 0_pInt) return

View File

@ -53,11 +53,6 @@ contains
!> @details reads in material parameters, allocates arrays, and does sanity checks
!--------------------------------------------------------------------------------------------------
subroutine source_damage_isoDuctile_init
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
use, intrinsic :: iso_fortran_env, only: &
compiler_version, &
compiler_options
#endif
use prec, only: &
pStringLen
use debug, only: &
@ -65,7 +60,6 @@ subroutine source_damage_isoDuctile_init
debug_constitutive,&
debug_levelBasic
use IO, only: &
IO_warning, &
IO_error
use material, only: &
material_allocateSourceState, &
@ -78,8 +72,7 @@ subroutine source_damage_isoDuctile_init
sourceState
use config, only: &
config_phase, &
material_Nphase, &
MATERIAL_partPhase
material_Nphase
implicit none
@ -95,12 +88,11 @@ subroutine source_damage_isoDuctile_init
outputs
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ISODUCTILE_LABEL//' init -+>>>'
#include "compilation_info.f90"
Ninstance = int(count(phase_source == SOURCE_damage_isoDuctile_ID),pInt)
Ninstance = count(phase_source == SOURCE_damage_isoDuctile_ID)
if (Ninstance == 0_pInt) return
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) &
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
allocate(source_damage_isoDuctile_offset(material_Nphase), source=0_pInt)

View File

@ -60,8 +60,7 @@ subroutine source_thermal_dissipation_init
sourceState
use config, only: &
config_phase, &
material_Nphase, &
MATERIAL_partPhase
material_Nphase
implicit none
integer(pInt) :: Ninstance,instance,source,sourceOffset

View File

@ -62,8 +62,7 @@ subroutine source_thermal_externalheat_init
SOURCE_thermal_externalheat_ID
use config, only: &
config_phase, &
material_Nphase, &
MATERIAL_partPhase
material_Nphase
implicit none

View File

@ -57,7 +57,6 @@ subroutine thermal_adiabatic_init
temperature, &
temperatureRate
use config, only: &
material_partHomogenization, &
config_homogenization
implicit none
@ -277,7 +276,6 @@ function thermal_adiabatic_getMassDensity(ip,el)
lattice_massDensity
use material, only: &
homogenization_Ngrains, &
mappingHomogenization, &
material_phase
use mesh, only: &
mesh_element

View File

@ -58,7 +58,6 @@ subroutine thermal_conduction_init
temperature, &
temperatureRate
use config, only: &
material_partHomogenization, &
config_homogenization
implicit none
@ -70,7 +69,7 @@ subroutine thermal_conduction_init
write(6,'(/,a)') ' <<<+- thermal_'//THERMAL_CONDUCTION_label//' init -+>>>'
maxNinstance = int(count(thermal_type == THERMAL_conduction_ID),pInt)
maxNinstance = count(thermal_type == THERMAL_conduction_ID)
if (maxNinstance == 0_pInt) return
allocate(thermal_conduction_sizePostResult (maxval(homogenization_Noutput),maxNinstance),source=0_pInt)