/[MITgcm]/MITgcm/pkg/thsice/thsice_extend.F
ViewVC logotype

Contents of /MITgcm/pkg/thsice/thsice_extend.F

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


Revision 1.8 - (show annotations) (download)
Fri May 4 19:15:56 2007 UTC (17 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint62, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62l, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.7: +7 -5 lines
fix few little problems:
in thsice_calc_thickn.F:
 1) growth vertically (and not laterally) if iceFrac == iceMaskMax
 2) melt laterally only if hIce < hThinIce (as the comments say)
and in thsice_extend.F:
 3) allow to form ice even when iceFrac == iceMaskMax
     (by increasing thickness)
 4) start to form ice as soon as the minimum ice-volume is reachable.

1 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_extend.F,v 1.7 2007/05/01 02:37:44 jmc Exp $
2 C $Name: $
3
4 #include "THSICE_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: THSICE_EXTEND
8 C !INTERFACE:
9 SUBROUTINE THSICE_EXTEND(
10 I bi, bj, siLo, siHi, sjLo, sjHi,
11 I iMin,iMax, jMin,jMax, dBugFlag,
12 I fzMlOc, tFrz, tOce,
13 U icFrac, hIce, hSnow,
14 U tSrf, tIc1, tIc2, qIc1, qIc2,
15 O flx2oc, frw2oc, fsalt,
16 I myTime, myIter, myThid )
17 C !DESCRIPTION: \bv
18 C *==========================================================*
19 C | S/R THSICE_EXTEND
20 C | o Extend sea-ice area incresing ice fraction
21 C *==========================================================*
22 C | o incorporate surplus of energy to
23 C | make new ice or make ice grow laterally
24 C *==========================================================*
25 C \ev
26
27 C !USES:
28 IMPLICIT NONE
29
30 C == Global variables ==
31 #include "EEPARAMS.h"
32 #include "THSICE_SIZE.h"
33 #include "THSICE_PARAMS.h"
34 #ifdef ALLOW_AUTODIFF_TAMC
35 # include "SIZE.h"
36 # include "tamc.h"
37 # include "tamc_keys.h"
38 #endif
39
40 C !INPUT/OUTPUT PARAMETERS:
41 C == Routine Arguments ==
42 C siLo,siHi :: size of input/output array: 1rst dim. lower,higher bounds
43 C sjLo,sjHi :: size of input/output array: 2nd dim. lower,higher bounds
44 C bi,bj :: tile indices
45 C iMin,iMax :: computation domain: 1rst index range
46 C jMin,jMax :: computation domain: 2nd index range
47 C dBugFlag :: allow to print debugging stuff (e.g. on 1 grid point).
48 C--- Input:
49 C iceMask :: sea-ice fractional mask [0-1]
50 C fzMlOc (esurp) :: ocean mixed-layer freezing/melting potential [W/m2]
51 C tFrz (Tf) :: sea-water freezing temperature [oC] (function of S)
52 C tOce :: surface level oceanic temperature [oC]
53 C--- Modified (input&output):
54 C icFrac(iceFrac):: fraction of grid area covered in ice
55 C hIce (iceThick):: ice height [m]
56 C hSnow :: snow height [m]
57 C tSrf :: surface (ice or snow) temperature [oC]
58 C tIc1 :: temperature of ice layer 1 [oC]
59 C tIc2 :: temperature of ice layer 2 [oC]
60 C qIc1 (qicen) :: ice enthalpy (J/kg), 1rst level
61 C qIc2 (qicen) :: ice enthalpy (J/kg), 2nd level
62 C--- Output
63 C flx2oc (=) :: (additional) heat flux to ocean [W/m2] (+=dwn)
64 C frw2oc (=) :: (additional) fresh water flux to ocean [kg/m2/s] (+=dwn)
65 C fsalt (=) :: (additional) salt flux to ocean [g/m2/s] (+=dwn)
66 C--- Input:
67 C myTime :: current Time of simulation [s]
68 C myIter :: current Iteration number in simulation
69 C myThid :: my Thread Id number
70 INTEGER siLo, siHi, sjLo, sjHi
71 INTEGER bi,bj
72 INTEGER iMin, iMax
73 INTEGER jMin, jMax
74 LOGICAL dBugFlag
75 c _RL iceMask(siLo:siHi,sjLo:sjHi)
76 _RL fzMlOc (siLo:siHi,sjLo:sjHi)
77 _RL tFrz (siLo:siHi,sjLo:sjHi)
78 _RL tOce (siLo:siHi,sjLo:sjHi)
79 _RL icFrac (siLo:siHi,sjLo:sjHi)
80 _RL hIce (siLo:siHi,sjLo:sjHi)
81 _RL hSnow (siLo:siHi,sjLo:sjHi)
82 _RL tSrf (siLo:siHi,sjLo:sjHi)
83 _RL tIc1 (siLo:siHi,sjLo:sjHi)
84 _RL tIc2 (siLo:siHi,sjLo:sjHi)
85 _RL qIc1 (siLo:siHi,sjLo:sjHi)
86 _RL qIc2 (siLo:siHi,sjLo:sjHi)
87 _RL flx2oc (siLo:siHi,sjLo:sjHi)
88 _RL frw2oc (siLo:siHi,sjLo:sjHi)
89 _RL fsalt (siLo:siHi,sjLo:sjHi)
90 _RL myTime
91 INTEGER myIter
92 INTEGER myThid
93 CEOP
94
95 #ifdef ALLOW_THSICE
96 C !LOCAL VARIABLES:
97 C--- local copy of input/output argument list variables (see description above)
98 _RL esurp
99 _RL Tf
100 _RL iceFrac
101 _RL iceThick
102 _RL qicen(nlyr)
103
104 C == Local variables ==
105 C iceVol :: previous ice volume
106 C newIce :: new ice volume to produce
107 C hNewIce :: thickness of new ice to form
108 C iceFormed :: ice-volume formed (new ice volume = iceVol+iceFormed )
109 C qicAv :: mean enthalpy of ice (layer 1 & 2) [J/m^3]
110 _RL deltaTice ! time-step for ice model
111 _RL iceVol
112 _RL newIce
113 _RL hNewIce
114 _RL iceFormed
115 _RL qicAv
116 INTEGER i,j ! loop indices
117
118 C- define grid-point location where to print debugging values
119 #include "THSICE_DEBUG.h"
120
121 1010 FORMAT(A,I3,3F8.3)
122 1020 FORMAT(A,1P4E11.3)
123
124 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
125
126 #ifdef ALLOW_AUTODIFF_TAMC
127 act1 = bi - myBxLo(myThid)
128 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
129 act2 = bj - myByLo(myThid)
130 max2 = myByHi(myThid) - myByLo(myThid) + 1
131 act3 = myThid - 1
132 max3 = nTx*nTy
133 act4 = ikey_dynamics - 1
134 #endif /* ALLOW_AUTODIFF_TAMC */
135
136 deltaTice = thSIce_deltaT
137
138 DO j = jMin, jMax
139 DO i = iMin, iMax
140 #ifdef ALLOW_AUTODIFF_TAMC
141 ikey_1 = i
142 & + sNx*(j-1)
143 & + sNx*sNy*act1
144 & + sNx*sNy*max1*act2
145 & + sNx*sNy*max1*max2*act3
146 & + sNx*sNy*max1*max2*max3*act4
147 #endif /* ALLOW_AUTODIFF_TAMC */
148 C--
149 #ifdef ALLOW_AUTODIFF_TAMC
150 CADJ STORE hice(i,j) = comlev1_thsice_1, key=ikey_1
151 CADJ STORE hsnow(i,j) = comlev1_thsice_1, key=ikey_1
152 CADJ STORE icfrac(i,j) = comlev1_thsice_1, key=ikey_1
153 CADJ STORE qic1(i,j) = comlev1_thsice_1, key=ikey_1
154 CADJ STORE qic2(i,j) = comlev1_thsice_1, key=ikey_1
155 #endif
156
157 IF (fzMlOc(i,j).GT.0. _d 0) THEN
158 esurp = fzMlOc(i,j)
159 Tf = tFrz(i,j)
160 iceFrac = icFrac(i,j)
161 iceThick= hIce(i,j)
162 qicen(1)= qIc1(i,j)
163 qicen(2)= qIc2(i,j)
164 C---
165 C-- start ice
166 iceFormed = 0. _d 0
167 iceVol = iceFrac*iceThick
168
169 C- enthalpy of new ice to form :
170 IF ( iceFrac.LE.0. _d 0 ) THEN
171 qicen(1)= -cpWater*Tmlt1
172 & + cpIce *(Tmlt1-Tf) + Lfresh*(1. _d 0-Tmlt1/Tf)
173 qicen(2)= -cpIce *Tf + Lfresh
174 ENDIF
175 qicAv = rhoi*(qicen(1)+qicen(2))*0.5 _d 0
176 newIce = esurp*deltaTice/qicAv
177
178 IF ( icFrac(i,j).EQ.0. _d 0 ) THEN
179 C- to keep identical results (as it use to be):
180 c-old_v IF ( newIce.GE.hThinIce*iceMaskMin ) THEN
181 C- here we allow to form ice earlier (as soon as min-ice-vol is reached)
182 c-new_v:
183 IF ( newIce.GT.hIceMin*iceMaskMin ) THEN
184 C- if there is no ice in grid-cell and enough ice to form:
185 C- make ice over iceMaskMin fraction, up to hThinIce,
186 C and if more ice to form, then increase fraction
187 iceThick = MIN(hThinIce,newIce/iceMaskMin)
188 iceThick = MAX(iceThick,newIce/iceMaskMax)
189 iceFrac = newIce/iceThick
190 iceFormed = newIce
191 ENDIF
192 ELSEIF ( iceVol.LT.hiMax*iceMaskMax ) THEN
193 C- if there is already some ice
194 C create ice with same thickness or hNewIceMax (the smallest of the 2)
195 hNewIce = MIN(iceThick,hNewIceMax)
196 iceFrac = MIN(icFrac(i,j)+newIce/hNewIce,iceMaskMax)
197 C- update thickness: area weighted average
198 c-new_v:
199 iceThick = MIN(hiMax,(iceVol+newIce)/iceFrac)
200 C- to keep identical results: comment the line above and uncomment line below:
201 c-old_v iceFrac = MIN(icFrac(i,j)+newIce/iceThick,iceMaskMax)
202 iceFormed = iceThick*iceFrac - iceVol
203 C- spread snow out over ice
204 hSnow(i,j) = hSnow(i,j)*icFrac(i,j)/iceFrac
205 ENDIF
206 C- oceanic fluxes:
207 flx2oc(i,j)= qicAv*iceFormed/deltaTice
208 frw2oc(i,j)= -rhoi*iceFormed/deltaTice
209 fsalt(i,j)= -(rhoi*saltIce)*iceFormed/deltaTice
210
211 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
212 #ifdef ALLOW_DBUG_THSICE
213 IF ( dBug(i,j,bi,bj) ) THEN
214 WRITE(6,1020) 'ThSI_EXT: iceH, newIce, newIceFrac=',
215 & iceThick, newIce, iceFrac-icFrac(i,j)
216 WRITE(6,1020) 'ThSI_EXT: iceFrac,flx2oc,fsalt,frw2oc=',
217 & iceFrac,flx2oc(i,j),fsalt(i,j),frw2oc(i,j)
218 ENDIF
219 #endif
220 #ifdef CHECK_ENERGY_CONSERV
221 CALL THSICE_CHECK_CONSERV( dBugFlag, i, j, bi, bj, 1,
222 I icFrac(i,j), iceFrac, iceThick, hSnow(i,j), qicen,
223 I flx2oc(i,j), frw2oc(i,j), fsalt(i,j),
224 I myTime, myIter, myThid )
225 #endif /* CHECK_ENERGY_CONSERV */
226 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
227 C-- Update Sea-Ice state output:
228 IF ( iceFrac.GT.0. _d 0 .AND. icFrac(i,j).EQ.0. _d 0) THEN
229 c hSnow(i,j) = 0. _d 0
230 tSrf(i,j) = tFrz(i,j)
231 tIc1(i,j) = tFrz(i,j)
232 tIc2(i,j) = tFrz(i,j)
233 qIc1(i,j) = qicen(1)
234 qIc2(i,j) = qicen(2)
235 ENDIF
236 icFrac(i,j) = iceFrac
237 hIce(i,j) = iceThick
238 ENDIF
239 ENDDO
240 ENDDO
241
242 #endif /* ALLOW_THSICE */
243
244 RETURN
245 END

  ViewVC Help
Powered by ViewVC 1.1.22