/[MITgcm]/MITgcm/pkg/shelfice/shelfice_thermodynamics.F
ViewVC logotype

Annotation of /MITgcm/pkg/shelfice/shelfice_thermodynamics.F

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


Revision 1.5 - (hide annotations) (download)
Mon Aug 14 16:52:45 2006 UTC (17 years, 10 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint58u_post, checkpoint58w_post, checkpoint58r_post, checkpoint58t_post, checkpoint58q_post, checkpoint58o_post, checkpoint58v_post, checkpoint58s_post, checkpoint58p_post
Changes since 1.4: +46 -8 lines
add a simple boundary layer scheme to reduce noise, off by default for
now

1 mlosch 1.5 C $Header: /u/gcmpack/MITgcm/pkg/shelfice/shelfice_thermodynamics.F,v 1.4 2006/02/14 13:09:46 mlosch Exp $
2 mlosch 1.1 C $Name: $
3    
4     #include "SHELFICE_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: SHELFICE_THERMODYNAMICS
8     C !INTERFACE:
9     SUBROUTINE SHELFICE_THERMODYNAMICS(
10     I myTime, myIter, myThid )
11     C !DESCRIPTION: \bv
12     C *=============================================================*
13     C | S/R SHELFICE_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 "SHELFICE.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_SHELFICE
45 mlosch 1.5 C !LOCAL VARIABLES :
46 mlosch 1.1 C === Local variables ===
47 mlosch 1.5 INTEGER I,J,K,Kp1
48 mlosch 1.1 INTEGER bi,bj
49     _RL tLoc, sLoc, pLoc
50 mlosch 1.3 _RL thetaFreeze, saltFreeze
51     _RL a0, a1, a2, b, c0
52     _RL eps1, eps2, eps3, eps4, aqe, bqe, cqe, discrim, recip_aqe
53 mlosch 1.5 _RL drKp1, recip_drLoc
54 mlosch 1.1
55     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
56    
57 mlosch 1.3 C linear dependence of freezing point on salinity
58 mlosch 1.1 a0 = -0.0575 _d 0
59 mlosch 1.3 a1 = 0.0 _d -0
60     a2 = 0.0 _d -0
61     c0 = 0.0901 _d 0
62     b = -7.61 _d -4
63     #ifdef ALLOW_ISOMIP_TD
64     IF ( useISOMIPTD ) THEN
65     C non-linear dependence of freezing point on salinity
66     a0 = -0.0575 _d 0
67     a1 = 1.710523 _d -3
68     a2 = -2.154996 _d -4
69     b = -7.53 _d -4
70     c0 = 0. _d 0
71     ENDIF
72     #endif ALLOW_ISOMIP_TD
73     C first a few abbreviations
74     eps1 = rhoConst*HeatCapacity_Cp*SHELFICEheatTransCoeff
75     eps2 = rhoConst*SHELFICElatentHeat*SHELFICEsaltTransCoeff
76    
77 mlosch 1.1 DO bj = myByLo(myThid), myByHi(myThid)
78     DO bi = myBxLo(myThid), myBxHi(myThid)
79 mlosch 1.5 DO J = 1-Oly,sNy+Oly
80     DO I = 1-Olx,sNx+Olx
81     shelfIceHeatFlux (I,J,bi,bj) = 0. _d 0
82     shelfIceFreshWaterFlux(I,J,bi,bj) = 0. _d 0
83     shelficeForcingT (I,J,bi,bj) = 0. _d 0
84     shelficeForcingS (I,J,bi,bj) = 0. _d 0
85     ENDDO
86     ENDDO
87 mlosch 1.1 #ifdef ALLOW_ISOMIP_TD
88     IF ( useISOMIPTD ) THEN
89     DO J = 1, sNy
90     DO I = 1, sNx
91     K = kTopC(I,J,bi,bj)
92     pLoc = ABS(R_shelfIce(I,J,bi,bj))
93     IF ( K .NE. 0 .AND. pLoc .GT. 0. _d 0 ) THEN
94     C-- Calculate the in-situ temperature
95     tLoc = theta(I,J,K,bi,bj)
96 mlosch 1.5 sLoc = MAX(salt(I,J,K,bi,bj), 0. _d 0)
97     IF ( SHELFICEBoundaryLayer .AND. K .LT. Nr ) THEN
98     C-- average over boundary layer width
99     Kp1 = MIN(Nr,K+1)
100     C-- overlap into lower cell
101     drKp1 = drF(K)*( 1. _d 0 - _hFacC(I,J,K,bi,bj) )
102     C-- lower cell may not be as thick as required
103     drKp1 = MIN( drKp1, drF(Kp1) * _hFacC(I,J,Kp1,bi,bj) )
104     recip_drLoc = 1. _d 0 /
105     & ( drF(K)*_hFacC(I,J,K,bi,bj) + drKp1 )
106     tloc = ( tloc * drF(K)*_hFacC(I,J,K,bi,bj)
107     & + theta(I,J,Kp1,bi,bj) *drKp1 )
108     & * recip_drLoc
109     sloc = ( sloc * drF(K)*_hFacC(I,J,K,bi,bj)
110     & + MAX(salt(I,J,Kp1,bi,bj), 0. _d 0) * drKp1 )
111     & * recip_drLoc
112     ENDIF
113 mlosch 1.1 C-- Calculate freezing temperature as a function of salinity and pressure
114 mlosch 1.3 CML thetaFreeze=-1.9 _d 0
115     thetaFreeze = sLoc * ( a0 + a1*sqrt(sLoc) + a2*sLoc )
116 mlosch 1.1 & + b*pLoc + c0
117     C-- Calculate the upward heat and fresh water fluxes
118     shelfIceHeatFlux(I,J,bi,bj) =
119 mlosch 1.3 & SHELFICEheatTransCoeff * ( tLoc - thetaFreeze )
120 mlosch 1.1 & *HeatCapacity_Cp*recip_horiVertRatio*rhoConst
121     C upward heat flux into the shelf-ice implies basal melting,
122     C thus a downward (negative upward) fresh water flux, and vice versa
123     shelfIceFreshWaterFlux(I,J,bi,bj) =
124     & - shelfIceHeatFlux(I,J,bi,bj)
125     & *recip_rhoConst*recip_SHELFICElatentHeat
126     C-- compute surface tendencies
127     shelficeForcingT(i,j,bi,bj) =
128     & - shelfIceHeatFlux(I,J,bi,bj)
129     & *recip_Cp*horiVertRatio*recip_rhoConst
130 mlosch 1.2 IF (convertFW2Salt .EQ. -1.) THEN
131     shelficeForcingS(i,j,bi,bj) =
132     & shelfIceFreshWaterFlux(I,J,bi,bj)
133     & * salt(I,J,K,bi,bj) * convertEmP2rUnit
134     ELSE
135     shelficeForcingS(i,j,bi,bj) =
136     & shelfIceFreshWaterFlux(I,J,bi,bj)
137     & * convertFW2Salt * convertEmP2rUnit
138     ENDIF
139 mlosch 1.1 C-- stress at the ice/water interface is computed in separate
140     C routines that are called from mom_fluxform/mom_vecinv
141     ENDIF
142     ENDDO
143     ENDDO
144     ELSE
145     #else
146     IF ( .TRUE. ) THEN
147     #endif /* ALLOW_ISOMIP_TD */
148 mlosch 1.3 C use BRIOS thermodynamics, following Hellmers PhD thesis:
149     C Hellmer, H., 1989, A two-dimensional model for the thermohaline
150     C circulation under an ice shelf, Reports on Polar Research, No. 60
151     C (in German).
152     DO J = 1, sNy
153     DO I = 1, sNx
154     K = kTopC(I,J,bi,bj)
155     pLoc = ABS(R_shelfIce(I,J,bi,bj))
156     IF ( K .NE. 0 .AND. pLoc .GT. 0. _d 0 ) THEN
157     C-- Calculate the in-situ temperature
158     tLoc = theta(I,J,K,bi,bj)
159 mlosch 1.5 sLoc = MAX(salt(I,J,K,bi,bj), 0. _d 0)
160     IF ( SHELFICEBoundaryLayer .AND. K .LT. Nr ) THEN
161     C-- average over boundary layer width
162     Kp1 = MIN(Nr,K+1)
163     C-- overlap into lower cell
164     drKp1 = drF(K)*( 1. _d 0 - _hFacC(I,J,K,bi,bj) )
165     C-- lower cell may not be as thick as required
166     drKp1 = MIN( drKp1, drF(Kp1) * _hFacC(I,J,Kp1,bi,bj) )
167     recip_drLoc = 1. _d 0 /
168     & ( drF(K)*_hFacC(I,J,K,bi,bj) + drKp1 )
169     tloc = ( tloc * drF(K)*_hFacC(I,J,K,bi,bj)
170     & + theta(I,J,Kp1,bi,bj) *drKp1 )
171     & * recip_drLoc
172     sloc = ( sloc * drF(K)*_hFacC(I,J,K,bi,bj)
173     & + MAX(salt(I,J,Kp1,bi,bj), 0. _d 0) * drKp1 )
174     & * recip_drLoc
175     ENDIF
176 mlosch 1.3 C solve quadratic equation to get salinity at shelfice-ocean interface
177     eps3 = rhoShelfIce*SHELFICEheatCapacity_Cp
178     & * SHELFICEkappa/ploc
179     eps4 = b*pLoc + c0
180     aqe = a0 *(eps1+eps3)
181     recip_aqe = 0. _d 0
182     IF ( aqe .NE. 0 ) recip_aqe = 0.5/aqe
183     bqe = eps4*(eps1+eps3) - eps2
184     & - eps1*tloc - eps3*SHELFICEthetaSurface
185     cqe = eps2*sloc
186     discrim = bqe*bqe - 4. _d 0*aqe*cqe
187     #ifdef ALLOW_SHELFICE_DEBUG
188     IF ( discrim .LT. 0. _d 0 ) THEN
189     print *, 'ml-shelfice: discrim = ', discrim,aqe,bqe,cqe
190     print *, 'ml-shelfice: ploc = ', ploc
191     print *, 'ml-shelfice: tloc = ', tloc
192     print *, 'ml-shelfice: sloc = ', sloc
193     print *, 'ml-shelfice: tsurface= ',
194     & SHELFICEthetaSurface
195     print *, 'ml-shelfice: eps1 = ', eps1
196     print *, 'ml-shelfice: eps2 = ', eps2
197     print *, 'ml-shelfice: eps3 = ', eps3
198     print *, 'ml-shelfice: eps4 = ', eps4
199     print *, 'ml-shelfice: rhoW = ', rhoConst
200     print *, 'ml-shelfice: rhoIce = ', rhoShelfIce
201     print *, 'ml-shelfice: Cp_W = ', HeatCapacity_Cp
202     print *, 'ml-shelfice: Cp_I = ',
203     & SHELFICEHeatCapacity_Cp
204     print *, 'ml-shelfice: gammaT = ',
205     & SHELFICEheatTransCoeff
206     print *, 'ml-shelfice: gammaS = ',
207     & SHELFICEsaltTransCoeff
208     print *, 'ml-shelfice: lat.heat= ',
209     & SHELFICElatentHeat
210     STOP 'ABNORMAL END in S/R SHELFICE_THERMODYNAMICS'
211     ENDIF
212     #endif /* ALLOW_SHELFICE_DEBUG */
213     saltFreeze = (- bqe - SQRT(discrim))*recip_aqe
214 mlosch 1.4 IF ( saltFreeze .LT. 0. _d 0 )
215 mlosch 1.3 & saltFreeze = (- bqe + SQRT(discrim))*recip_aqe
216     C-- Calculate freezing temperature as a function of salinity and pressure
217     thetaFreeze = saltFreeze * a0 + eps4
218     CML Inconsistent but more accurate:
219     CML thetaFreeze = sLoc * ( a0 + a1*sqrt(sLoc) + a2*sLoc )
220     CML & + b*pLoc + c0
221     C-- Calculate the upward heat and fresh water fluxes
222     shelfIceHeatFlux(I,J,bi,bj) =
223     & ( eps1 * ( tLoc - thetaFreeze ) )*recip_horiVertRatio
224     shelfIceFreshWaterFlux(I,J,bi,bj) =
225     & rhoConst/rhoShelfIce * SHELFICEsaltTransCoeff
226     & * ( saltFreeze - sloc )/saltFreeze
227     & * recip_horiVertRatio
228     C-- compute surface tendencies
229     shelficeForcingT(i,j,bi,bj) =
230     & - shelfIceHeatFlux(I,J,bi,bj)
231     & *recip_Cp*horiVertRatio*recip_rhoConst
232     shelficeForcingS(i,j,bi,bj) =
233     & shelfIceFreshWaterFlux(I,J,bi,bj)
234     & * saltFreeze * convertEmP2rUnit
235     ENDIF
236     ENDDO
237     ENDDO
238 mlosch 1.1 ENDIF
239 mlosch 1.3 C endif (not) useISOMIPTD
240 mlosch 1.1 ENDDO
241     ENDDO
242    
243     #endif /* ALLOW_SHELFICE */
244     RETURN
245     END

  ViewVC Help
Powered by ViewVC 1.1.22