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 9079 for branches/2017/dev_merge_2017/NEMOGCM/TOOLS/DOMAINcfg/src/nemogcm.f90 – NEMO

Ignore:
Timestamp:
2017-12-15T15:43:43+01:00 (6 years ago)
Author:
flavoni
Message:

update DOMAINcfg TOOLS, do not need xios anymore

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_merge_2017/NEMOGCM/TOOLS/DOMAINcfg/src/nemogcm.f90

    r7200 r9079  
    5252   USE lib_mpp        ! distributed memory computing 
    5353 
    54    USE xios           ! xIOserver 
    55  
    5654   USE lbcnfd , ONLY  : isendto, nsndto, nfsloop, nfeloop   ! Setup of north fold exchanges  
    5755 
     
    112110      CALL nemo_closefile 
    113111      ! 
    114       CALL xios_finalize                  ! end mpp communications with xios 
    115112      ! 
    116113   END SUBROUTINE nemo_gcm 
     
    137134      ! 
    138135      cltxt = '' 
    139       cxios_context = 'nemo' 
    140136      ! 
    141137      !                             ! Open reference namelist and configuration namelist files 
     
    167163      !                             !      on unit number numond on first proc   ! 
    168164      !                             !--------------------------------------------! 
    169       IF( Agrif_Root() ) THEN 
    170             CALL  xios_initialize( "for_xios_mpi_id",return_comm=ilocal_comm )    ! nemo local communicator given by xios 
    171       ENDIF 
    172165      ! Nodes selection (control print return in cltxt) 
    173       narea = mynode( cltxt, 'output.namelist.dyn', numnam_ref, numnam_cfg, numond , nstop, ilocal_comm ) 
     166      ilocal_comm = 0 
     167      narea = mynode( cltxt, 'output.namelist.dyn', numnam_ref, numnam_cfg, numond , nstop ) 
    174168      narea = narea + 1                                     ! mynode return the rank of proc (0 --> jpnij -1 ) 
    175169 
Note: See TracChangeset for help on using the changeset viewer.