Path: blob/devel/elmerice/UserFunctions/USF_Damage.F90
3196 views
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!1! USF_Damage.f902! Last modif : 12 December 20143! Computes the evolution of damage and computes the Enhancement factor of the Glen's law4! as a function of damage evolution5!6!7! (1) Enhancement Factor8! Need some inputs in the sif file.9! Parameters:10! Glen Exponent11!12!13! (2) SourceDamage14! Need some inputs in the sif file.15! Parameters:16! Damage Enhancement Factor17! Damage Parameter sigmath18!19!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!2021!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!22!23! EnhancementFactor24!25!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!2627FUNCTION EnhancementFactor ( Model, nodenumber, D) RESULT(E)28USE types29USE CoordinateSystems30USE SolverUtils31USE ElementDescription32USE DefUtils33IMPLICIT NONE34TYPE(Model_t) :: Model35TYPE(ValueList_t), POINTER :: Material36TYPE(Solver_t), TARGET :: Solver37REAL(KIND=dp) :: D, E, n38INTEGER :: nodenumber39LOGICAL :: FirstTime=.TRUE., GotIt4041SAVE FirstTime, n4243IF (FirstTime) THEN44FirstTime = .False.4546Material => GetMaterial()47n = GetConstReal( Material, 'Glen Exponent', GotIt )48IF (.NOT.GotIt) THEN49WRITE(Message,'(A)') 'Variable Glen Exponent not found. &50&Setting to 3.0'51CALL INFO('Damage EnhancementFactor', Message, level=2)52n = 3.0_dp53ELSE54WRITE(Message,'(A,F10.4)') 'n = ', n55CALL INFO('Damage EnhancementFactor', Message, level=2)56END IF57END IF5859E = (1.0 - D)**(-n)6061! write(*,*) D62! write(*,*)'E', E63END FUNCTION EnhancementFactor646566!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!67!68! SourceDamage69!70!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!7172FUNCTION SourceDamage (Model, nodenumber, D) RESULT(Source)737475USE types76USE CoordinateSystems77USE SolverUtils78USE ElementDescription79USE DefUtils80USE GeneralUtils81IMPLICIT NONE82TYPE(Model_t) :: Model83REAL (KIND=dp) :: D, Source84INTEGER :: nodenumber8586TYPE(Solver_t):: Solver87TYPE(ValueList_t), POINTER :: Material, Constants88TYPE(Variable_t), POINTER :: StressVariable, FlowVariable, ChiVariable, PSeaDVariable89REAL(KIND=dp), POINTER :: StressValues(:), FlowValues(:), ChiValues(:), PSeaDValues(:)90INTEGER, POINTER :: StressPerm(:), FlowPerm(:), ChiPerm(:), PSeaDPerm(:)9192INTEGER :: Ind(3,3), DIM, i, j, indice(3), infor93REAL (KIND=dp) :: Sig(3,3), SigDev(3,3), EigVect(3,3), EigValues(3),tmp94REAL (KIND=dp) :: SigmaI, SigmaII, Chi, B, sigmath, pwater95REAL (KIND=DP) :: EI(3),Dumy(1),Work(24), sigmath_var, stress_threshold96REAL (KIND=DP) :: u, v, nbrPi, s97LOGICAL :: GotIt, FirstTime = .TRUE., Cauchy, UnFoundFatal=.TRUE.98CHARACTER*20 :: USF_Name='SourceDamage'99100101SAVE :: Ind, DIM, sigmath, B102SAVE :: FirstTime, Cauchy103104105IF (FirstTime) THEN106FirstTime = .FALSE.107DIM = CoordinateSystemDimension()108109DO i=1, 3110Ind(i,i) = i111END DO112Ind(1,2) = 4113Ind(2,1) = 4114Ind(2,3) = 5115Ind(3,2) = 5116Ind(3,1) = 6117Ind(1,3) = 6118119Material => GetMaterial()120!Read the coefficients B and sigmath121122B = GetConstReal( Material, 'Damage Enhancement Factor', GotIt )123IF (.NOT.GotIt) THEN124CALL FATAL('Damage Source', 'Damage Enhancement Factor B not Found')125ELSE126WRITE(Message,'(A,F10.4)') 'Damage Enhancement Factor = ', B127CALL INFO('Damage Source', Message, level=2)128ENDIF129130sigmath = GetConstReal( Material, 'Damage Parameter sigmath', GotIt )131IF (.NOT.GotIt) THEN132CALL FATAL('Damage Source', 'Damage Parameter Sigmath not Found')133ELSE134WRITE(Message,'(A,F10.4)') 'Damage Parameter sigmath = ', sigmath135CALL INFO('Damage Source', Message, level=2)136ENDIF137138! Cauchy or deviatoric stresses ?139Cauchy = ListGetLogical( Material , 'Cauchy', Gotit )140WRITE(Message,'(A,L1)') 'Cauchy stress tensor computed ? ', Cauchy141CALL INFO('Damage Source', Message, level=2)142END IF ! FirstTime143144145! Get the Stress146StressVariable => VariableGet( Model % Variables, 'Stress',UnFoundFatal=UnFoundFatal)147StressPerm => StressVariable % Perm148StressValues => StressVariable % Values149150! Get Chi variable (positive where damage increases)151ChiVariable => VariableGet( Model % Variables, 'Chi',UnFoundFatal=UnFoundFatal)152ChiPerm => ChiVariable % Perm153ChiValues => ChiVariable % Values154155! Get the Sea Damage Pressure156PSeaDVariable => VariableGet( Model % Variables, 'PSeaD' )157IF ( ASSOCIATED( PSeaDVariable ) ) THEN158PSeaDPerm => PSeaDVariable % Perm159PSeaDValues => PSeaDVariable % Values160ELSE161CALL WARN('Damage Source', 'PSeaD not associated, basal pressure not taken into account in damage formation' )162CALL WARN('Damage Source', 'Taking default value PSeaD=0.0')163END IF164165! Get the variables to compute the hydrostatic pressure166FlowVariable => VariableGet( Model % Variables, 'Flow Solution',UnFoundFatal=UnFoundFatal)167FlowPerm => FlowVariable % Perm168FlowValues => FlowVariable % Values169170Sig = 0.0171DO i=1, DIM172DO j= 1, DIM173Sig(i,j) = &174StressValues( 2*DIM *(StressPerm(Nodenumber)-1) + Ind(i,j) )175END DO176END DO177IF (DIM==2) Sig(3,3) = StressValues( 2*DIM *(StressPerm(Nodenumber)-1) + Ind(3,3))178179! S = sigma + p180! Need Cauchy Stress and Deviatoric Stress181IF (.NOT.Cauchy) THEN ! If Deviatoric Stress is computed, then, get the182! Cauchy Stress183SigDev = Sig184DO i=1,3185Sig(i,i) = SigDev(i,i) - FlowValues((DIM+1)*FlowPerm(Nodenumber))186END DO187ELSE ! If the Cauchy Stress is computed, then get the Deviatoric Stress188DO i=1,3189SigDev(i,i) = Sig(i,i) + FlowValues((DIM+1)*FlowPerm(Nodenumber))190!write(*,*)Sig(i,1), Sig(i,2), Sig(i,3)191END DO192END IF193194195! Compute the principal stresses:196197! Get the principal stresses198CALL DGEEV('N','N',3,Sig,3,EigValues,EI,Dumy,1,Dumy,1,Work,24,infor )199IF (infor.ne.0) &200CALL FATAL('Compute EigenValues', 'Failed to compute EigenValues')201202! Get the eigenvectors (if necessary)203CALL DGEEV('N','V',3,Sig,3,EigValues,EI,Dumy,1,EigVect,3,Work,24,infor )204IF (infor.ne.0) &205CALL FATAL('Compute EigenVectors', 'Failed to compute EigenVectors')206207indice = (/(i,i=1,3)/)208CALL sortd(3,EigValues,indice)209210SigmaI = EigValues(3)211SigmaII = EigValues(2)212213!SigmaI = MAXVAL(EigValues)214!write(*,*)'SigI',SigmaI,EigValues215nbrPi = 3.141592_dp216217u = EvenRandom()218v = EvenRandom()219220! Determination of the stress threshold221Constants => GetConstants()222s = GetConstReal( Constants, 'Dev Tensile Strength Modifier', GotIt)223IF (.NOT.GotIt) THEN224CALL FATAL('USF_Damage','No "Dev tensile strength modifier" given, set &225to 0.05')226END IF227228! Get a normal distribution of mean 0 and std dev "s" using two random numbers229! "u" and "v"230sigmath_var = ABS(0+s*SQRT(-2.0_dp*LOG((1.0_dp-u)))*COS(2.0_dp*nbrPi*v))231232stress_threshold = sigmath*(1+sigmath_var)233234! Get the Sea pressure at the node235236IF ( ASSOCIATED( PSeaDVariable ) ) THEN237pwater = PseaDValues ( PSeaDPerm (nodenumber) )238ELSE239pwater = 0.0_dp240END IF241242! Damage Criterion243Chi = 1.0_dp / (1.0_dp - D) * (SigmaI + pwater) - stress_threshold244245! Save Chi in ChiVariable246ChiValues(ChiPerm(nodenumber)) = Chi247248! Advection-Reaction Source term :249Source = B * MAX(Chi,0.0_dp)250251END FUNCTION SourceDamage252253254