corrected syntax errors (long lines, line continuation by \) and logical mistake in mpie_cpfem_marc / abq_std which went unnoticed in ifort. Using SunStudio f90 surfaced those...
This commit is contained in:
parent
2c4f5c37dc
commit
298cecbfec
|
@ -43,10 +43,10 @@
|
||||||
rewind(fileunit)
|
rewind(fileunit)
|
||||||
do
|
do
|
||||||
read (fileunit,'(a1024)',END=100) line
|
read (fileunit,'(a1024)',END=100) line
|
||||||
positions = IO_stringPos(line,1)
|
positions(1:1+2*1) = IO_stringPos(line,1)
|
||||||
if( IO_lc(IO_stringValue(line,positions,1)) == 'solver' ) then
|
if( IO_lc(IO_stringValue(line,positions,1)) == 'solver' ) then
|
||||||
read (fileunit,'(a1024)',END=100) line ! Garbage line
|
read (fileunit,'(a1024)',END=100) line ! Garbage line
|
||||||
positions = IO_stringPos(line,2)
|
positions(1:1+2*2) = IO_stringPos(line,2)
|
||||||
symmetricSolver = (IO_intValue(line,positions,2) /= 1_pInt)
|
symmetricSolver = (IO_intValue(line,positions,2) /= 1_pInt)
|
||||||
exit
|
exit
|
||||||
endif
|
endif
|
||||||
|
|
|
@ -135,7 +135,7 @@ end function
|
||||||
use mpie_interface
|
use mpie_interface
|
||||||
implicit none
|
implicit none
|
||||||
|
|
||||||
character(len=*), parameter :: pathSep = achar(47)//achar(92) ! /, \
|
character(len=*), parameter :: pathSep = achar(47)//achar(92) ! forward and backward slash
|
||||||
character(len=*) relPath
|
character(len=*) relPath
|
||||||
integer(pInt) unit
|
integer(pInt) unit
|
||||||
|
|
||||||
|
|
|
@ -920,7 +920,8 @@ do f = 1,lattice_maxNslipFamily ! loop over all
|
||||||
constitutive_dislotwin_v0PerSlipSystem(f,myInstance)
|
constitutive_dislotwin_v0PerSlipSystem(f,myInstance)
|
||||||
|
|
||||||
!* Shear rates due to slip
|
!* Shear rates due to slip
|
||||||
gdot_slip(j) = DotGamma0*exp(-BoltzmannRatio*(1-StressRatio_p)**constitutive_dislotwin_q(myInstance))*sign(1.0_pReal,tau_slip(j))
|
gdot_slip(j) = DotGamma0*exp(-BoltzmannRatio*(1-StressRatio_p)**constitutive_dislotwin_q(myInstance))*&
|
||||||
|
sign(1.0_pReal,tau_slip(j))
|
||||||
|
|
||||||
!* Derivatives of shear rates
|
!* Derivatives of shear rates
|
||||||
dgdot_dtauslip(j) = &
|
dgdot_dtauslip(j) = &
|
||||||
|
@ -1008,10 +1009,13 @@ function constitutive_dislotwin_dotState(Tstar_v,Temperature,state,g,ip,el)
|
||||||
use prec, only: pReal,pInt,p_vec
|
use prec, only: pReal,pInt,p_vec
|
||||||
|
|
||||||
use math, only: pi
|
use math, only: pi
|
||||||
use mesh, only: mesh_NcpElems,mesh_maxNips
|
use mesh, only: mesh_NcpElems, mesh_maxNips
|
||||||
use material, only: homogenization_maxNgrains,material_phase, phase_constitutionInstance
|
use material, only: homogenization_maxNgrains, material_phase, phase_constitutionInstance
|
||||||
use lattice, only: lattice_Sslip,lattice_Sslip_v,lattice_Stwin,lattice_Stwin_v,lattice_maxNslipFamily,lattice_maxNtwinFamily, &
|
use lattice, only: lattice_Sslip,lattice_Sslip_v, &
|
||||||
lattice_NslipSystem,lattice_NtwinSystem,lattice_shearTwin
|
lattice_Stwin,lattice_Stwin_v, &
|
||||||
|
lattice_maxNslipFamily,lattice_maxNtwinFamily, &
|
||||||
|
lattice_NslipSystem,lattice_NtwinSystem, &
|
||||||
|
lattice_shearTwin
|
||||||
implicit none
|
implicit none
|
||||||
|
|
||||||
!* Input-Output variables
|
!* Input-Output variables
|
||||||
|
@ -1029,7 +1033,8 @@ real(pReal), dimension(constitutive_dislotwin_totalNslip(phase_constitutionInsta
|
||||||
gdot_slip,tau_slip,DotRhoMultiplication,EdgeDipDistance,DotRhoEdgeEdgeAnnihilation,DotRhoEdgeDipAnnihilation,&
|
gdot_slip,tau_slip,DotRhoMultiplication,EdgeDipDistance,DotRhoEdgeEdgeAnnihilation,DotRhoEdgeDipAnnihilation,&
|
||||||
|
|
||||||
ClimbVelocity,DotRhoEdgeDipClimb,DotRhoDipFormation
|
ClimbVelocity,DotRhoEdgeDipClimb,DotRhoDipFormation
|
||||||
real(pReal), dimension(constitutive_dislotwin_totalNtwin(phase_constitutionInstance(material_phase(g,ip,el)))) :: gdot_twin,tau_twin
|
real(pReal), dimension(constitutive_dislotwin_totalNtwin(phase_constitutionInstance(material_phase(g,ip,el)))) :: &
|
||||||
|
gdot_twin,tau_twin
|
||||||
|
|
||||||
!* Shortened notation
|
!* Shortened notation
|
||||||
myInstance = phase_constitutionInstance(material_phase(g,ip,el))
|
myInstance = phase_constitutionInstance(material_phase(g,ip,el))
|
||||||
|
@ -1064,7 +1069,8 @@ do f = 1,lattice_maxNslipFamily ! loop over all
|
||||||
constitutive_dislotwin_v0PerSlipSystem(f,myInstance)
|
constitutive_dislotwin_v0PerSlipSystem(f,myInstance)
|
||||||
|
|
||||||
!* Shear rates due to slip
|
!* Shear rates due to slip
|
||||||
gdot_slip(j) = DotGamma0*exp(-BoltzmannRatio*(1-StressRatio_p)**constitutive_dislotwin_q(myInstance))*sign(1.0_pReal,tau_slip(j))
|
gdot_slip(j) = DotGamma0*exp(-BoltzmannRatio*(1-StressRatio_p)**constitutive_dislotwin_q(myInstance))*&
|
||||||
|
sign(1.0_pReal,tau_slip(j))
|
||||||
|
|
||||||
!* Multiplication
|
!* Multiplication
|
||||||
DotRhoMultiplication(j) = abs(gdot_slip(j))/&
|
DotRhoMultiplication(j) = abs(gdot_slip(j))/&
|
||||||
|
|
|
@ -1500,7 +1500,8 @@ do o = 1,phase_Noutput(material_phase(g,ip,el))
|
||||||
tau = dot_product(Tstar_v,lattice_Sslip_v(:,index_myFamily+i,myStructure))
|
tau = dot_product(Tstar_v,lattice_Sslip_v(:,index_myFamily+i,myStructure))
|
||||||
!* Stress ratios
|
!* Stress ratios
|
||||||
StressRatio_p = (abs(tau)/state(g,ip,el)%p(5*ns+3*nt+j))**constitutive_titanmod_pe_PerSlipSystem(j,myInstance)
|
StressRatio_p = (abs(tau)/state(g,ip,el)%p(5*ns+3*nt+j))**constitutive_titanmod_pe_PerSlipSystem(j,myInstance)
|
||||||
StressRatio_pminus1 = (abs(tau)/state(g,ip,el)%p(5*ns+3*nt+j))**(constitutive_titanmod_pe_PerSlipSystem(j,myInstance)-1.0_pReal)
|
StressRatio_pminus1 = (abs(tau)/state(g,ip,el)%p(5*ns+3*nt+j))**&
|
||||||
|
(constitutive_titanmod_pe_PerSlipSystem(j,myInstance)-1.0_pReal)
|
||||||
!* Boltzmann ratio
|
!* Boltzmann ratio
|
||||||
BoltzmannRatio = constitutive_titanmod_f0_PerSlipSystem(j,myInstance)/(kB*Temperature)
|
BoltzmannRatio = constitutive_titanmod_f0_PerSlipSystem(j,myInstance)/(kB*Temperature)
|
||||||
!* Initial shear rates
|
!* Initial shear rates
|
||||||
|
|
|
@ -1436,7 +1436,8 @@ LpLoop: do
|
||||||
if (error) then
|
if (error) then
|
||||||
if (verboseDebugger .and. selectiveDebugger) then
|
if (verboseDebugger .and. selectiveDebugger) then
|
||||||
!$OMP CRITICAL (write2out)
|
!$OMP CRITICAL (write2out)
|
||||||
write(6,'(a,i3,x,i2,x,i5,x,a,x,i3)') '::: integrateStress failed on dR/dLp inversion at ',g,i,e,' ; iteration ', NiterationStress
|
write(6,'(a,i3,x,i2,x,i5,x,a,x,i3)') '::: integrateStress failed on dR/dLp inversion at ',g,i,e, &
|
||||||
|
' ; iteration ', NiterationStress
|
||||||
write(6,*)
|
write(6,*)
|
||||||
write(6,'(a,/,9(9(e15.3,x)/))') 'dRdLp',dRdLp
|
write(6,'(a,/,9(9(e15.3,x)/))') 'dRdLp',dRdLp
|
||||||
write(6,'(a,/,9(9(e15.3,x)/))') 'dLpdT_constitutive',dLpdT_constitutive
|
write(6,'(a,/,9(9(e15.3,x)/))') 'dLpdT_constitutive',dLpdT_constitutive
|
||||||
|
@ -1469,7 +1470,8 @@ LpLoop: do
|
||||||
if (error) then
|
if (error) then
|
||||||
if (verboseDebugger .and. selectiveDebugger) then
|
if (verboseDebugger .and. selectiveDebugger) then
|
||||||
!$OMP CRITICAL (write2out)
|
!$OMP CRITICAL (write2out)
|
||||||
write(6,'(a,i3,x,i2,x,i5,x,a,x,i3)') '::: integrateStress failed on invFp_new inversion at ',g,i,e,' ; iteration ', NiterationStress
|
write(6,'(a,i3,x,i2,x,i5,x,a,x,i3)') '::: integrateStress failed on invFp_new inversion at ',g,i,e, &
|
||||||
|
' ; iteration ', NiterationStress
|
||||||
write(6,*)
|
write(6,*)
|
||||||
write(6,'(a11,3(i3,x),/,3(3(f12.7,x)/))') 'invFp_new at ',g,i,e,invFp_new
|
write(6,'(a11,3(i3,x),/,3(3(f12.7,x)/))') 'invFp_new at ',g,i,e,invFp_new
|
||||||
!$OMPEND CRITICAL (write2out)
|
!$OMPEND CRITICAL (write2out)
|
||||||
|
|
|
@ -476,7 +476,9 @@ function homogenization_RGC_updateState(&
|
||||||
state%p(3*nIntFaceTot+8) = maxval(abs(drelax))/dt
|
state%p(3*nIntFaceTot+8) = maxval(abs(drelax))/dt
|
||||||
if (el == 1 .and. ip == 1) then
|
if (el == 1 .and. ip == 1) then
|
||||||
write(6,'(x,a30,x,e14.8)')'Constitutive work: ',constitutiveWork
|
write(6,'(x,a30,x,e14.8)')'Constitutive work: ',constitutiveWork
|
||||||
write(6,'(x,a30,3(x,e14.8))')'Magnitude mismatch: ',sum(NN(1,:))/dble(nGrain),sum(NN(2,:))/dble(nGrain),sum(NN(3,:))/dble(nGrain)
|
write(6,'(x,a30,3(x,e14.8))')'Magnitude mismatch: ',sum(NN(1,:))/dble(nGrain), &
|
||||||
|
sum(NN(2,:))/dble(nGrain), &
|
||||||
|
sum(NN(3,:))/dble(nGrain)
|
||||||
write(6,'(x,a30,x,e14.8)')'Penalty energy: ',penaltyEnergy
|
write(6,'(x,a30,x,e14.8)')'Penalty energy: ',penaltyEnergy
|
||||||
write(6,'(x,a30,x,e14.8)')'Volume discrepancy: ',volDiscrep
|
write(6,'(x,a30,x,e14.8)')'Volume discrepancy: ',volDiscrep
|
||||||
write(6,*)''
|
write(6,*)''
|
||||||
|
|
|
@ -2006,7 +2006,7 @@ subroutine mesh_marc_count_cpSizes (unit)
|
||||||
rewind(unit)
|
rewind(unit)
|
||||||
do
|
do
|
||||||
read (unit,610,END=630) line
|
read (unit,610,END=630) line
|
||||||
pos = IO_stringPos(line,1)
|
pos = IO_stringPos(line,maxNchunks)
|
||||||
if( IO_lc(IO_stringValue(line,pos,1)) == 'connectivity' ) then
|
if( IO_lc(IO_stringValue(line,pos,1)) == 'connectivity' ) then
|
||||||
read (unit,610,END=630) line ! Garbage line
|
read (unit,610,END=630) line ! Garbage line
|
||||||
do i=1,mesh_Nelems ! read all elements
|
do i=1,mesh_Nelems ! read all elements
|
||||||
|
@ -2060,7 +2060,7 @@ subroutine mesh_marc_count_cpSizes (unit)
|
||||||
rewind(unit)
|
rewind(unit)
|
||||||
do
|
do
|
||||||
read (unit,610,END=620) line
|
read (unit,610,END=620) line
|
||||||
pos = IO_stringPos(line,2)
|
pos = IO_stringPos(line,maxNchunks)
|
||||||
if ( IO_lc(IO_stringValue(line,pos,1)) == '*part' ) inPart = .true.
|
if ( IO_lc(IO_stringValue(line,pos,1)) == '*part' ) inPart = .true.
|
||||||
if ( IO_lc(IO_stringValue(line,pos,1)) == '*end' .and. &
|
if ( IO_lc(IO_stringValue(line,pos,1)) == '*end' .and. &
|
||||||
IO_lc(IO_stringValue(line,pos,2)) == 'part' ) inPart = .false.
|
IO_lc(IO_stringValue(line,pos,2)) == 'part' ) inPart = .false.
|
||||||
|
@ -2348,7 +2348,7 @@ subroutine mesh_marc_count_cpSizes (unit)
|
||||||
do while (e < mesh_NcpElems)
|
do while (e < mesh_NcpElems)
|
||||||
read(unit,'(a1024)',END=110) line
|
read(unit,'(a1024)',END=110) line
|
||||||
if (IO_isBlank(line)) cycle ! skip empty lines
|
if (IO_isBlank(line)) cycle ! skip empty lines
|
||||||
pos = IO_stringPos(line,1)
|
pos(1:1+2*1) = IO_stringPos(line,1)
|
||||||
|
|
||||||
e = e+1 ! valid element entry
|
e = e+1 ! valid element entry
|
||||||
mesh_element ( 1,e) = e ! FE id
|
mesh_element ( 1,e) = e ! FE id
|
||||||
|
@ -2399,7 +2399,7 @@ subroutine mesh_marc_count_cpSizes (unit)
|
||||||
rewind(unit)
|
rewind(unit)
|
||||||
do
|
do
|
||||||
read (unit,610,END=620) line
|
read (unit,610,END=620) line
|
||||||
pos = IO_stringPos(line,1)
|
pos(1:1+2*1) = IO_stringPos(line,1)
|
||||||
if( IO_lc(IO_stringValue(line,pos,1)) == 'connectivity' ) then
|
if( IO_lc(IO_stringValue(line,pos,1)) == 'connectivity' ) then
|
||||||
read (unit,610,END=620) line ! Garbage line
|
read (unit,610,END=620) line ! Garbage line
|
||||||
do i = 1,mesh_Nelems
|
do i = 1,mesh_Nelems
|
||||||
|
@ -2421,16 +2421,16 @@ subroutine mesh_marc_count_cpSizes (unit)
|
||||||
620 rewind(unit) ! just in case "initial state" apears before "connectivity"
|
620 rewind(unit) ! just in case "initial state" apears before "connectivity"
|
||||||
read (unit,610,END=620) line
|
read (unit,610,END=620) line
|
||||||
do
|
do
|
||||||
pos = IO_stringPos(line,2)
|
pos(1:1+2*2) = IO_stringPos(line,2)
|
||||||
if( (IO_lc(IO_stringValue(line,pos,1)) == 'initial') .and. &
|
if( (IO_lc(IO_stringValue(line,pos,1)) == 'initial') .and. &
|
||||||
(IO_lc(IO_stringValue(line,pos,2)) == 'state') ) then
|
(IO_lc(IO_stringValue(line,pos,2)) == 'state') ) then
|
||||||
if (initialcondTableStyle == 2) read (unit,610,END=620) line ! read extra line for new style
|
if (initialcondTableStyle == 2) read (unit,610,END=620) line ! read extra line for new style
|
||||||
read (unit,610,END=630) line ! read line with index of state var
|
read (unit,610,END=630) line ! read line with index of state var
|
||||||
pos = IO_stringPos(line,1)
|
pos(1:1+2*1) = IO_stringPos(line,1)
|
||||||
sv = IO_IntValue(line,pos,1) ! figure state variable index
|
sv = IO_IntValue(line,pos,1) ! figure state variable index
|
||||||
if( (sv == 2).or.(sv == 3) ) then ! only state vars 2 and 3 of interest
|
if( (sv == 2).or.(sv == 3) ) then ! only state vars 2 and 3 of interest
|
||||||
read (unit,610,END=620) line ! read line with value of state var
|
read (unit,610,END=620) line ! read line with value of state var
|
||||||
pos = IO_stringPos(line,1)
|
pos(1:1+2*1) = IO_stringPos(line,1)
|
||||||
do while (scan(IO_stringValue(line,pos,1),'+-',back=.true.)>1) ! is noEfloat value?
|
do while (scan(IO_stringValue(line,pos,1),'+-',back=.true.)>1) ! is noEfloat value?
|
||||||
val = NINT(IO_fixedNoEFloatValue(line,(/0,20/),1)) ! state var's value
|
val = NINT(IO_fixedNoEFloatValue(line,(/0,20/),1)) ! state var's value
|
||||||
mesh_maxValStateVar(sv-1) = max(val,mesh_maxValStateVar(sv-1)) ! remember max val of homogenization and microstructure index
|
mesh_maxValStateVar(sv-1) = max(val,mesh_maxValStateVar(sv-1)) ! remember max val of homogenization and microstructure index
|
||||||
|
@ -2445,7 +2445,7 @@ subroutine mesh_marc_count_cpSizes (unit)
|
||||||
enddo
|
enddo
|
||||||
if (initialcondTableStyle == 0) read (unit,610,END=620) line ! ignore IP range for old table style
|
if (initialcondTableStyle == 0) read (unit,610,END=620) line ! ignore IP range for old table style
|
||||||
read (unit,610,END=630) line
|
read (unit,610,END=630) line
|
||||||
pos = IO_stringPos(line,1)
|
pos(1:1+2*1) = IO_stringPos(line,1)
|
||||||
enddo
|
enddo
|
||||||
endif
|
endif
|
||||||
else
|
else
|
||||||
|
@ -2487,7 +2487,7 @@ subroutine mesh_marc_count_cpSizes (unit)
|
||||||
rewind(unit)
|
rewind(unit)
|
||||||
do
|
do
|
||||||
read (unit,610,END=620) line
|
read (unit,610,END=620) line
|
||||||
pos = IO_stringPos(line,2)
|
pos(1:1+2*2) = IO_stringPos(line,2)
|
||||||
if ( IO_lc(IO_stringValue(line,pos,1)) == '*part' ) inPart = .true.
|
if ( IO_lc(IO_stringValue(line,pos,1)) == '*part' ) inPart = .true.
|
||||||
if ( IO_lc(IO_stringValue(line,pos,1)) == '*end' .and. &
|
if ( IO_lc(IO_stringValue(line,pos,1)) == '*end' .and. &
|
||||||
IO_lc(IO_stringValue(line,pos,2)) == 'part' ) inPart = .false.
|
IO_lc(IO_stringValue(line,pos,2)) == 'part' ) inPart = .false.
|
||||||
|
@ -2539,7 +2539,7 @@ subroutine mesh_marc_count_cpSizes (unit)
|
||||||
if (i <= mesh_Nmaterials) then ! found one?
|
if (i <= mesh_Nmaterials) then ! found one?
|
||||||
elemSetName = mesh_mapMaterial(i) ! take corresponding elemSet
|
elemSetName = mesh_mapMaterial(i) ! take corresponding elemSet
|
||||||
read (unit,610,END=630) line ! read homogenization and microstructure
|
read (unit,610,END=630) line ! read homogenization and microstructure
|
||||||
pos = IO_stringPos(line,2)
|
pos(1:1+2*2) = IO_stringPos(line,2)
|
||||||
homog = NINT(IO_floatValue(line,pos,1))
|
homog = NINT(IO_floatValue(line,pos,1))
|
||||||
micro = NINT(IO_floatValue(line,pos,2))
|
micro = NINT(IO_floatValue(line,pos,2))
|
||||||
do i = 1,mesh_NelemSets ! look thru all elemSet definitions
|
do i = 1,mesh_NelemSets ! look thru all elemSet definitions
|
||||||
|
|
|
@ -174,7 +174,7 @@ subroutine UMAT(STRESS,STATEV,DDSDDE,SSE,SPD,SCD,&
|
||||||
calcMode(npt,cp_en) = .not. calcMode(npt,cp_en) ! ping pong (calc <--> collect)
|
calcMode(npt,cp_en) = .not. calcMode(npt,cp_en) ! ping pong (calc <--> collect)
|
||||||
|
|
||||||
if ( calcMode(npt,cp_en) ) then ! now calc
|
if ( calcMode(npt,cp_en) ) then ! now calc
|
||||||
if ( lastMode .ne. calcMode(npt,cp_en) ) then ! first after ping pong
|
if ( lastMode .neqv. calcMode(npt,cp_en) ) then ! first after ping pong
|
||||||
call debug_reset() ! resets debugging
|
call debug_reset() ! resets debugging
|
||||||
outdatedFFN1 = .false.
|
outdatedFFN1 = .false.
|
||||||
cycleCounter = cycleCounter + 1
|
cycleCounter = cycleCounter + 1
|
||||||
|
@ -186,7 +186,7 @@ subroutine UMAT(STRESS,STATEV,DDSDDE,SSE,SPD,SCD,&
|
||||||
computationMode = 2 ! plain calc
|
computationMode = 2 ! plain calc
|
||||||
endif
|
endif
|
||||||
else ! now collect
|
else ! now collect
|
||||||
if ( lastMode .ne. calcMode(npt,cp_en) ) call debug_info() ! first after ping pong reports debugging
|
if ( lastMode .neqv. calcMode(npt,cp_en) ) call debug_info() ! first after ping pong reports debugging
|
||||||
if ( lastIncConverged ) then
|
if ( lastIncConverged ) then
|
||||||
lastIncConverged = .false.
|
lastIncConverged = .false.
|
||||||
computationMode = 4 ! collect and backup Jacobian after convergence
|
computationMode = 4 ! collect and backup Jacobian after convergence
|
||||||
|
|
|
@ -57,7 +57,7 @@ end subroutine
|
||||||
function getSolverWorkingDirectoryName()
|
function getSolverWorkingDirectoryName()
|
||||||
implicit none
|
implicit none
|
||||||
character(1024) getSolverWorkingDirectoryName, outName
|
character(1024) getSolverWorkingDirectoryName, outName
|
||||||
character(len=*), parameter :: pathSep = achar(47)//achar(92) ! /, \
|
character(len=*), parameter :: pathSep = achar(47)//achar(92) ! forward and backward slash
|
||||||
|
|
||||||
getSolverWorkingDirectoryName=''
|
getSolverWorkingDirectoryName=''
|
||||||
outName=''
|
outName=''
|
||||||
|
@ -71,7 +71,7 @@ function getSolverJobName()
|
||||||
implicit none
|
implicit none
|
||||||
|
|
||||||
character(1024) getSolverJobName, outName
|
character(1024) getSolverJobName, outName
|
||||||
character(len=*), parameter :: pathSep = achar(47)//achar(92) ! /, \
|
character(len=*), parameter :: pathSep = achar(47)//achar(92) ! forward and backward slash
|
||||||
integer(pInt) extPos
|
integer(pInt) extPos
|
||||||
|
|
||||||
getSolverJobName=''
|
getSolverJobName=''
|
||||||
|
@ -262,7 +262,7 @@ subroutine hypela2(&
|
||||||
calcMode(nn,cp_en) = .not. calcMode(nn,cp_en) ! ping pong (calc <--> collect)
|
calcMode(nn,cp_en) = .not. calcMode(nn,cp_en) ! ping pong (calc <--> collect)
|
||||||
|
|
||||||
if ( calcMode(nn,cp_en) ) then ! now calc
|
if ( calcMode(nn,cp_en) ) then ! now calc
|
||||||
if ( lastMode .ne. calcMode(nn,cp_en) ) then ! first after ping pong
|
if ( lastMode .neqv. calcMode(nn,cp_en) ) then ! first after ping pong
|
||||||
call debug_reset() ! resets debugging
|
call debug_reset() ! resets debugging
|
||||||
outdatedFFN1 = .false.
|
outdatedFFN1 = .false.
|
||||||
cycleCounter = cycleCounter + 1
|
cycleCounter = cycleCounter + 1
|
||||||
|
@ -274,7 +274,7 @@ subroutine hypela2(&
|
||||||
computationMode = 2 ! plain calc
|
computationMode = 2 ! plain calc
|
||||||
endif
|
endif
|
||||||
else ! now collect
|
else ! now collect
|
||||||
if ( lastMode /= calcMode(nn,cp_en) ) call debug_info() ! first after ping pong reports debugging
|
if ( lastMode .neqv. calcMode(nn,cp_en) ) call debug_info() ! first after ping pong reports debugging
|
||||||
if ( lastIncConverged ) then
|
if ( lastIncConverged ) then
|
||||||
lastIncConverged = .false.
|
lastIncConverged = .false.
|
||||||
computationMode = 4 ! collect and backup Jacobian after convergence
|
computationMode = 4 ! collect and backup Jacobian after convergence
|
||||||
|
|
|
@ -55,7 +55,7 @@ function getSolverWorkingDirectoryName()
|
||||||
implicit none
|
implicit none
|
||||||
|
|
||||||
character(len=1024) cwd,outname,getSolverWorkingDirectoryName
|
character(len=1024) cwd,outname,getSolverWorkingDirectoryName
|
||||||
character(len=*), parameter :: pathSep = achar(47)//achar(92) ! /, \
|
character(len=*), parameter :: pathSep = achar(47)//achar(92) ! forward and backward slash
|
||||||
|
|
||||||
call getarg(2,outname) ! path to loadFile
|
call getarg(2,outname) ! path to loadFile
|
||||||
|
|
||||||
|
@ -83,7 +83,7 @@ function getSolverJobName()
|
||||||
implicit none
|
implicit none
|
||||||
|
|
||||||
character(1024) getSolverJobName, outName, cwd
|
character(1024) getSolverJobName, outName, cwd
|
||||||
character(len=*), parameter :: pathSep = achar(47)//achar(92) ! /, \
|
character(len=*), parameter :: pathSep = achar(47)//achar(92) ! forward and backward slash
|
||||||
integer(pInt) posExt,posSep
|
integer(pInt) posExt,posSep
|
||||||
|
|
||||||
getSolverJobName = ''
|
getSolverJobName = ''
|
||||||
|
@ -119,9 +119,10 @@ function getLoadcaseName()
|
||||||
implicit none
|
implicit none
|
||||||
|
|
||||||
character(len=1024) getLoadcaseName, outName, cwd
|
character(len=1024) getLoadcaseName, outName, cwd
|
||||||
character(len=*), parameter :: pathSep = achar(47)//achar(92) ! /, \
|
character(len=*), parameter :: pathSep = achar(47)//achar(92) ! forward and backward slash
|
||||||
integer(pInt) posExt,posSep
|
integer(pInt) posExt,posSep
|
||||||
posExt = 0 !not sure if its needed
|
|
||||||
|
posExt = 0 ! not sure if required
|
||||||
|
|
||||||
call getarg(2,getLoadcaseName)
|
call getarg(2,getLoadcaseName)
|
||||||
posExt = scan(getLoadcaseName,'.',back=.true.)
|
posExt = scan(getLoadcaseName,'.',back=.true.)
|
||||||
|
|
Loading…
Reference in New Issue