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.
Changeset 13463 for NEMO/branches/2019/dev_r11351_fldread_with_XIOS/tests/CANAL/MY_SRC/usrdef_nam.F90 – NEMO

Ignore:
Timestamp:
2020-09-14T17:40:34+02:00 (4 years ago)
Author:
andmirek
Message:

Ticket #2195:update to trunk 13461

Location:
NEMO/branches/2019/dev_r11351_fldread_with_XIOS
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS

    • Property svn:externals
      •  

        old new  
        33^/utils/build/mk@HEAD         mk 
        44^/utils/tools@HEAD            tools 
        5 ^/vendors/AGRIF/dev@HEAD      ext/AGRIF 
         5^/vendors/AGRIF/dev_r12970_AGRIF_CMEMS      ext/AGRIF 
        66^/vendors/FCM@HEAD            ext/FCM 
        77^/vendors/IOIPSL@HEAD         ext/IOIPSL 
         8 
         9# SETTE 
         10^/utils/CI/sette@13382        sette 
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS/tests/CANAL/MY_SRC/usrdef_nam.F90

    r10074 r13463  
    1414   !!   usr_def_hgr   : initialize the horizontal mesh  
    1515   !!---------------------------------------------------------------------- 
    16    USE dom_oce  , ONLY: nimpp , njmpp            ! i- & j-indices of the local domain 
     16   USE dom_oce 
    1717   USE par_oce        ! ocean space and time domain 
    1818   USE phycst         ! physical constants 
     
    5858CONTAINS 
    5959 
    60    SUBROUTINE usr_def_nam( ldtxt, ldnam, cd_cfg, kk_cfg, kpi, kpj, kpk, kperio ) 
     60   SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, kperio ) 
    6161      !!---------------------------------------------------------------------- 
    6262      !!                     ***  ROUTINE dom_nam  *** 
     
    7070      !! ** input   : - namusr_def namelist found in namelist_cfg 
    7171      !!---------------------------------------------------------------------- 
    72       CHARACTER(len=*), DIMENSION(:), INTENT(out) ::   ldtxt, ldnam    ! stored print information 
    7372      CHARACTER(len=*)              , INTENT(out) ::   cd_cfg          ! configuration name 
    7473      INTEGER                       , INTENT(out) ::   kk_cfg          ! configuration resolution 
     
    7675      INTEGER                       , INTENT(out) ::   kperio          ! lateral global domain b.c.  
    7776      ! 
    78       INTEGER ::   ios, ii      ! Local integer 
    79       REAL(wp)::   zh ! Local scalars 
     77      INTEGER ::   ios      ! Local integer 
     78      REAL(wp)::   zh       ! Local scalars 
    8079      !! 
    8180      NAMELIST/namusr_def/  rn_domszx, rn_domszy, rn_domszz, rn_dx, rn_dy, rn_dz, rn_0xratio, rn_0yratio   & 
     
    8584      !!---------------------------------------------------------------------- 
    8685      ! 
    87       ii = 1 
     86      READ  ( numnam_cfg, namusr_def, IOSTAT = ios, ERR = 902 ) 
     87902   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namusr_def in configuration namelist' ) 
    8888      ! 
    89       REWIND( numnam_cfg )          ! Namelist namusr_def (exist in namelist_cfg only) 
    90       READ  ( numnam_cfg, namusr_def, IOSTAT = ios, ERR = 902 ) 
    91 902   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namusr_def in configuration namelist', .TRUE. ) 
     89      IF(lwm)   WRITE( numond, namusr_def ) 
    9290      ! 
    9391#if defined key_agrif  
     
    103101#endif 
    104102      ! 
    105       WRITE( ldnam(:), namusr_def ) 
     103      IF(lwm)   WRITE( numond, namusr_def ) 
    106104      ! 
    107105      cd_cfg = 'EW_CANAL'             ! name & resolution (not used) 
    108106      kk_cfg = INT( rn_dx ) 
    109107      ! 
    110       ! Global Domain size:  EW_CANAL global domain is  1800 km x 1800 Km x 5000 m 
    111       kpi = NINT( rn_domszx / rn_dx ) + 1 
    112       kpj = NINT( rn_domszy / rn_dy ) + 3 
    113       kpk = NINT( rn_domszz / rn_dz ) + 1 
    114 #if defined key_agrif 
    115       IF( .NOT. Agrif_Root() ) THEN 
    116          kpi  = nbcellsx + 2 + 2*nbghostcells 
    117          kpj  = nbcellsy + 2 + 2*nbghostcells 
     108      IF( Agrif_Root() ) THEN        ! Global Domain size:  EW_CANAL global domain is  1800 km x 1800 Km x 5000 m 
     109         kpi = NINT( rn_domszx / rn_dx ) + 1 
     110         kpj = NINT( rn_domszy / rn_dy ) + 3 
     111      ELSE                           ! Global Domain size: add nbghostcells + 1 "land" point on each side 
     112         kpi  = nbcellsx + nbghostcells_x   + nbghostcells_x   + 2 
     113         kpj  = nbcellsy + nbghostcells_y_s + nbghostcells_y_n + 2 
    118114      ENDIF 
    119 #endif 
     115      kpk = MAX( 2, NINT( rn_domszz / rn_dz ) + 1 ) 
    120116      ! 
    121117      zh  = (kpk-1)*rn_dz 
    122       !                             ! control print 
    123       WRITE(ldtxt(ii),*) '   '                                                                          ;   ii = ii + 1 
    124       WRITE(ldtxt(ii),*) 'usr_def_nam  : read the user defined namelist (namusr_def) in namelist_cfg'   ;   ii = ii + 1 
    125       WRITE(ldtxt(ii),*) '~~~~~~~~~~~ '                                                                 ;   ii = ii + 1 
    126       WRITE(ldtxt(ii),*) '   Namelist namusr_def : EW_CANAL test case'                                  ;   ii = ii + 1 
    127       WRITE(ldtxt(ii),*) '      horizontal domain size-x          rn_domszx  = ', rn_domszx, ' km'      ;   ii = ii + 1 
    128       WRITE(ldtxt(ii),*) '      horizontal domain size-y          rn_domszy  = ', rn_domszy, ' km'      ;   ii = ii + 1 
    129       WRITE(ldtxt(ii),*) '      vertical   domain size-z          rn_domszz  = ', rn_domszz, '  m'      ;   ii = ii + 1 
    130       WRITE(ldtxt(ii),*) '      horizontal x-resolution           rn_dx      = ',     rn_dx, ' km'      ;   ii = ii + 1 
    131       WRITE(ldtxt(ii),*) '      horizontal y-resolution           rn_dy      = ',     rn_dy, ' km'      ;   ii = ii + 1 
    132       WRITE(ldtxt(ii),*) '      vertical resolution               rn_dz      = ',     rn_dz, '  m'      ;   ii = ii + 1 
    133       WRITE(ldtxt(ii),*) '      x-domain ratio of the 0           rn_0xratio = ', rn_0xratio            ;   ii = ii + 1 
    134       WRITE(ldtxt(ii),*) '      y-domain ratio of the 0           rn_0yratio = ', rn_0yratio            ;   ii = ii + 1 
    135       WRITE(ldtxt(ii),*) '          H [m] : ', zh                                                       ;   ii = ii + 1 
    136       WRITE(ldtxt(ii),*) '      F computation                     nn_fcase   = ',   nn_fcase            ;   ii = ii + 1 
    137       WRITE(ldtxt(ii),*) '      Reference latitude                rn_ppgphi0 = ', rn_ppgphi0            ;   ii = ii + 1 
    138       WRITE(ldtxt(ii),*) '      10m wind speed                    rn_u10     = ',     rn_u10, ' m/s'    ;   ii = ii + 1 
    139       WRITE(ldtxt(ii),*) '         wind latitudinal extension     rn_windszy = ', rn_windszy, ' km'     ;   ii = ii + 1 
    140       WRITE(ldtxt(ii),*) '         wind longitudinal extension    rn_windszx = ', rn_windszx, ' km'     ;   ii = ii + 1 
    141       WRITE(ldtxt(ii),*) '         Uoce multiplicative factor     rn_uofac   = ',   rn_uofac            ;   ii = ii + 1 
    142       WRITE(ldtxt(ii),*) '      initial Canal max current        rn_vtxmax  = ',  rn_vtxmax, ' m/s'    ;   ii = ii + 1 
    143       WRITE(ldtxt(ii),*) '      initial zonal current             rn_uzonal  = ',  rn_uzonal, ' m/s'    ;   ii = ii + 1 
    144       WRITE(ldtxt(ii),*) '         Jet latitudinal extension      rn_ujetszy = ', rn_ujetszy, ' km'     ;   ii = ii + 1 
    145       WRITE(ldtxt(ii),*) '         Jet longitudinal extension     rn_ujetszx = ', rn_ujetszx, ' km'     ;   ii = ii + 1 
    146       WRITE(ldtxt(ii),*) '      bottom definition (0:flat)        nn_botcase = ', nn_botcase            ;   ii = ii + 1 
    147       WRITE(ldtxt(ii),*) '      initial condition case            nn_initcase= ', nn_initcase           ;   ii = ii + 1 
    148       WRITE(ldtxt(ii),*) '                   (0:rest, 1:zonal current, 10:shear)'                       ;   ii = ii + 1 
    149       WRITE(ldtxt(ii),*) '      add random noise on initial ssh   ln_sshnoise= ', ln_sshnoise           ;   ii = ii + 1 
    150       WRITE(ldtxt(ii),*) '      Gaussian lambda parameter          rn_lambda = ', rn_lambda             ;   ii = ii + 1 
    151       ! 
    152118      !                             ! Set the lateral boundary condition of the global domain 
    153119      kperio = 1                    ! EW_CANAL configuration : closed basin 
    154       ! 
    155       WRITE(ldtxt(ii),*) '   '                                                                          ;   ii = ii + 1 
    156       WRITE(ldtxt(ii),*) '   Lateral boundary condition of the global domain'                           ;   ii = ii + 1 
    157       WRITE(ldtxt(ii),*) '      EW_CANAL : closed basin            jperio = ', kperio                   ;   ii = ii + 1 
     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 : EW_CANAL test case' 
     126         WRITE(numout,*) '      horizontal domain size-x          rn_domszx  = ', rn_domszx, ' km' 
     127         WRITE(numout,*) '      horizontal domain size-y          rn_domszy  = ', rn_domszy, ' km' 
     128         WRITE(numout,*) '      vertical   domain size-z          rn_domszz  = ', rn_domszz, '  m' 
     129         WRITE(numout,*) '      horizontal x-resolution           rn_dx      = ',     rn_dx, ' km' 
     130         WRITE(numout,*) '      horizontal y-resolution           rn_dy      = ',     rn_dy, ' km' 
     131         WRITE(numout,*) '      vertical resolution               rn_dz      = ',     rn_dz, '  m' 
     132         WRITE(numout,*) '      x-domain ratio of the 0           rn_0xratio = ', rn_0xratio 
     133         WRITE(numout,*) '      y-domain ratio of the 0           rn_0yratio = ', rn_0yratio 
     134         WRITE(numout,*) '          H [m] : ', zh 
     135         WRITE(numout,*) '      F computation                     nn_fcase   = ',   nn_fcase 
     136         WRITE(numout,*) '      Reference latitude                rn_ppgphi0 = ', rn_ppgphi0 
     137         WRITE(numout,*) '      10m wind speed                    rn_u10     = ',     rn_u10, ' m/s' 
     138         WRITE(numout,*) '         wind latitudinal extension     rn_windszy = ', rn_windszy, ' km' 
     139         WRITE(numout,*) '         wind longitudinal extension    rn_windszx = ', rn_windszx, ' km' 
     140         WRITE(numout,*) '         Uoce multiplicative factor     rn_uofac   = ',   rn_uofac 
     141         WRITE(numout,*) '      initial Canal max current         rn_vtxmax  = ',  rn_vtxmax, ' m/s' 
     142         WRITE(numout,*) '      initial zonal current             rn_uzonal  = ',  rn_uzonal, ' m/s' 
     143         WRITE(numout,*) '         Jet latitudinal extension      rn_ujetszy = ', rn_ujetszy, ' km' 
     144         WRITE(numout,*) '         Jet longitudinal extension     rn_ujetszx = ', rn_ujetszx, ' km' 
     145         WRITE(numout,*) '      bottom definition (0:flat)        nn_botcase = ', nn_botcase 
     146         WRITE(numout,*) '      initial condition case            nn_initcase= ', nn_initcase 
     147         WRITE(numout,*) '                   (0:rest, 1:zonal current, 10:shear)' 
     148         WRITE(numout,*) '      add random noise on initial ssh   ln_sshnoise= ', ln_sshnoise 
     149         WRITE(numout,*) '      Gaussian lambda parameter          rn_lambda = ', rn_lambda 
     150         WRITE(numout,*) '   ' 
     151         WRITE(numout,*) '   Lateral boundary condition of the global domain' 
     152         WRITE(numout,*) '      EW_CANAL : closed basin               jperio = ', kperio 
     153      ENDIF 
    158154      ! 
    159155   END SUBROUTINE usr_def_nam 
Note: See TracChangeset for help on using the changeset viewer.