MODULE mod_boundary ! !svn $Id: mod_boundary.F 314 2009-02-20 22:06:49Z arango $ !================================================== Hernan G. Arango === ! Copyright (c) 2002-2009 The ROMS/TOMS Group ! ! Licensed under a MIT/X style license ! ! See License_ROMS.txt ! !======================================================================= ! ! ! Open boundary conditions arrays: ! ! ! ! zeta_west Free-surface (m) western boundary conditions. ! ! zeta_east Free-surface (m) eastern boundary conditions. ! ! zeta_south Free-surface (m) southern boundary conditions. ! ! ubar_west 2D u-momentum (m/s) western boundary conditions. ! ! vbar_west 2D v-momentum (m/s) western boundary conditions. ! ! ubar_east 2D u-momentum (m/s) eastern boundary conditions. ! ! vbar_east 2D v-momentum (m/s) eastern boundary conditions. ! ! ubar_south 2D u-momentum (m/s) southern boundary conditions. ! ! vbar_south 2D v-momentum (m/s) southern boundary conditions. ! ! ! !======================================================================= ! USE mod_kinds implicit none TYPE T_BOUNDARY ! ! Nonlinear model state. ! real(r8), pointer :: zeta_west(:) real(r8), pointer :: zeta_east(:) real(r8), pointer :: zeta_south(:) real(r8), pointer :: ubar_west(:) real(r8), pointer :: vbar_west(:) real(r8), pointer :: ubar_east(:) real(r8), pointer :: vbar_east(:) real(r8), pointer :: ubar_south(:) real(r8), pointer :: vbar_south(:) END TYPE T_BOUNDARY TYPE (T_BOUNDARY), allocatable ::BOUNDARY(:) CONTAINS SUBROUTINE allocate_boundary (ng) ! !======================================================================= ! ! ! This routine initializes all variables in the module for all nested ! ! grids. Currently, there is not parallel tiling in boundary arrays. ! ! ! !======================================================================= ! USE mod_param ! ! Imported variable declarations. ! integer, intent(in) :: ng ! !----------------------------------------------------------------------- ! Initialize module variables. !----------------------------------------------------------------------- ! IF (ng.eq.1) allocate ( BOUNDARY(Ngrids) ) ! ! Nonlinear model state. ! allocate ( BOUNDARY(ng) % zeta_west(0:Jm(ng)+1) ) allocate ( BOUNDARY(ng) % zeta_east(0:Jm(ng)+1) ) allocate ( BOUNDARY(ng) % zeta_south(0:Im(ng)+1) ) allocate ( BOUNDARY(ng) % ubar_west(0:Jm(ng)+1) ) allocate ( BOUNDARY(ng) % vbar_west(0:Jm(ng)+1) ) allocate ( BOUNDARY(ng) % ubar_east(0:Jm(ng)+1) ) allocate ( BOUNDARY(ng) % vbar_east(0:Jm(ng)+1) ) allocate ( BOUNDARY(ng) % ubar_south(0:Im(ng)+1) ) allocate ( BOUNDARY(ng) % vbar_south(0:Im(ng)+1) ) RETURN END SUBROUTINE allocate_boundary SUBROUTINE initialize_boundary (ng, tile, model) ! !======================================================================= ! ! ! This routine initialize all variables in the module using first ! ! touch distribution policy. In shared-memory configuration, this ! ! operation actually performs propagation of the "shared arrays" ! ! across the cluster, unless another policy is specified to ! ! override the default. ! ! ! !======================================================================= ! USE mod_param ! ! Imported variable declarations. ! integer, intent(in) :: ng, tile, model ! ! Local variable declarations. ! real(r8), parameter :: IniVal = 0.0_r8 ! !----------------------------------------------------------------------- ! Initialize module variables. !----------------------------------------------------------------------- ! ! Nonlinear model state. ! IF ((model.eq.0).or.(model.eq.iNLM)) THEN IF (.TRUE.) THEN BOUNDARY(ng) % zeta_west = IniVal END IF IF (.TRUE.) THEN BOUNDARY(ng) % zeta_east = IniVal END IF IF (.TRUE.) THEN BOUNDARY(ng) % zeta_south = IniVal END IF IF (.TRUE.) THEN BOUNDARY(ng) % ubar_west = IniVal BOUNDARY(ng) % vbar_west = IniVal END IF IF (.TRUE.) THEN BOUNDARY(ng) % ubar_east = IniVal BOUNDARY(ng) % vbar_east = IniVal END IF IF (.TRUE.) THEN BOUNDARY(ng) % ubar_south = IniVal BOUNDARY(ng) % vbar_south = IniVal END IF END IF RETURN END SUBROUTINE initialize_boundary END MODULE mod_boundary