/[MITgcm]/MITgcm/pkg/icefront/icefront_thermodynamics.F
ViewVC logotype

Contents of /MITgcm/pkg/icefront/icefront_thermodynamics.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.10 - (show annotations) (download)
Sun Nov 10 02:58:34 2013 UTC (10 years, 6 months ago) by yunx
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, HEAD
Changes since 1.9: +1 -7 lines
Remove ALLOW_SUBGLACIAL_RUNOFF and relative code. Instead, subglacial runoff
is added using obcs pkg. An example is given at
MITgcm_contrib/icefront/2D_example

1 C $Header: /u/gcmpack/MITgcm/pkg/icefront/icefront_thermodynamics.F,v 1.9 2011/05/16 22:41:03 yunx Exp $
2 C $Name: $
3
4 #include "ICEFRONT_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: ICEFRONT_THERMODYNAMICS
8 C !INTERFACE:
9 SUBROUTINE ICEFRONT_THERMODYNAMICS(
10 I myTime, myIter, myThid )
11 C !DESCRIPTION: \bv
12 C *=============================================================*
13 C | S/R ICEFRONT_THERMODYNAMICS
14 C | o shelf-ice main routine.
15 C | compute temperature and (virtual) salt flux at the
16 C | shelf-ice ocean interface
17 C |
18 C | stresses at the ice/water interface are computed in separate
19 C | routines that are called from mom_fluxform/mom_vecinv
20 C *=============================================================*
21
22 C !USES:
23 IMPLICIT NONE
24
25 C === Global variables ===
26 #include "SIZE.h"
27 #include "EEPARAMS.h"
28 #include "PARAMS.h"
29 #include "GRID.h"
30 #include "DYNVARS.h"
31 #include "FFIELDS.h"
32 #include "ICEFRONT.h"
33
34 C !INPUT/OUTPUT PARAMETERS:
35 C === Routine arguments ===
36 C myIter :: iteration counter for this thread
37 C myTime :: time counter for this thread
38 C myThid :: thread number for this instance of the routine.
39 _RL myTime
40 INTEGER myIter
41 INTEGER myThid
42 CEOP
43
44 #ifdef ALLOW_ICEFRONT
45 C !LOCAL VARIABLES :
46 C === Local variables ===
47 C I,J,K,bi,bj :: loop counters
48 C tLoc, sLoc, pLoc :: local in-situ temperature, salinity, pressure
49 C thetaICE :: averaged temperature of glacier interior
50 C theta/saltFreeze :: temperature and salinity of water at the
51 C ice-ocean interface (at the freezing point)
52 C FreshWaterFlux :: fresh water flux due to freezing or melting of ice
53 C front in kg/m^2/s (positive increases ocean salinity)
54 C HeatFlux :: ice front heat flux in W/m^2
55 C (positive decreases ocean temperature)
56 C auxiliary variables and abbreviations:
57 C a0, b, c0
58 C eps1, eps2, eps3, eps4, eps5, eps6, eps7
59 C aqe, bqe, cqe, discrim, recip_aqe
60 INTEGER I,J,K
61 INTEGER bi,bj
62 _RL tLoc, sLoc, pLoc
63 _RL thetaICE
64 _RL thetaFreeze, saltFreeze
65 _RS FreshWaterFlux( 1:sNx, 1:sNy )
66 _RS HeatFlux ( 1:sNx, 1:sNy )
67 _RS ICEFRONTheatTransCoeff ( 1:sNx, 1:sNy )
68 _RS ICEFRONTsaltTransCoeff ( 1:sNx, 1:sNy )
69 _RL a0, b, c0
70 _RL eps1, eps2, eps3, eps4, eps5, eps6, eps7
71 _RL aqe, bqe, cqe, discrim, recip_aqe
72
73
74 _RL SW_TEMP
75 EXTERNAL SW_TEMP
76
77 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
78
79 C Linear dependence of freezing point on salinity.
80 a0 = -0.0575 _d 0
81 c0 = 0.0901 _d 0
82 b = -7.61 _d -4
83
84
85 DO bj = myByLo(myThid), myByHi(myThid)
86 DO bi = myBxLo(myThid), myBxHi(myThid)
87 DO K = 1, Nr
88 DO J = 1, sNy
89 DO I = 1, sNx
90
91 C Calculate ICEFRONTheatTransCoeff & ICEFRONTsaltTransCoeff
92 IF( ICEFRONTlength(I,J,bi,bj) .GT. 0. _d 0
93 & .AND. K .LE. K_icefront(I,J,bi,bj) ) THEN
94 ICEFRONTheatTransCoeff(I,J) = 1.0 _d -02
95 & *abs(wVEL(I,J,K,bi,bj))
96 & *sqrt(1.5 _d -03)
97 ICEFRONTheatTransCoeff(I,J) = max
98 & (ICEFRONTheatTransCoeff(I,J),1. _d -04)
99 ICEFRONTsaltTransCoeff(I,J) = 5.05 _d -3
100 & *ICEFRONTheatTransCoeff(I,J)
101
102 C A few abbreviations.
103 eps1 = rUnit2mass*HeatCapacity_Cp*ICEFRONTheatTransCoeff(I,J)
104 eps2 = rUnit2mass*ICEFRONTlatentHeat*ICEFRONTsaltTransCoeff(I,J)
105 eps3 = rUnit2mass*ICEFRONTheatCapacity_Cp
106 & *ICEFRONTsaltTransCoeff(I,J)
107 eps5 = mass2rUnit/HeatCapacity_Cp
108 aqe = a0 *(-eps1+eps3)
109 recip_aqe = 0.5 _d 0/aqe
110
111 C Make local copies of temperature, salinity and depth (pressure).
112 pLoc = ABS(rC(k))
113 tLoc = theta(I,J,K,bi,bj)
114 sLoc = MAX(salt(I,J,K,bi,bj), 0. _d 0)
115
116 C Turn potential temperature into in-situ temperature.
117 tLoc = SW_TEMP(sLoc,tLoc,pLoc,0.D0)
118
119 C Get ice temperature. Assume linear ice temperature change from
120 C the surface (ICEFRONTthetaSurface) to the base(0 degree C).
121 IF ( K .EQ. K_icefront(I,J,bi,bj)) THEN
122 pLoc = 0.5*(ABS(R_icefront(I,J,bi,bj))+ABS(rF(K)))
123 ENDIF
124 thetaICE = ICEFRONTthetaSurface*
125 & (R_icefront(I,J,bi,bj)-pLoc)
126 & / R_icefront(I,J,bi,bj)
127
128 C A few more abbreviations.
129 eps4 = b*pLoc + c0
130 eps6 = eps4 - tLoc
131 eps7 = eps4 - thetaIce
132
133 C Solve quadratic equation to get salinity at icefront-ocean interface.
134 bqe = - eps1*eps6 -sLoc*a0*eps3 + eps3*eps7 + eps2
135 cqe = -(eps2+eps3*eps7)*sLoc
136 discrim = bqe*bqe - 4. _d 0*aqe*cqe
137 saltFreeze = (- bqe - SQRT(discrim))*recip_aqe
138 IF ( saltFreeze .LT. 0. _d 0 )
139 & saltFreeze = (- bqe + SQRT(discrim))*recip_aqe
140 thetaFreeze = a0*saltFreeze + eps4
141
142 C-- Calculate the outward (leaving the ocean) heat (W/m^2)
143 C and freshwater (kg/m^2/s).
144 C Sign convention: inward (negative) fresh water flux implies glacier
145 C melting due to outward (positive) heat flux.
146 FreshWaterFlux(I,J) = maskC(I,J,K,bi,bj) *
147 & eps1 * ( thetaFreeze - tLoc ) /
148 & (ICEFRONTlatentHeat + ICEFRONTheatCapacity_cp*
149 & (thetaFreeze - thetaIce))
150 HeatFlux(I,J) = maskC(I,J,K,bi,bj) * HeatCapacity_Cp *
151 & ( -rUnit2mass*ICEFRONTheatTransCoeff(I,J) +
152 & FreshWaterFlux(I,J) ) * ( thetaFreeze - tLoc )
153
154 C Compute tendencies.
155 icefront_TendT(i,j,K,bi,bj) = - HeatFlux(I,J)* eps5
156 icefront_TendS(i,j,K,bi,bj) = FreshWaterFlux(I,J) *
157 & mass2rUnit * sLoc
158
159 C Scale by icefrontlength, which is the ratio of the horizontal length
160 C of the ice front in each model grid cell divided by the grid cell area.
161 IF (k .LT. k_icefront(i,j,bi,bj)) THEN
162 icefront_TendT(i,j,K,bi,bj) = icefront_TendT(i,j,K,bi,bj)
163 & * ICEFRONTlength(i,j,bi,bj)
164 icefront_TendS(i,j,K,bi,bj) = icefront_TendS(i,j,K,bi,bj)
165 & * ICEFRONTlength(i,j,bi,bj)
166 ELSEIF (k .EQ. k_icefront(i,j,bi,bj)) THEN
167 C At the bottom of the ice shelf there is additional scaling due
168 C to the partial depth of the ice front.
169 icefront_TendT(i,j,K,bi,bj) = icefront_TendT(i,j,K,bi,bj)
170 & * ICEFRONTlength(i,j,bi,bj)
171 & * (ABS(R_icefront(I,J,bi,bj))-ABS(rF(K)))
172 & * recip_drF(K)
173 icefront_TendS(i,j,K,bi,bj) = icefront_TendS(i,j,K,bi,bj)
174 & * ICEFRONTlength(i,j,bi,bj)
175 & * (ABS(R_icefront(I,J,bi,bj))-ABS(rF(K)))
176 & * recip_drF(K)
177 ENDIF
178
179 ELSE ! K .LE. K_icefront
180
181 HeatFlux (I,J) = 0. _d 0
182 FreshWaterFlux(I,J) = 0. _d 0
183
184 ENDIF ! K .LE. K_icefront
185
186 ENDDO ! I = 1, sNx
187 ENDDO ! J = 1, sNy
188
189 #ifdef ALLOW_DIAGNOSTICS
190 IF ( useDiagnostics ) THEN
191 CALL DIAGNOSTICS_FILL_RS(FreshWaterFlux,'ICFfwFlx',
192 & k,1,3,bi,bj,myThid)
193 CALL DIAGNOSTICS_FILL_RS(HeatFlux, 'ICFhtFlx',
194 & k,1,3,bi,bj,myThid)
195 ENDIF
196 #endif /* ALLOW_DIAGNOSTICS */
197
198 ENDDO ! K = 1, Nr
199 ENDDO ! bi = myBxLo, myBxHi
200 ENDDO ! bj = myByLo, myByHi
201
202 #endif /* ALLOW_ICEFRONT */
203 RETURN
204 END

  ViewVC Help
Powered by ViewVC 1.1.22