/[MITgcm]/MITgcm_contrib/dcarroll/iceberg/code/shelfice_thermodynamics.F
ViewVC logotype

Contents of /MITgcm_contrib/dcarroll/iceberg/code/shelfice_thermodynamics.F

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


Revision 1.2 - (show annotations) (download)
Thu Aug 29 19:47:27 2019 UTC (6 years, 3 months ago) by dcarroll
Branch: MAIN
Changes since 1.1: +0 -0 lines
Checked in update of iceberg simulation code

1 C $Header: /home/ubuntu/mnt/e9_copy/MITgcm/pkg/shelfice/shelfice_thermodynamics.F,v 1.47 2015/12/17 01:52:05 jmc Exp $
2 C $Name: $
3
4 #include "SHELFICE_OPTIONS.h"
5 #ifdef ALLOW_AUTODIFF
6 # include "AUTODIFF_OPTIONS.h"
7 #endif
8 #ifdef ALLOW_CTRL
9 # include "CTRL_OPTIONS.h"
10 #endif
11
12 CBOP
13 C !ROUTINE: SHELFICE_THERMODYNAMICS
14 C !INTERFACE:
15 SUBROUTINE SHELFICE_THERMODYNAMICS(
16 I myTime, myIter, myThid )
17 C !DESCRIPTION: \bv
18 C *=============================================================*
19 C | S/R SHELFICE_THERMODYNAMICS
20 C | o shelf-ice main routine.
21 C | compute temperature and (virtual) salt flux at the
22 C | shelf-ice ocean interface
23 C |
24 C | stresses at the ice/water interface are computed in separate
25 C | routines that are called from mom_fluxform/mom_vecinv
26
27 CIGF | ASSUMES
28 C--- | * SHELFICEconserve = true
29 C *=============================================================*
30 C \ev
31
32 C !USES:
33 IMPLICIT NONE
34
35 C === Global variables ===
36 #include "SIZE.h"
37 #include "EEPARAMS.h"
38 #include "PARAMS.h"
39 #include "GRID.h"
40 #include "DYNVARS.h"
41 #include "FFIELDS.h"
42 #include "SHELFICE.h"
43 #include "SHELFICE_COST.h"
44 #ifdef ALLOW_AUTODIFF
45 # include "CTRL_SIZE.h"
46 # include "ctrl.h"
47 # include "ctrl_dummy.h"
48 #endif /* ALLOW_AUTODIFF */
49 #ifdef ALLOW_AUTODIFF_TAMC
50 # ifdef SHI_ALLOW_GAMMAFRICT
51 # include "tamc.h"
52 # include "tamc_keys.h"
53 # endif /* SHI_ALLOW_GAMMAFRICT */
54 #endif /* ALLOW_AUTODIFF_TAMC */
55
56 C !INPUT/OUTPUT PARAMETERS:
57 C === Routine arguments ===
58 C myIter :: iteration counter for this thread
59 C myTime :: time counter for this thread
60 C myThid :: thread number for this instance of the routine.
61 _RL myTime
62 INTEGER myIter
63 INTEGER myThid
64
65 #ifdef ALLOW_SHELFICE
66 C !LOCAL VARIABLES :
67 C === Local variables ===
68 C I,J,K,Kp1,bi,bj :: loop counters
69 C tLoc, sLoc, pLoc :: local potential temperature, salinity, pressure
70 C theta/saltFreeze :: temperature and salinity of water at the
71 C ice-ocean interface (at the freezing point)
72 C freshWaterFlux :: local variable for fresh water melt flux due
73 C to melting in kg/m^2/s
74 C (negative density x melt rate)
75 C iceFrontCellThickness :: the ratio of the horizontal length
76 C of the ice front in each model grid cell
77 C divided by the grid cell area. The "thickness"
78 C of the colum perpendicular to the front
79 C iceFrontWidth :: the width of the ice front.
80
81 INTEGER I,J,K,Kp1
82 INTEGER bi,bj
83 INTEGER CURI, CURJ, FRONT_K
84
85 _RL tLoc
86 _RL sLoc
87 _RL pLoc
88
89 #ifndef SHI_USTAR_WETPOINT
90 _RL uLoc(1-olx:snx+olx,1-oly:sny+oly)
91 _RL vLoc(1-olx:snx+olx,1-oly:sny+oly)
92 #endif
93 _RL velSq(1-olx:snx+olx,1-oly:sny+oly)
94
95 _RL freshWaterFlux
96
97 _RL ice_bottom_Z_C, seafloor_N
98 _RL wet_top_Z_N, wet_bottom_Z_N
99 _RL iceFrontWetContact_Z_max, iceFrontContact_Z_min
100 _RL iceFrontContact_H
101 _RL iceFrontVertContactFrac, iceFrontCellThickness
102 _RL iceFrontWidth, iceFrontFaceArea
103 _RL thermalConductionDistance, thermalConductionTemp
104 _RL tmpHeatFlux, tmpFWFLX
105 _RL tmpForcingT, tmpForcingS
106 _RL tmpFac, icfgridareaFrac
107 INTEGER SI
108
109 #ifdef ALLOW_DIAGNOSTICS
110 _RL uStarDiag(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
111 #endif /* ALLOW_DIAGNOSTICS */
112
113 _RL epsilon_H
114
115 #ifdef ALLOW_SHIFWFLX_CONTROL
116 _RL xx_shifwflx_loc(1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
117 #endif
118
119 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
120
121 C-- minimum fraction of a cell adjacent to an ice front that must be
122 C-- wet for exchange to happen
123 epsilon_H = 1. _d -03
124
125 C-- hard coded for now.
126 thermalConductionDistance = 100.0 _d 0
127 thermalConductionTemp = -20.0 _d 0
128 icfgridareaFrac = 1.0 _d 0
129
130 C heat flux into the ice shelf, default is diffusive flux
131 C (Holland and Jenkins, 1999, eq.21)
132
133 DO bj = myByLo(myThid), myByHi(myThid)
134 DO bi = myBxLo(myThid), myBxHi(myThid)
135 DO J = 1-OLy,sNy+OLy
136 DO I = 1-OLx,sNx+OLx
137 shelfIceHeatFlux (I,J,bi,bj) = 0. _d 0
138 shelfIceFreshWaterFlux(I,J,bi,bj) = 0. _d 0
139 SHIICFHeatFlux (I,J,bi,bj) = 0. _d 0
140 SHIICFFreshWaterFlux(I,J,bi,bj) = 0. _d 0
141 shelficeForcingT (I,J,bi,bj) = 0. _d 0
142 shelficeForcingS (I,J,bi,bj) = 0. _d 0
143 shelficeForcingTR (I,J,bi,bj) = 0. _d 0
144 #ifndef ALLOW_shiTransCoeff_3d
145 shiTransCoeffS(I,J,bi,bj) = 5.05 _d -3 *
146 & shiTransCoeffT(I,J,bi,bj)
147 #endif
148 DO K = 1, NR
149 #ifdef ALLOW_shiTransCoeff_3d
150 shiTransCoeffS(I,J,K,bi,bj) = 5.05 _d -3 *
151 & shiTransCoeffT(I,J,K,bi,bj)
152 #endif
153 iceFrontHeatFlux(I,J,K,bi,bj) = 0. _d 0
154 iceFrontFreshWaterFlux(I,J,K,bi,bj) = 0. _d 0
155 iceFrontForcingT(I,J,K,bi,bj) = 0. _d 0
156 iceFrontForcingS(I,J,K,bi,bj) = 0. _d 0
157 iceFrontForcingTR(I,J,K,bi,bj) = 0. _d 0
158 ENDDO /* K */
159
160 ENDDO /* I */
161 ENDDO /* J */
162
163 C-- First ice front then ice shelf. Loop through each i,j point
164 C-- process ice fronts in k, then process ice shelf.
165 DO J = 1, sNy
166 DO I = 1, sNx
167
168 C-- The K index where the ice front ends (0 if no ice front)
169 FRONT_K = K_icefront(I,J,bi,bj)
170
171 C-- If there is an ice front at this (I,J) continue
172 IF (FRONT_K .GT. 0) THEN
173
174 C-- Loop through all depths where the ice front is fround
175 DO K = 1, FRONT_K
176 C-- Loop around the four laterally neighboring cells of the ice front.
177 C-- If any neighboring points has wet volume in contact with the ice
178 C-- front at (I,J) then calculate ice-ocean exchanges.
179 C-- The four laterally neighboring point are at (CURI,CURJ)
180 DO SI = 1,4
181 IF (SI .EQ. 1) THEN
182 C-- Looking to right
183 CURI = I+1
184 CURJ = J
185
186 iceFrontWidth = dyG(I+1,J,bi,bj)
187
188 ELSEIF (SI .EQ. 2) THEN
189 C-- Looking to LEFT
190 CURI = I-1
191 CURJ = J
192
193 iceFrontWidth = dyG(I,J,bi,bj)
194 ELSEIF (SI .EQ. 3) THEN
195 C-- Looking to NORTH
196 CURI = I
197 CURJ = J+1
198
199 iceFrontWidth = dxG(I,J+1,bi,bj)
200 ELSEIF (SI .EQ. 4) THEN
201 C-- Looking to south
202 CURI = I
203 CURJ = J-1
204
205 iceFrontWidth = dxG(I,J,bi,bj)
206 endif
207
208 C-- cell depth describes the average distance
209 C-- perpendicular to the ice front fact
210
211 iceFrontCellThickness = 0. _d 0
212 IF(iceFrontWidth.NE.0. _d 0)
213 & iceFrontCellThickness = RA(CURI,CURJ,bi,bj)
214 & /iceFrontWidth
215 iceFrontFaceArea = DRF(K)*iceFrontWidth
216
217 C-- First, make sure the adjacent point has at least some water in it.
218 IF (_hFacC(CURI,CURJ,K,bi,bj) .GT. zeroRL) THEN
219
220 C-- we need to determine how much of the ice front is in contact with
221 C-- water in the neighboring grid cell at this depth level.
222
223 C-- 1. Determine the top depth with water in the current cell
224 C-- 2. Determine the top depth with water in the neighbor cell
225 C-- 3. Determine the depth where water gap between (1) and (2).
226 C-- 4. If there is a gap then ice front is in contact with water in
227 C-- the neighboring cell
228
229 C-- ice_bottom_Z_C: the depth (m) of the bottom of the ice in the
230 C-- current cell. Bounded between rF(K) and rF(K+1).
231 C-- * If the ice extends past the bottom of the cell then
232 C-- ice_bottom_Z_C = rF(K+1)
233 C-- [rF(k) >= ice_bottom_Z_C >= rF(K+1)] (rF is negative)
234 ice_bottom_Z_C = max(rF(K+1),
235 & min(Ro_surf(I,J, bi,bj), rF(K)))
236
237 C-- wet_top_Z_N: the depth (m) of the bottom of the ice in the
238 C-- neighboring grid. If the neighboring cell has ice in
239 C-- (in the form of a shelf or front) then wet_top_Z_N is
240 C-- the depth of this neighboring ice.
241 C--
242 C-- * If neighbor cell has no ice, then Ro_surf = 0 and
243 C-- wet_top_Z_N = rF(K)
244 C-- [rF(k) >= wet_top_Z_N >= rF(K+1)] (rF is negative)
245
246 wet_top_Z_N = max(rF(K+1),
247 & min(Ro_surf(CURI,CURJ, bi,bj), rF(K)))
248
249 C-- wet_bottom_Z_N: the depth (m) of the bottom of the wet part of the
250 C-- neighboring cell. If the seafloor reaches into
251 C-- the grid cell then the bottom of the wet part of the
252 C-- grid cell is at the seafloor.
253 C--
254 C-- * If the seafloor is deeper than this grid cell then
255 C-- wet_bottom_Z = rF(K+1)
256 C-- * If the seafloor is shallower than this grid cell then
257 C-- wet_bottom_Z = rF(K)
258 C-- * If the seafloor reaches partly into this grid cell
259 C-- then wet_bottom_Z = R_low
260
261 C-- [rF(k) >= wet_bottom_Z >= rF(K+1)] (rF is negative)
262
263 wet_bottom_Z_N = min(rF(K),
264 & max(R_low(CURI,CURJ, bi,bj), rF(K+1)))
265
266 C-- iceFrontWetContact_Z_max: The deepest point where the
267 C-- the ice front at (I,J) is in contact with water
268 C-- in the neighboring cell. The shallower of
269 C-- wet_bottom_Z_N (seafloor depth of neighboring point) and
270 C-- ice_bottom_Z_C (bottom of ice front in this center cell).
271
272 C-- * wet_bottom_Z_N if the seafloor of the neighboring
273 C-- cell is shallower than the ice draft at (I,J).
274 C-- * ice_bottom_Z_C if the ice draft at (I,J) is shallower
275 C-- than the seafloor of the neighboring cell.
276
277 IF (ice_bottom_Z_C .GT. wet_bottom_Z_N) THEN
278 iceFrontWetContact_Z_max = ice_bottom_Z_C
279 ELSE
280 iceFrontWetContact_Z_max = wet_bottom_Z_N
281 ENDIF
282
283 C-- The shallowest depth where the ice front at (I,J) is in contact
284 C-- with water in the neighboring cell. If the neighboring cell has
285 C-- no ice draft then wet_top_Z_N = rF(k), the top of the cell.
286 C-- Otherwise, the shallowest depth where the ice front at (I,J) can
287 C-- be in in contact with water (not ice) in (CURI, CURJ)
288 C-- is wet_top_Z_N.
289
290 C-- the fraction of the grid cell height that has ice draft in contact
291 C-- with water in the neighboring cell.
292 iceFrontVertContactFrac =
293 & (wet_top_Z_N - iceFrontWetContact_Z_max)/ DRF(K)
294
295
296 C-- Only proceed if iceFrontVertContactFrac is > 0, the
297 C-- ice draft at (I,J)
298 C-- is in contact with some water in the neighboring grid cell.
299 IF (iceFrontVertContactFrac .GT. epsilon_H) THEN
300 tLoc = theta(CURI,CURJ,K,bi,bj)
301 sLoc = MAX(salt(CURI,CURJ,K,bi,bj), zeroRL)
302
303 C-- use pressure at the halfway point between the top and bottom of
304 C-- points of the ice front where the ice front is in contact with
305 C-- open water.
306 pLoc = 0.5 _d 0 * ABS(wet_top_Z_N +
307 & iceFrontWetContact_Z_max)
308
309 CALL SHELFICE_SOLVE4FLUXES(
310 I tLoc, sLoc, pLoc,
311 #ifndef ALLOW_shiTransCoeff_3d
312 I shiTransCoeffT(CURI,CURJ,bi,bj),
313 I shiTransCoeffS(CURI,CURJ,bi,bj),
314 #else
315 I shiTransCoeffT(CURI,CURJ,K,bi,bj),
316 I shiTransCoeffS(CURI,CURJ,K,bi,bj),
317 #endif
318 I thermalConductionDistance,
319 I thermalConductionTemp,
320 O tmpHeatFlux, tmpFWFLX,
321 O tmpForcingT, tmpForcingS,
322 I bi, bj, myTime, myIter, myThid )
323
324 C-- fluxes and forcing must be scaled by iceFrontVertContactFract and
325 C-- iceFrontContactFrac some fraction of the heigth and width of the
326 C-- grid cell face may not ice in contact with water.
327
328 C tmpHeatFlux and tmpFWFLX come as W/m^2 and kg/m^2/s respectively
329 C-- but these rates only apply to the
330 C-- fraction of the grid cell that has ice in contact with seawater.
331 C-- we must scale by iceFrontVertContactFrac to get to the average
332 C-- fluxes in this grid cell.
333
334 C-- In units W/m^2
335 iceFrontHeatFlux(CURI,CURJ,K,bi,bj) =
336 & iceFrontHeatFlux(CURI,CURJ,K,bi,bj) +
337 & tmpHeatFlux*iceFrontVertContactFrac
338
339 C In units of kg/m^2/s
340 iceFrontFreshWaterFlux(CURI,CURJ,K,bi,bj) =
341 & iceFrontFreshWaterFlux(CURI,CURJ,K,bi,bj) +
342 & tmpFWFLX*iceFrontVertContactFrac
343
344 iceFrontForcingTR(CURI,CURJ,K,bi,bj) =
345 & iceFrontFreshWaterFlux(CURI,CURJ,K,bi,bj) *
346 & mass2rUnit
347
348 C ow - 06/29/2018
349 C ow - Verticallly sum up the 3D icefront heat and freshwater fluxes to
350 C ow - compute the total flux for the water column. The shelfice fluxes,
351 C ow - which are 2D, will be added later. NOTE that only
352 C ow - ice-front melts below shelf-ice are included to be consistent
353 C ow - with Rignot's data
354 if(k.GE.kTopC(I,J,bi,bj))then
355 if(RA(CURI,CURJ,bi,bj).NE.0. _d 0)then
356 icfgridareaFrac =
357 & iceFrontFaceArea/RA(CURI,CURJ,bi,bj)
358 SHIICFHeatFlux(CURI,CURJ,bi,bj) =
359 & SHIICFHeatFlux(CURI,CURJ,bi,bj) +
360 & iceFrontHeatFlux(CURI,CURJ,K,bi,bj)
361 & * icfgridareaFrac
362 SHIICFFreshWaterFlux(CURI,CURJ,bi,bj) =
363 & SHIICFFreshWaterFlux(CURI,CURJ,bi,bj) +
364 & iceFrontFreshWaterFlux(CURI,CURJ,K,bi,bj)
365 & * icfgridareaFrac
366 endif
367 endif
368 C iceFrontForcing[T,S] X m/s but these rates only apply to the
369 C-- fraction of the grid cell that has ice in contact with seawater.
370 C-- we must scale by iceFrontVertContactFrac to get to the average
371 C-- fluxes in this grid cell. We must also divide the by the length
372 C-- of the grid cell perpendicular to the face.
373
374 IF (iceFrontCellThickness .NE. 0. _d 0) THEN
375 C In units of K / s
376 iceFrontForcingT(CURI,CURJ,K,bi,bj) =
377 & iceFrontForcingT(CURI,CURJ,K,bi,bj) +
378 & tmpForcingT/iceFrontCellThickness*
379 & iceFrontVertContactFrac
380
381 C In units of psu /s
382 iceFrontForcingS(CURI,CURJ,K,bi,bj) =
383 & iceFrontForcingS(CURI,CURJ,K,bi,bj) +
384 & tmpForcingS/iceFrontCellThickness*
385 & iceFrontVertContactFrac
386
387 ENDIF /* iceFrontCellThickness */
388 C In units of kg /s
389 addMass(CURI,CURJ,K,bi,bj) =
390 & addMass(CURI,CURJ,K,bi,bj) -
391 & tmpFWFLX*iceFrontFaceArea*
392 & iceFrontVertContactFrac
393 ENDIF /* iceFrontVertContactFrac */
394 ENDIF /* hFacC(CURI,CURJ,K,bi,bj) */
395 ENDDO /* SI loop for adjacent cells */
396 ENDDO /* K LOOP */
397 ENDIF /* FRONT K */
398
399 C-- ice shelf
400 K = kTopC(I,J,bi,bj)
401
402 C-- If there is an ice front at this (I,J) continue
403 C-- I am assuming K is only .GT. when there is at least some
404 C-- nonzero wet point below the shelf in the grid cell.
405 IF (K .GT. 0) THEN
406 C-- Initialize these values to zero
407 pLoc = 0 _d 0
408 tLoc = 0 _d 0
409 sLoc = 0 _d 0
410
411 C-- make local copies of temperature, salinity and depth
412 C-- (pressure in deci-bar) underneath the ice
413 C-- for the ice shelf case we use hydrostatic pressure at the ice
414 C-- base of the ice shelf, top of the cavity.
415
416 pLoc = ABS(R_shelfIce(I,J,bi,bj))
417 tLoc = theta(I,J,K,bi,bj)
418 sLoc = MAX(salt(I,J,K,bi,bj), zeroRL)
419
420 CALL SHELFICE_SOLVE4FLUXES(
421 I tLoc, sLoc, pLoc,
422 #ifndef ALLOW_shiTransCoeff_3d
423 I shiTransCoeffT(I,J,bi,bj),
424 I shiTransCoeffS(I,J,bi,bj),
425 #else
426 I shiTransCoeffT(I,J,K,bi,bj),
427 I shiTransCoeffS(I,J,K,bi,bj),
428 #endif
429 I pLoc, thermalConductionTemp,
430 O tmpHeatFlux, tmpFWFLX,
431 O tmpForcingT, tmpForcingS,
432 I bi, bj, myTime, myIter, myThid )
433
434 C In units of W/m^2
435 shelficeHeatFlux(I,J,bi,bj) = tmpHeatFlux
436 C In units of kg/m^2/s
437 shelfIceFreshWaterFlux(I,J,bi,bj) = tmpFWFLX
438
439 shelficeForcingTR(I,J,bi,bj) =
440 & shelfIceFreshWaterFlux(I,J,bi,bj) * mass2rUnit
441
442 C ow - 06/29/2018
443 C ow - Now add shelfice heat and freshwater fluxes
444 SHIICFHeatFlux(i,j,bi,bj) =
445 & SHIICFHeatFlux(i,j,bi,bj) +
446 & shelficeHeatFlux(i,j,bi,bj)
447 SHIICFFreshWaterFlux(i,j,bi,bj) =
448 & SHIICFFreshWaterFlux(i,j,bi,bj) +
449 & shelfIceFreshWaterFlux(i,j,bi,bj)
450 C In units of K/s -- division by drF required first
451 shelficeForcingT(I,J,bi,bj) = tmpForcingT*
452 & recip_drF(K)* _recip_hFacC(i,j,K,bi,bj)
453 C In units of psu/s -- division by drF required first
454 shelficeForcingS(I,J,bi,bj) = tmpForcingS*
455 & recip_drF(K)* _recip_hFacC(i,j,K,bi,bj)
456 C In units of kg/s -- multiplication of area required first
457 addMass(I,J,K, bi,bj) = addMass(I,J,K, bi,bj) -
458 & tmpFWFLX*RA(I,J,bi,bj)
459 ENDIF /* SHELF K > 0 */
460 ENDDO /* i */
461 ENDDO /* j */
462 ENDDO /* bi */
463 ENDDO /* bj */
464
465
466 C-- Calculate new loading anomaly (in case the ice-shelf mass was updated)
467 #ifndef ALLOW_AUTODIFF
468 c IF ( SHELFICEloadAnomalyFile .EQ. ' ' ) THEN
469 DO bj = myByLo(myThid), myByHi(myThid)
470 DO bi = myBxLo(myThid), myBxHi(myThid)
471 DO j = 1-OLy, sNy+OLy
472 DO i = 1-OLx, sNx+OLx
473 shelficeLoadAnomaly(i,j,bi,bj) = gravity
474 & *( shelficeMass(i,j,bi,bj) + rhoConst*Ro_surf(i,j,bi,bj) )
475 ENDDO
476 ENDDO
477 ENDDO
478 ENDDO
479 c ENDIF
480 #endif /* ndef ALLOW_AUTODIFF */
481
482 #ifdef ALLOW_DIAGNOSTICS
483 IF ( useDiagnostics ) THEN
484 CALL DIAGNOSTICS_FILL_RS(shelfIceFreshWaterFlux,'SHIfwFlx',
485 & 0,1,0,1,1,myThid)
486 CALL DIAGNOSTICS_FILL_RS(shelfIceHeatFlux, 'SHIhtFlx',
487 & 0,1,0,1,1,myThid)
488
489 CALL DIAGNOSTICS_FILL_RS(SHIICFFreshWaterFlux,'SHIICFfwFlx',
490 & 0,1,0,1,1,myThid)
491 CALL DIAGNOSTICS_FILL_RS(SHIICFHeatFlux, 'SHIICFhtFlx',
492 & 0,1,0,1,1,myThid)
493
494 CALL DIAGNOSTICS_FILL(iceFrontFreshWaterFlux, 'ICFfwFlx',
495 & 0,Nr,0,1,1,myThid)
496 CALL DIAGNOSTICS_FILL(iceFrontHeatFlux, 'ICFhtFlx',
497 & 0,Nr,0,1,1,myThid)
498
499 CALL DIAGNOSTICS_FILL(shelfIceForcingTR, 'SHITR ',
500 & 0,Nr,0,1,1,myThid)
501
502 CALL DIAGNOSTICS_FILL(iceFrontForcingTR, 'ICFTR ',
503 & 0,Nr,0,1,1,myThid)
504
505 C SHIForcT (Ice shelf forcing for theta [W/m2], >0 increases theta)
506 tmpFac = HeatCapacity_Cp*rUnit2mass
507 CALL DIAGNOSTICS_SCALE_FILL(shelficeForcingT,tmpFac,1,
508 & 'SHIForcT',0,1,0,1,1,myThid)
509 C SHIForcS (Ice shelf forcing for salt [g/m2/s], >0 increases salt)
510 tmpFac = rUnit2mass
511 CALL DIAGNOSTICS_SCALE_FILL(shelficeForcingS,tmpFac,1,
512 & 'SHIForcS',0,1,0,1,1,myThid)
513
514 C ICFForcT (Ice front forcing for theta [W/m2], >0 increases theta)
515 tmpFac = HeatCapacity_Cp*rUnit2mass
516 CALL DIAGNOSTICS_SCALE_FILL(iceFrontForcingT,tmpFac,1,
517 & 'ICFForcT',0,Nr,0,1,1,myThid)
518 C ICFForcS (Ice front forcing for salt [g/m2/s], >0 increases salt)
519 tmpFac = rUnit2mass
520 CALL DIAGNOSTICS_SCALE_FILL(iceFrontForcingS,tmpFac,1,
521 & 'ICFForcS',0,Nr,0,1,1,myThid)
522
523 C Transfer coefficients
524 #ifndef ALLOW_shiTransCoeff_3d
525 CALL DIAGNOSTICS_FILL(shiTransCoeffT,'SHIgammT',
526 & 0,1,0,1,1,myThid)
527 CALL DIAGNOSTICS_FILL(shiTransCoeffS,'SHIgammS',
528 & 0,1,0,1,1,myThid)
529 #else
530 CALL DIAGNOSTICS_FILL(shiTransCoeffT,'SHIgammT',
531 & 0,Nr,0,1,1,myThid)
532 CALL DIAGNOSTICS_FILL(shiTransCoeffS,'SHIgammS',
533 & 0,Nr,0,1,1,myThid)
534 #endif
535 C Friction velocity
536 #ifdef SHI_ALLOW_GAMMAFRICT
537 IF ( SHELFICEuseGammaFrict )
538 & CALL DIAGNOSTICS_FILL(uStarDiag,'SHIuStar',0,1,0,1,1,myThid)
539 #endif /* SHI_ALLOW_GAMMAFRICT */
540 ENDIF
541 #endif
542
543 #endif /* ALLOW_SHELFICE */
544 RETURN
545 END

  ViewVC Help
Powered by ViewVC 1.1.22