/[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.16 by heimbach, Sun Apr 9 17:35:30 2006 UTC revision 1.17 by jmc, Thu May 25 18:03:25 2006 UTC
# Line 9  C     !INTERFACE: Line 9  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,
      U             evpAtm, flxSW,  
12       I             myTime, myIter, myThid )       I             myTime, myIter, myThid )
13  C     !DESCRIPTION: \bv  C     !DESCRIPTION: \bv
14  C     *==========================================================*  C     *==========================================================*
# Line 30  C     === Global variables === Line 29  C     === Global variables ===
29  #include "THSICE_PARAMS.h"  #include "THSICE_PARAMS.h"
30  #include "THSICE_VARS.h"  #include "THSICE_VARS.h"
31  #include "THSICE_TAVE.h"  #include "THSICE_TAVE.h"
32          INTEGER siLo, siHi, sjLo, sjHi
33          PARAMETER ( siLo = 1-OLx , siHi = sNx+OLx )
34          PARAMETER ( sjLo = 1-OLy , sjHi = sNy+OLy )
35    
36  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
37  C     === Routine arguments ===  C     === Routine arguments ===
38    C- input:
39  C     bi,bj   :: tile indices  C     bi,bj   :: tile indices
40  C   iMin,iMax :: computation domain: 1rst index range  C   iMin,iMax :: computation domain: 1rst index range
41  C   jMin,jMax :: computation domain: 2nd  index range  C   jMin,jMax :: computation domain: 2nd  index range
 C- input:  
42  C     prcAtm  :: total precip from the atmosphere [kg/m2/s]  C     prcAtm  :: total precip from the atmosphere [kg/m2/s]
43  C     evpAtm  :: (Inp) evaporation to the atmosphere [kg/m2/s] (>0 if evaporate)  C     myTime  :: current Time of simulation [s]
44  C     flxSW   :: (Inp) short-wave heat flux (+=down): downward comp. only  C     myIter  :: current Iteration number in simulation
45  C                      (part.1), becomes net SW flux into ocean (part.2).  C     myThid  :: my Thread Id number
46    C-- Use fluxes hold in commom blocks
47    C- input:
48    C     icFlxSW :: net short-wave heat flux (+=down) below sea-ice, into ocean
49    C     icFlxAtm  :: net Atmospheric surf. heat flux over sea-ice [W/m2], (+=down)
50    C     icFrwAtm  :: evaporation over sea-ice to the atmosphere [kg/m2/s] (+=up)
51  C- output  C- output
52  C     evpAtm  :: (Out) net fresh-water flux (E-P) from the atmosphere [m/s] (+=up)  C     icFlxAtm  :: net Atmospheric surf. heat flux over ice+ocean [W/m2], (+=down)
53  C     flxSW   :: (Out) net surf. heat flux from the atmosphere [W/m2], (+=down)  C     icFrwAtm  :: net fresh-water flux (E-P) from the atmosphere [m/s] (+=up)
 C     myTime  :: time counter for this thread  
 C     myIter  :: iteration counter for this thread  
 C     myThid  :: thread number for this instance of the routine.  
54        INTEGER bi,bj        INTEGER bi,bj
55        INTEGER iMin, iMax        INTEGER iMin, iMax
56        INTEGER jMin, jMax        INTEGER jMin, jMax
57        _RL prcAtm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL prcAtm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
       _RL evpAtm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL flxSW (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
58        _RL  myTime        _RL  myTime
59        INTEGER myIter        INTEGER myIter
60        INTEGER myThid        INTEGER myThid
# Line 61  CEOP Line 63  CEOP
63  #ifdef ALLOW_THSICE  #ifdef ALLOW_THSICE
64  C     !LOCAL VARIABLES:  C     !LOCAL VARIABLES:
65  C     === Local variables ===  C     === Local variables ===
66  C     snowPr    :: snow precipitation [kg/m2/s]  C     iceFrac   :: fraction of grid area covered in ice
 C     agingTime :: aging time scale (s)  
 C     ageFac    :: snow aging factor [1]  
 C     albedo    :: surface albedo [0-1]  
 C     flxAtm    :: net heat flux from the atmosphere (+=down) [W/m2]  
 C     frwAtm    :: net fresh-water flux (E-P) to the atmosphere  [kg/m2/s]  
 C     Fbot      :: the oceanic heat flux already incorporated (ice_therm)  
67  C     flx2oc    :: net heat flux from the ice to the ocean (+=down) [W/m2]  C     flx2oc    :: net heat flux from the ice to the ocean (+=down) [W/m2]
68  C     frw2oc    :: fresh-water flux from the ice to the ocean  C     frw2oc    :: fresh-water flux from the ice to the ocean
69  C     fsalt     :: mass salt flux to the ocean  C     fsalt     :: mass salt flux to the ocean
70  C     frzmltMxL :: ocean mixed-layer freezing/melting potential [W/m2]  C     frzmltMxL :: ocean mixed-layer freezing/melting potential [W/m2]
71  C     TFrzOce   :: sea-water freezing temperature [oC] (function of S)  C     tFrzOce   :: sea-water freezing temperature [oC] (function of S)
72  C     isIceFree :: true for ice-free grid-cell that remains ice-free  C     isIceFree :: true for ice-free grid-cell that remains ice-free
73        INTEGER i,j  C     ageFac    :: snow aging factor [1]
74        _RL snowPr  C     snowFac   :: snowing refreshing-age factor [units of 1/snowPr]
       _RL agingTime, ageFac  
       _RL albedo  
       _RL frwAtm  
       _RL flx2oc  
       _RL frw2oc  
       _RL fsalt  
       _RL TFrzOce, cphm, frzmltMxL  
       _RL Fbot, esurp  
       _RL opFrac, icFrac  
       _RL oceV2s, oceTs  
       _RL Tsf, Tice(nlyr), qicen(nlyr)  
       _RL tmpflx(0:2), tmpdTs  
       _RL hSnow  
 c  
       _RL flxAtm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL compact(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL hIce(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
 c  
75        LOGICAL isIceFree(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        LOGICAL isIceFree(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
76          _RL     iceFrac  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
77          _RL     flx2oc   (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
78          _RL     frw2oc   (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
79          _RL     fsalt    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
80          _RL     tFrzOce  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
81          _RL     frzmltMxL(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
82          _RL ageFac
83          _RL snowFac
84          _RL cphm
85          _RL opFrac, icFrac
86  #ifdef ALLOW_DIAGNOSTICS  #ifdef ALLOW_DIAGNOSTICS
87        _RL tmpFac        _RL tmpFac
88  #endif  #endif
89          INTEGER i,j
90          LOGICAL dBugFlag
91    
92        LOGICAL dBug  C-    define grid-point location where to print debugging values
93    #include "THSICE_DEBUG.h"
94    
95   1010 FORMAT(A,1P4E14.6)   1010 FORMAT(A,1P4E14.6)
96        dBug = .FALSE.  
97  C-    Initialise flxAtm  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
98         DO j = 1-Oly, sNy+Oly  
99          DO i = 1-Olx, sNx+Olx  C-    Initialise
100            flxAtm(i,j) = 0.        dBugFlag = debugLevel.GE.debLevB
101          DO j = 1-OLy, sNy+OLy
102            DO i = 1-OLx, sNx+OLx
103            isIceFree(i,j) = .FALSE.            isIceFree(i,j) = .FALSE.
104              saltFlux(i,j,bi,bj) = 0. _d 0
105  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
106            compact(i,j) = 0.            iceFrac(i,j) = 0.
           hIce(i,j) = 0.  
107  #endif  #endif
108          ENDDO          ENDDO
109         ENDDO        ENDDO
   
       IF ( fluidIsWater ) THEN  
        DO j = jMin, jMax  
         DO i = iMin, iMax  
 c        dBug = ( bi.EQ.3 .AND. i.EQ.15 .AND. j.EQ.11 )  
110    
111  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|        ageFac = 1. _d 0 - thSIce_deltaT/snowAgTime
112  C    part.1 : ice-covered fraction ;        snowFac = thSIce_deltaT/(rhos*hNewSnowAge)
113  C     Solve for surface and ice temperature (implicitly) ; compute surf. fluxes        DO j = jMin, jMax
114           DO i = iMin, iMax
115            IF (iceMask(i,j,bi,bj).GT.0. _d 0) THEN
116    C--  Snow aging :
117              snowAge(i,j,bi,bj) = thSIce_deltaT
118         &                       + snowAge(i,j,bi,bj)*ageFac
119              IF ( snowPrc(i,j,bi,bj).GT.0. _d 0 )
120         &      snowAge(i,j,bi,bj) = snowAge(i,j,bi,bj)
121         &          * EXP( - snowFac*snowPrc(i,j,bi,bj) )
122    c    &          * EXP( -(thSIce_deltaT*snowPrc(i,j,bi,bj)/rhos)
123    c    &                  /hNewSnowAge )
124  C-------  C-------
125           IF (iceMask(i,j,bi,bj).GT.0. _d 0) THEN  C note: Any flux of mass (here fresh water) that enter or leave the system
126            icFrac  = iceMask(i,j,bi,bj)  C       with a non zero energy HAS TO be counted: add snow precip.
127            TFrzOce = -mu_Tf*sOceMxL(i,j,bi,bj)            icFlxAtm(i,j,bi,bj) = icFlxAtm(i,j,bi,bj)
128            hIce(i,j)    = iceHeight(i,j,bi,bj)       &                        - Lfresh*snowPrc(i,j,bi,bj)
129            hSnow   = snowHeight(i,j,bi,bj)  C--
130            Tsf     = Tsrf(i,j,bi,bj)          ENDIF
           qicen(1)= Qice1(i,j,bi,bj)  
           qicen(2)= Qice2(i,j,bi,bj)  
           IF ( dBug ) THEN  
            WRITE(6,'(A,2I4,2I2)') 'ThSI_FWD: i,j=',i,j,bi,bj  
            WRITE(6,1010) 'ThSI_FWD:-0- iceMask, hIc, hSn, Tsf  =',  
      &                                 icFrac, hIce,hSnow,Tsf  
           ENDIF  
   
           CALL THSICE_ALBEDO(  
      I               hIce(i,j), hSnow, Tsf, snowAge(i,j,bi,bj),  
      O               albedo,  
      I               myThid )  
           flxSW(i,j) = flxSW(i,j)*(1. _d 0 - albedo)  
           siceAlb(i,j,bi,bj) = albedo  
   
           CALL THSICE_SOLVE4TEMP(  
      I          useBulkForce, tmpflx, TFrzOce, hIce(i,j), hSnow,  
      U          flxSW(i,j), Tsf, qicen,  
      O          Tice, sHeating(i,j,bi,bj), flxCndBt(i,j,bi,bj),  
      O          tmpdTs, flxAtm(i,j), evpAtm(i,j),  
      I          i,j, bi,bj, myThid)  
   
 #ifdef SHORTWAVE_HEATING  
 C--    Update Fluxes :  
           opFrac= 1. _d 0-icFrac  
           Qsw(i,j,bi,bj)=-icFrac*flxSW(i,j) +opFrac*Qsw(i,j,bi,bj)  
 #endif  
 C--    Update Sea-Ice state :  
           Tsrf(i,j,bi,bj) =Tsf  
           Tice1(i,j,bi,bj)=Tice(1)  
           Tice2(i,j,bi,bj)=Tice(2)  
           Qice1(i,j,bi,bj)=qicen(1)  
           Qice2(i,j,bi,bj)=qicen(2)  
           IF ( dBug ) THEN  
            WRITE(6,1010) 'ThSI_FWD: Tsf, Tice(1,2), TFrzOce =',  
      &                              Tsf, Tice, TFrzOce  
            WRITE(6,1010) 'ThSI_FWD: sHeat,fxCndBt, fxAtm,evAtm=',  
      &                  sHeating(i,j,bi,bj), flxCndBt(i,j,bi,bj),  
      &                  flxAtm(i,j), evpAtm(i,j)  
           ENDIF  
          ENDIF  
         ENDDO  
131         ENDDO         ENDDO
132        ENDIF        ENDDO
       dBug = .FALSE.  
133    
134  #ifdef ALLOW_DIAGNOSTICS  #ifdef ALLOW_DIAGNOSTICS
135        IF ( useDiagnostics ) THEN        IF ( useDiagnostics ) THEN
# Line 198  C    part.2 : ice-covered fraction ; Line 153  C    part.2 : ice-covered fraction ;
153  C     change in ice/snow thickness and ice-fraction  C     change in ice/snow thickness and ice-fraction
154  C     note: can only reduce the ice-fraction but not increase it.  C     note: can only reduce the ice-fraction but not increase it.
155  C-------  C-------
       agingTime = 50. _d 0 * 86400. _d 0  
       ageFac = 1. _d 0 - thSIce_deltaT/agingTime  
156        DO j = jMin, jMax        DO j = jMin, jMax
157         DO i = iMin, iMax         DO i = iMin, iMax
 c       dBug = ( bi.EQ.3 .AND. i.EQ.15 .AND. j.EQ.11 )  
158    
159          TFrzOce = -mu_Tf*sOceMxL(i,j,bi,bj)          tFrzOce(i,j) = -mu_Tf*sOceMxL(i,j,bi,bj)
         oceTs   = tOceMxL(i,j,bi,bj)  
160          cphm    = cpwater*rhosw*hOceMxL(i,j,bi,bj)          cphm    = cpwater*rhosw*hOceMxL(i,j,bi,bj)
161          frzmltMxL = (TFrzOce-oceTs)*cphm/ocean_deltaT          frzmltMxL(i,j) = ( tFrzOce(i,j)-tOceMxL(i,j,bi,bj) )
162         &                 * cphm/ocean_deltaT
163          Fbot   = 0. _d 0          iceFrac(i,j) = iceMask(i,j,bi,bj)
164          saltFlux(i,j,bi,bj) = 0. _d 0          flx2oc(i,j)  = icFlxSW(i,j,bi,bj)
         compact(i,j)= iceMask(i,j,bi,bj)  
165  C-------  C-------
166          IF (dBug .AND. (frzmltMxL.GT.0. .OR. compact(i,j).GT.0.) ) THEN  #ifdef ALLOW_DBUG_THSICE
167            IF ( dBug(i,j,bi,bj) ) THEN
168             IF (frzmltMxL(i,j).GT.0. .OR. iceFrac(i,j).GT.0.) THEN
169            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
170            WRITE(6,1010) 'ThSI_FWD:-1- iceMask, hIc, hSn, Tsf  =',            WRITE(6,1010) 'ThSI_FWD:-1- iceMask, hIc, hSn, Tsf  =',
171       &                  compact(i,j), iceHeight(i,j,bi,bj),       &                  iceFrac(i,j), iceHeight(i,j,bi,bj),
172       &                  snowHeight(i,j,bi,bj), Tsrf(i,j,bi,bj)       &                  snowHeight(i,j,bi,bj), Tsrf(i,j,bi,bj)
173            WRITE(6,1010) 'ThSI_FWD: ocTs,TFrzOce,frzmltMxL,Qnet=',            WRITE(6,1010) 'ThSI_FWD: ocTs,tFrzOce,frzmltMxL,Qnet=',
174       &                     oceTs, TFrzOce, frzmltMxL,Qnet(i,j,bi,bj)       &                     tOceMxL(i,j,bi,bj), tFrzOce(i,j),
175         &                     frzmltMxL(i,j), Qnet(i,j,bi,bj)
176             ENDIF
177             IF (iceFrac(i,j).GT.0.)
178         &    WRITE(6,1010) 'ThSI_FWD: icFrac,flxAtm,evpAtm,flxSnw=',
179         &      iceFrac(i,j), icFlxAtm(i,j,bi,bj),
180         &      icFrwAtm(i,j,bi,bj),-Lfresh*snowPrc(i,j,bi,bj)
181          ENDIF          ENDIF
182  C-------  #endif
183          IF (iceMask(i,j,bi,bj).GT.0. _d 0) THEN         ENDDO
184          ENDDO
           oceV2s  = v2ocMxL(i,j,bi,bj)  
           snowPr  = snowPrc(i,j,bi,bj)  
           hIce(i,j)    = iceHeight(i,j,bi,bj)  
           hSnow   = snowHeight(i,j,bi,bj)  
           Tsf     = Tsrf(i,j,bi,bj)  
           qicen(1)= Qice1(i,j,bi,bj)  
           qicen(2)= Qice2(i,j,bi,bj)  
           flx2oc  = flxSW(i,j)  
   
           CALL THSICE_CALC_THICKN(  
      I          frzmltMxL, TFrzOce, oceTs, oceV2s, snowPr,  
      I          sHeating(i,j,bi,bj), flxCndBt(i,j,bi,bj), evpAtm(i,j),  
      U          compact(i,j), hIce(i,j), hSnow, Tsf, qicen, flx2oc,  
      O          frw2oc, fsalt, Fbot,  
      I          dBug, myThid)  
   
 C- note : snowPr was not supposed to be modified in THSICE_THERM ;  
 C         but to reproduce old results, is reset to zero if Tsf >= 0  
           snowPrc(i,j,bi,bj) = snowPr  
   
 C--  Snow aging :  
           snowAge(i,j,bi,bj) = thSIce_deltaT  
      &                       + snowAge(i,j,bi,bj)*ageFac  
           IF ( snowPr.GT.0. _d 0 )  
      &      snowAge(i,j,bi,bj) = snowAge(i,j,bi,bj)  
      &          * EXP( -(thSIce_deltaT*snowPr/rhos)/hNewSnowAge )  
 C--  
   
 C-- Diagnostic of Atmospheric Fluxes over sea-ice :  
           frwAtm = evpAtm(i,j) - prcAtm(i,j)  
 C note: Any flux of mass (here fresh water) that enter or leave the system  
 C       with a non zero energy HAS TO be counted: add snow precip.  
           flxAtm(i,j) = flxAtm(i,j) - Lfresh*snowPrc(i,j,bi,bj)  
   
 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  
       IF (dBug) WRITE(6,1010) 'ThSI_FWD: icFrac,flxAtm,evpAtm,flxSnw=',  
      &  iceMask(i,j,bi,bj),flxAtm(i,j),evpAtm(i,j),-Lfresh*snowPr  
       IF (dBug) WRITE(6,1010) 'ThSI_FWD: compact,flx2oc,fsalt,frw2oc=',  
      &   compact(i,j),flx2oc,fsalt,frw2oc  
 #ifdef CHECK_ENERGY_CONSERV  
           icFrac = iceMask(i,j,bi,bj)  
           CALL THSICE_CHECK_CONSERV( dBug, i, j, bi, bj, 0,  
      I            icFrac, compact(i,j), hIce(i,j), hSnow, qicen,  
      I            flx2oc, frw2oc, fsalt, flxAtm(i,j), frwAtm,  
      I            myTime, myIter, myThid )  
 #endif /* CHECK_ENERGY_CONSERV */  
 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  
185    
186  C--    Update Sea-Ice state :        CALL THSICE_CALC_THICKN(
187  c         iceMask(i,j,bi,bj)=compact       I          bi, bj, siLo, siHi, sjLo, sjHi,
188            iceHeight(i,j,bi,bj) = hIce(i,j)       I          iMin,iMax, jMin,jMax, dBugFlag,
189            snowHeight(i,j,bi,bj)= hSnow       I          iceMask(siLo,sjLo,bi,bj), tFrzOce,
190            Tsrf(i,j,bi,bj) =Tsf       I          tOceMxL(siLo,sjLo,bi,bj), v2ocMxL(siLo,sjLo,bi,bj),
191            Qice1(i,j,bi,bj)=qicen(1)       I          snowPrc(siLo,sjLo,bi,bj), prcAtm,
192            Qice2(i,j,bi,bj)=qicen(2)       I          sHeating(siLo,sjLo,bi,bj), flxCndBt(siLo,sjLo,bi,bj),
193         U          iceFrac, iceHeight(siLo,sjLo,bi,bj),
194         U          snowHeight(siLo,sjLo,bi,bj), Tsrf(siLo,sjLo,bi,bj),
195         U          Qice1(siLo,sjLo,bi,bj), Qice2(siLo,sjLo,bi,bj),
196         U          icFrwAtm(siLo,sjLo,bi,bj), frzmltMxL, flx2oc,
197         O          frw2oc, fsalt,
198         I          myTime, myIter, myThid )
199    
200  C--    Net fluxes :  C--    Net fluxes :
201            frw2oc = frw2oc + (prcAtm(i,j)-snowPrc(i,j,bi,bj))        DO j = jMin, jMax
202           DO i = iMin, iMax
203            IF (iceMask(i,j,bi,bj).GT.0. _d 0) THEN
204  C-     weighted average net fluxes:  C-     weighted average net fluxes:
205            icFrac = iceMask(i,j,bi,bj)            icFrac = iceMask(i,j,bi,bj)
206            opFrac= 1. _d 0-icFrac            opFrac= 1. _d 0-icFrac
207            flxAtm(i,j) = icFrac*flxAtm(i,j) - opFrac*Qnet(i,j,bi,bj)            icFlxAtm(i,j,bi,bj) = icFrac*icFlxAtm(i,j,bi,bj)
208            frwAtm =     icFrac*frwAtm + opFrac*rhofw*EmPmR(i,j,bi,bj)       &                        - opFrac*Qnet(i,j,bi,bj)
209            Qnet(i,j,bi,bj)=-icFrac*flx2oc +opFrac*Qnet(i,j,bi,bj)            icFrwAtm(i,j,bi,bj) = icFrac*icFrwAtm(i,j,bi,bj)
210            EmPmR(i,j,bi,bj)=-icFrac*frw2oc/rhofw+opFrac*EmPmR(i,j,bi,bj)       &                        + opFrac*rhofw*EmPmR(i,j,bi,bj)
211            saltFlux(i,j,bi,bj)=-icFrac*fsalt            Qnet(i,j,bi,bj) = -icFrac*flx2oc(i,j) + opFrac*Qnet(i,j,bi,bj)
212              EmPmR(i,j,bi,bj)= -icFrac*frw2oc(i,j)/rhofw
213            IF (dBug) WRITE(6,1010)       &                    +  opFrac*EmPmR(i,j,bi,bj)
214       &          'ThSI_FWD:-3- compact, hIc, hSn, Qnet =',            saltFlux(i,j,bi,bj) = -icFrac*fsalt(i,j)
215       &                        compact(i,j),hIce(i,j),hSnow,  
216       &                        Qnet(i,j,bi,bj)  #ifdef ALLOW_DBUG_THSICE
217              IF (dBug(i,j,bi,bj)) WRITE(6,1010)
218         &          'ThSI_FWD:-3- iceFrac, hIc, hSn, Qnet =',
219         &           iceFrac(i,j), iceHeight(i,j,bi,bj),
220         &           snowHeight(i,j,bi,bj), Qnet(i,j,bi,bj)
221    #endif
222    
223          ELSEIF (hOceMxL(i,j,bi,bj).gt.0. _d 0) THEN          ELSEIF (hOceMxL(i,j,bi,bj).gt.0. _d 0) THEN
224            flxAtm(i,j) =  -Qnet(i,j,bi,bj)            icFlxAtm(i,j,bi,bj) = -Qnet(i,j,bi,bj)
225            frwAtm = rhofw*EmPmR(i,j,bi,bj)            icFrwAtm(i,j,bi,bj) = rhofw*EmPmR(i,j,bi,bj)
226          ELSE          ELSE
227            flxAtm(i,j) = 0. _d 0            icFlxAtm(i,j,bi,bj) = 0. _d 0
228            frwAtm      = 0. _d 0            icFrwAtm(i,j,bi,bj) = 0. _d 0
229          ENDIF          ENDIF
230           ENDDO
231          ENDDO
232    
233  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
234  C    part.3 : freezing of sea-water  C    part.3 : freezing of sea-water
235  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
236  C-------  C-------
237  c       compact(i,j) = iceMask(i,j,bi,bj)        CALL THSICE_EXTEND(
238          hIce(i,j)   = iceHeight(i,j,bi,bj)       I          bi, bj, siLo, siHi, sjLo, sjHi,
239          hSnow  = snowHeight(i,j,bi,bj)       I          iMin,iMax, jMin,jMax, dBugFlag,
240         I          frzmltMxL, tFrzOce,
241          esurp  = frzmltMxL - Fbot*iceMask(i,j,bi,bj)       I          tOceMxL(siLo,sjLo,bi,bj),
242          IF (esurp.GT.0. _d 0) THEN       U          iceFrac, iceHeight(siLo,sjLo,bi,bj),
243            icFrac = compact(i,j)       U          snowHeight(siLo,sjLo,bi,bj), Tsrf(siLo,sjLo,bi,bj),
244            qicen(1)= Qice1(i,j,bi,bj)       U          Tice1(siLo,sjLo,bi,bj), Tice2(siLo,sjLo,bi,bj),
245            qicen(2)= Qice2(i,j,bi,bj)       U          Qice1(siLo,sjLo,bi,bj), Qice2(siLo,sjLo,bi,bj),
246            CALL THSICE_EXTEND(       O          flx2oc, frw2oc, fsalt,
247       I               esurp, TFrzOce,       I          myTime, myIter, myThid )
248       U               oceTs, compact(i,j), hIce(i,j), hSnow, qicen,  
249       O               flx2oc, frw2oc, fsalt,        DO j = jMin, jMax
250       I               dBug, myThid )         DO i = iMin, iMax
251  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|          IF (frzmltMxL(i,j).GT.0. _d 0) THEN
       IF (dBug) WRITE(6,1010) 'ThSI_FWD: compact,flx2oc,fsalt,frw2oc='  
      &                 ,compact(i,j),flx2oc,fsalt,frw2oc  
 #ifdef CHECK_ENERGY_CONSERV  
           tmpflx(1) = 0.  
           tmpflx(2) = 0.  
           CALL THSICE_CHECK_CONSERV( dBug, i, j, bi, bj, 1,  
      I            icFrac, compact(i,j), hIce(i,j), hSnow, qicen,  
      I            flx2oc, frw2oc, fsalt, tmpflx(1), tmpflx(2),  
      I            myTime, myIter, myThid )  
 #endif /* CHECK_ENERGY_CONSERV */  
 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  
 C--    Update Sea-Ice state :  
           IF ( compact(i,j).GT.0. _d 0 .AND. icFrac.EQ.0. _d 0) THEN  
              Tsrf(i,j,bi,bj)  = TFrzOce  
              Tice1(i,j,bi,bj) = TFrzOce  
              Tice2(i,j,bi,bj) = TFrzOce  
              Qice1(i,j,bi,bj) = qicen(1)  
              Qice2(i,j,bi,bj) = qicen(2)  
           ENDIF  
           iceHeight(i,j,bi,bj) = hIce(i,j)  
           snowHeight(i,j,bi,bj)= hSnow  
252  C--    Net fluxes :  C--    Net fluxes :
253            Qnet(i,j,bi,bj) = Qnet(i,j,bi,bj) - flx2oc            Qnet(i,j,bi,bj) = Qnet(i,j,bi,bj) - flx2oc(i,j)
254            EmPmR(i,j,bi,bj)= EmPmR(i,j,bi,bj)- frw2oc/rhofw            EmPmR(i,j,bi,bj)= EmPmR(i,j,bi,bj)- frw2oc(i,j)/rhofw
255            saltFlux(i,j,bi,bj)=saltFlux(i,j,bi,bj) - fsalt            saltFlux(i,j,bi,bj)=saltFlux(i,j,bi,bj) - fsalt(i,j)
256    
257            IF (dBug) WRITE(6,1010)  #ifdef ALLOW_DBUG_THSICE
258       &         'ThSI_FWD:-4- compact, hIc, hSn, Qnet =',            IF (dBug(i,j,bi,bj)) WRITE(6,1010)
259       &         compact(i,j),hIce(i,j),hSnow,       &         'ThSI_FWD:-4- iceFrac, hIc, hSn, Qnet =',
260       &         Qnet(i,j,bi,bj)       &           iceFrac(i,j), iceHeight(i,j,bi,bj),
261  C--   - if esurp > 0 : end       &           snowHeight(i,j,bi,bj), Qnet(i,j,bi,bj)
262    #endif
263          ENDIF          ENDIF
264    
265          IF ( hOceMxL(i,j,bi,bj).GT.0. _d 0 )          IF ( hOceMxL(i,j,bi,bj).GT.0. _d 0 )
266       &    isIceFree(i,j) = iceMask(i,j,bi,bj).LE.0. _d 0       &    isIceFree(i,j) = iceMask(i,j,bi,bj).LE.0. _d 0
267       &                       .AND.   compact(i,j) .LE.0. _d 0       &                       .AND.   iceFrac(i,j) .LE.0. _d 0
268          IF ( compact(i,j) .GT. 0. _d 0 ) THEN          IF ( iceFrac(i,j) .GT. 0. _d 0 ) THEN
269            iceMask(i,j,bi,bj)=compact(i,j)            iceMask(i,j,bi,bj)=iceFrac(i,j)
270            IF ( hSnow .EQ. 0. _d 0 ) snowAge(i,j,bi,bj) = 0. _d 0            IF ( snowHeight(i,j,bi,bj).EQ.0. _d 0 )
271         &     snowAge(i,j,bi,bj) = 0. _d 0
272          ELSE          ELSE
273            iceMask(i,j,bi,bj)  = 0. _d 0            iceMask(i,j,bi,bj)  = 0. _d 0
274            iceHeight(i,j,bi,bj)= 0. _d 0            iceHeight(i,j,bi,bj)= 0. _d 0
275            snowHeight(i,j,bi,bj)=0. _d 0            snowHeight(i,j,bi,bj)=0. _d 0
276            snowAge(i,j,bi,bj)  = 0. _d 0            snowAge(i,j,bi,bj)  = 0. _d 0
277            Tsrf(i,j,bi,bj)     = oceTs            Tsrf(i,j,bi,bj)     = tOceMxL(i,j,bi,bj)
278            Tice1(i,j,bi,bj)    = 0. _d 0            Tice1(i,j,bi,bj)    = 0. _d 0
279            Tice2(i,j,bi,bj)    = 0. _d 0            Tice2(i,j,bi,bj)    = 0. _d 0
280            Qice1(i,j,bi,bj)    = 0. _d 0            Qice1(i,j,bi,bj)    = 0. _d 0
281            Qice2(i,j,bi,bj)    = 0. _d 0            Qice2(i,j,bi,bj)    = 0. _d 0
282          ENDIF          ENDIF
283    
 C--     Return atmospheric fluxes in evpAtm & flxSW (same sign and units):  
         evpAtm(i,j) = frwAtm  
         flxSW (i,j) = flxAtm(i,j)  
   
284  #ifdef ATMOSPHERIC_LOADING  #ifdef ATMOSPHERIC_LOADING
285  C--     Compute Sea-Ice Loading (= mass of sea-ice + snow / area unit)  C--     Compute Sea-Ice Loading (= mass of sea-ice + snow / area unit)
286          sIceLoad(i,j,bi,bj) = ( snowHeight(i,j,bi,bj)*rhos          sIceLoad(i,j,bi,bj) = ( snowHeight(i,j,bi,bj)*rhos

Legend:
Removed from v.1.16  
changed lines
  Added in v.1.17

  ViewVC Help
Powered by ViewVC 1.1.22