Path: blob/devel/elmerice/Solvers/GetHydrostaticLoads.F90
3203 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: Olivier Gagliardini, Ga¨el Durand, Mondher Chekki25! * Email:26! * Web: http://elmerice.elmerfem.org27! *28! * Original Date:29! *30! *****************************************************************************31!> Computes nodes surface loads from surface pressure32SUBROUTINE GetHydrostaticLoads( Model,Solver,dt,TransientSimulation )3334!------------------------------------------------------------------------------35!******************************************************************************36!37!38! TODO: switch y and z as DIM=339!40! ARGUMENTS:41!42! TYPE(Model_t) :: Model,43! INPUT: All model information (mesh, materials, BCs, etc...)44!45! TYPE(Solver_t) :: Solver46! INPUT: Linear & nonlinear equation solver options47!48! REAL(KIND=dp) :: dt,49! INPUT: Timestep size for time dependent simulations50!51! LOGICAL :: TransientSimulation52! INPUT: Steady state or transient simulation53!54!******************************************************************************55USE DefUtils56USE ElmerIceUtils5758IMPLICIT NONE59!------------------------------------------------------------------------------60TYPE(Solver_t) :: Solver61TYPE(Model_t) :: Model6263REAL(KIND=dp) :: dt64LOGICAL :: TransientSimulation65!------------------------------------------------------------------------------66! Local variables67!------------------------------------------------------------------------------68TYPE(Element_t),POINTER :: Element69TYPE(ValueList_t), POINTER :: BC70TYPE(Variable_t), POINTER :: PointerToVariable71TYPE(Solver_t), POINTER :: PointerToSolver72TYPE(Nodes_t), SAVE :: Nodes73TYPE(GaussIntegrationPoints_t) :: IP7475LOGICAL :: AllocationsDone = .FALSE., GotIt, stat, Active7677INTEGER :: i, j, n, m, t, p, Nn, istat, DIM, jdim78INTEGER, POINTER :: Permutation(:)7980REAL(KIND=dp), POINTER :: VariableValues(:)81REAL(KIND=dp) :: Norm, Normal(3), PwVector(3), pwi, s82REAL(KIND=dp) :: detJ8384REAL(KIND=dp), ALLOCATABLE :: pwt(:), Basis(:), dBasisdx(:,:), &85ddBasisddx(:,:,:)8687CHARACTER(LEN=MAX_NAME_LEN) :: VarName88CHARACTER(LEN=MAX_NAME_LEN),PARAMETER :: SolverName='GetHydrostaticLoads'8990SAVE AllocationsDone, DIM, pwt91SAVE Basis, dBasisdx, ddBasisddx9293!------------------------------------------------------------------------------9495PointerToVariable => Solver % Variable96IF (.NOT.ASSOCIATED(PointerToVariable)) &97CALL FATAL(SolverName,"Variable not associated")98Permutation => PointerToVariable % Perm99VariableValues => PointerToVariable % Values100101Active = ANY(Permutation > 0)102103!--------------------------------------------------------------104!Allocate some permanent storage, this is done first time only:105!--------------------------------------------------------------106107IF ( (.NOT. AllocationsDone) .OR. Solver % MeshChanged ) THEN108DIM = CoordinateSystemDimension()109n = Solver % Mesh % MaxElementNodes ! just big enough for elemental arrays110m = Model % Mesh % NumberOfNodes111IF (AllocationsDone) DEALLOCATE(pwt, Basis, dBasisdx, ddBasisddx)112113ALLOCATE(pwt(n), Basis(n), dBasisdx(n,3), ddBasisddx(n,3,3), STAT=istat )114115IF ( istat /= 0 ) THEN116CALL FATAL( SolverName, 'Memory allocation error.' )117END IF118119AllocationsDone = .TRUE.120CALL INFO( SolverName, 'Memory allocation done.',Level=1 )121122END IF123124!--------------------------------------------125! Calculate the water force for each elements126!--------------------------------------------127128VariableValues = 0.0_dp129130DO t = Model % Mesh % NumberOfBulkElements+1,&131Model % Mesh % NumberOfBulkElements + Model % Mesh % NumberOfBoundaryElements132Element => Model % Mesh % Elements(t)133IF (.NOT.ASSOCIATED(Element)) THEN134WRITE(Message,*) 'Element no. ', t,' not associated'135CALL FATAL(SolverName,Message)136END IF137Model % CurrentElement => Element138139IF (ParEnv % myPe .NE. Element % partIndex) CYCLE140n = GetElementNOFNodes( Element )141142!Does this element contribute to any basal nodes?143IF(.NOT. ANY(Permutation(Element % NodeIndexes(1:n)) > 0)) CYCLE144145BC => GetBC( Element )146IF (.NOT.ASSOCIATED(BC)) CYCLE147148pwt(1:n) = -1.0 * ListGetReal(BC, 'External Pressure', n, &149Element % NodeIndexes , GotIt)150151!Is there an external pressure to consider?152IF(.NOT. GotIt) CYCLE153IF(ALL(pwt(1:n) == 0.0)) CYCLE154155! Integration156!157CALL GetElementNodes( Nodes, Element )158IP = GaussPoints( Element )159DO p = 1, IP % n160161stat = ElementInfo( Element, Nodes, IP % U(p), IP % V(p), &162IP % W(p), detJ, Basis, dBasisdx, ddBasisddx, .FALSE.)163s = detJ * IP % S(p)164165Normal = NormalVector( Element, Nodes, IP % U(p), IP % V(p), .TRUE.)166!167! Value of pwt at integration point168!169pwi = SUM(pwt(1:n)*Basis(1:n))170!171! Compute pw_x, pw_y, pw_z172!173PwVector(1:DIM) = pwi * Normal(1:DIM)174175DO i = 1, n176Nn = Permutation(Element % NodeIndexes(i))177IF(Nn <= 0) CYCLE178DO j = 1, DIM179VariableValues(DIM*(Nn-1)+j) = VariableValues(DIM*(Nn-1)+j) + PwVector(j) * s * Basis(i)180END DO181END DO182183END DO184185END DO186187IF(Active .NEQV. ASSOCIATED(Solver % Matrix)) CALL Fatal(SolverName, &188"Inconsistency between allocation of matrix and number of active nodes")189190IF(Active) THEN191DO jdim=1, DIM192IF (DIM > 1) THEN193VarName=ComponentNameStr( Solver % Variable % Name, jdim )194ELSE195VarName=GetVarName(Solver % Variable)196ENDIF197IF (jdim .eq. 1 ) THEN198IF ( ParEnv % PEs >1 ) CALL ParallelSumVector( Solver % Matrix, VariableValues)199END IF200!------------------------------------------------------------------------------201! Update Periodic Nodes202!------------------------------------------------------------------------------203CALL UpdatePeriodicNodes(Model, Solver, VarName, PointerToVariable, jdim)204ENDDO205END IF206207CALL INFO(SolverName, 'End', level=3)208209!------------------------------------------------------------------------------210END SUBROUTINE GetHydrostaticLoads211!------------------------------------------------------------------------------212213214215216217