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_r12527_Gurvan_ShallowWater/cfgs/AM98/MY_SRC – NEMO

source: NEMO/branches/2020/dev_r12527_Gurvan_ShallowWater/cfgs/AM98/MY_SRC/usrdef_nam.F90 @ 13005

Last change on this file since 13005 was 13005, checked in by gm, 4 years ago

ADE and more options to AM98 config

File size: 7.7 KB
Line 
1MODULE usrdef_nam
2   !!======================================================================
3   !!                     ***  MODULE usrdef_nam   ***
4   !!
5   !!                     ===  AM98 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  , ONLY: nimpp, njmpp       ! ocean space and time domain
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   
23   IMPLICIT NONE
24   PRIVATE
25
26   PUBLIC   usr_def_nam   ! called in nemogcm.F90 module
27   !                              !!* namusr_def namelist *!!
28   INTEGER , PUBLIC ::   nn_AM98            ! 1/nn_AM98 = the resolution chosen in degrees and thus defining the horizontal domain size
29   REAL(wp), PUBLIC ::   rn_theta           ! rotation angle (in degree) of the grid
30   INTEGER , PUBLIC ::   nn_gc              ! number of ghostcells
31   REAL(wp), PUBLIC ::   rn_domsiz          ! size of the domain (default 2000km)  [m]
32   REAL(wp), PUBLIC ::   rn_dx              ! gridspacing (default 100km)          [m]
33   REAL(wp), PUBLIC ::   rn_tau             ! wind stress on the surface           [N/m2]
34   REAL(wp), PUBLIC ::   rn_f0              !    f-plan coriolis parameter         [1/s]
35   REAL(wp), PUBLIC ::   rn_beta            ! beta-plan coriolis parameter         [1/m.s]
36   REAL(wp), PUBLIC ::   rn_modified_grav   ! modified gravity                     [m/s2]
37   REAL(wp), PUBLIC ::   rn_rfr             ! layer friction                       [1/s]
38   !                              !!* temporary *!!
39   INTEGER , PUBLIC ::   nn_dynldf_lap_typ            ! choose type of laplacian (ideally from namelist)
40   !                                                  ! = 1   divrot    laplacian
41   !                                                  ! = 2   symmetric laplacian (Griffies&Hallberg 2000)
42   !                                                  ! = 3   symmetric laplacian (cartesian)
43   LOGICAL , PUBLIC ::   ln_dynldf_lap_PM             ! if True - apply the P.Marchand boundary condition on the laplacian
44   !
45   !!----------------------------------------------------------------------
46   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
47   !! $Id: usrdef_nam.F90 11536 2019-09-11 13:54:18Z smasson $
48   !! Software governed by the CeCILL license (see ./LICENSE)
49   !!----------------------------------------------------------------------
50CONTAINS
51
52   SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, kperio )
53      !!----------------------------------------------------------------------
54      !!                     ***  ROUTINE dom_nam  ***
55      !!                   
56      !! ** Purpose :   read user defined namelist and define the domain size
57      !!
58      !! ** Method  :   read in namusr_def containing all the user specific namelist parameter
59      !!
60      !!                Here AM98 configuration
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      INTEGER         , INTENT(out) ::   kperio          ! lateral global domain b.c.
68      !
69      INTEGER  ::   ios             ! Local integer
70      REAL(wp) ::   ze1, zgl, zbl   ! gridspacing, length of the biggest square
71      !!
72      NAMELIST/namusr_def/ nn_AM98, rn_theta, jpkglo,           &   !
73         &                 nn_gc ,rn_domsiz, rn_dx,             &   ! domain parameters
74         &                 rn_f0 ,rn_beta,                      &   ! coriolis parameter
75         &                 rn_modified_grav, rn_rfr , rn_tau,   &   ! reduced gravity, friction, wind
76         &                 nn_dynldf_lap_typ, ln_dynldf_lap_PM      ! temporary parameter
77      !!----------------------------------------------------------------------
78      !
79      READ  ( numnam_cfg, namusr_def, IOSTAT = ios, ERR = 902 )
80902   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namusr_def in configuration namelist' )
81      !
82      IF(lwm)   WRITE( numond, namusr_def )
83      !
84      cd_cfg = 'AM98'               ! name & resolution (not used)
85     
86#if defined key_agrif
87      IF (.NOT.Agrif_root()) nn_AM98 = Agrif_parent(nn_AM98) * Agrif_irhox()
88#endif
89
90      kk_cfg = nn_AM98
91       !
92      ze1 =  rn_dx / REAL(nn_AM98, wp)                   ! [m] gridspacing used
93      zgl =  rn_domsiz + 2._wp * REAL(nn_gc, wp) * ze1   ! [m] length of the square with ghostcells
94      ! rotation
95      zbl = zgl * ( COS( rn_theta * rad ) + SIN( rn_theta * rad ) )   ! length side bigger domain [m] 
96      !
97      kpi = ceiling(zbl / ze1 )    ! Global Domain size + ghost cells               
98      kpj = ceiling(zbl / ze1 )    ! Global Domain size + ghost cells             
99
100!!an
101!#if defined key_agrif
102!      IF( .NOT. Agrif_Root() ) THEN
103!         kpi  = nbcellsx + 2 + 2*nbghostcells
104!         kpj  = nbcellsy + 2 + 2*nbghostcells
105!      ENDIF
106!#endif
107!!an
108      !
109      IF( rn_modified_grav /= 0._wp) grav = rn_modified_grav   ! update the gravity
110      !
111      !        !== Temporary namelist parameter ==!
112      !
113      ! ll_dynldf_lap_PM = ln_dynldf_lap_PM
114      !
115      kpk = jpkglo
116      !                             ! Set the lateral boundary condition of the global domain
117      kperio = 0                    ! AM98 configuration : closed domain
118      !
119      !                             ! control print
120      IF(lwp) THEN
121         WRITE(numout,*) '   '
122         WRITE(numout,*) 'usr_def_nam  : read the user defined namelist (namusr_def) in namelist_cfg'
123         WRITE(numout,*) '~~~~~~~~~~~ '
124         WRITE(numout,*) '   Namelist namusr_def : AM98 case'
125         WRITE(numout,*) '                                   domain size       rn_domsiz   = ', rn_domsiz, 'm'
126         WRITE(numout,*) '                                   gridspacing           rn_dx   = ', rn_dx, 'm'
127         WRITE(numout,*) '      inverse resolution & implied domain size         nn_AM98   = ', nn_AM98
128         WRITE(numout,*) '                           implied gridspacing           rn_dx   = ', rn_dx, 'm'
129         WRITE(numout,*) '                          number of ghostcells           nn_gc   = ', nn_gc
130         WRITE(numout,*) '   '
131         WRITE(numout,*) '                    rotation angle chosen             rn_theta   = ', rn_theta, 'deg'
132         WRITE(numout,*) '                    modified gravity          rn_modified_grav   = ', rn_modified_grav, 'm2/s'
133#if defined key_agrif
134         IF( Agrif_Root() ) THEN
135#endif
136         WRITE(numout,*) '         jpiglo = Nx*nn_AM98 + 2*n_ghost                    jpiglo = ', kpi
137         WRITE(numout,*) '         jpjglo = Nx*nn_AM98 + 2*n_ghost                    jpjglo = ', kpj
138#if defined key_agrif
139         ENDIF
140#endif
141         WRITE(numout,*) '      number of model levels                              jpkglo = ', kpk
142         WRITE(numout,*) '   '
143         WRITE(numout,*) '   Lateral b.c. of the global domain set to closed        jperio = ', kperio
144      ENDIF
145      !
146   END SUBROUTINE usr_def_nam
147
148   !!======================================================================
149END MODULE usrdef_nam
Note: See TracBrowser for help on using the repository browser.