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/2020/dev_r12973_AGRIF_CMEMS/src/NST – NEMO

source: NEMO/branches/2020/dev_r12973_AGRIF_CMEMS/src/NST/agrif_oce.F90 @ 13147

Last change on this file since 13147 was 13141, checked in by jchanut, 4 years ago

#2129, corrections/add ons to initial state interpolation with AGRIF
1) add namelist flag for child grid initial state interpolation - ice not considered yet
2) provide depths and not thicknesses as inputs to vertical linear interpolation
3) extend initial state interpolation to a restart scenario for parent grid (warning should be added in that case in order to prevent users doing this at each model restart...)
The online interpolation seems to work fine in the VORTEX case (provided 0. is not considered as a special value in the initial velocity field, i.e. ln_spc_dyn=F)

  • Property svn:keywords set to Id
File size: 6.1 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_init_chfrpar = .FALSE. !: set child grids initial state from parent
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
25   REAL(wp), PUBLIC ::   rn_sponge_tra = 2800.     !: sponge coeff. for tracers
26   REAL(wp), PUBLIC ::   rn_sponge_dyn = 2800.     !: sponge coeff. for dynamics
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
29   LOGICAL , PUBLIC ::   ln_chk_bathy  = .FALSE.   !: check of parent bathymetry
30   !
31   INTEGER , PUBLIC, PARAMETER ::   nn_sponge_len = 2  !: Sponge width (in number of parent grid points)
32   LOGICAL , PUBLIC ::   ln_bry_south  = .TRUE. !: Is the South boundary open ?
33
34   LOGICAL , PUBLIC :: spongedoneT = .FALSE.       !: tracer   sponge layer indicator
35   LOGICAL , PUBLIC :: spongedoneU = .FALSE.       !: dynamics sponge layer indicator
36   LOGICAL , PUBLIC :: lk_agrif_fstep = .TRUE.     !: if true: first step
37   LOGICAL , PUBLIC :: lk_agrif_debug = .FALSE.    !: if true: print debugging info
38
39   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: tabspongedone_tsn
40# if defined key_top
41   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: tabspongedone_trn
42# endif
43   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: tabspongedone_u
44   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: tabspongedone_v
45   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: utint_stage
46   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: vtint_stage
47   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: fspu, fspv !: sponge arrays
48   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: fspt, fspf !:   "      "
49
50   ! Barotropic arrays used to store open boundary data during time-splitting loop:
51   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::  ubdy, vbdy, hbdy
52   INTEGER , PUBLIC,              SAVE                 ::  Kbb_a, Kmm_a, Krhs_a   !: AGRIF module-specific copies of time-level indices
53
54   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: ht0_parent, hu0_parent, hv0_parent
55   INTEGER,  PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: mbkt_parent, mbku_parent, mbkv_parent
56
57   INTEGER, PUBLIC :: tsn_id                                                  ! AGRIF profile for tracers interpolation and update
58   INTEGER, PUBLIC :: un_interp_id, vn_interp_id                              ! AGRIF profiles for interpolations
59   INTEGER, PUBLIC :: un_update_id, vn_update_id                              ! AGRIF profiles for udpates
60   INTEGER, PUBLIC :: tsn_sponge_id, un_sponge_id, vn_sponge_id               ! AGRIF profiles for sponge layers
61   INTEGER, PUBLIC :: tsini_id, uini_id, vini_id, sshini_id                   ! AGRIF profile for initialization
62# if defined key_top
63   INTEGER, PUBLIC :: trn_id, trn_sponge_id
64# endif 
65   INTEGER, PUBLIC :: unb_id, vnb_id, ub2b_interp_id, vb2b_interp_id
66   INTEGER, PUBLIC :: ub2b_update_id, vb2b_update_id
67   INTEGER, PUBLIC :: e3t_id, e1u_id, e2v_id, sshn_id
68   INTEGER, PUBLIC :: scales_t_id
69   INTEGER, PUBLIC :: avt_id, avm_id, en_id                ! TKE related identificators
70   INTEGER, PUBLIC :: mbkt_id, ht0_id
71   INTEGER, PUBLIC :: kindic_agr
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
84   
85   !!----------------------------------------------------------------------
86   !! NEMO/NST 4.0 , NEMO Consortium (2018)
87   !! $Id$
88   !! Software governed by the CeCILL license (see ./LICENSE)
89   !!----------------------------------------------------------------------
90CONTAINS
91
92   INTEGER FUNCTION agrif_oce_alloc()
93      !!----------------------------------------------------------------------
94      !!                ***  FUNCTION agrif_oce_alloc  ***
95      !!----------------------------------------------------------------------
96      INTEGER, DIMENSION(2) :: ierr
97      !!----------------------------------------------------------------------
98      ierr(:) = 0
99      !
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), &
104# if defined key_top         
105         &      tabspongedone_trn(jpi,jpj),           &
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),  &
110         &      tabspongedone_u  (jpi,jpj),           &
111         &      tabspongedone_v  (jpi,jpj), STAT = ierr(1) )
112
113      ALLOCATE( ubdy(jpi,jpj), vbdy(jpi,jpj), hbdy(jpi,jpj), STAT = ierr(2) )
114
115      agrif_oce_alloc = MAXVAL(ierr)
116      !
117   END FUNCTION agrif_oce_alloc
118
119#endif
120   !!======================================================================
121END MODULE agrif_oce
Note: See TracBrowser for help on using the repository browser.