PUBLIC INTERFACE / ROUTINES / NAMELIST / CHANGES / ERRORS / REFERENCES / NOTES


module mg_drag_mod

     Contact:   Bill Stern
     Reviewers:


OVERVIEW

     MG_DRAG - MOUNTAIN GRAVITY WAVE DRAG - PIerrehumbert (1986)
Calculates partial tendencies for the zonal and meridional winds due to the effect of mountain gravity wave drag.
Given temperature and wind profiles at the model's pressure levels, this module returns tendencies of wind due to orographically induced gravity wave drag.

This parameterization was developed by Pierrehumbert (see reference) and implemented by Bill Stern. This parameterization develops a saturation flux profile which s defined as a limiting amount of momentum flux, above which wave breaking will take place and flux absorption will take place (i.e., wave drag). A key feature of this scheme is that the base momentum flux will obey linear theory for small Froude number (Fr), but for large Fr it attempts to incorporate nonlinear effects which will act to limit the growth of the flux. A second significant distinction in this scheme is the separation of a low-level region (which may involve a strong nonlinear drag enhancement that is not part of this parameterization) from upper atmospheric flux absorption, which is the focus of this scheme.

OTHER MODULES USED

          constants_mod
          utilities_mod
          topography_mod
 
 
 


PUBLIC INTERFACE

use mg_drag_mod [,only: mg_drag_init, mg_drag, mg_drag_end]

mg_drag_init  - Called once to initialize mg_drag - read in subgrid mountains as a restart file. Also reads namelist. Must be called before mg_drag.

mg_drag       - Driver for mountain gravity wave drag module

mg_drag_end  - Writes out subgrid mountains as a restart file..

Notes:
 * A namelist interface ( &mg_drag_nml ) controls runtime options.
 
 


PUBLIC ROUTINES

call mg_drag_init (lonb,latb,hprime)

!--------------------------------------------------------------
! Input Arguments
!     lonb  - longitude in radians of the grid box edges
!     latb  - latitude in radians of the grid box edges
!---------------------------------------------------------------------
 real, intent(in), dimension(:) :: lonb,latb

!---------------------------------------------------------------------
! Optional Output Argument
!    hprime - array of sub-grid scale mountain heights (in meters)
!---------------------------------------------------------------------
 real, intent(out), dimension(:,:), optional :: hprime
!--------------------------------------------------------------
 

  call mg_drag (is,js,delt,uwnd,vwnd,temp,pfull,phalf,   &
                    zfull,zhalf,dtaux,dtauy,dtemp,taub,kbot)

!--------------------------------------------------------------
! Input Arguments
!      IS,JS   - integers containing the starting
!                  i,j indices from the full horizontal grid
!      delt    - time step in seconds (real)
!      UWND     Zonal wind (dimensioned IDIM x JDIM x KDIM)
!      VWND     Meridional wind (dimensioned IDIM x JDIM x KDIM)
!      TEMP     Temperature at full model levels
!                   (dimensioned IDIM x JDIM x KDIM)
!      PFULL    Pressure at full model levels
!                   (dimensioned IDIM x JDIM x KDIM)
!      PHALF    Pressure at half model levels
!                   (dimensioned IDIM x JDIM x KDIM+1)
!      ZHALF    Height at half model levels
!                   (dimensioned IDIM x JDIM x KDIM+1)
!      ZFULL    Height at full model levels
!                   (dimensioned IDIM x JDIM x KDIM+1)
!      KBOT     OPTIONAL;lowest model level index (integer)
!                   (dimensioned IDIM x JDIM)
!--------------------------------------------------------------
 integer, intent(in) :: is,js
 real, intent(in), dimension (:,:,:) ::  uwnd, vwnd, temp, pfull, phalf, zfull, zhalf
 integer, intent(in), OPTIONAL, dimension(:,:)   :: kbot

!---------------------------------------------------------------------
! Output Arguments
!       TAUB    base momentum flux - output for diagnostics
!                   (dimensioned IDIM x JDIM)-kg/m/s**2
!                   = -(RHO*U**3/(N*XL))*G(FR) FOR N**2 > 0
!                   =          0               FOR N**2 <=0
!      DTAUX    Tendency of the zonal wind component deceleration
!                   (dimensioned IDIM x JDIM x KDIM)
!      DTAUY    Tendency of the meridional wind component deceleration
!                   (dimensioned IDIM x JDIM x KDIM)
!      DTEMP    Tendency of the temperature due to the dissipation of momentum
!                  
!---------------------------------------------------------------------
 real, intent(out), dimension (:,:) :: taub
 real, intent(out), dimension (:,:,:) :: dtaux, dtauy
!-----------------------------------------------------------------------
 

call mg_drag_end ()
there are no arguments to this routine


NAMELIST

&mg_drag_nml
  xl_mtn        Effective mountain length ( set currently to 100km)

  acoef         Order unity "tunable" parameter (may have nonlinear impact)

  gmax          Order unity "tunable" parameter  (may be enhanced to increase drag)

  rho           Stand value for density of the air at sea-level (1.13 KG/M**3)

  low_lev_frac  Fraction of atmosphere (from bottom up) considered to be 
                "low-level-layer" for base flux calc. and where no
                wave breaking is allowed.

  do_conserve_energy  If TRUE the heating due to the dissipation of kinetic energy
                      by Rayleigh damping will be computed (default is FALSE).

  source_of_sgsmtn  ='computed': The topography sub-grid scale variance is
                                 computed from the navy 1/6'th degree topography data.
                    =   'input': The topography sub-grid scale variance is read
                                 from a netcdf data file (INPUT/mg_drag.data.nc).
                                 The field name in this file must be "sgsmtn".
                                 A check exists that the resolution the model and data match.
				 A previously generated output file containing "sgsmtn" may
                                 be used, but the result may not reproduce exactly if the
                                 data is not 8 byte.

  do_mcm_mg_drag  If TRUE the gravity wave drag calculation mimics Manabe Climate Model.
                       (default is FALSE).

CHANGE HISTORY



     MPP version created. Minor changes for open_file, error_mesg,
     and Fortran write statements.

ERROR MESSAGES

Fatal error in mg_drag_init:

    No sub-grid orography restart file specified

REFERENCES

Pierrehumbert, R.T., 1986. An essay on the parameterization of orographic gravity wave drag.
                          Published in the Proceedings from ECMWF 1986 Seminar, Vol. I, 251-282.
Stern, W.F., 1987. Parameterization of gravity wave drag - a techinical description.
                          Unpublished, GFDL  Exp. Prediction Group technical document. 10 pp.
 
 
 
 


KNOWN BUGS

     There are no known bugs.


NOTES

   Code developed by Bill Stern & Ray Pierrehumbert
   Original code ~ Summer 1986.
   First Fortran 90 version created by Bill Stern in June 1999.
   

   -------------------------------------------------------------------
   Important Note:

   The subgrid scale topography is now generated automatically
   (using topograpy_mod) when mg_drag_init is called and the navy
   hires-topography file is present.

   Users can still read their own subgrid scale topography from file
   INPUT/mg_drag.res if they remove the navy hires-topography file.

   Refer to module topograpy_mod for details on how the subgrid scale
   topography is computed.

   -------------------------------------------------------------------


 

Code for calculating subgrid-scale mountains was developed by Bruce Wyman. Subgrid-scale mountains are available for a number of resolutions including: N30, N45, T30, T42, T63, R15, R30. Subgrid-scale orography is computed from the Navy 1/6 degree dataset which may be found at: /archive/bw/HiresNavyTape/Zmean The following sample code may be used to create subgrid-scale orography for other resolutions: integer, parameter :: nlon = 2160, nlat = 1080 real, dimension :: data(nlon,nlat) real :: hpie, wb, sb, dlat, dlon ! INPUT: unit = unit number of topography file ! lon = longitude (in radians) of grid box boundaries ! lat = latitude (in radians) of grid box boundaries ! OUTPUT: zsurf = height of topography (in meters) ! stdev = standard deviation of height (m) within grid-box ! ! (zsurf and stdev must be dimensioned size(lon)-1 by size(lat)-1) integer, intent(in) :: unit real, intent(in), dimension(:) :: lon,lat real, intent(out), dimension(:,:) :: zsurf, stdev ! --- input (hires) grid resolution --- hpie = acos(0.0) wb = 0.0; sb = -hpie dlat = 2.0*hpie/float(nlat) dlon = 4.0*hpie/float(nlon) ! --- Read global 10 minute files --- open (unit, file='Zmean', form='unformatted') read (unit) data close (unit) ! --- convert topog from cm to m --- data(:,:)=data(:,:)*0.01 call horiz_interp (data, wb, sb, dlon, dlat, & lon, lat, zsurf) ! --- compute standard deviation of topography --- data(:,:)=data(:,:)*data(:,:) call horiz_interp (data, wb, sb, dlon, dlat, & lon, lat, stdev) stdev = stdev - zsurf*zsurf where (stdev > 0.0) stdev = sqrt ( stdev ) elsewhere stdev = 0.0 endwhere


FUTURE PLANS

     none at this time