/[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.12 by jmc, Wed Apr 4 02:40:42 2007 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     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 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 .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 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 113  C--     Mixed layer thickness: take the Line 114  C--     Mixed layer thickness: take the
114              IF ( ksurfC(i,j,bi,bj).EQ.1 ) THEN              IF ( ksurfC(i,j,bi,bj).EQ.1 ) THEN
115               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)
116              ELSE              ELSE
117               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)
118              ENDIF              ENDIF
119             ENDDO             ENDDO
120            ENDDO            ENDDO
# Line 124  C--     Mixed layer thickness: take the Line 125  C--     Mixed layer thickness: take the
125  #endif /* NONLIN_FRSURF */  #endif /* NONLIN_FRSURF */
126            DO j = jMin, jMax            DO j = jMin, jMax
127             DO i = iMin, iMax             DO i = iMin, iMax
128               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)
129             ENDDO             ENDDO
130            ENDDO            ENDDO
131          ENDIF          ENDIF
# 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 174  CADJ STORE empmr   = comlev1, key = iice Line 176  CADJ STORE empmr   = comlev1, key = iice
176  CADJ STORE qnet    = comlev1, key = iicekey  CADJ STORE qnet    = comlev1, key = iicekey
177  #endif  #endif
178    
179    C-      do sea-ice advection before getting surface fluxes
180    C Note: will inline this S/R once thSIce in Atmos. set-up is settled
181            IF ( thSIceAdvScheme.GT.0 )
182         &   CALL THSICE_DO_ADVECT(
183         I                   bi,bj, myTime, myIter, myThid )
184    
185  #ifdef ALLOW_BULK_FORCE  #ifdef ALLOW_BULK_FORCE
186           IF ( useBulkforce ) THEN          IF ( useBulkforce ) THEN
187             CALL THSICE_GET_PRECIP(           CALL THSICE_GET_PRECIP(
188       I                  iceMask,       I                  iceMask,
189       O                  prcAtm, snowPrc(1-Olx,1-Oly,bi,bj), flxSW,       O                  prcAtm, snowPrc(1-OLx,1-OLy,bi,bj),
190         O                  icFlxSW(1-OLx,1-OLy,bi,bj),
191       I                  iMin,iMax,jMin,jMax, bi,bj, myThid )       I                  iMin,iMax,jMin,jMax, bi,bj, myThid )
192           ENDIF          ENDIF
193    #endif
194    #ifdef ALLOW_EXF
195            IF ( useEXF ) THEN
196             CALL THSICE_MAP_EXF(
197         I                  iceMask,
198         O                  prcAtm, snowPrc(1-OLx,1-OLy,bi,bj),
199         O                  icFlxSW(1-OLx,1-OLy,bi,bj),
200         I                  iMin,iMax,jMin,jMax, bi,bj, myThid )
201            ENDIF
202  #endif  #endif
203    
204    
205           CALL THSICE_STEP_FWD(          CALL THSICE_STEP_TEMP(
206       I                     bi, bj, iMin, iMax, jMin, jMax,       I                     bi, bj, iMin, iMax, jMin, jMax,
      I                     prcAtm,  
      U                     evpAtm, flxSW,  
207       I                     myTime, myIter, myThid )       I                     myTime, myIter, myThid )
208    
209           CALL THSICE_AVE(          CALL THSICE_STEP_FWD(
210       I                   evpAtm, flxSW,       I                     bi, bj, iMin, iMax, jMin, jMax,
211       I                   bi,bj, myTime, myIter, myThid )       I                     prcAtm,
212         I                     myTime, myIter, myThid )
213    
214            CALL THSICE_AVE(
215         I                     bi,bj, myTime, myIter, myThid )
216    
217  c      ENDDO  c      ENDDO
218  c     ENDDO  c     ENDDO
219    
220  c       IF ( .FALSE. ) THEN  C--   note: If useSEAICE=.true., the stress is computed in seaice_model,
221    C--   and stressReduction is always set to zero
222  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
223  CADJ STORE fu(:,:,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte  CADJ STORE fu(:,:,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte
224  CADJ STORE fv(:,:,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte  CADJ STORE fv(:,:,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte
225  #endif  #endif
226          IF ( stressReduction.GT. 0. _d 0 ) THEN          IF ( stressReduction.GT. 0. _d 0 ) THEN
227           DO j = jMin, jMax            DO j = jMin, jMax
228            DO i = iMin+1,iMax             DO i = iMin+1,iMax
229              tauFac = stressReduction              tauFac = stressReduction
230       &             *(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
231              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)
232               ENDDO
233            ENDDO            ENDDO
234           ENDDO            DO j = jMin+1, jMax
235           DO j = jMin+1, jMax             DO i = iMin, iMax
           DO i = iMin, iMax  
236              tauFac = stressReduction              tauFac = stressReduction
237       &             *(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
238              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)
239               ENDDO
240            ENDDO            ENDDO
          ENDDO  
241          ENDIF          ENDIF
242    
243  C--  end bi,bj loop  C--  end bi,bj loop
244         ENDDO         ENDDO
245        ENDDO        ENDDO
246    
247    
248          IF ( useSEAICE .OR. thSIceAdvScheme.GT.0 ) THEN
249    C--   Exchange fields that are advected by seaice dynamics
250            _EXCH_XY_R8( iceMask, myThid )
251            _EXCH_XY_R8( iceHeight, myThid )
252            _EXCH_XY_R8( snowHeight, myThid )
253            _EXCH_XY_R8( Qice1, myThid )
254            _EXCH_XY_R8( Qice2, myThid )
255  #ifdef ATMOSPHERIC_LOADING  #ifdef ATMOSPHERIC_LOADING
256  c     IF (useRealFreshWaterFlux) _EXCH_XY_RS(sIceLoad, myThid)          IF (useRealFreshWaterFlux)
257         &  _EXCH_XY_RS( sIceLoad, myThid )
258  #endif  #endif
259          ENDIF
260    
261  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
262  #endif  /*ALLOW_THSICE*/  #endif  /*ALLOW_THSICE*/

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

  ViewVC Help
Powered by ViewVC 1.1.22