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

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

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

revision 1.7 by heimbach, Sun Apr 9 17:35:30 2006 UTC revision 1.10 by mlosch, Mon Jun 5 22:33:50 2006 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    
6  CBOP  CBOP
7  C     !ROUTINE: THSICE_MAIN  C     !ROUTINE: THSICE_MAIN
8  C     !INTERFACE:  C     !INTERFACE:
9        SUBROUTINE THSICE_MAIN(        SUBROUTINE THSICE_MAIN(
10       I                        myTime, myIter, myThid )       I                        myTime, myIter, myThid )
11  C     !DESCRIPTION: \bv  C     !DESCRIPTION: \bv
12  C     *==========================================================*  C     *==========================================================*
13  C     | S/R  THSICE_MAIN              C     | S/R  THSICE_MAIN
14  C     | o Therm_SeaIce main routine.  C     | o Therm_SeaIce main routine.
15  C     |   step forward Thermodynamic_SeaIce variables and modify  C     |   step forward Thermodynamic_SeaIce variables and modify
16  C     |    ocean surface forcing accordingly.  C     |    ocean surface forcing accordingly.
17  C     *==========================================================*  C     *==========================================================*
# Line 33  C     === Global variables === Line 33  C     === Global variables ===
33  # include "tamc.h"  # include "tamc.h"
34  # include "tamc_keys.h"  # include "tamc_keys.h"
35  #endif  #endif
36    
37  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
38  C     === Routine arguments ===  C     === Routine arguments ===
39  C     myIter :: iteration counter for this thread  C     myIter :: iteration counter for this thread
# Line 52  C     === Local variables === Line 52  C     === Local variables ===
52        INTEGER iMin, iMax        INTEGER iMin, iMax
53        INTEGER jMin, jMax        INTEGER jMin, jMax
54        _RL prcAtm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL prcAtm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
55        _RL evpAtm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  c     _RL evpAtm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
56        _RL flxSW (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  c     _RL flxAtm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
57    c     _RL flxSW (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
58    
59        _RL tauFac        _RL tauFac
60    
# Line 61  C---+----1----+----2----+----3----+----4 Line 62  C---+----1----+----2----+----3----+----4
62    
63        IF ( stressReduction.GT. 0. _d 0 ) THEN        IF ( stressReduction.GT. 0. _d 0 ) THEN
64  C-     needs new Ice Fraction in halo region to apply wind-stress reduction  C-     needs new Ice Fraction in halo region to apply wind-stress reduction
65         iMin = 1-Olx         iMin = 1-OLx
66         iMax = sNx+Olx-1         iMax = sNx+OLx-1
67         jMin = 1-Oly         jMin = 1-OLy
68         jMax = sNy+Oly-1         jMax = sNy+OLy-1
69  #ifdef ATMOSPHERIC_LOADING  #ifdef ATMOSPHERIC_LOADING
70        ELSEIF ( useRealFreshWaterFlux ) THEN        ELSEIF ( useRealFreshWaterFlux ) THEN
71  C-     needs sea-ice loading in part of the halo regions for grad.Phi0surf  C-     needs sea-ice loading in part of the halo regions for grad.Phi0surf
# Line 104  C--     Mixed layer thickness: take the Line 105  C--     Mixed layer thickness: take the
105            DO j = jMin, jMax            DO j = jMin, jMax
106             DO i = iMin, iMax             DO i = iMin, iMax
107               hOceMxL(i,j,bi,bj) = drF(1)*h0FacC(i,j,1,bi,bj)               hOceMxL(i,j,bi,bj) = drF(1)*h0FacC(i,j,1,bi,bj)
108       &                                  *rStarFacC(i,j,bi,bj)       &                                  *rStarFacC(i,j,bi,bj)
109             ENDDO             ENDDO
110            ENDDO            ENDDO
111           ELSE           ELSE
# Line 134  CADJ STORE uvel (:,:,1,bi,bj) = comlev1_ Line 135  CADJ STORE uvel (:,:,1,bi,bj) = comlev1_
135  CADJ STORE vvel (:,:,1,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte  CADJ STORE vvel (:,:,1,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte
136  #endif  #endif
137    
138           DO j = jMin, jMax          DO j = jMin, jMax
139            DO i = iMin, iMax           DO i = iMin, iMax
140             tOceMxL(i,j,bi,bj) = theta(i,j,1,bi,bj)            tOceMxL(i,j,bi,bj) = theta(i,j,1,bi,bj)
141             sOceMxL(i,j,bi,bj) = salt (i,j,1,bi,bj)            sOceMxL(i,j,bi,bj) = salt (i,j,1,bi,bj)
142             v2ocMxL(i,j,bi,bj) =            v2ocMxL(i,j,bi,bj) =
143       &              ( uvel(i,j,1,bi,bj)*uvel(i,j,1,bi,bj)       &              ( uvel(i,j,1,bi,bj)*uvel(i,j,1,bi,bj)
144       &              + uvel(i+1,j,1,bi,bj)*uvel(i+1,j,1,bi,bj)       &              + uvel(i+1,j,1,bi,bj)*uvel(i+1,j,1,bi,bj)
145       &              + vvel(i,j+1,1,bi,bj)*vvel(i,j+1,1,bi,bj)       &              + vvel(i,j+1,1,bi,bj)*vvel(i,j+1,1,bi,bj)
146       &              + vvel(i,j,1,bi,bj)*vvel(i,j,1,bi,bj)       &              + vvel(i,j,1,bi,bj)*vvel(i,j,1,bi,bj)
147       &              )*0.5 _d 0       &              )*0.5 _d 0
148             prcAtm(i,j) = 0.            prcAtm(i,j) = 0.
149             evpAtm(i,j) = 0.            icFrwAtm(i,j,bi,bj) = 0. _d 0
150             flxSW (i,j) = 0.            icFlxAtm(i,j,bi,bj) = 0. _d 0
151             snowPrc(i,j,bi,bj) = 0. _d 0            icFlxSW (i,j,bi,bj) = 0. _d 0
152             siceAlb(i,j,bi,bj) = 0. _d 0            snowPrc(i,j,bi,bj) = 0. _d 0
153            ENDDO            siceAlb(i,j,bi,bj) = 0. _d 0
154           ENDDO           ENDDO
155            ENDDO
156    
157  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
158  CADJ STORE iceMask = comlev1, key = iicekey  CADJ STORE iceMask = comlev1, key = iicekey
# Line 175  CADJ STORE qnet    = comlev1, key = iice Line 177  CADJ STORE qnet    = comlev1, key = iice
177  #endif  #endif
178    
179  #ifdef ALLOW_BULK_FORCE  #ifdef ALLOW_BULK_FORCE
180           IF ( useBulkforce ) THEN          IF ( useBulkforce ) THEN
181             CALL THSICE_GET_PRECIP(           CALL THSICE_GET_PRECIP(
182       I                  iceMask,       I                  iceMask,
183       O                  prcAtm, snowPrc(1-Olx,1-Oly,bi,bj), flxSW,       O                  prcAtm, snowPrc(1-OLx,1-OLy,bi,bj),
184         O                  icFlxSW(1-OLx,1-OLy,bi,bj),
185       I                  iMin,iMax,jMin,jMax, bi,bj, myThid )       I                  iMin,iMax,jMin,jMax, bi,bj, myThid )
186           ENDIF          ENDIF
187    #endif
188    #ifdef ALLOW_EXF
189            IF ( useEXF ) THEN
190             CALL THSICE_MAP_EXF(
191         I                  iceMask,
192         O                  prcAtm, snowPrc(1-OLx,1-OLy,bi,bj),
193         O                  icFlxSW(1-OLx,1-OLy,bi,bj),
194         I                  iMin,iMax,jMin,jMax, bi,bj, myThid )
195            ENDIF
196  #endif  #endif
197    
198    
199           CALL THSICE_STEP_FWD(          CALL THSICE_STEP_TEMP(
200       I                     bi, bj, iMin, iMax, jMin, jMax,       I                     bi, bj, iMin, iMax, jMin, jMax,
      I                     prcAtm,  
      U                     evpAtm, flxSW,  
201       I                     myTime, myIter, myThid )       I                     myTime, myIter, myThid )
202    
203           CALL THSICE_AVE(          CALL THSICE_STEP_FWD(
204       I                   evpAtm, flxSW,       I                     bi, bj, iMin, iMax, jMin, jMax,
205       I                   bi,bj, myTime, myIter, myThid )       I                     prcAtm,
206         I                     myTime, myIter, myThid )
207    
208            CALL THSICE_AVE(
209         I                     bi,bj, myTime, myIter, myThid )
210    
211  c      ENDDO  c      ENDDO
212  c     ENDDO  c     ENDDO
213    
214  c       IF ( .FALSE. ) THEN  #ifdef ALLOW_SEAICE        
215    C--   If useSEAICE=.true., the stress is computed in seaice_model,
216    C--   so that it does not need any further reduction
217            IF ( .NOT. useSEAICE ) THEN
218    #endif /* ALLOW_SEAICE */
219  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
220  CADJ STORE fu(:,:,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte  CADJ STORE fu(:,:,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte
221  CADJ STORE fv(:,:,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte  CADJ STORE fv(:,:,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte
222  #endif  #endif
223          IF ( stressReduction.GT. 0. _d 0 ) THEN           IF ( stressReduction.GT. 0. _d 0 ) THEN
224           DO j = jMin, jMax            DO j = jMin, jMax
225            DO i = iMin+1,iMax             DO i = iMin+1,iMax
226              tauFac = stressReduction              tauFac = stressReduction
227       &             *(iceMask(i-1,j,bi,bj)+iceMask(i,j,bi,bj))*0.5 _d 0       &             *(iceMask(i-1,j,bi,bj)+iceMask(i,j,bi,bj))*0.5 _d 0
228              fu(i,j,bi,bj) = (1. _d 0 - tauFac)*fu(i,j,bi,bj)              fu(i,j,bi,bj) = (1. _d 0 - tauFac)*fu(i,j,bi,bj)
229               ENDDO
230            ENDDO            ENDDO
231           ENDDO            DO j = jMin+1, jMax
232           DO j = jMin+1, jMax             DO i = iMin, iMax
           DO i = iMin, iMax  
233              tauFac = stressReduction              tauFac = stressReduction
234       &             *(iceMask(i,j-1,bi,bj)+iceMask(i,j,bi,bj))*0.5 _d 0       &             *(iceMask(i,j-1,bi,bj)+iceMask(i,j,bi,bj))*0.5 _d 0
235              fv(i,j,bi,bj) = (1. _d 0 - tauFac)*fv(i,j,bi,bj)              fv(i,j,bi,bj) = (1. _d 0 - tauFac)*fv(i,j,bi,bj)
236               ENDDO
237            ENDDO            ENDDO
238           ENDDO           ENDIF
239    #ifdef ALLOW_SEAICE        
240    C     not useSEAICE
241          ENDIF          ENDIF
242    #endif /* ALLOW_SEAICE */
243    
244  C--  end bi,bj loop  C--  end bi,bj loop
245         ENDDO         ENDDO
# Line 227  C--  end bi,bj loop Line 249  C--  end bi,bj loop
249  c     IF (useRealFreshWaterFlux) _EXCH_XY_RS(sIceLoad, myThid)  c     IF (useRealFreshWaterFlux) _EXCH_XY_RS(sIceLoad, myThid)
250  #endif  #endif
251    
252    #ifdef ALLOW_SEAICE        
253          IF ( useSEAICE ) THEN
254    C--   Exchange fields that are advected by seaice dynamics
255          _EXCH_XY_R8( iceMask, myThid )
256          _EXCH_XY_R8( iceHeight, myThid )
257          _EXCH_XY_R8( snowHeight, myThid )
258          _EXCH_XY_R8( Qice1, myThid )
259          _EXCH_XY_R8( Qice2, myThid )
260          ENDIF
261    #endif /* ALLOW_SEAICE */
262  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
263  #endif  /*ALLOW_THSICE*/  #endif  /*ALLOW_THSICE*/
264    

Legend:
Removed from v.1.7  
changed lines
  Added in v.1.10

  ViewVC Help
Powered by ViewVC 1.1.22