/[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.5 by jmc, Fri Feb 11 19:33:59 2005 UTC revision 1.18 by jmc, Sun Aug 24 21:50:12 2008 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 29  C     === Global variables === Line 29  C     === Global variables ===
29  #include "FFIELDS.h"  #include "FFIELDS.h"
30  #include "THSICE_PARAMS.h"  #include "THSICE_PARAMS.h"
31  #include "THSICE_VARS.h"  #include "THSICE_VARS.h"
32  #ifdef ALLOW_BULK_FORCE  #ifdef ALLOW_AUTODIFF_TAMC
33  #include "BULKF.h"  # include "tamc.h"
34    # 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     myTime    :: Current time in simulation (s)
40  C     myTime :: time counter for this thread  C     myIter    :: Current iteration number
41  C     myThid :: thread number for this instance of the routine.  C     myThid    :: My Thread Id. number
42        _RL  myTime        _RL     myTime
43        INTEGER myIter        INTEGER myIter
44        INTEGER myThid        INTEGER myThid
45  CEOP  CEOP
# Line 51  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 60  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 .AND. .NOT.useSEAICE ) 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
72  C      to be valid at the boundaries ( d/dx 1:sNx+1 ; d/dy 1:sNy+1 )  C      to be valid at the boundaries ( d/dx 1:sNx+1 ; d/dy 1:sNy+1 )
73         iMin = 0         iMin = 0
# Line 83  C      to be valid at the boundaries ( d Line 85  C      to be valid at the boundaries ( d
85        DO bj=myByLo(myThid),myByHi(myThid)        DO bj=myByLo(myThid),myByHi(myThid)
86         DO bi=myBxLo(myThid),myBxHi(myThid)         DO bi=myBxLo(myThid),myBxHi(myThid)
87    
88    #ifdef ALLOW_AUTODIFF_TAMC
89              act1 = bi - myBxLo(myThid)
90              max1 = myBxHi(myThid) - myBxLo(myThid) + 1
91              act2 = bj - myByLo(myThid)
92              max2 = myByHi(myThid) - myByLo(myThid) + 1
93              act3 = myThid - 1
94              max3 = nTx*nTy
95              act4 = ikey_dynamics - 1
96              iicekey = (act1 + 1) + act2*max1
97         &                         + act3*max1*max2
98         &                         + act4*max1*max2*max3
99    #endif /* ALLOW_AUTODIFF_TAMC */
100    
101    #ifdef ALLOW_AUTODIFF_TAMC
102    CADJ STORE ocefwfx(:,:,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte
103    CADJ STORE oceqnet(:,:,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte
104    CADJ STORE ocesflx(:,:,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte
105    # ifdef ALLOW_EXF
106    CADJ STORE qsw(:,:,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte
107    # endif
108    #endif
109    
110  C--     Mixed layer thickness: take the 1rst layer  C--     Mixed layer thickness: take the 1rst layer
111  #ifdef NONLIN_FRSURF  #ifdef NONLIN_FRSURF
112          IF ( staggerTimeStep .AND. nonlinFreeSurf.GT.0 ) THEN          IF ( staggerTimeStep .AND. nonlinFreeSurf.GT.0 ) THEN
# Line 90  C--     Mixed layer thickness: take the Line 114  C--     Mixed layer thickness: take the
114            DO j = jMin, jMax            DO j = jMin, jMax
115             DO i = iMin, iMax             DO i = iMin, iMax
116               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)
117       &                                  *rStarFacC(i,j,bi,bj)       &                                  *rStarFacC(i,j,bi,bj)
118             ENDDO             ENDDO
119            ENDDO            ENDDO
120           ELSE           ELSE
# Line 99  C--     Mixed layer thickness: take the Line 123  C--     Mixed layer thickness: take the
123              IF ( ksurfC(i,j,bi,bj).EQ.1 ) THEN              IF ( ksurfC(i,j,bi,bj).EQ.1 ) THEN
124               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)
125              ELSE              ELSE
126               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)
127              ENDIF              ENDIF
128             ENDDO             ENDDO
129            ENDDO            ENDDO
# Line 110  C--     Mixed layer thickness: take the Line 134  C--     Mixed layer thickness: take the
134  #endif /* NONLIN_FRSURF */  #endif /* NONLIN_FRSURF */
135            DO j = jMin, jMax            DO j = jMin, jMax
136             DO i = iMin, iMax             DO i = iMin, iMax
137               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)
138             ENDDO             ENDDO
139            ENDDO            ENDDO
140          ENDIF          ENDIF
141    
142           DO j = jMin, jMax  #ifdef ALLOW_AUTODIFF_TAMC
143            DO i = iMin, iMax  CADJ STORE uvel (:,:,1,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte
144             tOceMxL(i,j,bi,bj) = theta(i,j,1,bi,bj)  CADJ STORE vvel (:,:,1,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte
145             sOceMxL(i,j,bi,bj) = salt (i,j,1,bi,bj)  #endif
146             v2ocMxL(i,j,bi,bj) =  
147            DO j = jMin, jMax
148             DO i = iMin, iMax
149              tOceMxL(i,j,bi,bj) = theta(i,j,1,bi,bj)
150              sOceMxL(i,j,bi,bj) = salt (i,j,1,bi,bj)
151              v2ocMxL(i,j,bi,bj) =
152       &              ( uvel(i,j,1,bi,bj)*uvel(i,j,1,bi,bj)       &              ( uvel(i,j,1,bi,bj)*uvel(i,j,1,bi,bj)
153       &              + 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)
154       &              + 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)
155       &              + vvel(i,j,1,bi,bj)*vvel(i,j,1,bi,bj)       &              + vvel(i,j,1,bi,bj)*vvel(i,j,1,bi,bj)
156       &              )*0.5 _d 0       &              )*0.5 _d 0
157             prcAtm(i,j) = 0.            prcAtm(i,j) = 0.
158             evpAtm(i,j) = 0.            icFrwAtm(i,j,bi,bj) = 0. _d 0
159             flxSW (i,j) = 0.            icFlxAtm(i,j,bi,bj) = 0. _d 0
160             snowPrc(i,j,bi,bj) = 0. _d 0            icFlxSW (i,j,bi,bj) = 0. _d 0
161             siceAlb(i,j,bi,bj) = 0. _d 0            snowPrc(i,j,bi,bj) = 0. _d 0
162              siceAlb(i,j,bi,bj) = 0. _d 0
163             ENDDO
164            ENDDO
165    
166    #ifdef ALLOW_AUTODIFF_TAMC
167    CADJ STORE iceMask = comlev1, key = iicekey
168    CADJ STORE iceHeight  = comlev1, key = iicekey
169    CADJ STORE snowHeight = comlev1, key = iicekey
170    CADJ STORE Tsrf    = comlev1, key = iicekey
171    CADJ STORE Qice1   = comlev1, key = iicekey
172    CADJ STORE Qice2   = comlev1, key = iicekey
173    CADJ STORE snowAge = comlev1, key = iicekey
174    CADJ STORE snowPrc  = comlev1, key = iicekey
175    
176    CADJ STORE hOceMxL = comlev1, key = iicekey
177    CADJ STORE tOceMxL = comlev1, key = iicekey
178    CADJ STORE sOceMxL = comlev1, key = iicekey
179    CADJ STORE v2ocMxL = comlev1, key = iicekey
180    
181    CADJ STORE empmr   = comlev1, key = iicekey
182    CADJ STORE qnet    = comlev1, key = iicekey
183    #endif
184    
185    C-      do sea-ice advection before getting surface fluxes
186    C Note: will inline this S/R once thSIce in Atmos. set-up is settled
187            IF ( thSIceAdvScheme.GT.0 )
188         &   CALL THSICE_DO_ADVECT(
189         I                   bi,bj, myTime, myIter, myThid )
190    
191  #ifdef ALLOW_BULK_FORCE  #ifdef ALLOW_BULK_FORCE
192             prcAtm(i,j) = ( rain(i,j,bi,bj)+runoff(i,j,bi,bj) )*rhofw          IF ( useBulkforce ) THEN
193             flxSW (i,j) = solar(i,j,bi,bj)           CALL THSICE_GET_PRECIP(
194             IF ( iceMask(i,j,bi,bj).GT.0. _d 0       I                  iceMask,
195       &       .AND. Tair(i,j,bi,bj).LE.Tf0kel )  THEN       O                  prcAtm, snowPrc(1-OLx,1-OLy,bi,bj),
196               snowPrc(i,j,bi,bj) = rain(i,j,bi,bj)*rhofw       O                  icFlxSW(1-OLx,1-OLy,bi,bj),
197             ENDIF       I                  iMin,iMax,jMin,jMax, bi,bj, myThid )
198            ENDIF
199    #endif
200    #ifdef ALLOW_EXF
201            IF ( useEXF ) THEN
202             CALL THSICE_MAP_EXF(
203         I                  iceMask,
204         O                  prcAtm, snowPrc(1-OLx,1-OLy,bi,bj),
205         O                  icFlxSW(1-OLx,1-OLy,bi,bj),
206         I                  iMin,iMax,jMin,jMax, bi,bj, myThid )
207            ENDIF
208  #endif  #endif
           ENDDO  
          ENDDO  
209    
210           CALL THSICE_STEP_FWD(          CALL THSICE_STEP_TEMP(
211       I                     bi, bj, iMin, iMax, jMin, jMax,       I                     bi, bj, iMin, iMax, jMin, jMax,
      I                     prcAtm,  
      U                     evpAtm, flxSW,  
212       I                     myTime, myIter, myThid )       I                     myTime, myIter, myThid )
213    
214           CALL THSICE_AVE(  #ifdef ALLOW_AUTODIFF_TAMC
215       I                   evpAtm, flxSW,  CADJ STORE empmr, qnet = comlev1, key = iicekey
216       I                   bi,bj, myTime, myIter, myThid )  CADJ STORE iceMask = comlev1, key = iicekey
217    CADJ STORE iceHeight  = comlev1, key = iicekey
218    CADJ STORE snowHeight = comlev1, key = iicekey
219    CADJ STORE Tsrf    = comlev1, key = iicekey
220    CADJ STORE Qice1   = comlev1, key = iicekey
221    CADJ STORE Qice2   = comlev1, key = iicekey
222    CADJ STORE snowAge = comlev1, key = iicekey
223    #endif
224    
225            CALL THSICE_STEP_FWD(
226         I                     bi, bj, iMin, iMax, jMin, jMax,
227         I                     prcAtm,
228         I                     myTime, myIter, myThid )
229    
230            CALL THSICE_AVE(
231         I                     bi,bj, myTime, myIter, myThid )
232    
233  c      ENDDO  c      ENDDO
234  c     ENDDO  c     ENDDO
235    
236  c       IF ( .FALSE. ) THEN  C--   note: If useSEAICE=.true., the stress is computed in seaice_model,
237    C--   and stressReduction is always set to zero
238    #ifdef ALLOW_AUTODIFF_TAMC
239    CADJ STORE fu(:,:,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte
240    CADJ STORE fv(:,:,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte
241    #endif
242          IF ( stressReduction.GT. 0. _d 0 ) THEN          IF ( stressReduction.GT. 0. _d 0 ) THEN
243           DO j = jMin, jMax            DO j = jMin, jMax
244            DO i = iMin+1,iMax             DO i = iMin+1,iMax
245              tauFac = stressReduction              tauFac = stressReduction
246       &             *(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
247              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)
248               ENDDO
249            ENDDO            ENDDO
250           ENDDO            DO j = jMin+1, jMax
251           DO j = jMin+1, jMax             DO i = iMin, iMax
           DO i = iMin, iMax  
252              tauFac = stressReduction              tauFac = stressReduction
253       &             *(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
254              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)
255               ENDDO
256            ENDDO            ENDDO
          ENDDO  
257          ENDIF          ENDIF
258    
259  C--  end bi,bj loop  C--  end bi,bj loop
260         ENDDO         ENDDO
261        ENDDO        ENDDO
262    
263    C     add a small piece of code to check AddFluid implementation:
264    c#include "thsice_test_addfluid.h"
265    
266          IF ( useSEAICE .OR. thSIceAdvScheme.GT.0 ) THEN
267    C--   Exchange fields that are advected by seaice dynamics
268            _EXCH_XY_R8( iceMask, myThid )
269            _EXCH_XY_R8( iceHeight, myThid )
270            _EXCH_XY_R8( snowHeight, myThid )
271            _EXCH_XY_R8( Qice1, myThid )
272            _EXCH_XY_R8( Qice2, myThid )
273  #ifdef ATMOSPHERIC_LOADING  #ifdef ATMOSPHERIC_LOADING
274  c     IF (useRealFreshWaterFlux) _EXCH_XY_RS(sIceLoad, myThid)          IF (useRealFreshWaterFlux)
275         &  _EXCH_XY_RS( sIceLoad, myThid )
276  #endif  #endif
277          ENDIF
278    
279  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
280  #endif  /*ALLOW_THSICE*/  #endif  /*ALLOW_THSICE*/

Legend:
Removed from v.1.5  
changed lines
  Added in v.1.18

  ViewVC Help
Powered by ViewVC 1.1.22