Path: blob/devel/elmerice/Utils/PorousMaterialModels.F90
3203 views
!/*****************************************************************************/1! *2! * Elmer, A Finite Element Software for Multiphysical Problems3! *4! * Copyright 1st April 1995 - , CSC - IT Center for Science Ltd., Finland5! *6! * This library is free software; you can redistribute it and/or7! * modify it under the terms of the GNU Lesser General Public8! * License as published by the Free Software Foundation; either9! * version 2.1 of the License, or (at your option) any later version.10! *11! * This library is distributed in the hope that it will be useful,12! * but WITHOUT ANY WARRANTY; without even the implied warranty of13! * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU14! * Lesser General Public License for more details.15! *16! * You should have received a copy of the GNU Lesser General Public17! * License along with this library (in file ../LGPL-2.1); if not, write18! * to the Free Software Foundation, Inc., 51 Franklin Street,19! * Fifth Floor, Boston, MA 02110-1301 USA20! *21! *****************************************************************************/22!23!/******************************************************************************24! *25! * Authors: Olivier Gagliardini and Julien Brondex26! * Email: [email protected]27! * [email protected]28! *29! * Web: http://elmerice.elmerfem.org30! *31! * Original Date: January 202432! *33! ******************************************************************************/34!--------------------------------------------------------------------------------35!> Module containing utility routines for the Porous Solver36!--------------------------------------------------------------------------------3738MODULE PorousMaterialModels3940USE DefUtils4142IMPLICIT NONE4344CONTAINS454647!-------------------------------------------------------------------------------48!> Function a(D) and b(D) from Gagliardini and Meyssonier, 1997.49!> modified to fulfill the condition 3x a(D) >= 2x b(D) for D > 0.150!> for n=3 only51!-------------------------------------------------------------------------------5253!> Function a (Olivier Gagliardini)54FUNCTION ParameterA ( D ) RESULT(a)55USE types56USE CoordinateSystems57USE SolverUtils58USE ElementDescription59USE DefUtils60IMPLICIT NONE61REAL(KIND=dp) :: a, D, DD6263IF (D > 0.99_dp ) THEN64a = 1.0_dp6566ELSE IF (D <= 0.81) THEN67DD = D68IF (D < 0.4 ) DD = 0.4_dp69a = EXP( 13.22240_dp - 15.78652_dp * DD )7071ELSE72a = 1.0_dp + 2.0/3.0 * (1.0_dp - D)73a = a / ( D**1.5 )74END IF75END FUNCTION ParameterA767778!> Function b (Olivier Gagliardini)79FUNCTION ParameterB ( D ) RESULT(b)80USE types81USE CoordinateSystems82USE SolverUtils83USE ElementDescription84USE DefUtils85IMPLICIT NONE86REAL(KIND=dp) :: b, D, DD8788IF (D > 0.99_dp) THEN89b = 0.0_dp9091ELSE IF (D <= 0.81) THEN92DD = D93IF (D < 0.4 ) DD = 0.4_dp94b = EXP( 15.09371_dp - 20.46489_dp * DD )9596ELSE97b = (1.0_dp - D)**(1.0/3.0)98b = 3.0/4.0 * ( b / (3.0 * (1 - b)) )**1.599100END IF101END FUNCTION ParameterB102103!------------------------------------------------------------------------------104!> Returns effective viscosity for Porous Solver (Julien Brondex)105!------------------------------------------------------------------------------106FUNCTION PorousEffectiveViscosity( Fluidity, Density, SR, Em, Element, &107Nodes, n, nd, u, v, w, LocalIP ) RESULT(mu)108!------------------------------------------------------------------------------109110REAL(KIND=dp) :: Fluidity, Density, u, v, w, eta, Kcp, mu(2)111REAL(KIND=dp) :: SR(:,:)112TYPE(Nodes_t) :: Nodes113INTEGER :: n,nd114INTEGER, OPTIONAL :: LocalIP115TYPE(Element_t),POINTER :: Element116117!------------------------------------------------------------------------------118TYPE(ValueList_t), POINTER :: Material119REAL(KIND=dp) :: Wn, MinSRInvariant, fa, fb, ss, nn, Em120121INTEGER :: i, j122INTEGER :: body_id123INTEGER :: old_body = -1124125LOGICAL :: GotIt126127SAVE :: old_body, Wn, MinSRInvariant128129Material => GetMaterial(Element)130131! Get uniform rheological parameters only once per body to save computational time132!-------------------------------------------------------------------------------------133body_id = Element % BodyId134IF (body_id /= old_body) Then135old_body = body_id136! Get flow law exponent137Wn = GetConstReal( Material , 'Powerlaw Exponent', GotIt )138IF (.NOT.GotIt) THEN139CALL INFO('ComputeDevStress', 'Variable Powerlaw Exponent not found. &140& Setting to 1.0', Level = 20)141Wn = 1.0142ELSE143WRITE(Message,'(A,F10.4)') 'Powerlaw Exponent = ', Wn144CALL INFO('ComputeDevStress', Message, Level = 20)145END IF146! Get the Minimum value of the Effective Strain rate147MinSRInvariant = 100.0*AEPS148IF ( Wn > 1.0 ) THEN149MinSRInvariant = GetConstReal( Material, 'Min Second Invariant', GotIt )150IF (.NOT.GotIt) THEN151WRITE(Message,'(A)') 'Variable Min Second Invariant not &152&found. Setting to 100.0*AEPS )'153CALL INFO('ComputeDevStress', Message, Level = 20)154ELSE155WRITE(Message,'(A,F14.8)') 'Min Second Invariant = ', MinSRInvariant156CALL INFO('ComputeDevStress', Message, Level = 20)157END IF158END IF159END IF160161! Get non-uniform rheological parameters for Porous at current point162!-------------------------------------------------------------------------------------163! Evaluate parameterized functions a and b from Density interpolated at current point164fa = ParameterA(Density)165fb = ParameterB(Density)166167! Calculate Strain Rate invariant as E_D^2 = gamma_e^2/fa + E_m^2/fb168ss = 1.0_dp !case linear by default -> ss = E_D^((1-n)/n) -> ss = 1 if n = 1169IF ( Wn > 1.0 ) THEN !case non-linear170ss = 0.0_dp !Initialize ss171DO i = 1, 3172DO j = 1, 3173ss = ss + SR(i,j)**2 ! Gamma_e^2/2 = e_ij e_ij174END DO175END DO176ss = 2.0*ss / fa !Gamma_e^2/fa177IF ( fb > 1.0e-8 ) ss = ss + Em**2 / fb !Full E_D^2 = gamma_e^2/fa + E_m^2/fb178179nn =(1.0 - Wn)/Wn !nn = (1 -n)/n180181ss = SQRT(ss)! Full E_D182IF (ss < MinSRInvariant ) ss = MinSRInvariant !Invariant not less than prescribed min183ss = ss**nn ! ss = E_D^((1-n)/n)184END IF185186! Compute effective viscosity at current point187!-------------------------------------------------------------------------------------188eta = ss / ( fa * Fluidity ** (1.0 / Wn ) )189! Compute compressibility parameter at current point190!-------------------------------------------------------------------------------------191Kcp = fb * Fluidity ** (1.0 / Wn ) / ss192! Return output array as [eta, Kcp]193!-------------------------------------------------------------------------------------194mu = [ eta, Kcp ]195!------------------------------------------------------------------------------196END FUNCTION PorousEffectiveViscosity197!------------------------------------------------------------------------------198199END MODULE PorousMaterialModels200201202