/[MITgcm]/MITgcm/model/src/do_oceanic_phys.F
ViewVC logotype

Diff of /MITgcm/model/src/do_oceanic_phys.F

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

revision 1.15 by heimbach, Fri Dec 10 20:15:10 2004 UTC revision 1.29 by jmc, Thu Jun 15 16:27:54 2006 UTC
# Line 11  C $Name$ Line 11  C $Name$
11  # ifdef ALLOW_KPP  # ifdef ALLOW_KPP
12  #  include "KPP_OPTIONS.h"  #  include "KPP_OPTIONS.h"
13  # endif  # endif
14    # ifdef ALLOW_SEAICE
15    #  include "SEAICE_OPTIONS.h"
16    # endif
17  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
18    
19  CBOP  CBOP
# Line 19  C     !INTERFACE: Line 22  C     !INTERFACE:
22        SUBROUTINE DO_OCEANIC_PHYS(myTime, myIter, myThid)        SUBROUTINE DO_OCEANIC_PHYS(myTime, myIter, myThid)
23  C     !DESCRIPTION: \bv  C     !DESCRIPTION: \bv
24  C     *==========================================================*  C     *==========================================================*
25  C     | SUBROUTINE DO_OCEANIC_PHYS                                  C     | SUBROUTINE DO_OCEANIC_PHYS
26  C     | o Controlling routine for oceanic physics and  C     | o Controlling routine for oceanic physics and
27  C     |   parameterization  C     |   parameterization
28  C     *==========================================================*  C     *==========================================================*
29  C     | o originally, part of S/R thermodynamics  C     | o originally, part of S/R thermodynamics
# Line 35  C     == Global variables === Line 38  C     == Global variables ===
38  #include "PARAMS.h"  #include "PARAMS.h"
39  #include "DYNVARS.h"  #include "DYNVARS.h"
40  #include "GRID.h"  #include "GRID.h"
41  c #include "GAD.h"  #ifdef ALLOW_TIMEAVE
42  c #ifdef ALLOW_PTRACERS  #include "TIMEAVE_STATV.h"
43  c #include "PTRACERS_SIZE.h"  #endif
44  c #include "PTRACERS.h"  #if defined (ALLOW_BALANCE_FLUXES) && !(defined ALLOW_AUTODIFF_TAMC)
45  c #endif  #include "FFIELDS.h"
46  c #ifdef ALLOW_TIMEAVE  #endif
 c #include "TIMEAVE_STATV.h"  
 c #endif  
47    
48  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
49  # include "tamc.h"  # include "tamc.h"
# Line 61  c #endif Line 62  c #endif
62  # ifdef EXACT_CONSERV  # ifdef EXACT_CONSERV
63  #  include "SURFACE.h"  #  include "SURFACE.h"
64  # endif  # endif
65    # ifdef ALLOW_EXF
66    #  include "ctrl.h"
67    #  include "exf_fields.h"
68    #  include "exf_clim_fields.h"
69    #  ifdef ALLOW_BULKFORMULAE
70    #   include "exf_constants.h"
71    #  endif
72    # endif
73    # ifdef ALLOW_SEAICE
74    #  include "SEAICE.h"
75    # endif
76  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
77    
78  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
79  C     == Routine arguments ==  C     == Routine arguments ==
80  C     myTime - Current time in simulation  C     myTime :: Current time in simulation
81  C     myIter - Current iteration number in simulation  C     myIter :: Current iteration number in simulation
82  C     myThid - Thread number for this instance of the routine.  C     myThid :: Thread number for this instance of the routine.
83        _RL myTime        _RL myTime
84        INTEGER myIter        INTEGER myIter
85        INTEGER myThid        INTEGER myThid
86    
87  C     !LOCAL VARIABLES:  C     !LOCAL VARIABLES:
88  C     == Local variables  C     == Local variables
89  C     rhoK, rhoKM1   - Density at current level, and level above  C     rhoK, rhoKM1  :: Density at current level, and level above
90  C     useVariableK   = T when vertical diffusion is not constant  C     iMin, iMax    :: Ranges and sub-block indices on which calculations
 C     iMin, iMax     - Ranges and sub-block indices on which calculations  
91  C     jMin, jMax       are applied.  C     jMin, jMax       are applied.
92  C     bi, bj  C     bi, bj        :: tile indices
93  C     k, kup,        - Index for layer above and below. kup and kDown  C     i,j,k         :: loop indices
 C     kDown, km1       are switched with layer to be the appropriate  
 C                      index into fVerTerm.  
94        _RL rhokm1  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rhokm1  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
95        _RL rhok    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rhok    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
96        _RL sigmaX  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL sigmaX  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
97        _RL sigmaY  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL sigmaY  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
98        _RL sigmaR  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL sigmaR  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
       _RL kp1Msk  
       LOGICAL useVariableK  
99        INTEGER iMin, iMax        INTEGER iMin, iMax
100        INTEGER jMin, jMax        INTEGER jMin, jMax
101        INTEGER bi, bj        INTEGER bi, bj
102        INTEGER i, j        INTEGER i, j, k
103        INTEGER k, km1, kup, kDown        INTEGER doDiagsRho
104        INTEGER iTracer, ip  #ifdef ALLOW_DIAGNOSTICS
105          LOGICAL  DIAGNOSTICS_IS_ON
106          EXTERNAL DIAGNOSTICS_IS_ON
107    #endif /* ALLOW_DIAGNOSTICS */
108    
109  CEOP  CEOP
110    
# Line 104  C--   dummy statement to end declaration Line 114  C--   dummy statement to end declaration
114  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
115    
116  #ifdef ALLOW_DEBUG  #ifdef ALLOW_DEBUG
117        IF ( debugLevel .GE. debLevB )        IF ( debugLevel .GE. debLevB )
118       &    CALL DEBUG_ENTER('DO_OCEANIC_PHYS',myThid)       &     CALL DEBUG_ENTER('DO_OCEANIC_PHYS',myThid)
119  #endif  #endif
120    
121          doDiagsRho = 0
122    #ifdef ALLOW_DIAGNOSTICS
123          IF ( useDiagnostics .AND. fluidIsWater ) THEN
124            IF ( DIAGNOSTICS_IS_ON('DRHODR  ',myThid) ) doDiagsRho = 1
125            IF ( DIAGNOSTICS_IS_ON('RHOANOSQ',myThid) .OR.
126         &       DIAGNOSTICS_IS_ON('URHOMASS',myThid) .OR.
127         &       DIAGNOSTICS_IS_ON('VRHOMASS',myThid) .OR.
128         &       DIAGNOSTICS_IS_ON('WRHOMASS',myThid) .OR.
129         &       DIAGNOSTICS_IS_ON('WRHOMASS',myThid) ) doDiagsRho = 2
130          ENDIF
131    #endif /* ALLOW_DIAGNOSTICS */
132    
133    #ifdef ALLOW_SEAICE
134    C--   Call sea ice model to compute forcing/external data fields.  In
135    C     addition to computing prognostic sea-ice variables and diagnosing the
136    C     forcing/external data fields that drive the ocean model, SEAICE_MODEL
137    C     also sets theta to the freezing point under sea-ice.  The implied
138    C     surface heat flux is then stored in variable surfaceTendencyTice,
139    C     which is needed by KPP package (kpp_calc.F and kpp_transport_t.F)
140    C     to diagnose surface buoyancy fluxes and for the non-local transport
141    C     term.  Because this call precedes model thermodynamics, temperature
142    C     under sea-ice may not be "exactly" at the freezing point by the time
143    C     theta is dumped or time-averaged.
144          IF ( useSEAICE ) THEN
145    #ifdef ALLOW_AUTODIFF_TAMC
146    CADJ STORE aqh,precip,swdown   = comlev1, key = ikey_dynamics
147    CADJ STORE theta               = comlev1, key = ikey_dynamics
148    # ifdef SEAICE_ALLOW_DYNAMICS
149    CADJ STORE uvel,vvel           = comlev1, key = ikey_dynamics
150    # endif
151    #endif
152    #ifdef ALLOW_DEBUG
153            IF ( debugLevel .GE. debLevB )
154         &    CALL DEBUG_CALL('SEAICE_MODEL',myThid)
155    #endif
156            CALL TIMER_START('SEAICE_MODEL    [DO_OCEANIC_PHYS]', myThid)
157            CALL SEAICE_MODEL( myTime, myIter, myThid )
158            CALL TIMER_STOP ('SEAICE_MODEL    [DO_OCEANIC_PHYS]', myThid)
159    #ifdef ALLOW_COST_ICE
160            CALL COST_ICE_TEST ( myTime, myIter, myThid )
161    #endif
162          ENDIF
163    #endif /* ALLOW_SEAICE */
164    
165  #ifdef ALLOW_THSICE  #ifdef ALLOW_THSICE
166        IF ( useThSIce .AND. fluidIsWater ) THEN        IF ( useThSIce .AND. fluidIsWater ) THEN
167  #ifdef ALLOW_DEBUG  #ifdef ALLOW_DEBUG
# Line 122  C       and modify forcing terms includi Line 176  C       and modify forcing terms includi
176        ENDIF        ENDIF
177  #endif /* ALLOW_THSICE */  #endif /* ALLOW_THSICE */
178    
179    #ifdef ALLOW_SHELFICE
180          IF ( useShelfIce .AND. fluidIsWater ) THEN
181    #ifdef ALLOW_DEBUG
182            IF ( debugLevel .GE. debLevB )
183         &    CALL DEBUG_CALL('SHELFICE_THERMODYNAMICS',myThid)
184    #endif
185    C     compute temperature and (virtual) salt flux at the
186    C     shelf-ice ocean interface
187           CALL TIMER_START('SHELFICE_THERMODYNAMICS [DO_OCEANIC_PHYS]',
188         &       myThid)
189           CALL SHELFICE_THERMODYNAMICS( myTime, myIter, myThid )
190           CALL TIMER_STOP( 'SHELFICE_THERMODYNAMICS [DO_OCEANIC_PHYS]',
191         &      myThid)
192          ENDIF
193    #endif /* ALLOW_SHELFICE */
194    
195  C--   Freeze water at the surface  C--   Freeze water at the surface
196  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
197  CADJ STORE theta = comlev1, key = ikey_dynamics  CADJ STORE theta = comlev1, key = ikey_dynamics
# Line 132  CADJ STORE theta = comlev1, key = ikey_d Line 202  CADJ STORE theta = comlev1, key = ikey_d
202          CALL FREEZE_SURFACE(  myTime, myIter, myThid )          CALL FREEZE_SURFACE(  myTime, myIter, myThid )
203        ENDIF        ENDIF
204    
205  #ifdef COMPONENT_MODULE  #ifdef ALLOW_OCN_COMPON_INTERF
 # ifndef ALLOW_AIM  
206  C--    Apply imported data (from coupled interface) to forcing fields  C--    Apply imported data (from coupled interface) to forcing fields
207  C jmc: do not know precisely where to put this call (bf or af thSIce ?)  C jmc: do not know precisely where to put this call (bf or af thSIce ?)
208         IF ( useCoupler ) THEN         IF ( useCoupler ) THEN
209           CALL OCN_APPLY_IMPORT( .TRUE., myTime, myIter, myThid )           CALL OCN_APPLY_IMPORT( .TRUE., myTime, myIter, myThid )
210         ENDIF         ENDIF
211  # endif  #endif /* ALLOW_OCN_COMPON_INTERF */
212  #endif /* COMPONENT_MODULE */  
213    #ifdef ALLOW_BALANCE_FLUXES
214    C     balance fluxes
215           IF ( balanceEmPmR )
216         &        CALL REMOVE_MEAN_RS( 1, EmPmR, maskH, maskH, rA, drF,
217         &        'EmPmR', myTime, myThid )
218           IF ( balanceQnet )
219         &        CALL REMOVE_MEAN_RS( 1, Qnet,  maskH, maskH, rA, drF,
220         &        'Qnet ', myTime, myThid )
221    #endif /* ALLOW_BALANCE_FLUXES */
222    
223  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
224  C--   HPF directive to help TAMC  C--   HPF directive to help TAMC
# Line 229  CADJ &     = comlev1_bibj, key=itdkey, b Line 307  CADJ &     = comlev1_bibj, key=itdkey, b
307  CADJ STORE uvel (:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte  CADJ STORE uvel (:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
308  CADJ STORE vvel (:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte  CADJ STORE vvel (:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
309  # endif  # endif
 # ifdef EXACT_CONSERV  
 CADJ STORE pmepr(:,:,bi,bj)   = comlev1_bibj, key=itdkey, byte=isbyte  
 # endif  
310  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
311    
312  #ifdef ALLOW_DEBUG  #ifdef ALLOW_DEBUG
# Line 253  cph Needed for rhok, rhokm1, in the case Line 328  cph Needed for rhok, rhokm1, in the case
328  C--       Calculate gradients of potential density for isoneutral  C--       Calculate gradients of potential density for isoneutral
329  C         slope terms (e.g. GM/Redi tensor or IVDC diffusivity)  C         slope terms (e.g. GM/Redi tensor or IVDC diffusivity)
330  c         IF ( k.GT.1 .AND. (useGMRedi.OR.ivdc_kappa.NE.0.) ) THEN  c         IF ( k.GT.1 .AND. (useGMRedi.OR.ivdc_kappa.NE.0.) ) THEN
331            IF ( useGMRedi .OR. (k.GT.1 .AND. ivdc_kappa.NE.0.) ) THEN            IF ( useGMRedi .OR. (k.GT.1 .AND. ivdc_kappa.NE.0.)
332         &                   .OR. doDiagsRho.GE.1 ) THEN
333  #ifdef ALLOW_DEBUG  #ifdef ALLOW_DEBUG
334              IF ( debugLevel .GE. debLevB )              IF ( debugLevel .GE. debLevB )
335       &       CALL DEBUG_CALL('FIND_RHO',myThid)       &       CALL DEBUG_CALL('FIND_RHO',myThid)
# Line 309  c ==> should use sigmaR !!! Line 385  c ==> should use sigmaR !!!
385       I        myTime, myIter, myThid)       I        myTime, myIter, myThid)
386            ENDIF            ENDIF
387    
388    #ifdef ALLOW_DIAGNOSTICS
389              IF ( doDiagsRho.GE.2 ) THEN
390                CALL DIAGS_RHO( k, bi, bj,
391         I                      rhoK, rhoKm1,
392         I                      myTime, myIter, myThid)
393              ENDIF
394    #endif
395    
396  C--     end of diagnostic k loop (Nr:1)  C--     end of diagnostic k loop (Nr:1)
397          ENDDO          ENDDO
398    
399  #ifdef ALLOW_DIAGNOSTICS  #ifdef ALLOW_DIAGNOSTICS
400          IF ( usediagnostics .AND.  c       IF ( useDiagnostics .AND.
401       &       (useGMRedi .OR. ivdc_kappa.NE.0.) ) THEN  c    &       (useGMRedi .OR. ivdc_kappa.NE.0.) ) THEN
402            CALL fill_diagnostics (myThid, 'DRHODR  ', 0, Nr,          IF ( doDiagsRho.GE.1 ) THEN
403       &         3, bi, bj, sigmaR)            CALL DIAGNOSTICS_FILL (sigmaR, 'DRHODR  ', 0, Nr,
404         &         2, bi, bj, myThid)
405          ENDIF          ENDIF
406  #endif  #endif
407    
# Line 342  C       relaxation terms, etc. Line 427  C       relaxation terms, etc.
427          IF ( debugLevel .GE. debLevB )          IF ( debugLevel .GE. debLevB )
428       &    CALL DEBUG_CALL('EXTERNAL_FORCING_SURF',myThid)       &    CALL DEBUG_CALL('EXTERNAL_FORCING_SURF',myThid)
429  #endif  #endif
430    #ifdef ALLOW_AUTODIFF_TAMC
431    CADJ STORE EmPmR(:,:,bi,bj)
432    CADJ &     = comlev1_bibj, key=itdkey, byte=isbyte
433    # ifdef EXACT_CONSERV
434    CADJ STORE PmEpR(:,:,bi,bj)
435    CADJ &     = comlev1_bibj, key=itdkey, byte=isbyte
436    # endif
437    # ifdef NONLIN_FRSURF
438    CADJ STORE hFac_surfC(:,:,bi,bj)
439    CADJ &     = comlev1_bibj, key=itdkey, byte=isbyte
440    CADJ STORE recip_hFacC(:,:,:,bi,bj)
441    CADJ &     = comlev1_bibj, key=itdkey, byte=isbyte
442    # endif
443    #endif
444           CALL EXTERNAL_FORCING_SURF(           CALL EXTERNAL_FORCING_SURF(
445       I             bi, bj, iMin, iMax, jMin, jMax,       I             bi, bj, iMin, iMax, jMin, jMax,
446       I             myTime, myIter, myThid )       I             myTime, myIter, myThid )
447  #ifndef ALLOW_AUTODIFF_TAMC  #ifndef ALLOW_AUTODIFF_TAMC
448          ENDIF          ENDIF
449  #endif  #endif
450    #ifdef ALLOW_AUTODIFF_TAMC
451    # ifdef EXACT_CONSERV
452    cph-test
453    cphCADJ STORE PmEpR(:,:,bi,bj)
454    cphCADJ &     = comlev1_bibj, key=itdkey, byte=isbyte
455    # endif
456    #endif
457    
458  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
459  cph needed for KPP  cph needed for KPP
# Line 361  CADJ STORE surfaceForcingT(:,:,bi,bj) Line 467  CADJ STORE surfaceForcingT(:,:,bi,bj)
467  CADJ &     = comlev1_bibj, key=itdkey, byte=isbyte  CADJ &     = comlev1_bibj, key=itdkey, byte=isbyte
468  CADJ STORE surfaceForcingTice(:,:,bi,bj)  CADJ STORE surfaceForcingTice(:,:,bi,bj)
469  CADJ &     = comlev1_bibj, key=itdkey, byte=isbyte  CADJ &     = comlev1_bibj, key=itdkey, byte=isbyte
   
470  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
471    
472  #ifdef  ALLOW_GMREDI  #ifdef  ALLOW_GMREDI
# Line 453  C--     Compute GGL90 mixing coefficient Line 558  C--     Compute GGL90 mixing coefficient
558          ENDIF          ENDIF
559  #endif /* ALLOW_GGL90 */  #endif /* ALLOW_GGL90 */
560    
561    #ifdef ALLOW_TIMEAVE
562            IF ( taveFreq.GT. 0. _d 0 .AND. fluidIsWater ) THEN
563              CALL TIMEAVE_SURF_FLUX( bi, bj, myTime, myIter, myThid)
564            ENDIF
565            IF (taveFreq.GT.0. .AND. ivdc_kappa.NE.0.) THEN
566              CALL TIMEAVE_CUMULATE(ConvectCountTave, IVDConvCount,
567         I                           Nr, deltaTclock, bi, bj, myThid)
568            ENDIF
569    #endif /* ALLOW_TIMEAVE */
570    
571  C--   end bi,bj loops.  C--   end bi,bj loops.
572         ENDDO         ENDDO
573        ENDDO        ENDDO
574    
575    #ifdef ALLOW_DIAGNOSTICS
576          IF ( fluidIsWater .AND. useDiagnostics ) THEN
577            CALL DIAGS_OCEANIC_SURF_FLUX( myTime, myIter, myThid )
578          ENDIF
579          IF ( ivdc_kappa.NE.0 .AND. useDiagnostics ) THEN
580            CALL DIAGNOSTICS_FILL( IVDConvCount,'CONVADJ ',
581         &                         0, Nr, 0, 1, 1, myThid )
582          ENDIF
583    #endif
584    
585  #ifdef ALLOW_DEBUG  #ifdef ALLOW_DEBUG
586           IF ( debugLevel .GE. debLevB )        IF ( debugLevel .GE. debLevB )
587       &    CALL DEBUG_LEAVE('DO_OCEANIC_PHYS',myThid)       &     CALL DEBUG_LEAVE('DO_OCEANIC_PHYS',myThid)
588  #endif  #endif
589    
590        RETURN        RETURN

Legend:
Removed from v.1.15  
changed lines
  Added in v.1.29

  ViewVC Help
Powered by ViewVC 1.1.22