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

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

first Shallow Water Eq. update

File size: 6.2 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   REAL(wp), PUBLIC ::   rn_tau             ! wind stress on the surface    [N/m2]
31   REAL(wp), PUBLIC ::   rn_f0              !    f-plan coriolis parameter  [1/s]
32   REAL(wp), PUBLIC ::   rn_beta            ! beta-plan coriolis parameter  [1/m.s]
33   REAL(wp), PUBLIC ::   rn_modified_grav   ! modified gravity              [m/s2]
34   REAL(wp), PUBLIC ::   rn_rfr             ! layer friction                [1/s]
35   !
36   !!----------------------------------------------------------------------
37   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
38   !! $Id: usrdef_nam.F90 11536 2019-09-11 13:54:18Z smasson $
39   !! Software governed by the CeCILL license (see ./LICENSE)
40   !!----------------------------------------------------------------------
41CONTAINS
42
43   SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, kperio )
44      !!----------------------------------------------------------------------
45      !!                     ***  ROUTINE dom_nam  ***
46      !!                   
47      !! ** Purpose :   read user defined namelist and define the domain size
48      !!
49      !! ** Method  :   read in namusr_def containing all the user specific namelist parameter
50      !!
51      !!                Here AM98 configuration
52      !!
53      !! ** input   : - namusr_def namelist found in namelist_cfg
54      !!----------------------------------------------------------------------
55      CHARACTER(len=*), INTENT(out) ::   cd_cfg          ! configuration name
56      INTEGER         , INTENT(out) ::   kk_cfg          ! configuration resolution
57      INTEGER         , INTENT(out) ::   kpi, kpj, kpk   ! global domain sizes
58      INTEGER         , INTENT(out) ::   kperio          ! lateral global domain b.c.
59      !
60      INTEGER  ::   ios             ! Local integer
61      REAL(wp) ::   ze1, zgl, zbl   ! gridspacing, length of the biggest square
62      !!
63      NAMELIST/namusr_def/ nn_AM98, rn_theta, jpkglo, rn_tau,   &   !
64         &                 rn_f0 ,rn_beta,                      &   ! coriolis parameter
65         &                 rn_modified_grav, rn_rfr                 !
66      !!----------------------------------------------------------------------
67      !
68      READ  ( numnam_cfg, namusr_def, IOSTAT = ios, ERR = 902 )
69902   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namusr_def in configuration namelist' )
70      !
71      IF(lwm)   WRITE( numond, namusr_def )
72      !
73      cd_cfg = 'AM98'               ! name & resolution (not used)
74     
75#if defined key_agrif
76      IF (.NOT.Agrif_root()) nn_AM98 = Agrif_parent(nn_AM98) * Agrif_irhox()
77#endif
78
79      kk_cfg = nn_AM98
80     
81      ! square domain of 2000km x 2000km with dx = dy = 100km
82      ! kpi = 20 * nn_AM98 + 2        ! Global Domain size
83      ! kpj = 20 * nn_AM98 + 2
84     
85      ! Number of cells
86      ! lenght of the biggest square + 2 ghost cells on each side
87      ze1 =  100000._wp / REAL(nn_AM98, wp)       ! (100km) gridspacing [m]
88      zgl = 2000000._wp + 4._wp*ze1               ! length side square + ghostcells [m]
89      !zbl = zgl / COS( rn_theta * rad )           ! length side bigger domain [m] 
90      zbl = zgl * ( COS( rn_theta * rad ) + SIN( rn_theta * rad ) )   ! length side bigger domain [m] 
91       
92      kpi = ceiling(zbl / ze1 )    ! Global Domain size + ghost cells               
93      kpj = ceiling(zbl / ze1 )    ! Global Domain size + ghost cells             
94
95!!an
96!#if defined key_agrif
97!      IF( .NOT. Agrif_Root() ) THEN
98!         kpi  = nbcellsx + 2 + 2*nbghostcells
99!         kpj  = nbcellsy + 2 + 2*nbghostcells
100!      ENDIF
101!#endif
102!!an
103      !
104      IF( rn_modified_grav /= 0._wp) grav = rn_modified_grav   ! update the gravity
105      !
106      kpk = jpkglo
107      !                             ! Set the lateral boundary condition of the global domain
108      kperio = 0                    ! AM98 configuration : closed domain
109      !
110      !                             ! control print
111      IF(lwp) THEN
112         WRITE(numout,*) '   '
113         WRITE(numout,*) 'usr_def_nam  : read the user defined namelist (namusr_def) in namelist_cfg'
114         WRITE(numout,*) '~~~~~~~~~~~ '
115         WRITE(numout,*) '   Namelist namusr_def : AM98 case'
116         WRITE(numout,*) '      inverse resolution & implied domain size         nn_AM98   = ', nn_AM98
117#if defined key_agrif
118         IF( Agrif_Root() ) THEN
119#endif
120         WRITE(numout,*) '         jpiglo = Nx*nn_AM98+4                            jpiglo = ', kpi
121         WRITE(numout,*) '         jpjglo = Ny*nn_AM98+4                            jpjglo = ', kpj
122#if defined key_agrif
123         ENDIF
124#endif
125         WRITE(numout,*) '      number of model levels                              jpkglo = ', kpk
126         WRITE(numout,*) '   '
127         WRITE(numout,*) '   Lateral b.c. of the global domain set to closed        jperio = ', kperio
128      ENDIF
129      !
130   END SUBROUTINE usr_def_nam
131
132   !!======================================================================
133END MODULE usrdef_nam
Note: See TracBrowser for help on using the repository browser.