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

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

#2222: correct definition of parent vertical grid on the child domain to perform vertical interpolation at boundaries. Use additionnal parent depths and number of levels arrays interpolated on the child grid domain to do so.
Correction of vertical interpolation of viscosity remains to be done as well as duplication of changes for passive tracers.

  • Property svn:keywords set to Id
File size: 5.4 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
[11590]19 
[1605]20   !                                              !!* Namelist namagrif: AGRIF parameters
[11574]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
[5656]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
[11574]27   !
28   INTEGER , PUBLIC, PARAMETER ::   nn_sponge_len = 2  !: Sponge width (in number of parent grid points)
[5656]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
[1605]33
[5656]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
[11574]40   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: utint_stage
41   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: vtint_stage
[9019]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
[2715]44
[9019]45   ! Barotropic arrays used to store open boundary data during time-splitting loop:
[11574]46   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::  ubdy, vbdy, hbdy
[5656]47
[11741]48# if defined key_vertical
49   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: ht0_parent, hu0_parent, hv0_parent
50   INTEGER,  PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: mbkt_parent, mbku_parent, mbkv_parent
51# endif
[9019]52
53   INTEGER, PUBLIC :: tsn_id                                                  ! AGRIF profile for tracers interpolation and update
54   INTEGER, PUBLIC :: un_interp_id, vn_interp_id                              ! AGRIF profiles for interpolations
55   INTEGER, PUBLIC :: un_update_id, vn_update_id                              ! AGRIF profiles for udpates
56   INTEGER, PUBLIC :: tsn_sponge_id, un_sponge_id, vn_sponge_id               ! AGRIF profiles for sponge layers
[5656]57# if defined key_top
[9019]58   INTEGER, PUBLIC :: trn_id, trn_sponge_id
[5656]59# endif 
[9019]60   INTEGER, PUBLIC :: unb_id, vnb_id, ub2b_interp_id, vb2b_interp_id
61   INTEGER, PUBLIC :: ub2b_update_id, vb2b_update_id
62   INTEGER, PUBLIC :: e3t_id, e1u_id, e2v_id, sshn_id
63   INTEGER, PUBLIC :: scales_t_id
64   INTEGER, PUBLIC :: avt_id, avm_id, en_id                ! TKE related identificators
65   INTEGER, PUBLIC :: umsk_id, vmsk_id
[11741]66   INTEGER, PUBLIC :: mbkt_id, ht0_id
[9019]67   INTEGER, PUBLIC :: kindic_agr
68   
[1605]69   !!----------------------------------------------------------------------
[9598]70   !! NEMO/NST 4.0 , NEMO Consortium (2018)
[1605]71   !! $Id$
[10068]72   !! Software governed by the CeCILL license (see ./LICENSE)
[2715]73   !!----------------------------------------------------------------------
74CONTAINS
75
76   INTEGER FUNCTION agrif_oce_alloc()
77      !!----------------------------------------------------------------------
78      !!                ***  FUNCTION agrif_oce_alloc  ***
79      !!----------------------------------------------------------------------
[5656]80      INTEGER, DIMENSION(2) :: ierr
81      !!----------------------------------------------------------------------
82      ierr(:) = 0
83      !
[11574]84      ALLOCATE( fsaht_spu(jpi,jpj), fsaht_spv(jpi,jpj),     &
85         &      fsahm_spt(jpi,jpj), fsahm_spf(jpi,jpj),     &
86         &      tabspongedone_tsn(jpi,jpj),                 &
87         &      utint_stage(jpi,jpj), vtint_stage(jpi,jpj), &
[5656]88# if defined key_top         
89         &      tabspongedone_trn(jpi,jpj),           &
[11741]90# endif   
91# if defined key_vertical
92         &      ht0_parent(jpi,jpj), mbkt_parent(jpi,jpj),  &
93         &      hu0_parent(jpi,jpj), mbku_parent(jpi,jpj),  &
94         &      hv0_parent(jpi,jpj), mbkv_parent(jpi,jpj),  &
95# endif     
[5656]96         &      tabspongedone_u  (jpi,jpj),           &
97         &      tabspongedone_v  (jpi,jpj), STAT = ierr(1) )
98
[11574]99      ALLOCATE( ubdy(jpi,jpj), vbdy(jpi,jpj), hbdy(jpi,jpj), STAT = ierr(2) )
[5656]100
101      agrif_oce_alloc = MAXVAL(ierr)
102      !
[2715]103   END FUNCTION agrif_oce_alloc
104
105#endif
[1605]106   !!======================================================================
[782]107END MODULE agrif_oce
Note: See TracBrowser for help on using the repository browser.