/[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.3 by jmc, Wed Apr 7 23:40:34 2004 UTC revision 1.13 by jmc, Mon Mar 13 03:53:40 2006 UTC
# Line 6  C $Name$ Line 6  C $Name$
6  CBOP  CBOP
7  C     !ROUTINE: THSICE_STEP_FWD  C     !ROUTINE: THSICE_STEP_FWD
8  C     !INTERFACE:  C     !INTERFACE:
9        SUBROUTINE THSICE_STEP_FWD(        SUBROUTINE THSICE_STEP_FWD(
10       I             bi, bj, iMin, iMax, jMin, jMax,       I             bi, bj, iMin, iMax, jMin, jMax,
11       I             prcAtm,       I             prcAtm,
12       U             evpAtm, flxSW,       U             evpAtm, flxSW,
13       I             myTime, myIter, myThid )       I             myTime, myIter, myThid )
14  C     !DESCRIPTION: \bv  C     !DESCRIPTION: \bv
15  C     *==========================================================*  C     *==========================================================*
16  C     | S/R  THSICE_STEP_FWD              C     | S/R  THSICE_STEP_FWD
17  C     | o Step Forward Therm-SeaIce model.  C     | o Step Forward Therm-SeaIce model.
18  C     *==========================================================*  C     *==========================================================*
19  C     \ev  C     \ev
# Line 30  C     === Global variables === Line 30  C     === Global variables ===
30  #include "THSICE_PARAMS.h"  #include "THSICE_PARAMS.h"
31  #include "THSICE_VARS.h"  #include "THSICE_VARS.h"
32  #include "THSICE_TAVE.h"  #include "THSICE_TAVE.h"
33    
34  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
35  C     === Routine arguments ===  C     === Routine arguments ===
36  C     bi,bj   :: tile indices  C     bi,bj   :: tile indices
37  C   iMin,iMax :: computation domain: 1rst index range  C   iMin,iMax :: computation domain: 1rst index range
38  C   jMin,jMax :: computation domain: 2nd  index range  C   jMin,jMax :: computation domain: 2nd  index range
39  C- input:  C- input:
40  C     prcAtm  :: total precip from the atmosphere [kg/m2/s]  C     prcAtm  :: total precip from the atmosphere [kg/m2/s]
41  C     evpAtm  :: (Inp) evaporation to the atmosphere [kg/m2/s] (>0 if evaporate)  C     evpAtm  :: (Inp) evaporation to the atmosphere [kg/m2/s] (>0 if evaporate)
42  C     flxSW   :: (Inp) short-wave heat flux (+=down): downward comp. only  C     flxSW   :: (Inp) short-wave heat flux (+=down): downward comp. only
43  C                      (part.1), becomes net SW flux into ocean (part.2).  C                      (part.1), becomes net SW flux into ocean (part.2).
# Line 88  C     TFrzOce   :: sea-water freezing te Line 88  C     TFrzOce   :: sea-water freezing te
88        _RL oceV2s, oceTs        _RL oceV2s, oceTs
89        _RL compact, hIce, hSnow, Tsf, Tice(nlyr), qicen(nlyr)        _RL compact, hIce, hSnow, Tsf, Tice(nlyr), qicen(nlyr)
90        _RL tmpflx(0:2), tmpdTs        _RL tmpflx(0:2), tmpdTs
91    #ifdef ALLOW_DIAGNOSTICS
92          _RL tmpFac
93    #endif
94    
95        LOGICAL dBug        LOGICAL dBug
96    
97     1010 FORMAT(A,1P4E14.6)
98        dBug = .FALSE.        dBug = .FALSE.
99   1010 FORMAT(A,1P4E11.3)  C-    Initialise flxAtm
100           DO j = 1-Oly, sNy+Oly
101            DO i = 1-Olx, sNx+Olx
102              flxAtm(i,j) = 0.
103            ENDDO
104           ENDDO
105    
106        IF ( buoyancyRelation(1:7) .EQ. 'OCEANIC' ) THEN        IF ( fluidIsWater ) THEN
107         DO j = jMin, jMax         DO j = jMin, jMax
108          DO i = iMin, iMax          DO i = iMin, iMax
109  c        dBug = ( bi.EQ.3 .AND. i.EQ.15 .AND. j.EQ.15 )  c        dBug = ( bi.EQ.3 .AND. i.EQ.15 .AND. j.EQ.11 )
110    
111  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
112  C    part.1 : ice-covered fraction ;  C    part.1 : ice-covered fraction ;
113  C     Solve for surface and ice temperature (implicitly) ; compute surf. fluxes  C     Solve for surface and ice temperature (implicitly) ; compute surf. fluxes
114  C-------  C-------
115           IF (iceMask(i,j,bi,bj).GT.0. _d 0) THEN           IF (iceMask(i,j,bi,bj).GT.0. _d 0) THEN
116            icFrac  = iceMask(i,j,bi,bj)            icFrac  = iceMask(i,j,bi,bj)
117            TFrzOce = -mu_Tf*sOceMxL(i,j,bi,bj)            TFrzOce = -mu_Tf*sOceMxL(i,j,bi,bj)
118            hIce    = iceHeight(i,j,bi,bj)            hIce    = iceHeight(i,j,bi,bj)
# Line 111  C------- Line 120  C-------
120            Tsf     = Tsrf(i,j,bi,bj)            Tsf     = Tsrf(i,j,bi,bj)
121            qicen(1)= Qice1(i,j,bi,bj)            qicen(1)= Qice1(i,j,bi,bj)
122            qicen(2)= Qice2(i,j,bi,bj)            qicen(2)= Qice2(i,j,bi,bj)
123              IF ( dBug ) THEN
124               WRITE(6,'(A,2I4,2I2)') 'ThSI_FWD: i,j=',i,j,bi,bj
125               WRITE(6,1010) 'ThSI_FWD:-0- iceMask, hIc, hSn, Tsf  =',
126         &                                 icFrac, hIce,hSnow,Tsf
127              ENDIF
128    
129            CALL THSICE_ALBEDO(            CALL THSICE_ALBEDO(
130       I               hIce, hSnow, Tsf, snowAge(i,j,bi,bj),       I               hIce, hSnow, Tsf, snowAge(i,j,bi,bj),
131       O               albedo,       O               albedo,
132       I               myThid )       I               myThid )
133            flxSW(i,j) = flxSW(i,j)*(1. _d 0 - albedo)            flxSW(i,j) = flxSW(i,j)*(1. _d 0 - albedo)
134              siceAlb(i,j,bi,bj) = albedo
135    
136            CALL THSICE_SOLVE4TEMP(            CALL THSICE_SOLVE4TEMP(
137       I          useBulkforce, tmpflx, TFrzOce, hIce, hSnow,       I          useBulkforce, tmpflx, TFrzOce, hIce, hSnow,
# Line 136  C--    Update Sea-Ice state : Line 151  C--    Update Sea-Ice state :
151            Tice2(i,j,bi,bj)=Tice(2)            Tice2(i,j,bi,bj)=Tice(2)
152            Qice1(i,j,bi,bj)=qicen(1)            Qice1(i,j,bi,bj)=qicen(1)
153            Qice2(i,j,bi,bj)=qicen(2)            Qice2(i,j,bi,bj)=qicen(2)
154  #ifdef ALLOW_TIMEAVE            IF ( dBug ) THEN
155            ice_albedo_Ave(i,j,bi,bj) = ice_albedo_Ave(i,j,bi,bj)             WRITE(6,1010) 'ThSI_FWD: Tsf, Tice(1,2), frzmltMxL =',
156       &                              + icFrac*albedo*thSIce_deltaT       &                              Tsf, Tice, frzmltMxL
157  #endif /*ALLOW_TIMEAVE*/             WRITE(6,1010) 'ThSI_FWD: sHeat,fxCndBt, fxAtm,evAtm=',
158         &                  sHeating(i,j,bi,bj), flxCndBt(i,j,bi,bj),
159         &                  flxAtm(i,j), evpAtm(i,j)
160              ENDIF
161           ENDIF           ENDIF
162          ENDDO          ENDDO
163         ENDDO         ENDDO
164        ENDIF        ENDIF
165        dBug = .FALSE.        dBug = .FALSE.
166    
167    #ifdef ALLOW_DIAGNOSTICS
168          IF ( useDiagnostics ) THEN
169            tmpFac = 1. _d 0
170            CALL DIAGNOSTICS_FRACT_FILL(
171         I                   snowPrc,   iceMask,tmpFac,1,'SIsnwPrc',
172         I                   0,1,1,bi,bj,myThid)
173            CALL DIAGNOSTICS_FRACT_FILL(
174         I                   siceAlb,   iceMask,tmpFac,1,'SIalbedo',
175         I                   0,1,1,bi,bj,myThid)
176          ENDIF
177    #endif /* ALLOW_DIAGNOSTICS */
178          DO j = jMin, jMax
179           DO i = iMin, iMax
180              siceAlb(i,j,bi,bj) = iceMask(i,j,bi,bj)*siceAlb(i,j,bi,bj)
181           ENDDO
182          ENDDO
183    
184  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
185  C    part.2 : ice-covered fraction ;  C    part.2 : ice-covered fraction ;
186  C     change in ice/snow thickness and ice-fraction  C     change in ice/snow thickness and ice-fraction
187  C     note: can only reduce the ice-fraction but not increase it.  C     note: can only reduce the ice-fraction but not increase it.
188  C-------  C-------
189        agingTime = 50. _d 0 * 86400. _d 0        agingTime = 50. _d 0 * 86400. _d 0
190        ageFac = 1. _d 0 - thSIce_deltaT/agingTime        ageFac = 1. _d 0 - thSIce_deltaT/agingTime
191        DO j = jMin, jMax        DO j = jMin, jMax
192         DO i = iMin, iMax         DO i = iMin, iMax
193  c       dBug = ( bi.EQ.3 .AND. i.EQ.15 .AND. j.EQ.15 )  c       dBug = ( bi.EQ.3 .AND. i.EQ.15 .AND. j.EQ.11 )
194    
195          TFrzOce = -mu_Tf*sOceMxL(i,j,bi,bj)          TFrzOce = -mu_Tf*sOceMxL(i,j,bi,bj)
196          oceTs   = tOceMxL(i,j,bi,bj)          oceTs   = tOceMxL(i,j,bi,bj)
# Line 167  c       dBug = ( bi.EQ.3 .AND. i.EQ.15 . Line 202  c       dBug = ( bi.EQ.3 .AND. i.EQ.15 .
202          compact= iceMask(i,j,bi,bj)          compact= iceMask(i,j,bi,bj)
203  C-------  C-------
204          IF (dBug .AND. (frzmltMxL.GT.0. .OR. compact.GT.0.) ) THEN          IF (dBug .AND. (frzmltMxL.GT.0. .OR. compact.GT.0.) ) THEN
205            WRITE(6,1010) 'ThSI_FWD:-1- iceMask,hIc,hSn,Qnet=',            WRITE(6,'(A,2I4,2I2)') 'ThSI_FWD: i,j=',i,j,bi,bj
206       &                  compact, hIce, hSnow, Qnet(i,j,bi,bj)            WRITE(6,1010) 'ThSI_FWD:-1- iceMask, hIc, hSn, Tsf  =',
207            WRITE(6,1010) 'ThSI_FWD: ocTs,TFrzOce,frzmltMxL=',       &                  compact, iceHeight(i,j,bi,bj),
208       &                            oceTs,TFrzOce,frzmltMxL       &                  snowHeight(i,j,bi,bj), Tsrf(i,j,bi,bj)
209              WRITE(6,1010) 'ThSI_FWD: ocTs,TFrzOce,frzmltMxL,Qnet=',
210         &                     oceTs, TFrzOce, frzmltMxL,Qnet(i,j,bi,bj)
211          ENDIF          ENDIF
212  C-------  C-------
213          IF (iceMask(i,j,bi,bj).GT.0. _d 0) THEN          IF (iceMask(i,j,bi,bj).GT.0. _d 0) THEN
214    
215            oceV2s  = v2ocMxL(i,j,bi,bj)            oceV2s  = v2ocMxL(i,j,bi,bj)
216            snowPr  = snowPrc(i,j,bi,bj)            snowPr  = snowPrc(i,j,bi,bj)
# Line 196  C         but to reproduce old results, Line 233  C         but to reproduce old results,
233            snowPrc(i,j,bi,bj) = snowPr            snowPrc(i,j,bi,bj) = snowPr
234    
235  C--  Snow aging :  C--  Snow aging :
236            snowAge(i,j,bi,bj) = thSIce_deltaT            snowAge(i,j,bi,bj) = thSIce_deltaT
237       &                       + snowAge(i,j,bi,bj)*ageFac       &                       + snowAge(i,j,bi,bj)*ageFac
238            IF ( snowPr.GT.0. _d 0 )            IF ( snowPr.GT.0. _d 0 )
239       &      snowAge(i,j,bi,bj) = snowAge(i,j,bi,bj)       &      snowAge(i,j,bi,bj) = snowAge(i,j,bi,bj)
240       &          * EXP( -(thSIce_deltaT*snowPr/rhos)/hNewSnowAge )       &          * EXP( -(thSIce_deltaT*snowPr/rhos)/hNewSnowAge )
241  C--  C--
242    
# Line 225  C---+----1----+----2----+----3----+----4 Line 262  C---+----1----+----2----+----3----+----4
262    
263  C--    Update Sea-Ice state :  C--    Update Sea-Ice state :
264  c         iceMask(i,j,bi,bj)=compact  c         iceMask(i,j,bi,bj)=compact
265            iceheight(i,j,bi,bj) = hIce            iceHeight(i,j,bi,bj) = hIce
266            snowheight(i,j,bi,bj)= hSnow            snowHeight(i,j,bi,bj)= hSnow
267            Tsrf(i,j,bi,bj) =Tsf            Tsrf(i,j,bi,bj) =Tsf
268            Qice1(i,j,bi,bj)=qicen(1)            Qice1(i,j,bi,bj)=qicen(1)
269            Qice2(i,j,bi,bj)=qicen(2)            Qice2(i,j,bi,bj)=qicen(2)
# Line 242  C-     weighted average net fluxes: Line 279  C-     weighted average net fluxes:
279            EmPmR(i,j,bi,bj)=-icFrac*frw2oc/rhofw+opFrac*EmPmR(i,j,bi,bj)            EmPmR(i,j,bi,bj)=-icFrac*frw2oc/rhofw+opFrac*EmPmR(i,j,bi,bj)
280            saltFlux(i,j,bi,bj)=-icFrac*fsalt            saltFlux(i,j,bi,bj)=-icFrac*fsalt
281    
282            IF (dBug) WRITE(6,1010)'ThSI_FWD:-3- compact,hIc,hSn,Qnet=',            IF (dBug) WRITE(6,1010)
283       &                      compact,hIce,hSnow,Qnet(i,j,bi,bj)       &          'ThSI_FWD:-3- compact, hIc, hSn, Qnet =',
284         &                        compact,hIce,hSnow,Qnet(i,j,bi,bj)
285    
286          ELSEIF (hOceMxL(i,j,bi,bj).gt.0. _d 0) THEN          ELSEIF (hOceMxL(i,j,bi,bj).gt.0. _d 0) THEN
287            flxAtm(i,j) =  -Qnet(i,j,bi,bj)            flxAtm(i,j) =  -Qnet(i,j,bi,bj)
# Line 274  c       compact= iceMask(i,j,bi,bj) Line 312  c       compact= iceMask(i,j,bi,bj)
312  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
313        IF (dBug) WRITE(6,1010) 'ThSI_FWD: compact,flx2oc,fsalt,frw2oc='        IF (dBug) WRITE(6,1010) 'ThSI_FWD: compact,flx2oc,fsalt,frw2oc='
314       &                 ,compact,flx2oc,fsalt,frw2oc       &                 ,compact,flx2oc,fsalt,frw2oc
315  #ifdef CHECK_ENERGY_CONSERV  #ifdef CHECK_ENERGY_CONSERV
316            tmpflx(1) = 0.            tmpflx(1) = 0.
317            tmpflx(2) = 0.            tmpflx(2) = 0.
318            CALL THSICE_CHECK_CONSERV( dBug, i, j, bi, bj, 1,            CALL THSICE_CHECK_CONSERV( dBug, i, j, bi, bj, 1,
319       I            icFrac, compact, hIce, hSnow, qicen,       I            icFrac, compact, hIce, hSnow, qicen,
320       I            flx2oc, frw2oc, fsalt, tmpflx(1), tmpflx(2),       I            flx2oc, frw2oc, fsalt, tmpflx(1), tmpflx(2),
# Line 291  C--    Update Sea-Ice state : Line 329  C--    Update Sea-Ice state :
329               Qice1(i,j,bi,bj) = qicen(1)               Qice1(i,j,bi,bj) = qicen(1)
330               Qice2(i,j,bi,bj) = qicen(2)               Qice2(i,j,bi,bj) = qicen(2)
331            ENDIF            ENDIF
332            iceheight(i,j,bi,bj) = hIce            iceHeight(i,j,bi,bj) = hIce
333            snowheight(i,j,bi,bj)= hSnow            snowHeight(i,j,bi,bj)= hSnow
334  C--    Net fluxes :  C--    Net fluxes :
335            Qnet(i,j,bi,bj) = Qnet(i,j,bi,bj) - flx2oc            Qnet(i,j,bi,bj) = Qnet(i,j,bi,bj) - flx2oc
336            EmPmR(i,j,bi,bj)= EmPmR(i,j,bi,bj)- frw2oc/rhofw            EmPmR(i,j,bi,bj)= EmPmR(i,j,bi,bj)- frw2oc/rhofw
337            saltFlux(i,j,bi,bj)=saltFlux(i,j,bi,bj) - fsalt            saltFlux(i,j,bi,bj)=saltFlux(i,j,bi,bj) - fsalt
338    
339            IF (dBug) WRITE(6,1010)'ThSI_FWD:-4- compact,hIc,hSn,Qnet=',            IF (dBug) WRITE(6,1010)
340         &          'ThSI_FWD:-4- compact, hIc, hSn, Qnet =',
341       &                        compact,hIce,hSnow,Qnet(i,j,bi,bj)       &                        compact,hIce,hSnow,Qnet(i,j,bi,bj)
342  C--   - if esurp > 0 : end  C--   - if esurp > 0 : end
343          ENDIF          ENDIF
# Line 321  C--   - if esurp > 0 : end Line 360  C--   - if esurp > 0 : end
360  C--     Return atmospheric fluxes in evpAtm & flxSW (same sign and units):  C--     Return atmospheric fluxes in evpAtm & flxSW (same sign and units):
361          evpAtm(i,j) = frwAtm          evpAtm(i,j) = frwAtm
362          flxSW (i,j) = flxAtm(i,j)          flxSW (i,j) = flxAtm(i,j)
363    
364    #ifdef ATMOSPHERIC_LOADING
365    C--     Compute Sea-Ice Loading (= mass of sea-ice + snow / area unit)
366            sIceLoad(i,j,bi,bj) = ( snowHeight(i,j,bi,bj)*rhos
367         &                         + iceHeight(i,j,bi,bj)*rhoi
368         &                        )*iceMask(i,j,bi,bj)
369    #endif
370    
371         ENDDO         ENDDO
372        ENDDO        ENDDO
373    

Legend:
Removed from v.1.3  
changed lines
  Added in v.1.13

  ViewVC Help
Powered by ViewVC 1.1.22