/[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.12 - (show annotations) (download)
Fri Dec 17 04:00:14 2010 UTC (13 years, 4 months ago) by gforget
Branch: MAIN
CVS Tags: checkpoint63h, checkpoint63i, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.11: +7 -7 lines
rename iicekey as ticekey to avoid conflict with pkg/seaice

1 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_extend.F,v 1.11 2010/10/21 19:03:31 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,
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 1010 FORMAT(A,I3,3F8.3)
119 1020 FORMAT(A,1P4E11.3)
120
121 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
122
123 #ifdef ALLOW_AUTODIFF_TAMC
124 act1 = bi - myBxLo(myThid)
125 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
126 act2 = bj - myByLo(myThid)
127 max2 = myByHi(myThid) - myByLo(myThid) + 1
128 act3 = myThid - 1
129 max3 = nTx*nTy
130 act4 = ikey_dynamics - 1
131 ticekey = (act1 + 1) + act2*max1
132 & + act3*max1*max2
133 & + act4*max1*max2*max3
134 #endif /* ALLOW_AUTODIFF_TAMC */
135
136 deltaTice = thSIce_deltaT
137
138 #ifdef ALLOW_AUTODIFF_TAMC
139 CADJ STORE hIce(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
140 CADJ STORE hSnow(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
141 CADJ STORE icFrac(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
142 CADJ STORE qIc1(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
143 CADJ STORE qIc2(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
144 #endif
145 DO j = jMin, jMax
146 DO i = iMin, iMax
147 c#ifdef ALLOW_AUTODIFF_TAMC
148 c ikey_1 = i
149 c & + sNx*(j-1)
150 c & + sNx*sNy*act1
151 c & + sNx*sNy*max1*act2
152 c & + sNx*sNy*max1*max2*act3
153 c & + sNx*sNy*max1*max2*max3*act4
154 c#endif /* ALLOW_AUTODIFF_TAMC */
155 c#ifdef ALLOW_AUTODIFF_TAMC
156 cCADJ STORE hice(i,j) = comlev1_thsice_1, key=ikey_1
157 cCADJ STORE hsnow(i,j) = comlev1_thsice_1, key=ikey_1
158 cCADJ STORE icfrac(i,j) = comlev1_thsice_1, key=ikey_1
159 cCADJ STORE qic1(i,j) = comlev1_thsice_1, key=ikey_1
160 cCADJ STORE qic2(i,j) = comlev1_thsice_1, key=ikey_1
161 c#endif
162
163 IF (fzMlOc(i,j).GT.0. _d 0) THEN
164 esurp = fzMlOc(i,j)
165 Tf = tFrz(i,j)
166 iceFrac = icFrac(i,j)
167 iceThick= hIce(i,j)
168 qicen(1)= qIc1(i,j)
169 qicen(2)= qIc2(i,j)
170 C---
171 C-- start ice
172 iceFormed = 0. _d 0
173 iceVol = iceFrac*iceThick
174
175 C- enthalpy of new ice to form :
176 IF ( iceFrac.LE.0. _d 0 ) THEN
177 qicen(1)= -cpWater*Tmlt1
178 & + cpIce *(Tmlt1-Tf) + Lfresh*(1. _d 0-Tmlt1/Tf)
179 qicen(2)= -cpIce *Tf + Lfresh
180 ENDIF
181 qicAv = rhoi*(qicen(1)+qicen(2))*0.5 _d 0
182 newIce = esurp*deltaTice/qicAv
183
184 IF ( icFrac(i,j).EQ.0. _d 0 ) THEN
185 C- to keep identical results (as it use to be):
186 c-old_v IF ( newIce.GE.hThinIce*iceMaskMin ) THEN
187 C- here we allow to form ice earlier (as soon as min-ice-vol is reached)
188 c-new_v:
189 IF ( newIce.GT.hIceMin*iceMaskMin ) THEN
190 C- if there is no ice in grid-cell and enough ice to form:
191 C- make ice over iceMaskMin fraction, up to hThinIce,
192 C and if more ice to form, then increase fraction
193 iceThick = MIN(hThinIce,newIce/iceMaskMin)
194 iceThick = MAX(iceThick,newIce/iceMaskMax)
195 iceFrac = newIce/iceThick
196 iceFormed = newIce
197 ENDIF
198 ELSEIF ( iceVol.LT.hiMax*iceMaskMax ) THEN
199 C- if there is already some ice
200 C create ice with same thickness or hNewIceMax (the smallest of the 2)
201 hNewIce = MIN(iceThick,hNewIceMax)
202 iceFrac = MIN(icFrac(i,j)+newIce/hNewIce,iceMaskMax)
203 C- update thickness: area weighted average
204 c-new_v:
205 iceThick = MIN(hiMax,(iceVol+newIce)/iceFrac)
206 C- to keep identical results: comment the line above and uncomment line below:
207 c-old_v iceFrac = MIN(icFrac(i,j)+newIce/iceThick,iceMaskMax)
208 iceFormed = iceThick*iceFrac - iceVol
209 C- spread snow out over ice
210 hSnow(i,j) = hSnow(i,j)*icFrac(i,j)/iceFrac
211 ENDIF
212 C- oceanic fluxes:
213 flx2oc(i,j)= qicAv*iceFormed/deltaTice
214 frw2oc(i,j)= -rhoi*iceFormed/deltaTice
215 fsalt(i,j)= -(rhoi*saltIce)*iceFormed/deltaTice
216
217 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
218 #ifdef ALLOW_DBUG_THSICE
219 IF ( dBug(i,j,bi,bj) ) THEN
220 WRITE(6,1020) 'ThSI_EXT: iceH, newIce, newIceFrac=',
221 & iceThick, newIce, iceFrac-icFrac(i,j)
222 WRITE(6,1020) 'ThSI_EXT: iceFrac,flx2oc,fsalt,frw2oc=',
223 & iceFrac,flx2oc(i,j),fsalt(i,j),frw2oc(i,j)
224 ENDIF
225 #endif
226 #ifdef CHECK_ENERGY_CONSERV
227 CALL THSICE_CHECK_CONSERV( dBugFlag, i, j, bi, bj, 1,
228 I icFrac(i,j), iceFrac, iceThick, hSnow(i,j), qicen,
229 I flx2oc(i,j), frw2oc(i,j), fsalt(i,j),
230 I myTime, myIter, myThid )
231 #endif /* CHECK_ENERGY_CONSERV */
232 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
233 C-- Update Sea-Ice state output:
234 IF ( iceFrac.GT.0. _d 0 .AND. icFrac(i,j).EQ.0. _d 0) THEN
235 c hSnow(i,j) = 0. _d 0
236 tSrf(i,j) = tFrz(i,j)
237 tIc1(i,j) = tFrz(i,j)
238 tIc2(i,j) = tFrz(i,j)
239 qIc1(i,j) = qicen(1)
240 qIc2(i,j) = qicen(2)
241 ENDIF
242 icFrac(i,j) = iceFrac
243 hIce(i,j) = iceThick
244 ENDIF
245 ENDDO
246 ENDDO
247
248 #endif /* ALLOW_THSICE */
249
250 RETURN
251 END

  ViewVC Help
Powered by ViewVC 1.1.22