Fortran: Module Interface domain - sets up the calculation domain. (Source File: domain.F90)

INTERFACE:

    module domain
DESCRIPTION:

This module provides all variables related to the bathymetry and model grid. The public subroutine $init\_domain()$ is called once and upon successful completion the bathymetry has been read and optionally modified, the calculation masks have been setup and all grid related variables have been initialised.
The $domain$-module depends on another module doing the actual reading of variables from files. This is provided through the generic subroutine $read\_topo\_file$. This subroutine takes two parameters - 1) a fileformat and 2) a filename. Adding a new input file format is thus straight forward and can be done without any changes to $domain$. Public variables defined in this module is used through out the code. USES:

    use exceptions
    use halo_zones,     only: update_2d_halo,wait_halo
    use halo_zones,     only: H_TAG,U_TAG,V_TAG
    IMPLICIT NONE
PUBLIC DATA MEMBERS:
    integer                             :: bathy_format   = NETCDF
 
    integer                             :: grid_type      = 1
    integer                             :: vert_cord      = 1
    integer                             :: il=-1,ih=-1,jl=-1,jh=-1
    global index range
    integer                             :: ilg=-1,ihg=-1,jlg=-1,jhg=-1
    local index range
    integer                             :: ill=-1,ihl=-1,jll=-1,jhl=-1
 
    logical                             :: have_lonlat    = .true.
    logical                             :: have_xy        = .true.
 
    REALTYPE                            :: rearth
 
    REALTYPE                            :: maxdepth       = -1.
    REALTYPE                            :: ddu            = -_ONE_
    REALTYPE                            :: ddl            = -_ONE_
    REALTYPE                            :: d_gamma        = 20.
    logical                             :: gamma_surf     = .true.
    REALTYPE, allocatable, dimension(:) :: ga
 
    integer                             :: NWB=-1,NNB=-1,NEB=-1,NSB=-1,NOB
    integer                             :: calc_points
    logical                             :: openbdy        = .false.
 
    REALTYPE                            :: Hland=-10.0
    REALTYPE                            :: min_depth,crit_depth
 
    REALTYPE                            :: longitude      = _ZERO_
    REALTYPE                            :: latitude       = _ZERO_
    logical                             :: f_plane        = .true.
    logical                             :: check_cfl      = .true.
 
 #ifdef STATIC
 #include "static_domain.h"
 #else
 #include "dynamic_declarations_domain.h"
 #endif
    integer                             :: nsbv
 
    integer                             :: ioff=0,joff=0
    integer, dimension(:), allocatable  :: bdy_2d_type
    integer, dimension(:), allocatable  :: bdy_3d_type
    integer, dimension(:), allocatable  :: wi,wfj,wlj
    integer, dimension(:), allocatable  :: nj,nfi,nli
    integer, dimension(:), allocatable  :: ei,efj,elj
    integer, dimension(:), allocatable  :: sj,sfi,sli
    integer, allocatable                :: bdy_index(:),bdy_map(:,:)
    logical                             :: have_boundaries=.false.
 
    character(len=64)                   :: bdy_2d_desc(5)
    logical                             :: need_2d_bdy_elev = .false.
    logical                             :: need_2d_bdy_u    = .false.
    logical                             :: need_2d_bdy_v    = .false.
 
    REALTYPE                            :: cori= _ZERO_
 
    method for specifying bottom roughness (0=const, 1=from topo.nc)
    integer                             :: z0_method=0
    REALTYPE                            :: z0_const=0.01d0
DEFINED PARAMETERS:
    integer,           parameter        :: INNER          = 1
    REALTYPE, private, parameter        :: pi             = 3.141592654
    REALTYPE, private, parameter        :: deg2rad        = pi/180.
    REALTYPE, private, parameter        :: omega          = 2.*pi/86164.
REVISION HISTORY:
    Original author(s): Karsten Bolding & Hans Burchard
LOCAL VARIABLES:
    REALTYPE, parameter                  :: rearth_default = 6378815.



Subsections