diff --git a/code/CPFEM.f90 b/code/CPFEM.f90 index 4d8b1e829..9184c5938 100644 --- a/code/CPFEM.f90 +++ b/code/CPFEM.f90 @@ -92,7 +92,7 @@ end subroutine subroutine CPFEM_init() use prec, only: pInt - use debug, only: debugger + use debug, only: debug_verbosity use IO, only: IO_read_jobBinaryFile use FEsolving, only: parallelExecution, & symmetricSolver, & @@ -125,9 +125,9 @@ subroutine CPFEM_init() ! *** restore the last converged values of each essential variable from the binary file if (restartRead) then - if (debugger) then + if (debug_verbosity > 0) then !$OMP CRITICAL (write2out) - write(6,'(a)') '<<< cpfem >>> Restored state variables of last converged step from binary files' + write(6,'(a)') '<< CPFEM >> Restored state variables of last converged step from binary files' !$OMP END CRITICAL (write2out) endif if (IO_read_jobBinaryFile(777,'recordedPhase',restartJob,size(material_phase))) then @@ -187,15 +187,16 @@ subroutine CPFEM_init() write(6,*) '<<<+- cpfem init -+>>>' write(6,*) '$Id$' write(6,*) - write(6,'(a32,x,6(i5,x))') 'CPFEM_cs: ', shape(CPFEM_cs) - write(6,'(a32,x,6(i5,x))') 'CPFEM_dcsdE: ', shape(CPFEM_dcsdE) - write(6,'(a32,x,6(i5,x))') 'CPFEM_dcsdE_knownGood: ', shape(CPFEM_dcsdE_knownGood) - write(6,*) - write(6,*) 'parallelExecution: ', parallelExecution - write(6,*) 'symmetricSolver: ', symmetricSolver + if (debug_verbosity > 0) then + write(6,'(a32,x,6(i5,x))') 'CPFEM_cs: ', shape(CPFEM_cs) + write(6,'(a32,x,6(i5,x))') 'CPFEM_dcsdE: ', shape(CPFEM_dcsdE) + write(6,'(a32,x,6(i5,x))') 'CPFEM_dcsdE_knownGood: ', shape(CPFEM_dcsdE_knownGood) + write(6,*) + write(6,*) 'parallelExecution: ', parallelExecution + write(6,*) 'symmetricSolver: ', symmetricSolver + endif call flush(6) !$OMP END CRITICAL (write2out) - return endsubroutine @@ -214,11 +215,11 @@ subroutine CPFEM_general(mode, ffn, ffn1, Temperature, dt, element, IP, cauchySt use numerics, only: relevantStrain, & defgradTolerance, & iJacoStiffness - use debug, only: debug_g, & + use debug, only: debug_e, & debug_i, & - debug_e, & - debugger, & - verboseDebugger, & + debug_g, & + debug_selectiveDebugger, & + debug_verbosity, & debug_stressMaxLocation, & debug_stressMinLocation, & debug_jacobianMaxLocation, & @@ -332,17 +333,17 @@ subroutine CPFEM_general(mode, ffn, ffn1, Temperature, dt, element, IP, cauchySt cp_en = mesh_FEasCP('elem',element) - if (cp_en == debug_e .and. IP == debug_i) then + if (debug_verbosity > 0 .and. cp_en == 1 .and. IP == 1) then !$OMP CRITICAL (write2out) write(6,*) - write(6,'(a)') '#######################################################' - write(6,'(a32,x,i5,x,i2)') 'reporting for element, ip:',cp_en,IP - write(6,'(a32,x,f15.7)') 'theTime',theTime - write(6,'(a32,x,f15.7)') 'theDelta',theDelta - write(6,'(a32,x,i8)') 'theInc',theInc - write(6,'(a32,x,i8)') 'cycleCounter',cycleCounter - write(6,'(a32,x,i8)') 'computationMode',mode - write(6,'(a)') '#######################################################' + write(6,'(a)') '#############################################' + write(6,'(a1,a22,x,f15.7,a6)') '#','theTime',theTime,'#' + write(6,'(a1,a22,x,f15.7,a6)') '#','theDelta',theDelta,'#' + write(6,'(a1,a22,x,i8,a13)') '#','theInc',theInc,'#' + write(6,'(a1,a22,x,i8,a13)') '#','cycleCounter',cycleCounter,'#' + write(6,'(a1,a22,x,i8,a13)') '#','computationMode',mode,'#' + write(6,'(a)') '#############################################' + write(6,*) call flush (6) !$OMP END CRITICAL (write2out) endif @@ -363,10 +364,13 @@ subroutine CPFEM_general(mode, ffn, ffn1, Temperature, dt, element, IP, cauchySt j = 1:mesh_maxNips, & k = 1:mesh_NcpElems ) & constitutive_state0(i,j,k)%p = constitutive_state(i,j,k)%p ! microstructure of crystallites - if (cp_en == debug_e .and. IP == debug_i) then + if (debug_verbosity > 0) then !$OMP CRITICAL (write2out) - write(6,'(a,x,i8,x,i2,/,4(3(e20.8,x),/))') '<< cpfem >> AGED state of grain 1, element ip',& - cp_en,IP, constitutive_state(1,IP,cp_en)%p + write(6,'(a)') '<< CPFEM >> Aging states' + if (debug_e == cp_en .and. debug_i == IP) then + write(6,'(a,x,i5,x,i2,x,i3,/,(12(x),6(e20.8,x),/))') '<< CPFEM >> AGED state of element ip grain',& + cp_en, IP, 1, constitutive_state(1,IP,cp_en)%p + endif !$OMP END CRITICAL (write2out) endif do k = 1,mesh_NcpElems @@ -379,9 +383,9 @@ subroutine CPFEM_general(mode, ffn, ffn1, Temperature, dt, element, IP, cauchySt ! *** dump the last converged values of each essential variable to a binary file if (restartWrite) then - if (debugger) then + if (debug_verbosity > 0) then !$OMP CRITICAL (write2out) - write(6,'(a)') '<<< cpfem >>> Writing state variables of last converged step to binary files' + write(6,'(a)') '<< CPFEM >> Writing state variables of last converged step to binary files' !$OMP END CRITICAL (write2out) endif if (IO_write_jobBinaryFile(777,'recordedPhase',size(material_phase))) then @@ -445,11 +449,13 @@ subroutine CPFEM_general(mode, ffn, ffn1, Temperature, dt, element, IP, cauchySt ! deformation gradient outdated or any actual deformation gradient differs more than relevantStrain from the stored one if (terminallyIll .or. outdatedFFN1 .or. any(abs(ffn1 - materialpoint_F(1:3,1:3,IP,cp_en)) > defgradTolerance)) then if (.not. terminallyIll .and. .not. outdatedFFN1) then - !$OMP CRITICAL (write2out) - write(6,'(a,x,i5,x,i2)') '<< cpfem >> OUTDATED at element ip',cp_en,IP - write(6,'(a,/,3(3(f10.6,x),/))') ' FFN1 old:',math_transpose3x3(materialpoint_F(1:3,1:3,IP,cp_en)) - write(6,'(a,/,3(3(f10.6,x),/))') ' FFN1 now:',math_transpose3x3(ffn1) - !$OMP END CRITICAL (write2out) + if (debug_verbosity > 0) then + !$OMP CRITICAL (write2out) + write(6,'(a,x,i5,x,i2)') '<< CPFEM >> OUTDATED at element ip',cp_en,IP + write(6,'(a,/,3(12(x),3(f10.6,x),/))') '<< CPFEM >> FFN1 old:',math_transpose3x3(materialpoint_F(1:3,1:3,IP,cp_en)) + write(6,'(a,/,3(12(x),3(f10.6,x),/))') '<< CPFEM >> FFN1 now:',math_transpose3x3(ffn1) + !$OMP END CRITICAL (write2out) + endif outdatedFFN1 = .true. endif call random_number(rnd) @@ -469,11 +475,21 @@ subroutine CPFEM_general(mode, ffn, ffn1, Temperature, dt, element, IP, cauchySt FEsolving_execElem(2) = cp_en FEsolving_execIP(1,cp_en) = IP FEsolving_execIP(2,cp_en) = IP + if (debug_verbosity > 0) then + !$OMP CRITICAL (write2out) + write(6,'(a,i5,x,i2)') '<< CPFEM >> Calculation for element ip ',cp_en,IP + !$OMP END CRITICAL (write2out) + endif call materialpoint_stressAndItsTangent(updateJaco, dt) ! calculate stress and its tangent call materialpoint_postResults(dt) ! post results ! parallel computation and calulation not yet done elseif (.not. CPFEM_calc_done) then + if (debug_verbosity > 0) then + !$OMP CRITICAL (write2out) + write(6,'(a,i5,a,i5)') '<< CPFEM >> Calculation for elements ',FEsolving_execElem(1),' to ',FEsolving_execElem(2) + !$OMP END CRITICAL (write2out) + endif call materialpoint_stressAndItsTangent(updateJaco, dt) ! calculate stress and its tangent (parallel execution inside) call materialpoint_postResults(dt) ! post results do e = FEsolving_execElem(1),FEsolving_execElem(2) ! loop over all parallely processed elements @@ -556,10 +572,10 @@ subroutine CPFEM_general(mode, ffn, ffn1, Temperature, dt, element, IP, cauchySt call IO_warning(601,cp_en,IP) endif - if (cp_en == debug_e .and. IP == debug_i .and. mode < 6) then + if (mode < 6 .and. debug_verbosity > 0 .and. ((debug_e == cp_en .and. debug_i == IP) .or. .not. debug_selectiveDebugger)) then !$OMP CRITICAL (write2out) - write(6,'(a,x,i2,x,a,x,i4,/,6(f10.3,x)/)') 'stress/MPa at ip', IP, 'el', cp_en, cauchyStress/1e6 - write(6,'(a,x,i2,x,a,x,i4,/,6(6(f10.3,x)/))') 'jacobian/GPa at ip', IP, 'el', cp_en, transpose(jacobian)/1e9 + write(6,'(a,i5,x,i2,/,12(x),6(f10.3,x)/)') '<< CPFEM >> stress/MPa at el ip ', cp_en, IP, cauchyStress/1e6 + write(6,'(a,i5,x,i2,/,6(12(x),6(f10.3,x)/))') '<< CPFEM >> jacobian/GPa at el ip ', cp_en, IP, transpose(jacobian)/1e9 call flush(6) !$OMP END CRITICAL (write2out) endif diff --git a/code/FEsolving.f90 b/code/FEsolving.f90 index 5fc11f908..183b63f97 100644 --- a/code/FEsolving.f90 +++ b/code/FEsolving.f90 @@ -28,6 +28,7 @@ subroutine FE_init() use prec, only: pInt + use debug, only: debug_verbosity use IO implicit none @@ -83,14 +84,13 @@ write(6,*) '<<<+- FEsolving init -+>>>' write(6,*) '$Id$' write(6,*) - write(6,*) 'restart writing: ', restartWrite - write(6,*) 'restart reading: ', restartRead - if (restartRead) write(6,*) 'restart Job: ', trim(restartJob) - write(6,*) + if (debug_verbosity > 0) then + write(6,*) 'restart writing: ', restartWrite + write(6,*) 'restart reading: ', restartRead + if (restartRead) write(6,*) 'restart Job: ', trim(restartJob) + write(6,*) + endif !$OMP END CRITICAL (write2out) - - - return end subroutine diff --git a/code/constitutive.f90 b/code/constitutive.f90 index 106a6ecbb..ccfc82202 100644 --- a/code/constitutive.f90 +++ b/code/constitutive.f90 @@ -49,7 +49,7 @@ subroutine constitutive_init() !* Module initialization * !************************************** use prec, only: pReal,pInt - use debug, only: debugger, selectiveDebugger, debug_e, debug_i, debug_g + use debug, only: debug_verbosity, debug_selectiveDebugger, debug_e, debug_i, debug_g use numerics, only: numerics_integrator use IO, only: IO_error, IO_open_file, IO_open_jobFile use mesh, only: mesh_maxNips,mesh_NcpElems,mesh_element,FE_Nips @@ -289,24 +289,26 @@ subroutine constitutive_init() constitutive_maxSizePostResults = maxval(constitutive_sizePostResults) !$OMP CRITICAL (write2out) - write(6,*) - write(6,*) '<<<+- constitutive init -+>>>' - write(6,*) '$Id$' - write(6,*) - write(6,'(a32,x,7(i5,x))') 'constitutive_state0: ', shape(constitutive_state0) - write(6,'(a32,x,7(i5,x))') 'constitutive_partionedState0: ', shape(constitutive_partionedState0) - write(6,'(a32,x,7(i5,x))') 'constitutive_subState0: ', shape(constitutive_subState0) - write(6,'(a32,x,7(i5,x))') 'constitutive_state: ', shape(constitutive_state) - write(6,'(a32,x,7(i5,x))') 'constitutive_aTolState: ', shape(constitutive_aTolState) - write(6,'(a32,x,7(i5,x))') 'constitutive_dotState: ', shape(constitutive_dotState) - write(6,'(a32,x,7(i5,x))') 'constitutive_sizeState: ', shape(constitutive_sizeState) - write(6,'(a32,x,7(i5,x))') 'constitutive_sizeDotState: ', shape(constitutive_sizeDotState) - write(6,'(a32,x,7(i5,x))') 'constitutive_sizePostResults: ', shape(constitutive_sizePostResults) - write(6,*) - write(6,'(a32,x,7(i5,x))') 'maxSizeState: ', constitutive_maxSizeState - write(6,'(a32,x,7(i5,x))') 'maxSizeDotState: ', constitutive_maxSizeDotState - write(6,'(a32,x,7(i5,x))') 'maxSizePostResults: ', constitutive_maxSizePostResults - call flush(6) + write(6,*) + write(6,*) '<<<+- constitutive init -+>>>' + write(6,*) '$Id$' + write(6,*) + if (debug_verbosity > 0) then + write(6,'(a32,x,7(i5,x))') 'constitutive_state0: ', shape(constitutive_state0) + write(6,'(a32,x,7(i5,x))') 'constitutive_partionedState0: ', shape(constitutive_partionedState0) + write(6,'(a32,x,7(i5,x))') 'constitutive_subState0: ', shape(constitutive_subState0) + write(6,'(a32,x,7(i5,x))') 'constitutive_state: ', shape(constitutive_state) + write(6,'(a32,x,7(i5,x))') 'constitutive_aTolState: ', shape(constitutive_aTolState) + write(6,'(a32,x,7(i5,x))') 'constitutive_dotState: ', shape(constitutive_dotState) + write(6,'(a32,x,7(i5,x))') 'constitutive_sizeState: ', shape(constitutive_sizeState) + write(6,'(a32,x,7(i5,x))') 'constitutive_sizeDotState: ', shape(constitutive_sizeDotState) + write(6,'(a32,x,7(i5,x))') 'constitutive_sizePostResults: ', shape(constitutive_sizePostResults) + write(6,*) + write(6,'(a32,x,7(i5,x))') 'maxSizeState: ', constitutive_maxSizeState + write(6,'(a32,x,7(i5,x))') 'maxSizeDotState: ', constitutive_maxSizeDotState + write(6,'(a32,x,7(i5,x))') 'maxSizePostResults: ', constitutive_maxSizePostResults + endif + call flush(6) !$OMP END CRITICAL (write2out) return @@ -533,7 +535,8 @@ subroutine constitutive_collectDotState(Tstar_v, Fe, Fp, Temperature, subdt, ori use prec, only: pReal, pInt use debug, only: debug_cumDotStateCalls, & - debug_cumDotStateTicks + debug_cumDotStateTicks, & + debug_verbosity use mesh, only: mesh_NcpElems, & mesh_maxNips, & mesh_maxNipNeighbors @@ -574,7 +577,9 @@ integer(pLongInt) tick, tock, & tickrate, & maxticks -call system_clock(count=tick,count_rate=tickrate,count_max=maxticks) +if (debug_verbosity > 0) then + call system_clock(count=tick,count_rate=tickrate,count_max=maxticks) +endif select case (phase_constitution(material_phase(ipc,ip,el))) @@ -596,12 +601,15 @@ select case (phase_constitution(material_phase(ipc,ip,el))) end select -call system_clock(count=tock,count_rate=tickrate,count_max=maxticks) -!$OMP CRITICAL (debugTimingDotState) - debug_cumDotStateCalls = debug_cumDotStateCalls + 1_pInt - debug_cumDotStateTicks = debug_cumDotStateTicks + tock-tick - if (tock < tick) debug_cumDotStateTicks = debug_cumDotStateTicks + maxticks -!$OMP END CRITICAL (debugTimingDotState) +if (debug_verbosity > 0) then + call system_clock(count=tock,count_rate=tickrate,count_max=maxticks) + !$OMP CRITICAL (debugTimingDotState) + debug_cumDotStateCalls = debug_cumDotStateCalls + 1_pInt + debug_cumDotStateTicks = debug_cumDotStateTicks + tock-tick + !$OMP FLUSH (debug_cumDotStateTicks) + if (tock < tick) debug_cumDotStateTicks = debug_cumDotStateTicks + maxticks + !$OMP END CRITICAL (debugTimingDotState) +endif endsubroutine @@ -615,7 +623,8 @@ function constitutive_dotTemperature(Tstar_v,Temperature,ipc,ip,el) use prec, only: pReal,pInt use debug, only: debug_cumDotTemperatureCalls, & - debug_cumDotTemperatureTicks + debug_cumDotTemperatureTicks, & + debug_verbosity use material, only: phase_constitution, & material_phase use constitutive_j2, only: constitutive_j2_dotTemperature, & @@ -647,7 +656,9 @@ integer(pLongInt) tick, tock, & maxticks -call system_clock(count=tick,count_rate=tickrate,count_max=maxticks) +if (debug_verbosity > 0) then + call system_clock(count=tick,count_rate=tickrate,count_max=maxticks) +endif select case (phase_constitution(material_phase(ipc,ip,el))) @@ -668,12 +679,15 @@ select case (phase_constitution(material_phase(ipc,ip,el))) end select -call system_clock(count=tock,count_rate=tickrate,count_max=maxticks) -!$OMP CRITICAL (debugTimingDotTemperature) - debug_cumDotTemperatureCalls = debug_cumDotTemperatureCalls + 1_pInt - debug_cumDotTemperatureTicks = debug_cumDotTemperatureTicks + tock-tick - if (tock < tick) debug_cumDotTemperatureTicks = debug_cumDotTemperatureTicks + maxticks -!$OMP END CRITICAL (debugTimingDotTemperature) +if (debug_verbosity > 0) then + call system_clock(count=tock,count_rate=tickrate,count_max=maxticks) + !$OMP CRITICAL (debugTimingDotTemperature) + debug_cumDotTemperatureCalls = debug_cumDotTemperatureCalls + 1_pInt + debug_cumDotTemperatureTicks = debug_cumDotTemperatureTicks + tock-tick + !$OMP FLUSH (debug_cumDotTemperatureTicks) + if (tock < tick) debug_cumDotTemperatureTicks = debug_cumDotTemperatureTicks + maxticks + !$OMP END CRITICAL (debugTimingDotTemperature) +endif endfunction diff --git a/code/constitutive_dislotwin.f90 b/code/constitutive_dislotwin.f90 index 9702aacfa..64a4ab135 100644 --- a/code/constitutive_dislotwin.f90 +++ b/code/constitutive_dislotwin.f90 @@ -122,10 +122,12 @@ integer(pInt) section,maxNinstance,f,i,j,k,l,m,n,o,p,q,r,s,s1,s2,t1,t2,ns,nt,out character(len=64) tag character(len=1024) line -!write(6,*) -!write(6,'(a20,a20,a12)') '<<<+- constitutive_',constitutive_dislotwin_label,' init -+>>>' -!write(6,*) '$Id$' -!write(6,*) +!$OMP CRITICAL (write2out) + write(6,*) + write(6,'(a20,a20,a12)') '<<<+- constitutive_',constitutive_dislotwin_label,' init -+>>>' + write(6,*) '$Id$' + write(6,*) +!$OMP END CRITICAL (write2out) maxNinstance = count(phase_constitution == constitutive_dislotwin_label) if (maxNinstance == 0) return diff --git a/code/constitutive_j2.f90 b/code/constitutive_j2.f90 index 86adfca64..757dfbf3e 100644 --- a/code/constitutive_j2.f90 +++ b/code/constitutive_j2.f90 @@ -68,6 +68,7 @@ subroutine constitutive_j2_init(file) use math, only: math_Mandel3333to66, math_Voigt66to3333 use IO use material + use debug, only: debug_verbosity integer(pInt), intent(in) :: file integer(pInt), parameter :: maxNchunks = 7 integer(pInt), dimension(1+2*maxNchunks) :: positions @@ -76,19 +77,21 @@ subroutine constitutive_j2_init(file) character(len=1024) line !$OMP CRITICAL (write2out) - write(6,*) - write(6,'(a20,a20,a12)') '<<<+- constitutive_',constitutive_j2_label,' init -+>>>' - write(6,*) '$Id$' - write(6,*) + write(6,*) + write(6,'(a20,a20,a12)') '<<<+- constitutive_',constitutive_j2_label,' init -+>>>' + write(6,*) '$Id$' + write(6,*) !$OMP END CRITICAL (write2out) maxNinstance = count(phase_constitution == constitutive_j2_label) if (maxNinstance == 0) return - !$OMP CRITICAL (write2out) - write(6,'(a16,x,i5)') '# instances:',maxNinstance - write(6,*) - !$OMP END CRITICAL (write2out) + if (debug_verbosity > 0) then + !$OMP CRITICAL (write2out) + write(6,'(a16,x,i5)') '# instances:',maxNinstance + write(6,*) + !$OMP END CRITICAL (write2out) + endif allocate(constitutive_j2_sizeDotState(maxNinstance)) ; constitutive_j2_sizeDotState = 0_pInt allocate(constitutive_j2_sizeState(maxNinstance)) ; constitutive_j2_sizeState = 0_pInt diff --git a/code/constitutive_nonlocal.f90 b/code/constitutive_nonlocal.f90 index 60782dbd0..7a7c8e1cb 100644 --- a/code/constitutive_nonlocal.f90 +++ b/code/constitutive_nonlocal.f90 @@ -120,6 +120,7 @@ use IO, only: IO_lc, & IO_floatValue, & IO_intValue, & IO_error +use debug, only: debug_verbosity use mesh, only: mesh_NcpElems, & mesh_maxNips, & FE_maxNipNeighbors @@ -180,6 +181,12 @@ character(len=1024) line maxNinstance = count(phase_constitution == constitutive_nonlocal_label) if (maxNinstance == 0) return ! we don't have to do anything if there's no instance for this constitutive law +if (debug_verbosity > 0) then + !$OMP CRITICAL (write2out) + write(6,'(a16,x,i5)') '# instances:',maxNinstance + !$OMP END CRITICAL (write2out) +endif + !*** space allocation for global variables @@ -805,8 +812,11 @@ use math, only: math_Plain3333to99, & math_det3x3, & math_transpose3x3, & pi -use debug, only: debugger, & - verboseDebugger +use debug, only: debug_verbosity, & + debug_selectiveDebugger, & + debug_g, & + debug_i, & + debug_e use mesh, only: mesh_NcpElems, & mesh_maxNips, & mesh_maxNipNeighbors, & @@ -918,7 +928,6 @@ forall (s = 1:ns) & constitutive_nonlocal_forestProjectionEdge(s, 1:ns, myInstance) ) & + dot_product( ( sum(abs(rhoSgl(1:ns,(/3,4,7,8/))),2) + rhoDip(1:ns,2) ), & constitutive_nonlocal_forestProjectionScrew(s, 1:ns, myInstance) ) ! calculation of forest dislocation density as projection of screw and edge dislocations -! if (debugger) write(6,'(a30,3(i3,x),/,12(e10.3,x),/)') 'forest dislocation density at ',g,ip,el, rhoForest !*** calculate the threshold shear stress for dislocation slip @@ -928,7 +937,6 @@ forall (s = 1:ns) & * constitutive_nonlocal_burgersPerSlipSystem(s, myInstance) & * sqrt( dot_product( ( sum(abs(rhoSgl),2) + sum(abs(rhoDip),2) ), & constitutive_nonlocal_interactionMatrixSlipSlip(s, 1:ns, myInstance) ) ) -! if (debugger) write(6,'(a22,3(i3,x),/,12(f10.5,x),/)') 'tauThreshold / MPa at ',g,ip,el, tauThreshold/1e6 !*** calculate the dislocation stress of the neighboring excess dislocation densities @@ -1021,6 +1029,16 @@ if (.not. phase_localConstitution(myPhase)) then endif +if (debug_verbosity > 6 .and. ((debug_e == el .and. debug_i == ip .and. debug_g == g) .or. .not. debug_selectiveDebugger)) then + !$OMP CRITICAL (write2out) + write(6,*) + write(6,'(a,i5,x,i2,x,i1)') '<< CONST >> nonlocal_microstructure at el ip g',el,ip,g + write(6,*) + write(6,'(a,/,12(x),12(e10.3,x))') '<< CONST >> rhoForest', rhoForest + write(6,'(a,/,12(x),12(f10.5,x))') '<< CONST >> tauThreshold / MPa', tauThreshold/1e6 + write(6,'(a,/,3(12(x),3(f10.5,x),/))') '<< CONST >> Tdislocation / MPa', math_Mandel6to33(Tdislocation_v)/1e6 + !$OMP END CRITICAL (write2out) +endif !********************************************************************** !*** set states @@ -1045,8 +1063,8 @@ use prec, only: pReal, & p_vec use math, only: math_mul6x6, & math_Mandel6to33 -use debug, only: debugger, & - verboseDebugger, & +use debug, only: debug_verbosity, & + debug_selectiveDebugger, & debug_g, & debug_i, & debug_e @@ -1148,17 +1166,15 @@ endif constitutive_nonlocal_v(1:ns,1:4,g,ip,el) = v !$OMP FLUSH(constitutive_nonlocal_v) -!if (verboseDebugger .and. s) then -! !$OMP CRITICAL (write2out) -! write(6,*) '::: kinetics',g,ip,el -! write(6,*) -! write(6,'(a,/,3(3(f12.3,x)/))') 'Tdislocation / MPa', math_Mandel6to33(Tdislocation_v/1e6) -! write(6,'(a,/,3(3(f12.3,x)/))') 'Tstar / MPa', math_Mandel6to33(Tstar_v/1e6) -! write(6,'(a,/,12(f12.5,x),/)') 'tau / MPa', tau/1e6_pReal -! write(6,'(a,/,12(e12.5,x),/)') 'rhoForest / 1/m**2', rhoForest -! write(6,'(a,/,4(12(f12.5,x),/))') 'v / 1e-3m/s', constitutive_nonlocal_v(:,:,g,ip,el)*1e3 -! !$OMP END CRITICAL (write2out) -!endif +if (debug_verbosity > 6 .and. ((debug_e == el .and. debug_i == ip .and. debug_g == g) .or. .not. debug_selectiveDebugger)) then + !$OMP CRITICAL (write2out) + write(6,*) + write(6,'(a,i5,x,i2,x,i1)') '<< CONST >> nonlocal_kinetics at el ip g',el,ip,g + write(6,*) + write(6,'(a,/,12(x),12(f12.5,x))') '<< CONST >> tau / MPa', tau/1e6_pReal + write(6,'(a,/,4(12(x),12(f12.5,x),/))') '<< CONST >> v / 1e-3m/s', constitutive_nonlocal_v(:,:,g,ip,el)*1e3 + !$OMP END CRITICAL (write2out) +endif endsubroutine @@ -1175,8 +1191,8 @@ use prec, only: pReal, & use math, only: math_Plain3333to99, & math_mul6x6, & math_Mandel6to33 -use debug, only: debugger, & - verboseDebugger, & +use debug, only: debug_verbosity, & + debug_selectiveDebugger, & debug_g, & debug_i, & debug_e @@ -1273,18 +1289,16 @@ do s = 1,ns enddo dLp_dTstar99 = math_Plain3333to99(dLp_dTstar3333) - -!if (verboseDebugger .and. (debug_g==g .and. debug_i==i .and. debug_e==e)) then -! !$OMP CRITICAL (write2out) -! write(6,*) '::: LpandItsTangent',g,ip,el -! write(6,*) -! write(6,'(a,/,12(f12.5,x),/)') 'v / 1e-3m/s', constitutive_nonlocal_v(:,:,g,ip,el)*1e3 -! write(6,'(a,/,12(f12.5,x),/)') 'gdot / 1e-3',gdot*1e3_pReal -! write(6,'(a,/,12(f12.5,x),/)') 'gdot total / 1e-3',gdotTotal*1e3_pReal -! write(6,'(a,/,3(3(f12.7,x)/))') 'Lp',Lp -! ! call flush(6) -! !$OMP END CRITICAL (write2out) -!endif +if (debug_verbosity > 6 .and. ((debug_e == el .and. debug_i == ip .and. debug_g == g) .or. .not. debug_selectiveDebugger)) then + !$OMP CRITICAL (write2out) + write(6,*) + write(6,'(a,i5,x,i2,x,i1)') '<< CONST >> nonlocal_LpandItsTangent at el ip g ',el,ip,g + write(6,*) + write(6,'(a,/,4(12(x),12(f12.5,x)),/)') '<< CONST >> gdot / 1e-3',gdot*1e3_pReal + write(6,'(a,/,12(x),12(f12.5,x))') '<< CONST >> gdot total / 1e-3',gdotTotal*1e3_pReal + write(6,'(a,/,3(12(x),3(f12.7,x),/))') '<< CONST >> Lp',Lp + !$OMP END CRITICAL (write2out) +endif endsubroutine @@ -1300,11 +1314,11 @@ use prec, only: pReal, & p_vec use numerics, only: numerics_integrationMode use IO, only: IO_error -use debug, only: debugger, & +use debug, only: debug_verbosity, & + debug_selectiveDebugger, & debug_g, & debug_i, & - debug_e, & - verboseDebugger + debug_e use math, only: math_norm3, & math_mul6x6, & math_mul3x3, & @@ -1428,9 +1442,10 @@ real(pReal) area, & ! area logical considerEnteringFlux, & considerLeavingFlux -if (verboseDebugger .and. (debug_g==g .and. debug_i==ip .and. debug_e==el)) then +if (debug_verbosity > 6 .and. ((debug_e == el .and. debug_i == ip .and. debug_g == g) .or. .not. debug_selectiveDebugger)) then !$OMP CRITICAL (write2out) - write(6,*) '::: constitutive_nonlocal_dotState at ',g,ip,el + write(6,*) + write(6,'(a,i5,x,i2,x,i1)') '<< CONST >> nonlocal_dotState at el ip g ',el,ip,g write(6,*) !$OMP END CRITICAL (write2out) endif @@ -1484,11 +1499,10 @@ forall (s = 1:ns, t = 1:4, rhoSgl(s,t+4) * constitutive_nonlocal_v(s,t,g,ip,el) gdot(s,t) = gdot(s,t) + abs(rhoSgl(s,t+4)) * constitutive_nonlocal_burgersPerSlipSystem(s,myInstance) & * constitutive_nonlocal_v(s,t,g,ip,el) -if (verboseDebugger .and. (debug_g==g .and. debug_i==ip .and. debug_e==el)) then +if (debug_verbosity > 6 .and. ((debug_e == el .and. debug_i == ip .and. debug_g == g) .or. .not. debug_selectiveDebugger)) then !$OMP CRITICAL (write2out) - write(6,'(a,/,10(12(e12.5,x),/))') 'rho / 1/m^2', rhoSgl, rhoDip - write(6,'(a,/,4(12(e12.5,x),/))') 'v / m/s', constitutive_nonlocal_v(:,:,g,ip,el) - write(6,'(a,/,4(12(e12.5,x),/))') 'gdot / 1/s',gdot + write(6,'(a,/,10(12(x),12(e12.5,x),/))') '<< CONST >> rho / 1/m^2', rhoSgl, rhoDip + write(6,'(a,/,4(12(x),12(e12.5,x),/))') '<< CONST >> gdot / 1/s',gdot !$OMP END CRITICAL (write2out) endif @@ -1738,18 +1752,20 @@ forall (t = 1:10) & + rhoDotAthermalAnnihilation(1:ns,t) & + rhoDotThermalAnnihilation(1:ns,t) -if (verboseDebugger .and. (debug_g==g .and. debug_i==ip .and. debug_e==el)) then +if (debug_verbosity > 6 .and. ((debug_e == el .and. debug_i == ip .and. debug_g == g) .or. .not. debug_selectiveDebugger)) then !$OMP CRITICAL (write2out) - write(6,'(a,/,8(12(e12.5,x),/))') 'dislocation remobilization', rhoDotRemobilization(1:ns,1:8) * timestep - write(6,'(a,/,4(12(e12.5,x),/))') 'dislocation multiplication', rhoDotMultiplication(1:ns,1:4) * timestep - write(6,'(a,/,8(12(e12.5,x),/))') 'dislocation flux', rhoDotFlux(1:ns,1:8) * timestep - write(6,'(a,/,10(12(e12.5,x),/))') 'dipole formation by glide', rhoDotSingle2DipoleGlide * timestep - write(6,'(a,/,2(12(e12.5,x),/))') 'athermal dipole annihilation', rhoDotAthermalAnnihilation(1:ns,1:2) * timestep - write(6,'(a,/,2(12(e12.5,x),/))') 'thermally activated dipole annihilation', rhoDotThermalAnnihilation(1:ns,9:10) * timestep - write(6,'(a,/,10(12(e12.5,x),/))') 'total density change', rhoDot * timestep - write(6,'(a,/,10(12(f12.7,x),/))') 'relative density change', rhoDot(1:ns,1:8) * timestep / (abs(rhoSgl)+1.0e-10), & - rhoDot(1:ns,9:10) * timestep / (rhoDip+1.0e-10) - write(6,*) + write(6,'(a,/,8(12(x),12(e12.5,x),/))') '<< CONST >> dislocation remobilization', rhoDotRemobilization(1:ns,1:8) * timestep + write(6,'(a,/,4(12(x),12(e12.5,x),/))') '<< CONST >> dislocation multiplication', rhoDotMultiplication(1:ns,1:4) * timestep + write(6,'(a,/,8(12(x),12(e12.5,x),/))') '<< CONST >> dislocation flux', rhoDotFlux(1:ns,1:8) * timestep + write(6,'(a,/,10(12(x),12(e12.5,x),/))') '<< CONST >> dipole formation by glide', rhoDotSingle2DipoleGlide * timestep + write(6,'(a,/,2(12(x),12(e12.5,x),/))') '<< CONST >> athermal dipole annihilation', & + rhoDotAthermalAnnihilation(1:ns,1:2) * timestep + write(6,'(a,/,2(12(x),12(e12.5,x),/))') '<< CONST >> thermally activated dipole annihilation', & + rhoDotThermalAnnihilation(1:ns,9:10) * timestep + write(6,'(a,/,10(12(x),12(e12.5,x),/))') '<< CONST >> total density change', rhoDot * timestep + write(6,'(a,/,10(12(x),12(f12.7,x),/))') '<< CONST >> relative density change', & + rhoDot(1:ns,1:8) * timestep / (abs(rhoSgl)+1.0e-10), & + rhoDot(1:ns,9:10) * timestep / (rhoDip+1.0e-10) !$OMP END CRITICAL (write2out) endif diff --git a/code/constitutive_phenopowerlaw.f90 b/code/constitutive_phenopowerlaw.f90 index c5b514312..7e89b3c93 100644 --- a/code/constitutive_phenopowerlaw.f90 +++ b/code/constitutive_phenopowerlaw.f90 @@ -133,6 +133,7 @@ subroutine constitutive_phenopowerlaw_init(file) use math, only: math_Mandel3333to66, math_Voigt66to3333 use IO use material + use debug, only: debug_verbosity use lattice, only: lattice_initializeStructure, lattice_symmetryType, & lattice_maxNslipFamily, lattice_maxNtwinFamily, & @@ -151,19 +152,21 @@ subroutine constitutive_phenopowerlaw_init(file) character(len=1024) line !$OMP CRITICAL (write2out) - write(6,*) - write(6,'(a20,a20,a12)') '<<<+- constitutive_',constitutive_phenopowerlaw_label,' init -+>>>' - write(6,*) '$Id$' - write(6,*) + write(6,*) + write(6,'(a20,a20,a12)') '<<<+- constitutive_',constitutive_phenopowerlaw_label,' init -+>>>' + write(6,*) '$Id$' + write(6,*) !$OMP END CRITICAL (write2out) maxNinstance = count(phase_constitution == constitutive_phenopowerlaw_label) if (maxNinstance == 0) return - !$OMP CRITICAL (write2out) - write(6,'(a16,x,i5)') '# instances:',maxNinstance - write(6,*) - !$OMP END CRITICAL (write2out) + if (debug_verbosity > 0) then + !$OMP CRITICAL (write2out) + write(6,'(a16,x,i5)') '# instances:',maxNinstance + write(6,*) + !$OMP END CRITICAL (write2out) + endif allocate(constitutive_phenopowerlaw_sizeDotState(maxNinstance)) ; constitutive_phenopowerlaw_sizeDotState = 0_pInt allocate(constitutive_phenopowerlaw_sizeState(maxNinstance)) ; constitutive_phenopowerlaw_sizeState = 0_pInt diff --git a/code/crystallite.f90 b/code/crystallite.f90 index 0c22a1a15..68bf01db1 100644 --- a/code/crystallite.f90 +++ b/code/crystallite.f90 @@ -85,7 +85,8 @@ subroutine crystallite_init(Temperature) use prec, only: pInt, & pReal use debug, only: debug_info, & - debug_reset + debug_reset, & + debug_verbosity use numerics, only: subStepSizeCryst, & stepIncreaseCryst use math, only: math_I3, & @@ -106,6 +107,7 @@ use lattice, only: lattice_symmetryType, & lattice_Sslip,lattice_Sslip_v,lattice_Stwin,lattice_Stwin_v, lattice_maxNslipFamily, lattice_maxNtwinFamily, & lattice_NslipSystem,lattice_NtwinSystem +use constitutive, only: constitutive_microstructure use constitutive_phenopowerlaw, only: constitutive_phenopowerlaw_label, & constitutive_phenopowerlaw_structure, & constitutive_phenopowerlaw_Nslip @@ -304,15 +306,6 @@ close(file) enddo enddo !$OMP ENDDO -!$OMP DO - do e = FEsolving_execElem(1),FEsolving_execElem(2) ! iterate over all cp elements - myNgrains = homogenization_Ngrains(mesh_element(3,e)) ! look up homogenization-->grainCount - do i = FEsolving_execIP(1,e),FEsolving_execIP(2,e) ! iterate over IPs of this element - do g = 1,myNgrains - enddo - enddo - enddo -!$OMP ENDDO crystallite_partionedTemperature0 = Temperature ! isothermal assumption crystallite_partionedFp0 = crystallite_Fp0 crystallite_partionedF0 = crystallite_F0 @@ -358,54 +351,56 @@ call crystallite_stressAndItsTangent(.true.) ! request elastic crystallite_fallbackdPdF = crystallite_dPdF ! use initial elastic stiffness as fallback ! *** Output to MARC output file *** -!$OMP CRITICAL (write2out) -write(6,'(a35,x,7(i5,x))') 'crystallite_Temperature: ', shape(crystallite_Temperature) -write(6,'(a35,x,7(i5,x))') 'crystallite_dotTemperature: ', shape(crystallite_dotTemperature) -write(6,'(a35,x,7(i5,x))') 'crystallite_Fe: ', shape(crystallite_Fe) -write(6,'(a35,x,7(i5,x))') 'crystallite_Fp: ', shape(crystallite_Fp) -write(6,'(a35,x,7(i5,x))') 'crystallite_Lp: ', shape(crystallite_Lp) -write(6,'(a35,x,7(i5,x))') 'crystallite_F0: ', shape(crystallite_F0) -write(6,'(a35,x,7(i5,x))') 'crystallite_Fp0: ', shape(crystallite_Fp0) -write(6,'(a35,x,7(i5,x))') 'crystallite_Lp0: ', shape(crystallite_Lp0) -write(6,'(a35,x,7(i5,x))') 'crystallite_partionedF: ', shape(crystallite_partionedF) -write(6,'(a35,x,7(i5,x))') 'crystallite_partionedTemp0: ', shape(crystallite_partionedTemperature0) -write(6,'(a35,x,7(i5,x))') 'crystallite_partionedF0: ', shape(crystallite_partionedF0) -write(6,'(a35,x,7(i5,x))') 'crystallite_partionedFp0: ', shape(crystallite_partionedFp0) -write(6,'(a35,x,7(i5,x))') 'crystallite_partionedLp0: ', shape(crystallite_partionedLp0) -write(6,'(a35,x,7(i5,x))') 'crystallite_subF: ', shape(crystallite_subF) -write(6,'(a35,x,7(i5,x))') 'crystallite_subTemperature0: ', shape(crystallite_subTemperature0) -write(6,'(a35,x,7(i5,x))') 'crystallite_symmetryID: ', shape(crystallite_symmetryID) -write(6,'(a35,x,7(i5,x))') 'crystallite_subF0: ', shape(crystallite_subF0) -write(6,'(a35,x,7(i5,x))') 'crystallite_subFp0: ', shape(crystallite_subFp0) -write(6,'(a35,x,7(i5,x))') 'crystallite_subLp0: ', shape(crystallite_subLp0) -write(6,'(a35,x,7(i5,x))') 'crystallite_P: ', shape(crystallite_P) -write(6,'(a35,x,7(i5,x))') 'crystallite_Tstar_v: ', shape(crystallite_Tstar_v) -write(6,'(a35,x,7(i5,x))') 'crystallite_Tstar0_v: ', shape(crystallite_Tstar0_v) -write(6,'(a35,x,7(i5,x))') 'crystallite_partionedTstar0_v: ', shape(crystallite_partionedTstar0_v) -write(6,'(a35,x,7(i5,x))') 'crystallite_subTstar0_v: ', shape(crystallite_subTstar0_v) -write(6,'(a35,x,7(i5,x))') 'crystallite_dPdF: ', shape(crystallite_dPdF) -write(6,'(a35,x,7(i5,x))') 'crystallite_dPdF0: ', shape(crystallite_dPdF0) -write(6,'(a35,x,7(i5,x))') 'crystallite_partioneddPdF0: ', shape(crystallite_partioneddPdF0) -write(6,'(a35,x,7(i5,x))') 'crystallite_fallbackdPdF: ', shape(crystallite_fallbackdPdF) -write(6,'(a35,x,7(i5,x))') 'crystallite_orientation: ', shape(crystallite_orientation) -write(6,'(a35,x,7(i5,x))') 'crystallite_orientation0: ', shape(crystallite_orientation0) -write(6,'(a35,x,7(i5,x))') 'crystallite_rotation: ', shape(crystallite_rotation) -write(6,'(a35,x,7(i5,x))') 'crystallite_disorientation: ', shape(crystallite_disorientation) -write(6,'(a35,x,7(i5,x))') 'crystallite_dt: ', shape(crystallite_dt) -write(6,'(a35,x,7(i5,x))') 'crystallite_subdt: ', shape(crystallite_subdt) -write(6,'(a35,x,7(i5,x))') 'crystallite_subFrac: ', shape(crystallite_subFrac) -write(6,'(a35,x,7(i5,x))') 'crystallite_subStep: ', shape(crystallite_subStep) -write(6,'(a35,x,7(i5,x))') 'crystallite_stateDamper: ', shape(crystallite_stateDamper) -write(6,'(a35,x,7(i5,x))') 'crystallite_localConstitution: ', shape(crystallite_localConstitution) -write(6,'(a35,x,7(i5,x))') 'crystallite_requested: ', shape(crystallite_requested) -write(6,'(a35,x,7(i5,x))') 'crystallite_todo: ', shape(crystallite_todo) -write(6,'(a35,x,7(i5,x))') 'crystallite_converged: ', shape(crystallite_converged) -write(6,'(a35,x,7(i5,x))') 'crystallite_sizePostResults: ', shape(crystallite_sizePostResults) -write(6,'(a35,x,7(i5,x))') 'crystallite_sizePostResult: ', shape(crystallite_sizePostResult) -write(6,*) -write(6,*) 'Number of nonlocal grains: ',count(.not. crystallite_localConstitution) -call flush(6) -!$OMP END CRITICAL (write2out) +if (debug_verbosity > 0) then + !$OMP CRITICAL (write2out) + write(6,'(a35,x,7(i5,x))') 'crystallite_Temperature: ', shape(crystallite_Temperature) + write(6,'(a35,x,7(i5,x))') 'crystallite_dotTemperature: ', shape(crystallite_dotTemperature) + write(6,'(a35,x,7(i5,x))') 'crystallite_Fe: ', shape(crystallite_Fe) + write(6,'(a35,x,7(i5,x))') 'crystallite_Fp: ', shape(crystallite_Fp) + write(6,'(a35,x,7(i5,x))') 'crystallite_Lp: ', shape(crystallite_Lp) + write(6,'(a35,x,7(i5,x))') 'crystallite_F0: ', shape(crystallite_F0) + write(6,'(a35,x,7(i5,x))') 'crystallite_Fp0: ', shape(crystallite_Fp0) + write(6,'(a35,x,7(i5,x))') 'crystallite_Lp0: ', shape(crystallite_Lp0) + write(6,'(a35,x,7(i5,x))') 'crystallite_partionedF: ', shape(crystallite_partionedF) + write(6,'(a35,x,7(i5,x))') 'crystallite_partionedTemp0: ', shape(crystallite_partionedTemperature0) + write(6,'(a35,x,7(i5,x))') 'crystallite_partionedF0: ', shape(crystallite_partionedF0) + write(6,'(a35,x,7(i5,x))') 'crystallite_partionedFp0: ', shape(crystallite_partionedFp0) + write(6,'(a35,x,7(i5,x))') 'crystallite_partionedLp0: ', shape(crystallite_partionedLp0) + write(6,'(a35,x,7(i5,x))') 'crystallite_subF: ', shape(crystallite_subF) + write(6,'(a35,x,7(i5,x))') 'crystallite_subTemperature0: ', shape(crystallite_subTemperature0) + write(6,'(a35,x,7(i5,x))') 'crystallite_symmetryID: ', shape(crystallite_symmetryID) + write(6,'(a35,x,7(i5,x))') 'crystallite_subF0: ', shape(crystallite_subF0) + write(6,'(a35,x,7(i5,x))') 'crystallite_subFp0: ', shape(crystallite_subFp0) + write(6,'(a35,x,7(i5,x))') 'crystallite_subLp0: ', shape(crystallite_subLp0) + write(6,'(a35,x,7(i5,x))') 'crystallite_P: ', shape(crystallite_P) + write(6,'(a35,x,7(i5,x))') 'crystallite_Tstar_v: ', shape(crystallite_Tstar_v) + write(6,'(a35,x,7(i5,x))') 'crystallite_Tstar0_v: ', shape(crystallite_Tstar0_v) + write(6,'(a35,x,7(i5,x))') 'crystallite_partionedTstar0_v: ', shape(crystallite_partionedTstar0_v) + write(6,'(a35,x,7(i5,x))') 'crystallite_subTstar0_v: ', shape(crystallite_subTstar0_v) + write(6,'(a35,x,7(i5,x))') 'crystallite_dPdF: ', shape(crystallite_dPdF) + write(6,'(a35,x,7(i5,x))') 'crystallite_dPdF0: ', shape(crystallite_dPdF0) + write(6,'(a35,x,7(i5,x))') 'crystallite_partioneddPdF0: ', shape(crystallite_partioneddPdF0) + write(6,'(a35,x,7(i5,x))') 'crystallite_fallbackdPdF: ', shape(crystallite_fallbackdPdF) + write(6,'(a35,x,7(i5,x))') 'crystallite_orientation: ', shape(crystallite_orientation) + write(6,'(a35,x,7(i5,x))') 'crystallite_orientation0: ', shape(crystallite_orientation0) + write(6,'(a35,x,7(i5,x))') 'crystallite_rotation: ', shape(crystallite_rotation) + write(6,'(a35,x,7(i5,x))') 'crystallite_disorientation: ', shape(crystallite_disorientation) + write(6,'(a35,x,7(i5,x))') 'crystallite_dt: ', shape(crystallite_dt) + write(6,'(a35,x,7(i5,x))') 'crystallite_subdt: ', shape(crystallite_subdt) + write(6,'(a35,x,7(i5,x))') 'crystallite_subFrac: ', shape(crystallite_subFrac) + write(6,'(a35,x,7(i5,x))') 'crystallite_subStep: ', shape(crystallite_subStep) + write(6,'(a35,x,7(i5,x))') 'crystallite_stateDamper: ', shape(crystallite_stateDamper) + write(6,'(a35,x,7(i5,x))') 'crystallite_localConstitution: ', shape(crystallite_localConstitution) + write(6,'(a35,x,7(i5,x))') 'crystallite_requested: ', shape(crystallite_requested) + write(6,'(a35,x,7(i5,x))') 'crystallite_todo: ', shape(crystallite_todo) + write(6,'(a35,x,7(i5,x))') 'crystallite_converged: ', shape(crystallite_converged) + write(6,'(a35,x,7(i5,x))') 'crystallite_sizePostResults: ', shape(crystallite_sizePostResults) + write(6,'(a35,x,7(i5,x))') 'crystallite_sizePostResult: ', shape(crystallite_sizePostResult) + write(6,*) + write(6,*) 'Number of nonlocal grains: ',count(.not. crystallite_localConstitution) + call flush(6) + !$OMP END CRITICAL (write2out) +endif call debug_info() call debug_reset() @@ -431,8 +426,8 @@ use numerics, only: subStepMinCryst, & iJacoStiffness, & numerics_integrator, & numerics_integrationMode -use debug, only: debugger, & - verboseDebugger, & +use debug, only: debug_verbosity, & + debug_selectiveDebugger, & debug_e, & debug_i, & debug_g, & @@ -514,6 +509,22 @@ logical, dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems) :: & ! --+>> INITIALIZE TO STARTING CONDITION <<+-- + if (debug_verbosity > 4 .and. debug_e > 0 .and. debug_e <= mesh_NcpElems & + .and. debug_i > 0 .and. debug_i <= mesh_maxNips & + .and. debug_g > 0 .and. debug_g <= homogenization_maxNgrains) then + !$OMP CRITICAL (write2out) + write (6,*) + write (6,'(a,i5,x,i2,x,i3)') '<< CRYST >> crystallite start at el ip g ', debug_e, debug_i, debug_g + write (6,'(a,/,12(x),f14.9)') '<< CRYST >> Temp0', crystallite_partionedTemperature0(debug_g,debug_i,debug_e) + write (6,'(a,/,3(12(x),3(f14.9,x)/))') '<< CRYST >> F0 ', & + math_transpose3x3(crystallite_partionedF0(1:3,1:3,debug_g,debug_i,debug_e)) + write (6,'(a,/,3(12(x),3(f14.9,x)/))') '<< CRYST >> Fp0', & + math_transpose3x3(crystallite_partionedFp0(1:3,1:3,debug_g,debug_i,debug_e)) + write (6,'(a,/,3(12(x),3(f14.9,x)/))') '<< CRYST >> Lp0', & + math_transpose3x3(crystallite_partionedLp0(1:3,1:3,debug_g,debug_i,debug_e)) + !$OMP END CRITICAL (write2out) + endif + crystallite_subStep = 0.0_pReal !$OMP PARALLEL DO PRIVATE(myNgrains) @@ -556,9 +567,10 @@ do while (any(crystallite_subStep(:,:,FEsolving_execELem(1):FEsolving_execElem(2 ! --- wind forward --- if (crystallite_converged(g,i,e)) then - if (debugger .and. (e == debug_e .and. i == debug_i .and. g == debug_g)) then + if (debug_verbosity > 4 & + .and. ((e == debug_e .and. i == debug_i .and. g == debug_g) .or. .not. debug_selectiveDebugger)) then !$OMP CRITICAL (write2out) - write(6,'(a21,f10.8,a32,f10.8,a35)') 'winding forward from ', & + write(6,'(a,f10.8,a,f10.8,a)') '<< CRYST >> winding forward from ', & crystallite_subFrac(g,i,e),' to current crystallite_subfrac ', & crystallite_subFrac(g,i,e)+crystallite_subStep(g,i,e),' in crystallite_stressAndItsTangent' write(6,*) @@ -579,10 +591,12 @@ do while (any(crystallite_subStep(:,:,FEsolving_execELem(1):FEsolving_execElem(2 crystallite_subTstar0_v(1:6,g,i,e) = crystallite_Tstar_v(1:6,g,i,e) ! ...2nd PK stress !$OMP FLUSH(crystallite_subF0) elseif (formerSubStep > subStepMinCryst) then ! this crystallite just converged - !$OMP CRITICAL (distributionCrystallite) - debug_CrystalliteLoopDistribution(min(nCryst+1,NiterationCrystallite)) = & - debug_CrystalliteLoopDistribution(min(nCryst+1,NiterationCrystallite)) + 1 - !$OMP END CRITICAL (distributionCrystallite) + if (debug_verbosity > 0) then + !$OMP CRITICAL (distributionCrystallite) + debug_CrystalliteLoopDistribution(min(nCryst+1,NiterationCrystallite)) = & + debug_CrystalliteLoopDistribution(min(nCryst+1,NiterationCrystallite)) + 1 + !$OMP END CRITICAL (distributionCrystallite) + endif endif ! --- cutback --- @@ -597,9 +611,10 @@ do while (any(crystallite_subStep(:,:,FEsolving_execELem(1):FEsolving_execElem(2 crystallite_Tstar_v(1:6,g,i,e) = crystallite_subTstar0_v(1:6,g,i,e) ! ...2nd PK stress ! cant restore dotState here, since not yet calculated in first cutback after initialization !$OMP FLUSH(crystallite_subStep,crystallite_invFp) - if (debugger .and. (e == debug_e .and. i == debug_i .and. g == debug_g)) then + if (debug_verbosity > 4 & + .and. ((e == debug_e .and. i == debug_i .and. g == debug_g) .or. .not. debug_selectiveDebugger)) then !$OMP CRITICAL (write2out) - write(6,'(a78,f10.8)') 'cutback step in crystallite_stressAndItsTangent with new crystallite_subStep: ',& + write(6,'(a,f10.8)') '<< CRYST >> cutback step in crystallite_stressAndItsTangent with new crystallite_subStep: ',& crystallite_subStep(g,i,e) write(6,*) !$OMP END CRITICAL (write2out) @@ -660,16 +675,17 @@ enddo Tstar = math_Mandel6to33( math_mul66x6( 0.5_pReal*constitutive_homogenizedC(g,i,e), & math_Mandel33to6( math_mul33x33(transpose(Fe_guess),Fe_guess) - math_I3 ) ) ) crystallite_P(1:3,1:3,g,i,e) = math_mul33x33(Fe_guess,math_mul33x33(Tstar,transpose(invFp))) - !$OMP FLUSH(crystallite_P) endif - if (debugger .and. (e == debug_e .and. i == debug_i .and. g == debug_g)) then + if (debug_verbosity > 4 & + .and. ((e == debug_e .and. i == debug_i .and. g == debug_g) .or. .not. debug_selectiveDebugger)) then + !$OMP FLUSH(crystallite_P) !$OMP CRITICAL (write2out) - write (6,*) '#############' - write (6,*) 'central solution of cryst_StressAndTangent' - write (6,*) '#############' - write (6,'(a8,3(x,i4),/,3(3(f12.4,x)/))') ' P of', g, i, e, math_transpose3x3(crystallite_P(1:3,1:3,g,i,e)) / 1e6 - write (6,'(a8,3(x,i4),/,3(3(f14.9,x)/))') ' Fp of', g, i, e, math_transpose3x3(crystallite_Fp(1:3,1:3,g,i,e)) - write (6,'(a8,3(x,i4),/,3(3(f14.9,x)/))') ' Lp of', g, i, e, math_transpose3x3(crystallite_Lp(1:3,1:3,g,i,e)) + write (6,'(a,i5,x,i2,x,i3)') '<< CRYST >> central solution of cryst_StressAndTangent at el ip g ',e,i,g + write (6,*) + write (6,'(a,/,3(12(x),3(f12.4,x)/))') '<< CRYST >> P / MPa', math_transpose3x3(crystallite_P(1:3,1:3,g,i,e)) / 1e6 + write (6,'(a,/,3(12(x),3(f14.9,x)/))') '<< CRYST >> Fp', math_transpose3x3(crystallite_Fp(1:3,1:3,g,i,e)) + write (6,'(a,/,3(12(x),3(f14.9,x)/))') '<< CRYST >> Lp', math_transpose3x3(crystallite_Lp(1:3,1:3,g,i,e)) + write (6,*) !$OMP END CRITICAL (write2out) endif enddo @@ -717,9 +733,10 @@ if(updateJaco) then if (iand(pert_method,perturbation) > 0) then ! mask for desired direction myPert = -pert_Fg * (-1.0_pReal)**perturbation ! set perturbation step do k = 1,3; do l = 1,3 ! ...alter individual components - if (verboseDebugger .and. (e == debug_e .and. i == debug_i .and. g == debug_g)) then + if (debug_verbosity> 5) then !$OMP CRITICAL (write2out) - write (6,'(a,x,i1,x,i1,x,a)') '[[[[[[[ Stiffness perturbation',k,l,']]]]]]]' + write(6,'(a,2(x,i1),x,a)') '<< CRYST >> [[[[[[ Stiffness perturbation',k,l,']]]]]]' + write(6,*) !$OMP END CRITICAL (write2out) endif crystallite_subF(k,l,:,:,:) = crystallite_subF(k,l,:,:,:) + myPert ! perturb either forward or backward @@ -824,11 +841,11 @@ subroutine crystallite_integrateStateRK4(gg,ii,ee) use prec, only: pInt, & pReal use numerics, only: numerics_integrationMode -use debug, only: debugger, & - verboseDebugger, & +use debug, only: debug_verbosity, & debug_e, & debug_i, & debug_g, & + debug_selectiveDebugger, & debug_StateLoopDistribution use FEsolving, only: FEsolving_execElem, & FEsolving_execIP @@ -986,22 +1003,26 @@ do n = 1,4 if (crystallite_todo(g,i,e)) then if (crystallite_integrateStress(g,i,e,timeStepFraction(n))) then ! fraction of original times step if (n == 4) then ! final integration step - if (verboseDebugger .and. e == debug_e .and. i == debug_i .and. g == debug_g) then + if (debug_verbosity > 5 & + .and. ((e == debug_e .and. i == debug_i .and. g == debug_g) .or. .not. debug_selectiveDebugger)) then mySizeDotState = constitutive_sizeDotState(g,i,e) !$OMP CRITICAL (write2out) - write(6,*) '::: updateState',g,i,e + write(6,'(a,i5,x,i2,x,i3)') '<< CRYST >> updateState at el ip g ',e,i,g write(6,*) - write(6,'(a,/,12(e12.5,x))') 'updateState: dotState', constitutive_dotState(g,i,e)%p(1:mySizeDotState) + write(6,'(a,/,(12(x),12(e12.5,x)))') '<< CRYST >> dotState', constitutive_dotState(g,i,e)%p(1:mySizeDotState) write(6,*) - write(6,'(a,/,12(e12.5,x))') 'updateState: new state', constitutive_state(g,i,e)%p(1:mySizeDotState) + write(6,'(a,/,(12(x),12(e12.5,x)))') '<< CRYST >> new state', constitutive_state(g,i,e)%p(1:mySizeDotState) write(6,*) !$OMP END CRITICAL (write2out) endif crystallite_converged(g,i,e) = .true. ! ... converged per definition crystallite_todo(g,i,e) = .false. ! ... integration done - !$OMP CRITICAL (distributionState) - debug_StateLoopDistribution(n,numerics_integrationMode) = debug_StateLoopDistribution(n,numerics_integrationMode) + 1 - !$OMP END CRITICAL (distributionState) + if (debug_verbosity > 0) then + !$OMP CRITICAL (distributionState) + debug_StateLoopDistribution(n,numerics_integrationMode) = & + debug_StateLoopDistribution(n,numerics_integrationMode) + 1 + !$OMP END CRITICAL (distributionState) + endif endif else ! broken stress integration if (.not. crystallite_localConstitution(g,i,e)) then ! if broken non-local... @@ -1078,11 +1099,11 @@ subroutine crystallite_integrateStateRKCK45(gg,ii,ee) !*** variables and functions from other modules ***! use prec, only: pInt, & pReal -use debug, only: debugger, & - verboseDebugger, & +use debug, only: debug_verbosity, & debug_e, & debug_i, & debug_g, & + debug_selectiveDebugger, & debug_StateLoopDistribution use numerics, only: rTol_crystalliteState, & rTol_crystalliteTemperature, & @@ -1217,10 +1238,10 @@ endif ! --- FIRST RUNGE KUTTA STEP --- -if (verboseDebugger) then +if (debug_verbosity > 5) then !$OMP SINGLE !$OMP CRITICAL (write2out) - write(6,'(a,x,i1)') '<<> RUNGE KUTTA STEP',1 !$OMP END CRITICAL (write2out) !$OMP END SINGLE endif @@ -1355,10 +1376,10 @@ do n = 1,5 ! --- dot state and RK dot state--- - if (verboseDebugger) then + if (debug_verbosity > 5) then !$OMP SINGLE !$OMP CRITICAL (write2out) - write(6,'(a,x,i1)') '<<> RUNGE KUTTA STEP',n+1 !$OMP END CRITICAL (write2out) !$OMP END SINGLE endif @@ -1481,24 +1502,20 @@ relTemperatureResiduum = 0.0_pReal .or. abs(stateResiduum(1:mySizeDotState,g,i,e)) < constitutive_aTolState(g,i,e)%p(1:mySizeDotState) ) & .and. abs(relTemperatureResiduum(g,i,e)) < rTol_crystalliteTemperature ) - if (verboseDebugger .and. (e == debug_e .and. i == debug_i .and. g == debug_g)) then + if (debug_verbosity > 5 & + .and. ((e == debug_e .and. i == debug_i .and. g == debug_g) .or. .not. debug_selectiveDebugger)) then !$OMP CRITICAL (write2out) - write(6,*) '::: updateState',g,i,e + write(6,'(a,i5,x,i3,x,i3)') '<< CRYST >> updateState at el ip g ',e,i,g write(6,*) - write(6,'(a,/,12(f12.1,x))') 'updateState: absolute residuum tolerance', stateResiduum(1:mySizeDotState,g,i,e) & - / constitutive_aTolState(g,i,e)%p(1:mySizeDotState) + write(6,'(a,/,(12(x),12(f12.1,x)))') '<< CRYST >> absolute residuum tolerance', & + stateResiduum(1:mySizeDotState,g,i,e) / constitutive_aTolState(g,i,e)%p(1:mySizeDotState) write(6,*) - write(6,'(a,/,12(f12.1,x))') 'updateState: relative residuum tolerance', relStateResiduum(1:mySizeDotState,g,i,e) & - / rTol_crystalliteState + write(6,'(a,/,(12(x),12(f12.1,x)))') '<< CRYST >> relative residuum tolerance', & + relStateResiduum(1:mySizeDotState,g,i,e) / rTol_crystalliteState write(6,*) -! write(6,'(a)') 'updateState: RKCK45dotState' -! do j = 1,6 -! write(6,'(12(e14.8,x))') constitutive_RKCK45dotState(j,g,i,e)%p(1:mySizeDotState) -! write(6,*) -! enddo - write(6,'(a,/,12(e12.5,x))') 'updateState: dotState', constitutive_dotState(g,i,e)%p(1:mySizeDotState) + write(6,'(a,/,(12(x),12(e12.5,x)))') '<< CRYST >> dotState', constitutive_dotState(g,i,e)%p(1:mySizeDotState) write(6,*) - write(6,'(a,/,12(e12.5,x))') 'updateState: new state', constitutive_state(g,i,e)%p(1:mySizeDotState) + write(6,'(a,/,(12(x),12(e12.5,x)))') '<< CRYST >> new state', constitutive_state(g,i,e)%p(1:mySizeDotState) write(6,*) !$OMP END CRITICAL (write2out) endif @@ -1528,9 +1545,11 @@ relTemperatureResiduum = 0.0_pReal if (crystallite_integrateStress(g,i,e)) then crystallite_converged(g,i,e) = .true. ! ... converged per definitionem crystallite_todo(g,i,e) = .false. ! ... integration done - !$OMP CRITICAL (distributionState) - debug_StateLoopDistribution(6,numerics_integrationMode) = debug_StateLoopDistribution(6,numerics_integrationMode) + 1 - !$OMP END CRITICAL (distributionState) + if (debug_verbosity > 0) then + !$OMP CRITICAL (distributionState) + debug_StateLoopDistribution(6,numerics_integrationMode) = debug_StateLoopDistribution(6,numerics_integrationMode) + 1 + !$OMP END CRITICAL (distributionState) + endif else if (.not. crystallite_localConstitution(g,i,e)) then ! if broken non-local... !$OMP CRITICAL (checkTodo) @@ -1546,9 +1565,9 @@ relTemperatureResiduum = 0.0_pReal ! --- nonlocal convergence check --- -if (verboseDebugger .and. numerics_integrationMode == 1) then +if (debug_verbosity > 5) then !$OMP CRITICAL (write2out) - write(6,*) 'crystallite_converged',crystallite_converged + write(6,'(a,L)') '<< CRYST >> crystallite_converged',crystallite_converged !$OMP END CRITICAL (write2out) endif if (.not. singleRun) then ! if not requesting Integration of just a single IP @@ -1571,8 +1590,8 @@ subroutine crystallite_integrateStateAdaptiveEuler(gg,ii,ee) !*** variables and functions from other modules ***! use prec, only: pInt, & pReal -use debug, only: debugger, & - verboseDebugger, & +use debug, only: debug_verbosity, & + debug_selectiveDebugger, & debug_e, & debug_i, & debug_g, & @@ -1797,20 +1816,21 @@ relTemperatureResiduum = 0.0_pReal relTemperatureResiduum(g,i,e) = temperatureResiduum(g,i,e) / crystallite_Temperature(g,i,e) !$OMP FLUSH(relStateResiduum,relTemperatureResiduum) - if (verboseDebugger .and. (e == debug_e .and. i == debug_i .and. g == debug_g)) then + if (debug_verbosity > 5 & + .and. ((e == debug_e .and. i == debug_i .and. g == debug_g) .or. .not. debug_selectiveDebugger)) then !$OMP CRITICAL (write2out) - write(6,*) '::: updateState',g,i,e + write(6,'(a,i5,x,i2,x,i3)') '<< CRYST >> updateState at el ip g ',e,i,g write(6,*) - write(6,'(a,/,12(f12.1,x))') 'updateState: absolute residuum tolerance', stateResiduum(1:mySizeDotState,g,i,e) & - / constitutive_aTolState(g,i,e)%p(1:mySizeDotState) + write(6,'(a,/,(12(x),12(f12.1,x)))') '<< CRYST >> absolute residuum tolerance', & + stateResiduum(1:mySizeDotState,g,i,e) / constitutive_aTolState(g,i,e)%p(1:mySizeDotState) write(6,*) - write(6,'(a,/,12(f12.1,x))') 'updateState: relative residuum tolerance', relStateResiduum(1:mySizeDotState,g,i,e) & - / rTol_crystalliteState + write(6,'(a,/,(12(x),12(f12.1,x)))') '<< CRYST >> relative residuum tolerance', & + relStateResiduum(1:mySizeDotState,g,i,e) / rTol_crystalliteState write(6,*) - write(6,'(a,/,12(e12.5,x))') 'updateState: dotState', constitutive_dotState(g,i,e)%p(1:mySizeDotState) & + write(6,'(a,/,(12(x),12(e12.5,x)))') '<< CRYST >> dotState', constitutive_dotState(g,i,e)%p(1:mySizeDotState) & - 2.0_pReal * stateResiduum(1:mySizeDotState,g,i,e) / crystallite_subdt(g,i,e) ! calculate former dotstate from higher order solution and state residuum write(6,*) - write(6,'(a,/,12(e12.5,x))') 'updateState: new state', constitutive_state(g,i,e)%p(1:mySizeDotState) + write(6,'(a,/,(12(x),12(e12.5,x)))') '<< CRYST >> new state', constitutive_state(g,i,e)%p(1:mySizeDotState) write(6,*) !$OMP END CRITICAL (write2out) endif @@ -1821,13 +1841,13 @@ relTemperatureResiduum = 0.0_pReal if ( all( abs(relStateResiduum(:,g,i,e)) < rTol_crystalliteState & .or. abs(stateResiduum(1:mySizeDotState,g,i,e)) < constitutive_aTolState(g,i,e)%p(1:mySizeDotState)) & .and. abs(relTemperatureResiduum(g,i,e)) < rTol_crystalliteTemperature ) then - crystallite_converged(g,i,e) = .true. ! ... converged per definitionem crystallite_todo(g,i,e) = .false. ! ... integration done - !$OMP CRITICAL (distributionState) - debug_StateLoopDistribution(2,numerics_integrationMode) = debug_StateLoopDistribution(2,numerics_integrationMode) + 1 - !$OMP END CRITICAL (distributionState) - + if (debug_verbosity > 0) then + !$OMP CRITICAL (distributionState) + debug_StateLoopDistribution(2,numerics_integrationMode) = debug_StateLoopDistribution(2,numerics_integrationMode) + 1 + !$OMP END CRITICAL (distributionState) + endif endif endif @@ -1838,9 +1858,9 @@ relTemperatureResiduum = 0.0_pReal ! --- NONLOCAL CONVERGENCE CHECK --- -if (verboseDebugger .and. numerics_integrationMode==1_pInt) then +if (debug_verbosity > 5) then !$OMP CRITICAL (write2out) - write(6,*) 'crystallite_converged',crystallite_converged + write(6,'(a,L)') '<< CRYST >> crystallite_converged',crystallite_converged !$OMP END CRITICAL (write2out) endif if (.not. singleRun) then ! if not requesting Integration of just a single IP @@ -1863,9 +1883,8 @@ subroutine crystallite_integrateStateEuler(gg,ii,ee) use prec, only: pInt, & pReal use numerics, only: numerics_integrationMode -use debug, only: debugger, & - selectiveDebugger, & - verboseDebugger, & +use debug, only: debug_verbosity, & + debug_selectiveDebugger, & debug_e, & debug_i, & debug_g, & @@ -1977,13 +1996,13 @@ endif endif enddo; enddo; enddo !$OMP ENDDO -if (verboseDebugger .and. selectiveDebugger) then +if (debug_verbosity > 5 .and. ((e == debug_e .and. i == debug_i .and. g == debug_g) .or. .not. debug_selectiveDebugger)) then !$OMP CRITICAL (write2out) - write(6,*) '::: updateState', debug_g, debug_i, debug_e + write(6,'(a,i5,x,i2,x,i3)') '<< CRYST >> updateState at el ip g ',e,i,g write(6,*) - write(6,'(a,/,12(e12.5,x))') 'updateState: dotState', constitutive_dotState(debug_g,debug_i,debug_e)%p(1:mySizeDotState) + write(6,'(a,/,(12(x),12(e12.5,x)))') '<< CRYST >> dotState', constitutive_dotState(debug_g,debug_i,debug_e)%p(1:mySizeDotState) write(6,*) - write(6,'(a,/,12(e12.5,x))') 'updateState: new state', constitutive_state(debug_g,debug_i,debug_e)%p(1:mySizeDotState) + write(6,'(a,/,(12(x),12(e12.5,x)))') '<< CRYST >> new state', constitutive_state(debug_g,debug_i,debug_e)%p(1:mySizeDotState) write(6,*) !$OMP END CRITICAL (write2out) endif @@ -2008,9 +2027,11 @@ endif if (crystallite_todo(g,i,e)) then if (crystallite_integrateStress(g,i,e)) then crystallite_converged(g,i,e) = .true. - !$OMP CRITICAL (distributionState) - debug_StateLoopDistribution(1,numerics_integrationMode) = debug_StateLoopDistribution(1,numerics_integrationMode) + 1 - !$OMP END CRITICAL (distributionState) + if (debug_verbosity > 0) then + !$OMP CRITICAL (distributionState) + debug_StateLoopDistribution(1,numerics_integrationMode) = debug_StateLoopDistribution(1,numerics_integrationMode) + 1 + !$OMP END CRITICAL (distributionState) + endif else ! broken stress integration if (.not. crystallite_localConstitution(g,i,e)) then ! if broken non-local... !$OMP CRITICAL (checkTodo) @@ -2048,8 +2069,8 @@ subroutine crystallite_integrateStateFPI(gg,ii,ee) !*** variables and functions from other modules ***! use prec, only: pInt, & pReal -use debug, only: debugger, & - verboseDebugger, & +use debug, only: debug_verbosity, & + debug_selectiveDebugger, & debug_e, & debug_i, & debug_g, & @@ -2207,10 +2228,10 @@ do while (any(crystallite_todo) .and. NiterationState < nState ) enddo; enddo; enddo !$OMP ENDDO - if (verboseDebugger .and. numerics_integrationMode == 1) then + if (debug_verbosity > 5) then !$OMP SINGLE !$OMP CRITICAL (write2out) - write(6,*) count(crystallite_todo(:,:,:)),'grains todo after stress integration' + write(6,'(a,i8,a)') '<< CRYST >> ', count(crystallite_todo(:,:,:)),' grains todo after stress integration' !$OMP END CRITICAL (write2out) !$OMP END SINGLE endif @@ -2262,10 +2283,12 @@ do while (any(crystallite_todo) .and. NiterationState < nState ) crystallite_todo = crystallite_todo .and. crystallite_localConstitution ! ...all non-locals skipped !$OMP END CRITICAL (checkTodo) elseif (stateConverged .and. temperatureConverged) then ! check (private) logicals "stateConverged" and "temperatureConverged" instead of (shared) "crystallite_converged", so no need to flush the "crystallite_converged" array - !$OMP CRITICAL (distributionState) - debug_StateLoopDistribution(NiterationState,numerics_integrationMode) = & - debug_StateLoopDistribution(NiterationState,numerics_integrationMode) + 1 - !$OMP END CRITICAL (distributionState) + if (debug_verbosity > 0) then + !$OMP CRITICAL (distributionState) + debug_StateLoopDistribution(NiterationState,numerics_integrationMode) = & + debug_StateLoopDistribution(NiterationState,numerics_integrationMode) + 1 + !$OMP END CRITICAL (distributionState) + endif endif endif enddo; enddo; enddo @@ -2287,10 +2310,11 @@ do while (any(crystallite_todo) .and. NiterationState < nState ) !$OMP ENDDO - if (verboseDebugger .and. numerics_integrationMode == 1) then + if (debug_verbosity > 5) then !$OMP SINGLE !$OMP CRITICAL (write2out) - write(6,*) count(crystallite_converged(:,:,:)),'grains converged after state integration no.', NiterationState + write(6,'(a,i8,a,i2)') '<< CRYST >> ', count(crystallite_converged(:,:,:)), & + ' grains converged after state integration no. ', NiterationState write(6,*) !$OMP END CRITICAL (write2out) !$OMP END SINGLE @@ -2311,11 +2335,12 @@ do while (any(crystallite_todo) .and. NiterationState < nState ) crystallite_todo = crystallite_todo .and. .not. crystallite_converged ! skip all converged !$OMP END SINGLE - if (verboseDebugger .and. numerics_integrationMode == 1) then + if (debug_verbosity > 5) then !$OMP SINGLE !$OMP CRITICAL (write2out) - write(6,*) count(crystallite_converged(:,:,:)),'grains converged after non-local check' - write(6,*) count(crystallite_todo(:,:,:)),'grains todo after state integration no.', NiterationState + write(6,'(a,i8,a)') '<< CRYST >> ', count(crystallite_converged(:,:,:)),' grains converged after non-local check' + write(6,'(a,i8,a,i2)') '<< CRYST >> ', count(crystallite_todo(:,:,:)),' grains todo after state integration no. ',& + NiterationState write(6,*) !$OMP END CRITICAL (write2out) !$OMP END SINGLE @@ -2348,11 +2373,11 @@ use constitutive, only: constitutive_dotState, & constitutive_state, & constitutive_aTolState, & constitutive_microstructure -use debug, only: debugger, & +use debug, only: debug_verbosity, & debug_g, & debug_i, & debug_e, & - verboseDebugger + debug_selectiveDebugger !*** input variables ***! integer(pInt), intent(in):: e, & ! element index @@ -2388,9 +2413,9 @@ dotState(1:mySize) = constitutive_dotState(g,i,e)%p(1:mySize) * crystallite_stat residuum = constitutive_state(g,i,e)%p(1:mySize) - constitutive_subState0(g,i,e)%p(1:mySize) & - dotState(1:mySize) * crystallite_subdt(g,i,e) if (any(residuum /= residuum)) then ! if NaN occured then return without changing the state - if (verboseDebugger) then + if (debug_verbosity > 4) then !$OMP CRITICAL (write2out) - write(6,*) '::: updateState encountered NaN',g,i,e + write(6,'(a,i5,x,i2,x,i3)') '<< CRYST >> updateState encountered NaN at el ip g ',e,i,g !$OMP END CRITICAL (write2out) endif return @@ -2404,21 +2429,19 @@ done = .true. converged = all( abs(residuum) < constitutive_aTolState(g,i,e)%p(1:mySize) & .or. abs(residuum) < rTol_crystalliteState * abs(state(1:mySize)) ) -if ( verboseDebugger & - .and. (e == debug_e .and. i == debug_i .and. g == debug_g) & - .and. numerics_integrationMode == 1_pInt) then +if (debug_verbosity > 5 .and. ((e == debug_e .and. i == debug_i .and. g == debug_g) .or. .not. debug_selectiveDebugger)) then !$OMP CRITICAL (write2out) if (converged) then - write(6,*) '::: updateState converged',g,i,e + write(6,'(a,i5,x,i2,x,i3)') '<< CRYST >> updateState converged at el ip g ',e,i,g else - write(6,*) '::: updateState did not converge',g,i,e + write(6,'(a,i5,x,i2,x,i3)') '<< CRYST >> updateState did not converge at el ip g ',e,i,g endif write(6,*) - write(6,'(a,f6.1)') 'updateState: crystallite_statedamper',crystallite_statedamper(g,i,e) + write(6,'(a,f6.1)') '<< CRYST >> crystallite_statedamper ',crystallite_statedamper(g,i,e) write(6,*) - write(6,'(a,/,12(e12.5,x))') 'updateState: dotState',dotState(1:mySize) + write(6,'(a,/,(12(x),12(e12.5,x)))') '<< CRYST >> dotState',dotState(1:mySize) write(6,*) - write(6,'(a,/,12(e12.5,x))') 'updateState: new state',state(1:mySize) + write(6,'(a,/,(12(x),12(e12.5,x)))') '<< CRYST >> new state',state(1:mySize) write(6,*) !$OMP END CRITICAL (write2out) endif @@ -2445,7 +2468,7 @@ use prec, only: pReal, & pLongInt use numerics, only: rTol_crystalliteTemperature use constitutive, only: constitutive_dotTemperature -use debug, only: debugger +use debug, only: debug_verbosity !*** input variables ***! integer(pInt), intent(in):: e, & ! element index @@ -2473,10 +2496,12 @@ residuum = crystallite_Temperature(g,i,e) - crystallite_subTemperature0(g,i,e) & - constitutive_dotTemperature(crystallite_Tstar_v(1:6,g,i,e),crystallite_Temperature(g,i,e),g,i,e) & * crystallite_subdt(g,i,e) if (residuum /= residuum) then - !$OMP CRITICAL (write2out) - write(6,*) '::: updateTemperature encountered NaN',g,i,e - !$OMP END CRITICAL (write2out) - return + if (debug_verbosity > 4) then + !$OMP CRITICAL (write2out) + write(6,'(a,i5,x,i2,x,i3)') '<< CRYST >> updateTemperature encountered NaN at el ip g ',e,i,g + !$OMP END CRITICAL (write2out) + endif + return endif @@ -2515,11 +2540,11 @@ use numerics, only: nStress, & iJacoLpresiduum, & relevantStrain, & numerics_integrationMode -use debug, only: debugger, & +use debug, only: debug_verbosity, & debug_g, & debug_i, & debug_e, & - verboseDebugger, & + debug_selectiveDebugger, & debug_cumLpCalls, & debug_cumLpTicks, & debug_StressLoopDistribution, & @@ -2598,6 +2623,11 @@ integer(pLongInt) tick, & !* be pessimistic crystallite_integrateStress = .false. +if (debug_verbosity > 5 .and. ((e == debug_e .and. i == debug_i .and. g == debug_g) .or. .not. debug_selectiveDebugger)) then + !$OMP CRITICAL (write2out) + write(6,'(a,i5,x,i2,x,i3)') '<< CRYST >> integrateStress at el ip g ',e,i,g + !$OMP END CRITICAL (write2out) +endif !* only integrate over fraction of timestep? @@ -2623,11 +2653,13 @@ Lpguess = crystallite_Lp(1:3,1:3,g,i,e) ! ... and tak invFp_current = math_inv3x3(Fp_current) if (all(invFp_current == 0.0_pReal)) then ! ... failed? - if (verboseDebugger .and. (e == debug_e .and. i == debug_i .and. g == debug_g)) then + if (debug_verbosity > 4) then !$OMP CRITICAL (write2out) - write(6,*) '::: integrateStress failed on invFp_current inversion',g,i,e - write(6,*) - write(6,'(a11,i3,x,i2,x,i5,/,3(3(f12.7,x)/))') 'invFp_new at ',g,i,e,math_transpose3x3(invFp_new(1:3,1:3)) + write(6,'(a,i5,x,i2,x,i3)') '<< CRYST >> integrateStress failed on invFp_current inversion at el ip g ',e,i,g + if (debug_verbosity > 5 .and. ((e == debug_e .and. i == debug_i .and. g == debug_g) .or. .not. debug_selectiveDebugger)) then + write(6,*) + write(6,'(a,/,3(12(x),3(f12.7,x)/))') '<< CRYST >> invFp_new',math_transpose3x3(invFp_new(1:3,1:3)) + endif !$OMP END CRITICAL (write2out) endif return @@ -2638,7 +2670,6 @@ A = math_mul33x33(transpose(invFp_current), math_mul33x33(transpose(Fg_new),math !* get elasticity tensor C_66 = constitutive_homogenizedC(g,i,e) -! if (debugger) write(6,'(a,/,6(6(f10.4,x)/))') 'elasticity',transpose(C_66(1:6,1:6))/1e9 C = math_Mandel66to3333(C_66) @@ -2656,9 +2687,9 @@ LpLoop: do !* too many loops required ? if (NiterationStress > nStress) then - if (verboseDebugger) then + if (debug_verbosity > 4) then !$OMP CRITICAL (write2out) - write(6,*) '::: integrateStress reached loop limit at ',g,i,e + write(6,'(a,i5,x,i2,x,i3)') '<< CRYST >> integrateStress reached loop limit at el ip g ',e,i,g write(6,*) !$OMP END CRITICAL (write2out) endif @@ -2680,21 +2711,27 @@ LpLoop: do !* calculate plastic velocity gradient and its tangent according to constitutive law - call system_clock(count=tick,count_rate=tickrate,count_max=maxticks) + if (debug_verbosity > 0) then + call system_clock(count=tick,count_rate=tickrate,count_max=maxticks) + endif call constitutive_LpAndItsTangent(Lp_constitutive, dLpdT_constitutive, Tstar_v, crystallite_Temperature(g,i,e), g, i, e) - call system_clock(count=tock,count_rate=tickrate,count_max=maxticks) - !$OMP CRITICAL (debugTimingLpTangent) - debug_cumLpCalls = debug_cumLpCalls + 1_pInt - debug_cumLpTicks = debug_cumLpTicks + tock-tick - if (tock < tick) debug_cumLpTicks = debug_cumLpTicks + maxticks - !$OMP END CRITICAL (debugTimingLpTangent) + if (debug_verbosity > 0) then + call system_clock(count=tock,count_rate=tickrate,count_max=maxticks) + !$OMP CRITICAL (debugTimingLpTangent) + debug_cumLpCalls = debug_cumLpCalls + 1_pInt + debug_cumLpTicks = debug_cumLpTicks + tock-tick + !$OMP FLUSH (debug_cumLpTicks) + if (tock < tick) debug_cumLpTicks = debug_cumLpTicks + maxticks + !$OMP END CRITICAL (debugTimingLpTangent) + endif - if (verboseDebugger .and. (e == debug_e .and. i == debug_i .and. g == debug_g) .and. numerics_integrationMode == 1_pInt) then + if (debug_verbosity > 5 .and. ((e == debug_e .and. i == debug_i .and. g == debug_g) .or. .not. debug_selectiveDebugger) & + .and. numerics_integrationMode == 1_pInt) then !$OMP CRITICAL (write2out) - write(6,'(a,i3,x,i2,x,i5,x,a,x,i3)') '::: integrateStress at ' ,g,i,e, ' ; iteration ', NiterationStress + write(6,'(a,i3)') '<< CRYST >> iteration ', NiterationStress write(6,*) - write(6,'(a,/,3(3(e20.7,x)/))') 'Lp_constitutive', math_transpose3x3(Lp_constitutive) - write(6,'(a,/,3(3(e20.7,x)/))') 'Lpguess', math_transpose3x3(Lpguess) + write(6,'(a,/,3(12(x),3(e20.7,x)/))') '<< CRYST >> Lp_constitutive', math_transpose3x3(Lp_constitutive) + write(6,'(a,/,3(12(x),3(e20.7,x)/))') '<< CRYST >> Lpguess', math_transpose3x3(Lpguess) !$OMP END CRITICAL (write2out) endif @@ -2716,11 +2753,11 @@ LpLoop: do !* NaN occured at regular speed? -> return if (any(residuum/=residuum) .and. leapfrog == 1.0) then - if (debugger) then + if (debug_verbosity > 4) then !$OMP CRITICAL (write2out) - write(6,'(a,i3,x,i2,x,i5,x,a,i3,x,a)') '::: integrateStress encountered NaN at ',g,i,e,& - '; iteration ', NiterationStress, & - '>> returning..!' + write(6,'(a,i5,x,i2,x,i3,a,i3,a)') '<< CRYST >> integrateStress encountered NaN at el ip g ',e,i,g,& + ' ; iteration ', NiterationStress,& + ' >> returning..!' !$OMP END CRITICAL (write2out) endif return @@ -2734,9 +2771,9 @@ LpLoop: do any(residuum/=residuum) & ! NaN occured ) & ) then - if (verboseDebugger) then + if (debug_verbosity > 5) then !$OMP CRITICAL (write2out) - write(6,'(a,i3,x,i2,x,i5,x,a,i3)') '::: integrateStress encountered high-speed crash at ',g,i,e,& + write(6,'(a,i5,x,i2,x,i3,x,a,i3)') '<< CRYST >> integrateStress encountered high-speed crash at el ip g ',e,i,g,& '; iteration ', NiterationStress !$OMP END CRITICAL (write2out) endif @@ -2745,10 +2782,12 @@ LpLoop: do jacoCounter = 0_pInt ! reset counter for Jacobian update (we want to do an update next time!) Lpguess = Lpguess_old residuum = residuum_old - !$OMP CRITICAL (distributionLeapfrogBreak) - debug_LeapfrogBreakDistribution(NiterationStress,numerics_integrationMode) = & - debug_LeapfrogBreakDistribution(NiterationStress,numerics_integrationMode) + 1 - !$OMP END CRITICAL (distributionLeapfrogBreak) + if (debug_verbosity > 0) then + !$OMP CRITICAL (distributionLeapfrogBreak) + debug_LeapfrogBreakDistribution(NiterationStress,numerics_integrationMode) = & + debug_LeapfrogBreakDistribution(NiterationStress,numerics_integrationMode) + 1 + !$OMP END CRITICAL (distributionLeapfrogBreak) + endif !* residuum got better? -> calculate Jacobian for correction term and remember current residuum and Lpguess @@ -2764,28 +2803,21 @@ LpLoop: do invdRdLp = 0.0_pReal call math_invert(9,dRdLp,invdRdLp,dummy,error) ! invert dR/dLp --> dLp/dR if (error) then - if (verboseDebugger .and. (e == debug_e .and. i == debug_i .and. g == debug_g)) then + if (debug_verbosity > 4) then !$OMP CRITICAL (write2out) - write(6,'(a,i3,x,i2,x,i5,x,a,i3)') '::: integrateStress failed on dR/dLp inversion at ',g,i,e, & - '; iteration ', NiterationStress - write(6,*) - write(6,'(a,/,9(9(e15.3,x)/))') 'dRdLp',transpose(dRdLp) - write(6,'(a,/,9(9(e15.3,x)/))') 'dLpdT_constitutive',transpose(dLpdT_constitutive) - write(6,'(a,/,3(3(e20.7,x)/))') 'Lp_constitutive',math_transpose3x3(Lp_constitutive) - write(6,'(a,/,3(3(e20.7,x)/))') 'Lpguess',math_transpose3x3(Lpguess) + write(6,'(a,i5,x,i2,x,i3,a,i3)') '<< CRYST >> integrateStress failed on dR/dLp inversion at el ip g ',e,i,g,& + ' ; iteration ', NiterationStress + if (debug_verbosity > 5 & + .and. ((e == debug_e .and. i == debug_i .and. g == debug_g) .or. .not. debug_selectiveDebugger)) then + write(6,*) + write(6,'(a,/,9(12(x),9(e15.3,x)/))') '<< CRYST >> dRdLp',transpose(dRdLp) + write(6,'(a,/,9(12(x),9(e15.3,x)/))') '<< CRYST >> dLpdT_constitutive',transpose(dLpdT_constitutive) + write(6,'(a,/,3(12(x),3(e20.7,x)/))') '<< CRYST >> Lp_constitutive',math_transpose3x3(Lp_constitutive) + write(6,'(a,/,3(12(x),3(e20.7,x)/))') '<< CRYST >> Lpguess',math_transpose3x3(Lpguess) + endif !$OMP END CRITICAL (write2out) endif return - else - if (verboseDebugger .and. (e == debug_e .and. i == debug_i .and. g == debug_g) .and. numerics_integrationMode==1_pInt) then - !$OMP CRITICAL (write2out) - write(6,'(a,i3,x,i2,x,i5,x,a,i3)') '::: integrateStress did dR/dLp inversion at ',g,i,e, & - '; iteration ', NiterationStress - write(6,*) - write(6,'(a,/,9(9(e15.3,x)/))') 'dRdLp',transpose(dRdLp(:,:)) - write(6,'(a,/,9(9(e15.3,x)/))') 'dLpdT_constitutive',transpose(dLpdT_constitutive) - !$OMP END CRITICAL (write2out) - endif endif endif jacoCounter = jacoCounter + 1_pInt ! increase counter for jaco update @@ -2815,12 +2847,14 @@ invFp_new = math_mul33x33(invFp_current,B) invFp_new = invFp_new/math_det3x3(invFp_new)**(1.0_pReal/3.0_pReal) ! regularize by det call math_invert3x3(invFp_new,Fp_new,det,error) if (error) then - if (verboseDebugger .and. (e == debug_e .and. i == debug_i .and. g == debug_g)) then + if (debug_verbosity > 4) then !$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, & + write(6,'(a,i5,x,i2,x,i3,a,i3)') '<< CRYST >> integrateStress failed on invFp_new inversion at el ip g ',e,i,g, & ' ; iteration ', NiterationStress - write(6,*) - write(6,'(a11,3(i3,x),/,3(3(f12.7,x)/))') 'invFp_new at ',g,i,e,math_transpose3x3(invFp_new) + if (debug_verbosity > 5 .and. ((e == debug_e .and. i == debug_i .and. g == debug_g) .or. .not. debug_selectiveDebugger)) then + write(6,*) + write(6,'(a,/,3(12(x),3(f12.7,x)/))') '<< CRYST >> invFp_new',math_transpose3x3(invFp_new) + endif !$OMP END CRITICAL (write2out) endif return @@ -2846,24 +2880,24 @@ crystallite_invFp(1:3,1:3,g,i,e) = invFp_new !* set return flag to true crystallite_integrateStress = .true. -if (verboseDebugger .and. (e == debug_e .and. i == debug_i .and. g == debug_g) .and. numerics_integrationMode == 1_pInt) then +if (debug_verbosity > 5 .and. ((e == debug_e .and. i == debug_i .and. g == debug_g) .or. .not. debug_selectiveDebugger) & + .and. numerics_integrationMode == 1_pInt) then !$OMP CRITICAL (write2out) - write(6,'(a,i3,x,i2,x,i5,x,a,x,i3)') '::: integrateStress converged at ',g,i,e,' ; iteration ', NiterationStress - write(6,*) - write(6,'(a,/,3(3(f12.7,x)/))') 'P / MPa',math_transpose3x3(crystallite_P(1:3,1:3,g,i,e))/1e6 - write(6,'(a,/,3(3(f12.7,x)/))') 'Cauchy / MPa', math_mul33x33(crystallite_P(1:3,1:3,g,i,e), math_transpose3x3(Fg_new)) & - / 1e6 / math_det3x3(Fg_new) - write(6,'(a,/,3(3(f12.7,x)/))') 'Fe Lp Fe^-1',math_transpose3x3( & - math_mul33x33(Fe_new, math_mul33x33(crystallite_Lp(1:3,1:3,g,i,e), & - math_inv3x3(Fe_new)))) ! transpose to get correct print out order - write(6,'(a,/,3(3(f12.7,x)/))') 'Fp',math_transpose3x3(crystallite_Fp(1:3,1:3,g,i,e)) + write(6,'(a,/,3(12(x),3(f12.7,x)/))') '<< CRYST >> P / MPa',math_transpose3x3(crystallite_P(1:3,1:3,g,i,e))/1e6 + write(6,'(a,/,3(12(x),3(f12.7,x)/))') '<< CRYST >> Cauchy / MPa', & + math_mul33x33(crystallite_P(1:3,1:3,g,i,e), math_transpose3x3(Fg_new)) / 1e6 / math_det3x3(Fg_new) + write(6,'(a,/,3(12(x),3(f12.7,x)/))') '<< CRYST >> Fe Lp Fe^-1', & + math_transpose3x3(math_mul33x33(Fe_new, math_mul33x33(crystallite_Lp(1:3,1:3,g,i,e), math_inv3x3(Fe_new)))) ! transpose to get correct print out order + write(6,'(a,/,3(12(x),3(f12.7,x)/))') '<< CRYST >> Fp',math_transpose3x3(crystallite_Fp(1:3,1:3,g,i,e)) !$OMP END CRITICAL (write2out) endif -!$OMP CRITICAL (distributionStress) - debug_StressLoopDistribution(NiterationStress,numerics_integrationMode) = & - debug_StressLoopDistribution(NiterationStress,numerics_integrationMode) + 1 -!$OMP END CRITICAL (distributionStress) +if (debug_verbosity > 0) then + !$OMP CRITICAL (distributionStress) + debug_StressLoopDistribution(NiterationStress,numerics_integrationMode) = & + debug_StressLoopDistribution(NiterationStress,numerics_integrationMode) + 1 + !$OMP END CRITICAL (distributionStress) +endif endfunction @@ -2893,7 +2927,8 @@ use material, only: material_phase, & use mesh, only: mesh_element, & mesh_ipNeighborhood, & FE_NipNeighbors -use debug, only: debugger, & +use debug, only: debug_verbosity, & + debug_selectiveDebugger, & debug_e, debug_i, debug_g, & verboseDebugger use constitutive_nonlocal, only: constitutive_nonlocal_structure, & diff --git a/code/debug.config b/code/debug.config index c6414c580..8f0a28b03 100644 --- a/code/debug.config +++ b/code/debug.config @@ -1,8 +1,16 @@ ### $Id$ ### ### debugging parameters ### -debug 1 # >0 true to switch on debugging -verbose 1 # >0 true to switch on verbose output +verbosity 1 # level of detail of the debugging output (0-8) + # 0 : only version infos and all from "hypela2"/"umat" + # 1 : basic outputs from "CPFEM.f90", basic output from initialization routines, debug_info + # 2 : extensive outputs from "CPFEM.f90", extensive output from initialization routines + # 3 : basic outputs from "homogenization.f90" + # 4 : extensive outputs from "homogenization.f90" + # 5 : basic outputs from "crystallite.f90" + # 6 : extensive outputs from "crystallite.f90" + # 7 : basic outputs from the constitutive files + # 8 : extensive outputs from the constitutive files selective 1 # >0 true to switch on e,i,g selective debugging element 1 # selected element for debugging (synonymous: "el", "e") ip 1 # selected integration point for debugging (synonymous: "integrationpoint", "i") diff --git a/code/debug.f90 b/code/debug.f90 index 71e1a392c..4c869ece3 100644 --- a/code/debug.f90 +++ b/code/debug.f90 @@ -33,7 +33,8 @@ real(pReal) :: debug_jacobianMin logical :: selectiveDebugger = .true. logical :: verboseDebugger = .false. logical :: debugger = .true. -logical :: distribution_init = .false. +logical :: debug_selectiveDebugger = .true. +integer(pInt) :: debug_verbosity = 1_pInt CONTAINS @@ -69,7 +70,7 @@ subroutine debug_init() integer(pInt), dimension(1+2*maxNchunks) :: positions character(len=64) tag character(len=1024) line - + !$OMP CRITICAL (write2out) write(6,*) write(6,*) '<<<+- debug init -+>>>' @@ -87,11 +88,6 @@ subroutine debug_init() ! try to open the config file if(IO_open_file(fileunit,debug_configFile)) then - !$OMP CRITICAL (write2out) - write(6,*) ' ... using values from config file' - write(6,*) - !$OMP END CRITICAL (write2out) - line = '' ! read variables from config file and overwrite parameters do @@ -107,37 +103,47 @@ subroutine debug_init() case ('grain','g','gr') debug_g = IO_intValue(line,positions,2) case ('selective') - selectiveDebugger = IO_intValue(line,positions,2) > 0_pInt - case ('verbose') - verboseDebugger = IO_intValue(line,positions,2) > 0_pInt - case ('debug') - debugger = IO_intValue(line,positions,2) > 0_pInt + debug_selectiveDebugger = IO_intValue(line,positions,2) > 0_pInt + case ('verbosity') + debug_verbosity = IO_intValue(line,positions,2) endselect enddo 100 close(fileunit) - + + if (debug_verbosity > 0) then + !$OMP CRITICAL (write2out) + write(6,*) ' ... using values from config file' + write(6,*) + !$OMP END CRITICAL (write2out) + endif + ! no config file, so we use standard values else - !$OMP CRITICAL (write2out) - write(6,*) ' ... using standard values' - write(6,*) - !$OMP END CRITICAL (write2out) - + if (debug_verbosity > 0) then + !$OMP CRITICAL (write2out) + write(6,*) ' ... using standard values' + write(6,*) + !$OMP END CRITICAL (write2out) + endif + endif - ! writing parameters to output file - !$OMP CRITICAL (write2out) - write(6,'(a24,x,l)') 'debug: ',debugger - write(6,'(a24,x,l)') 'verbose: ',verboseDebugger - write(6,'(a24,x,l)') 'selective: ',selectiveDebugger - !$OMP END CRITICAL (write2out) - if (selectiveDebugger) then + if (debug_verbosity > 0) then !$OMP CRITICAL (write2out) - write(6,'(a24,x,i8)') ' element: ',debug_e - write(6,'(a24,x,i8)') ' ip: ',debug_i - write(6,'(a24,x,i8)') ' grain: ',debug_g + write(6,'(a24,x,l)') 'debug: ',debugger + write(6,'(a24,x,l)') 'verbose: ',verboseDebugger + write(6,'(a24,x,l)') 'selective: ',selectiveDebugger !$OMP END CRITICAL (write2out) + endif + if (debug_selectiveDebugger) then + if (debug_verbosity > 0) then + !$OMP CRITICAL (write2out) + write(6,'(a24,x,i8)') 'element: ',debug_e + write(6,'(a24,x,i8)') 'ip: ',debug_i + write(6,'(a24,x,i8)') 'grain: ',debug_g + !$OMP END CRITICAL (write2out) + endif else debug_e = 0_pInt ! switch off selective debugging debug_i = 0_pInt @@ -197,115 +203,116 @@ subroutine debug_info() call system_clock(count_rate=tickrate) - !$OMP CRITICAL (write2out) + if (debug_verbosity > 0) then + !$OMP CRITICAL (write2out) - write(6,*) - write(6,*) 'DEBUG Info (from previous cycle)' - write(6,*) - write(6,'(a33,x,i12)') 'total calls to LpAndItsTangent :',debug_cumLpCalls - if (debug_cumLpCalls > 0_pInt) then - write(6,'(a33,x,f12.3)') 'total CPU time/s :',dble(debug_cumLpTicks)/tickrate - write(6,'(a33,x,f12.6)') 'avg CPU time/microsecs per call :',& - dble(debug_cumLpTicks)*1.0e6_pReal/tickrate/debug_cumLpCalls - endif - write(6,*) - write(6,'(a33,x,i12)') 'total calls to collectDotState :',debug_cumDotStateCalls - if (debug_cumdotStateCalls > 0_pInt) then - write(6,'(a33,x,f12.3)') 'total CPU time/s :',dble(debug_cumDotStateTicks)/tickrate - write(6,'(a33,x,f12.6)') 'avg CPU time/microsecs per call :',& - dble(debug_cumDotStateTicks)*1.0e6_pReal/tickrate/debug_cumDotStateCalls - endif - write(6,*) - write(6,'(a33,x,i12)') 'total calls to dotTemperature :',debug_cumDotTemperatureCalls - if (debug_cumdotTemperatureCalls > 0_pInt) then - write(6,'(a33,x,f12.3)') 'total CPU time/s :', dble(debug_cumDotTemperatureTicks)/tickrate - write(6,'(a33,x,f12.6)') 'avg CPU time/microsecs per call :',& - dble(debug_cumDotTemperatureTicks)*1.0e6_pReal/tickrate/debug_cumDotTemperatureCalls - endif - - integral = 0_pInt - write(6,*) - write(6,*) - write(6,*) 'distribution_StressLoop : stress frogbreak stiffness frogbreak' - do i=1,nStress - if (any(debug_StressLoopDistribution(i,:) /= 0_pInt ) .or. & - any(debug_LeapfrogBreakDistribution(i,:) /= 0_pInt ) ) then - integral = integral + i*debug_StressLoopDistribution(i,1) + i*debug_StressLoopDistribution(i,2) - write(6,'(i25,x,i10,x,i10,x,i10,x,i10)') i,debug_StressLoopDistribution(i,1),debug_LeapfrogBreakDistribution(i,1), & - debug_StressLoopDistribution(i,2),debug_LeapfrogBreakDistribution(i,2) + write(6,*) + write(6,*) 'DEBUG Info (from previous cycle)' + write(6,*) + write(6,'(a33,x,i12)') 'total calls to LpAndItsTangent :',debug_cumLpCalls + if (debug_cumLpCalls > 0_pInt) then + write(6,'(a33,x,f12.3)') 'total CPU time/s :',dble(debug_cumLpTicks)/tickrate + write(6,'(a33,x,f12.6)') 'avg CPU time/microsecs per call :',& + dble(debug_cumLpTicks)*1.0e6_pReal/tickrate/debug_cumLpCalls + endif + write(6,*) + write(6,'(a33,x,i12)') 'total calls to collectDotState :',debug_cumDotStateCalls + if (debug_cumdotStateCalls > 0_pInt) then + write(6,'(a33,x,f12.3)') 'total CPU time/s :',dble(debug_cumDotStateTicks)/tickrate + write(6,'(a33,x,f12.6)') 'avg CPU time/microsecs per call :',& + dble(debug_cumDotStateTicks)*1.0e6_pReal/tickrate/debug_cumDotStateCalls + endif + write(6,*) + write(6,'(a33,x,i12)') 'total calls to dotTemperature :',debug_cumDotTemperatureCalls + if (debug_cumdotTemperatureCalls > 0_pInt) then + write(6,'(a33,x,f12.3)') 'total CPU time/s :', dble(debug_cumDotTemperatureTicks)/tickrate + write(6,'(a33,x,f12.6)') 'avg CPU time/microsecs per call :',& + dble(debug_cumDotTemperatureTicks)*1.0e6_pReal/tickrate/debug_cumDotTemperatureCalls endif - enddo - write(6,'(a15,i10,x,i10,12x,i10)') ' total',integral,& - sum(debug_StressLoopDistribution(:,1)), & - sum(debug_StressLoopDistribution(:,2)) - integral = 0_pInt - write(6,*) - write(6,*) 'distribution_CrystalliteStateLoop :' - do i=1,nState - if (any(debug_StateLoopDistribution(i,:) /= 0)) then - integral = integral + i*debug_StateLoopDistribution(i,1) + i*debug_StateLoopDistribution(i,2) - write(6,'(i25,x,i10,12x,i10)') i,debug_StateLoopDistribution(i,1),debug_StateLoopDistribution(i,2) - endif - enddo - write(6,'(a15,i10,x,i10,12x,i10)') ' total',integral,& - sum(debug_StateLoopDistribution(:,1)), & - sum(debug_StateLoopDistribution(:,2)) - - integral = 0_pInt - write(6,*) - write(6,*) 'distribution_CrystalliteCutbackLoop :' - do i=1,nCryst+1 - if (debug_CrystalliteLoopDistribution(i) /= 0) then - integral = integral + i*debug_CrystalliteLoopDistribution(i) - if (i <= nCryst) then - write(6,'(i25,x,i10)') i,debug_CrystalliteLoopDistribution(i) - else - write(6,'(i25,a1,i10)') i-1,'+',debug_CrystalliteLoopDistribution(i) + integral = 0_pInt + write(6,*) + write(6,*) + write(6,*) 'distribution_StressLoop : stress frogbreak stiffness frogbreak' + do i=1,nStress + if (any(debug_StressLoopDistribution(i,:) /= 0_pInt ) .or. & + any(debug_LeapfrogBreakDistribution(i,:) /= 0_pInt ) ) then + integral = integral + i*debug_StressLoopDistribution(i,1) + i*debug_StressLoopDistribution(i,2) + write(6,'(i25,x,i10,x,i10,x,i10,x,i10)') i,debug_StressLoopDistribution(i,1),debug_LeapfrogBreakDistribution(i,1), & + debug_StressLoopDistribution(i,2),debug_LeapfrogBreakDistribution(i,2) endif - endif - enddo - write(6,'(a15,i10,x,i10)') ' total',integral,sum(debug_CrystalliteLoopDistribution) - - integral = 0_pInt - write(6,*) - write(6,*) 'distribution_MaterialpointStateLoop :' - do i=1,nMPstate - if (debug_MaterialpointStateLoopDistribution(i) /= 0) then - integral = integral + i*debug_MaterialpointStateLoopDistribution(i) - write(6,'(i25,x,i10)') i,debug_MaterialpointStateLoopDistribution(i) - endif - enddo - write(6,'(a15,i10,x,i10)') ' total',integral,sum(debug_MaterialpointStateLoopDistribution) - - integral = 0_pInt - write(6,*) - write(6,*) 'distribution_MaterialpointCutbackLoop :' - do i=1,nHomog+1 - if (debug_MaterialpointLoopDistribution(i) /= 0) then - integral = integral + i*debug_MaterialpointLoopDistribution(i) - if (i <= nHomog) then - write(6,'(i25,x,i10)') i,debug_MaterialpointLoopDistribution(i) - else - write(6,'(i25,a1,i10)') i-1,'+',debug_MaterialpointLoopDistribution(i) + enddo + write(6,'(a15,i10,x,i10,12x,i10)') ' total',integral,& + sum(debug_StressLoopDistribution(:,1)), & + sum(debug_StressLoopDistribution(:,2)) + + integral = 0_pInt + write(6,*) + write(6,*) 'distribution_CrystalliteStateLoop :' + do i=1,nState + if (any(debug_StateLoopDistribution(i,:) /= 0)) then + integral = integral + i*debug_StateLoopDistribution(i,1) + i*debug_StateLoopDistribution(i,2) + write(6,'(i25,x,i10,12x,i10)') i,debug_StateLoopDistribution(i,1),debug_StateLoopDistribution(i,2) endif - endif - enddo - write(6,'(a15,i10,x,i10)') ' total',integral,sum(debug_MaterialpointLoopDistribution) - - write(6,*) - write(6,*) - write(6,*) 'Extreme values of returned stress and jacobian' - write(6,*) - write(6,'(a39)') ' value el ip' - write(6,'(a14,x,e12.3,x,i6,x,i4)') 'stress min :', debug_stressMin, debug_stressMinLocation - write(6,'(a14,x,e12.3,x,i6,x,i4)') ' max :', debug_stressMax, debug_stressMaxLocation - write(6,'(a14,x,e12.3,x,i6,x,i4)') 'jacobian min :', debug_jacobianMin, debug_jacobianMinLocation - write(6,'(a14,x,e12.3,x,i6,x,i4)') ' max :', debug_jacobianMax, debug_jacobianMaxLocation + enddo + write(6,'(a15,i10,x,i10,12x,i10)') ' total',integral,& + sum(debug_StateLoopDistribution(:,1)), & + sum(debug_StateLoopDistribution(:,2)) + + integral = 0_pInt + write(6,*) + write(6,*) 'distribution_CrystalliteCutbackLoop :' + do i=1,nCryst+1 + if (debug_CrystalliteLoopDistribution(i) /= 0) then + integral = integral + i*debug_CrystalliteLoopDistribution(i) + if (i <= nCryst) then + write(6,'(i25,x,i10)') i,debug_CrystalliteLoopDistribution(i) + else + write(6,'(i25,a1,i10)') i-1,'+',debug_CrystalliteLoopDistribution(i) + endif + endif + enddo + write(6,'(a15,i10,x,i10)') ' total',integral,sum(debug_CrystalliteLoopDistribution) + + integral = 0_pInt + write(6,*) + write(6,*) 'distribution_MaterialpointStateLoop :' + do i=1,nMPstate + if (debug_MaterialpointStateLoopDistribution(i) /= 0) then + integral = integral + i*debug_MaterialpointStateLoopDistribution(i) + write(6,'(i25,x,i10)') i,debug_MaterialpointStateLoopDistribution(i) + endif + enddo + write(6,'(a15,i10,x,i10)') ' total',integral,sum(debug_MaterialpointStateLoopDistribution) + + integral = 0_pInt + write(6,*) + write(6,*) 'distribution_MaterialpointCutbackLoop :' + do i=1,nHomog+1 + if (debug_MaterialpointLoopDistribution(i) /= 0) then + integral = integral + i*debug_MaterialpointLoopDistribution(i) + if (i <= nHomog) then + write(6,'(i25,x,i10)') i,debug_MaterialpointLoopDistribution(i) + else + write(6,'(i25,a1,i10)') i-1,'+',debug_MaterialpointLoopDistribution(i) + endif + endif + enddo + write(6,'(a15,i10,x,i10)') ' total',integral,sum(debug_MaterialpointLoopDistribution) + + write(6,*) + write(6,*) + write(6,*) 'Extreme values of returned stress and jacobian' + write(6,*) + write(6,'(a39)') ' value el ip' + write(6,'(a14,x,e12.3,x,i6,x,i4)') 'stress min :', debug_stressMin, debug_stressMinLocation + write(6,'(a14,x,e12.3,x,i6,x,i4)') ' max :', debug_stressMax, debug_stressMaxLocation + write(6,'(a14,x,e12.3,x,i6,x,i4)') 'jacobian min :', debug_jacobianMin, debug_jacobianMinLocation + write(6,'(a14,x,e12.3,x,i6,x,i4)') ' max :', debug_jacobianMax, debug_jacobianMaxLocation + write(6,*) - write(6,*) - - !$OMP END CRITICAL (write2out) + !$OMP END CRITICAL (write2out) + endif endsubroutine diff --git a/code/homogenization.f90 b/code/homogenization.f90 index 6715a0183..98664e526 100644 --- a/code/homogenization.f90 +++ b/code/homogenization.f90 @@ -55,6 +55,7 @@ CONTAINS subroutine homogenization_init(Temperature) use prec, only: pReal,pInt use math, only: math_I3 + use debug, only: debug_verbosity use IO, only: IO_error, IO_open_file, IO_open_jobFile use mesh, only: mesh_maxNips,mesh_NcpElems,mesh_element,FE_Nips use material @@ -180,30 +181,32 @@ subroutine homogenization_init(Temperature) write(6,*) '<<<+- homogenization init -+>>>' write(6,*) '$Id$' write(6,*) - write(6,'(a32,x,7(i5,x))') 'homogenization_state0: ', shape(homogenization_state0) - write(6,'(a32,x,7(i5,x))') 'homogenization_subState0: ', shape(homogenization_subState0) - write(6,'(a32,x,7(i5,x))') 'homogenization_state: ', shape(homogenization_state) - write(6,'(a32,x,7(i5,x))') 'homogenization_sizeState: ', shape(homogenization_sizeState) - write(6,'(a32,x,7(i5,x))') 'homogenization_sizePostResults: ', shape(homogenization_sizePostResults) - write(6,*) - write(6,'(a32,x,7(i5,x))') 'materialpoint_dPdF: ', shape(materialpoint_dPdF) - write(6,'(a32,x,7(i5,x))') 'materialpoint_F0: ', shape(materialpoint_F0) - write(6,'(a32,x,7(i5,x))') 'materialpoint_F: ', shape(materialpoint_F) - write(6,'(a32,x,7(i5,x))') 'materialpoint_subF0: ', shape(materialpoint_subF0) - write(6,'(a32,x,7(i5,x))') 'materialpoint_subF: ', shape(materialpoint_subF) - write(6,'(a32,x,7(i5,x))') 'materialpoint_P: ', shape(materialpoint_P) - write(6,'(a32,x,7(i5,x))') 'materialpoint_Temperature: ', shape(materialpoint_Temperature) - write(6,'(a32,x,7(i5,x))') 'materialpoint_subFrac: ', shape(materialpoint_subFrac) - write(6,'(a32,x,7(i5,x))') 'materialpoint_subStep: ', shape(materialpoint_subStep) - write(6,'(a32,x,7(i5,x))') 'materialpoint_subdt: ', shape(materialpoint_subdt) - write(6,'(a32,x,7(i5,x))') 'materialpoint_requested: ', shape(materialpoint_requested) - write(6,'(a32,x,7(i5,x))') 'materialpoint_converged: ', shape(materialpoint_converged) - write(6,'(a32,x,7(i5,x))') 'materialpoint_doneAndHappy: ', shape(materialpoint_doneAndHappy) - write(6,*) - write(6,'(a32,x,7(i5,x))') 'materialpoint_results: ', shape(materialpoint_results) - write(6,*) - write(6,'(a32,x,7(i5,x))') 'maxSizeState: ', homogenization_maxSizeState - write(6,'(a32,x,7(i5,x))') 'maxSizePostResults: ', homogenization_maxSizePostResults + if (debug_verbosity > 0) then + write(6,'(a32,x,7(i5,x))') 'homogenization_state0: ', shape(homogenization_state0) + write(6,'(a32,x,7(i5,x))') 'homogenization_subState0: ', shape(homogenization_subState0) + write(6,'(a32,x,7(i5,x))') 'homogenization_state: ', shape(homogenization_state) + write(6,'(a32,x,7(i5,x))') 'homogenization_sizeState: ', shape(homogenization_sizeState) + write(6,'(a32,x,7(i5,x))') 'homogenization_sizePostResults: ', shape(homogenization_sizePostResults) + write(6,*) + write(6,'(a32,x,7(i5,x))') 'materialpoint_dPdF: ', shape(materialpoint_dPdF) + write(6,'(a32,x,7(i5,x))') 'materialpoint_F0: ', shape(materialpoint_F0) + write(6,'(a32,x,7(i5,x))') 'materialpoint_F: ', shape(materialpoint_F) + write(6,'(a32,x,7(i5,x))') 'materialpoint_subF0: ', shape(materialpoint_subF0) + write(6,'(a32,x,7(i5,x))') 'materialpoint_subF: ', shape(materialpoint_subF) + write(6,'(a32,x,7(i5,x))') 'materialpoint_P: ', shape(materialpoint_P) + write(6,'(a32,x,7(i5,x))') 'materialpoint_Temperature: ', shape(materialpoint_Temperature) + write(6,'(a32,x,7(i5,x))') 'materialpoint_subFrac: ', shape(materialpoint_subFrac) + write(6,'(a32,x,7(i5,x))') 'materialpoint_subStep: ', shape(materialpoint_subStep) + write(6,'(a32,x,7(i5,x))') 'materialpoint_subdt: ', shape(materialpoint_subdt) + write(6,'(a32,x,7(i5,x))') 'materialpoint_requested: ', shape(materialpoint_requested) + write(6,'(a32,x,7(i5,x))') 'materialpoint_converged: ', shape(materialpoint_converged) + write(6,'(a32,x,7(i5,x))') 'materialpoint_doneAndHappy: ', shape(materialpoint_doneAndHappy) + write(6,*) + write(6,'(a32,x,7(i5,x))') 'materialpoint_results: ', shape(materialpoint_results) + write(6,*) + write(6,'(a32,x,7(i5,x))') 'maxSizeState: ', homogenization_maxSizeState + write(6,'(a32,x,7(i5,x))') 'maxSizePostResults: ', homogenization_maxSizePostResults + endif call flush(6) !$OMP END CRITICAL (write2out) @@ -234,7 +237,9 @@ subroutine materialpoint_stressAndItsTangent(& use FEsolving, only: FEsolving_execElem, & FEsolving_execIP, & terminallyIll - use mesh, only: mesh_element + use mesh, only: mesh_element, & + mesh_NcpElems, & + mesh_maxNips use material, only: homogenization_Ngrains use constitutive, only: constitutive_state0, & constitutive_partionedState0, & @@ -261,8 +266,8 @@ subroutine materialpoint_stressAndItsTangent(& crystallite_converged, & crystallite_stressAndItsTangent, & crystallite_orientations - use debug, only: debugger, & - verboseDebugger, & + use debug, only: debug_verbosity, & + debug_selectiveDebugger, & debug_e, & debug_i, & debug_MaterialpointLoopDistribution, & @@ -279,14 +284,14 @@ subroutine materialpoint_stressAndItsTangent(& ! ------ initialize to starting condition ------ - if (debugger) then - write (6,*) - write (6,*) 'Material Point start' - write (6,'(a,/,(f14.9,x))') 'Temp0 of 1 1',materialpoint_Temperature(1,1) - write (6,'(a,/,3(3(f14.9,x)/))') 'F0 of 1 1',math_transpose3x3(materialpoint_F0(1:3,1:3,1,1)) - write (6,'(a,/,3(3(f14.9,x)/))') 'F of 1 1',math_transpose3x3(materialpoint_F(1:3,1:3,1,1)) - write (6,'(a,/,3(3(f14.9,x)/))') 'Fp0 of 1 1 1',math_transpose3x3(crystallite_Fp0(1:3,1:3,1,1,1)) - write (6,'(a,/,3(3(f14.9,x)/))') 'Lp0 of 1 1 1',math_transpose3x3(crystallite_Lp0(1:3,1:3,1,1,1)) + if (debug_verbosity > 2 .and. debug_e > 0 .and. debug_e <= mesh_NcpElems .and. debug_i > 0 .and. debug_i <= mesh_maxNips) then + !$OMP CRITICAL (write2out) + write (6,*) + write (6,'(a,i5,x,i2)') '<< HOMOG >> Material Point start at el ip ', debug_e, debug_i + write (6,'(a,/,12(x),f14.9)') '<< HOMOG >> Temp0', materialpoint_Temperature(debug_i,debug_e) + write (6,'(a,/,3(12(x),3(f14.9,x)/))') '<< HOMOG >> F0', math_transpose3x3(materialpoint_F0(1:3,1:3,debug_i,debug_e)) + write (6,'(a,/,3(12(x),3(f14.9,x)/))') '<< HOMOG >> F', math_transpose3x3(materialpoint_F(1:3,1:3,debug_i,debug_e)) + !$OMP END CRITICAL (write2out) endif @@ -330,9 +335,9 @@ subroutine materialpoint_stressAndItsTangent(& do i = FEsolving_execIP(1,e),FEsolving_execIP(2,e) ! iterate over IPs of this element to be processed if ( materialpoint_converged(i,e) ) then - if (verboseDebugger .and. (e == debug_e .and. i == debug_i)) then + if (debug_verbosity > 2 .and. ((e == debug_e .and. i == debug_i) .or. .not. debug_selectiveDebugger)) then !$OMP CRITICAL (write2out) - write(6,'(a,x,f10.8,x,a,x,f10.8,x,a,/)') '°°° winding forward from', & + write(6,'(a,x,f10.8,x,a,x,f10.8,x,a,/)') '<< HOMOG >> winding forward from', & materialpoint_subFrac(i,e), 'to current materialpoint_subFrac', & materialpoint_subFrac(i,e)+materialpoint_subStep(i,e),'in materialpoint_stressAndItsTangent' !$OMP END CRITICAL (write2out) @@ -361,10 +366,12 @@ subroutine materialpoint_stressAndItsTangent(& materialpoint_subF0(1:3,1:3,i,e) = materialpoint_subF(1:3,1:3,i,e) ! ...def grad !$OMP FLUSH(materialpoint_subF0) elseif (materialpoint_requested(i,e)) then ! this materialpoint just converged ! already at final time (??) - !$OMP CRITICAL (distributionHomog) - debug_MaterialpointLoopDistribution(min(nHomog+1,NiterationHomog)) = & - debug_MaterialpointLoopDistribution(min(nHomog+1,NiterationHomog)) + 1 - !$OMP END CRITICAL (distributionHomog) + if (debug_verbosity > 0) then + !$OMP CRITICAL (distributionHomog) + debug_MaterialpointLoopDistribution(min(nHomog+1,NiterationHomog)) = & + debug_MaterialpointLoopDistribution(min(nHomog+1,NiterationHomog)) + 1 + !$OMP END CRITICAL (distributionHomog) + endif endif ! materialpoint didn't converge, so we need a cutback here @@ -379,9 +386,9 @@ subroutine materialpoint_stressAndItsTangent(& materialpoint_subStep(i,e) = subStepSizeHomog * materialpoint_subStep(i,e) ! crystallite had severe trouble, so do a significant cutback !$OMP FLUSH(materialpoint_subStep) - if (verboseDebugger .and. (e == debug_e .and. i == debug_i)) then + if (debug_verbosity > 2 .and. ((e == debug_e .and. i == debug_i) .or. .not. debug_selectiveDebugger)) then !$OMP CRITICAL (write2out) - write(6,'(a,x,f10.8,/)') '°°° cutback step in materialpoint_stressAndItsTangent with new materialpoint_subStep:',& + write(6,'(a,x,f10.8,/)') '<< HOMOG >> cutback step in materialpoint_stressAndItsTangent with new materialpoint_subStep:',& materialpoint_subStep(i,e) !$OMP END CRITICAL (write2out) endif @@ -410,11 +417,6 @@ subroutine materialpoint_stressAndItsTangent(& enddo ! loop elements !$OMP END PARALLEL DO -!* Checks for cutback/substepping loops - ! write (6,'(a,/,8(L,x))') 'MP exceeds substep min',materialpoint_subStep(:,FEsolving_execELem(1):FEsolving_execElem(2)) > subStepMinHomog - ! write (6,'(a,/,8(L,x))') 'MP requested',materialpoint_requested(:,FEsolving_execELem(1):FEsolving_execElem(2)) - ! write (6,'(a,/,8(f6.4,x))') 'MP subFrac',materialpoint_subFrac(:,FEsolving_execELem(1):FEsolving_execElem(2)) - ! write (6,'(a,/,8(f6.4,x))') 'MP subStep',materialpoint_subStep(:,FEsolving_execELem(1):FEsolving_execElem(2)) ! ------ convergence loop material point homogenization ------ @@ -427,9 +429,6 @@ subroutine materialpoint_stressAndItsTangent(& NiterationMPstate < nMPstate) ! convergence loop for materialpoint NiterationMPstate = NiterationMPstate + 1 -! write(6,'(a,/,125(8(l,x),/))') 'material point request and not done', & -! materialpoint_requested .and. .not. materialpoint_doneAndHappy(1,:,:) - ! --+>> deformation partitioning <<+-- ! ! based on materialpoint_subF0,.._subF, @@ -452,7 +451,6 @@ subroutine materialpoint_stressAndItsTangent(& enddo enddo !$OMP END PARALLEL DO -! write(6,'(a,/,125(8(8(l,x),2x),/))') 'crystallite request with updated partitioning', crystallite_requested ! --+>> crystallite integration <<+-- @@ -461,7 +459,6 @@ subroutine materialpoint_stressAndItsTangent(& ! incrementing by crystallite_dt call crystallite_stressAndItsTangent(updateJaco) ! request stress and tangent calculation for constituent grains -! write(6,'(a,/,125(8(8(l,x),2x),/))') 'crystallite converged', crystallite_converged ! --+>> state update <<+-- @@ -479,17 +476,17 @@ subroutine materialpoint_stressAndItsTangent(& endif !$OMP FLUSH(materialpoint_converged) if (materialpoint_converged(i,e)) then - !$OMP CRITICAL (distributionMPState) - debug_MaterialpointStateLoopdistribution(NiterationMPstate) = & - debug_MaterialpointStateLoopdistribution(NiterationMPstate) + 1 - !$OMP END CRITICAL (distributionMPState) + if (debug_verbosity > 0) then + !$OMP CRITICAL (distributionMPState) + debug_MaterialpointStateLoopdistribution(NiterationMPstate) = & + debug_MaterialpointStateLoopdistribution(NiterationMPstate) + 1 + !$OMP END CRITICAL (distributionMPState) + endif endif endif enddo enddo !$OMP END PARALLEL DO -! write(6,'(a,/,125(8(l,x),/))') 'material point done', materialpoint_doneAndHappy(1,:,:) -! write(6,'(a,/,125(8(l,x),/))') 'material point converged', materialpoint_converged enddo ! homogenization convergence loop @@ -509,15 +506,19 @@ subroutine materialpoint_stressAndItsTangent(& enddo; enddo !$OMP END PARALLEL DO - if (debugger) then - write (6,*) - write (6,'(a)') '°°° Material Point end' - write (6,*) + if (debug_verbosity > 2) then + !$OMP CRITICAL (write2out) + write (6,*) + write (6,'(a)') '<< HOMOG >> Material Point end' + write (6,*) + !$OMP END CRITICAL (write2out) endif else - write (6,*) - write (6,'(a)') '°°° Material Point terminally ill' - write (6,*) + !$OMP CRITICAL (write2out) + write (6,*) + write (6,'(a)') '<< HOMOG >> Material Point terminally ill' + write (6,*) + !$OMP END CRITICAL (write2out) endif return diff --git a/code/homogenization_RGC.f90 b/code/homogenization_RGC.f90 index 52ae8aae6..6e89dd5bf 100644 --- a/code/homogenization_RGC.f90 +++ b/code/homogenization_RGC.f90 @@ -60,10 +60,10 @@ subroutine homogenization_RGC_init(& character(len=1024) line !$OMP CRITICAL (write2out) - write(6,*) - write(6,'(a21,a20,a12)') '<<<+- homogenization',homogenization_RGC_label,' init -+>>>' - write(6,*) '$Id$' - write(6,*) + write(6,*) + write(6,'(a21,a20,a12)') '<<<+- homogenization',homogenization_RGC_label,' init -+>>>' + write(6,*) '$Id$' + write(6,*) !$OMP END CRITICAL (write2out) maxNinstance = count(homogenization_type == homogenization_RGC_label) diff --git a/code/homogenization_isostrain.f90 b/code/homogenization_isostrain.f90 index 50c9e578d..9b8daaea0 100644 --- a/code/homogenization_isostrain.f90 +++ b/code/homogenization_isostrain.f90 @@ -54,10 +54,12 @@ subroutine homogenization_isostrain_init(& character(len=64) tag character(len=1024) line - write(6,*) - write(6,'(a21,a20,a12)') '<<<+- homogenization',homogenization_isostrain_label,' init -+>>>' - write(6,*) '$Id$' - write(6,*) + !$OMP CRITICAL (write2out) + write(6,*) + write(6,'(a21,a20,a12)') '<<<+- homogenization',homogenization_isostrain_label,' init -+>>>' + write(6,*) '$Id$' + write(6,*) + !$OMP END CRITICAL (write2out) maxNinstance = count(homogenization_type == homogenization_isostrain_label) if (maxNinstance == 0) return diff --git a/code/lattice.f90 b/code/lattice.f90 index 61338a213..54d25347a 100644 --- a/code/lattice.f90 +++ b/code/lattice.f90 @@ -689,16 +689,17 @@ subroutine lattice_init() !************************************** use IO, only: IO_open_file,IO_countSections,IO_countTagInPart,IO_error use material, only: material_configfile,material_partPhase + use debug, only: debug_verbosity implicit none integer(pInt), parameter :: fileunit = 200 integer(pInt) i,Nsections !$OMP CRITICAL (write2out) - write(6,*) - write(6,*) '<<<+- lattice init -+>>>' - write(6,*) '$Id$' - write(6,*) + write(6,*) + write(6,*) '<<<+- lattice init -+>>>' + write(6,*) '$Id$' + write(6,*) !$OMP END CRITICAL (write2out) if(.not. IO_open_file(fileunit,material_configFile)) call IO_error(100) ! cannot open config file @@ -707,11 +708,13 @@ subroutine lattice_init() ! lattice_Nstructure = Nsections + 2_pInt ! most conservative assumption close(fileunit) - !$OMP CRITICAL (write2out) - write(6,'(a16,x,i5)') '# phases:',Nsections - write(6,'(a16,x,i5)') '# structures:',lattice_Nstructure - write(6,*) - !$OMP END CRITICAL (write2out) + if (debug_verbosity > 0) then + !$OMP CRITICAL (write2out) + write(6,'(a16,x,i5)') '# phases:',Nsections + write(6,'(a16,x,i5)') '# structures:',lattice_Nstructure + write(6,*) + !$OMP END CRITICAL (write2out) + endif allocate(lattice_Sslip(3,3,lattice_maxNslip,lattice_Nstructure)); lattice_Sslip = 0.0_pReal allocate(lattice_Sslip_v(6,lattice_maxNslip,lattice_Nstructure)); lattice_Sslip_v = 0.0_pReal diff --git a/code/material.f90 b/code/material.f90 index 7da65e97a..306b621d3 100644 --- a/code/material.f90 +++ b/code/material.f90 @@ -87,6 +87,7 @@ subroutine material_init() !************************************** use prec, only: pReal,pInt use IO, only: IO_error, IO_open_file + use debug, only: debug_verbosity implicit none !* Definition of variables @@ -94,10 +95,10 @@ subroutine material_init() integer(pInt) i,j !$OMP CRITICAL (write2out) - write(6,*) - write(6,*) '<<<+- material init -+>>>' - write(6,*) '$Id$' - write(6,*) + write(6,*) + write(6,*) '<<<+- material init -+>>>' + write(6,*) '$Id$' + write(6,*) !$OMP END CRITICAL (write2out) if(.not. IO_open_file(fileunit,material_configFile)) call IO_error(100) ! cannot open config file @@ -108,7 +109,6 @@ subroutine material_init() call material_parsePhase(fileunit,material_partPhase) close(fileunit) - !$OMP CRITICAL (write2out) do i = 1,material_Nmicrostructure if (microstructure_crystallite(i) < 1 .or. & microstructure_crystallite(i) > material_Ncrystallite) call IO_error(150,i) @@ -117,34 +117,41 @@ subroutine material_init() if (minval(microstructure_texture(1:microstructure_Nconstituents(i),i)) < 1 .or. & maxval(microstructure_texture(1:microstructure_Nconstituents(i),i)) > material_Ntexture) call IO_error(160,i) if (abs(sum(microstructure_fraction(:,i)) - 1.0_pReal) >= 1.0e-10_pReal) then - write(6,*)'sum of microstructure fraction = ',sum(microstructure_fraction(:,i)) + if (debug_verbosity > 0) then + !$OMP CRITICAL (write2out) + write(6,*)'sum of microstructure fraction = ',sum(microstructure_fraction(:,i)) + !$OMP END CRITICAL (write2out) + endif call IO_error(170,i) endif enddo - write (6,*) - write (6,*) 'MATERIAL configuration' - write (6,*) - write (6,'(a32,x,a16,x,a6)') 'homogenization ','type ','grains' - do i = 1,material_Nhomogenization - write (6,'(x,a32,x,a16,x,i4)') homogenization_name(i),homogenization_type(i),homogenization_Ngrains(i) - enddo - write (6,*) - write (6,'(a32,x,a11,x,a12,x,a13)') 'microstructure ','crystallite','constituents','homogeneous' - do i = 1,material_Nmicrostructure - write (6,'(a32,4x,i4,8x,i4,8x,l)') microstructure_name(i), & - microstructure_crystallite(i), & - microstructure_Nconstituents(i), & - microstructure_elemhomo(i) - if (microstructure_Nconstituents(i) > 0_pInt) then - do j = 1,microstructure_Nconstituents(i) - write (6,'(a1,x,a32,x,a32,x,f6.4)') '>',phase_name(microstructure_phase(j,i)),& - texture_name(microstructure_texture(j,i)),& - microstructure_fraction(j,i) + if (debug_verbosity > 0) then + !$OMP CRITICAL (write2out) + write (6,*) + write (6,*) 'MATERIAL configuration' + write (6,*) + write (6,'(a32,x,a16,x,a6)') 'homogenization ','type ','grains' + do i = 1,material_Nhomogenization + write (6,'(x,a32,x,a16,x,i4)') homogenization_name(i),homogenization_type(i),homogenization_Ngrains(i) enddo write (6,*) - endif - enddo - !$OMP END CRITICAL (write2out) + write (6,'(a32,x,a11,x,a12,x,a13)') 'microstructure ','crystallite','constituents','homogeneous' + do i = 1,material_Nmicrostructure + write (6,'(a32,4x,i4,8x,i4,8x,l)') microstructure_name(i), & + microstructure_crystallite(i), & + microstructure_Nconstituents(i), & + microstructure_elemhomo(i) + if (microstructure_Nconstituents(i) > 0_pInt) then + do j = 1,microstructure_Nconstituents(i) + write (6,'(a1,x,a32,x,a32,x,f6.4)') '>',phase_name(microstructure_phase(j,i)),& + texture_name(microstructure_texture(j,i)),& + microstructure_fraction(j,i) + enddo + write (6,*) + endif + enddo + !$OMP END CRITICAL (write2out) + endif call material_populateGrains() @@ -540,6 +547,7 @@ subroutine material_populateGrains() use mesh, only: mesh_element, mesh_maxNips, mesh_NcpElems, mesh_ipVolume, FE_Nips use IO, only: IO_error, IO_hybridIA use FEsolving, only: FEsolving_execIP + use debug, only: debug_verbosity implicit none integer(pInt), dimension (:,:), allocatable :: Ngrains @@ -581,21 +589,25 @@ subroutine material_populateGrains() allocate(phaseOfGrain(maxval(Ngrains))) ! reserve memory for maximum case allocate(orientationOfGrain(3,maxval(Ngrains))) ! reserve memory for maximum case - !$OMP CRITICAL (write2out) - write (6,*) - write (6,*) 'MATERIAL grain population' - write (6,*) - write (6,'(a32,x,a32,x,a6)') 'homogenization_name','microstructure_name','grain#' - !$OMP END CRITICAL (write2out) + if (debug_verbosity > 0) then + !$OMP CRITICAL (write2out) + write (6,*) + write (6,*) 'MATERIAL grain population' + write (6,*) + write (6,'(a32,x,a32,x,a6)') 'homogenization_name','microstructure_name','grain#' + !$OMP END CRITICAL (write2out) + endif do homog = 1,material_Nhomogenization ! loop over homogenizations dGrains = homogenization_Ngrains(homog) ! grain number per material point do micro = 1,material_Nmicrostructure ! all pairs of homog and micro if (Ngrains(homog,micro) > 0) then ! an active pair of homog and micro myNgrains = Ngrains(homog,micro) ! assign short name for total number of grains to populate - !$OMP CRITICAL (write2out) - write (6,*) - write (6,'(a32,x,a32,x,i6)') homogenization_name(homog),microstructure_name(micro),myNgrains - !$OMP END CRITICAL (write2out) + if (debug_verbosity > 0) then + !$OMP CRITICAL (write2out) + write (6,*) + write (6,'(a32,x,a32,x,i6)') homogenization_name(homog),microstructure_name(micro),myNgrains + !$OMP END CRITICAL (write2out) + endif ! ---------------------------------------------------------------------------- calculate volume of each grain volumeOfGrain = 0.0_pReal @@ -728,9 +740,6 @@ subroutine material_populateGrains() end forall grain = grain + FE_Nips(mesh_element(2,e)) * dGrains ! wind forward by Nips*NgrainsPerIP endif - ! write (6,*) e - ! write (6,*) material_phase(:,:,e) - ! write (6,*) material_EulerAngles(:,:,:,e) endif enddo diff --git a/code/math.f90 b/code/math.f90 index bb1c5e4e0..9b4e12a05 100644 --- a/code/math.f90 +++ b/code/math.f90 @@ -121,6 +121,7 @@ real(pReal), dimension(4,36), parameter :: math_symOperations = & use prec, only: pReal,pInt,tol_math_check use numerics, only: fixedSeed use IO, only: IO_error + use debug, only: debug_verbosity implicit none real(pReal), dimension(3,3) :: R,R2 @@ -145,11 +146,13 @@ real(pReal), dimension(4,36), parameter :: math_symOperations = & endif call random_seed(get=randInit) - !$OMP CRITICAL (write2out) - write(6,*) 'random seed: ',randInit(1) - write(6,*) - !$OMP END CRITICAL (write2out) - + if (debug_verbosity > 0) then + !$OMP CRITICAL (write2out) + write(6,*) 'random seed: ',randInit(1) + write(6,*) + !$OMP END CRITICAL (write2out) + endif + call halton_seed_set(randInit(1)) call halton_ndim_set(3) diff --git a/code/mesh.f90 b/code/mesh.f90 index 5f54e10f3..acb41b4b2 100644 --- a/code/mesh.f90 +++ b/code/mesh.f90 @@ -240,10 +240,10 @@ integer(pInt) e,element,ip !$OMP CRITICAL (write2out) - write(6,*) - write(6,*) '<<<+- mesh init -+>>>' - write(6,*) '$Id$' - write(6,*) + write(6,*) + write(6,*) '<<<+- mesh init -+>>>' + write(6,*) '$Id$' + write(6,*) !$OMP END CRITICAL (write2out) call mesh_build_FEdata() ! --- get properties of the different types of elements @@ -306,9 +306,6 @@ forall (e = 1:mesh_NcpElems) FEsolving_execIP(2,e) = FE_Nips(mesh_element(2,e)) allocate(calcMode(mesh_maxNips,mesh_NcpElems)) - !$OMP CRITICAL (write2out) - write(6,*) '<<<+- mesh init done -+>>>' - !$OMP END CRITICAL (write2out) calcMode = .false. ! pretend to have collected what first call is asking (F = I) calcMode(ip,mesh_FEasCP('elem',element)) = .true. ! first ip,el needs to be already pingponged to "calc" lastMode = .true. ! and its mode is already known... @@ -3232,7 +3229,10 @@ subroutine mesh_tell_statistics() use prec, only: pInt use math, only: math_range use IO, only: IO_error -use debug, only: verboseDebugger +use debug, only: debug_verbosity, & + debug_e, & + debug_i, & + debug_selectiveDebugger implicit none @@ -3252,15 +3252,51 @@ do e = 1,mesh_NcpElems mesh_HomogMicro(mesh_element(3,e),mesh_element(4,e)) + 1 ! count combinations of homogenization and microstructure enddo -if (verboseDebugger) then +if (debug_verbosity > 0) then + !$OMP CRITICAL (write2out) + write (6,*) + write (6,*) "Input Parser: STATISTICS" + write (6,*) + write (6,*) mesh_Nelems, " : total number of elements in mesh" + write (6,*) mesh_NcpElems, " : total number of CP elements in mesh" + write (6,*) mesh_Nnodes, " : total number of nodes in mesh" + write (6,*) mesh_maxNnodes, " : max number of nodes in any CP element" + write (6,*) mesh_maxNips, " : max number of IPs in any CP element" + write (6,*) mesh_maxNipNeighbors, " : max number of IP neighbors in any CP element" + write (6,*) mesh_maxNsubNodes, " : max number of (additional) subnodes in any CP element" + write (6,*) mesh_maxNsharedElems, " : max number of CP elements sharing a node" + write (6,*) + write (6,*) "Input Parser: HOMOGENIZATION/MICROSTRUCTURE" + write (6,*) + write (6,*) mesh_maxValStateVar(1), " : maximum homogenization index" + write (6,*) mesh_maxValStateVar(2), " : maximum microstructure index" + write (6,*) + write (fmt,"(a,i5,a)") "(9(x),a2,x,",mesh_maxValStateVar(2),"(i8))" + write (6,fmt) "+-",math_range(mesh_maxValStateVar(2)) + write (fmt,"(a,i5,a)") "(i8,x,a2,x,",mesh_maxValStateVar(2),"(i8))" + do i=1,mesh_maxValStateVar(1) ! loop over all (possibly assigned) homogenizations + write (6,fmt) i,"| ",mesh_HomogMicro(i,:) ! loop over all (possibly assigned) microstrcutures + enddo + write(6,*) + write(6,*) "Input Parser: ADDITIONAL MPIE OPTIONS" + write(6,*) + write(6,*) "periodic surface : ", mesh_periodicSurface + write(6,*) + call flush(6) + !$OMP END CRITICAL (write2out) +endif + +if (debug_verbosity > 1) then !$OMP CRITICAL (write2out) write (6,*) write (6,*) "Input Parser: SUBNODE COORDINATES" write (6,*) write(6,'(a5,x,a5,x,a15,x,a15,x,a20,3(x,a12))') 'elem','IP','IP neighbor','IPFaceNodes','subNodeOnIPFace','x','y','z' do e = 1,mesh_NcpElems ! loop over cpElems + if (debug_selectiveDebugger .and. debug_e /= e) cycle t = mesh_element(2,e) ! get elemType do i = 1,FE_Nips(t) ! loop over IPs of elem + if (debug_selectiveDebugger .and. debug_i /= i) cycle do f = 1,FE_NipNeighbors(t) ! loop over interfaces of IP do n = 1,FE_NipFaceNodes ! loop over nodes on interface write(6,'(i5,x,i5,x,i15,x,i15,x,i20,3(x,f12.8))') e,i,f,n,FE_subNodeOnIPFace(n,f,i,t),& @@ -3275,7 +3311,9 @@ if (verboseDebugger) then write(6,*) 'Input Parser: IP COORDINATES' write(6,'(a5,x,a5,3(x,a12))') 'elem','IP','x','y','z' do e = 1,mesh_NcpElems + if (debug_selectiveDebugger .and. debug_e /= e) cycle do i = 1,FE_Nips(mesh_element(2,e)) + if (debug_selectiveDebugger .and. debug_i /= i) cycle write (6,'(i5,x,i5,3(x,f12.8))') e, i, mesh_ipCenterOfGravity(:,i,e) enddo enddo @@ -3286,7 +3324,9 @@ if (verboseDebugger) then write (6,*) write (6,"(a5,x,a5,x,a15,x,a5,x,a15,x,a16)") "elem","IP","volume","face","area","-- normal --" do e = 1,mesh_NcpElems + if (debug_selectiveDebugger .and. debug_e /= e) cycle do i = 1,FE_Nips(mesh_element(2,e)) + if (debug_selectiveDebugger .and. debug_i /= i) cycle write (6,"(i5,x,i5,x,e15.8)") e,i,mesh_IPvolume(i,e) do f = 1,FE_NipNeighbors(mesh_element(2,e)) write (6,"(i33,x,e15.8,x,3(f6.3,x))") f,mesh_ipArea(f,i,e),mesh_ipAreaNormal(:,f,i,e) @@ -3298,15 +3338,21 @@ if (verboseDebugger) then write (6,*) write(6,'(a6,3(3(x),a6))') ' node','twin_x','twin_y','twin_z' do n = 1,mesh_Nnodes ! loop over cpNodes - write(6,'(i6,3(3(x),i6))') n, mesh_nodeTwins(1:3,n) + if (debug_e <= mesh_NcpElems) then + if (any(mesh_element(5:,debug_e) == n)) then + write(6,'(i6,3(3(x),i6))') n, mesh_nodeTwins(1:3,n) + endif + endif enddo write(6,*) write(6,*) "Input Parser: IP NEIGHBORHOOD" write(6,*) write(6,"(a10,x,a10,x,a10,x,a3,x,a13,x,a13)") "elem","IP","neighbor","","elemNeighbor","ipNeighbor" do e = 1,mesh_NcpElems ! loop over cpElems + if (debug_selectiveDebugger .and. debug_e /= e) cycle t = mesh_element(2,e) ! get elemType do i = 1,FE_Nips(t) ! loop over IPs of elem + if (debug_selectiveDebugger .and. debug_i /= i) cycle do n = 1,FE_NipNeighbors(t) ! loop over neighbors of IP write (6,"(i10,x,i10,x,i10,x,a3,x,i13,x,i13)") e,i,n,'-->',mesh_ipNeighborhood(1,n,i,e),mesh_ipNeighborhood(2,n,i,e) enddo @@ -3315,39 +3361,6 @@ if (verboseDebugger) then !$OMP END CRITICAL (write2out) endif - -!$OMP CRITICAL (write2out) - write (6,*) - write (6,*) "Input Parser: STATISTICS" - write (6,*) - write (6,*) mesh_Nelems, " : total number of elements in mesh" - write (6,*) mesh_NcpElems, " : total number of CP elements in mesh" - write (6,*) mesh_Nnodes, " : total number of nodes in mesh" - write (6,*) mesh_maxNnodes, " : max number of nodes in any CP element" - write (6,*) mesh_maxNips, " : max number of IPs in any CP element" - write (6,*) mesh_maxNipNeighbors, " : max number of IP neighbors in any CP element" - write (6,*) mesh_maxNsubNodes, " : max number of (additional) subnodes in any CP element" - write (6,*) mesh_maxNsharedElems, " : max number of CP elements sharing a node" - write (6,*) - write (6,*) "Input Parser: HOMOGENIZATION/MICROSTRUCTURE" - write (6,*) - write (6,*) mesh_maxValStateVar(1), " : maximum homogenization index" - write (6,*) mesh_maxValStateVar(2), " : maximum microstructure index" - write (6,*) - write (fmt,"(a,i5,a)") "(9(x),a2,x,",mesh_maxValStateVar(2),"(i8))" - write (6,fmt) "+-",math_range(mesh_maxValStateVar(2)) - write (fmt,"(a,i5,a)") "(i8,x,a2,x,",mesh_maxValStateVar(2),"(i8))" - do i=1,mesh_maxValStateVar(1) ! loop over all (possibly assigned) homogenizations - write (6,fmt) i,"| ",mesh_HomogMicro(i,:) ! loop over all (possibly assigned) microstrcutures - enddo - write(6,*) - write(6,*) "Input Parser: ADDITIONAL MPIE OPTIONS" - write(6,*) - write(6,*) "periodic surface : ", mesh_periodicSurface - write(6,*) - call flush(6) -!$OMP END CRITICAL (write2out) - deallocate(mesh_HomogMicro) endsubroutine diff --git a/code/mpie_cpfem_abaqus_exp.f b/code/mpie_cpfem_abaqus_exp.f index 4c60f315b..7b0a3c249 100644 --- a/code/mpie_cpfem_abaqus_exp.f +++ b/code/mpie_cpfem_abaqus_exp.f @@ -73,25 +73,25 @@ end function END MODULE - include "IO.f90" ! uses prec - include "numerics.f90" ! uses prec, IO - include "math.f90" ! uses prec, numerics - include "debug.f90" ! uses prec, numerics - include "FEsolving.f90" ! uses prec, IO - include "mesh.f90" ! uses prec, math, IO, FEsolving - include "material.f90" ! uses prec, math, IO, mesh - include "lattice.f90" ! uses prec, math, IO, material - include "constitutive_phenopowerlaw.f90" ! uses prec, math, IO, latt ice, material, debug - include "constitutive_titanmod.f90" ! uses prec, math, IO, lattice, material, debug - include "constitutive_j2.f90" ! uses prec, math, IO, latt ice, material, debug - include "constitutive_dislotwin.f90" ! uses prec, math, IO, latt ice, material, debug - include "constitutive_nonlocal.f90" ! uses prec, math, IO, latt ice, material, debug - include "constitutive.f90" ! uses prec, IO, math, lattice, mesh, debug - include "crystallite.f90" ! uses prec, math, IO, numerics - include "homogenization_isostrain.f90" ! uses prec, math, IO, - include "homogenization_RGC.f90" ! uses prec, math, IO, numerics, mesh: added <<>> - include "homogenization.f90" ! uses prec, math, IO, numerics - include "CPFEM.f90" ! uses prec, math, IO, numerics, debug, FEsolving, mesh, lattice, constitutive, crystallite +include "IO.f90" ! uses prec +include "numerics.f90" ! uses prec, IO +include "debug.f90" ! uses prec, numerics +include "math.f90" ! uses prec, numerics, debug +include "FEsolving.f90" ! uses prec, IO, debug +include "mesh.f90" ! uses prec, math, IO, FEsolving, debug +include "material.f90" ! uses prec, math, IO, mesh, debug +include "lattice.f90" ! uses prec, math, IO, material, debug +include "constitutive_j2.f90" ! uses prec, math, IO, lattice, material, debug +include "constitutive_phenopowerlaw.f90" ! uses prec, math, IO, lattice, material, debug +include "constitutive_titanmod.f90" ! uses prec, math, IO, lattice, material, debug +include "constitutive_dislotwin.f90" ! uses prec, math, IO, lattice, material, debug +include "constitutive_nonlocal.f90" ! uses prec, math, IO, lattice, material, debug +include "constitutive.f90" ! uses prec, IO, math, lattice, mesh, debug +include "crystallite.f90" ! uses prec, math, IO, numerics, Fesolving, material, mesh, constitutive, debug +include "homogenization_isostrain.f90" ! uses prec, math, IO, debug +include "homogenization_RGC.f90" ! uses prec, math, IO, numerics, mesh, debug +include "homogenization.f90" ! uses prec, math, IO, numerics, debug +include "CPFEM.f90" ! uses prec, math, IO, numerics, debug, FEsolving, mesh, lattice, constitutive, crystallite, debug subroutine vumat (jblock, ndir, nshr, nstatev, nfieldv, nprops, lanneal, & stepTime, totalTime, dt, cmname, coordMp, charLength, & @@ -154,7 +154,7 @@ subroutine vumat (jblock, ndir, nshr, nstatev, nfieldv, nprops, lanneal, & use math, only: invnrmMandel use debug, only: debug_info, & debug_reset, & - verboseDebugger + debug_verbosity use mesh, only: mesh_FEasCP use CPFEM, only: CPFEM_general,CPFEM_init_done, CPFEM_initAll use homogenization, only: materialpoint_sizeResults, materialpoint_results @@ -192,7 +192,7 @@ subroutine vumat (jblock, ndir, nshr, nstatev, nfieldv, nprops, lanneal, & call CPFEM_initAll(temp,nElement(n),nMatPoint(n)) outdatedByNewInc = .false. - if ( verboseDebugger ) then + if ( debug_verbosity > 1 ) then !$OMP CRITICAL (write2out) write(6,'(i6,x,i2,x,a)') nElement(n),nMatPoint(n),'first call special case..!'; call flush(6) !$OMP END CRITICAL (write2out) @@ -201,7 +201,7 @@ subroutine vumat (jblock, ndir, nshr, nstatev, nfieldv, nprops, lanneal, & else if (theTime < totalTime) then ! reached convergence outdatedByNewInc = .true. - if ( verboseDebugger ) then + if ( debug_verbosity > 1 ) then !$OMP CRITICAL (write2out) write (6,'(i6,x,i2,x,a)') nElement(n),nMatPoint(n),'lastIncConverged + outdated'; call flush(6) !$OMP END CRITICAL (write2out) @@ -223,7 +223,7 @@ subroutine vumat (jblock, ndir, nshr, nstatev, nfieldv, nprops, lanneal, & theTime = totalTime ! record current starting time - if ( verboseDebugger ) then + if ( debug_verbosity > 1 ) then !$OMP CRITICAL (write2out) write(6,'(a16,x,i2,x,a,i5,x,i5,a)') 'computationMode',computationMode,'(',nElement(n),nMatPoint(n),')'; call flush(6) !$OMP END CRITICAL (write2out) diff --git a/code/mpie_cpfem_abaqus_std.f b/code/mpie_cpfem_abaqus_std.f index e5aca179e..c173b8770 100644 --- a/code/mpie_cpfem_abaqus_std.f +++ b/code/mpie_cpfem_abaqus_std.f @@ -75,25 +75,25 @@ end function END MODULE - include "IO.f90" ! uses prec - include "numerics.f90" ! uses prec, IO - include "math.f90" ! uses prec, numerics - include "debug.f90" ! uses prec, numerics - include "FEsolving.f90" ! uses prec, IO - include "mesh.f90" ! uses prec, math, IO, FEsolving - include "material.f90" ! uses prec, math, IO, mesh - include "lattice.f90" ! uses prec, math, IO, material - include "constitutive_phenopowerlaw.f90" ! uses prec, math, IO, latt ice, material, debug - include "constitutive_titanmod.f90" ! uses prec, math, IO, lattice, material, debug - include "constitutive_j2.f90" ! uses prec, math, IO, latt ice, material, debug - include "constitutive_dislotwin.f90" ! uses prec, math, IO, latt ice, material, debug - include "constitutive_nonlocal.f90" ! uses prec, math, IO, latt ice, material, debug - include "constitutive.f90" ! uses prec, IO, math, lattice, mesh, debug - include "crystallite.f90" ! uses prec, math, IO, numerics - include "homogenization_isostrain.f90" ! uses prec, math, IO, - include "homogenization_RGC.f90" ! uses prec, math, IO, numerics, mesh: added <<>> - include "homogenization.f90" ! uses prec, math, IO, numerics - include "CPFEM.f90" ! uses prec, math, IO, numerics, debug, FEsolving, mesh, lattice, constitutive, crystallite +include "IO.f90" ! uses prec +include "numerics.f90" ! uses prec, IO +include "debug.f90" ! uses prec, numerics +include "math.f90" ! uses prec, numerics, debug +include "FEsolving.f90" ! uses prec, IO, debug +include "mesh.f90" ! uses prec, math, IO, FEsolving, debug +include "material.f90" ! uses prec, math, IO, mesh, debug +include "lattice.f90" ! uses prec, math, IO, material, debug +include "constitutive_j2.f90" ! uses prec, math, IO, lattice, material, debug +include "constitutive_phenopowerlaw.f90" ! uses prec, math, IO, lattice, material, debug +include "constitutive_titanmod.f90" ! uses prec, math, IO, lattice, material, debug +include "constitutive_dislotwin.f90" ! uses prec, math, IO, lattice, material, debug +include "constitutive_nonlocal.f90" ! uses prec, math, IO, lattice, material, debug +include "constitutive.f90" ! uses prec, IO, math, lattice, mesh, debug +include "crystallite.f90" ! uses prec, math, IO, numerics, Fesolving, material, mesh, constitutive, debug +include "homogenization_isostrain.f90" ! uses prec, math, IO, debug +include "homogenization_RGC.f90" ! uses prec, math, IO, numerics, mesh, debug +include "homogenization.f90" ! uses prec, math, IO, numerics, debug +include "CPFEM.f90" ! uses prec, math, IO, numerics, debug, FEsolving, mesh, lattice, constitutive, crystallite, debug subroutine UMAT(STRESS,STATEV,DDSDDE,SSE,SPD,SCD,& RPL,DDSDDT,DRPLDE,DRPLDT,STRAN,DSTRAN,& @@ -118,7 +118,7 @@ subroutine UMAT(STRESS,STATEV,DDSDDE,SSE,SPD,SCD,& use math, only: invnrmMandel use debug, only: debug_info, & debug_reset, & - verboseDebugger + debug_verbosity use mesh, only: mesh_FEasCP use CPFEM, only: CPFEM_general,CPFEM_init_done, CPFEM_initAll use homogenization, only: materialpoint_sizeResults, materialpoint_results @@ -144,7 +144,7 @@ subroutine UMAT(STRESS,STATEV,DDSDDE,SSE,SPD,SCD,& real(pReal), dimension(6,6) :: ddsdde_h integer(pInt) computationMode, i, cp_en - if (verboseDebugger .and. noel == 1 .and. npt == 1) then + if (debug_verbosity > 1 .and. noel == 1 .and. npt == 1) then !$OMP CRITICAL (write2out) write(6,*) 'el',noel,'ip',npt write(6,*) 'got kinc as',kinc @@ -232,7 +232,7 @@ subroutine UMAT(STRESS,STATEV,DDSDDE,SSE,SPD,SCD,& theInc = kinc ! record current increment number lastMode = calcMode(npt,cp_en) ! record calculationMode - if ( verboseDebugger ) then + if ( debug_verbosity > 1 ) then !$OMP CRITICAL (write2out) write(6,'(a16,x,i2,x,a,i5,a,i5,x,i5,a)') 'computationMode',computationMode,'(',cp_en,':',noel,npt,')'; call flush(6) !$OMP END CRITICAL (write2out) diff --git a/code/mpie_cpfem_marc.f90 b/code/mpie_cpfem_marc.f90 index f376ec28e..6bb0f9d10 100644 --- a/code/mpie_cpfem_marc.f90 +++ b/code/mpie_cpfem_marc.f90 @@ -100,25 +100,25 @@ end function END MODULE - include "IO.f90" ! uses prec - include "numerics.f90" ! uses prec, IO - include "math.f90" ! uses prec, numerics - include "debug.f90" ! uses prec, numerics - include "FEsolving.f90" ! uses prec, IO - include "mesh.f90" ! uses prec, math, IO, FEsolving - include "material.f90" ! uses prec, math, IO, mesh - include "lattice.f90" ! uses prec, math, IO, material - include "constitutive_j2.f90" ! uses prec, math, IO, lattice, material, debug - include "constitutive_phenopowerlaw.f90" ! uses prec, math, IO, lattice, material, debug - include "constitutive_titanmod.f90" ! uses prec, math, IO, lattice, material, debug - include "constitutive_dislotwin.f90" ! uses prec, math, IO, lattice, material, debug - include "constitutive_nonlocal.f90" ! uses prec, math, IO, lattice, material, debug - include "constitutive.f90" ! uses prec, IO, math, lattice, mesh, debug - include "crystallite.f90" ! uses prec, math, IO, numerics, Fesolving, material, mesh, constitutive - include "homogenization_isostrain.f90" ! uses prec, math, IO - include "homogenization_RGC.f90" ! uses prec, math, IO, numerics, mesh: added <<>> - include "homogenization.f90" ! uses prec, math, IO, numerics - include "CPFEM.f90" ! uses prec, math, IO, numerics, debug, FEsolving, mesh, lattice, constitutive, crystallite +include "IO.f90" ! uses prec +include "numerics.f90" ! uses prec, IO +include "debug.f90" ! uses prec, numerics +include "math.f90" ! uses prec, numerics, debug +include "FEsolving.f90" ! uses prec, IO, debug +include "mesh.f90" ! uses prec, math, IO, FEsolving, debug +include "material.f90" ! uses prec, math, IO, mesh, debug +include "lattice.f90" ! uses prec, math, IO, material, debug +include "constitutive_j2.f90" ! uses prec, math, IO, lattice, material, debug +include "constitutive_phenopowerlaw.f90" ! uses prec, math, IO, lattice, material, debug +include "constitutive_titanmod.f90" ! uses prec, math, IO, lattice, material, debug +include "constitutive_dislotwin.f90" ! uses prec, math, IO, lattice, material, debug +include "constitutive_nonlocal.f90" ! uses prec, math, IO, lattice, material, debug +include "constitutive.f90" ! uses prec, IO, math, lattice, mesh, debug +include "crystallite.f90" ! uses prec, math, IO, numerics, Fesolving, material, mesh, constitutive, debug +include "homogenization_isostrain.f90" ! uses prec, math, IO, debug +include "homogenization_RGC.f90" ! uses prec, math, IO, numerics, mesh, debug +include "homogenization.f90" ! uses prec, math, IO, numerics, debug +include "CPFEM.f90" ! uses prec, math, IO, numerics, debug, FEsolving, mesh, lattice, constitutive, crystallite, debug !******************************************************************** @@ -269,7 +269,8 @@ subroutine hypela2(& lastMode = .false. ! pretend last step was collection calcMode = .false. ! pretend last step was collection !$OMP CRITICAL (write2out) - write (6,'(i6,x,i2,x,a)') n(1),nn,'<< hypela2 >> start of analysis..!'; call flush(6) + write (6,'(a,i6,x,i2)') '<< HYPELA2 >> start of analysis..! ',n(1),nn + call flush(6) !$OMP END CRITICAL (write2out) else if (inc - theInc > 1) then ! >> restart of broken analysis << lastIncConverged = .false. ! no Jacobian backup @@ -277,7 +278,8 @@ subroutine hypela2(& lastMode = .true. ! pretend last step was calculation calcMode = .true. ! pretend last step was calculation !$OMP CRITICAL (write2out) - write (6,'(i6,x,i2,x,a)') n(1),nn,'<< hypela2 >> restart of analysis..!'; call flush(6) + write (6,'(a,i6,x,i2)') '<< HYPELA2 >> restart of analysis..! ',n(1),nn + call flush(6) !$OMP END CRITICAL (write2out) else ! >> just the next inc << lastIncConverged = .true. ! request Jacobian backup @@ -285,7 +287,8 @@ subroutine hypela2(& lastMode = .true. ! assure last step was calculation calcMode = .true. ! assure last step was calculation !$OMP CRITICAL (write2out) - write (6,'(i6,x,i2,x,a)') n(1),nn,'<< hypela2 >> new increment..!'; call flush(6) + write (6,'(a,i6,x,i2)') '<< HYPELA2 >> new increment..! ',n(1),nn + call flush(6) !$OMP END CRITICAL (write2out) endif else if ( timinc < theDelta ) then ! >> cutBack << @@ -293,7 +296,8 @@ subroutine hypela2(& cycleCounter = -1 ! first calc step increments this to cycle = 0 calcMode = .true. ! pretend last step was calculation !$OMP CRITICAL (write2out) - write(6,'(i6,x,i2,x,a)') n(1),nn,'<< hypela2 >> cutback detected..!'; call flush(6) + write(6,'(a,i6,x,i2)') '<< HYPELA2 >> cutback detected..! ',n(1),nn + call flush(6) !$OMP END CRITICAL (write2out) endif ! convergence treatment end