/[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.10 by mlosch, Mon Jun 5 22:33:50 2006 UTC revision 1.24 by jmc, Fri Dec 24 00:55:40 2010 UTC
# Line 28  C     === Global variables === Line 28  C     === Global variables ===
28  #include "DYNVARS.h"  #include "DYNVARS.h"
29  #include "FFIELDS.h"  #include "FFIELDS.h"
30  #include "THSICE_PARAMS.h"  #include "THSICE_PARAMS.h"
31    #include "THSICE_SIZE.h"
32  #include "THSICE_VARS.h"  #include "THSICE_VARS.h"
33  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
34  # include "tamc.h"  # include "tamc.h"
# Line 36  C     === Global variables === Line 37  C     === Global variables ===
37    
38  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
39  C     === Routine arguments ===  C     === Routine arguments ===
40  C     myIter :: iteration counter for this thread  C     myTime    :: Current time in simulation (s)
41  C     myTime :: time counter for this thread  C     myIter    :: Current iteration number
42  C     myThid :: thread number for this instance of the routine.  C     myThid    :: My Thread Id. number
43        _RL  myTime        _RL     myTime
44        INTEGER myIter        INTEGER myIter
45        INTEGER myThid        INTEGER myThid
46  CEOP  CEOP
# Line 60  c     _RL flxSW (1-OLx:sNx+OLx,1-OLy:sNy Line 61  c     _RL flxSW (1-OLx:sNx+OLx,1-OLy:sNy
61    
62  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
63    
64        IF ( stressReduction.GT. 0. _d 0 ) THEN        IF ( useEXF .OR. useSEAICE ) THEN
65    C-    EXF does not provide valid fields in overlap
66           iMin = 1
67           iMax = sNx
68           jMin = 1
69           jMax = sNy
70          ELSEIF ( stressReduction.GT. 0. _d 0 ) THEN
71  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
72         iMin = 1-OLx         iMin = 1-OLx
73         iMax = sNx+OLx-1         iMax = sNx+OLx-1
# Line 93  C      to be valid at the boundaries ( d Line 100  C      to be valid at the boundaries ( d
100            act3 = myThid - 1            act3 = myThid - 1
101            max3 = nTx*nTy            max3 = nTx*nTy
102            act4 = ikey_dynamics - 1            act4 = ikey_dynamics - 1
103            iicekey = (act1 + 1) + act2*max1            ticekey = (act1 + 1) + act2*max1
104       &                         + act3*max1*max2       &                         + act3*max1*max2
105       &                         + act4*max1*max2*max3       &                         + act4*max1*max2*max3
106  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
107    
108    #ifdef ALLOW_AUTODIFF_TAMC
109    CADJ STORE ocefwfx(:,:,bi,bj) = comlev1_bibj, key=ticekey, byte=isbyte
110    CADJ STORE oceqnet(:,:,bi,bj) = comlev1_bibj, key=ticekey, byte=isbyte
111    CADJ STORE ocesflx(:,:,bi,bj) = comlev1_bibj, key=ticekey, byte=isbyte
112    # ifdef ALLOW_EXF
113    CADJ STORE qsw(:,:,bi,bj) = comlev1_bibj, key=ticekey, byte=isbyte
114    # endif
115    #endif
116    
117  C--     Mixed layer thickness: take the 1rst layer  C--     Mixed layer thickness: take the 1rst layer
118  #ifdef NONLIN_FRSURF  #ifdef NONLIN_FRSURF
119          IF ( staggerTimeStep .AND. nonlinFreeSurf.GT.0 ) THEN          IF ( staggerTimeStep .AND. nonlinFreeSurf.GT.0 ) THEN
120           IF ( select_rStar.GT.0 ) THEN           IF ( select_rStar.GT.0 ) THEN
121            DO j = jMin, jMax            DO j=1-OLy,sNy+OLy
122             DO i = iMin, iMax             DO i=1-OLx,sNx+OLx
123               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)
124       &                                  *rStarFacC(i,j,bi,bj)       &                                  *rStarFacC(i,j,bi,bj)
125             ENDDO             ENDDO
126            ENDDO            ENDDO
127           ELSE           ELSE
128            DO j = jMin, jMax            DO j=1-OLy,sNy+OLy
129             DO i = iMin, iMax             DO i=1-OLx,sNx+OLx
130              IF ( ksurfC(i,j,bi,bj).EQ.1 ) THEN              IF ( ksurfC(i,j,bi,bj).EQ.1 ) THEN
131               hOceMxL(i,j,bi,bj) = drF(1)*hFac_surfC(i,j,bi,bj)               hOceMxL(i,j,bi,bj) = drF(1)*hFac_surfC(i,j,bi,bj)
132              ELSE              ELSE
133               hOceMxL(i,j,bi,bj) = drF(1)*hfacC(i,j,1,bi,bj)               hOceMxL(i,j,bi,bj) = drF(1)*hFacC(i,j,1,bi,bj)
134              ENDIF              ENDIF
135             ENDDO             ENDDO
136            ENDDO            ENDDO
# Line 123  C--     Mixed layer thickness: take the Line 139  C--     Mixed layer thickness: take the
139  #else /* ndef NONLIN_FRSURF */  #else /* ndef NONLIN_FRSURF */
140          IF (.TRUE.) THEN          IF (.TRUE.) THEN
141  #endif /* NONLIN_FRSURF */  #endif /* NONLIN_FRSURF */
142            DO j = jMin, jMax            DO j=1-OLy,sNy+OLy
143             DO i = iMin, iMax             DO i=1-OLx,sNx+OLx
144               hOceMxL(i,j,bi,bj) = drF(1)*hfacC(i,j,1,bi,bj)               hOceMxL(i,j,bi,bj) = drF(1)*hFacC(i,j,1,bi,bj)
145             ENDDO             ENDDO
146            ENDDO            ENDDO
147          ENDIF          ENDIF
148    
149  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
150  CADJ STORE uvel (:,:,1,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte  CADJ STORE uvel (:,:,1,bi,bj) = comlev1_bibj, key=ticekey, byte=isbyte
151  CADJ STORE vvel (:,:,1,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte  CADJ STORE vvel (:,:,1,bi,bj) = comlev1_bibj, key=ticekey, byte=isbyte
152  #endif  #endif
153    
154          DO j = jMin, jMax          DO j = jMin, jMax
# Line 155  CADJ STORE vvel (:,:,1,bi,bj) = comlev1_ Line 171  CADJ STORE vvel (:,:,1,bi,bj) = comlev1_
171          ENDDO          ENDDO
172    
173  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
174  CADJ STORE iceMask = comlev1, key = iicekey  CADJ STORE iceMask(:,:,bi,bj) = comlev1_bibj, key = ticekey
175  CADJ STORE iceHeight  = comlev1, key = iicekey  CADJ STORE iceHeight(:,:,bi,bj)  = comlev1_bibj, key = ticekey
176  CADJ STORE snowHeight = comlev1, key = iicekey  CADJ STORE snowHeight(:,:,bi,bj) = comlev1_bibj, key = ticekey
177  CADJ STORE Tsrf    = comlev1, key = iicekey  CADJ STORE Tsrf(:,:,bi,bj)    = comlev1_bibj, key = ticekey
178  CADJ STORE Qice1   = comlev1, key = iicekey  CADJ STORE Qice1(:,:,bi,bj)   = comlev1_bibj, key = ticekey
179  CADJ STORE Qice2   = comlev1, key = iicekey  CADJ STORE Qice2(:,:,bi,bj)   = comlev1_bibj, key = ticekey
180  CADJ STORE snowAge = comlev1, key = iicekey  CADJ STORE snowAge(:,:,bi,bj) = comlev1_bibj, key = ticekey
181    CADJ STORE snowPrc(:,:,bi,bj)  = comlev1_bibj, key = ticekey
182  CADJ STORE sHeating = comlev1, key = iicekey  
183  CADJ STORE flxCndBt = comlev1, key = iicekey  CADJ STORE hOceMxL(:,:,bi,bj) = comlev1_bibj, key = ticekey
184  CADJ STORE snowPrc  = comlev1, key = iicekey  CADJ STORE tOceMxL(:,:,bi,bj) = comlev1_bibj, key = ticekey
185    CADJ STORE sOceMxL(:,:,bi,bj) = comlev1_bibj, key = ticekey
186  CADJ STORE hOceMxL = comlev1, key = iicekey  CADJ STORE v2ocMxL(:,:,bi,bj) = comlev1_bibj, key = ticekey
 CADJ STORE tOceMxL = comlev1, key = iicekey  
 CADJ STORE sOceMxL = comlev1, key = iicekey  
 CADJ STORE v2ocMxL = comlev1, key = iicekey  
   
 CADJ STORE empmr   = comlev1, key = iicekey  
 CADJ STORE qnet    = comlev1, key = iicekey  
187  #endif  #endif
188    
189    C-      do sea-ice advection before getting surface fluxes
190    C Note: will inline this S/R once thSIce in Atmos. set-up is settled
191            IF ( thSIceAdvScheme.GT.0 )
192         &   CALL THSICE_DO_ADVECT(
193         I                   bi,bj, myTime, myIter, myThid )
194    
195  #ifdef ALLOW_BULK_FORCE  #ifdef ALLOW_BULK_FORCE
196          IF ( useBulkforce ) THEN          IF ( useBulkforce ) THEN
197           CALL THSICE_GET_PRECIP(           CALL THSICE_GET_PRECIP(
# Line 195  CADJ STORE qnet    = comlev1, key = iice Line 211  CADJ STORE qnet    = comlev1, key = iice
211          ENDIF          ENDIF
212  #endif  #endif
213    
214    #ifdef ALLOW_AUTODIFF_TAMC
215    CADJ STORE sheating(:,:,bi,bj) = comlev1_bibj, key = ticekey
216    CADJ STORE tice1(:,:,bi,bj) = comlev1_bibj, key = ticekey
217    CADJ STORE tice2(:,:,bi,bj) = comlev1_bibj, key = ticekey
218    #endif
219          CALL THSICE_STEP_TEMP(          CALL THSICE_STEP_TEMP(
220       I                     bi, bj, iMin, iMax, jMin, jMax,       I                     bi, bj, iMin, iMax, jMin, jMax,
221       I                     myTime, myIter, myThid )       I                     myTime, myIter, myThid )
222    
223    #ifdef ALLOW_AUTODIFF_TAMC
224    CADJ STORE empmr(:,:,bi,bj) = comlev1_bibj, key = ticekey
225    CADJ STORE qnet(:,:,bi,bj) = comlev1_bibj, key = ticekey
226    CADJ STORE iceMask(:,:,bi,bj) = comlev1_bibj, key = ticekey
227    CADJ STORE iceHeight(:,:,bi,bj)  = comlev1_bibj, key = ticekey
228    CADJ STORE snowHeight(:,:,bi,bj) = comlev1_bibj, key = ticekey
229    cphCADJ STORE Tsrf(:,:,bi,bj)    = comlev1_bibj, key = ticekey
230    CADJ STORE Qice1(:,:,bi,bj)   = comlev1_bibj, key = ticekey
231    CADJ STORE Qice2(:,:,bi,bj)   = comlev1_bibj, key = ticekey
232    CADJ STORE snowAge(:,:,bi,bj) = comlev1_bibj, key = ticekey
233    CADJ STORE sheating(:,:,bi,bj) = comlev1_bibj, key = ticekey
234    #endif
235    
236          CALL THSICE_STEP_FWD(          CALL THSICE_STEP_FWD(
237       I                     bi, bj, iMin, iMax, jMin, jMax,       I                     bi, bj, iMin, iMax, jMin, jMax,
238       I                     prcAtm,       I                     prcAtm,
# Line 208  CADJ STORE qnet    = comlev1, key = iice Line 241  CADJ STORE qnet    = comlev1, key = iice
241          CALL THSICE_AVE(          CALL THSICE_AVE(
242       I                     bi,bj, myTime, myIter, myThid )       I                     bi,bj, myTime, myIter, myThid )
243    
244  c      ENDDO  C--  end bi,bj loop
245  c     ENDDO         ENDDO
246          ENDDO
247    
248    C     add a small piece of code to check AddFluid implementation:
249    c#include "thsice_test_addfluid.h"
250    
251  #ifdef ALLOW_SEAICE                IF ( useSEAICE .OR. thSIceAdvScheme.GT.0 ) THEN
252  C--   If useSEAICE=.true., the stress is computed in seaice_model,  C--   Exchange fields that are advected by seaice dynamics
253  C--   so that it does not need any further reduction          _EXCH_XY_RL( iceMask, myThid )
254          IF ( .NOT. useSEAICE ) THEN          _EXCH_XY_RL( iceHeight, myThid )
255  #endif /* ALLOW_SEAICE */          _EXCH_XY_RL( snowHeight, myThid )
256            _EXCH_XY_RL( Qice1, myThid )
257            _EXCH_XY_RL( Qice2, myThid )
258          ELSEIF ( useEXF .AND. stressReduction.GT. 0. _d 0 ) THEN
259            _EXCH_XY_RL( iceMask, myThid )
260          ENDIF
261    #ifdef ATMOSPHERIC_LOADING
262          IF ( useRealFreshWaterFlux .AND. (useEXF.OR.useSEAICE ) )
263         &  _EXCH_XY_RS( sIceLoad, myThid )
264    #endif
265    
266          DO bj=myByLo(myThid),myByHi(myThid)
267           DO bi=myBxLo(myThid),myBxHi(myThid)
268    C--   note: If useSEAICE=.true., the stress is computed in seaice_model,
269    C--   and stressReduction is always set to zero
270  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
271  CADJ STORE fu(:,:,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte  CADJ STORE fu(:,:,bi,bj) = comlev1_bibj, key=ticekey, byte=isbyte
272  CADJ STORE fv(:,:,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte  CADJ STORE fv(:,:,bi,bj) = comlev1_bibj, key=ticekey, byte=isbyte
273  #endif  #endif
274           IF ( stressReduction.GT. 0. _d 0 ) THEN          IF ( stressReduction.GT. 0. _d 0 ) THEN
275            DO j = jMin, jMax            DO j = jMin, jMax
276             DO i = iMin+1,iMax             DO i = iMin+1,iMax
277              tauFac = stressReduction              tauFac = stressReduction
# Line 235  CADJ STORE fv(:,:,bi,bj) = comlev1_bibj, Line 286  CADJ STORE fv(:,:,bi,bj) = comlev1_bibj,
286              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)
287             ENDDO             ENDDO
288            ENDDO            ENDDO
          ENDIF  
 #ifdef ALLOW_SEAICE          
 C     not useSEAICE  
289          ENDIF          ENDIF
 #endif /* ALLOW_SEAICE */  
290    
291  C--  end bi,bj loop  C--  end bi,bj loop
292         ENDDO         ENDDO
293        ENDDO        ENDDO
294    
 #ifdef ATMOSPHERIC_LOADING  
 c     IF (useRealFreshWaterFlux) _EXCH_XY_RS(sIceLoad, myThid)  
 #endif  
   
 #ifdef ALLOW_SEAICE          
       IF ( useSEAICE ) THEN  
 C--   Exchange fields that are advected by seaice dynamics  
       _EXCH_XY_R8( iceMask, myThid )  
       _EXCH_XY_R8( iceHeight, myThid )  
       _EXCH_XY_R8( snowHeight, myThid )  
       _EXCH_XY_R8( Qice1, myThid )  
       _EXCH_XY_R8( Qice2, myThid )  
       ENDIF  
 #endif /* ALLOW_SEAICE */  
295  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
296  #endif  /*ALLOW_THSICE*/  #endif  /*ALLOW_THSICE*/
297    

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

  ViewVC Help
Powered by ViewVC 1.1.22