Path: blob/devel/elmerice/Solvers/ComputeEigenValues.F90
3204 views
!/*****************************************************************************/1! *2! * Elmer/Ice, a glaciological add-on to Elmer3! * http://elmerice.elmerfem.org4! *5! *6! * This program is free software; you can redistribute it and/or7! * modify it under the terms of the GNU General Public License8! * as published by the Free Software Foundation; either version 29! * of the License, or (at your option) any later version.10! *11! * This program 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 the14! * GNU General Public License for more details.15! *16! * You should have received a copy of the GNU General Public License17! * along with this program (in file fem/GPL-2); if not, write to the18! * Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor,19! * Boston, MA 02110-1301, USA.20! *21! *****************************************************************************/22! ******************************************************************************23! *24! * Authors: Fabien / OG25! * Email:26! * Web: http://elmerice.elmerfem.org27! *28! * Original Date: 13/10/05 from version 1.529! *30! *****************************************************************************/31!------------------------------------------------------------------------------32RECURSIVE SUBROUTINE ComputeEigenValues( Model,Solver,dt,TransientSimulation )33!------------------------------------------------------------------------------3435USE DefUtils3637IMPLICIT NONE3839!------------------------------------------------------------------------------40!******************************************************************************41!42! ARGUMENTS:43!44! TYPE(Model_t) :: Model,45! INPUT: All model information (mesh,materials,BCs,etc...)46!47! TYPE(Solver_t) :: Solver48! INPUT: Linear equation solver options49!50! REAL(KIND=dp) :: dt,51! INPUT: Timestep size for time dependent simulations (NOTE: Not used52! currently)53!54!******************************************************************************5556TYPE(Model_t) :: Model57TYPE(Solver_t), TARGET :: Solver5859LOGICAL :: TransientSimulation60REAL(KIND=dp) :: dt61!------------------------------------------------------------------------------62! Local variables63!------------------------------------------------------------------------------64656667INTEGER :: dim, StressDOFs68TYPE(Variable_t), POINTER :: StressSol,EigenSol,EigenV1,EigenV2,EigenV369REAL(KIND=dp), POINTER :: Stress(:),Eigen(:)70INTEGER, POINTER :: StressPerm(:),EigenPerm(:)7172REAL(KIND=dp),dimension(3,3) :: localM,EigenVec73REAL(KIND=dp),dimension(3) :: EigValues, EI, ki74REAL(KIND=dp) :: WORK(24),Dumy(1)75Real(KIND=dp) :: a76INTEGER :: i, j, t, ordre(3),infor77LOGICAL :: GotIt,UnFoundFatal=.TRUE.78CHARACTER(LEN=MAX_NAME_LEN) :: TensorVarName, EigenVarName798081!------------------------------------------------------------------------------82! Get variables needed for solution83!------------------------------------------------------------------------------84dim = CoordinateSystemDimension()8586TensorVarName = GetString( Solver % Values, 'Tensor Variable Name', GotIt )87IF (.NOT.Gotit) TensorVarName = 'Stress'88StressSol => VariableGet( Solver % Mesh % Variables, TensorVarName )89StressPerm => StressSol % Perm90StressDOFs = StressSol % DOFs91Stress => StressSol % Values9293! Eigen Values (dimension 3)94EigenVarName = GetString( Solver % Values, 'EigenValue Variable Name', GotIt )95IF (.NOT.Gotit) EigenVarName = 'EigenStress'96EigenSol => VariableGet( Solver % Mesh % Variables, EigenVarName,UnFoundFatal=UnFoundFatal)97EigenPerm => EigenSol % Perm98Eigen => EigenSol % Values99100! Eigen Vector (dimension 3)101EigenV1 => VariableGet( Solver % Mesh % Variables, 'EigenVector1' )102EigenV2 => VariableGet( Solver % Mesh % Variables, 'EigenVector2' )103EigenV3 => VariableGet( Solver % Mesh % Variables, 'EigenVector3' )104105106Do t=1,Solver % Mesh % NumberOfNodes107108! the Stress components [Sxx, Syy, Szz, Sxy, Syz, Szx]109localM=0.0_dp110localM(1,1)=Stress( StressDOFs * (StressPerm(t) - 1 ) + 1)111localM(2,2)=Stress( StressDOFs * (StressPerm(t) - 1 ) + 2)112localM(3,3)=Stress( StressDOFs * (StressPerm(t) - 1 ) + 3)113localM(1,2)=Stress( StressDOFs * (StressPerm(t) - 1 ) + 4)114localM(2,1)=localM(1,2)115if (dim.eq.3) then116localM(2,3)=Stress( StressDOFs * (StressPerm(t) - 1 ) + 5)117localM(1,3)=Stress( StressDOFs * (StressPerm(t) - 1 ) + 6)118localM(3,2)=localM(2,3)119localM(3,1)=localM(1,3)120end if121122! Compute EigenValues using lapack DGEEV subroutine123CALL DGEEV('N','V',3,localM,3,EigValues,EI,Dumy,1,EigenVec,3,Work,24,infor )124IF (infor.ne.0) &125CALL FATAL('Compute EigenValues', 'Failed to compute EigenValues')126localM(1:3,1:3)=EigenVec(1:3,1:3)127! Ordered value Ev1 < Ev2 < Ev3128129Do i=1,3130ki(i)=EigValues(i)131ordre(i)=i132End Do133Do j=2,3134a=ki(j)135Do i=j-1,1,-1136If (ki(i).LE.a) Goto 20137ki(i+1)=ki(i)138ordre(i+1)=ordre(i)139End Do14020 Continue141ki(i+1)=a142ordre(i+1)=j143End Do144145Eigen( 3 * ( EigenPerm(t) - 1) + 1) = EigValues(ordre(1))146Eigen( 3 * ( EigenPerm(t) - 1) + 2) = EigValues(ordre(2))147Eigen( 3 * ( EigenPerm(t) - 1) + 3) = EigValues(ordre(3))148149If (associated(EigenV1)) then150EigenV1 % Values( 3 * (EigenV1 % Perm(t) - 1) + 1 ) = localM(ordre(1),1)151EigenV1 % Values( 3 * (EigenV1 % Perm(t) - 1) + 2 ) = localM(ordre(1),2)152EigenV1 % Values( 3 * (EigenV1 % Perm(t) - 1) + 3 ) = localM(ordre(1),3)153endif154If (associated(EigenV2)) then155EigenV2 % Values( 3 * (EigenV2 % Perm(t) - 1) + 1 ) = localM(ordre(2),1)156EigenV2 % Values( 3 * (EigenV2 % Perm(t) - 1) + 2 ) = localM(ordre(2),2)157EigenV2 % Values( 3 * (EigenV2 % Perm(t) - 1) + 3 ) = localM(ordre(2),3)158endif159If (associated(EigenV3)) then160EigenV3 % Values( 3 * (EigenV3 % Perm(t) - 1) + 1 ) = localM(ordre(3),1)161EigenV3 % Values( 3 * (EigenV3 % Perm(t) - 1) + 2 ) = localM(ordre(3),2)162EigenV3 % Values( 3 * (EigenV3 % Perm(t) - 1) + 3 ) = localM(ordre(3),3)163Endif164165End do166167!------------------------------------------------------------------------------168END SUBROUTINE ComputeEigenValues169!------------------------------------------------------------------------------170171172173