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

Last change on this file was 14086, checked in by cetlod, 3 years ago

Adding AGRIF branches into the trunk

  • Property svn:keywords set to Id
File size: 6.9 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   LOGICAL , PUBLIC ::   ln_vert_remap = .FALSE.   !: use vertical remapping
26   REAL(wp), PUBLIC ::   rn_sponge_tra = 0.002     !: sponge coeff. for tracers
27   REAL(wp), PUBLIC ::   rn_sponge_dyn = 0.002     !: sponge coeff. for dynamics
28   REAL(wp), PUBLIC ::   rn_trelax_tra = 0.01      !: time relaxation parameter for tracers
29   REAL(wp), PUBLIC ::   rn_trelax_dyn = 0.01      !: time relaxation parameter for momentum
30   LOGICAL , PUBLIC ::   ln_chk_bathy  = .FALSE.   !: check of parent bathymetry
31   !
32   INTEGER , PUBLIC, PARAMETER ::   nn_sponge_len = 2  !: Sponge width (in number of parent grid points)
33   INTEGER , PUBLIC, PARAMETER ::   nn_shift_bar = 0   !: nb of coarse grid points by which we shift 2d interface
34
35   LOGICAL , PUBLIC :: spongedoneT = .FALSE.       !: tracer   sponge layer indicator
36   LOGICAL , PUBLIC :: spongedoneU = .FALSE.       !: dynamics sponge layer indicator
37   LOGICAL , PUBLIC :: lk_agrif_fstep = .TRUE.     !: if true: first step
38   LOGICAL , PUBLIC :: lk_agrif_debug = .FALSE.    !: if true: print debugging info
39   LOGICAL , PUBLIC :: lk_tint2d_notinterp = .FALSE. !: if true, no time interp
40   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: tabspongedone_tsn
41# if defined key_top
42   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: tabspongedone_trn
43# endif
44   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: tabspongedone_u
45   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: tabspongedone_v
46   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: utint_stage
47   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: vtint_stage
48   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: fspu, fspv !: sponge arrays
49   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: fspt, fspf !:   "      "
50   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: fspu_2d,fspv_2d  !: sponge arrays (2d mode)
51   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: fspt_2d, fspf_2d !:   "       "     "   "
52
53   ! Barotropic arrays used to store open boundary data during time-splitting loop:
54   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::  ubdy, vbdy, hbdy
55   INTEGER , PUBLIC,              SAVE                 ::  Kbb_a, Kmm_a, Krhs_a   !: AGRIF module-specific copies of time-level indices
56
57   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   :: ht0_parent, hu0_parent, hv0_parent
58   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: e3t0_parent, e3u0_parent, e3v0_parent
59   INTEGER,  PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   :: mbkt_parent, mbku_parent, mbkv_parent
60
61
62   INTEGER, PUBLIC :: ts_interp_id, ts_update_id                              ! AGRIF profile for tracers interpolation and update
63   INTEGER, PUBLIC :: un_interp_id, vn_interp_id                              ! AGRIF profiles for interpolations
64   INTEGER, PUBLIC :: un_update_id, vn_update_id                              ! AGRIF profiles for udpates
65   INTEGER, PUBLIC :: ts_sponge_id, un_sponge_id, vn_sponge_id                ! AGRIF profiles for sponge layers (3d)
66   INTEGER, PUBLIC :: unb_sponge_id, vnb_sponge_id                            ! AGRIF profiles for sponge layers (2d)
67   INTEGER, PUBLIC :: tsini_id, uini_id, vini_id, sshini_id                   ! AGRIF profile for initialization
68# if defined key_top
69   INTEGER, PUBLIC :: trn_id, trn_sponge_id
70# endif 
71   INTEGER, PUBLIC :: unb_interp_id, vnb_interp_id, ub2b_interp_id, vb2b_interp_id
72   INTEGER, PUBLIC :: ub2b_update_id, vb2b_update_id, unb_update_id, vnb_update_id
73   INTEGER, PUBLIC :: ub2b_cor_id, vb2b_cor_id
74   INTEGER, PUBLIC :: e3t_id, sshn_id
75   INTEGER, PUBLIC :: scales_t_id
76   INTEGER, PUBLIC :: avt_id, avm_id, en_id                ! TKE related identificators
77   INTEGER, PUBLIC :: mbkt_id, ht0_id, e3t0_interp_id
78   INTEGER, PUBLIC :: glamt_id, gphit_id
79   INTEGER, PUBLIC :: batupd_id
80   INTEGER, PUBLIC :: kindic_agr
81
82   ! North fold
83!$AGRIF_DO_NOT_TREAT
84   LOGICAL, PUBLIC :: use_sign_north
85   REAL, PUBLIC    :: sign_north
86   LOGICAL, PUBLIC :: l_ini_child = .FALSE.
87   LOGICAL, PUBLIC :: l_vremap    = .FALSE.
88!$AGRIF_END_DO_NOT_TREAT
89   
90   !!----------------------------------------------------------------------
91   !! NEMO/NST 4.0 , NEMO Consortium (2018)
92   !! $Id$
93   !! Software governed by the CeCILL license (see ./LICENSE)
94   !!----------------------------------------------------------------------
95CONTAINS
96
97   INTEGER FUNCTION agrif_oce_alloc()
98      !!----------------------------------------------------------------------
99      !!                ***  FUNCTION agrif_oce_alloc  ***
100      !!----------------------------------------------------------------------
101      INTEGER, DIMENSION(2) :: ierr
102      !!----------------------------------------------------------------------
103      ierr(:) = 0
104      !
105      ALLOCATE( fspu(jpi,jpj), fspv(jpi,jpj),          &
106         &      fspt(jpi,jpj), fspf(jpi,jpj),               &
107         &      fspu_2d(jpi,jpj), fspv_2d(jpi,jpj),         &
108         &      fspt_2d(jpi,jpj), fspf_2d(jpi,jpj),         &
109         &      tabspongedone_tsn(jpi,jpj),                 &
110         &      utint_stage(jpi,jpj), vtint_stage(jpi,jpj), &
111# if defined key_top         
112         &      tabspongedone_trn(jpi,jpj),           &
113# endif   
114         &      ht0_parent(jpi,jpj), mbkt_parent(jpi,jpj),  &
115         &      hu0_parent(jpi,jpj), mbku_parent(jpi,jpj),  &
116         &      hv0_parent(jpi,jpj), mbkv_parent(jpi,jpj),  &
117         &      tabspongedone_u  (jpi,jpj),           &
118         &      tabspongedone_v  (jpi,jpj), STAT = ierr(1) )
119
120      ALLOCATE( ubdy(jpi,jpj), vbdy(jpi,jpj), hbdy(jpi,jpj), STAT = ierr(2) )
121
122      agrif_oce_alloc = MAXVAL(ierr)
123      !
124   END FUNCTION agrif_oce_alloc
125#endif
126   !!======================================================================
127END MODULE agrif_oce
Note: See TracBrowser for help on using the repository browser.