Path: blob/devel/elmerice/UserFunctions/USF_CouplingGlaDS_SSA.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 Gagliardini25! * Email:26! * Web: http://elmerice.elmerfem.org27! *28! * Original Date:29! * 2014/02/20 - Start wrinting User functions needed for the coupling between30! * the hydrology model (GlaDS) and the ice flow (SSA).31! *****************************************************************************32!> USF_CouplingGlaDS_SSA.F9033!>34!> HorizontalVelo returns the horizontal velocity (positive)35!>36FUNCTION HorizontalVelo (Model, nodenumber, x) RESULT(ub)37USE types38USE CoordinateSystems39USE SolverUtils40USE ElementDescription41USE DefUtils42IMPLICIT NONE43TYPE(Model_t) :: Model44REAL (KIND=dp) :: x, ub45INTEGER :: nodenumber4647TYPE(ValueList_t), POINTER :: Constants48TYPE(Variable_t), POINTER :: FlowVariable, Gravity49REAL(KIND=dp), POINTER :: FlowValues(:)50INTEGER, POINTER :: FlowPerm(:)51INTEGER :: DIM, i52REAL (KIND=dp) :: velo(2)53LOGICAL :: GotIt5455CHARACTER(LEN=MAX_NAME_LEN) :: USFName5657USFName = 'HorizontalVelo'58DIM = CoordinateSystemDimension()5960! Get the variables to compute ub : the fields velocity 1 and 261FlowVariable => VariableGet( Model % Variables, 'ssavelocity' )6263IF ( ASSOCIATED( FlowVariable ) ) THEN64FlowPerm => FlowVariable % Perm65FlowValues => FlowVariable % Values66ELSE67CALL FATAL(USFName, 'Need SSA Solver, variable >SSAVelocity< not associated !!!')68END IF6970velo = 0.0_dp71DO i=1, DIM72velo(i) = FlowValues( (DIM)*(FlowPerm(Nodenumber)-1) + i )73END DO74ub = SQRT(velo(1)**2+velo(2)**2)75END FUNCTION HorizontalVelo7677!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!78!> Function OverburdenPressure return the cryostatic pressure79!>80FUNCTION OverburdenPressure (Model, nodenumber, x) RESULT(IcePress)81USE types82USE CoordinateSystems83USE SolverUtils84USE ElementDescription85USE DefUtils86IMPLICIT NONE87TYPE(Model_t) :: Model88REAL (KIND=dp) :: x, IcePress89INTEGER :: nodenumber90TYPE(ValueList_t), POINTER :: Constants91TYPE(Variable_t), POINTER :: ZbVariable, ZsVariable92REAL(KIND=dp), POINTER :: ZbValues(:), ZsValues(:)93INTEGER, POINTER :: ZbPerm(:), ZsPerm(:)94INTEGER :: DIM, i95REAL (KIND=dp) :: zb, zs, gravity, rhoi96LOGICAL :: GotIt9798CHARACTER(LEN=MAX_NAME_LEN) :: USFName99100USFName = 'OverburdenPressure'101DIM = CoordinateSystemDimension()102103! Get the constants needed to compute the overburden ice pressure104Constants => GetConstants()105gravity = GetConstReal( Constants, 'Gravity Norm', GotIt )106IF (.NOT.GotIt) THEN107WRITE(Message,'(a)')'Keyword >Gravity Norm< not found in Constant section'108CALL FATAL(USFName, Message)109END IF110rhoi = GetConstReal ( Constants, 'Ice Density', GotIt )111IF (.NOT.GotIt) THEN112WRITE(Message,'(a)')'Keyword >Ice Density< not found in Constant section'113CALL FATAL(USFName, Message)114END IF115116! Get the variables to compute IcePress117ZbVariable => VariableGet( Model % Variables, 'zb' )118IF ( ASSOCIATED( ZbVariable ) ) THEN119ZbPerm => ZbVariable % Perm120ZbValues => ZbVariable % Values121ELSE122CALL FATAL(USFName, 'Variable >Zb< not associated !!!')123END IF124125! Get the variables to compute IcePress126ZsVariable => VariableGet( Model % Variables, 'zs' )127IF ( ASSOCIATED( ZsVariable ) ) THEN128ZsPerm => ZsVariable % Perm129ZsValues => ZsVariable % Values130ELSE131CALL FATAL(USFName, 'Variable >Zs< not associated !!!')132END IF133zb = 0.0_dp134zs = 0.0_dp135136zb = ZbValues( ZbPerm(Nodenumber))137zs = ZsValues( ZsPerm(Nodenumber))138IcePress = rhoi*gravity*(zs-zb)139IF (IcePress .LT. 0) THEN140print*, "Ice pressure value :", IcePress141END IF142END FUNCTION OverburdenPressure143144145