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/branches/2019/dev_r11233_AGRIF-05_jchanut_vert_coord_interp/src/NST – NEMO

source: NEMO/branches/2019/dev_r11233_AGRIF-05_jchanut_vert_coord_interp/src/NST/agrif_oce.F90 @ 12152

Last change on this file since 12152 was 12119, checked in by jchanut, 4 years ago

#2222, remove useless mask checking (and restrict scale factor check at the boundary only until nesting tools are updated in sponge areas). Take into account special values in tracer updates, again, till nesting tools are updated.

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