/[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.12 by jmc, Tue Feb 21 01:15:16 2006 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 94  C     TFrzOce   :: sea-water freezing te Line 94  C     TFrzOce   :: sea-water freezing te
94    
95        LOGICAL dBug        LOGICAL dBug
96    
97   1010 FORMAT(A,1P4E11.3)   1010 FORMAT(A,1P4E14.6)
98        dBug = .FALSE.        dBug = .FALSE.
99  C-    Initialise flxAtm  C-    Initialise flxAtm
100         DO j = 1-Oly, sNy+Oly         DO j = 1-Oly, sNy+Oly
# Line 109  C-    Initialise flxAtm Line 109  C-    Initialise flxAtm
109  c        dBug = ( bi.EQ.3 .AND. i.EQ.15 .AND. j.EQ.11 )  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 182  C--    Update Sea-Ice state : Line 182  C--    Update Sea-Ice state :
182        ENDDO        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
# Line 204  C------- Line 204  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,'(A,2I4,2I2)') 'ThSI_FWD: i,j=',i,j,bi,bj            WRITE(6,'(A,2I4,2I2)') 'ThSI_FWD: i,j=',i,j,bi,bj
206            WRITE(6,1010) 'ThSI_FWD:-1- iceMask, hIc, hSn, Tsf  =',            WRITE(6,1010) 'ThSI_FWD:-1- iceMask, hIc, hSn, Tsf  =',
207       &                  compact, iceHeight(i,j,bi,bj),       &                  compact, iceHeight(i,j,bi,bj),
208       &                  snowHeight(i,j,bi,bj), Tsrf(i,j,bi,bj)       &                  snowHeight(i,j,bi,bj), Tsrf(i,j,bi,bj)
209            WRITE(6,1010) 'ThSI_FWD: ocTs,TFrzOce,frzmltMxL,Qnet=',            WRITE(6,1010) 'ThSI_FWD: ocTs,TFrzOce,frzmltMxL,Qnet=',
210       &                     oceTs, TFrzOce, frzmltMxL,Qnet(i,j,bi,bj)       &                     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 233  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 312  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 333  C--    Update Sea-Ice state : Line 333  C--    Update Sea-Ice state :
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)            IF (dBug) WRITE(6,1010)

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

  ViewVC Help
Powered by ViewVC 1.1.22