/[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.12 by heimbach, Wed Oct 13 07:05:50 2004 UTC revision 1.31 by heimbach, Sun Oct 22 01:11:44 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
94  C     kDown, km1       are switched with layer to be the appropriate        _RL rhokp1  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
 C                      index into fVerTerm.  
95        _RL rhokm1  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rhokm1  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
96        _RL rhok    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rhok    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
97        _RL sigmaX  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL sigmaX  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
98        _RL sigmaY  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL sigmaY  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
99        _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  
100        INTEGER iMin, iMax        INTEGER iMin, iMax
101        INTEGER jMin, jMax        INTEGER jMin, jMax
102        INTEGER bi, bj        INTEGER bi, bj
103        INTEGER i, j        INTEGER i, j, k
104        INTEGER k, km1, kup, kDown        INTEGER doDiagsRho
105        INTEGER iTracer, ip  #ifdef ALLOW_DIAGNOSTICS
106          LOGICAL  DIAGNOSTICS_IS_ON
107          EXTERNAL DIAGNOSTICS_IS_ON
108    #endif /* ALLOW_DIAGNOSTICS */
109    
110  CEOP  CEOP
111    
# Line 104  C--   dummy statement to end declaration Line 115  C--   dummy statement to end declaration
115  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
116    
117  #ifdef ALLOW_DEBUG  #ifdef ALLOW_DEBUG
118        IF ( debugLevel .GE. debLevB )        IF ( debugLevel .GE. debLevB )
119       &    CALL DEBUG_ENTER('DO_OCEANIC_PHYS',myThid)       &     CALL DEBUG_ENTER('DO_OCEANIC_PHYS',myThid)
120  #endif  #endif
121    
122  #ifdef ALLOW_THSICE        doDiagsRho = 0
123        IF ( useThSIce .AND. buoyancyRelation(1:7) .EQ. 'OCEANIC' ) THEN  #ifdef ALLOW_DIAGNOSTICS
124          IF ( useDiagnostics .AND. fluidIsWater ) THEN
125            IF ( DIAGNOSTICS_IS_ON('DRHODR  ',myThid) ) doDiagsRho = 1
126            IF ( DIAGNOSTICS_IS_ON('RHOANOSQ',myThid) .OR.
127         &       DIAGNOSTICS_IS_ON('URHOMASS',myThid) .OR.
128         &       DIAGNOSTICS_IS_ON('VRHOMASS',myThid) .OR.
129         &       DIAGNOSTICS_IS_ON('WRHOMASS',myThid) .OR.
130         &       DIAGNOSTICS_IS_ON('WRHOMASS',myThid) ) doDiagsRho = 2
131          ENDIF
132    #endif /* ALLOW_DIAGNOSTICS */
133    
134    #ifdef ALLOW_SEAICE
135    C--   Call sea ice model to compute forcing/external data fields.  In
136    C     addition to computing prognostic sea-ice variables and diagnosing the
137    C     forcing/external data fields that drive the ocean model, SEAICE_MODEL
138    C     also sets theta to the freezing point under sea-ice.  The implied
139    C     surface heat flux is then stored in variable surfaceTendencyTice,
140    C     which is needed by KPP package (kpp_calc.F and kpp_transport_t.F)
141    C     to diagnose surface buoyancy fluxes and for the non-local transport
142    C     term.  Because this call precedes model thermodynamics, temperature
143    C     under sea-ice may not be "exactly" at the freezing point by the time
144    C     theta is dumped or time-averaged.
145          IF ( useSEAICE ) THEN
146    #ifdef ALLOW_AUTODIFF_TAMC
147    CADJ STORE qnet,qsw            = comlev1, key = ikey_dynamics
148    CADJ STORE aqh,precip,swdown   = comlev1, key = ikey_dynamics
149    CADJ STORE theta               = comlev1, key = ikey_dynamics
150    # ifdef SEAICE_ALLOW_DYNAMICS
151    CADJ STORE uvel,vvel           = comlev1, key = ikey_dynamics
152    # endif
153    #endif
154    #ifdef ALLOW_DEBUG
155            IF ( debugLevel .GE. debLevB )
156         &    CALL DEBUG_CALL('SEAICE_MODEL',myThid)
157    #endif
158            CALL TIMER_START('SEAICE_MODEL    [DO_OCEANIC_PHYS]', myThid)
159            CALL SEAICE_MODEL( myTime, myIter, myThid )
160            CALL TIMER_STOP ('SEAICE_MODEL    [DO_OCEANIC_PHYS]', myThid)
161    #ifdef ALLOW_COST_ICE
162            CALL COST_ICE_TEST ( myTime, myIter, myThid )
163    #endif
164          ENDIF
165    #endif /* ALLOW_SEAICE */
166    
167    #if (defined ALLOW_THSICE) && !(defined ALLOW_ATM2D)
168          IF ( useThSIce .AND. fluidIsWater ) THEN
169  #ifdef ALLOW_DEBUG  #ifdef ALLOW_DEBUG
170          IF ( debugLevel .GE. debLevB )          IF ( debugLevel .GE. debLevB )
171       &    CALL DEBUG_CALL('THSICE_MAIN',myThid)       &    CALL DEBUG_CALL('THSICE_MAIN',myThid)
# Line 122  C       and modify forcing terms includi Line 178  C       and modify forcing terms includi
178        ENDIF        ENDIF
179  #endif /* ALLOW_THSICE */  #endif /* ALLOW_THSICE */
180    
181    #ifdef ALLOW_SHELFICE
182          IF ( useShelfIce .AND. fluidIsWater ) THEN
183    #ifdef ALLOW_DEBUG
184            IF ( debugLevel .GE. debLevB )
185         &    CALL DEBUG_CALL('SHELFICE_THERMODYNAMICS',myThid)
186    #endif
187    C     compute temperature and (virtual) salt flux at the
188    C     shelf-ice ocean interface
189           CALL TIMER_START('SHELFICE_THERMODYNAMICS [DO_OCEANIC_PHYS]',
190         &       myThid)
191           CALL SHELFICE_THERMODYNAMICS( myTime, myIter, myThid )
192           CALL TIMER_STOP( 'SHELFICE_THERMODYNAMICS [DO_OCEANIC_PHYS]',
193         &      myThid)
194          ENDIF
195    #endif /* ALLOW_SHELFICE */
196    
197  C--   Freeze water at the surface  C--   Freeze water at the surface
198  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
199  CADJ STORE theta = comlev1, key = ikey_dynamics  CADJ STORE theta = comlev1, key = ikey_dynamics
# Line 132  CADJ STORE theta = comlev1, key = ikey_d Line 204  CADJ STORE theta = comlev1, key = ikey_d
204          CALL FREEZE_SURFACE(  myTime, myIter, myThid )          CALL FREEZE_SURFACE(  myTime, myIter, myThid )
205        ENDIF        ENDIF
206    
207  #ifdef COMPONENT_MODULE  #ifdef ALLOW_OCN_COMPON_INTERF
 # ifndef ALLOW_AIM  
208  C--    Apply imported data (from coupled interface) to forcing fields  C--    Apply imported data (from coupled interface) to forcing fields
209  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 ?)
210         IF ( useCoupler ) THEN         IF ( useCoupler ) THEN
211           CALL OCN_APPLY_IMPORT( .TRUE., myTime, myIter, myThid )           CALL OCN_APPLY_IMPORT( .TRUE., myTime, myIter, myThid )
212         ENDIF         ENDIF
213  # endif  #endif /* ALLOW_OCN_COMPON_INTERF */
214  #endif /* COMPONENT_MODULE */  
215    #ifdef ALLOW_BALANCE_FLUXES
216    C     balance fluxes
217           IF ( balanceEmPmR )
218         &        CALL REMOVE_MEAN_RS( 1, EmPmR, maskH, maskH, rA, drF,
219         &        'EmPmR', myTime, myThid )
220           IF ( balanceQnet )
221         &        CALL REMOVE_MEAN_RS( 1, Qnet,  maskH, maskH, rA, drF,
222         &        'Qnet ', myTime, myThid )
223    #endif /* ALLOW_BALANCE_FLUXES */
224    
225  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
226  C--   HPF directive to help TAMC  C--   HPF directive to help TAMC
227  CHPF$ INDEPENDENT  CHPF$ INDEPENDENT
228  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
   
229        DO bj=myByLo(myThid),myByHi(myThid)        DO bj=myByLo(myThid),myByHi(myThid)
   
230  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
231  C--    HPF directive to help TAMC  C--   HPF directive to help TAMC
232  CHPF$  INDEPENDENT, NEW (rTrans,fVerT,fVerS  CHPF$ INDEPENDENT
 CHPF$&                  ,utrans,vtrans,xA,yA  
 CHPF$&                  )  
233  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
   
234         DO bi=myBxLo(myThid),myBxHi(myThid)         DO bi=myBxLo(myThid),myBxHi(myThid)
235    
236  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
# Line 181  C     uninitialised but inert locations. Line 256  C     uninitialised but inert locations.
256           DO i=1-OLx,sNx+OLx           DO i=1-OLx,sNx+OLx
257            rhok   (i,j)   = 0. _d 0            rhok   (i,j)   = 0. _d 0
258            rhoKM1 (i,j)   = 0. _d 0            rhoKM1 (i,j)   = 0. _d 0
259              rhoKP1 (i,j)   = 0. _d 0
260           ENDDO           ENDDO
261          ENDDO          ENDDO
262    
# Line 234  CADJ &     = comlev1_bibj, key=itdkey, b Line 310  CADJ &     = comlev1_bibj, key=itdkey, b
310  CADJ STORE uvel (:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte  CADJ STORE uvel (:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
311  CADJ STORE vvel (:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte  CADJ STORE vvel (:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
312  # endif  # endif
 # ifdef EXACT_CONSERV  
 CADJ STORE pmepr(:,:,bi,bj)   = comlev1_bibj, key=itdkey, byte=isbyte  
 # endif  
313  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
314    
315  #ifdef ALLOW_DEBUG  #ifdef ALLOW_DEBUG
# Line 258  cph Needed for rhok, rhokm1, in the case Line 331  cph Needed for rhok, rhokm1, in the case
331  C--       Calculate gradients of potential density for isoneutral  C--       Calculate gradients of potential density for isoneutral
332  C         slope terms (e.g. GM/Redi tensor or IVDC diffusivity)  C         slope terms (e.g. GM/Redi tensor or IVDC diffusivity)
333  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
334            IF ( useGMRedi .OR. (k.GT.1 .AND. ivdc_kappa.NE.0.) ) THEN            IF ( useGMRedi .OR. (k.GT.1 .AND. ivdc_kappa.NE.0.)
335         &                   .OR. doDiagsRho.GE.1 ) THEN
336  #ifdef ALLOW_DEBUG  #ifdef ALLOW_DEBUG
337              IF ( debugLevel .GE. debLevB )              IF ( debugLevel .GE. debLevB )
338       &       CALL DEBUG_CALL('FIND_RHO',myThid)       &       CALL DEBUG_CALL('FIND_RHO',myThid)
# Line 288  CADJ STORE salt (:,:,k-1,bi,bj) = comlev Line 362  CADJ STORE salt (:,:,k-1,bi,bj) = comlev
362              IF ( debugLevel .GE. debLevB )              IF ( debugLevel .GE. debLevB )
363       &       CALL DEBUG_CALL('GRAD_SIGMA',myThid)       &       CALL DEBUG_CALL('GRAD_SIGMA',myThid)
364  #endif  #endif
365    cph Avoid variable aliasing for adjoint !!!
366                DO j=jMin,jMax
367                 DO i=iMin,iMax
368                  rhoKP1(i,j) = rhoK(i,j)
369                 ENDDO
370                ENDDO
371              CALL GRAD_SIGMA(              CALL GRAD_SIGMA(
372       I             bi, bj, iMin, iMax, jMin, jMax, k,       I             bi, bj, iMin, iMax, jMin, jMax, k,
373       I             rhoK, rhoKm1, rhoK,       I             rhoK, rhoKm1, rhoKp1,
374       O             sigmaX, sigmaY, sigmaR,       O             sigmaX, sigmaY, sigmaR,
375       I             myThid )       I             myThid )
376            ENDIF            ENDIF
# Line 314  c ==> should use sigmaR !!! Line 394  c ==> should use sigmaR !!!
394       I        myTime, myIter, myThid)       I        myTime, myIter, myThid)
395            ENDIF            ENDIF
396    
397    #ifdef ALLOW_DIAGNOSTICS
398              IF ( doDiagsRho.GE.2 ) THEN
399                CALL DIAGS_RHO( k, bi, bj,
400         I                      rhoK, rhoKm1,
401         I                      myTime, myIter, myThid)
402              ENDIF
403    #endif
404    
405  C--     end of diagnostic k loop (Nr:1)  C--     end of diagnostic k loop (Nr:1)
406          ENDDO          ENDDO
407    
408  #ifdef ALLOW_DIAGNOSTICS  #ifdef ALLOW_DIAGNOSTICS
409          IF ( usediagnostics .AND.  c       IF ( useDiagnostics .AND.
410       &       (useGMRedi .OR. ivdc_kappa.NE.0.) ) THEN  c    &       (useGMRedi .OR. ivdc_kappa.NE.0.) ) THEN
411            CALL fill_diagnostics (myThid, 'DRHODR  ', 0, Nr,          IF ( doDiagsRho.GE.1 ) THEN
412       &         3, bi, bj, sigmaR)            CALL DIAGNOSTICS_FILL (sigmaR, 'DRHODR  ', 0, Nr,
413         &         2, bi, bj, myThid)
414          ENDIF          ENDIF
415  #endif  #endif
416    
# Line 339  C--     Calculate future values on open Line 428  C--     Calculate future values on open
428  #endif  /* ALLOW_OBCS */  #endif  /* ALLOW_OBCS */
429    
430  #ifndef ALLOW_AUTODIFF_TAMC  #ifndef ALLOW_AUTODIFF_TAMC
431          IF ( buoyancyRelation(1:7) .EQ. 'OCEANIC' ) THEN          IF ( fluidIsWater ) THEN
432  #endif  #endif
433  C--     Determines forcing terms based on external fields  C--     Determines forcing terms based on external fields
434  C       relaxation terms, etc.  C       relaxation terms, etc.
# Line 347  C       relaxation terms, etc. Line 436  C       relaxation terms, etc.
436          IF ( debugLevel .GE. debLevB )          IF ( debugLevel .GE. debLevB )
437       &    CALL DEBUG_CALL('EXTERNAL_FORCING_SURF',myThid)       &    CALL DEBUG_CALL('EXTERNAL_FORCING_SURF',myThid)
438  #endif  #endif
439    #ifdef ALLOW_AUTODIFF_TAMC
440    CADJ STORE EmPmR(:,:,bi,bj)
441    CADJ &     = comlev1_bibj, key=itdkey, byte=isbyte
442    # ifdef EXACT_CONSERV
443    CADJ STORE PmEpR(:,:,bi,bj)
444    CADJ &     = comlev1_bibj, key=itdkey, byte=isbyte
445    # endif
446    # ifdef NONLIN_FRSURF
447    CADJ STORE hFac_surfC(:,:,bi,bj)
448    CADJ &     = comlev1_bibj, key=itdkey, byte=isbyte
449    CADJ STORE recip_hFacC(:,:,:,bi,bj)
450    CADJ &     = comlev1_bibj, key=itdkey, byte=isbyte
451    # endif
452    #endif
453           CALL EXTERNAL_FORCING_SURF(           CALL EXTERNAL_FORCING_SURF(
454       I             bi, bj, iMin, iMax, jMin, jMax,       I             bi, bj, iMin, iMax, jMin, jMax,
455       I             myTime, myIter, myThid )       I             myTime, myIter, myThid )
456  #ifndef ALLOW_AUTODIFF_TAMC  #ifndef ALLOW_AUTODIFF_TAMC
457          ENDIF          ENDIF
458  #endif  #endif
459    #ifdef ALLOW_AUTODIFF_TAMC
460    # ifdef EXACT_CONSERV
461    cph-test
462    cphCADJ STORE PmEpR(:,:,bi,bj)
463    cphCADJ &     = comlev1_bibj, key=itdkey, byte=isbyte
464    # endif
465    #endif
466    
467  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
468  cph needed for KPP  cph needed for KPP
# Line 457  C--     Compute GGL90 mixing coefficient Line 567  C--     Compute GGL90 mixing coefficient
567          ENDIF          ENDIF
568  #endif /* ALLOW_GGL90 */  #endif /* ALLOW_GGL90 */
569    
570    #ifdef ALLOW_TIMEAVE
571            IF ( taveFreq.GT. 0. _d 0 .AND. fluidIsWater ) THEN
572              CALL TIMEAVE_SURF_FLUX( bi, bj, myTime, myIter, myThid)
573            ENDIF
574            IF (taveFreq.GT.0. .AND. ivdc_kappa.NE.0.) THEN
575              CALL TIMEAVE_CUMULATE(ConvectCountTave, IVDConvCount,
576         I                           Nr, deltaTclock, bi, bj, myThid)
577            ENDIF
578    #endif /* ALLOW_TIMEAVE */
579    
580  C--   end bi,bj loops.  C--   end bi,bj loops.
581         ENDDO         ENDDO
582        ENDDO        ENDDO
583    
584    #ifdef ALLOW_DIAGNOSTICS
585          IF ( fluidIsWater .AND. useDiagnostics ) THEN
586            CALL DIAGS_OCEANIC_SURF_FLUX( myTime, myIter, myThid )
587          ENDIF
588          IF ( ivdc_kappa.NE.0 .AND. useDiagnostics ) THEN
589            CALL DIAGNOSTICS_FILL( IVDConvCount,'CONVADJ ',
590         &                         0, Nr, 0, 1, 1, myThid )
591          ENDIF
592    #endif
593    
594  #ifdef ALLOW_DEBUG  #ifdef ALLOW_DEBUG
595           IF ( debugLevel .GE. debLevB )        IF ( debugLevel .GE. debLevB )
596       &    CALL DEBUG_LEAVE('DO_OCEANIC_PHYS',myThid)       &     CALL DEBUG_LEAVE('DO_OCEANIC_PHYS',myThid)
597  #endif  #endif
598    
599        RETURN        RETURN

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

  ViewVC Help
Powered by ViewVC 1.1.22