SUBROUTINE mod_arrays (allocate_vars) ! !svn $Id: mod_arrays.F 352 2009-05-29 20:57:39Z arango $ !================================================== Hernan G. Arango === ! Copyright (c) 2002-2009 The ROMS/TOMS Group ! ! Licensed under a MIT/X style license ! ! See License_ROMS.txt ! !======================================================================= ! ! ! This routine routine allocates and initializa model state arrays ! ! for each nested and/or multiple connected grids. ! ! ! !======================================================================= ! USE mod_param USE mod_parallel ! USE mod_boundary, ONLY : allocate_boundary, initialize_boundary USE mod_coupling, ONLY : allocate_coupling, initialize_coupling USE mod_forces, ONLY : allocate_forces, initialize_forces USE mod_grid, ONLY : allocate_grid, initialize_grid USE mod_mixing, ONLY : allocate_mixing, initialize_mixing USE mod_ocean, ONLY : allocate_ocean, initialize_ocean USE mod_sources, ONLY : allocate_sources USE mod_tides, ONLY : allocate_tides, initialize_tides USE mod_bbl, ONLY : allocate_bbl, initialize_bbl ! implicit none ! ! Imported variable declarations ! logical, intent(in) :: allocate_vars ! ! Local variable declarations. ! integer :: ng integer :: LBi, UBi, LBj, UBj, LBij, UBij integer :: tile, subs, thread integer, parameter :: model = 0 ! !----------------------------------------------------------------------- ! Allocate model structures. !----------------------------------------------------------------------- ! IF (allocate_vars) then tile=0 DO ng=1,Ngrids LBi=BOUNDS(ng)%LBi(MyRank) UBi=BOUNDS(ng)%UBi(MyRank) LBj=BOUNDS(ng)%LBj(MyRank) UBj=BOUNDS(ng)%UBj(MyRank) LBij=BOUNDS(ng)%LBij UBij=BOUNDS(ng)%UBij CALL allocate_boundary (ng) CALL allocate_bbl (ng, LBi, UBi, LBj, UBj) CALL allocate_coupling (ng, LBi, UBi, LBj, UBj) CALL allocate_forces (ng, LBi, UBi, LBj, UBj) CALL allocate_grid (ng, LBi, UBi, LBj, UBj, LBij, UBij) CALL allocate_mixing (ng, LBi, UBi, LBj, UBj) CALL allocate_ocean (ng, LBi, UBi, LBj, UBj) CALL allocate_tides (ng, LBi, UBi, LBj, UBj) CALL allocate_sources (ng) END DO END IF ! !----------------------------------------------------------------------- ! Allocate and intialize variables within structures for each grid. !----------------------------------------------------------------------- ! DO thread=0,numthreads-1 DO ng=1,Ngrids subs=NtileX(ng)*NtileE(ng)/numthreads DO tile=subs*thread,subs*(thread+1)-1 CALL initialize_bbl (ng, MyRank) CALL initialize_boundary (ng, MyRank, model) CALL initialize_coupling (ng, MyRank, model) CALL initialize_forces (ng, MyRank, model) CALL initialize_grid (ng, MyRank, model) CALL initialize_mixing (ng, MyRank, model) CALL initialize_ocean (ng, MyRank, model) CALL initialize_tides (ng, MyRank) END DO END DO END DO RETURN END SUBROUTINE mod_arrays