!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!1! USF_Haf.f902! Calculates height above floatation at the lower boundary based on ice thickness, density,3! lower surface height and grounded mask (latter is optional).4!5! Call this function from the lower boundary condition (BC) in the sif like this:6! Haf = real coord 37! Real Procedure "ElmerIceUSF" "Calculate_Haf"8! (where coord 3 is NOT a dummy argument - we actually use this as height of current node9! relative to sea level!)10!11! Relevant parameters can be given in the lower BC like this:12! Haf GroundedMask = String GroundedMask13! Haf Thickness = String Depth14! Haf rhoRatio = Variable Coordinate 315! Real MATC "1.0 * rhoi/rhow"16!17! The second and third are required, the first is optional. The third, rhoRatio, assumes that18! rhow and rhoi are defined at the start of the sif, e.g.19! $yearinsec = 365.25*24*60*6020! $rhoi = 910.0/(1.0e6*yearinsec^2)21! $rhow = 1000.0/(1.0e6*yearinsec^2)22!23! Note that if depth is a variable giving the vertical distance of each node from the upper24! surface then it is equal to the ice thickness when taken at the lower surface.25!26!27! In order to calculate volume above floatation, this user function can be used in conjunction28! with the SaveScalars Solver like this:29!30! Solver x31! Equation = SaveScalars32! Procedure = "SaveData" "SaveScalars"33! Filename = f.dat34! Variable 1 = Haf35! Operator 1 = Int36! Variable 2 = dummy37! Operator 2 = Area38! Exported Variable 1 = Haf39! End40!41! The SaveScalars solver needs, in the lower surface boundary condition:42!43! Save Scalars = True44!4546!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!4748FUNCTION Calculate_Haf ( Model, nodenumber, nodeHeight) RESULT(Haf)4950USE types51USE DefUtils5253IMPLICIT NONE5455TYPE(Model_t) :: Model56REAL(KIND=dp) :: nodeHeight57INTEGER :: nodenumber5859REAL(KIND=dp) :: Haf6061REAL(KIND=dp) :: rhoRatio, Thickness62LOGICAL :: FirstTime=.TRUE., GotIt, UseGroundedMask, UnFoundFatal=.TRUE.6364CHARACTER(LEN=MAX_NAME_LEN) :: FunctionName = "USF_Haf", thickName, GroundedMaskName65TYPE(Variable_t), POINTER :: GroundedMask, thick66TYPE(ValueList_t), POINTER :: BC6768SAVE FirstTime, UseGroundedMask, UnFoundFatal, thickName, GroundedMaskName6970IF (FirstTime) THEN71FirstTime = .False.7273BC => GetBC(Model % CurrentElement)74IF (.NOT.ASSOCIATED(BC))THEN75CALL Fatal(FunctionName, 'No BC Found')76END IF7778GroundedMaskName = GetString( BC, 'Haf GroundedMask', GotIt )79IF (Gotit) THEN80UseGroundedMask = .TRUE.81ELSE82UseGroundedMask = .FALSE.83END IF8485thickName = GetString( BC, 'Haf Thickness', GotIt )86IF (.NOT.Gotit) THEN87CALL Fatal(FunctionName, 'Can not find >Haf Thickness< in BC')88END IF8990rhoRatio = GetConstReal( BC, 'Haf rhoRatio', GotIt )91IF (.NOT.Gotit) THEN92CALL Fatal(FunctionName, 'Can not find >Haf rhoRatio< in BC')93END IF9495END IF9697GroundedMask => VariableGet(Model % Variables,GroundedMaskName,UnFoundFatal=UnFoundFatal)98thick => VariableGet(Model % Variables,thickName,UnFoundFatal=UnFoundFatal)99100Haf = 0.0_dp101102thickness = thick%values(thick%perm( nodenumber ))103! nodeHeight = Model%Nodes%z104105! we assume sea level is at zero height. Hence:106! (-nodeHeight/rhoRatio) =107! (vertical distance from lower surface to sea level)*rho_ocean / rho_ice =108! is the thickness of ice up to floatation.109IF (nodeHeight.GT.0.0_dp) THEN110Haf = thickness111ELSE112Haf = thickness + nodeHeight/rhoRatio113END IF114115! We assume mask value for ungrounded ice is -1116IF (UseGroundedMask) THEN117IF (GroundedMask%values(GroundedMask%perm( nodenumber )) .LT.-0.5 ) THEN118Haf = 0.0_dp119END IF120END IF121122END FUNCTION Calculate_Haf123124125