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

Annotation of /MITgcm/pkg/thsice/thsice_step_fwd.F

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


Revision 1.1 - (hide annotations) (download)
Sun Nov 23 01:20:13 2003 UTC (20 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: branch-netcdf, checkpoint52d_pre, checkpoint52d_post, checkpoint52b_post, checkpoint52c_post
Branch point for: netcdf-sm0
new pkg "thSIce" (replace therm_seaice).

1 jmc 1.1 C $Header: $
2     C $Name: $
3    
4     #include "THSICE_OPTIONS.h"
5    
6     C !ROUTINE: THSICE_STEP_FWD
7     C !INTERFACE:
8     SUBROUTINE THSICE_STEP_FWD(
9     I bi, bj, iMin, iMax, jMin, jMax,
10     I myTime, myIter, myThid )
11     C *==========================================================*
12     C | SUBROUTINE THSICE_STEP_FWD
13     C | o Step Forward Therm-SeaIce model.
14     C *==========================================================*
15    
16     C !USES:
17     IMPLICIT NONE
18     C === Global variables ===
19     #include "SIZE.h"
20     #include "EEPARAMS.h"
21     #include "PARAMS.h"
22     #include "FFIELDS.h"
23     #include "DYNVARS.h"
24     #include "GRID.h"
25     #ifdef ALLOW_BULK_FORCE
26     #include "BULKF.h"
27     #endif
28     #include "THSICE_SIZE.h"
29     #include "THSICE_PARAMS.h"
30     #include "THSICE.h"
31     #include "THSICE_DIAGS.h"
32    
33     C !INPUT/OUTPUT PARAMETERS:
34     C === Routine arguments ===
35     C myIter :: iteration counter for this thread
36     C myTime :: time counter for this thread
37     C myThid :: thread number for this instance of the routine.
38     INTEGER bi,bj
39     INTEGER iMin, iMax
40     INTEGER jMin, jMax
41     _RL myTime
42     INTEGER myIter
43     INTEGER myThid
44    
45     #ifdef ALLOW_THSICE
46     C !LOCAL VARIABLES:
47     C === Local variables ===
48     C Fbot :: the oceanic heat flux already incorporated (ice_therm)
49     C flxAtm :: net heat flux from the atmosphere ( >0 downward)
50     C evpAtm :: evaporation to the atmosphere
51     C frwAtm :: net fresh-water flux (E-P-R) to the atmosphere (m/s)
52     C qleft :: net heat flux from the ice to the ocean
53     C ffresh :: fresh-water flux from the ice to the ocean
54     C fsalt :: mass salt flux to the ocean
55     INTEGER i,j
56     _RL fswdown, qleft, qNewIce
57     _RL fsalt
58     _RL ffresh
59     _RL Tf, cphm, frzmlt
60     _RL Fbot, esurp
61     _RL flxAtm, evpAtm, frwAtm
62     _RL openFrac, iceFrac, qicAv
63     _RL oceHs, oceV2s, oceSs, oceTs
64     _RL compact, hIce, hSnow, Tsf, Tice(nlyr), qicen(nlyr)
65    
66     LOGICAL dBug
67    
68     dBug = .FALSE.
69     1010 FORMAT(A,1P4E11.3)
70    
71     DO j = jMin, jMax
72     DO i = iMin, iMax
73     c dBug = ( bi.EQ.3 .AND. i.EQ.13 .AND. j.EQ.13 )
74    
75     Tf = -mu_Tf*salt(i,j,1,bi,bj)
76     cphm = cpwater*rhosw*drF(1)*hFacC(i,j,1,bi,bj)
77     frzmlt = (Tf-theta(i,j,1,bi,bj))*cphm/thSIce_deltaT
78     Fbot = 0. _d 0
79     compact= 0. _d 0
80     snow(i,j,bi,bj) = 0. _d 0
81     saltFlux(i,j,bi,bj) = 0. _d 0
82    
83     IF (dBug.AND.(frzmlt.GT.0. .OR.iceMask(i,j,bi,bj).GT.0.)) THEN
84     WRITE(6,1010) 'ThSI_FWD:-0- iceMask,hIc,hSn,Qnet=',
85     & iceMask(i,j,bi,bj),iceHeight(i,j,bi,bj),
86     & snowHeight(i,j,bi,bj), Qnet(i,j,bi,bj)
87     WRITE(6,1010) 'ThSI_FWD: ocTs,Tf,frzmlt=',
88     & theta(i,j,1,bi,bj),Tf,frzmlt
89     ENDIF
90    
91     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
92     C part.1 : ice-covered fraction ;
93     C can only reduce the ice-fraction but not increase it.
94     C-------
95     IF (iceMask(i,j,bi,bj).GT.0. _d 0) THEN
96     fswdown = solar(i,j,bi,bj)
97     oceHs = hfacC(i,j,1,bi,bj)*drF(1)
98     oceTs = theta(i,j,1,bi,bj)
99     oceSs = salt (i,j,1,bi,bj)
100     oceV2s = ( uvel(i,j,1,bi,bj)*uvel(i,j,1,bi,bj)
101     & + uvel(i+1,j,1,bi,bj)*uvel(i+1,j,1,bi,bj)
102     & + vvel(i,j+1,1,bi,bj)*vvel(i,j+1,1,bi,bj)
103     & + vvel(i,j,1,bi,bj)*vvel(i,j,1,bi,bj) )*0.5 _d 0
104     compact = iceMask(i,j,bi,bj)
105     hIce = iceHeight(i,j,bi,bj)
106     hSnow = snowHeight(i,j,bi,bj)
107     Tsf = Tsrf(i,j,bi,bj)
108     Tice(1) = Tice1(i,j,bi,bj)
109     Tice(2) = Tice2(i,j,bi,bj)
110     qicen(1)= Qice1(i,j,bi,bj)
111     qicen(2)= Qice2(i,j,bi,bj)
112     CALL THSICE_THERM(
113     I fswdown, oceHs, oceV2s, oceSs, oceTs,
114     U compact, hIce, hSnow, Tsf, Tice, qicen,
115     O qleft, ffresh, fsalt, Fbot,
116     O flxAtm, evpAtm,
117     I i,j, bi,bj, myThid)
118    
119     C-- Diagnostic of Atmospheric Fluxes over sea-ice :
120     frwAtm = evpAtm - snow(i,j,bi,bj)*rhos/rhofw
121     C note: Any flux of mass (here fresh water) that enter or leave the system
122     C with a non zero energy HAS TO be counted: add snow precip.
123     flxAtm = flxAtm - Lfresh*snow(i,j,bi,bj)*rhos
124    
125     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
126     IF (dBug) WRITE(6,1010) 'ThSI_FWD: iceFrac,flxAtm,evpAtm,flxSnw=',
127     & iceMask(i,j,bi,bj),flxAtm,evpAtm,-Lfresh*snow(i,j,bi,bj)*rhos
128     IF (dBug) WRITE(6,1010) 'ThSI_FWD: compact,qleft,fsalt,ffresh=',
129     & compact,qleft,fsalt,ffresh
130     #ifdef CHECK_ENERGY_CONSERV
131     iceFrac = iceMask(i,j,bi,bj)
132     CALL THSICE_CHECK_CONSERV( dBug, i, j, bi, bj, 0,
133     I iceFrac, compact, hIce, hSnow, qicen,
134     I qleft, ffresh, fsalt, flxAtm, frwAtm,
135     I myTime, myIter, myThid )
136     #endif /* CHECK_ENERGY_CONSERV */
137     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
138    
139     C-- Update Sea-Ice state :
140     c theta(i,j,1,bi,bj) = oceTs
141     c iceMask(i,j,bi,bj)=compact
142     iceheight(i,j,bi,bj) = hIce
143     snowheight(i,j,bi,bj)= hSnow
144     Tsrf(i,j,bi,bj) =Tsf
145     Tice1(i,j,bi,bj)=Tice(1)
146     Tice2(i,j,bi,bj)=Tice(2)
147     Qice1(i,j,bi,bj)=qicen(1)
148     Qice2(i,j,bi,bj)=qicen(2)
149    
150     C-- Net fluxes :
151     ffresh = ffresh/rhofw
152     ffresh = -ffresh-rain(i,j,bi,bj)-runoff(i,j,bi,bj)
153     frwAtm = frwAtm-rain(i,j,bi,bj)-runoff(i,j,bi,bj)
154     iceFrac = iceMask(i,j,bi,bj)
155     openFrac= 1. _d 0-iceFrac
156     #ifdef ALLOW_TIMEAVE
157     ICE_Qnet_AVE(i,j,bi,bj) = ICE_Qnet_AVE(i,j,bi,bj)
158     & + ( -iceFrac*flxAtm + openFrac*Qnet(i,j,bi,bj)
159     & )*thSIce_deltaT
160     ICE_FWfx_AVE(i,j,bi,bj) = ICE_FWfx_AVE(i,j,bi,bj)
161     & + ( iceFrac*frwAtm + openFrac*EmPmR(i,j,bi,bj)
162     & )*thSIce_deltaT
163     #endif /*ALLOW_TIMEAVE*/
164     Qnet(i,j,bi,bj)=-iceFrac*qleft + openFrac*Qnet(i,j,bi,bj)
165     EmPmR(i,j,bi,bj)=iceFrac*ffresh+openFrac*EmPmR(i,j,bi,bj)
166     saltFlux(i,j,bi,bj)=-iceFrac*fsalt
167    
168     IF (dBug) WRITE(6,1010)'ThSI_FWD:-1- compact,hIc,hSn,Qnet=',
169     & compact,hIce,hSnow,Qnet(i,j,bi,bj)
170    
171     ELSEIF (hFacC(i,j,1,bi,bj).gt.0. _d 0) THEN
172    
173     #ifdef ALLOW_TIMEAVE
174     ICE_Qnet_AVE(i,j,bi,bj) = ICE_Qnet_AVE(i,j,bi,bj)
175     & +Qnet(i,j,bi,bj)*thSIce_deltaT
176     ICE_FWfx_AVE(i,j,bi,bj) = ICE_FWfx_AVE(i,j,bi,bj)
177     & +EmPmR(i,j,bi,bj)*thSIce_deltaT
178     #endif /*ALLOW_TIMEAVE*/
179    
180     ENDIF
181    
182     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
183     C part.2 : freezing of sea-water
184     C over ice-free fraction and what is left from ice-covered fraction
185     C-------
186     esurp = frzmlt - Fbot*iceMask(i,j,bi,bj)
187     IF (esurp.GT.0. _d 0) THEN
188     iceFrac = compact
189     IF ( compact.GT.0. _d 0 ) THEN
190     qicen(1)= Qice1(i,j,bi,bj)
191     qicen(2)= Qice2(i,j,bi,bj)
192     ELSE
193     qicen(1)= -cpwater*Tmlt1
194     & + cpice *(Tmlt1-Tf) + Lfresh*(1. _d 0-Tmlt1/Tf)
195     qicen(2)= -cpice *Tf + Lfresh
196     ENDIF
197     qicAv = rhoi*(qicen(1)+qicen(2))*0.5 _d 0
198     oceTs = theta(i,j,1,bi,bj)
199     hIce = iceHeight(i,j,bi,bj)
200     hSnow = snowHeight(i,j,bi,bj)
201     CALL THSICE_START( myThid,
202     I esurp, qicAv, Tf,
203     O qNewIce, ffresh, fsalt,
204     U oceTs, compact, hIce, hSnow )
205     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
206     IF (dBug) WRITE(6,1010) 'ThSI_FWD: compact,qNewIce,fsalt,ffresh='
207     & ,compact,qNewIce,fsalt,ffresh
208     #ifdef CHECK_ENERGY_CONSERV
209     flxAtm = 0.
210     frwAtm = 0.
211     CALL THSICE_CHECK_CONSERV( dBug, i, j, bi, bj, 1,
212     I iceFrac, compact, hIce, hSnow, qicen,
213     I qNewIce, ffresh, fsalt, flxAtm, frwAtm,
214     I myTime, myIter, myThid )
215     #endif /* CHECK_ENERGY_CONSERV */
216     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
217     C-- Update Sea-Ice state :
218     IF ( compact.GT.0. _d 0 .AND. iceFrac.EQ.0. _d 0) THEN
219     Tsrf(i,j,bi,bj) = Tf
220     Tice1(i,j,bi,bj) = Tf
221     Tice2(i,j,bi,bj) = Tf
222     Qice1(i,j,bi,bj) = qicen(1)
223     Qice2(i,j,bi,bj) = qicen(2)
224     c theta(i,j,1,bi,bj)= oceTs
225     ENDIF
226     iceheight(i,j,bi,bj) = hIce
227     snowheight(i,j,bi,bj)= hSnow
228     C-- Net fluxes :
229     Qnet(i,j,bi,bj) = Qnet(i,j,bi,bj) - qNewIce
230     EmPmR(i,j,bi,bj)= EmPmR(i,j,bi,bj)- ffresh/rhofw
231     saltFlux(i,j,bi,bj)=saltFlux(i,j,bi,bj) - fsalt
232    
233     IF (dBug) WRITE(6,1010)'ThSI_FWD:-2- compact,hIc,hSn,Qnet=',
234     & compact,hIce,hSnow,Qnet(i,j,bi,bj)
235     C-- - if esurp > 0 : end
236     ENDIF
237    
238     IF ( compact .GT. 0. _d 0 ) THEN
239     iceMask(i,j,bi,bj)=compact
240     ELSE
241     iceMask(i,j,bi,bj) = 0. _d 0
242     iceHeight(i,j,bi,bj)= 0. _d 0
243     snowHeight(i,j,bi,bj)=0. _d 0
244     Tsrf(i,j,bi,bj)=theta(i,j,1,bi,bj)
245     Tice1(i,j,bi,bj) = 0. _d 0
246     Tice2(i,j,bi,bj) = 0. _d 0
247     Qice1(i,j,bi,bj) = 0. _d 0
248     Qice2(i,j,bi,bj) = 0. _d 0
249     ENDIF
250    
251     #ifndef CHECK_ENERGY_CONSERV
252     #ifdef ALLOW_TIMEAVE
253     ICE_qleft_AVE(i,j,bi,bj)=ICE_qleft_AVE(i,j,bi,bj)
254     & + ( Qnet(i,j,bi,bj)
255     & )*thSIce_deltaT
256     ICE_fresh_AVE(i,j,bi,bj)=ICE_fresh_AVE(i,j,bi,bj)
257     & + ( EmPmR(i,j,bi,bj)
258     & )*thSIce_deltaT
259     ICE_salFx_AVE(i,j,bi,bj)=ICE_salFx_AVE(i,j,bi,bj)
260     & +saltFlux(i,j,bi,bj)*thSIce_deltaT
261     #endif /* ALLOW_TIMEAVE */
262     #endif /* CHECK_ENERGY_CONSERV */
263    
264     ENDDO
265     ENDDO
266    
267     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
268     #endif /* ALLOW_THSICE */
269    
270     RETURN
271     END

  ViewVC Help
Powered by ViewVC 1.1.22