Fortran: Module Interface rivers (Source File: rivers.F90)

INTERFACE:

    module rivers
DESCRIPTION:

This module includes support for river input. Rivers are treated the same way as meteorology, i.e. as external module to the hydrodynamic model itself. The module follows the same scheme as all other modules, i.e. init_rivers sets up necessary information, and do_rivers updates the relevant variables. do_river is called in getm/integration.F90 between the 2d and 3d routines as it only updates the sea surface elevation (in 2d) and sea surface elevation, and optionally salinity and temperature (in 3d). At present the momentum of the river water is not include, the model however has a direct response to the river water because of the pressure gradient introduced. USES:

    use domain, only: imin,jmin,imax,jmax,ioff,joff
 #if defined(SPHERICAL) || defined(CURVILINEAR)
    use domain, only: H,az,kmax,arcd1
 #else
    use domain, only: H,az,kmax,ard1
 #endif
    use m2d, only: dtm
    use variables_2d, only: z
 #ifndef NO_BAROCLINIC
    use m3d, only: calc_salt,calc_temp
    use variables_3d, only: hn,ssen,T,S
 #endif
 #ifdef GETM_BIO
    use bio, only: bio_calc
    use bio_var, only: numc
    use variables_3d, only: cc3d
 #endif
 #ifdef _FABM_
    use getm_fabm, only: model,fabm_pel
 #endif
    IMPLICIT NONE
    private
PUBLIC DATA MEMBERS:
    public init_rivers, do_rivers, clean_rivers
 #ifdef GETM_BIO
    public init_rivers_bio
 #endif
 #ifdef _FABM_
    public init_rivers_fabm
 #endif
    integer, public                     :: river_method=0,nriver=0,rriver=0
    logical,public                      :: use_river_temp = .false.
    logical,public                      :: use_river_salt = .false.
    character(len=64), public           :: river_data="rivers.nc"
    character(len=64), public, allocatable  :: river_name(:)
    character(len=64), public, allocatable  :: real_river_name(:)
    integer, public, allocatable        :: ok(:)
    REALTYPE, public, allocatable       :: river_flow(:)
    REALTYPE, public, allocatable       :: river_salt(:)
    REALTYPE, public, allocatable       :: river_temp(:)
    integer, public                     :: river_ramp= -1
    REALTYPE, public                    :: river_factor= _ONE_
    REALTYPE, public,parameter          :: temp_missing=-9999.0
    REALTYPE, public,parameter          :: salt_missing=-9999.0
    integer,  public, allocatable       :: river_split(:)
 #ifdef GETM_BIO
    REALTYPE, public, allocatable       :: river_bio(:,:)
    REALTYPE, public, parameter         :: bio_missing=-9999.0
 #endif
 #ifdef _FABM_
    REALTYPE, public, allocatable       :: river_fabm(:,:)
 #endif
   !PRIVATE DATA MEMBERS:
    integer                   :: river_format=2
    character(len=64)         :: river_info="riverinfo.dat"
    integer, allocatable      :: ir(:),jr(:)
    REALTYPE, allocatable     :: rzl(:),rzu(:)
    REALTYPE, allocatable     :: irr(:)
    REALTYPE, allocatable     :: macro_height(:)
    REALTYPE, allocatable     :: flow_fraction(:),flow_fraction_rel(:)
    logical                   :: river_outflow_properties_follow_source_cell=.true.
REVISION HISTORY:
    Original author(s): Karsten Bolding & Hans Burchard



Subsections