MODULE usrdef_nam !!====================================================================== !! *** MODULE usrdef_nam *** !! !! === WAD_TEST_CASES configuration === !! !! User defined : set the domain characteristics of a user configuration !!====================================================================== !! History : 4.0 ! 2016-03 (S. Flavoni, G. Madec) Original code !!---------------------------------------------------------------------- !!---------------------------------------------------------------------- !! usr_def_nam : read user defined namelist and set global domain size !! usr_def_hgr : initialize the horizontal mesh !!---------------------------------------------------------------------- USE dom_oce , ONLY: nimpp , njmpp ! i- & j-indices of the local domain USE dom_oce , ONLY: ln_zco, ln_zps, ln_sco ! flag of type of coordinate USE par_oce ! ocean space and time domain USE phycst ! physical constants ! USE in_out_manager ! I/O manager USE lib_mpp ! MPP library USE timing ! Timing IMPLICIT NONE PRIVATE PUBLIC usr_def_nam ! called by nemogcm.F90 ! !!* namusr_def namelist *!! REAL(wp), PUBLIC :: rn_dx ! resolution in meters defining the horizontal domain size REAL(wp), PUBLIC :: rn_dz ! resolution in meters defining the vertical domain size REAL(wp), PUBLIC :: rn_length REAL(wp), PUBLIC :: rn_width REAL(wp), PUBLIC :: rn_drho ! resolution in meters defining the horizontal domain size REAL(wp), PUBLIC :: rn_initrho REAL(wp), PUBLIC :: rn_s REAL(wp), PUBLIC :: rn_bathy REAL(wp), PUBLIC :: rn_seamountheight REAL(wp), PUBLIC :: rn_l REAL(wp), PUBLIC :: rn_f !!---------------------------------------------------------------------- !! NEMO/OCE 4.0 , NEMO Consortium (2018) !! $Id: usrdef_nam.F90 10074 2018-08-28 16:15:49Z nicolasmartin $ !! Software governed by the CeCILL license (see ./LICENSE) !!---------------------------------------------------------------------- CONTAINS SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, kperio ) !!---------------------------------------------------------------------- !! *** ROUTINE dom_nam *** !! !! ** Purpose : read user defined namelist and define the domain size !! !! ** Method : read in namusr_def containing all the user specific namelist parameter !! !! Here WAD_TEST_CASES configuration !! !! ** input : - namusr_def namelist found in namelist_cfg !!---------------------------------------------------------------------- CHARACTER(len=*) , INTENT(out) :: cd_cfg ! configuration name INTEGER , INTENT(out) :: kk_cfg ! configuration resolution INTEGER , INTENT(out) :: kpi, kpj, kpk ! global domain sizes INTEGER , INTENT(out) :: kperio ! lateral global domain b.c. ! INTEGER :: ios ! Local integer !! 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 !!---------------------------------------------------------------------- ! REWIND( numnam_cfg ) ! Namelist namusr_def (exist in namelist_cfg only) READ ( numnam_cfg, namusr_def, IOSTAT = ios, ERR = 902 ) 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namusr_def in configuration namelist' ) ! IF(lwm) WRITE( numond, namusr_def ) ! ! cd_cfg = 'Seamount' ! name & resolution (not used) ! ! Global Domain size: SEAMOUNT_TEST_CASE domain is rn_length km x rn_width km x rn_bathy m kpi = INT( 1000._wp * rn_length / rn_dx ) + 1 kpj = INT( 1000._wp * rn_width / rn_dx ) + 2 kpk = INT( rn_bathy / rn_dz ) + 1 ! Calculating the density difference from the given Burger Number in the namelist_cfg ! rn_drho = rho_ref * depth * (S * f * L)^2 / g rn_drho = 1000._wp * rn_bathy * ( rn_s * rn_f * rn_l / rn_bathy ) ** 2._wp / grav ! ! ! control print IF(lwp) THEN WRITE(numout,*) ' ' WRITE(numout,*) 'usr_def_nam : read the user defined namelist (namusr_def) in namelist_cfg' WRITE(numout,*) '~~~~~~~~~~~ ' WRITE(numout,*) ' Namelist namusr_def : SEAMOUNT_TEST_CASE test case' WRITE(numout,*) ' horizontal resolution rn_dx = ', rn_dx, ' meters' WRITE(numout,*) ' vertical resolution rn_dz = ', rn_dz, ' meters' WRITE(numout,*) ' SEAMOUNT_TEST_CASE domain' WRITE(numout,*) ' resulting global domain size : jpiglo = ', kpi WRITE(numout,*) ' jpjglo = ', kpj WRITE(numout,*) ' jpkglo = ', kpk WRITE(numout,*) ' For Burger Number S = ', rn_s, ' rn_drho = ', rn_drho ! ! Set the lateral boundary condition of the global domain kperio = 1 ! SEAMOUNT_TEST_CASE configuration : closed domain ! WRITE(numout,*) ' ' WRITE(numout,*) ' Lateral boundary condition of the global domain' WRITE(numout,*) ' closed jperio = ', kperio ENDIF ! END SUBROUTINE usr_def_nam !!====================================================================== END MODULE usrdef_nam