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

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

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

revision 1.8 by jmc, Thu May 25 18:03:25 2006 UTC revision 1.9 by mlosch, Tue May 30 22:48:59 2006 UTC
# Line 8  C     !ROUTINE: THSICE_SOLVE4TEMP Line 8  C     !ROUTINE: THSICE_SOLVE4TEMP
8  C     !INTERFACE:  C     !INTERFACE:
9        SUBROUTINE THSICE_SOLVE4TEMP(        SUBROUTINE THSICE_SOLVE4TEMP(
10       I                  bi, bj, siLo, siHi, sjLo, sjHi,       I                  bi, bj, siLo, siHi, sjLo, sjHi,
11       I                  iMin,iMax, jMin,jMax, dBugFlag, useBlkFlx,       I                  iMin,iMax, jMin,jMax, dBugFlag,
12         I                  useBulkForce, useEXF,
13       I                  iceMask, hIce, hSnow, tFrz, flxExSW,       I                  iceMask, hIce, hSnow, tFrz, flxExSW,
14       U                  flxSW, tSrf, qIc1, qIc2,       U                  flxSW, tSrf, qIc1, qIc2,
15       O                  tIc1, tIc2, dTsrf,       O                  tIc1, tIc2, dTsrf,
# Line 54  C     bi,bj       :: tile indices Line 55  C     bi,bj       :: tile indices
55  C     iMin,iMax   :: computation domain: 1rst index range  C     iMin,iMax   :: computation domain: 1rst index range
56  C     jMin,jMax   :: computation domain: 2nd  index range  C     jMin,jMax   :: computation domain: 2nd  index range
57  C     dBugFlag    :: allow to print debugging stuff (e.g. on 1 grid point).  C     dBugFlag    :: allow to print debugging stuff (e.g. on 1 grid point).
58  C     useBlkFlx   :: use surf. fluxes from bulk-forcing external S/R  C     useBulkForce:: use surf. fluxes from bulk-forcing external S/R
59    C     useEXF      :: use surf. fluxes from exf          external S/R
60  C---  Input:  C---  Input:
61  C         iceMask :: sea-ice fractional mask [0-1]  C         iceMask :: sea-ice fractional mask [0-1]
62  C  hIce    (hi)   :: ice height [m]  C  hIce    (hi)   :: ice height [m]
# Line 86  C     myThid      :: my Thread Id number Line 88  C     myThid      :: my Thread Id number
88        INTEGER iMin, iMax        INTEGER iMin, iMax
89        INTEGER jMin, jMax        INTEGER jMin, jMax
90        LOGICAL dBugFlag        LOGICAL dBugFlag
91        LOGICAL useBlkFlx        LOGICAL useBulkForce
92          LOGICAL useEXF
93        _RL iceMask(siLo:siHi,sjLo:sjHi)        _RL iceMask(siLo:siHi,sjLo:sjHi)
94        _RL hIce   (siLo:siHi,sjLo:sjHi)        _RL hIce   (siLo:siHi,sjLo:sjHi)
95        _RL hSnow  (siLo:siHi,sjLo:sjHi)        _RL hSnow  (siLo:siHi,sjLo:sjHi)
# Line 148  C     dEvdT          :: derivative of ev Line 151  C     dEvdT          :: derivative of ev
151  c     _RL  Tsf_start     ! old value of Tsf  c     _RL  Tsf_start     ! old value of Tsf
152        _RL  dt            ! timestep        _RL  dt            ! timestep
153        INTEGER iceornot        INTEGER iceornot
154          LOGICAL useBlkFlx
155    
156  C-    define grid-point location where to print debugging values  C-    define grid-point location where to print debugging values
157  #include "THSICE_DEBUG.h"  #include "THSICE_DEBUG.h"
# Line 157  C-    define grid-point location where t Line 161  C-    define grid-point location where t
161    
162  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
163    
164          useBlkFlx = useEXF .OR. useBulkForce
165    
166        dt  = thSIce_deltaT        dt  = thSIce_deltaT
167        DO j = jMin, jMax        DO j = jMin, jMax
168         DO i = iMin, iMax         DO i = iMin, iMax
# Line 249  C Compute top surface flux. Line 255  C Compute top surface flux.
255           ELSE           ELSE
256                iceornot=1                iceornot=1
257           ENDIF           ENDIF
258           CALL THSICE_GET_BULKF(           IF ( useBulkForce ) THEN
259       I                        iceornot, Tsf,            CALL THSICE_GET_BULKF(
260       O                        flxExceptSw, df0dT, evap, dEvdT,       I                         iceornot, Tsf,
261       I                        i,j,bi,bj,myThid )       O                         flxExceptSw, df0dT, evap, dEvdT,
262         I                         i,j,bi,bj,myThid )
263             ELSEIF ( useEXF ) THEN
264              CALL THSICE_GET_EXF  (
265         I                         iceornot, Tsf,
266         O                         flxExceptSw, df0dT, evap, dEvdT,
267         I                         i,j,bi,bj,myThid )
268             ENDIF
269          ELSE          ELSE
270           flxExceptSw = flxExSW(i,j,1)           flxExceptSw = flxExSW(i,j,1)
271           df0dT = flxExSW(i,j,2)           df0dT = flxExSW(i,j,2)
# Line 287  C with different coefficients. Line 300  C with different coefficients.
300              ELSE              ELSE
301                   iceornot=1                   iceornot=1
302              ENDIF              ENDIF
303              CALL THSICE_GET_BULKF(              IF ( useBulkForce ) THEN
304       I                        iceornot, Tsf,               CALL THSICE_GET_BULKF(
305       O                        flxExceptSw, df0dT, evap, dEvdT,       I                            iceornot, Tsf,
306       I                        i,j,bi,bj,myThid )       O                            flxExceptSw, df0dT, evap, dEvdT,
307         I                            i,j,bi,bj,myThid )
308                ELSEIF ( useEXF ) THEN
309                 CALL THSICE_GET_EXF  (
310         I                            iceornot, Tsf,
311         O                            flxExceptSw, df0dT, evap, dEvdT,
312         I                            i,j,bi,bj,myThid )
313                ENDIF
314              dTsf = 0. _d 0              dTsf = 0. _d 0
315             ELSE             ELSE
316              flxExceptSw = flxExSW(i,j,0)              flxExceptSw = flxExSW(i,j,0)

Legend:
Removed from v.1.8  
changed lines
  Added in v.1.9

  ViewVC Help
Powered by ViewVC 1.1.22