/[MITgcm]/MITgcm/pkg/ggl90/ggl90_calc.F
ViewVC logotype

Diff of /MITgcm/pkg/ggl90/ggl90_calc.F

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

revision 1.14 by jmc, Sat Oct 31 03:18:50 2009 UTC revision 1.18 by gforget, Wed Aug 11 03:32:29 2010 UTC
# Line 84  c     _RL     SQRTTKE Line 84  c     _RL     SQRTTKE
84        _RL     RiNumber        _RL     RiNumber
85        _RL     TKEdissipation        _RL     TKEdissipation
86        _RL     tempU, tempV, prTemp        _RL     tempU, tempV, prTemp
87        _RL     MaxLength, tmpmlx        _RL     MaxLength, tmpmlx, tmpVisc
88        _RL     TKEPrandtlNumber (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL     TKEPrandtlNumber (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
89        _RL     GGL90mixingLength(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL     GGL90mixingLength(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
90        _RL     rMixingLength    (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL     rMixingLength    (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
# Line 94  c     _RL     SQRTTKE Line 94  c     _RL     SQRTTKE
94        _RL     rhoKm1           (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL     rhoKm1           (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
95        _RL     totalDepth       (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL     totalDepth       (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
96        _RL     gTKE             (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL     gTKE             (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
97          _RL     GGL90visctmp     (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
98  C-    tri-diagonal matrix  C-    tri-diagonal matrix
99        _RL     a(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL     a(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
100        _RL     b(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL     b(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
101        _RL     c(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL     c(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
102  c     INTEGER errCode        INTEGER errCode
103  #ifdef ALLOW_GGL90_HORIZDIFF  #ifdef ALLOW_GGL90_HORIZDIFF
104  C-    xA, yA   - area of lateral faces  C-    xA, yA   - area of lateral faces
105  C-    dfx, dfy - diffusive flux across lateral faces  C-    dfx, dfy - diffusive flux across lateral faces
# Line 108  C-    dfx, dfy - diffusive flux across l Line 109  C-    dfx, dfy - diffusive flux across l
109        _RL     dfy(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL     dfy(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
110  #endif /* ALLOW_GGL90_HORIZDIFF */  #endif /* ALLOW_GGL90_HORIZDIFF */
111  #ifdef ALLOW_GGL90_SMOOTH  #ifdef ALLOW_GGL90_SMOOTH
112        _RL p4, p8, p16, tmpdiffKrS        _RL p4, p8, p16
113        p4=0.25 _d 0        p4=0.25 _d 0
114        p8=0.125 _d 0        p8=0.125 _d 0
115        p16=0.0625 _d 0        p16=0.0625 _d 0
# Line 136  C     Initialize local fields Line 137  C     Initialize local fields
137           KappaE(I,J,K)            = 0. _d 0           KappaE(I,J,K)            = 0. _d 0
138           TKEPrandtlNumber(I,J,K)  = 1. _d 0           TKEPrandtlNumber(I,J,K)  = 1. _d 0
139           GGL90mixingLength(I,J,K) = GGL90mixingLengthMin           GGL90mixingLength(I,J,K) = GGL90mixingLengthMin
140             GGL90visctmp(I,J,K)      = 0. _d 0
141          ENDDO          ENDDO
142         ENDDO         ENDDO
143        ENDDO        ENDDO
# Line 240  c         MaxLength=MAX(MaxLength,20. _d Line 242  c         MaxLength=MAX(MaxLength,20. _d
242    
243        ELSEIF ( mxlMaxFlag .EQ. 2 ) THEN        ELSEIF ( mxlMaxFlag .EQ. 2 ) THEN
244  C-  C-
245    cgf ensure mixing between first and second level
246    c      DO J=jMin,jMax
247    c        DO I=iMin,iMax
248    c         GGL90mixingLength(I,J,2)=drF(1)
249    c        ENDDO
250    c      ENDDO
251    cgf
252         DO k=2,Nr         DO k=2,Nr
253          DO J=jMin,jMax          DO J=jMin,jMax
254           DO I=iMin,iMax           DO I=iMin,iMax
# Line 325  c       ENDDO Line 334  c       ENDDO
334  c      ENDDO  c      ENDDO
335  c     ENDDO  c     ENDDO
336    
337    
338        DO k=2,Nr        DO k=2,Nr
339         Km1 = K-1         Km1 = K-1
340         DO J=jMin,jMax         DO J=jMin,jMax
# Line 346  c         TKEPrandtlNumber(I,J,K) = 1. _ Line 356  c         TKEPrandtlNumber(I,J,K) = 1. _
356    
357  C     viscosity and diffusivity  C     viscosity and diffusivity
358           KappaM = GGL90ck*GGL90mixingLength(I,J,K)*SQRTTKE(i,j,k)           KappaM = GGL90ck*GGL90mixingLength(I,J,K)*SQRTTKE(i,j,k)
359             GGL90visctmp(I,J,K) = MAX(KappaM,diffKrNrT(k))
360         &                            * maskC(I,J,K,bi,bj)
361    c        note: storing GGL90visctmp like this, and using it later to compute
362    c              GGL9rdiffKr etc. is robust in case of smoothing (e.g. see OPA)
363             KappaM = MAX(KappaM,viscArNr(k)) * maskC(I,J,K,bi,bj)
364           KappaH = KappaM/TKEPrandtlNumber(I,J,K)           KappaH = KappaM/TKEPrandtlNumber(I,J,K)
365             KappaE(I,J,K) = GGL90alpha * KappaM * maskC(I,J,K,bi,bj)
 C     Set a minium (= background) and maximum value  
          KappaM = MAX(KappaM,viscArNr(k))  
          KappaH = MAX(KappaH,diffKrNrT(k))  
          KappaM = MIN(KappaM,GGL90viscMax)  
          KappaH = MIN(KappaH,GGL90diffMax)  
   
 C     Mask land points and storage  
          GGL90viscAr(I,J,K,bi,bj) = KappaM * maskC(I,J,K,bi,bj)  
          GGL90diffKr(I,J,K,bi,bj) = KappaH * maskC(I,J,K,bi,bj)  
          KappaE(I,J,K) = GGL90alpha * GGL90viscAr(I,J,K,bi,bj)  
366    
367  C     dissipation term  C     dissipation term
368           TKEdissipation = ab05*GGL90ceps           TKEdissipation = ab05*GGL90ceps
# Line 414  C     ... across y-faces Line 419  C     ... across y-faces
419           ENDDO           ENDDO
420          ENDDO          ENDDO
421  C     Compute divergence of fluxes  C     Compute divergence of fluxes
 C- jmc: concerned about missing a deltaT since gTKE is already the future TKE.  
422          DO j=1-Oly,sNy+Oly-1          DO j=1-Oly,sNy+Oly-1
423           DO i=1-Olx,sNx+Olx-1           DO i=1-Olx,sNx+Olx-1
424            gTKE(i,j,k)=gTKE(i,j,k)            gTKE(i,j,k)=gTKE(i,j,k)
425       &   -_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)*recip_rA(i,j,bi,bj)       &   -_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)*recip_rA(i,j,bi,bj)
426       &         *( (dfx(i+1,j)-dfx(i,j))       &         *( (dfx(i+1,j)-dfx(i,j))
427       &           +(dfy(i,j+1)-dfy(i,j))       &           +(dfy(i,j+1)-dfy(i,j))
428       &           )       &           )*deltaTggl90
429           ENDDO           ENDDO
430          ENDDO          ENDDO
431  C       end of k-loop  C       end of k-loop
# Line 442  C--   Lower diagonal Line 446  C--   Lower diagonal
446         ENDDO         ENDDO
447        ENDDO        ENDDO
448        DO k=2,Nr        DO k=2,Nr
449  C- jmc: concerned that a(k=2) should always be zero         km1=MAX(2,k-1)
 C       and would be better without recip_hFacC  
        km1=max(2,k-1)  
450         DO j=jMin,jMax         DO j=jMin,jMax
451          DO i=iMin,iMax          DO i=iMin,iMax
452    C-    We keep recip_hFacC in the diffusive flux calculation,
453    C-    but no hFacC in TKE volume control
454    C-    No need for maskC(k-1) with recip_hFacC(k-1)
455           a(i,j,k) = -deltaTggl90           a(i,j,k) = -deltaTggl90
 c     &        *recip_drF(km1)*recip_hFacI(i,j,k,bi,bj)  
456       &        *recip_drF(k-1)*recip_hFacC(i,j,k-1,bi,bj)       &        *recip_drF(k-1)*recip_hFacC(i,j,k-1,bi,bj)
457       &        *.5 _d 0*(KappaE(i,j, k )+KappaE(i,j,km1))       &        *.5 _d 0*(KappaE(i,j, k )+KappaE(i,j,km1))
458       &        *recip_drC(k)*maskC(i,j,k,bi,bj)*maskC(i,j,k-1,bi,bj)       &        *recip_drC(k)*maskC(i,j,k,bi,bj)
459          ENDDO          ENDDO
460         ENDDO         ENDDO
461        ENDDO        ENDDO
# Line 462  C--   Upper diagonal Line 466  C--   Upper diagonal
466         ENDDO         ENDDO
467        ENDDO        ENDDO
468        DO k=2,Nr        DO k=2,Nr
 C- jmc: concerned that c(k) from k=kLow to k=Nr should always be zero  
469         DO j=jMin,jMax         DO j=jMin,jMax
470          DO i=iMin,iMax          DO i=iMin,iMax
471  C- jmc: this is dangerous since klowC could be zero if land column            kp1=MAX(1,MIN(klowC(i,j,bi,bj),k+1))
472  C       and would be better without recip_hFacC  C-    We keep recip_hFacC in the diffusive flux calculation,
473            kp1=min(klowC(i,j,bi,bj),k+1)  C-    but no hFacC in TKE volume control
474    C-    No need for maskC(k) with recip_hFacC(k)
475            c(i,j,k) = -deltaTggl90            c(i,j,k) = -deltaTggl90
 c     &        *recip_drF( k )*recip_hFacI(i,j,k,bi,bj)  
476       &        *recip_drF( k ) * recip_hFacC(i,j,k,bi,bj)       &        *recip_drF( k ) * recip_hFacC(i,j,k,bi,bj)
477       &        *.5 _d 0*(KappaE(i,j,k)+KappaE(i,j,kp1))       &        *.5 _d 0*(KappaE(i,j,k)+KappaE(i,j,kp1))
478       &        *recip_drC(k)*maskC(i,j,k,bi,bj)*maskC(i,j,k-1,bi,bj)       &        *recip_drC(k)*maskC(i,j,k-1,bi,bj)
479          ENDDO          ENDDO
480         ENDDO         ENDDO
481        ENDDO        ENDDO
482  C--   Center diagonal  C--   Center diagonal
483        DO k=1,Nr        DO k=1,Nr
484           km1 = MAX(k-1,1)
485         DO j=jMin,jMax         DO j=jMin,jMax
486          DO i=iMin,iMax          DO i=iMin,iMax
487            b(i,j,k) = 1. _d 0 - c(i,j,k) - a(i,j,k)            b(i,j,k) = 1. _d 0 - c(i,j,k) - a(i,j,k)
488       &        + ab15*deltaTggl90*GGL90ceps*SQRTTKE(I,J,K)       &        + ab15*deltaTggl90*GGL90ceps*SQRTTKE(I,J,K)
489       &        *rMixingLength(I,J,K)*maskC(i,j,k,bi,bj)       &        * rMixingLength(I,J,K)
490         &        * maskC(i,j,k,bi,bj)*maskC(i,j,km1,bi,bj)
491           ENDDO           ENDDO
492         ENDDO         ENDDO
493        ENDDO        ENDDO
494  C     end set up matrix  C     end set up matrix
495    
496  C     Apply boundary condition  C     Apply boundary condition
497  C- jmc: concerned about conservation when a or c are changed after computing b        kp1 = MIN(Nr,kSurf+1)
498        DO J=jMin,jMax        DO J=jMin,jMax
499         DO I=iMin,iMax         DO I=iMin,iMax
500  C     estimate friction velocity uStar from surface forcing  C     estimate friction velocity uStar from surface forcing
# Line 500  C     estimate friction velocity uStar f Line 505  C     estimate friction velocity uStar f
505       &              + surfaceForcingV(I,  J+1,bi,bj) ) )**2       &              + surfaceForcingV(I,  J+1,bi,bj) ) )**2
506       &                     )       &                     )
507  C     Dirichlet surface boundary condition for TKE  C     Dirichlet surface boundary condition for TKE
 C- jmc: would be much better to update the provisional TKE (i.e. gTKE) at k=2  
508          gTKE(I,J,kSurf) = MAX(GGL90TKEsurfMin,GGL90m2*uStarSquare)          gTKE(I,J,kSurf) = MAX(GGL90TKEsurfMin,GGL90m2*uStarSquare)
509       &                     *maskC(I,J,kSurf,bi,bj)       &                     *maskC(I,J,kSurf,bi,bj)
510            gTKE(i,j,kp1) = gTKE(i,j,kp1)
511         &                - a(i,j,kp1)*gTKE(i,j,kSurf)
512            a(i,j,kp1) = 0. _d 0
513  C     Dirichlet bottom boundary condition for TKE = GGL90TKEbottom  C     Dirichlet bottom boundary condition for TKE = GGL90TKEbottom
514          kBottom   = MAX(kLowC(I,J,bi,bj),1)          kBottom   = MAX(kLowC(I,J,bi,bj),1)
515          gTKE(I,J,kBottom) = gTKE(I,J,kBottom)          gTKE(I,J,kBottom) = gTKE(I,J,kBottom)
# Line 512  C     Dirichlet bottom boundary conditio Line 519  C     Dirichlet bottom boundary conditio
519        ENDDO        ENDDO
520    
521  C     solve tri-diagonal system, and store solution on gTKE (previously rhs)  C     solve tri-diagonal system, and store solution on gTKE (previously rhs)
522  c     CALL SOLVE_TRIDIAGONAL( iMin,iMax, jMin,jMax,        CALL SOLVE_TRIDIAGONAL( iMin,iMax, jMin,jMax,
523  c    I                        a, b, c,       I                        a, b, c,
524  c    U                        gTKE,       U                        gTKE,
525  c    O                        errCode,       O                        errCode,
526  c    I                        bi, bj, myThid )       I                        1, 1, myThid )
       CALL GGL90_SOLVE( bi, bj, iMin, iMax, jMin, jMax,  
      I     a, b, c,  
      U     gTKE,  
      I     myThid )  
527    
528  C     now update TKE  C     now update TKE
529        DO K=1,Nr        DO K=1,Nr
# Line 536  C     impose minimum TKE to avoid numeri Line 539  C     impose minimum TKE to avoid numeri
539  C     end of time step  C     end of time step
540  C     ===============================  C     ===============================
541    
542          DO K=2,Nr
543           DO J=1,sNy
544            DO I=1,sNx
545  #ifdef ALLOW_GGL90_SMOOTH  #ifdef ALLOW_GGL90_SMOOTH
546        DO K=1,Nr           tmpVisc=
        DO J=jMin,jMax  
         DO I=iMin,iMax  
          tmpdiffKrS=  
547       &  (       &  (
548       &   p4 *  GGL90viscAr(i  ,j  ,k,bi,bj) * mskCor(i  ,j  ,bi,bj)       &   p4 *  GGL90visctmp(i  ,j  ,k) * mskCor(i  ,j  ,bi,bj)
549       &  +p8 *( GGL90viscAr(i-1,j  ,k,bi,bj) * mskCor(i-1,j  ,bi,bj)       &  +p8 *( GGL90visctmp(i-1,j  ,k) * mskCor(i-1,j  ,bi,bj)
550       &       + GGL90viscAr(i  ,j-1,k,bi,bj) * mskCor(i  ,j-1,bi,bj)       &       + GGL90visctmp(i  ,j-1,k) * mskCor(i  ,j-1,bi,bj)
551       &       + GGL90viscAr(i+1,j  ,k,bi,bj) * mskCor(i+1,j  ,bi,bj)       &       + GGL90visctmp(i+1,j  ,k) * mskCor(i+1,j  ,bi,bj)
552       &       + GGL90viscAr(i  ,j+1,k,bi,bj) * mskCor(i  ,j+1,bi,bj))       &       + GGL90visctmp(i  ,j+1,k) * mskCor(i  ,j+1,bi,bj))
553       &  +p16*( GGL90viscAr(i+1,j+1,k,bi,bj) * mskCor(i+1,j+1,bi,bj)       &  +p16*( GGL90visctmp(i+1,j+1,k) * mskCor(i+1,j+1,bi,bj)
554       &       + GGL90viscAr(i+1,j-1,k,bi,bj) * mskCor(i+1,j-1,bi,bj)       &       + GGL90visctmp(i+1,j-1,k) * mskCor(i+1,j-1,bi,bj)
555       &       + GGL90viscAr(i-1,j+1,k,bi,bj) * mskCor(i-1,j+1,bi,bj)       &       + GGL90visctmp(i-1,j+1,k) * mskCor(i-1,j+1,bi,bj)
556       &       + GGL90viscAr(i-1,j-1,k,bi,bj) * mskCor(i-1,j-1,bi,bj))       &       + GGL90visctmp(i-1,j-1,k) * mskCor(i-1,j-1,bi,bj))
557       &  )       &  )
558       & /(p4       & /(p4
559       &  +p8 *(       maskC(i-1,j  ,k,bi,bj) * mskCor(i-1,j  ,bi,bj)       &  +p8 *(       maskC(i-1,j  ,k,bi,bj) * mskCor(i-1,j  ,bi,bj)
# Line 562  C     =============================== Line 565  C     ===============================
565       &       +       maskC(i-1,j+1,k,bi,bj) * mskCor(i-1,j+1,bi,bj)       &       +       maskC(i-1,j+1,k,bi,bj) * mskCor(i-1,j+1,bi,bj)
566       &       +       maskC(i-1,j-1,k,bi,bj) * mskCor(i-1,j-1,bi,bj))       &       +       maskC(i-1,j-1,k,bi,bj) * mskCor(i-1,j-1,bi,bj))
567       &  )*maskC(i,j,k,bi,bj)*mskCor(i,j,bi,bj)       &  )*maskC(i,j,k,bi,bj)*mskCor(i,j,bi,bj)
568       &   /TKEPrandtlNumber(i,j,k)  #else
569           GGL90diffKrS(I,J,K,bi,bj)= MAX( tmpdiffKrS , diffKrNrT(k) )           tmpVisc = GGL90visctmp(I,J,K)
570    #endif
571             tmpVisc = MIN(tmpVisc/TKEPrandtlNumber(i,j,k),GGL90diffMax)
572             GGL90diffKr(I,J,K,bi,bj)= MAX( tmpVisc , diffKrNrT(k) )
573            ENDDO
574           ENDDO
575          ENDDO
576    
577    
578    
579          DO K=2,Nr
580           DO J=1,sNy
581            DO I=1,sNx+1
582    #ifdef ALLOW_GGL90_SMOOTH
583            tmpVisc =
584         & (
585         &   p4 *(GGL90visctmp(i  ,j  ,k) * mskCor(i  ,j  ,bi,bj)
586         &       +GGL90visctmp(i-1,j  ,k) * mskCor(i-1,j  ,bi,bj))
587         &  +p8 *(GGL90visctmp(i-1,j-1,k) * mskCor(i-1,j-1,bi,bj)
588         &       +GGL90visctmp(i-1,j+1,k) * mskCor(i-1,j+1,bi,bj)
589         &       +GGL90visctmp(i  ,j-1,k) * mskCor(i  ,j-1,bi,bj)
590         &       +GGL90visctmp(i  ,j+1,k) * mskCor(i  ,j+1,bi,bj))
591         &  )
592         & /(p4 * 2. _d 0
593         &  +p8 *(      maskC(i-1,j-1,k,bi,bj) * mskCor(i-1,j-1,bi,bj)
594         &       +      maskC(i-1,j+1,k,bi,bj) * mskCor(i-1,j+1,bi,bj)
595         &       +      maskC(i  ,j-1,k,bi,bj) * mskCor(i  ,j-1,bi,bj)
596         &       +      maskC(i  ,j+1,k,bi,bj) * mskCor(i  ,j+1,bi,bj))
597         &  )
598         &  *maskC(i  ,j,k,bi,bj)*mskCor(i  ,j,bi,bj)
599         &  *maskC(i-1,j,k,bi,bj)*mskCor(i-1,j,bi,bj)
600    #else
601            tmpVisc = _maskW(i,j,k,bi,bj) *
602         &                   (.5 _d 0*(GGL90visctmp(i,j,k)
603         &                            +GGL90visctmp(i-1,j,k))
604         &                   )
605    #endif
606            tmpVisc = MIN( tmpVisc , GGL90viscMax )
607            GGL90viscArU(i,j,k,bi,bj) = MAX( tmpVisc , viscArNr(k)  )
608          ENDDO          ENDDO
609         ENDDO         ENDDO
610        ENDDO        ENDDO
611    
612    
613          DO K=2,Nr
614           DO J=1,sNy+1
615            DO I=1,sNx
616    #ifdef ALLOW_GGL90_SMOOTH
617            tmpVisc =
618         & (
619         &   p4 *(GGL90visctmp(i  ,j  ,k) * mskCor(i  ,j  ,bi,bj)
620         &       +GGL90visctmp(i  ,j-1,k) * mskCor(i  ,j-1,bi,bj))
621         &  +p8 *(GGL90visctmp(i-1,j  ,k) * mskCor(i-1,j  ,bi,bj)
622         &       +GGL90visctmp(i-1,j-1,k) * mskCor(i-1,j-1,bi,bj)
623         &       +GGL90visctmp(i+1,j  ,k) * mskCor(i+1,j  ,bi,bj)
624         &       +GGL90visctmp(i+1,j-1,k) * mskCor(i+1,j-1,bi,bj))
625         &  )
626         & /(p4 * 2. _d 0
627         &  +p8 *(      maskC(i-1,j  ,k,bi,bj) * mskCor(i-1,j  ,bi,bj)
628         &       +      maskC(i-1,j-1,k,bi,bj) * mskCor(i-1,j-1,bi,bj)
629         &       +      maskC(i+1,j  ,k,bi,bj) * mskCor(i+1,j  ,bi,bj)
630         &       +      maskC(i+1,j-1,k,bi,bj) * mskCor(i+1,j-1,bi,bj))
631         &  )
632         &   *maskC(i,j  ,k,bi,bj)*mskCor(i,j  ,bi,bj)
633         &   *maskC(i,j-1,k,bi,bj)*mskCor(i,j-1,bi,bj)
634    #else
635            tmpVisc = _maskS(i,j,k,bi,bj) *
636         &                   (.5 _d 0*(GGL90visctmp(i,j,k)
637         &                            +GGL90visctmp(i,j-1,k))
638         &                   )
639    
640  #endif  #endif
641            tmpVisc = MIN( tmpVisc , GGL90viscMax )
642            GGL90viscArV(i,j,k,bi,bj) = MAX( tmpVisc , viscArNr(k)  )
643            ENDDO
644           ENDDO
645          ENDDO
646    
647  #ifdef ALLOW_DIAGNOSTICS  #ifdef ALLOW_DIAGNOSTICS
648        IF ( useDiagnostics ) THEN        IF ( useDiagnostics ) THEN
649           CALL DIAGNOSTICS_FILL( GGL90TKE   ,'GGL90TKE',           CALL DIAGNOSTICS_FILL( GGL90TKE   ,'GGL90TKE',
650       &                          0,Nr, 1, bi, bj, myThid )       &                          0,Nr, 1, bi, bj, myThid )
651           CALL DIAGNOSTICS_FILL( GGL90viscAr,'GGL90Ar ',           CALL DIAGNOSTICS_FILL( GGL90viscArU,'GGL90ArU',
652         &                          0,Nr, 1, bi, bj, myThid )
653             CALL DIAGNOSTICS_FILL( GGL90viscArV,'GGL90ArV',
654       &                          0,Nr, 1, bi, bj, myThid )       &                          0,Nr, 1, bi, bj, myThid )
655           CALL DIAGNOSTICS_FILL( GGL90diffKr,'GGL90Kr ',           CALL DIAGNOSTICS_FILL( GGL90diffKr,'GGL90Kr ',
656       &                          0,Nr, 1, bi, bj, myThid )       &                          0,Nr, 1, bi, bj, myThid )

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

  ViewVC Help
Powered by ViewVC 1.1.22