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

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

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

revision 1.35 by jmc, Mon Feb 5 03:20:39 2007 UTC revision 1.36 by jmc, Mon Aug 11 22:25:52 2008 UTC
# Line 16  C     !INTERFACE: Line 16  C     !INTERFACE:
16  C     !DESCRIPTION: \bv  C     !DESCRIPTION: \bv
17  C     *==========================================================*  C     *==========================================================*
18  C     | SUBROUTINE CALC_PHI_HYD                                  |  C     | SUBROUTINE CALC_PHI_HYD                                  |
19  C     | o Integrate the hydrostatic relation to find the Hydros. |  C     | o Integrate the hydrostatic relation to find the Hydros. |
20  C     *==========================================================*  C     *==========================================================*
21  C     |    Potential (ocean: Pressure/rho ; atmos = geopotential)  C     |    Potential (ocean: Pressure/rho ; atmos = geopotential)
22  C     | On entry:  C     | On entry:
23  C     |   tFld,sFld     are the current thermodynamics quantities  C     |   tFld,sFld     are the current thermodynamics quantities
24  C     |                 (unchanged on exit)  C     |                 (unchanged on exit)
25  C     |   phiHydF(i,j) is the hydrostatic Potential anomaly  C     |   phiHydF(i,j) is the hydrostatic Potential anomaly
26  C     |                at middle between tracer points k-1,k  C     |                at middle between tracer points k-1,k
27  C     | On exit:  C     | On exit:
28  C     |   phiHydC(i,j) is the hydrostatic Potential anomaly  C     |   phiHydC(i,j) is the hydrostatic Potential anomaly
29  C     |                at cell centers (tracer points), level k  C     |                at cell centers (tracer points), level k
30  C     |   phiHydF(i,j) is the hydrostatic Potential anomaly  C     |   phiHydF(i,j) is the hydrostatic Potential anomaly
31  C     |                at middle between tracer points k,k+1  C     |                at middle between tracer points k,k+1
32  C     |   dPhiHydX,Y   hydrostatic Potential gradient (X&Y dir)  C     |   dPhiHydX,Y   hydrostatic Potential gradient (X&Y dir)
33  C     |                at cell centers (tracer points), level k  C     |                at cell centers (tracer points), level k
34  C     | integr_GeoPot allows to select one integration method  C     | integr_GeoPot allows to select one integration method
# Line 51  C     == Global variables == Line 51  C     == Global variables ==
51    
52  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
53  C     == Routine arguments ==  C     == Routine arguments ==
54  C     bi, bj, k  :: tile and level indices  C     bi, bj, k  :: tile and level indices
55  C     iMin,iMax,jMin,jMax :: computational domain  C     iMin,iMax,jMin,jMax :: computational domain
56  C     tFld       :: potential temperature  C     tFld       :: potential temperature
57  C     sFld       :: salinity  C     sFld       :: salinity
# Line 72  c     _RL phiHyd(1-OLx:sNx+OLx,1-OLy:sNy Line 72  c     _RL phiHyd(1-OLx:sNx+OLx,1-OLy:sNy
72        _RL dPhiHydY(1-Olx:sNx+Olx,1-Oly:sNy+Oly)        _RL dPhiHydY(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
73        _RL myTime        _RL myTime
74        INTEGER myIter, myThid        INTEGER myIter, myThid
75          
76  #ifdef INCLUDE_PHIHYD_CALCULATION_CODE  #ifdef INCLUDE_PHIHYD_CALCULATION_CODE
77    
78  C     !LOCAL VARIABLES:  C     !LOCAL VARIABLES:
# Line 92  CEOP Line 92  CEOP
92        IF (addSurfPhiAnom) surfPhiFac = 1.        IF (addSurfPhiAnom) surfPhiFac = 1.
93    
94  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
95  C  Atmosphere:    C  Atmosphere:
96  C integr_GeoPot => select one option for the integration of the Geopotential:  C integr_GeoPot => select one option for the integration of the Geopotential:
97  C   = 0 : Energy Conserving Form, accurate with Topo full cell;  C   = 0 : Energy Conserving Form, accurate with Topo full cell;
98  C   = 1 : Finite Volume Form, with Part-Cell, linear in P by Half level;  C   = 1 : Finite Volume Form, with Part-Cell, linear in P by Half level;
99  C   =2,3: Finite Difference Form, with Part-Cell,  C   =2,3: Finite Difference Form, with Part-Cell,
100  C         linear in P between 2 Tracer levels.  C         linear in P between 2 Tracer levels.
101  C       can handle both cases: Tracer lev at the middle of InterFace_W  C       can handle both cases: Tracer lev at the middle of InterFace_W
102  C                          and InterFace_W at the middle of Tracer lev;  C                          and InterFace_W at the middle of Tracer lev;
103  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
104    
# Line 119  C---+----1----+----2----+----3----+----4 Line 119  C---+----1----+----2----+----3----+----4
119       &                      + act4*max1*max2*max3       &                      + act4*max1*max2*max3
120  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
121    
122  C--   Initialize phiHydF to zero :  C--   Initialize phiHydF to zero :
123  C     note: atmospheric_loading or Phi_topo anomaly are incorporated  C     note: atmospheric_loading or Phi_topo anomaly are incorporated
124  C           later in S/R calc_grad_phi_hyd  C           later in S/R calc_grad_phi_hyd
125        IF (k.EQ.1) THEN        IF (k.EQ.1) THEN
# Line 145  C---    Calculate density Line 145  C---    Calculate density
145  CADJ STORE tFld (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte  CADJ STORE tFld (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
146  CADJ STORE sFld (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte  CADJ STORE sFld (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
147  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
148          CALL FIND_RHO( bi, bj, iMin, iMax, jMin, jMax, k, k,        CALL FIND_RHO_2D(
149       &                 tFld, sFld,       I          iMin, iMax, jMin, jMax, k,
150       &                 alphaRho, myThid)       I          tFld(1-OLx,1-OLy,k,bi,bj), sFld(1-OLx,1-OLy,k,bi,bj),
151         O          alphaRho,
152         I          k, bi, bj, myThid )
153    
154  #ifdef ALLOW_SHELFICE  #ifdef ALLOW_SHELFICE
155  C     mask rho, so that there is no contribution of phiHyd from  C     mask rho, so that there is no contribution of phiHyd from
156  C     overlying shelfice (whose density we do not know)  C     overlying shelfice (whose density we do not know)
157          IF ( useShelfIce ) THEN          IF ( useShelfIce ) THEN
158           DO j=jMin,jMax           DO j=jMin,jMax
# Line 228  C Line 231  C
231    
232  C  --  end if integr_GeoPot = ...  C  --  end if integr_GeoPot = ...
233         ENDIF         ENDIF
234            
235  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
236        ELSEIF ( buoyancyRelation .EQ. 'OCEANICP' ) THEN        ELSEIF ( buoyancyRelation .EQ. 'OCEANICP' ) THEN
237  C       This is the hydrostatic pressure calculation for the Ocean  C       This is the hydrostatic pressure calculation for the Ocean
# Line 244  C--     Calculate density Line 247  C--     Calculate density
247  CADJ STORE tFld (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte  CADJ STORE tFld (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
248  CADJ STORE sFld (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte  CADJ STORE sFld (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
249  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
250          CALL FIND_RHO( bi, bj, iMin, iMax, jMin, jMax, k, k,          CALL FIND_RHO_2D(
251       &                 tFld, sFld,       I            iMin, iMax, jMin, jMax, k,
252       &                 alphaRho, myThid)       I            tFld(1-OLx,1-OLy,k,bi,bj), sFld(1-OLx,1-OLy,k,bi,bj),
253         O            alphaRho,
254         I            k, bi, bj, myThid )
255  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
256  CADJ STORE alphaRho (:,:) = comlev1_bibj_k, key=kkey, byte=isbyte  CADJ STORE alphaRho (:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
257  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
# Line 283  C Line 288  C
288               ddRloc = ddRloc + surfPhiFac*etaH(i,j,bi,bj)               ddRloc = ddRloc + surfPhiFac*etaH(i,j,bi,bj)
289  #endif  #endif
290               phiHydC(i,j) = ddRloc*alphaRho(i,j)               phiHydC(i,j) = ddRloc*alphaRho(i,j)
291  c--to reproduce results of c48d_post: uncomment those 4+1 lines  c--to reproduce results of c48d_post: uncomment those 4+1 lines
292  c            phiHydC(i,j)=phiHydF(i,j)  c            phiHydC(i,j)=phiHydF(i,j)
293  c    &          +(hFacC(i,j,k,bi,bj)-half)*drF(k)*alphaRho(i,j)  c    &          +(hFacC(i,j,k,bi,bj)-half)*drF(k)*alphaRho(i,j)
294  c            phiHydF(i,j)=phiHydF(i,j)  c            phiHydF(i,j)=phiHydF(i,j)
# Line 344  C--     virtual potential temperature an Line 349  C--     virtual potential temperature an
349          DO j=jMin,jMax          DO j=jMin,jMax
350           DO i=iMin,iMax           DO i=iMin,iMax
351            alphaRho(i,j)=maskC(i,j,k,bi,bj)            alphaRho(i,j)=maskC(i,j,k,bi,bj)
352       &             *( tFld(i,j,k,bi,bj)*(sFld(i,j,k,bi,bj)*atm_Rq+one)       &             *( tFld(i,j,k,bi,bj)*(sFld(i,j,k,bi,bj)*atm_Rq+one)
353       &               -tRef(k) )       &               -tRef(k) )
354           ENDDO           ENDDO
355          ENDDO          ENDDO
# Line 355  C---    Integrate d Phi / d pi Line 360  C---    Integrate d Phi / d pi
360  C  --  Energy Conserving Form, accurate with Full cell topo  --  C  --  Energy Conserving Form, accurate with Full cell topo  --
361  C------------ The integration for the first level phi(k=1) is the same  C------------ The integration for the first level phi(k=1) is the same
362  C             for both the "finite volume" and energy conserving methods.  C             for both the "finite volume" and energy conserving methods.
363  C    *NOTE* o Working with geopotential Anomaly, the geopotential boundary  C    *NOTE* o Working with geopotential Anomaly, the geopotential boundary
364  C             condition is simply Phi-prime(Ro_surf)=0.  C             condition is simply Phi-prime(Ro_surf)=0.
365  C           o convention ddPI > 0 (same as drF & drC)  C           o convention ddPI > 0 (same as drF & drC)
366  C-----------------------------------------------------------------------  C-----------------------------------------------------------------------
# Line 371  C--------------------------------------- Line 376  C---------------------------------------
376       &                   -((rF(k+1)/atm_Po)**atm_kappa) )       &                   -((rF(k+1)/atm_Po)**atm_kappa) )
377           ELSE           ELSE
378             ddPIp=atm_Cp*( ((rC( k )/atm_Po)**atm_kappa)             ddPIp=atm_Cp*( ((rC( k )/atm_Po)**atm_kappa)
379       &                   -((rC(k+1)/atm_Po)**atm_kappa) )*half       &                   -((rC(k+1)/atm_Po)**atm_kappa) )*half
380           ENDIF           ENDIF
381  C-------- This discretization is the energy conserving form  C-------- This discretization is the energy conserving form
382           DO j=jMin,jMax           DO j=jMin,jMax
# Line 390  C  Finite Volume formulation consistent Line 395  C  Finite Volume formulation consistent
395  C   Note: a true Finite Volume form should be linear between 2 Interf_W :  C   Note: a true Finite Volume form should be linear between 2 Interf_W :
396  C     phi_C = (phi_W_k+ phi_W_k+1)/2 ; but not accurate in Stratosphere (low p)  C     phi_C = (phi_W_k+ phi_W_k+1)/2 ; but not accurate in Stratosphere (low p)
397  C   also: if Interface_W at the middle between tracer levels, this form  C   also: if Interface_W at the middle between tracer levels, this form
398  C     is close to the Energy Cons. form in the Interior, except for the  C     is close to the Energy Cons. form in the Interior, except for the
399  C     non-linearity in PI(p)  C     non-linearity in PI(p)
400  C---------  C---------
401             ddPIm=atm_Cp*( ((rF( k )/atm_Po)**atm_kappa)             ddPIm=atm_Cp*( ((rF( k )/atm_Po)**atm_kappa)
# Line 417  C--------------------------------------- Line 422  C---------------------------------------
422    
423         ELSEIF ( integr_GeoPot.EQ.2         ELSEIF ( integr_GeoPot.EQ.2
424       &     .OR. integr_GeoPot.EQ.3 ) THEN       &     .OR. integr_GeoPot.EQ.3 ) THEN
425  C  --  Finite Difference Form, with Part-Cell Topo,  C  --  Finite Difference Form, with Part-Cell Topo,
426  C       works with Interface_W  at the middle between 2.Tracer_Level  C       works with Interface_W  at the middle between 2.Tracer_Level
427  C        and  with Tracer_Level at the middle between 2.Interface_W.  C        and  with Tracer_Level at the middle between 2.Interface_W.
428  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
429  C  Finite Difference formulation consistent with Partial Cell,  C  Finite Difference formulation consistent with Partial Cell,
430  C   Valid & accurate if Interface_W at middle between tracer levels  C   Valid & accurate if Interface_W at middle between tracer levels
431  C   linear in p between 2 Tracer levels ; conserve energy in the Interior  C   linear in p between 2 Tracer levels ; conserve energy in the Interior
432  C---------  C---------
433           IF (k.EQ.1) THEN           IF (k.EQ.1) THEN
434             ddPIm=atm_Cp*( ((rF( k )/atm_Po)**atm_kappa)             ddPIm=atm_Cp*( ((rF( k )/atm_Po)**atm_kappa)
# Line 437  C--------- Line 442  C---------
442       &                   -((rF(k+1)/atm_Po)**atm_kappa) )       &                   -((rF(k+1)/atm_Po)**atm_kappa) )
443           ELSE           ELSE
444             ddPIp=atm_Cp*( ((rC( k )/atm_Po)**atm_kappa)             ddPIp=atm_Cp*( ((rC( k )/atm_Po)**atm_kappa)
445       &                   -((rC(k+1)/atm_Po)**atm_kappa) )*half       &                   -((rC(k+1)/atm_Po)**atm_kappa) )*half
446           ENDIF           ENDIF
447           rec_dRm = one/(rF(k)-rC(k))           rec_dRm = one/(rF(k)-rC(k))
448           rec_dRp = one/(rC(k)-rF(k+1))           rec_dRp = one/(rC(k)-rF(k+1))
# Line 477  C       = Top atmosphere height (Atmos, Line 482  C       = Top atmosphere height (Atmos,
482          CALL DIAGS_PHI_RLOW(          CALL DIAGS_PHI_RLOW(
483       I                      k, bi, bj, iMin,iMax, jMin,jMax,       I                      k, bi, bj, iMin,iMax, jMin,jMax,
484       I                      phiHydF, phiHydC, alphaRho, tFld, sFld,       I                      phiHydF, phiHydC, alphaRho, tFld, sFld,
485       I                      myTime, myIter, myThid)         I                      myTime, myIter, myThid)
486        ENDIF        ENDIF
487    
488  C---   Diagnose Full Hydrostatic Potential at cell center level  C---   Diagnose Full Hydrostatic Potential at cell center level
# Line 486  C---   Diagnose Full Hydrostatic Potenti Line 491  C---   Diagnose Full Hydrostatic Potenti
491       I                      phiHydC,       I                      phiHydC,
492       I                      myTime, myIter, myThid)       I                      myTime, myIter, myThid)
493    
494        IF (momPressureForcing) THEN        IF (momPressureForcing) THEN
495          CALL CALC_GRAD_PHI_HYD(          CALL CALC_GRAD_PHI_HYD(
496       I                         k, bi, bj, iMin,iMax, jMin,jMax,       I                         k, bi, bj, iMin,iMax, jMin,jMax,
497       I                         phiHydC, alphaRho, tFld, sFld,       I                         phiHydC, alphaRho, tFld, sFld,
498       O                         dPhiHydX, dPhiHydY,       O                         dPhiHydX, dPhiHydY,
499       I                         myTime, myIter, myThid)         I                         myTime, myIter, myThid)
500        ENDIF        ENDIF
501    
502  #endif /* INCLUDE_PHIHYD_CALCULATION_CODE */  #endif /* INCLUDE_PHIHYD_CALCULATION_CODE */

Legend:
Removed from v.1.35  
changed lines
  Added in v.1.36

  ViewVC Help
Powered by ViewVC 1.1.22