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 6979 for branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/OFF_SRC/nemogcm.F90 – NEMO

Ignore:
Timestamp:
2016-10-03T18:23:58+02:00 (8 years ago)
Author:
cetlod
Message:

SIMPLIF_2_usrdef : make it work for standard Offline configuration

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/OFF_SRC/nemogcm.F90

    r6596 r6979  
    1919   USE domcfg          ! domain configuration               (dom_cfg routine) 
    2020   USE domain          ! domain initialization from coordinate & bathymetry (dom_init routine) 
    21    USE domrea          ! domain initialization from mesh_mask            (dom_init routine) 
     21!   USE domrea          ! domain initialization from mesh_mask            (dom_init routine) 
    2222   USE eosbn2          ! equation of state            (eos bn2 routine) 
    2323   !              ! ocean physics 
     
    5454   USE sbc_oce, ONLY: ln_rnf 
    5555   USE sbcrnf 
     56   USE usrdef_nam     ! user defined configuration 
     57 
    5658 
    5759   IMPLICIT NONE 
     
    147149      INTEGER ::   ji            ! dummy loop indices 
    148150      INTEGER ::   ilocal_comm   ! local integer 
    149       INTEGER ::   ios 
    150       LOGICAL ::   llexist 
    151       CHARACTER(len=80), DIMENSION(16) ::   cltxt 
     151      INTEGER ::   ios, inum 
     152      REAL(wp) ::   ziglo, zjglo, zkglo, zperio   ! local scalars 
     153      CHARACTER(len=120), DIMENSION(30) ::   cltxt, cltxt2, clnam 
    152154      !! 
    153155      NAMELIST/namctl/ ln_ctl  , nn_print, nn_ictls, nn_ictle,   & 
    154156         &             nn_isplt, nn_jsplt, nn_jctls, nn_jctle,   & 
    155          &             nn_bench, nn_timing, nn_diacfl 
    156       NAMELIST/namcfg/ cp_cfg, cp_cfz, jp_cfg, jpidta, jpjdta, jpkdta, jpiglo, jpjglo, & 
    157          &             jperio, ln_use_jattr 
    158       !!---------------------------------------------------------------------- 
    159       cltxt = '' 
     157         &             nn_timing, nn_diacfl 
     158 
     159      NAMELIST/namcfg/ ln_read_cfg, ln_write_cfg, cp_cfg, jp_cfg, ln_use_jattr 
     160      !!---------------------------------------------------------------------- 
     161      cltxt  = '' 
     162      cltxt2 = '' 
     163      clnam  = ''   
    160164      cxios_context = 'nemo' 
    161165      ! 
     
    181185904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcfg in configuration namelist', .TRUE. )    
    182186 
     187 
     188      !                             !--------------------------! 
     189      !                             !  Set global domain size  !   (control print return in cltxt2) 
     190      !                             !--------------------------! 
     191      IF( ln_read_cfg ) THEN              ! Read sizes in configuration "mesh_mask" file 
     192         CALL iom_open( 'domain_cfg', inum ) 
     193         CALL iom_get( inum, 'jpiglo', ziglo  )   ;   jpiglo = INT( ziglo ) 
     194         CALL iom_get( inum, 'jpjglo', zjglo  )   ;   jpjglo = INT( zjglo ) 
     195         CALL iom_get( inum, 'jpkglo', zkglo  )   ;   jpkglo = INT( zkglo ) 
     196         CALL iom_get( inum, 'jperio', zperio )   ;   jperio = INT( zperio ) 
     197         CALL iom_close( inum ) 
     198         WRITE(cltxt2(1),*) '~~~~~~~~~~   '       
     199         WRITE(cltxt2(2),*) 'domain_cfg : domain size read in "domain_cfg" file : jp(i,j,k)glo = ' 
     200         WRITE(cltxt2(3),*) '            ', jpiglo, jpjglo, jpkglo         
     201         WRITE(cltxt2(1),*) '~~~~~~~~~~   lateral boudary type of the global domain jperio= ', jperio 
     202         !         
     203      ELSE                                ! user-defined namelist 
     204         CALL usr_def_nam( cltxt2, clnam, jpiglo, jpjglo, jpkglo, jperio ) 
     205      ENDIF 
     206      jpk    = jpkglo 
    183207      ! 
    184208      !                             !--------------------------------------------! 
     
    206230         WRITE( numond, namctl ) 
    207231         WRITE( numond, namcfg ) 
     232         IF( .NOT.ln_read_cfg ) THEN 
     233            DO ji = 1, SIZE(clnam) 
     234               IF( TRIM(clnam (ji)) /= '' )   WRITE(numond, * ) clnam(ji)    ! namusr_def print 
     235            END DO 
     236         ENDIF 
    208237      ENDIF 
    209238 
     
    225254      jpi = ( jpiglo-2*jpreci + (jpni-1) ) / jpni + 2*jpreci   ! first  dim. 
    226255      jpj = ( jpjglo-2*jprecj + (jpnj-1) ) / jpnj + 2*jprecj   ! second dim. 
    227       jpk = jpkdta                                             ! third dim 
    228256      jpim1 = jpi-1                                            ! inner domain indices 
    229257      jpjm1 = jpj-1                                            !   "           " 
     
    274302                            CALL     eos_init   ! Equation of state 
    275303      IF( lk_c1d        )   CALL     c1d_init   ! 1D column configuration 
     304 
    276305                            CALL     dom_cfg    ! Domain configuration 
    277       ! 
    278       INQUIRE( FILE='coordinates.nc', EXIST = llexist )   ! Check if coordinate file exist 
    279       ! 
    280       IF( llexist )  THEN  ;  CALL  dom_init   !  compute the grid from coordinates and bathymetry 
    281       ELSE                 ;  CALL  dom_rea    !  read grid from the meskmask 
    282       ENDIF 
     306                            CALL     dom_init   ! Domain 
     307 
    283308                            CALL  istate_init   ! ocean initial state (Dynamics and tracers) 
    284309 
     
    315340      !!                     ***  ROUTINE nemo_ctl  *** 
    316341      !! 
    317       !! ** Purpose :   control print setting  
     342      !! ** Purpose :   control print setting 
    318343      !! 
    319344      !! ** Method  : - print namctl information and check some consistencies 
    320345      !!---------------------------------------------------------------------- 
    321346      ! 
    322       IF(lwp) THEN                  ! Parameter print 
     347      IF(lwp) THEN                  ! control print 
    323348         WRITE(numout,*) 
    324          WRITE(numout,*) 'nemo_flg: Control prints & Benchmark' 
     349         WRITE(numout,*) 'nemo_ctl: Control prints' 
    325350         WRITE(numout,*) '~~~~~~~ ' 
    326351         WRITE(numout,*) '   Namelist namctl' 
     
    333358         WRITE(numout,*) '      number of proc. following i     nn_isplt   = ', nn_isplt 
    334359         WRITE(numout,*) '      number of proc. following j     nn_jsplt   = ', nn_jsplt 
    335          WRITE(numout,*) '      benchmark parameter (0/1)       nn_bench   = ', nn_bench 
     360         WRITE(numout,*) '      timing activated    (0/1)       nn_timing  = ', nn_timing 
    336361      ENDIF 
    337362      ! 
     
    343368      isplt     = nn_isplt 
    344369      jsplt     = nn_jsplt 
    345       nbench    = nn_bench 
    346      IF(lwp) THEN                  ! control print 
     370 
     371      IF(lwp) THEN                  ! control print 
    347372         WRITE(numout,*) 
    348373         WRITE(numout,*) 'namcfg  : configuration initialization through namelist read' 
    349374         WRITE(numout,*) '~~~~~~~ ' 
    350375         WRITE(numout,*) '   Namelist namcfg' 
    351          WRITE(numout,*) '      configuration name              cp_cfg      = ', TRIM(cp_cfg) 
    352          WRITE(numout,*) '      configuration resolution        jp_cfg      = ', jp_cfg 
    353          WRITE(numout,*) '      lateral cond. type (between 0 and 6) jperio = ', jperio    
     376         WRITE(numout,*) '      read configuration definition files          ln_read_cfg = ', ln_read_cfg 
     377         WRITE(numout,*) '      configuration name                               cp_cfg  = ', TRIM(cp_cfg) 
     378         WRITE(numout,*) '      configuration resolution                         jp_cfg  = ', jp_cfg 
    354379         WRITE(numout,*) '      use file attribute if exists as i/p j-start ln_use_jattr = ', ln_use_jattr 
    355380      ENDIF 
     
    357382      ! 
    358383      IF( ln_ctl ) THEN                 ! sub-domain area indices for the control prints 
    359          IF( lk_mpp ) THEN 
    360             isplt = jpni   ;   jsplt = jpnj   ;   ijsplt = jpni*jpnj   ! the domain is forced to the real splitted domain 
     384         IF( lk_mpp .AND. jpnij > 1 ) THEN 
     385            isplt = jpni   ;   jsplt = jpnj   ;   ijsplt = jpni*jpnj   ! the domain is forced to the real split domain 
    361386         ELSE 
    362387            IF( isplt == 1 .AND. jsplt == 1  ) THEN 
     
    393418      ENDIF 
    394419      ! 
    395       IF( lk_c1d .AND. .NOT.lk_iomput )   CALL ctl_stop( 'nemo_ctl: The 1D configuration must be used ',   & 
    396          &                                               'with the IOM Input/Output manager. '        ,   & 
    397          &                                               'Compile with key_iomput enabled' ) 
    398       ! 
    399420      IF( 1_wp /= SIGN(1._wp,-0._wp)  )   CALL ctl_stop( 'nemo_ctl: The intrinsec SIGN function follows ',  & 
    400421         &                                               'f2003 standard. '                              ,  & 
     
    419440      IF( numnam_cfg /= -1 )   CLOSE( numnam_cfg )   ! oce configuration namelist 
    420441      IF( numout     /=  6 )   CLOSE( numout     )   ! standard model output file 
     442      IF( lwm.AND.numond  /= -1 )   CLOSE( numond          )   ! oce output namelist 
     443 
    421444      numout = 6                                     ! redefine numout in case it is used after this point... 
    422445      ! 
Note: See TracChangeset for help on using the changeset viewer.