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.
usrdef_nam.F90 in NEMO/branches/2020/dev_14237_KERNEL-01_IMMERSE_SEAMOUNT/tests/SEAMOUNT/MY_SRC – NEMO

source: NEMO/branches/2020/dev_14237_KERNEL-01_IMMERSE_SEAMOUNT/tests/SEAMOUNT/MY_SRC/usrdef_nam.F90 @ 14683

Last change on this file since 14683 was 14683, checked in by ayoung, 3 years ago

Compatibility changes for periodic bc and north fold in usr def nam. See tickets #2480 and #2651.

File size: 6.7 KB
Line 
1MODULE usrdef_nam
2   !!======================================================================
3   !!                     ***  MODULE usrdef_nam   ***
4   !!
5   !!                   ===  SEAMOUNT configuration  ===
6   !!
7   !! User defined : set the domain characteristics of a user configuration
8   !!======================================================================
9   !! History :  4.0  ! 2016-03  (S. Flavoni, G. Madec)  Original code
10   !!----------------------------------------------------------------------
11
12   !!----------------------------------------------------------------------
13   !!   usr_def_nam   : read user defined namelist and set global domain size
14   !!   usr_def_hgr   : initialize the horizontal mesh
15   !!----------------------------------------------------------------------
16   USE dom_oce
17   USE par_oce        ! ocean space and time domain
18   USE phycst         ! physical constants
19   !
20   USE in_out_manager ! I/O manager
21   USE lib_mpp        ! MPP library
22   USE timing         ! Timing
23
24   IMPLICIT NONE
25   PRIVATE
26
27   PUBLIC   usr_def_nam   ! called in nemogcm.F90 module
28
29   !                              !!* namusr_def namelist *!!
30   REAL(wp), PUBLIC ::   rn_dx     ! resolution in meters defining the horizontal domain size
31   REAL(wp), PUBLIC ::   rn_dz     ! resolution in meters defining the vertical   domain size
32   REAL(wp), PUBLIC ::   rn_length
33   REAL(wp), PUBLIC ::   rn_width
34   REAL(wp), PUBLIC ::   rn_drho     ! resolution in meters defining the horizontal domain size
35   REAL(wp), PUBLIC ::   rn_initrho
36   REAL(wp), PUBLIC ::   rn_s
37   REAL(wp), PUBLIC ::   rn_bathy
38   REAL(wp), PUBLIC ::   rn_seamountheight
39   REAL(wp), PUBLIC ::   rn_l
40   REAL(wp), PUBLIC ::   rn_f
41   LOGICAL,  PUBLIC ::   ln_exp_init
42   LOGICAL,  PUBLIC ::   ln_linear_init
43
44   !!----------------------------------------------------------------------
45   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
46   !! $Id: usrdef_nam.F90 14072 2020-12-04 07:48:38Z laurent $
47   !! Software governed by the CeCILL license (see ./LICENSE)
48   !!----------------------------------------------------------------------
49CONTAINS
50
51   SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, ldIperio, ldJperio, ldNFold, cdNFtype )
52      !!----------------------------------------------------------------------
53      !!                     ***  ROUTINE dom_nam  ***
54      !!
55      !! ** Purpose :   read user defined namelist and define the domain size
56      !!
57      !! ** Method  :   read in namusr_def containing all the user specific namelist parameter
58      !!
59      !!                Here SEAMOUNT configuration defined as per Beckmann
60      !!                and Haidvogel (1993) with uniformly spaced sigma coordinates
61      !!
62      !! ** input   : - namusr_def namelist found in namelist_cfg
63      !!----------------------------------------------------------------------
64      CHARACTER(len=*), INTENT(out) ::   cd_cfg               ! configuration name
65      INTEGER         , INTENT(out) ::   kk_cfg               ! configuration resolution
66      INTEGER         , INTENT(out) ::   kpi, kpj, kpk        ! global domain sizes
67      LOGICAL         , INTENT(out) ::   ldIperio, ldJperio   ! i- and j- periodicity
68      LOGICAL         , INTENT(out) ::   ldNFold              ! North pole folding
69      CHARACTER(len=1), INTENT(out) ::   cdNFtype             ! Folding type: T or F
70
71      !
72      INTEGER ::   ios   ! Local integer
73      !!
74      NAMELIST/namusr_def/ ln_zco, ln_zps, ln_sco, rn_length, rn_width, rn_dx, rn_dz, rn_initrho, rn_s, rn_bathy, rn_seamountheight, rn_l, rn_f, ln_exp_init, ln_linear_init
75      !!----------------------------------------------------------------------
76      !
77      READ  ( numnam_cfg, namusr_def, IOSTAT = ios, ERR = 902 )
78902   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namusr_def in configuration namelist' )
79      !
80      IF(lwm)   WRITE( numond, namusr_def )
81      !
82      !
83      cd_cfg = 'Seamount'      ! name & resolution (not used)
84      kk_cfg = 0
85
86      !                             ! Set the lateral boundary condition of the global domain
87      ldIperio = .TRUE.    ;   ldJperio = .true.   ! C1D configuration : 3x3 basin with cyclic Est-West and Norht-South condition
88      ldNFold  = .FALSE.   ;   cdNFtype = '-'
89
90      !
91      ! Global Domain size:  SEAMOUNT_TEST_CASE domain is rn_length km x rn_width km x rn_bathy m
92      kpi = INT(  1000._wp * rn_length / rn_dx ) + 1
93      kpj = INT(  1000._wp * rn_width / rn_dx ) + 2
94      kpk = INT(  rn_bathy  / rn_dz ) + 1
95      ! Calculating the density difference from the given Burger Number in the namelist_cfg
96      ! rn_drho =  rho_ref * depth * (S * f * L)^2 / g
97      rn_drho = 1000._wp * rn_bathy * ( rn_s * rn_f * rn_l / rn_bathy ) ** 2._wp / grav
98      !
99      !                             ! SEAMOUNT_TEST_CASE configuration : closed domain
100      !                             ! control print
101      IF(lwp) THEN
102         WRITE(numout,*) '   '                                                                         
103         WRITE(numout,*) 'usr_def_nam  : read the user defined namelist (namusr_def) in namelist_cfg'   
104         WRITE(numout,*) '~~~~~~~~~~~ '                                                                 
105         WRITE(numout,*) '   Namelist namusr_def : SEAMOUNT_TEST_CASE test case'                       
106         WRITE(numout,*) '      horizontal resolution                    rn_dx   =  ', rn_dx, ' meters' 
107         WRITE(numout,*) '      vertical   resolution                    rn_dz   =  ', rn_dz, ' meters' 
108         WRITE(numout,*) '      SEAMOUNT_TEST_CASE domain'                                             
109         WRITE(numout,*) '         resulting global domain size :        jpiglo  =  ', kpi             
110         WRITE(numout,*) '                                               jpjglo  =  ', kpj             
111         WRITE(numout,*) '                                               jpkglo  =  ', kpk             
112         WRITE(numout,*) '   For Burger Number S = ', rn_s,            ' rn_drho =  ', rn_drho         
113         WRITE(numout,*) '   '                                                                         
114         WRITE(numout,*) '   Lateral boundary condition of the global domain'                           
115         WRITE(numout,*) '      east-west                                   ldIperio = ', ldIperio     
116         WRITE(numout,*) '      north-south                                 ldJperio = ', ldJperio   
117         WRITE(numout,*) '   Initial condition:                          ln_exp_init =    ', ln_exp_init
118         WRITE(numout,*) '                                               ln_linear_init = ', ln_linear_init
119      ENDIF
120      !
121   END SUBROUTINE usr_def_nam
122
123   !!======================================================================
124END MODULE usrdef_nam
Note: See TracBrowser for help on using the repository browser.