/[MITgcm]/MITgcm_contrib/dcarroll/highres_darwin/code/shelfice_init_fixed.F
ViewVC logotype

Contents of /MITgcm_contrib/dcarroll/highres_darwin/code/shelfice_init_fixed.F

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


Revision 1.1 - (show annotations) (download)
Sun Sep 22 21:23:47 2019 UTC (5 years, 10 months ago) by dcarroll
Branch: MAIN
CVS Tags: HEAD
Initial check in of high resolution Darwin simulation code

1 C $Header: /home/ubuntu/mnt/e9_copy/MITgcm/pkg/shelfice/shelfice_init_fixed.F,v 1.18 2017/04/10 23:49:35 jmc Exp $
2 C $Name: $
3
4 #include "SHELFICE_OPTIONS.h"
5 #ifdef ALLOW_COST
6 # include "COST_OPTIONS.h"
7 #endif
8 #ifdef ALLOW_CTRL
9 # include "CTRL_OPTIONS.h"
10 #endif
11
12 SUBROUTINE SHELFICE_INIT_FIXED( myThid )
13 C *============================================================*
14 C | SUBROUTINE SHELFICE_INIT_FIXED
15 C | o Routine to initialize SHELFICE parameters and variables.
16 C *============================================================*
17 C | Initialize SHELFICE parameters and variables.
18 C *============================================================*
19 IMPLICIT NONE
20
21 C === Global variables ===
22 #include "SIZE.h"
23 #include "EEPARAMS.h"
24 #include "PARAMS.h"
25 #include "GRID.h"
26 #include "SHELFICE.h"
27 #ifdef ALLOW_COST
28 # include "cost.h"
29 # include "SHELFICE_COST.h"
30 #endif /* ALLOW_COST */
31
32 C === Routine arguments ===
33 C myThid :: Number of this instance of SHELFICE_INIT_FIXED
34 INTEGER myThid
35
36 #ifdef ALLOW_SHELFICE
37 C === Local variables ===
38 C i, j, bi, bj :: Loop counters
39 INTEGER i, j, bi, bj, k
40 #ifdef ALLOW_DIAGNOSTICS
41 INTEGER diagNum
42 INTEGER diagMate
43 CHARACTER*8 diagName
44 CHARACTER*16 diagCode
45 CHARACTER*16 diagUnits
46 CHARACTER*(80) diagTitle
47 #endif /* ALLOW_DIAGNOSTICS */
48 #ifdef ALLOW_SHIFWFLX_CONTROL
49 INTEGER k
50 # ifdef ALLOW_SHIFWFLX_COST_CONTRIBUTION
51 _RL dummy
52 # endif
53 #endif
54
55 C local variabls used to determine shelf-ice and ice-front masks
56 C iceFrontCellThickness :: the ratio of the horizontal length
57 C of the ice front in each model grid cell
58 C divided by the grid cell area. The "thickness"
59 C of the colum perpendicular to the front
60 C iceFrontWidth :: the width of the ice front.
61
62 INTEGER CURI, CURJ, FRONT_K
63 _RL ice_bottom_Z_C
64 _RL wet_top_Z_N, wet_bottom_Z_N
65 _RL iceFrontWetContact_Z_max
66 _RL iceFrontContact_H
67 _RL iceFrontVertContactFrac, iceFrontCellThickness
68 _RL iceFrontWidth, iceFrontFaceArea
69 _RS fK_icefront (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
70
71 INTEGER SI
72 _RL epsilon_H
73
74 #ifdef ALLOW_MNC
75 C Initialize MNC variable information for SHELFICE
76 IF ( useMNC .AND. (shelfice_tave_mnc.OR.shelfice_dump_mnc)
77 & ) THEN
78 CALL SHELFICE_MNC_INIT( myThid )
79 ENDIF
80 #endif /* ALLOW_MNC */
81
82 C-----------------------------------------------------------------------
83 C-- Initialize SHELFICE variables kTopC
84 C-- kTopC is the same as kSurfC, except outside ice-shelf area:
85 C-- kTop = 0 where there is no ice-shelf (where kSurfC=1)
86 C-- and over land (completely dry column) where kSurfC = Nr+1
87 C-----------------------------------------------------------------------
88
89 DO bj = myByLo(myThid), myByHi(myThid)
90 DO bi = myBxLo(myThid), myBxHi(myThid)
91 DO j = 1-OLy, sNy+OLy
92 DO i = 1-OLx, sNx+OLx
93 IF ( kSurfC(i,j,bi,bj).LE.Nr .AND.
94 & R_shelfIce(i,j,bi,bj).LT.zeroRS ) THEN
95 kTopC(i,j,bi,bj) = kSurfC(i,j,bi,bj)
96 ELSE
97 kTopC(i,j,bi,bj) = 0
98 ENDIF
99 shelficeMassInit (i,j,bi,bj) = 0. _d 0
100 shelficeLoadAnomaly(i,j,bi,bj) = 0. _d 0
101 shelfIceMassDynTendency(i,j,bi,bj) = 0. _d 0
102 icefrontlength(i,j,bi,bj) = 0. _d 0
103 ENDDO
104 ENDDO
105 ENDDO
106 ENDDO
107
108 #ifdef ALLOW_SHIFWFLX_CONTROL
109 C maskSHI is a hack to play along with the general ctrl-package
110 C infrastructure, where only the k=1 layer of a 3D mask is used
111 C for 2D fields. We cannot use maskInC instead, because routines
112 C like ctrl_get_gen and ctrl_set_unpack_xy require 3D masks.
113 DO bj = myByLo(myThid), myByHi(myThid)
114 DO bi = myBxLo(myThid), myBxHi(myThid)
115 DO k=1,Nr
116 DO j=1-OLy,sNy+OLy
117 DO i=1-OLx,sNx+OLx
118 maskSHI(i,j,k,bi,bj) = 0. _d 0
119 ENDDO
120 ENDDO
121 ENDDO
122 DO k=1,Nr
123 DO j=1-OLy,sNy+OLy
124 DO i=1-OLx,sNx+OLx
125 IF ( R_shelfIce(i,j,bi,bj).LT.zeroRS
126 & .AND. hFacC(i,j,k,bi,bj).NE.zeroRS ) THEN
127 maskSHI(i,j,k,bi,bj) = 1. _d 0
128 maskSHI(i,j,1,bi,bj) = 1. _d 0
129 ENDIF
130 ENDDO
131 ENDDO
132 ENDDO
133 ENDDO
134 ENDDO
135 #endif /* ALLOW_SHIFWFLX_CONTROL */
136
137 C 06/29/2018
138 C ow - maskSHI above is not consistent with the spirit of gencost. Use mask2dSHI and mask3dSHI below
139 C ow - instead.
140 C ow - mask2dSHI and mask3dSHI are the 2d and 3d mask for shelfice. They are zero if there is no
141 C ow - shelfice and one if otherwise. For any i,j, if there is at least one non-zero mask3dSHI in
142 C ow - the vertical, then mask2dSHI at i,j is one.
143 DO bj = myByLo(myThid), myByHi(myThid)
144 DO bi = myBxLo(myThid), myBxHi(myThid)
145 DO k=1,Nr
146 DO j=1-OLy,sNy+OLy
147 DO i=1-OLx,sNx+OLx
148 mask3dSHIICF(i,j,k,bi,bj) = 0. _d 0
149 mask3dSHI(i,j,k,bi,bj) = 0. _d 0
150 mask3dICF(i,j,k,bi,bj) = 0. _d 0
151 if(k.eq.1)then
152 mask2dSHIICF(i,j,bi,bj) = 0. _d 0
153 mask2dSHI(i,j,bi,bj) = 0. _d 0
154 mask2dICF(i,j,bi,bj) = 0. _d 0
155 endif
156 ENDDO
157 ENDDO
158 ENDDO
159 C DO k=1,Nr
160 C DO j=1-OLy,sNy+OLy
161 C DO i=1-OLx,sNx+OLx
162 C IF ( R_shelfIce(i,j,bi,bj).LT.zeroRS
163 C & .AND. hFacC(i,j,k,bi,bj).NE.zeroRS ) THEN
164 C mask2dSHI(i,j,bi,bj) = 1. _d 0
165 C ENDIF
166 C ENDDO
167 C ENDDO
168 C ENDDO
169 ENDDO
170 ENDDO
171
172 #ifdef ALLOW_COST
173 #if (defined (ALLOW_SHIFWFLX_COST_CONTRIBUTION) && \
174 defined (ALLOW_SHIFWFLX_CONTROL))
175 IF ( shifwflx_errfile .NE. ' ' ) THEN
176 CALL READ_REC_XY_RL( shifwflx_errfile, wshifwflx, 1, 0, myThid )
177 ENDIF
178
179 DO bj = myByLo(myThid), myByHi(myThid)
180 DO bi = myBxLo(myThid), myBxHi(myThid)
181 DO j = 1-OLy, sNy+OLy
182 DO i = 1-OLx, sNx+OLx
183 c-- Test for missing values.
184 IF (wshifwflx(i,j,bi,bj) .LT. -9900.) THEN
185 wshifwflx(i,j,bi,bj) = 0. _d 0
186 ENDIF
187 c-- use weight as mask
188 wshifwflx(i,j,bi,bj) =
189 & max(wshifwflx(i,j,bi,bj),wshifwflx0)
190 & *maskSHI(i,j,1,bi,bj)
191 IF (wshifwflx(i,j,bi,bj) .NE. 0.) THEN
192 wshifwflx(i,j,bi,bj) =
193 & 1./wshifwflx(i,j,bi,bj)/wshifwflx(i,j,bi,bj)
194 ENDIF
195 ENDDO
196 ENDDO
197 ENDDO
198 ENDDO
199 CALL ACTIVE_WRITE_XY_LOC( 'wshifwflx', wshifwflx,
200 & 1, 0, myThid, dummy )
201 #endif /* ALLOW_SHIFWFLX_COST_CONTRIBUTION and ALLOW_SHIFWFLX_CONTROL */
202 #endif /* ALLOW_COST */
203
204 IF ( SHELFICEloadAnomalyFile .NE. ' ' ) THEN
205 CALL READ_FLD_XY_RL( SHELFICEloadAnomalyFile, ' ',
206 & shelficeLoadAnomaly, 0, myThid )
207 ENDIF
208 IF ( SHELFICEmassFile.NE.' ' ) THEN
209 CALL READ_FLD_XY_RL( SHELFICEmassFile, ' ',
210 & shelficeMassInit, 0, myThid )
211 ELSE
212 DO bj = myByLo(myThid), myByHi(myThid)
213 DO bi = myBxLo(myThid), myBxHi(myThid)
214 DO j = 1, sNy
215 DO i = 1, sNx
216 shelficeMassInit(i,j,bi,bj) =
217 & shelficeLoadAnomaly(i,j,bi,bj)*recip_gravity
218 & - rhoConst*Ro_surf(i,j,bi,bj)
219 ENDDO
220 ENDDO
221 ENDDO
222 ENDDO
223 ENDIF
224 _EXCH_XY_RL( shelficeMassInit, myThid )
225 CALL WRITE_FLD_XY_RL ( 'shelficemassinit', ' ',
226 & shelficeMassInit, 0, myThid )
227
228 c IF ( SHELFICEloadAnomalyFile .EQ. ' ' ) THEN
229 C- In case we need shelficeLoadAnomaly in phi0surf for initial pressure
230 C calculation (if using selectP_inEOS_Zc=2 or 3)
231 DO bj = myByLo(myThid), myByHi(myThid)
232 DO bi = myBxLo(myThid), myBxHi(myThid)
233 DO j = 1-OLy, sNy+OLy
234 DO i = 1-OLx, sNx+OLx
235 shelficeLoadAnomaly(i,j,bi,bj) = gravity
236 & *(shelficeMassInit(i,j,bi,bj)+rhoConst*Ro_surf(i,j,bi,bj))
237 ENDDO
238 ENDDO
239 ENDDO
240 ENDDO
241 c ELSE
242 c _EXCH_XY_RS( shelficeLoadAnomaly, myThid )
243 c ENDIF
244 IF ( debugLevel.GE.debLevC ) THEN
245 CALL WRITE_FLD_XY_RL( 'SHICE_pLoadAnom', ' ',
246 I shelficeLoadAnomaly, -1, myThid )
247 ENDIF
248
249 IF ( SHELFICEMassStepping .AND.
250 & SHELFICEMassDynTendFile .NE. ' ' ) THEN
251 CALL READ_FLD_XY_RS( SHELFICEMassDynTendFile, ' ',
252 & shelfIceMassDynTendency, 0, myThid )
253 ENDIF
254
255 C-- ICEFRONT parameters (BEGIN)
256 DO bj = myByLo(myThid), myByHi(myThid)
257 DO bi = myBxLo(myThid), myBxHi(myThid)
258 DO J = 1-OLy, sNy+OLy
259 DO I = 1-OLx, sNx+OLx
260 K_icefront(i,j,bi,bj) = 0
261 DO K = 1 , Nr
262 IF ( R_icefront(I,J,bi,bj) .GT. ABS(rF(K)))
263 & K_icefront(I,J,bi,bj) = K
264 ENDDO
265 fK_icefront(i,j,bi,bj) = 0.+K_icefront(i,j,bi,bj)
266 ENDDO
267 ENDDO
268 ENDDO
269 ENDDO
270 C-- ICEFRONT parameters (END)
271
272
273 C create masks for shelf-ice and ice-front by modifyig code from shelfice_thermodynamics.F
274 C-- minimum fraction of a cell adjacent to an ice front that must be
275 C-- wet for exchange to happen
276 epsilon_H = 1. _d -03
277
278 DO bj = myByLo(myThid), myByHi(myThid)
279 DO bi = myBxLo(myThid), myBxHi(myThid)
280
281 C-- First ice front then ice shelf. Loop through each i,j point
282 C-- process ice fronts in k, then process ice shelf.
283 DO J = 1, sNy
284 DO I = 1, sNx
285
286 C-- The K index where the ice front ends (0 if no ice front)
287 FRONT_K = K_icefront(I,J,bi,bj)
288
289 C-- If there is an ice front at this (I,J) continue
290 IF (FRONT_K .GT. 0) THEN
291
292 C-- Loop through all depths where the ice front is fround
293 DO K = 1, FRONT_K
294 C-- Loop around the four laterally neighboring cells of the ice front.
295 C-- If any neighboring points has wet volume in contact with the ice
296 C-- front at (I,J) then calculate ice-ocean exchanges.
297 C-- The four laterally neighboring point are at (CURI,CURJ)
298 DO SI = 1,4
299 IF (SI .EQ. 1) THEN
300 C-- Looking to right
301 CURI = I+1
302 CURJ = J
303
304 iceFrontWidth = dyG(I+1,J,bi,bj)
305
306 ELSEIF (SI .EQ. 2) THEN
307 C-- Looking to LEFT
308 CURI = I-1
309 CURJ = J
310
311 iceFrontWidth = dyG(I,J,bi,bj)
312 ELSEIF (SI .EQ. 3) THEN
313 C-- Looking to NORTH
314 CURI = I
315 CURJ = J+1
316
317 iceFrontWidth = dxG(I,J+1,bi,bj)
318 ELSEIF (SI .EQ. 4) THEN
319 C-- Looking to south
320 CURI = I
321 CURJ = J-1
322
323 iceFrontWidth = dxG(I,J,bi,bj)
324 endif
325
326 C-- cell depth describes the average distance
327 C-- perpendicular to the ice front fact
328
329 iceFrontCellThickness = RA(CURI,CURJ,bi,bj)
330 & /iceFrontWidth
331 iceFrontFaceArea = DRF(K)*iceFrontWidth
332
333 C-- First, make sure the adjacent point has at least some water in it.
334 IF (_hFacC(CURI,CURJ,K,bi,bj) .GT. zeroRL) THEN
335
336 C-- we need to determine how much of the ice front is in contact with
337 C-- water in the neighboring grid cell at this depth level.
338
339 C-- 1. Determine the top depth with water in the current cell
340 C-- 2. Determine the top depth with water in the neighbor cell
341 C-- 3. Determine the depth where water gap between (1) and (2).
342 C-- 4. If there is a gap then ice front is in contact with water in
343 C-- the neighboring cell
344
345 C-- ice_bottom_Z_C: the depth (m) of the bottom of the ice in the
346 C-- current cell. Bounded between rF(K) and rF(K+1).
347 C-- * If the ice extends past the bottom of the cell then
348 C-- ice_bottom_Z_C = rF(K+1)
349 C-- [rF(k) >= ice_bottom_Z_C >= rF(K+1)] (rF is negative)
350 ice_bottom_Z_C = max(rF(K+1),
351 & min(Ro_surf(I,J, bi,bj), rF(K)))
352
353 C-- wet_top_Z_N: the depth (m) of the bottom of the ice in the
354 C-- neighboring grid. If the neighboring cell has ice in
355 C-- (in the form of a shelf or front) then wet_top_Z_N is
356 C-- the depth of this neighboring ice.
357 C--
358 C-- * If neighbor cell has no ice, then Ro_surf = 0 and
359 C-- wet_top_Z_N = rF(K)
360 C-- [rF(k) >= wet_top_Z_N >= rF(K+1)] (rF is negative)
361
362 wet_top_Z_N = max(rF(K+1),
363 & min(Ro_surf(CURI,CURJ, bi,bj), rF(K)))
364
365 C-- wet_bottom_Z_N: the depth (m) of the bottom of the wet part of the
366 C-- neighboring cell. If the seafloor reaches into
367 C-- the grid cell then the bottom of the wet part of the
368 C-- grid cell is at the seafloor.
369 C--
370 C-- * If the seafloor is deeper than this grid cell then
371 C-- wet_bottom_Z = rF(K+1)
372 C-- * If the seafloor is shallower than this grid cell then
373 C-- wet_bottom_Z = rF(K)
374 C-- * If the seafloor reaches partly into this grid cell
375 C-- then wet_bottom_Z = R_low
376
377 C-- [rF(k) >= wet_bottom_Z >= rF(K+1)] (rF is negative)
378
379 wet_bottom_Z_N = min(rF(K),
380 & max(R_low(CURI,CURJ, bi,bj), rF(K+1)))
381
382 C-- iceFrontWetContact_Z_max: The deepest point where the
383 C-- the ice front at (I,J) is in contact with water
384 C-- in the neighboring cell. The shallower of
385 C-- wet_bottom_Z_N (seafloor depth of neighboring point) and
386 C-- ice_bottom_Z_C (bottom of ice front in this center cell).
387
388 C-- * wet_bottom_Z_N if the seafloor of the neighboring
389 C-- cell is shallower than the ice draft at (I,J).
390 C-- * ice_bottom_Z_C if the ice draft at (I,J) is shallower
391 C-- than the seafloor of the neighboring cell.
392
393 IF (ice_bottom_Z_C .GT. wet_bottom_Z_N) THEN
394 iceFrontWetContact_Z_max = ice_bottom_Z_C
395 ELSE
396 iceFrontWetContact_Z_max = wet_bottom_Z_N
397 ENDIF
398
399 C-- The shallowest depth where the ice front at (I,J) is in contact
400 C-- with water in the neighboring cell. If the neighboring cell has
401 C-- no ice draft then wet_top_Z_N = rF(k), the top of the cell.
402 C-- Otherwise, the shallowest depth where the ice front at (I,J) can
403 C-- be in in contact with water (not ice) in (CURI, CURJ)
404 C-- is wet_top_Z_N.
405
406 C-- the fraction of the grid cell height that has ice draft in contact
407 C-- with water in the neighboring cell.
408 iceFrontVertContactFrac =
409 & (wet_top_Z_N - iceFrontWetContact_Z_max)/ DRF(K)
410
411
412 C-- Only proceed if iceFrontVertContactFrac is > 0, the
413 C-- ice draft at (I,J)
414 C-- is in contact with some water in the neighboring grid cell.
415 IF (iceFrontVertContactFrac .GT. epsilon_H) THEN
416 mask3dSHIICF(CURI,CURJ,K,bi,bj) = 1. _d 0
417 mask2dSHIICF(CURI,CURJ,bi,bj) = 1. _d 0
418 mask3dICF(CURI,CURJ,K,bi,bj) = 1. _d 0
419 mask2dICF(CURI,CURJ,bi,bj) = 1. _d 0
420 ENDIF /* iceFrontVertContactFrac */
421 ENDIF /* hFacC(CURI,CURJ,K,bi,bj) */
422 ENDDO /* SI loop for adjacent cells */
423 ENDDO /* K LOOP */
424 ENDIF /* FRONT K */
425
426 C-- ice shelf
427 K = kTopC(I,J,bi,bj)
428
429 C-- If there is an ice front at this (I,J) continue
430 C-- I am assuming K is only .GT. when there is at least some
431 C-- nonzero wet point below the shelf in the grid cell.
432 IF (K .GT. 0) THEN
433 mask3dSHIICF(I,J,K,bi,bj) = 1. _d 0
434 mask2dSHIICF(I,J,bi,bj) = 1. _d 0
435 mask3dSHI(I,J,K,bi,bj) = 1. _d 0
436 mask2dSHI(I,J,bi,bj) = 1. _d 0
437 ENDIF /* SHELF K > 0 */
438 ENDDO /* i */
439 ENDDO /* j */
440 ENDDO /* bi */
441 ENDDO /* bj */
442
443 c fill in the hilos
444 _EXCH_XY_RS (mask2dSHIICF , myThid )
445 _EXCH_XY_RS (mask2dICF , myThid )
446 _EXCH_XY_RS (mask2dSHI , myThid )
447 _EXCH_XYZ_RS(mask3dSHIICF , myThid )
448 _EXCH_XYZ_RS(mask3dICF , myThid )
449 _EXCH_XYZ_RS(mask3dSHI , myThid )
450
451 C output the masks
452 CALL WRITE_FLD_XY_RS( 'mask2dSHIICF',' ',mask2dSHIICF,-1,myThid)
453 CALL WRITE_FLD_XYZ_RS( 'mask3dSHIICF',' ',mask3dSHIICF, 0,myThid)
454 CALL WRITE_FLD_XY_RS( 'mask2dSHI',' ',mask2dSHI,-1,myThid)
455 CALL WRITE_FLD_XYZ_RS( 'mask3dSHI',' ',mask3dSHI, 0,myThid)
456 CALL WRITE_FLD_XY_RS( 'mask2dICF',' ',mask2dICF,-1,myThid)
457 CALL WRITE_FLD_XYZ_RS( 'mask3dICF',' ',mask3dICF, 0,myThid)
458 CALL WRITE_FLD_XY_RS( 'R_icefront',' ',R_icefront,-1,myThid)
459 CALL WRITE_FLD_XY_RS( 'K_icefront',' ',fK_icefront,-1,myThid)
460
461 #ifdef ALLOW_DIAGNOSTICS
462 IF ( useDiagnostics ) THEN
463 diagName = 'SHIfwFlx'
464 diagTitle = 'Ice shelf fresh water flux (positive upward)'
465 diagUnits = 'kg/m^2/s '
466 diagCode = 'SM L1 '
467 CALL DIAGNOSTICS_ADDTOLIST( diagNum,
468 I diagName, diagCode, diagUnits, diagTitle, 0, myThid )
469
470 diagName = 'SHIhtFlx'
471 diagTitle = 'Ice shelf heat flux (positive upward)'
472 diagUnits = 'W/m^2 '
473 diagCode = 'SM L1 '
474 CALL DIAGNOSTICS_ADDTOLIST( diagNum,
475 I diagName, diagCode, diagUnits, diagTitle, 0, myThid )
476
477 diagName = 'SHIICFfwFlx'
478 diagTitle = 'total ice shelf and front FW flux (+ upward)'
479 diagUnits = 'kg/m^2/s '
480 diagCode = 'SM L1 '
481 CALL DIAGNOSTICS_ADDTOLIST( diagNum,
482 I diagName, diagCode, diagUnits, diagTitle, 0, myThid )
483
484 diagName = 'SHIICFhtFlx'
485 diagTitle = 'total ice shelf and ice front heat flux (+ upward)'
486 diagUnits = 'W/m^2 '
487 diagCode = 'SM L1 '
488 CALL DIAGNOSTICS_ADDTOLIST( diagNum,
489 I diagName, diagCode, diagUnits, diagTitle, 0, myThid )
490
491 diagName = 'ICFfwFlx'
492 diagTitle = 'Ice front freshwater flux (+ve increases ocean salt)'
493 diagUnits = 'kg/m^2/s '
494 diagCode = 'SM MR '
495 CALL DIAGNOSTICS_ADDTOLIST( diagNum,
496 I diagName, diagCode, diagUnits, diagTitle, 0, myThid )
497
498 diagName = 'ICFhtFlx'
499 diagTitle = 'Ice front heat flux (+ve cools ocean)'
500 diagUnits = 'W/m^2 '
501 diagCode = 'SM MR '
502 CALL DIAGNOSTICS_ADDTOLIST( diagNum,
503 I diagName, diagCode, diagUnits, diagTitle, 0, myThid )
504
505 diagName = 'SHITR '
506 diagTitle = 'Shelf ice passive tracer'
507 diagUnits = '1/s '
508 diagCode = 'SM MR '
509 CALL DIAGNOSTICS_ADDTOLIST( diagNum,
510 I diagName, diagCode, diagUnits, diagTitle, 0, myThid )
511
512 diagName = 'ICFTR '
513 diagTitle = 'Ice front passive tracer'
514 diagUnits = '1/s '
515 diagCode = 'SM MR '
516 CALL DIAGNOSTICS_ADDTOLIST( diagNum,
517 I diagName, diagCode, diagUnits, diagTitle, 0, myThid )
518
519 diagName = 'SHIUDrag'
520 diagTitle = 'U momentum tendency from ice shelf drag'
521 diagUnits = 'm/s^2 '
522 diagCode = 'UU MR '
523 diagMate = diagNum + 2
524 CALL DIAGNOSTICS_ADDTOLIST( diagNum,
525 I diagName, diagCode, diagUnits, diagTitle, diagMate, myThid )
526
527 diagName = 'SHIVDrag'
528 diagTitle = 'V momentum tendency from ice shelf drag'
529 diagUnits = 'm/s^2 '
530 diagCode = 'VV MR '
531 diagMate = diagNum
532 CALL DIAGNOSTICS_ADDTOLIST( diagNum,
533 I diagName, diagCode, diagUnits, diagTitle, diagMate, myThid )
534
535 diagName = 'SHIForcT'
536 diagTitle = 'Ice shelf forcing for theta, >0 increases theta'
537 diagUnits = 'W/m^2 '
538 diagCode = 'SM L1 '
539 CALL DIAGNOSTICS_ADDTOLIST( diagNum,
540 I diagName, diagCode, diagUnits, diagTitle, 0, myThid )
541
542 diagName = 'SHIForcS'
543 diagTitle = 'Ice shelf forcing for salt, >0 increases salt'
544 diagUnits = 'g/m^2/s '
545 diagCode = 'SM L1 '
546 CALL DIAGNOSTICS_ADDTOLIST( diagNum,
547 I diagName, diagCode, diagUnits, diagTitle, 0, myThid )
548
549 diagName = 'ICFForcT'
550 diagTitle = 'Ice front forcing for theta, >0 increases theta'
551 diagUnits = 'W/m^2 '
552 diagCode = 'SM MR '
553 CALL DIAGNOSTICS_ADDTOLIST( diagNum,
554 I diagName, diagCode, diagUnits, diagTitle, 0, myThid )
555
556 diagName = 'ICFForcS'
557 diagTitle = 'Ice front forcing for salt, >0 increases salt'
558 diagUnits = 'g/m^2/s '
559 diagCode = 'SM MR '
560 CALL DIAGNOSTICS_ADDTOLIST( diagNum,
561 I diagName, diagCode, diagUnits, diagTitle, 0, myThid )
562
563 diagName = 'SHIICFForcT'
564 diagTitle = 'total SHI and ICF forcing for T, >0 increases theta'
565 diagUnits = 'W/m^2 '
566 diagCode = 'SM L1 '
567 CALL DIAGNOSTICS_ADDTOLIST( diagNum,
568 I diagName, diagCode, diagUnits, diagTitle, 0, myThid )
569
570 diagName = 'SHIICFForcS'
571 diagTitle = 'total SHI and ICF forcing for S, >0 increases salt'
572 diagUnits = 'g/m^2/s '
573 diagCode = 'SM L1 '
574 CALL DIAGNOSTICS_ADDTOLIST( diagNum,
575 I diagName, diagCode, diagUnits, diagTitle, 0, myThid )
576 #ifndef ALLOW_shiTransCoeff_3d
577 diagName = 'SHIgammT'
578 diagTitle = 'Ice shelf exchange coefficient for theta'
579 diagUnits = 'm/s '
580 diagCode = 'SM L1 '
581 CALL DIAGNOSTICS_ADDTOLIST( diagNum,
582 I diagName, diagCode, diagUnits, diagTitle, 0, myThid )
583
584 diagName = 'SHIgammS'
585 diagTitle = 'Ice shelf exchange coefficient for salt'
586 diagUnits = 'm/s '
587 diagCode = 'SM L1 '
588 CALL DIAGNOSTICS_ADDTOLIST( diagNum,
589 I diagName, diagCode, diagUnits, diagTitle, 0, myThid )
590 #else
591 diagName = 'SHIgammT'
592 diagTitle = 'Ice shelf exchange coefficient for theta'
593 diagUnits = 'm/s '
594 diagCode = 'SMR MR '
595 CALL DIAGNOSTICS_ADDTOLIST( diagNum,
596 I diagName, diagCode, diagUnits, diagTitle, 0, myThid )
597
598 diagName = 'SHIgammS'
599 diagTitle = 'Ice shelf exchange coefficient for salt'
600 diagUnits = 'm/s '
601 diagCode = 'SMR MR '
602 CALL DIAGNOSTICS_ADDTOLIST( diagNum,
603 I diagName, diagCode, diagUnits, diagTitle, 0, myThid )
604 #endif
605
606
607
608 diagName = 'SHIuStar'
609 diagTitle = 'Friction velocity at bottom of ice shelf'
610 diagUnits = 'm/s '
611 diagCode = 'SM L1 '
612 CALL DIAGNOSTICS_ADDTOLIST( diagNum,
613 I diagName, diagCode, diagUnits, diagTitle, 0, myThid )
614
615 diagName = 'SHI_mass'
616 diagTitle = 'dynamic ice shelf mass for surface load anomaly'
617 diagUnits = 'kg/m^2 '
618 diagCode = 'SM L1 '
619 CALL DIAGNOSTICS_ADDTOLIST( diagNum,
620 I diagName, diagCode, diagUnits, diagTitle, 0, myThid )
621 ENDIF
622 #endif /* ALLOW_DIAGNOSTICS */
623 #endif /* ALLOW_SHELFICE */
624
625 RETURN
626 END

  ViewVC Help
Powered by ViewVC 1.1.22