New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
agrif_oce.F90 in NEMO/trunk/src/NST – NEMO

source: NEMO/trunk/src/NST/agrif_oce.F90 @ 13286

Last change on this file since 13286 was 13286, checked in by smasson, 4 years ago

trunk: merge extra halos branch in trunk, see #2366

  • Property svn:keywords set to Id
File size: 6.1 KB
RevLine 
[782]1MODULE agrif_oce
[1605]2   !!======================================================================
[782]3   !!                       ***  MODULE agrif_oce  ***
[1605]4   !! AGRIF :   define in memory AGRIF variables
[782]5   !!----------------------------------------------------------------------
[1605]6   !! History :  2.0  ! 2007-12  (R. Benshila)  Original code
[782]7   !!----------------------------------------------------------------------
[1605]8#if defined key_agrif
[782]9   !!----------------------------------------------------------------------
[1605]10   !!   'key_agrif'                                              AGRIF zoom
11   !!----------------------------------------------------------------------
[782]12   USE par_oce      ! ocean parameters
13   USE dom_oce      ! domain parameters
[5656]14
[782]15   IMPLICIT NONE
[2715]16   PRIVATE
[782]17
[2715]18   PUBLIC agrif_oce_alloc ! routine called by nemo_init in nemogcm.F90
[12377]19 
[1605]20   !                                              !!* Namelist namagrif: AGRIF parameters
[13216]21   LOGICAL , PUBLIC ::   ln_init_chfrpar = .FALSE. !: set child grids initial state from parent
[12377]22   LOGICAL , PUBLIC ::   ln_agrif_2way = .TRUE.    !: activate two way nesting
23   LOGICAL , PUBLIC ::   ln_spc_dyn    = .FALSE.   !: use zeros (.false.) or not (.true.) in
24                                                   !: bdys dynamical fields interpolation
[5656]25   REAL(wp), PUBLIC ::   rn_sponge_tra = 2800.     !: sponge coeff. for tracers
26   REAL(wp), PUBLIC ::   rn_sponge_dyn = 2800.     !: sponge coeff. for dynamics
[12377]27   REAL(wp), PUBLIC ::   rn_trelax_tra = 0.01      !: time relaxation parameter for tracers
28   REAL(wp), PUBLIC ::   rn_trelax_dyn = 0.01      !: time relaxation parameter for momentum
[5656]29   LOGICAL , PUBLIC ::   ln_chk_bathy  = .FALSE.   !: check of parent bathymetry
[12377]30   !
31   INTEGER , PUBLIC, PARAMETER ::   nn_sponge_len = 2  !: Sponge width (in number of parent grid points)
[13216]32
[5656]33   LOGICAL , PUBLIC :: spongedoneT = .FALSE.       !: tracer   sponge layer indicator
34   LOGICAL , PUBLIC :: spongedoneU = .FALSE.       !: dynamics sponge layer indicator
35   LOGICAL , PUBLIC :: lk_agrif_fstep = .TRUE.     !: if true: first step
36   LOGICAL , PUBLIC :: lk_agrif_debug = .FALSE.    !: if true: print debugging info
[1605]37
[5656]38   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: tabspongedone_tsn
39# if defined key_top
40   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: tabspongedone_trn
41# endif
42   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: tabspongedone_u
43   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: tabspongedone_v
[12377]44   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: utint_stage
45   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: vtint_stage
46   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: fspu, fspv !: sponge arrays
47   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: fspt, fspf !:   "      "
[2715]48
[9019]49   ! Barotropic arrays used to store open boundary data during time-splitting loop:
[12377]50   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::  ubdy, vbdy, hbdy
51   INTEGER , PUBLIC,              SAVE                 ::  Kbb_a, Kmm_a, Krhs_a   !: AGRIF module-specific copies of time-level indices
[5656]52
[12377]53   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: ht0_parent, hu0_parent, hv0_parent
54   INTEGER,  PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: mbkt_parent, mbku_parent, mbkv_parent
[9019]55
56   INTEGER, PUBLIC :: tsn_id                                                  ! AGRIF profile for tracers interpolation and update
57   INTEGER, PUBLIC :: un_interp_id, vn_interp_id                              ! AGRIF profiles for interpolations
58   INTEGER, PUBLIC :: un_update_id, vn_update_id                              ! AGRIF profiles for udpates
59   INTEGER, PUBLIC :: tsn_sponge_id, un_sponge_id, vn_sponge_id               ! AGRIF profiles for sponge layers
[13216]60   INTEGER, PUBLIC :: tsini_id, uini_id, vini_id, sshini_id                   ! AGRIF profile for initialization
[5656]61# if defined key_top
[9019]62   INTEGER, PUBLIC :: trn_id, trn_sponge_id
[5656]63# endif 
[9019]64   INTEGER, PUBLIC :: unb_id, vnb_id, ub2b_interp_id, vb2b_interp_id
65   INTEGER, PUBLIC :: ub2b_update_id, vb2b_update_id
66   INTEGER, PUBLIC :: e3t_id, e1u_id, e2v_id, sshn_id
67   INTEGER, PUBLIC :: scales_t_id
68   INTEGER, PUBLIC :: avt_id, avm_id, en_id                ! TKE related identificators
[12377]69   INTEGER, PUBLIC :: mbkt_id, ht0_id
[13286]70   INTEGER, PUBLIC :: glamt_id, gphit_id
[9019]71   INTEGER, PUBLIC :: kindic_agr
[13216]72
73   ! North fold
74!$AGRIF_DO_NOT_TREAT
75   LOGICAL, PUBLIC :: use_sign_north
76   REAL, PUBLIC :: sign_north
77   LOGICAL, PUBLIC :: l_ini_child = .FALSE.
78# if defined key_vertical
79   LOGICAL, PUBLIC :: l_vremap    = .TRUE.
80# else
81   LOGICAL, PUBLIC :: l_vremap    = .FALSE.
82# endif
83!$AGRIF_END_DO_NOT_TREAT
[9019]84   
[1605]85   !!----------------------------------------------------------------------
[9598]86   !! NEMO/NST 4.0 , NEMO Consortium (2018)
[1605]87   !! $Id$
[10068]88   !! Software governed by the CeCILL license (see ./LICENSE)
[2715]89   !!----------------------------------------------------------------------
90CONTAINS
91
92   INTEGER FUNCTION agrif_oce_alloc()
93      !!----------------------------------------------------------------------
94      !!                ***  FUNCTION agrif_oce_alloc  ***
95      !!----------------------------------------------------------------------
[5656]96      INTEGER, DIMENSION(2) :: ierr
97      !!----------------------------------------------------------------------
98      ierr(:) = 0
99      !
[12377]100      ALLOCATE( fspu(jpi,jpj), fspv(jpi,jpj),          &
101         &      fspt(jpi,jpj), fspf(jpi,jpj),               &
102         &      tabspongedone_tsn(jpi,jpj),                 &
103         &      utint_stage(jpi,jpj), vtint_stage(jpi,jpj), &
[5656]104# if defined key_top         
105         &      tabspongedone_trn(jpi,jpj),           &
[12377]106# endif   
107         &      ht0_parent(jpi,jpj), mbkt_parent(jpi,jpj),  &
108         &      hu0_parent(jpi,jpj), mbku_parent(jpi,jpj),  &
109         &      hv0_parent(jpi,jpj), mbkv_parent(jpi,jpj),  &
[5656]110         &      tabspongedone_u  (jpi,jpj),           &
111         &      tabspongedone_v  (jpi,jpj), STAT = ierr(1) )
112
[12377]113      ALLOCATE( ubdy(jpi,jpj), vbdy(jpi,jpj), hbdy(jpi,jpj), STAT = ierr(2) )
[5656]114
115      agrif_oce_alloc = MAXVAL(ierr)
116      !
[2715]117   END FUNCTION agrif_oce_alloc
118
119#endif
[1605]120   !!======================================================================
[782]121END MODULE agrif_oce
Note: See TracBrowser for help on using the repository browser.