/[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.14 - (show annotations) (download)
Sun Jan 19 14:47:35 2014 UTC (10 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, 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.13: +1 -2 lines
- avoid unused labels

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

  ViewVC Help
Powered by ViewVC 1.1.22