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/trunk/tests/SWG/MY_SRC – NEMO

source: NEMO/trunk/tests/SWG/MY_SRC/usrdef_nam.F90 @ 14433

Last change on this file since 14433 was 14433, checked in by smasson, 3 years ago

trunk: merge dev_r14312_MPI_Interface into the trunk, #2598

File size: 8.0 KB
Line 
1MODULE usrdef_nam
2   !!======================================================================
3   !!                     ***  MODULE usrdef_nam   ***
4   !!
5   !!                     ===  SWG 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   !!             -   ! 2020-03  (A. Nasser) Shallow Water Eq. configuration
11   !!----------------------------------------------------------------------
12
13   !!----------------------------------------------------------------------
14   !!   usr_def_nam   : read user defined namelist and set global domain size
15   !!   usr_def_hgr   : initialize the horizontal mesh
16   !!----------------------------------------------------------------------
17   USE dom_oce  , ONLY: nimpp, njmpp       ! ocean space and time domain
18   USE par_oce        ! ocean space and time domain
19   USE phycst         ! physical constants
20   !
21   USE in_out_manager ! I/O manager
22   USE lib_mpp        ! MPP library
23   
24   IMPLICIT NONE
25   PRIVATE
26
27   PUBLIC   usr_def_nam   ! called in nemogcm.F90 module
28   !                              !!* namusr_def namelist *!!
29   INTEGER , PUBLIC ::   nn_SWG             ! 1/nn_SWG = the resolution chosen in degrees and thus defining the horizontal domain size
30   REAL(wp), PUBLIC ::   rn_theta           ! rotation angle (in degree) of the grid
31   INTEGER , PUBLIC ::   nn_gc              ! number of ghostcells
32   REAL(wp), PUBLIC ::   rn_domsiz          ! size of the domain (default 2000km)  [m]
33   REAL(wp), PUBLIC ::   rn_dx              ! gridspacing (default 100km)          [m]
34   REAL(wp), PUBLIC ::   rn_tau             ! wind stress on the surface           [N/m2]
35   REAL(wp), PUBLIC ::   rn_f0              !    f-plan coriolis parameter         [1/s]
36   REAL(wp), PUBLIC ::   rn_beta            ! beta-plan coriolis parameter         [1/m.s]
37   REAL(wp), PUBLIC ::   rn_modified_grav   ! modified gravity                     [m/s2]
38   REAL(wp), PUBLIC ::   rn_rfr             ! layer friction                       [1/s]
39   !                              !!* temporary *!!
40   INTEGER , PUBLIC ::   nn_dynldf_lap_typ            ! choose type of laplacian (ideally from namelist)
41   !                                                  ! = 1   divrot    laplacian
42   !                                                  ! = 2   symmetric laplacian (Griffies&Hallberg 2000)
43   !                                                  ! = 3   symmetric laplacian (cartesian)
44   LOGICAL , PUBLIC ::   ln_dynldf_lap_PM             ! if True - apply the P.Marchand boundary condition on the laplacian
45   !                              !!* penalisation *!!
46   REAL(wp), PUBLIC ::   rn_abp             ! alpha boundary parameter                                       [-]
47   INTEGER , PUBLIC ::   nn_cnp             ! number of cell on which is smoothed the porosity (phi)         [-]
48   REAL(wp), PUBLIC ::   rn_fsp             ! friction parameter 1/epsilon of the permeability               [1/s]
49   !
50   REAL(wp), PUBLIC ::   r1_abp             ! inverse alpha boundary parameter                            [-]
51   !
52   !!----------------------------------------------------------------------
53   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
54   !! $Id: usrdef_nam.F90 11536 2019-09-11 13:54:18Z smasson $
55   !! Software governed by the CeCILL license (see ./LICENSE)
56   !!----------------------------------------------------------------------
57CONTAINS
58
59   SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, ldIperio, ldJperio, ldNFold, cdNFtype )
60      !!----------------------------------------------------------------------
61      !!                     ***  ROUTINE dom_nam  ***
62      !!                   
63      !! ** Purpose :   read user defined namelist and define the domain size
64      !!
65      !! ** Method  :   read in namusr_def containing all the user specific namelist parameter
66      !!
67      !!                Here SWG configuration
68      !!
69      !! ** input   : - namusr_def namelist found in namelist_cfg
70      !!----------------------------------------------------------------------
71      CHARACTER(len=*), INTENT(out) ::   cd_cfg               ! configuration name
72      INTEGER         , INTENT(out) ::   kk_cfg               ! configuration resolution
73      INTEGER         , INTENT(out) ::   kpi, kpj, kpk        ! global domain sizes
74      LOGICAL         , INTENT(out) ::   ldIperio, ldJperio   ! i- and j- periodicity
75      LOGICAL         , INTENT(out) ::   ldNFold              ! North pole folding
76      CHARACTER(len=1), INTENT(out) ::   cdNFtype             ! Folding type: T or F
77      !
78      INTEGER  ::   ios             ! Local integer
79      REAL(wp) ::   ze1, zgl, zbl   ! gridspacing, length of the biggest square
80      !!
81      NAMELIST/namusr_def/ nn_SWG, rn_theta, jpkglo,            &   !
82         &                 nn_gc ,rn_domsiz, rn_dx,             &   ! domain parameters
83         &                 rn_f0 ,rn_beta,                      &   ! coriolis parameter
84         &                 rn_modified_grav, rn_rfr , rn_tau,   &   ! reduced gravity, friction, wind
85         &                 nn_dynldf_lap_typ, ln_dynldf_lap_PM, &   ! temporary parameter
86         &                 rn_abp, nn_cnp, rn_fsp                   ! penalisation parameters
87      !!----------------------------------------------------------------------
88      !
89      READ  ( numnam_cfg, namusr_def, IOSTAT = ios, ERR = 902 )
90902   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namusr_def in configuration namelist' )
91      !
92      IF(lwm)   WRITE( numond, namusr_def )
93      !
94      cd_cfg = 'SWG'               ! name & resolution (not used)
95     
96#if defined key_agrif
97      IF (.NOT.Agrif_root()) nn_SWG = Agrif_parent(nn_SWG) * Agrif_irhox()
98#endif
99
100      kk_cfg = nn_SWG
101       !
102      ze1 =  rn_dx / REAL(nn_SWG, wp)                    ! [m] gridspacing used
103      zgl =  rn_domsiz + 2._wp * REAL(nn_gc, wp) * ze1   ! [m] length of the square with ghostcells
104      ! rotation
105      zbl = zgl * ( COS( rn_theta * rad ) + SIN( rn_theta * rad ) )   ! length side bigger domain [m] 
106      !
107      kpi = ceiling(zbl / ze1 )    ! Global Domain size + ghost cells               
108      kpj = ceiling(zbl / ze1 )    ! Global Domain size + ghost cells             
109      !
110      IF( rn_modified_grav /= 0._wp) grav = rn_modified_grav   ! update the gravity
111      !
112      kpk = jpkglo
113      !                             ! Set the lateral boundary condition of the global domain
114      ldIperio = .FALSE.   ;   ldJperio = .FALSE.   ! SWG configuration : closed domain
115      ldNFold  = .FALSE.   ;   cdNFtype = '-'
116      !
117# if defined key_bvp
118      r1_abp = 1._wp / rn_abp
119#endif
120      !                             ! control print
121      IF(lwp) THEN
122         WRITE(numout,*) '   '
123         WRITE(numout,*) 'usr_def_nam  : read the user defined namelist (namusr_def) in namelist_cfg'
124         WRITE(numout,*) '~~~~~~~~~~~ '
125         WRITE(numout,*) '   Namelist namusr_def : SWG case'
126         WRITE(numout,*) '                                   domain size       rn_domsiz   = ', rn_domsiz, 'm'
127         WRITE(numout,*) '                                   gridspacing           rn_dx   = ', rn_dx, 'm'
128         WRITE(numout,*) '      inverse resolution & implied domain size          nn_SWG   = ', nn_SWG
129         WRITE(numout,*) '                           implied gridspacing           rn_dx   = ', rn_dx, 'm'
130         WRITE(numout,*) '                          number of ghostcells           nn_gc   = ', nn_gc
131         WRITE(numout,*) '   '
132         WRITE(numout,*) '                    rotation angle chosen             rn_theta   = ', rn_theta, 'deg'
133         WRITE(numout,*) '                    modified gravity          rn_modified_grav   = ', rn_modified_grav, 'm2/s'
134         WRITE(numout,*) '      number of model levels                              jpkglo = ', kpk
135         WRITE(numout,*) '   '
136      ENDIF
137      !
138   END SUBROUTINE usr_def_nam
139
140   !!======================================================================
141END MODULE usrdef_nam
Note: See TracBrowser for help on using the repository browser.