removed unused variables

This commit is contained in:
Franz Roters 2011-04-13 14:16:22 +00:00
parent b4678112cd
commit 7d84a0911e
13 changed files with 43 additions and 70 deletions

View File

@ -75,7 +75,6 @@ recursive function IO_abaqus_assembleInputFile(unit1,unit2) result(createSuccess
character(len=300) line,fname character(len=300) line,fname
integer(pInt), intent(in) :: unit1, unit2 integer(pInt), intent(in) :: unit1, unit2
logical createSuccess,fexist logical createSuccess,fexist
integer(pInt) i
do do
read(unit2,'(A300)',END=220) line read(unit2,'(A300)',END=220) line

View File

@ -91,7 +91,7 @@ subroutine constitutive_j2_init(file)
integer(pInt), intent(in) :: file integer(pInt), intent(in) :: file
integer(pInt), parameter :: maxNchunks = 7 integer(pInt), parameter :: maxNchunks = 7
integer(pInt), dimension(1+2*maxNchunks) :: positions integer(pInt), dimension(1+2*maxNchunks) :: positions
integer(pInt) section, maxNinstance, i,j,k,l, output, mySize integer(pInt) section, maxNinstance, i,j,k, output, mySize
character(len=64) tag character(len=64) tag
character(len=1024) line character(len=1024) line

View File

@ -703,9 +703,7 @@ real(pReal), dimension(constitutive_nonlocal_totalNslip(myInstance)) :: &
rhoSglScrewPosUsed, & ! used positive screw dislocation density rhoSglScrewPosUsed, & ! used positive screw dislocation density
rhoSglScrewNegUsed, & ! used negative screw dislocation density rhoSglScrewNegUsed, & ! used negative screw dislocation density
rhoDipEdge, & ! edge dipole dislocation density rhoDipEdge, & ! edge dipole dislocation density
rhoDipScrew, & ! screw dipole dislocation density rhoDipScrew ! screw dipole dislocation density
rhoForest, & ! forest dislocation density
tauSlipThreshold ! threshold shear stress for slip
integer(pInt) ns, & ! short notation for total number of active slip systems integer(pInt) ns, & ! short notation for total number of active slip systems
f, & ! index of lattice family f, & ! index of lattice family
from, & from, &
@ -918,8 +916,7 @@ real(pReal), dimension(constitutive_nonlocal_totalNslip(phase_constitutionInstan
rhoDip ! dipole dislocation density (edge, screw) rhoDip ! dipole dislocation density (edge, screw)
real(pReal), dimension(constitutive_nonlocal_totalNslip(phase_constitutionInstance(material_phase(g,ip,el)))) :: & real(pReal), dimension(constitutive_nonlocal_totalNslip(phase_constitutionInstance(material_phase(g,ip,el)))) :: &
rhoForest, & ! forest dislocation density rhoForest, & ! forest dislocation density
tauThreshold, & ! threshold shear stress tauThreshold ! threshold shear stress
tau ! resolved shear stress
phase = material_phase(g,ip,el) phase = material_phase(g,ip,el)
instance = phase_constitutionInstance(phase) instance = phase_constitutionInstance(phase)
@ -1200,7 +1197,6 @@ real(pReal), dimension(constitutive_nonlocal_totalNslip(phase_constitutionInstan
integer(pInt) myInstance, & ! current instance of this constitution integer(pInt) myInstance, & ! current instance of this constitution
myStructure, & ! current lattice structure myStructure, & ! current lattice structure
ns, & ! short notation for the total number of active slip systems ns, & ! short notation for the total number of active slip systems
t, & ! dislocation type
s ! index of my current slip system s ! index of my current slip system
real(pReal), dimension(6) :: Tdislocation_v ! dislocation stress (resulting from the neighboring excess dislocation densities) as 2nd Piola-Kirchhoff stress real(pReal), dimension(6) :: Tdislocation_v ! dislocation stress (resulting from the neighboring excess dislocation densities) as 2nd Piola-Kirchhoff stress
real(pReal), dimension(constitutive_nonlocal_totalNslip(phase_constitutionInstance(material_phase(g,ip,el)))) :: & real(pReal), dimension(constitutive_nonlocal_totalNslip(phase_constitutionInstance(material_phase(g,ip,el)))) :: &
@ -1500,14 +1496,12 @@ integer(pInt) myInstance, & ! current
t, & ! type of dislocation t, & ! type of dislocation
topp, & ! type of dislocation with opposite sign to t topp, & ! type of dislocation with opposite sign to t
s, & ! index of my current slip system s, & ! index of my current slip system
sLattice, & ! index of my current slip system according to lattice order sLattice ! index of my current slip system according to lattice order
i
real(pReal), dimension(constitutive_nonlocal_totalNslip(phase_constitutionInstance(material_phase(g,ip,el))),10) :: & real(pReal), dimension(constitutive_nonlocal_totalNslip(phase_constitutionInstance(material_phase(g,ip,el))),10) :: &
rhoDot, & ! density evolution rhoDot, & ! density evolution
rhoDotRemobilization, & ! density evolution by remobilization rhoDotRemobilization, & ! density evolution by remobilization
rhoDotMultiplication, & ! density evolution by multiplication rhoDotMultiplication, & ! density evolution by multiplication
rhoDotFlux, & ! density evolution by flux rhoDotFlux, & ! density evolution by flux
neighboring_rhoDotFlux, & ! density evolution by flux at neighbor
rhoDotSingle2DipoleGlide, & ! density evolution by dipole formation (by glide) rhoDotSingle2DipoleGlide, & ! density evolution by dipole formation (by glide)
rhoDotAthermalAnnihilation, & ! density evolution by athermal annihilation rhoDotAthermalAnnihilation, & ! density evolution by athermal annihilation
rhoDotThermalAnnihilation ! density evolution by thermal annihilation rhoDotThermalAnnihilation ! density evolution by thermal annihilation
@ -1521,7 +1515,6 @@ real(pReal), dimension(constitutive_nonlocal_totalNslip(phase_constitutionInstan
rhoForest, & ! forest dislocation density rhoForest, & ! forest dislocation density
tauThreshold, & ! threshold shear stress tauThreshold, & ! threshold shear stress
tau, & ! current resolved shear stress tau, & ! current resolved shear stress
invLambda, & ! inverse of mean free path for dislocations
vClimb ! climb velocity of edge dipoles vClimb ! climb velocity of edge dipoles
real(pReal), dimension(constitutive_nonlocal_totalNslip(phase_constitutionInstance(material_phase(g,ip,el))),2) :: & real(pReal), dimension(constitutive_nonlocal_totalNslip(phase_constitutionInstance(material_phase(g,ip,el))),2) :: &
rhoDip, & ! current dipole dislocation densities (screw and edge dipoles) rhoDip, & ! current dipole dislocation densities (screw and edge dipoles)
@ -1542,8 +1535,7 @@ real(pReal), dimension(3) :: normal_neighbor2me, & ! inte
real(pReal) area, & ! area of the current interface real(pReal) area, & ! area of the current interface
transmissivity, & ! overall transmissivity of dislocation flux to neighboring material point transmissivity, & ! overall transmissivity of dislocation flux to neighboring material point
lineLength, & ! dislocation line length leaving the current interface lineLength, & ! dislocation line length leaving the current interface
D, & ! self diffusion D ! self diffusion
correction
logical considerEnteringFlux, & logical considerEnteringFlux, &
considerLeavingFlux considerLeavingFlux

View File

@ -165,9 +165,9 @@ subroutine constitutive_phenopowerlaw_init(file)
integer(pInt), intent(in) :: file integer(pInt), intent(in) :: file
integer(pInt), parameter :: maxNchunks = 21 integer(pInt), parameter :: maxNchunks = 21
integer(pInt), dimension(1+2*maxNchunks) :: positions integer(pInt), dimension(1+2*maxNchunks) :: positions
integer(pInt) section, maxNinstance, i,j,k,l,m, f,o, output, & integer(pInt) section, maxNinstance, i,j,k, f,o, output, &
mySize, myStructure, index_myFamily, index_otherFamily mySize, myStructure, index_myFamily, index_otherFamily
character(len=64) tag,formatting character(len=64) tag
character(len=1024) line character(len=1024) line
!$OMP CRITICAL (write2out) !$OMP CRITICAL (write2out)
@ -753,7 +753,7 @@ function constitutive_phenopowerlaw_dotState(Tstar_v,Temperature,state,ipc,ip,el
!* Definition of variables !* Definition of variables
integer(pInt) ipc,ip,el integer(pInt) ipc,ip,el
integer(pInt) matID,nSlip,nTwin,f,i,j,k, structID,index_Gamma,index_F,index_myFamily integer(pInt) matID,nSlip,nTwin,f,i,j, structID,index_Gamma,index_F,index_myFamily
real(pReal) Temperature,c_slipslip,c_sliptwin,c_twinslip,c_twintwin, ssat_offset real(pReal) Temperature,c_slipslip,c_sliptwin,c_twinslip,c_twintwin, ssat_offset
type(p_vec), dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems) :: state type(p_vec), dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems) :: state
real(pReal), dimension(6) :: Tstar_v real(pReal), dimension(6) :: Tstar_v

View File

@ -1168,7 +1168,7 @@ type(p_vec), dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), in
integer(pInt) myInstance,myStructure,ns,nt,s,t,i integer(pInt) myInstance,myStructure,ns,nt,s,t,i
real(pReal) sumf,sfe real(pReal) sumf,sfe
real(pReal), dimension(constitutive_titanmod_totalNtwin(phase_constitutionInstance(material_phase(g,ip,el)))) :: & real(pReal), dimension(constitutive_titanmod_totalNtwin(phase_constitutionInstance(material_phase(g,ip,el)))) :: &
fOverStacksize, volumefraction_pertwinsystem volumefraction_pertwinsystem
!* Shortened notation !* Shortened notation
myInstance = phase_constitutionInstance(material_phase(g,ip,el)) myInstance = phase_constitutionInstance(material_phase(g,ip,el))
@ -1292,14 +1292,14 @@ real(pReal), dimension(9,9), intent(out) :: dLp_dTstar
!* Local variables !* Local variables
integer(pInt) myInstance,myStructure,ns,nt,f,i,j,k,l,m,n,index_myFamily integer(pInt) myInstance,myStructure,ns,nt,f,i,j,k,l,m,n,index_myFamily
real(pReal) sumf,StressRatio_edge_p,minusStressRatio_edge_p,StressRatio_edge_pminus1,StressRatio_screw_p, & real(pReal) sumf,StressRatio_edge_p,minusStressRatio_edge_p,StressRatio_edge_pminus1,StressRatio_screw_p, &
StressRatio_screw_pminus1, StressRatio_r,BoltzmannRatioedge,DotGamma0, minusStressRatio_screw_p,gdotTotal, & StressRatio_screw_pminus1, BoltzmannRatioedge, minusStressRatio_screw_p, &
screwvelocity_prefactor,twinStressRatio_p,twinminusStressRatio_p,twinStressRatio_pminus1, & screwvelocity_prefactor,twinStressRatio_p,twinminusStressRatio_p,twinStressRatio_pminus1, &
twinStressRatio_r, twinDotGamma0,BoltzmannRatioscrew,BoltzmannRatiotwin,bottomstress_edge,bottomstress_screw twinDotGamma0,BoltzmannRatioscrew,BoltzmannRatiotwin,bottomstress_edge,bottomstress_screw
real(pReal), dimension(3,3,3,3) :: dLp_dTstar3333 real(pReal), dimension(3,3,3,3) :: dLp_dTstar3333
real(pReal), dimension(constitutive_titanmod_totalNslip(phase_constitutionInstance(material_phase(g,ip,el)))) :: & real(pReal), dimension(constitutive_titanmod_totalNslip(phase_constitutionInstance(material_phase(g,ip,el)))) :: &
gdot_slip,dgdot_dtauslip,tau_slip, edge_velocity, screw_velocity,gdot_slip_edge,gdot_slip_screw gdot_slip,dgdot_dtauslip,tau_slip, edge_velocity, screw_velocity,gdot_slip_edge,gdot_slip_screw
real(pReal), dimension(constitutive_titanmod_totalNtwin(phase_constitutionInstance(material_phase(g,ip,el)))) :: & real(pReal), dimension(constitutive_titanmod_totalNtwin(phase_constitutionInstance(material_phase(g,ip,el)))) :: &
gdot_twin,dgdot_dtautwin,tau_twin, twinedge_velocity, twinscrew_velocity,volumefraction_pertwinsystem gdot_twin,dgdot_dtautwin,tau_twin, volumefraction_pertwinsystem
!* Shortened notation !* Shortened notation
myInstance = phase_constitutionInstance(material_phase(g,ip,el)) myInstance = phase_constitutionInstance(material_phase(g,ip,el))
@ -1597,17 +1597,15 @@ type(p_vec), dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), in
real(pReal), dimension(constitutive_titanmod_sizeDotState(phase_constitutionInstance(material_phase(g,ip,el)))) :: & real(pReal), dimension(constitutive_titanmod_sizeDotState(phase_constitutionInstance(material_phase(g,ip,el)))) :: &
constitutive_titanmod_dotState constitutive_titanmod_dotState
!* Local variables !* Local variables
integer(pInt) MyInstance,MyStructure,ns,nt,f,i,j,k,index_myFamily,s,t integer(pInt) MyInstance,MyStructure,ns,nt,f,i,j,index_myFamily
real(pReal) sumf,StressRatio_edge_p,minusStressRatio_edge_p,StressRatio_pminus1,BoltzmannRatio,DotGamma0,& real(pReal) sumf,BoltzmannRatio,&
EdgeDipMinDistance,AtomicVolume,VacancyDiffusion,StressRatio_r,StressRatio_screw_p,minusStressRatio_screw_p, & twinStressRatio_p,twinminusStressRatio_p
twinStressRatio_p,twinminusStressRatio_p,twinStressRatio_pminus1, &
twinDotGamma0
real(pReal), dimension(constitutive_titanmod_totalNslip(phase_constitutionInstance(material_phase(g,ip,el)))) :: & real(pReal), dimension(constitutive_titanmod_totalNslip(phase_constitutionInstance(material_phase(g,ip,el)))) :: &
gdot_slip,tau_slip,DotRhoEdgeGeneration,EdgeDipDistance,DotRhoEdgeAnnihilation,DotRhoScrewAnnihilation,& DotRhoEdgeGeneration,DotRhoEdgeAnnihilation,DotRhoScrewAnnihilation,&
ClimbVelocity,DotRhoScrewGeneration, edge_velocity,screw_velocity DotRhoScrewGeneration
real(pReal), dimension(constitutive_titanmod_totalNtwin(phase_constitutionInstance(material_phase(g,ip,el)))) :: gdot_twin, & real(pReal), dimension(constitutive_titanmod_totalNtwin(phase_constitutionInstance(material_phase(g,ip,el)))) :: gdot_twin, &
tau_twin,twinedge_segment,twinscrew_segment,twinedge_velocity,twinscrew_velocity,TwinDotRhoEdgeGeneration, & tau_twin, &
TwinDotRhoEdgeAnnihilation,TwinDotRhoScrewGeneration,TwinDotRhoScrewAnnihilation,volumefraction_pertwinsystem volumefraction_pertwinsystem
!* Shortened notation !* Shortened notation
myInstance = phase_constitutionInstance(material_phase(g,ip,el)) myInstance = phase_constitutionInstance(material_phase(g,ip,el))
@ -1773,7 +1771,7 @@ integer(pInt), intent(in) :: g,ip,el
real(pReal), intent(in) :: dt,Temperature real(pReal), intent(in) :: dt,Temperature
real(pReal), dimension(6), intent(in) :: Tstar_v real(pReal), dimension(6), intent(in) :: Tstar_v
type(p_vec), dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), intent(in) :: state type(p_vec), dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), intent(in) :: state
integer(pInt) myInstance,myStructure,ns,nt,f,o,i,c,j,index_myFamily integer(pInt) myInstance,myStructure,ns,nt,o,i,c
real(pReal) sumf real(pReal) sumf
real(pReal), dimension(constitutive_titanmod_sizePostResults(phase_constitutionInstance(material_phase(g,ip,el)))) :: & real(pReal), dimension(constitutive_titanmod_sizePostResults(phase_constitutionInstance(material_phase(g,ip,el)))) :: &
constitutive_titanmod_postResults constitutive_titanmod_postResults

View File

@ -157,18 +157,14 @@ integer(pInt) g, & ! grain number
eMax, & ! maximum number of elements eMax, & ! maximum number of elements
nMax, & ! maximum number of ip neighbors nMax, & ! maximum number of ip neighbors
myNgrains, & ! number of grains in current IP myNgrains, & ! number of grains in current IP
myCrystallite, & ! crystallite of current elem
section, & section, &
f, &
j, & j, &
k, &
p, & p, &
output, & output, &
mySize, & mySize, &
myStructure, & ! lattice structure myStructure, & ! lattice structure
myPhase, & myPhase, &
myMat, & myMat
index_myFamily
character(len=64) tag character(len=64) tag
character(len=1024) line character(len=1024) line
@ -492,13 +488,11 @@ logical, intent(in) :: updateJaco
!*** output variables ***! !*** output variables ***!
!*** local variables ***! !*** local variables ***!
real(pReal) myTemperature, & ! local copy of the temperature real(pReal) myPert, & ! perturbation with correct sign
myPert, & ! perturbation with correct sign
formerSubStep formerSubStep
real(pReal), dimension(3,3) :: invFp, & ! inverse of the plastic deformation gradient real(pReal), dimension(3,3) :: invFp, & ! inverse of the plastic deformation gradient
Fe_guess, & ! guess for elastic deformation gradient Fe_guess, & ! guess for elastic deformation gradient
Tstar ! 2nd Piola-Kirchhoff stress tensor Tstar ! 2nd Piola-Kirchhoff stress tensor
real(pReal), dimension(9,9) :: dPdF99
real(pReal), dimension(3,3,3,3,homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems) :: & real(pReal), dimension(3,3,3,3,homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems) :: &
dPdF_perturbation1, & dPdF_perturbation1, &
dPdF_perturbation2 dPdF_perturbation2
@ -1156,7 +1150,6 @@ integer(pInt), optional, intent(in):: ee, & ! elemen
integer(pInt) e, & ! element index in element loop integer(pInt) e, & ! element index in element loop
i, & ! integration point index in ip loop i, & ! integration point index in ip loop
g, & ! grain index in grain loop g, & ! grain index in grain loop
j, &
n, & ! stage index in integration stage loop n, & ! stage index in integration stage loop
mySizeDotState, & ! size of dot State mySizeDotState, & ! size of dot State
s ! state index s ! state index
@ -1635,8 +1628,6 @@ integer(pInt), optional, intent(in):: ee, & ! elemen
integer(pInt) e, & ! element index in element loop integer(pInt) e, & ! element index in element loop
i, & ! integration point index in ip loop i, & ! integration point index in ip loop
g, & ! grain index in grain loop g, & ! grain index in grain loop
j, &
n, & ! stage index in integration stage loop
mySizeDotState, & ! size of dot State mySizeDotState, & ! size of dot State
s ! state index s ! state index
integer(pInt), dimension(2) :: eIter ! bounds for element iteration integer(pInt), dimension(2) :: eIter ! bounds for element iteration
@ -1913,7 +1904,6 @@ integer(pInt), optional, intent(in):: ee, & ! elemen
integer(pInt) e, & ! element index in element loop integer(pInt) e, & ! element index in element loop
i, & ! integration point index in ip loop i, & ! integration point index in ip loop
g, & ! grain index in grain loop g, & ! grain index in grain loop
n, &
mySizeDotState mySizeDotState
integer(pInt), dimension(2) :: eIter ! bounds for element iteration integer(pInt), dimension(2) :: eIter ! bounds for element iteration
integer(pInt), dimension(2,mesh_NcpElems) :: iIter, & ! bounds for ip iteration integer(pInt), dimension(2,mesh_NcpElems) :: iIter, & ! bounds for ip iteration
@ -3051,8 +3041,7 @@ function crystallite_postResults(&
!*** local variables ***! !*** local variables ***!
real(pReal), dimension(3,3) :: Ee real(pReal), dimension(3,3) :: Ee
integer(pInt) k,l,o,c,crystID,mySize integer(pInt) o,c,crystID,mySize
logical error
crystID = microstructure_crystallite(mesh_element(4,e)) crystID = microstructure_crystallite(mesh_element(4,e))

View File

@ -87,7 +87,7 @@ implicit none
real(pReal) Temperature real(pReal) Temperature
integer(pInt), parameter :: fileunit = 200 integer(pInt), parameter :: fileunit = 200
integer(pInt) e,i,g,p,myInstance,j integer(pInt) e,i,p,myInstance
integer(pInt), dimension(:,:), pointer :: thisSize integer(pInt), dimension(:,:), pointer :: thisSize
character(len=64), dimension(:,:), pointer :: thisOutput character(len=64), dimension(:,:), pointer :: thisOutput
logical knownHomogenization logical knownHomogenization
@ -303,7 +303,6 @@ subroutine materialpoint_stressAndItsTangent(&
logical, intent(in) :: updateJaco logical, intent(in) :: updateJaco
integer(pInt) NiterationHomog,NiterationMPstate integer(pInt) NiterationHomog,NiterationMPstate
integer(pInt) g,i,e,myNgrains integer(pInt) g,i,e,myNgrains
logical error
! ------ initialize to starting condition ------ ! ------ initialize to starting condition ------

View File

@ -74,7 +74,7 @@ subroutine homogenization_RGC_init(&
integer(pInt), intent(in) :: file integer(pInt), intent(in) :: file
integer(pInt), parameter :: maxNchunks = 4 integer(pInt), parameter :: maxNchunks = 4
integer(pInt), dimension(1+2*maxNchunks) :: positions integer(pInt), dimension(1+2*maxNchunks) :: positions
integer(pInt) section, maxNinstance, i,j,k,l,e, output, mySize, myInstance integer(pInt) section, maxNinstance, i,j,e, output, mySize, myInstance
character(len=64) tag character(len=64) tag
character(len=1024) line character(len=1024) line
@ -364,11 +364,11 @@ function homogenization_RGC_updateState(&
integer(pInt), dimension (4) :: intFaceN,intFaceP,faceID integer(pInt), dimension (4) :: intFaceN,intFaceP,faceID
integer(pInt), dimension (3) :: nGDim,iGr3N,iGr3P,stresLoc integer(pInt), dimension (3) :: nGDim,iGr3N,iGr3P,stresLoc
integer(pInt), dimension (2) :: residLoc integer(pInt), dimension (2) :: residLoc
integer(pInt) homID,i1,i2,i3,iNum,i,j,nIntFaceTot,iGrN,iGrP,iMun,iFace,k,l,ival,ipert,iGrain,nGrain integer(pInt) homID,iNum,i,j,nIntFaceTot,iGrN,iGrP,iMun,iFace,k,l,ival,ipert,iGrain,nGrain
real(pReal), dimension (3,3,homogenization_maxNgrains) :: R,pF,pR,D,pD real(pReal), dimension (3,3,homogenization_maxNgrains) :: R,pF,pR,D,pD
real(pReal), dimension (3,homogenization_maxNgrains) :: NN,pNN real(pReal), dimension (3,homogenization_maxNgrains) :: NN,pNN
real(pReal), dimension (3) :: normP,normN,mornP,mornN real(pReal), dimension (3) :: normP,normN,mornP,mornN
real(pReal) residMax,stresMax,constitutiveWork,penaltyEnergy,volDiscrep,penDiscrep real(pReal) residMax,stresMax,constitutiveWork,penaltyEnergy,volDiscrep
logical error,RGCdebug,RGCdebugJacobi,RGCcheck logical error,RGCdebug,RGCdebugJacobi,RGCcheck
! !
integer(pInt), parameter :: nFace = 6 integer(pInt), parameter :: nFace = 6
@ -804,7 +804,7 @@ subroutine homogenization_RGC_averageStressAndItsTangent(&
real(pReal), dimension (9,9) :: dPdF99 real(pReal), dimension (9,9) :: dPdF99
integer(pInt), intent(in) :: ip,el integer(pInt), intent(in) :: ip,el
! !
logical homogenization_RGC_stateUpdate,RGCdebug logical RGCdebug
integer(pInt) homID, i, j, Ngrains, iGrain integer(pInt) homID, i, j, Ngrains, iGrain
RGCdebug = .false. !(ip == 1 .and. el == 1) RGCdebug = .false. !(ip == 1 .and. el == 1)
@ -853,7 +853,7 @@ function homogenization_RGC_averageTemperature(&
real(pReal), dimension (homogenization_maxNgrains), intent(in) :: Temperature real(pReal), dimension (homogenization_maxNgrains), intent(in) :: Temperature
integer(pInt), intent(in) :: ip,el integer(pInt), intent(in) :: ip,el
real(pReal) homogenization_RGC_averageTemperature real(pReal) homogenization_RGC_averageTemperature
integer(pInt) homID, i, Ngrains integer(pInt) homID, Ngrains
!* Computing the average temperature !* Computing the average temperature
Ngrains = homogenization_Ngrains(mesh_element(3,el)) Ngrains = homogenization_Ngrains(mesh_element(3,el))
@ -950,11 +950,11 @@ subroutine homogenization_RGC_stressPenalty(&
integer(pInt), intent(in) :: ip,el integer(pInt), intent(in) :: ip,el
integer(pInt), dimension (4) :: intFace integer(pInt), dimension (4) :: intFace
integer(pInt), dimension (3) :: iGrain3,iGNghb3,nGDim integer(pInt), dimension (3) :: iGrain3,iGNghb3,nGDim
real(pReal), dimension (3,3) :: gDef,nDef,avgC real(pReal), dimension (3,3) :: gDef,nDef
real(pReal), dimension (3) :: nVect,surfCorr real(pReal), dimension (3) :: nVect,surfCorr
real(pReal), dimension (2) :: Gmoduli real(pReal), dimension (2) :: Gmoduli
integer(pInt) homID,iGrain,iGNghb,iFace,i,j,k,l,m integer(pInt) homID,iGrain,iGNghb,iFace,i,j,k,l
real(pReal) muGrain,muGNghb,nDefNorm,xiAlpha,ciAlpha,bgGrain,bgGNghb,detF real(pReal) muGrain,muGNghb,nDefNorm,bgGrain,bgGNghb
! !
integer(pInt), parameter :: nFace = 6 integer(pInt), parameter :: nFace = 6
real(pReal), parameter :: nDefToler = 1.0e-10 real(pReal), parameter :: nDefToler = 1.0e-10
@ -1084,7 +1084,7 @@ subroutine homogenization_RGC_volumePenalty(&
real(pReal), dimension (3,3), intent(in) :: fAvg real(pReal), dimension (3,3), intent(in) :: fAvg
integer(pInt), intent(in) :: ip,el integer(pInt), intent(in) :: ip,el
real(pReal), dimension (homogenization_maxNgrains) :: gVol real(pReal), dimension (homogenization_maxNgrains) :: gVol
integer(pInt) homID,iGrain,nGrain,i,j integer(pInt) homID,iGrain,nGrain
! !
nGrain = homogenization_Ngrains(mesh_element(3,el)) nGrain = homogenization_Ngrains(mesh_element(3,el))
@ -1251,7 +1251,7 @@ function homogenization_RGC_interfaceNormal(&
real(pReal), dimension (3) :: homogenization_RGC_interfaceNormal real(pReal), dimension (3) :: homogenization_RGC_interfaceNormal
integer(pInt), dimension (4), intent(in) :: intFace integer(pInt), dimension (4), intent(in) :: intFace
integer(pInt), intent(in) :: ip,el integer(pInt), intent(in) :: ip,el
integer(pInt) nPos,i integer(pInt) nPos
!* Get the normal of the interface, identified from the value of intFace(1) !* Get the normal of the interface, identified from the value of intFace(1)
homogenization_RGC_interfaceNormal = 0.0_pReal homogenization_RGC_interfaceNormal = 0.0_pReal
@ -1371,7 +1371,7 @@ function homogenization_RGC_interface4to1(&
integer(pInt), dimension (4), intent(in) :: iFace4D integer(pInt), dimension (4), intent(in) :: iFace4D
integer(pInt) :: homogenization_RGC_interface4to1 integer(pInt) :: homogenization_RGC_interface4to1
integer(pInt), dimension (3) :: nGDim,nIntFace integer(pInt), dimension (3) :: nGDim,nIntFace
integer(pInt) homID,dir integer(pInt) homID
nGDim = homogenization_RGC_Ngrains(:,homID) nGDim = homogenization_RGC_Ngrains(:,homID)
!* Compute the total number of interfaces, which ... !* Compute the total number of interfaces, which ...

View File

@ -69,7 +69,7 @@ subroutine homogenization_isostrain_init(&
integer(pInt), intent(in) :: file integer(pInt), intent(in) :: file
integer(pInt), parameter :: maxNchunks = 2 integer(pInt), parameter :: maxNchunks = 2
integer(pInt), dimension(1+2*maxNchunks) :: positions integer(pInt), dimension(1+2*maxNchunks) :: positions
integer(pInt) section, maxNinstance, i,j,k,l, output, mySize integer(pInt) section, maxNinstance, i,j, output, mySize
character(len=64) tag character(len=64) tag
character(len=1024) line character(len=1024) line
@ -190,7 +190,7 @@ subroutine homogenization_isostrain_partitionDeformation(&
real(pReal), dimension (3,3), intent(in) :: avgF real(pReal), dimension (3,3), intent(in) :: avgF
type(p_vec), intent(in) :: state type(p_vec), intent(in) :: state
integer(pInt), intent(in) :: ip,el integer(pInt), intent(in) :: ip,el
integer(pInt) homID, i integer(pInt) i
! homID = homogenization_typeInstance(mesh_element(3,el)) ! homID = homogenization_typeInstance(mesh_element(3,el))
forall (i = 1:homogenization_Ngrains(mesh_element(3,el))) & forall (i = 1:homogenization_Ngrains(mesh_element(3,el))) &
@ -259,8 +259,7 @@ subroutine homogenization_isostrain_averageStressAndItsTangent(&
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(in) :: P real(pReal), dimension (3,3,homogenization_maxNgrains), intent(in) :: P
real(pReal), dimension (3,3,3,3,homogenization_maxNgrains), intent(in) :: dPdF real(pReal), dimension (3,3,3,3,homogenization_maxNgrains), intent(in) :: dPdF
integer(pInt), intent(in) :: ip,el integer(pInt), intent(in) :: ip,el
logical homogenization_isostrain_stateUpdate integer(pInt) Ngrains
integer(pInt) homID, i, Ngrains
! homID = homogenization_typeInstance(mesh_element(3,el)) ! homID = homogenization_typeInstance(mesh_element(3,el))
Ngrains = homogenization_Ngrains(mesh_element(3,el)) Ngrains = homogenization_Ngrains(mesh_element(3,el))
@ -290,7 +289,7 @@ function homogenization_isostrain_averageTemperature(&
real(pReal), dimension (homogenization_maxNgrains), intent(in) :: Temperature real(pReal), dimension (homogenization_maxNgrains), intent(in) :: Temperature
integer(pInt), intent(in) :: ip,el integer(pInt), intent(in) :: ip,el
real(pReal) homogenization_isostrain_averageTemperature real(pReal) homogenization_isostrain_averageTemperature
integer(pInt) homID, i, Ngrains integer(pInt) Ngrains
! homID = homogenization_typeInstance(mesh_element(3,el)) ! homID = homogenization_typeInstance(mesh_element(3,el))
Ngrains = homogenization_Ngrains(mesh_element(3,el)) Ngrains = homogenization_Ngrains(mesh_element(3,el))

View File

@ -712,7 +712,7 @@ subroutine lattice_init()
implicit none implicit none
integer(pInt), parameter :: fileunit = 200 integer(pInt), parameter :: fileunit = 200
integer(pInt) i,Nsections integer(pInt) Nsections
!$OMP CRITICAL (write2out) !$OMP CRITICAL (write2out)
write(6,*) write(6,*)

View File

@ -341,7 +341,6 @@ subroutine material_parseCrystallite(file,myPart)
character(len=*), intent(in) :: myPart character(len=*), intent(in) :: myPart
integer(pInt), intent(in) :: file integer(pInt), intent(in) :: file
integer(pInt) Nsections, section integer(pInt) Nsections, section
character(len=64) tag
character(len=1024) line character(len=1024) line
Nsections = IO_countSections(file,myPart) Nsections = IO_countSections(file,myPart)

View File

@ -146,7 +146,6 @@ real(pReal), dimension(4,36), parameter :: math_symOperations = &
real(pReal), dimension(3,3) :: R,R2 real(pReal), dimension(3,3) :: R,R2
real(pReal), dimension(3) :: Eulers real(pReal), dimension(3) :: Eulers
real(pReal), dimension(4) :: q,q2,axisangle real(pReal), dimension(4) :: q,q2,axisangle
real(pReal), dimension(2) :: rnd
integer(pInt), dimension(1) :: randInit integer(pInt), dimension(1) :: randInit
@ -487,7 +486,7 @@ real(pReal), dimension(4,36), parameter :: math_symOperations = &
integer(pInt) i,j integer(pInt) i,j
real(pReal), dimension(3,3,3,3), intent(in) :: A real(pReal), dimension(3,3,3,3), intent(in) :: A
real(pReal), dimension(3,3), intent(in) :: B real(pReal), dimension(3,3), intent(in) :: B
real(pReal), dimension(3,3) :: C,math_mul3333xx33 real(pReal), dimension(3,3) :: math_mul3333xx33
do i = 1,3 do i = 1,3
do j = 1,3 do j = 1,3
@ -1598,7 +1597,6 @@ pure function math_transpose3x3(A)
real(pReal), dimension(4), intent(in) :: Q real(pReal), dimension(4), intent(in) :: Q
real(pReal), dimension(3,3) :: math_QuaternionToR, T,S real(pReal), dimension(3,3) :: math_QuaternionToR, T,S
real(pReal) w2
integer(pInt) i, j integer(pInt) i, j
forall (i = 1:3, j = 1:3) & forall (i = 1:3, j = 1:3) &

View File

@ -1935,7 +1935,7 @@ endsubroutine
character(len=300) line character(len=300) line
integer(pInt) unit,i,count integer(pInt) unit,i,count
logical inPart,materialFound logical inPart
character(len=64) elemSetName,materialName character(len=64) elemSetName,materialName
allocate (mesh_nameMaterial(mesh_Nmaterials)) ; mesh_nameMaterial = '' allocate (mesh_nameMaterial(mesh_Nmaterials)) ; mesh_nameMaterial = ''
@ -2962,7 +2962,7 @@ integer(pInt) myElem, & ! my CP element index
dir, & ! direction of periodicity dir, & ! direction of periodicity
matchingElem, & ! CP elem number of matching element matchingElem, & ! CP elem number of matching element
matchingFace, & ! face ID of matching element matchingFace, & ! face ID of matching element
k, a, anchor a, anchor
integer(pInt), dimension(FE_maxmaxNnodesAtIP) :: & integer(pInt), dimension(FE_maxmaxNnodesAtIP) :: &
linkedNodes, & linkedNodes, &
matchingNodes matchingNodes