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 @ 11590

Last change on this file since 11590 was 11590, checked in by jchanut, 5 years ago

#2222: 1) create remapping module (vremap) and integration of D. Engwirda piecewise polynomial recontruction package (PPR_LIB cpp key). 2) Various bug corrections with key_vertical activated.

  • Property svn:keywords set to Id
File size: 4.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_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   LOGICAL , PUBLIC ::   ln_chk_bathy  = .FALSE.   !: check of parent bathymetry
27   !
28   INTEGER , PUBLIC, PARAMETER ::   nn_sponge_len = 2  !: Sponge width (in number of parent grid points)
29   LOGICAL , PUBLIC :: spongedoneT = .FALSE.       !: tracer   sponge layer indicator
30   LOGICAL , PUBLIC :: spongedoneU = .FALSE.       !: dynamics sponge layer indicator
31   LOGICAL , PUBLIC :: lk_agrif_fstep = .TRUE.     !: if true: first step
32   LOGICAL , PUBLIC :: lk_agrif_debug = .FALSE.    !: if true: print debugging info
33
34   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: tabspongedone_tsn
35# if defined key_top
36   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: tabspongedone_trn
37# endif
38   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: tabspongedone_u
39   LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: tabspongedone_v
40   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: utint_stage
41   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: vtint_stage
42   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: fsaht_spu, fsaht_spv !: sponge diffusivities
43   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: fsahm_spt, fsahm_spf !: sponge viscosities
44
45   ! Barotropic arrays used to store open boundary data during time-splitting loop:
46   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::  ubdy, vbdy, hbdy
47
48
49   INTEGER, PUBLIC :: tsn_id                                                  ! AGRIF profile for tracers interpolation and update
50   INTEGER, PUBLIC :: un_interp_id, vn_interp_id                              ! AGRIF profiles for interpolations
51   INTEGER, PUBLIC :: un_update_id, vn_update_id                              ! AGRIF profiles for udpates
52   INTEGER, PUBLIC :: tsn_sponge_id, un_sponge_id, vn_sponge_id               ! AGRIF profiles for sponge layers
53# if defined key_top
54   INTEGER, PUBLIC :: trn_id, trn_sponge_id
55# endif 
56   INTEGER, PUBLIC :: unb_id, vnb_id, ub2b_interp_id, vb2b_interp_id
57   INTEGER, PUBLIC :: ub2b_update_id, vb2b_update_id
58   INTEGER, PUBLIC :: e3t_id, e1u_id, e2v_id, sshn_id
59   INTEGER, PUBLIC :: scales_t_id
60   INTEGER, PUBLIC :: avt_id, avm_id, en_id                ! TKE related identificators
61   INTEGER, PUBLIC :: umsk_id, vmsk_id
62   INTEGER, PUBLIC :: kindic_agr
63   
64   !!----------------------------------------------------------------------
65   !! NEMO/NST 4.0 , NEMO Consortium (2018)
66   !! $Id$
67   !! Software governed by the CeCILL license (see ./LICENSE)
68   !!----------------------------------------------------------------------
69CONTAINS
70
71   INTEGER FUNCTION agrif_oce_alloc()
72      !!----------------------------------------------------------------------
73      !!                ***  FUNCTION agrif_oce_alloc  ***
74      !!----------------------------------------------------------------------
75      INTEGER, DIMENSION(2) :: ierr
76      !!----------------------------------------------------------------------
77      ierr(:) = 0
78      !
79      ALLOCATE( fsaht_spu(jpi,jpj), fsaht_spv(jpi,jpj),     &
80         &      fsahm_spt(jpi,jpj), fsahm_spf(jpi,jpj),     &
81         &      tabspongedone_tsn(jpi,jpj),                 &
82         &      utint_stage(jpi,jpj), vtint_stage(jpi,jpj), &
83# if defined key_top         
84         &      tabspongedone_trn(jpi,jpj),           &
85# endif         
86         &      tabspongedone_u  (jpi,jpj),           &
87         &      tabspongedone_v  (jpi,jpj), STAT = ierr(1) )
88
89      ALLOCATE( ubdy(jpi,jpj), vbdy(jpi,jpj), hbdy(jpi,jpj), STAT = ierr(2) )
90
91      agrif_oce_alloc = MAXVAL(ierr)
92      !
93   END FUNCTION agrif_oce_alloc
94
95#endif
96   !!======================================================================
97END MODULE agrif_oce
Note: See TracBrowser for help on using the repository browser.