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/ICE_AGRIF/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/ICE_AGRIF/MY_SRC/usrdef_nam.F90

    r10516 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 
     
    4040CONTAINS 
    4141 
    42    SUBROUTINE usr_def_nam( ldtxt, ldnam, cd_cfg, kk_cfg, kpi, kpj, kpk, kperio ) 
     42   SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, kperio ) 
    4343      !!---------------------------------------------------------------------- 
    4444      !!                     ***  ROUTINE dom_nam  *** 
     
    5252      !! ** input   : - namusr_def namelist found in namelist_cfg 
    5353      !!---------------------------------------------------------------------- 
    54       CHARACTER(len=*), DIMENSION(:), INTENT(out) ::   ldtxt, ldnam    ! stored print information 
    5554      CHARACTER(len=*)              , INTENT(out) ::   cd_cfg          ! configuration name 
    5655      INTEGER                       , INTENT(out) ::   kk_cfg          ! configuration resolution 
     
    5857      INTEGER                       , INTENT(out) ::   kperio          ! lateral global domain b.c.  
    5958      ! 
    60       INTEGER ::   ios, ii   ! Local integer 
     59      INTEGER ::   ios       ! Local integer 
    6160      REAL(wp)::   zlx, zly  ! Local scalars 
    6261      !! 
     
    6463      !!---------------------------------------------------------------------- 
    6564      ! 
    66       ii = 1 
     65      READ  ( numnam_cfg, namusr_def, IOSTAT = ios, ERR = 902 ) 
     66902   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namusr_def in configuration namelist' ) 
    6767      ! 
    68       REWIND( numnam_cfg )          ! Namelist namusr_def (exist in namelist_cfg only) 
    69       READ  ( numnam_cfg, namusr_def, IOSTAT = ios, ERR = 902 ) 
    70 902   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namusr_def in configuration namelist', .TRUE. ) 
     68      IF(lwm)   WRITE( numond, namusr_def ) 
    7169      ! 
    7270#if defined key_agrif  
     
    7977#endif 
    8078      ! 
    81       WRITE( ldnam(:), namusr_def ) 
     79      IF(lwm)   WRITE( numond, namusr_def ) 
    8280      ! 
    8381      cd_cfg = 'ICE_AGRIF'           ! name & resolution (not used) 
    84       kk_cfg = INT( rn_dx ) 
     82      kk_cfg = NINT( rn_dx ) 
    8583      ! 
    86       ! Global Domain size:  ICE_AGRIF domain is  300 km x 300 Km x 10 m 
    87       kpi = INT( 300.e3 / rn_dx ) -1 
    88       kpj = INT( 300.e3 / rn_dy ) -1 
    89 #if defined key_agrif 
    90       IF( .NOT. Agrif_Root() ) THEN 
    91          kpi = nbcellsx + 2 + 2*nbghostcells 
    92          kpj = nbcellsy + 2 + 2*nbghostcells 
     84      IF( Agrif_Root() ) THEN        ! Global Domain size:  ICE_AGRIF domain is  300 km x 300 Km x 10 m 
     85         kpi = NINT( 300.e3 / rn_dx ) - 1 
     86         kpj = NINT( 300.e3 / rn_dy ) - 1 
     87         kpi = kpi - 2   ! for compatibility with old version (because kerio=7) --> to be removed 
     88         kpj = kpj - 2   ! for compatibility with old version (because kerio=7) --> to be removed 
     89      ELSE                           ! Global Domain size: add nbghostcells + 1 "land" point on each side 
     90         kpi  = nbcellsx + 2 * ( nbghostcells + 1 ) 
     91         kpj  = nbcellsy + 2 * ( nbghostcells + 1 ) 
     92!!$         kpi  = nbcellsx + nbghostcells_x   + nbghostcells_x   + 2 
     93!!$         kpj  = nbcellsy + nbghostcells_y_s + nbghostcells_y_n + 2 
    9394      ENDIF 
    94 #endif 
    95       kpk = 1 
     95      kpk = 2 
    9696      ! 
    9797!!      zlx = (kpi-2)*rn_dx*1.e-3 
     
    9999      zlx = kpi*rn_dx*1.e-3 
    100100      zly = kpj*rn_dy*1.e-3 
     101      ! 
     102      IF( Agrif_Root() ) THEN   ;   kperio = 7     ! ICE_AGRIF configuration : bi-periodic basin 
     103      ELSE                      ;   kperio = 0     ! closed periodicity for the zoom 
     104      ENDIF 
    101105      !                             ! control print 
    102       WRITE(ldtxt(ii),*) '   '                                                                          ;   ii = ii + 1 
    103       WRITE(ldtxt(ii),*) 'usr_def_nam  : read the user defined namelist (namusr_def) in namelist_cfg'   ;   ii = ii + 1 
    104       WRITE(ldtxt(ii),*) '~~~~~~~~~~~ '                                                                 ;   ii = ii + 1 
    105       WRITE(ldtxt(ii),*) '   Namelist namusr_def : ICE_AGRIF test case'                                 ;   ii = ii + 1 
    106       WRITE(ldtxt(ii),*) '      horizontal resolution                    rn_dx  = ', rn_dx, ' meters'   ;   ii = ii + 1 
    107       WRITE(ldtxt(ii),*) '      horizontal resolution                    rn_dy  = ', rn_dy, ' meters'   ;   ii = ii + 1 
    108       WRITE(ldtxt(ii),*) '      ICE_AGRIF domain = 300 km x 300Km x 1 grid-point '                      ;   ii = ii + 1 
    109       WRITE(ldtxt(ii),*) '         LX [km]: ', zlx                                                      ;   ii = ii + 1 
    110       WRITE(ldtxt(ii),*) '         LY [km]: ', zly                                                      ;   ii = ii + 1 
    111       WRITE(ldtxt(ii),*) '         resulting global domain size :        jpiglo = ', kpi                ;   ii = ii + 1 
    112       WRITE(ldtxt(ii),*) '                                               jpjglo = ', kpj                ;   ii = ii + 1 
    113       WRITE(ldtxt(ii),*) '                                               jpkglo = ', kpk                ;   ii = ii + 1 
    114       WRITE(ldtxt(ii),*) '         Coriolis:', ln_corio                                                 ;   ii = ii + 1 
    115       ! 
    116       !                             ! Set the lateral boundary condition of the global domain 
    117       kperio = 7                    ! ICE_AGRIF configuration : bi-periodic basin 
    118 #if defined key_agrif 
    119       IF( .NOT. Agrif_Root() ) THEN 
    120       kperio = 0 
     106      IF(lwp) THEN 
     107         WRITE(numout,*) '   ' 
     108         WRITE(numout,*) 'usr_def_nam  : read the user defined namelist (namusr_def) in namelist_cfg' 
     109         WRITE(numout,*) '~~~~~~~~~~~ ' 
     110         WRITE(numout,*) '   Namelist namusr_def : ICE_AGRIF test case' 
     111         WRITE(numout,*) '      horizontal resolution                    rn_dx  = ', rn_dx, ' meters' 
     112         WRITE(numout,*) '      horizontal resolution                    rn_dy  = ', rn_dy, ' meters' 
     113         WRITE(numout,*) '      ICE_AGRIF domain = 300 km x 300Km x 1 grid-point ' 
     114         WRITE(numout,*) '         LX [km]: ', zlx 
     115         WRITE(numout,*) '         LY [km]: ', zly 
     116         WRITE(numout,*) '         resulting global domain size :        Ni0glo = ', kpi 
     117         WRITE(numout,*) '                                               Nj0glo = ', kpj 
     118         WRITE(numout,*) '                                               jpkglo = ', kpk 
     119         WRITE(numout,*) '         Coriolis:', ln_corio 
     120         WRITE(numout,*) '   ' 
     121         WRITE(numout,*) '   Lateral boundary condition of the global domain' 
     122         WRITE(numout,*) '      ICE_AGRIF : bi-periodic basin            jperio = ', kperio 
    121123      ENDIF 
    122 #endif 
    123       ! 
    124       WRITE(ldtxt(ii),*) '   '                                                                          ;   ii = ii + 1 
    125       WRITE(ldtxt(ii),*) '   Lateral boundary condition of the global domain'                           ;   ii = ii + 1 
    126       WRITE(ldtxt(ii),*) '      ICE_AGRIF : bi-periodic basin               jperio = ', kperio          ;   ii = ii + 1 
    127124      ! 
    128125   END SUBROUTINE usr_def_nam 
Note: See TracChangeset for help on using the changeset viewer.