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 branches/2017/dev_merge_2017/NEMOGCM/NEMO/NST_SRC – NEMO

source: branches/2017/dev_merge_2017/NEMOGCM/NEMO/NST_SRC/agrif_oce.F90 @ 9019

Last change on this file since 9019 was 9019, checked in by timgraham, 6 years ago

Merge of dev_CNRS_2017 into branch

  • Property svn:keywords set to Id
File size: 5.5 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
19
[1605]20   !                                              !!* Namelist namagrif: AGRIF parameters
[5656]21   LOGICAL , PUBLIC ::   ln_spc_dyn    = .FALSE.   !:
22   INTEGER , PUBLIC ::   nn_cln_update = 3         !: update frequency
23   INTEGER , PUBLIC, PARAMETER ::   nn_sponge_len = 2  !: Sponge width (in number of parent grid points)
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
[782]27
[1605]28   !                                              !!! OLD namelist names
[3680]29   INTEGER , PUBLIC ::   nbcline = 0               !: update counter
[1605]30   INTEGER , PUBLIC ::   nbclineupdate             !: update frequency
31   REAL(wp), PUBLIC ::   visc_tra                  !: sponge coeff. for tracers
32   REAL(wp), PUBLIC ::   visc_dyn                  !: sponge coeff. for dynamics
[782]33
[5656]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_doupd = .TRUE.     !: if true: send update from current grid
38   LOGICAL , PUBLIC :: lk_agrif_debug = .FALSE.    !: if true: print debugging info
[1605]39
[5656]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
[9019]46   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: fsaht_spu, fsaht_spv !: sponge diffusivities
47   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: fsahm_spt, fsahm_spf !: sponge viscosities
[2715]48
[9019]49   ! Barotropic arrays used to store open boundary data during time-splitting loop:
50   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::  ubdy_w, vbdy_w, hbdy_w
51   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::  ubdy_e, vbdy_e, hbdy_e
52   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::  ubdy_n, vbdy_n, hbdy_n
53   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::  ubdy_s, vbdy_s, hbdy_s
[5656]54
[9019]55
56   INTEGER, PUBLIC :: tsn_id                                                  ! AGRIF profile for tracers interpolation and update
57   INTEGER, PUBLIC :: un_interp_id, vn_interp_id                              ! AGRIF profiles for interpolations
58   INTEGER, PUBLIC :: un_update_id, vn_update_id                              ! AGRIF profiles for udpates
59   INTEGER, PUBLIC :: tsn_sponge_id, un_sponge_id, vn_sponge_id               ! AGRIF profiles for sponge layers
[5656]60# if defined key_top
[9019]61   INTEGER, PUBLIC :: trn_id, trn_sponge_id
[5656]62# endif 
[9019]63   INTEGER, PUBLIC :: unb_id, vnb_id, ub2b_interp_id, vb2b_interp_id
64   INTEGER, PUBLIC :: ub2b_update_id, vb2b_update_id
65   INTEGER, PUBLIC :: e3t_id, e1u_id, e2v_id, sshn_id
66   INTEGER, PUBLIC :: scales_t_id
67   INTEGER, PUBLIC :: avt_id, avm_id, en_id                ! TKE related identificators
68   INTEGER, PUBLIC :: umsk_id, vmsk_id
69   INTEGER, PUBLIC :: kindic_agr
70   
[1605]71   !!----------------------------------------------------------------------
[9019]72   !! NEMO/NST 4.0 , NEMO Consortium (2017)
[1605]73   !! $Id$
[2715]74   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
75   !!----------------------------------------------------------------------
76CONTAINS
77
78   INTEGER FUNCTION agrif_oce_alloc()
79      !!----------------------------------------------------------------------
80      !!                ***  FUNCTION agrif_oce_alloc  ***
81      !!----------------------------------------------------------------------
[5656]82      INTEGER, DIMENSION(2) :: ierr
83      !!----------------------------------------------------------------------
84      ierr(:) = 0
85      !
86      ALLOCATE( fsaht_spu(jpi,jpj), fsaht_spv(jpi,jpj),   &
87         &      fsahm_spt(jpi,jpj), fsahm_spf(jpi,jpj),   &
88         &      tabspongedone_tsn(jpi,jpj),           &
89# if defined key_top         
90         &      tabspongedone_trn(jpi,jpj),           &
91# endif         
92         &      tabspongedone_u  (jpi,jpj),           &
93         &      tabspongedone_v  (jpi,jpj), STAT = ierr(1) )
94
95      ALLOCATE( ubdy_w(jpj), vbdy_w(jpj), hbdy_w(jpj),   &
96         &      ubdy_e(jpj), vbdy_e(jpj), hbdy_e(jpj),   & 
97         &      ubdy_n(jpi), vbdy_n(jpi), hbdy_n(jpi),   & 
98         &      ubdy_s(jpi), vbdy_s(jpi), hbdy_s(jpi), STAT = ierr(2) )
99
100      agrif_oce_alloc = MAXVAL(ierr)
101      !
[2715]102   END FUNCTION agrif_oce_alloc
103
104#endif
[1605]105   !!======================================================================
[782]106END MODULE agrif_oce
Note: See TracBrowser for help on using the repository browser.