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

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

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

revision 1.1 by jmc, Sun Nov 23 01:20:13 2003 UTC revision 1.23 by jscott, Fri Apr 20 19:24:47 2007 UTC
# Line 2  C $Header$ Line 2  C $Header$
2  C $Name$  C $Name$
3    
4  #include "THSICE_OPTIONS.h"  #include "THSICE_OPTIONS.h"
5    #ifdef ALLOW_ATM2D
6    # include "ctrparam.h"
7    #endif
8    
9    CBOP
10  C     !ROUTINE: THSICE_STEP_FWD  C     !ROUTINE: THSICE_STEP_FWD
11  C     !INTERFACE:  C     !INTERFACE:
12        SUBROUTINE THSICE_STEP_FWD(        SUBROUTINE THSICE_STEP_FWD(
13       I             bi, bj, iMin, iMax, jMin, jMax,       I             bi, bj, iMin, iMax, jMin, jMax,
14         I             prcAtm,
15       I             myTime, myIter, myThid )       I             myTime, myIter, myThid )
16    C     !DESCRIPTION: \bv
17  C     *==========================================================*  C     *==========================================================*
18  C     | SUBROUTINE  THSICE_STEP_FWD              C     | S/R  THSICE_STEP_FWD
19  C     | o Step Forward Therm-SeaIce model.  C     | o Step Forward Therm-SeaIce model.
20  C     *==========================================================*  C     *==========================================================*
21    C     \ev
22    
23  C     !USES:  C     !USES:
24        IMPLICIT NONE        IMPLICIT NONE
25    
26  C     === Global variables ===  C     === Global variables ===
27  #include "SIZE.h"  #include "SIZE.h"
28  #include "EEPARAMS.h"  #include "EEPARAMS.h"
29  #include "PARAMS.h"  #include "PARAMS.h"
30  #include "FFIELDS.h"  #include "FFIELDS.h"
31  #include "DYNVARS.h"  #ifdef  ALLOW_ATM2D
32  #include "GRID.h"  # include "ATMSIZE.h"
33  #ifdef ALLOW_BULK_FORCE  # include "ATM2D_VARS.h"
 #include "BULKF.h"  
34  #endif  #endif
35  #include "THSICE_SIZE.h"  #include "THSICE_SIZE.h"
36  #include "THSICE_PARAMS.h"  #include "THSICE_PARAMS.h"
37  #include "THSICE.h"  #include "THSICE_VARS.h"
38  #include "THSICE_DIAGS.h"  #include "THSICE_TAVE.h"
39    #include "THSICE_2DYN.h"
40    #ifdef ALLOW_AUTODIFF_TAMC
41    # include "tamc.h"
42    # include "tamc_keys.h"
43    #endif
44    
45          INTEGER siLo, siHi, sjLo, sjHi
46          PARAMETER ( siLo = 1-OLx , siHi = sNx+OLx )
47          PARAMETER ( sjLo = 1-OLy , sjHi = sNy+OLy )
48    
49  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
50  C     === Routine arguments ===  C     === Routine arguments ===
51  C     myIter :: iteration counter for this thread  C- input:
52  C     myTime :: time counter for this thread  C     bi,bj   :: tile indices
53  C     myThid :: thread number for this instance of the routine.  C   iMin,iMax :: computation domain: 1rst index range
54    C   jMin,jMax :: computation domain: 2nd  index range
55    C     prcAtm  :: total precip from the atmosphere [kg/m2/s]
56    C     myTime  :: current Time of simulation [s]
57    C     myIter  :: current Iteration number in simulation
58    C     myThid  :: my Thread Id number
59    C-- Use fluxes hold in commom blocks
60    C- input:
61    C     icFlxSW :: net short-wave heat flux (+=down) below sea-ice, into ocean
62    C     icFlxAtm  :: net Atmospheric surf. heat flux over sea-ice [W/m2], (+=down)
63    C     icFrwAtm  :: evaporation over sea-ice to the atmosphere [kg/m2/s] (+=up)
64    C- output
65    C     icFlxAtm  :: net Atmospheric surf. heat flux over ice+ocean [W/m2], (+=down)
66    C     icFrwAtm  :: net fresh-water flux (E-P) from the atmosphere [m/s] (+=up)
67        INTEGER bi,bj        INTEGER bi,bj
68        INTEGER iMin, iMax        INTEGER iMin, iMax
69        INTEGER jMin, jMax        INTEGER jMin, jMax
70          _RL prcAtm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
71        _RL  myTime        _RL  myTime
72        INTEGER myIter        INTEGER myIter
73        INTEGER myThid        INTEGER myThid
74    CEOP
75    
76  #ifdef ALLOW_THSICE  #ifdef ALLOW_THSICE
77  C     !LOCAL VARIABLES:  C     !LOCAL VARIABLES:
78  C     === Local variables ===  C     === Local variables ===
79  C     Fbot          :: the oceanic heat flux already incorporated (ice_therm)  C     iceFrac   :: fraction of grid area covered in ice
80  C     flxAtm        :: net heat flux from the atmosphere ( >0 downward)  C     flx2oc    :: net heat flux from the ice to the ocean (+=down) [W/m2]
81  C     evpAtm        :: evaporation to the atmosphere  C     frw2oc    :: fresh-water flux from the ice to the ocean
82  C     frwAtm        :: net fresh-water flux (E-P-R) to the atmosphere (m/s)  C     fsalt     :: mass salt flux to the ocean
83  C     qleft         :: net heat flux from the ice to the ocean  C     frzmltMxL :: ocean mixed-layer freezing/melting potential [W/m2]
84  C     ffresh        :: fresh-water flux from the ice to the ocean  C     tFrzOce   :: sea-water freezing temperature [oC] (function of S)
85  C     fsalt         :: mass salt flux to the ocean  C     isIceFree :: true for ice-free grid-cell that remains ice-free
86    C     ageFac    :: snow aging factor [1]
87    C     snowFac   :: snowing refreshing-age factor [units of 1/snowPr]
88          LOGICAL isIceFree(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
89          _RL     iceFrac  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
90          _RL     flx2oc   (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
91          _RL     frw2oc   (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
92          _RL     fsalt    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
93          _RL     tFrzOce  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
94          _RL     frzmltMxL(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
95          _RL ageFac
96          _RL snowFac
97          _RL cphm
98          _RL opFrac, icFrac
99    #ifdef ALLOW_DIAGNOSTICS
100          _RL tmpFac
101    #endif
102        INTEGER i,j        INTEGER i,j
103        _RL fswdown, qleft, qNewIce        LOGICAL dBugFlag
       _RL fsalt  
       _RL ffresh  
       _RL Tf, cphm, frzmlt  
       _RL Fbot, esurp  
       _RL flxAtm, evpAtm, frwAtm  
       _RL openFrac, iceFrac, qicAv  
       _RL oceHs, oceV2s, oceSs, oceTs  
       _RL compact, hIce, hSnow, Tsf, Tice(nlyr), qicen(nlyr)  
104    
105        LOGICAL dBug  C-    define grid-point location where to print debugging values
106    #include "THSICE_DEBUG.h"
107    
108        dBug = .FALSE.   1010 FORMAT(A,1P4E14.6)
  1010 FORMAT(A,1P4E11.3)  
109    
110    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
111    
112    #ifdef ALLOW_AUTODIFF_TAMC
113          act1 = bi - myBxLo(myThid)
114          max1 = myBxHi(myThid) - myBxLo(myThid) + 1
115          act2 = bj - myByLo(myThid)
116          max2 = myByHi(myThid) - myByLo(myThid) + 1
117          act3 = myThid - 1
118          max3 = nTx*nTy
119          act4 = ikey_dynamics - 1
120          iicekey = (act1 + 1) + act2*max1
121         &                     + act3*max1*max2
122         &                     + act4*max1*max2*max3
123    #endif /* ALLOW_AUTODIFF_TAMC */
124    
125    C-    Initialise
126          dBugFlag = debugLevel.GE.debLevB
127          DO j = 1-OLy, sNy+OLy
128            DO i = 1-OLx, sNx+OLx
129              isIceFree(i,j) = .FALSE.
130    #ifdef ALLOW_ATM2D
131              sFluxFromIce(i,j) = 0. _d 0
132    #else
133              saltFlux(i,j,bi,bj) = 0. _d 0
134    #endif
135    #ifdef ALLOW_AUTODIFF_TAMC
136              iceFrac(i,j) = 0.
137    #endif
138            ENDDO
139          ENDDO
140    
141          ageFac = 1. _d 0 - thSIce_deltaT/snowAgTime
142          snowFac = thSIce_deltaT/(rhos*hNewSnowAge)
143    
144    #ifdef ALLOW_AUTODIFF_TAMC
145    CADJ STORE iceMask(:,:,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte
146    #endif
147        DO j = jMin, jMax        DO j = jMin, jMax
148         DO i = iMin, iMax         DO i = iMin, iMax
149  c       dBug = ( bi.EQ.3 .AND. i.EQ.13 .AND. j.EQ.13 )          IF (iceMask(i,j,bi,bj).GT.0. _d 0) THEN
150    C--  Snow aging :
151          Tf     = -mu_Tf*salt(i,j,1,bi,bj)            snowAge(i,j,bi,bj) = thSIce_deltaT
152          cphm   = cpwater*rhosw*drF(1)*hFacC(i,j,1,bi,bj)       &                       + snowAge(i,j,bi,bj)*ageFac
153          frzmlt = (Tf-theta(i,j,1,bi,bj))*cphm/thSIce_deltaT            IF ( snowPrc(i,j,bi,bj).GT.0. _d 0 )
154          Fbot   = 0. _d 0       &      snowAge(i,j,bi,bj) = snowAge(i,j,bi,bj)
155          compact= 0. _d 0       &          * EXP( - snowFac*snowPrc(i,j,bi,bj) )
156          snow(i,j,bi,bj)     = 0. _d 0  c    &          * EXP( -(thSIce_deltaT*snowPrc(i,j,bi,bj)/rhos)
157          saltFlux(i,j,bi,bj) = 0. _d 0  c    &                  /hNewSnowAge )
158    C-------
159          IF (dBug.AND.(frzmlt.GT.0. .OR.iceMask(i,j,bi,bj).GT.0.)) THEN  C note: Any flux of mass (here fresh water) that enter or leave the system
160            WRITE(6,1010) 'ThSI_FWD:-0- iceMask,hIc,hSn,Qnet=',  C       with a non zero energy HAS TO be counted: add snow precip.
161       &       iceMask(i,j,bi,bj),iceHeight(i,j,bi,bj),            icFlxAtm(i,j,bi,bj) = icFlxAtm(i,j,bi,bj)
162       &       snowHeight(i,j,bi,bj), Qnet(i,j,bi,bj)       &                        - Lfresh*snowPrc(i,j,bi,bj)
163            WRITE(6,1010) 'ThSI_FWD: ocTs,Tf,frzmlt=',  C--
      &              theta(i,j,1,bi,bj),Tf,frzmlt  
164          ENDIF          ENDIF
165           ENDDO
166          ENDDO
167    
168    #ifdef ALLOW_DIAGNOSTICS
169          IF ( useDiagnostics ) THEN
170            tmpFac = 1. _d 0
171            CALL DIAGNOSTICS_FILL(iceMask,'SI_FrcFx',0,1,1,bi,bj,myThid)
172            CALL DIAGNOSTICS_FRACT_FILL(
173         I                   snowPrc,   iceMask,tmpFac,1,'SIsnwPrc',
174         I                   0,1,1,bi,bj,myThid)
175            CALL DIAGNOSTICS_FRACT_FILL(
176         I                   siceAlb,   iceMask,tmpFac,1,'SIalbedo',
177         I                   0,1,1,bi,bj,myThid)
178          ENDIF
179    #endif /* ALLOW_DIAGNOSTICS */
180          DO j = jMin, jMax
181           DO i = iMin, iMax
182              siceAlb(i,j,bi,bj) = iceMask(i,j,bi,bj)*siceAlb(i,j,bi,bj)
183           ENDDO
184          ENDDO
185    
186  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
187  C    part.1 : ice-covered fraction ;  C    part.2 : ice-covered fraction ;
188  C     can only reduce the ice-fraction but not increase it.  C     change in ice/snow thickness and ice-fraction
189    C     note: can only reduce the ice-fraction but not increase it.
190  C-------  C-------
191          IF (iceMask(i,j,bi,bj).GT.0. _d 0) THEN        DO j = jMin, jMax
192            fswdown = solar(i,j,bi,bj)         DO i = iMin, iMax
           oceHs   = hfacC(i,j,1,bi,bj)*drF(1)  
           oceTs   = theta(i,j,1,bi,bj)  
           oceSs   = salt (i,j,1,bi,bj)  
           oceV2s  = ( uvel(i,j,1,bi,bj)*uvel(i,j,1,bi,bj)  
      &              + uvel(i+1,j,1,bi,bj)*uvel(i+1,j,1,bi,bj)  
      &              + vvel(i,j+1,1,bi,bj)*vvel(i,j+1,1,bi,bj)  
      &              + vvel(i,j,1,bi,bj)*vvel(i,j,1,bi,bj) )*0.5 _d 0  
           compact = iceMask(i,j,bi,bj)  
           hIce    = iceHeight(i,j,bi,bj)  
           hSnow   = snowHeight(i,j,bi,bj)  
           Tsf     = Tsrf(i,j,bi,bj)  
           Tice(1) = Tice1(i,j,bi,bj)  
           Tice(2) = Tice2(i,j,bi,bj)  
           qicen(1)= Qice1(i,j,bi,bj)  
           qicen(2)= Qice2(i,j,bi,bj)  
           CALL THSICE_THERM(  
      I          fswdown, oceHs, oceV2s, oceSs, oceTs,  
      U          compact, hIce, hSnow, Tsf, Tice, qicen,  
      O          qleft, ffresh, fsalt, Fbot,  
      O          flxAtm, evpAtm,  
      I          i,j, bi,bj, myThid)  
193    
194  C-- Diagnostic of Atmospheric Fluxes over sea-ice :          tFrzOce(i,j) = -mu_Tf*sOceMxL(i,j,bi,bj)
195            frwAtm = evpAtm - snow(i,j,bi,bj)*rhos/rhofw          cphm    = cpwater*rhosw*hOceMxL(i,j,bi,bj)
196  C note: Any flux of mass (here fresh water) that enter or leave the system          frzmltMxL(i,j) = ( tFrzOce(i,j)-tOceMxL(i,j,bi,bj) )
197  C       with a non zero energy HAS TO be counted: add snow precip.       &                 * cphm/ocean_deltaT
198            flxAtm = flxAtm - Lfresh*snow(i,j,bi,bj)*rhos          iceFrac(i,j) = iceMask(i,j,bi,bj)
199            flx2oc(i,j)  = icFlxSW(i,j,bi,bj)
200    C-------
201    #ifdef ALLOW_DBUG_THSICE
202            IF ( dBug(i,j,bi,bj) ) THEN
203             IF (frzmltMxL(i,j).GT.0. .OR. iceFrac(i,j).GT.0.) THEN
204              WRITE(6,'(A,2I4,2I2)') 'ThSI_FWD: i,j=',i,j,bi,bj
205              WRITE(6,1010) 'ThSI_FWD:-1- iceMask, hIc, hSn, Tsf  =',
206         &                  iceFrac(i,j), iceHeight(i,j,bi,bj),
207         &                  snowHeight(i,j,bi,bj), Tsrf(i,j,bi,bj)
208              WRITE(6,1010) 'ThSI_FWD: ocTs,tFrzOce,frzmltMxL,Qnet=',
209         &                     tOceMxL(i,j,bi,bj), tFrzOce(i,j),
210         &                     frzmltMxL(i,j), Qnet(i,j,bi,bj)
211             ENDIF
212             IF (iceFrac(i,j).GT.0.)
213         &    WRITE(6,1010) 'ThSI_FWD: icFrac,flxAtm,evpAtm,flxSnw=',
214         &      iceFrac(i,j), icFlxAtm(i,j,bi,bj),
215         &      icFrwAtm(i,j,bi,bj),-Lfresh*snowPrc(i,j,bi,bj)
216            ENDIF
217    #endif
218           ENDDO
219          ENDDO
220    
221  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  #ifdef ALLOW_AUTODIFF_TAMC
222        IF (dBug) WRITE(6,1010) 'ThSI_FWD: iceFrac,flxAtm,evpAtm,flxSnw=',  CADJ STORE iceMask(:,:,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte
223       &  iceMask(i,j,bi,bj),flxAtm,evpAtm,-Lfresh*snow(i,j,bi,bj)*rhos  #endif
       IF (dBug) WRITE(6,1010) 'ThSI_FWD: compact,qleft,fsalt,ffresh=',  
      &   compact,qleft,fsalt,ffresh  
 #ifdef CHECK_ENERGY_CONSERV  
           iceFrac = iceMask(i,j,bi,bj)  
           CALL THSICE_CHECK_CONSERV( dBug, i, j, bi, bj, 0,  
      I            iceFrac, compact, hIce, hSnow, qicen,  
      I            qleft, ffresh, fsalt, flxAtm, frwAtm,  
      I            myTime, myIter, myThid )  
 #endif /* CHECK_ENERGY_CONSERV */  
 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  
224    
225  C--    Update Sea-Ice state :        CALL THSICE_CALC_THICKN(
226  c         theta(i,j,1,bi,bj) = oceTs       I          bi, bj, siLo, siHi, sjLo, sjHi,
227  c         iceMask(i,j,bi,bj)=compact       I          iMin,iMax, jMin,jMax, dBugFlag,
228            iceheight(i,j,bi,bj) = hIce       I          iceMask(siLo,sjLo,bi,bj), tFrzOce,
229            snowheight(i,j,bi,bj)= hSnow       I          tOceMxL(siLo,sjLo,bi,bj), v2ocMxL(siLo,sjLo,bi,bj),
230            Tsrf(i,j,bi,bj) =Tsf       I          snowPrc(siLo,sjLo,bi,bj), prcAtm,
231            Tice1(i,j,bi,bj)=Tice(1)       I          sHeating(siLo,sjLo,bi,bj), flxCndBt(siLo,sjLo,bi,bj),
232            Tice2(i,j,bi,bj)=Tice(2)       U          iceFrac, iceHeight(siLo,sjLo,bi,bj),
233            Qice1(i,j,bi,bj)=qicen(1)       U          snowHeight(siLo,sjLo,bi,bj), Tsrf(siLo,sjLo,bi,bj),
234            Qice2(i,j,bi,bj)=qicen(2)       U          Qice1(siLo,sjLo,bi,bj), Qice2(siLo,sjLo,bi,bj),
235         U          icFrwAtm(siLo,sjLo,bi,bj), frzmltMxL, flx2oc,
236         O          frw2oc, fsalt,
237         I          myTime, myIter, myThid )
238    
239  C--    Net fluxes :  C--    Net fluxes :
240            ffresh = ffresh/rhofw        DO j = jMin, jMax
241            ffresh = -ffresh-rain(i,j,bi,bj)-runoff(i,j,bi,bj)         DO i = iMin, iMax
242            frwAtm =  frwAtm-rain(i,j,bi,bj)-runoff(i,j,bi,bj)  #ifdef ALLOW_AUTODIFF_TAMC
243            iceFrac = iceMask(i,j,bi,bj)            ikey_1 = i
244            openFrac= 1. _d 0-iceFrac       &         + sNx*(j-1)
245  #ifdef ALLOW_TIMEAVE       &         + sNx*sNy*act1
246            ICE_Qnet_AVE(i,j,bi,bj) = ICE_Qnet_AVE(i,j,bi,bj)       &         + sNx*sNy*max1*act2
247       &          + ( -iceFrac*flxAtm + openFrac*Qnet(i,j,bi,bj)       &         + sNx*sNy*max1*max2*act3
248       &            )*thSIce_deltaT       &         + sNx*sNy*max1*max2*max3*act4
249            ICE_FWfx_AVE(i,j,bi,bj) = ICE_FWfx_AVE(i,j,bi,bj)  #endif /* ALLOW_AUTODIFF_TAMC */
250       &          + ( iceFrac*frwAtm + openFrac*EmPmR(i,j,bi,bj)  C--
251       &            )*thSIce_deltaT  #ifdef ALLOW_AUTODIFF_TAMC
252  #endif /*ALLOW_TIMEAVE*/  CADJ STORE  icemask(i,j,bi,bj) = comlev1_thsice_1, key=ikey_1
253            Qnet(i,j,bi,bj)=-iceFrac*qleft + openFrac*Qnet(i,j,bi,bj)  #endif
254            EmPmR(i,j,bi,bj)=iceFrac*ffresh+openFrac*EmPmR(i,j,bi,bj)          IF (iceMask(i,j,bi,bj).GT.0. _d 0) THEN
255            saltFlux(i,j,bi,bj)=-iceFrac*fsalt  C-     weighted average net fluxes:
256    #ifdef ALLOW_AUTODIFF_TAMC
257            IF (dBug) WRITE(6,1010)'ThSI_FWD:-1- compact,hIc,hSn,Qnet=',  CADJ STORE  fsalt(i,j) = comlev1_thsice_1, key=ikey_1
258       &                      compact,hIce,hSnow,Qnet(i,j,bi,bj)  CADJ STORE  flx2oc(i,j) = comlev1_thsice_1, key=ikey_1
259    CADJ STORE  frw2oc(i,j) = comlev1_thsice_1, key=ikey_1
260          ELSEIF (hFacC(i,j,1,bi,bj).gt.0. _d 0) THEN  CADJ STORE  icemask(i,j,bi,bj) = comlev1_thsice_1, key=ikey_1
261    #endif
262  #ifdef ALLOW_TIMEAVE            icFrac = iceMask(i,j,bi,bj)
263           ICE_Qnet_AVE(i,j,bi,bj) = ICE_Qnet_AVE(i,j,bi,bj)            opFrac= 1. _d 0-icFrac
264       &                   +Qnet(i,j,bi,bj)*thSIce_deltaT  #ifdef ALLOW_ATM2D
265           ICE_FWfx_AVE(i,j,bi,bj) = ICE_FWfx_AVE(i,j,bi,bj)            pass_qnet(i,j) = pass_qnet(i,j) - icFrac*flx2oc(i,j)
266       &                   +EmPmR(i,j,bi,bj)*thSIce_deltaT            pass_evap(i,j) = pass_evap(i,j) - icFrac*frw2oc(i,j)/rhofw
267  #endif /*ALLOW_TIMEAVE*/            sFluxFromIce(i,j) = -icFrac*fsalt(i,j)
268    #else
269              icFlxAtm(i,j,bi,bj) = icFrac*icFlxAtm(i,j,bi,bj)
270         &                        - opFrac*Qnet(i,j,bi,bj)
271              icFrwAtm(i,j,bi,bj) = icFrac*icFrwAtm(i,j,bi,bj)
272         &                        + opFrac*rhofw*EmPmR(i,j,bi,bj)
273              Qnet(i,j,bi,bj) = -icFrac*flx2oc(i,j) + opFrac*Qnet(i,j,bi,bj)
274              EmPmR(i,j,bi,bj)= -icFrac*frw2oc(i,j)/rhofw
275         &                    +  opFrac*EmPmR(i,j,bi,bj)
276              saltFlux(i,j,bi,bj) = -icFrac*fsalt(i,j)
277    #endif
278    
279    #ifdef ALLOW_DBUG_THSICE
280              IF (dBug(i,j,bi,bj)) WRITE(6,1010)
281         &          'ThSI_FWD:-3- iceFrac, hIc, hSn, Qnet =',
282         &           iceFrac(i,j), iceHeight(i,j,bi,bj),
283         &           snowHeight(i,j,bi,bj), Qnet(i,j,bi,bj)
284    #endif
285    
286            ELSEIF (hOceMxL(i,j,bi,bj).gt.0. _d 0) THEN
287              icFlxAtm(i,j,bi,bj) = -Qnet(i,j,bi,bj)
288              icFrwAtm(i,j,bi,bj) = rhofw*EmPmR(i,j,bi,bj)
289            ELSE
290              icFlxAtm(i,j,bi,bj) = 0. _d 0
291              icFrwAtm(i,j,bi,bj) = 0. _d 0
292          ENDIF          ENDIF
293           ENDDO
294          ENDDO
295    
296  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
297  C    part.2 : freezing of sea-water  C    part.3 : freezing of sea-water
298  C     over ice-free fraction and what is left from ice-covered fraction  C     over ice-free fraction and what is left from ice-covered fraction
299  C-------  C-------
300          esurp = frzmlt - Fbot*iceMask(i,j,bi,bj)        CALL THSICE_EXTEND(
301          IF (esurp.GT.0. _d 0) THEN       I          bi, bj, siLo, siHi, sjLo, sjHi,
302            iceFrac = compact       I          iMin,iMax, jMin,jMax, dBugFlag,
303            IF ( compact.GT.0. _d 0 ) THEN       I          frzmltMxL, tFrzOce,
304              qicen(1)= Qice1(i,j,bi,bj)       I          tOceMxL(siLo,sjLo,bi,bj),
305              qicen(2)= Qice2(i,j,bi,bj)       U          iceFrac, iceHeight(siLo,sjLo,bi,bj),
306            ELSE       U          snowHeight(siLo,sjLo,bi,bj), Tsrf(siLo,sjLo,bi,bj),
307              qicen(1)= -cpwater*Tmlt1       U          Tice1(siLo,sjLo,bi,bj), Tice2(siLo,sjLo,bi,bj),
308       &               + cpice *(Tmlt1-Tf) + Lfresh*(1. _d 0-Tmlt1/Tf)       U          Qice1(siLo,sjLo,bi,bj), Qice2(siLo,sjLo,bi,bj),
309              qicen(2)= -cpice *Tf + Lfresh       O          flx2oc, frw2oc, fsalt,
310            ENDIF       I          myTime, myIter, myThid )
311            qicAv = rhoi*(qicen(1)+qicen(2))*0.5 _d 0  
312            oceTs = theta(i,j,1,bi,bj)  #ifdef ALLOW_AUTODIFF_TAMC
313            hIce  = iceHeight(i,j,bi,bj)  CADJ STORE snowHeight(:,:,bi,bj) =
314            hSnow = snowHeight(i,j,bi,bj)  CADJ &     comlev1_bibj, key=iicekey, byte=isbyte
315            CALL THSICE_START( myThid,  #endif
316       I             esurp, qicAv, Tf,        DO j = jMin, jMax
317       O             qNewIce, ffresh, fsalt,         DO i = iMin, iMax
318       U             oceTs, compact, hIce, hSnow )          IF (frzmltMxL(i,j).GT.0. _d 0) THEN
 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  
       IF (dBug) WRITE(6,1010) 'ThSI_FWD: compact,qNewIce,fsalt,ffresh='  
      &                 ,compact,qNewIce,fsalt,ffresh  
 #ifdef CHECK_ENERGY_CONSERV  
           flxAtm = 0.  
           frwAtm = 0.  
           CALL THSICE_CHECK_CONSERV( dBug, i, j, bi, bj, 1,  
      I            iceFrac, compact, hIce, hSnow, qicen,  
      I            qNewIce, ffresh, fsalt, flxAtm, frwAtm,  
      I            myTime, myIter, myThid )  
 #endif /* CHECK_ENERGY_CONSERV */  
 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  
 C--    Update Sea-Ice state :  
           IF ( compact.GT.0. _d 0 .AND. iceFrac.EQ.0. _d 0) THEN  
              Tsrf(i,j,bi,bj)  = Tf  
              Tice1(i,j,bi,bj) = Tf  
              Tice2(i,j,bi,bj) = Tf  
              Qice1(i,j,bi,bj) = qicen(1)  
              Qice2(i,j,bi,bj) = qicen(2)  
 c            theta(i,j,1,bi,bj)= oceTs  
           ENDIF  
           iceheight(i,j,bi,bj) = hIce  
           snowheight(i,j,bi,bj)= hSnow  
319  C--    Net fluxes :  C--    Net fluxes :
320            Qnet(i,j,bi,bj) = Qnet(i,j,bi,bj) - qNewIce  #ifdef ALLOW_ATM2D
321            EmPmR(i,j,bi,bj)= EmPmR(i,j,bi,bj)- ffresh/rhofw            pass_qnet(i,j) = pass_qnet(i,j) - flx2oc(i,j)
322            saltFlux(i,j,bi,bj)=saltFlux(i,j,bi,bj) - fsalt            pass_evap(i,j) = pass_evap(i,j) - frw2oc(i,j)/rhofw
323              sFluxFromIce(i,j)= sFluxFromIce(i,j) - fsalt(i,j)
324            IF (dBug) WRITE(6,1010)'ThSI_FWD:-2- compact,hIc,hSn,Qnet=',  #else
325       &                        compact,hIce,hSnow,Qnet(i,j,bi,bj)            Qnet(i,j,bi,bj) = Qnet(i,j,bi,bj) - flx2oc(i,j)
326  C--   - if esurp > 0 : end            EmPmR(i,j,bi,bj)= EmPmR(i,j,bi,bj)- frw2oc(i,j)/rhofw
327              saltFlux(i,j,bi,bj)=saltFlux(i,j,bi,bj) - fsalt(i,j)
328    #endif
329    
330    #ifdef ALLOW_DBUG_THSICE
331              IF (dBug(i,j,bi,bj)) WRITE(6,1010)
332         &         'ThSI_FWD:-4- iceFrac, hIc, hSn, Qnet =',
333         &           iceFrac(i,j), iceHeight(i,j,bi,bj),
334         &           snowHeight(i,j,bi,bj), Qnet(i,j,bi,bj)
335    #endif
336          ENDIF          ENDIF
337    
338          IF ( compact .GT. 0. _d 0 ) THEN          IF ( hOceMxL(i,j,bi,bj).GT.0. _d 0 )
339            iceMask(i,j,bi,bj)=compact       &    isIceFree(i,j) = iceMask(i,j,bi,bj).LE.0. _d 0
340         &                  .AND.   iceFrac(i,j) .LE.0. _d 0
341            IF ( iceFrac(i,j) .GT. 0. _d 0 ) THEN
342              iceMask(i,j,bi,bj)=iceFrac(i,j)
343              IF ( snowHeight(i,j,bi,bj).EQ.0. _d 0 )
344         &     snowAge(i,j,bi,bj) = 0. _d 0
345          ELSE          ELSE
346            iceMask(i,j,bi,bj)  = 0. _d 0            iceMask(i,j,bi,bj)  = 0. _d 0
347            iceHeight(i,j,bi,bj)= 0. _d 0            iceHeight(i,j,bi,bj)= 0. _d 0
348            snowHeight(i,j,bi,bj)=0. _d 0            snowHeight(i,j,bi,bj)=0. _d 0
349            Tsrf(i,j,bi,bj)=theta(i,j,1,bi,bj)            snowAge(i,j,bi,bj)  = 0. _d 0
350              Tsrf(i,j,bi,bj)     = tOceMxL(i,j,bi,bj)
351            Tice1(i,j,bi,bj)    = 0. _d 0            Tice1(i,j,bi,bj)    = 0. _d 0
352            Tice2(i,j,bi,bj)    = 0. _d 0            Tice2(i,j,bi,bj)    = 0. _d 0
353            Qice1(i,j,bi,bj)    = 0. _d 0            Qice1(i,j,bi,bj)    = Lfresh
354            Qice2(i,j,bi,bj)    = 0. _d 0            Qice2(i,j,bi,bj)    = Lfresh
355          ENDIF          ENDIF
356           ENDDO
357          ENDDO
358    
359  #ifndef CHECK_ENERGY_CONSERV  #ifdef ATMOSPHERIC_LOADING
360  #ifdef ALLOW_TIMEAVE  # ifdef ALLOW_AUTODIFF_TAMC
361            ICE_qleft_AVE(i,j,bi,bj)=ICE_qleft_AVE(i,j,bi,bj)  CADJ STORE snowHeight(:,:,bi,bj) =
362       &         + ( Qnet(i,j,bi,bj)  CADJ &     comlev1_bibj, key=iicekey, byte=isbyte
363       &            )*thSIce_deltaT  # endif
364            ICE_fresh_AVE(i,j,bi,bj)=ICE_fresh_AVE(i,j,bi,bj)        DO j = jMin, jMax
365       &         + ( EmPmR(i,j,bi,bj)         DO i = iMin, iMax
366       &            )*thSIce_deltaT  C--     Compute Sea-Ice Loading (= mass of sea-ice + snow / area unit)
367            ICE_salFx_AVE(i,j,bi,bj)=ICE_salFx_AVE(i,j,bi,bj)          sIceLoad(i,j,bi,bj) = ( snowHeight(i,j,bi,bj)*rhos
368       &            +saltFlux(i,j,bi,bj)*thSIce_deltaT       &                         + iceHeight(i,j,bi,bj)*rhoi
369  #endif /* ALLOW_TIMEAVE */       &                        )*iceMask(i,j,bi,bj)
 #endif /* CHECK_ENERGY_CONSERV */  
   
370         ENDDO         ENDDO
371        ENDDO        ENDDO
372    #endif
373    
374          IF ( thSIceAdvScheme.GT.0 ) THEN
375    C--   note: those fluxes should to be added directly to Qnet, EmPmR & saltFlux
376           DO j = jMin, jMax
377            DO i = iMin, iMax
378             IF ( hOceMxL(i,j,bi,bj).GT.0. _d 0 ) THEN
379              Qnet(i,j,bi,bj) = Qnet(i,j,bi,bj) - oceQnet(i,j,bi,bj)
380              EmPmR(i,j,bi,bj)= EmPmR(i,j,bi,bj)- oceFWfx(i,j,bi,bj)/rhofw
381              saltFlux(i,j,bi,bj)=saltFlux(i,j,bi,bj) - oceSflx(i,j,bi,bj)
382             ENDIF
383            ENDDO
384           ENDDO
385          ENDIF
386    
387    #ifdef ALLOW_BULK_FORCE
388          IF ( useBulkForce ) THEN
389            CALL BULKF_FLUX_ADJUST(
390         I                          bi, bj, iMin, iMax, jMin, jMax,
391         I                          isIceFree, myTime, myIter, myThid )
392          ENDIF
393    #endif /* ALLOW_BULK_FORCE */
394    
395  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
396  #endif /* ALLOW_THSICE */  #endif /* ALLOW_THSICE */

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.23

  ViewVC Help
Powered by ViewVC 1.1.22