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 15276 – NEMO

Changeset 15276


Ignore:
Timestamp:
2021-09-21T17:32:52+02:00 (3 years ago)
Author:
vsmart
Message:

Merge in changes from couple_stage2_spmd branch to allow for running from the Fortran cap

Location:
NEMO/branches/UKMO/NEMO_4.0.1_NGMS_couple_stage3_spmd/src/OCE
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/UKMO/NEMO_4.0.1_NGMS_couple_stage3_spmd/src/OCE/LBC/lib_mpp.F90

    r13311 r15276  
    5858   ! 
    5959   PUBLIC   ctl_stop, ctl_warn, ctl_opn, ctl_nam 
     60   PUBLIC   set_mpi_pre_initialised 
    6061   PUBLIC   mpp_start, mppstop, mppsync, mpp_comm_free 
    6162   PUBLIC   mpp_ini_north 
     
    100101!$AGRIF_END_DO_NOT_TREAT 
    101102   LOGICAL, PUBLIC, PARAMETER ::   lk_mpp = .TRUE.    !: mpp flag 
     103   LOGICAL, PUBLIC            ::   mpi_pre_initialised = .FALSE. 
    102104#else    
    103105   INTEGER, PUBLIC, PARAMETER ::   MPI_STATUS_SIZE = 1 
     
    176178   !!---------------------------------------------------------------------- 
    177179CONTAINS 
     180 
     181   SUBROUTINE set_mpi_pre_initialised() 
     182      !!---------------------------------------------------------------------- 
     183      !!                  ***  routine set_mpi_pre_initialised  *** 
     184      !! 
     185      !! ** Purpose :   set global variable mpi_pre_initialised 
     186      !!---------------------------------------------------------------------- 
     187      INTEGER ::   ierr 
     188      !!---------------------------------------------------------------------- 
     189#if defined key_mpp_mpi 
     190      call mpi_initialized(mpi_pre_initialised, ierr) 
     191#endif 
     192      ! 
     193   END SUBROUTINE set_mpi_pre_initialised 
    178194 
    179195   SUBROUTINE mpp_start( localComm ) 
     
    692708      ELSE 
    693709         CALL mppsync 
    694          CALL mpi_finalize( info ) 
     710         IF (.NOT. mpi_pre_initialised) THEN 
     711             CALL mpi_finalize( info ) 
     712         ENDIF 
    695713      ENDIF 
    696714      IF( ll_abort ) STOP 123 
  • NEMO/branches/UKMO/NEMO_4.0.1_NGMS_couple_stage3_spmd/src/OCE/nemogcm.F90

    r13443 r15276  
    100100 
    101101   PUBLIC   nemo_gcm    ! called by model.F90 
     102   PUBLIC   nemo_gcm_init ! called by nemo_gcm or external subroutine 
     103   PUBLIC   nemo_gcm_run ! called by nemo_gcm or external subroutine 
     104   PUBLIC   nemo_gcm_finalise ! called by nemo_gcm or external subroutine 
    102105   PUBLIC   nemo_init   ! needed by AGRIF 
    103106   PUBLIC   nemo_alloc  ! needed by TAM 
     
    124127      !!              curvilinear mesh on the sphere. 
    125128      !! 
    126       !! ** Method  : - model general initialization 
    127       !!              - launch the time-stepping (stp routine) 
    128       !!              - finalize the run by closing files and communications 
     129      !! ** Method  : - calls nemo_gcm_init, nemo_gcm_run, nemo_gcm_finalise 
    129130      !! 
    130131      !! References : Madec, Delecluse, Imbard, and Levy, 1997:  internal report, IPSL. 
    131132      !!              Madec, 2008, internal report, IPSL. 
    132133      !!---------------------------------------------------------------------- 
    133       INTEGER ::   istp, nerror   ! time step index 
    134       REAL(wp)::   zstptiming   ! elapsed time for 1 time step 
    135       !!---------------------------------------------------------------------- 
    136       ! 
     134      CALL nemo_gcm_init 
     135      CALL nemo_gcm_run 
     136      CALL nemo_gcm_finalise 
     137   END SUBROUTINE nemo_gcm 
     138 
     139   SUBROUTINE nemo_gcm_init 
     140      !!---------------------------------------------------------------------- 
     141      !!                     ***  ROUTINE nemo_gcm_init  *** 
     142      !! 
     143      !! ** Purpose :   NEMO solves the primitive equations on an orthogonal 
     144      !!              curvilinear mesh on the sphere. 
     145      !! 
     146      !! ** Method  : - model general initialization 
     147      !! 
     148      !! References : Madec, Delecluse, Imbard, and Levy, 1997:  internal report, IPSL. 
     149      !!              Madec, 2008, internal report, IPSL. 
     150      !!---------------------------------------------------------------------- 
    137151#if defined key_agrif 
    138152      CALL Agrif_Init_Grids()      ! AGRIF: set the meshes 
     
    151165# endif 
    152166#endif 
     167   END SUBROUTINE nemo_gcm_init 
     168 
     169   SUBROUTINE nemo_gcm_run 
     170      !!---------------------------------------------------------------------- 
     171      !!                     ***  ROUTINE nemo_gcm_run  *** 
     172      !! 
     173      !! ** Purpose :   NEMO solves the primitive equations on an orthogonal 
     174      !!              curvilinear mesh on the sphere. 
     175      !! 
     176      !! ** Method  : - launch the time-stepping (stp routine) 
     177      !! 
     178      !! References : Madec, Delecluse, Imbard, and Levy, 1997:  internal report, IPSL. 
     179      !!              Madec, 2008, internal report, IPSL. 
     180      !!---------------------------------------------------------------------- 
     181      INTEGER ::   istp   ! time step index 
     182      REAL(wp)::   zstptiming   ! elapsed time for 1 time step 
     183      !!---------------------------------------------------------------------- 
     184      ! 
    153185      ! check that all process are still there... If some process have an error, 
    154186      ! they will never enter in step and other processes will wait until the end of the cpu time! 
     
    248280      write(numout,*) "RSRH done closefiles " , lk_oasis; flush(numout) 
    249281      ! 
     282   END SUBROUTINE nemo_gcm_run 
     283 
     284   SUBROUTINE nemo_gcm_finalise 
     285      !!---------------------------------------------------------------------- 
     286      !!                     ***  ROUTINE nemo_gcm_finalise  *** 
     287      !! 
     288      !! ** Purpose :   NEMO solves the primitive equations on an orthogonal 
     289      !!              curvilinear mesh on the sphere. 
     290      !! 
     291      !! ** Method  : - finalize the run by closing files and communications 
     292      !! 
     293      !! References : Madec, Delecluse, Imbard, and Levy, 1997:  internal report, IPSL. 
     294      !!              Madec, 2008, internal report, IPSL. 
     295      !!---------------------------------------------------------------------- 
     296      integer :: nerror 
     297      !!---------------------------------------------------------------------- 
     298      ! 
    250299#if defined key_iomput 
    251300      CALL xios_finalize()  ! end mpp communications with xios 
     
    262311#endif 
    263312      ! 
    264       IF(lwm) THEN 
    265          IF( nstop == 0 ) THEN    
    266                 STOP 0 
    267          ELSE         
    268                 STOP 123 
     313      IF (.NOT. mpi_pre_initialised) THEN 
     314         IF(lwm) THEN 
     315            IF( nstop == 0 ) THEN    
     316                  STOP 0 
     317            ELSE         
     318                  STOP 123 
     319            ENDIF 
    269320         ENDIF 
    270321      ENDIF 
    271322      ! 
    272    END SUBROUTINE nemo_gcm 
     323   END SUBROUTINE nemo_gcm_finalise 
    273324 
    274325 
     
    294345      !                             !-------------------------------------------------! 
    295346      ! 
     347      CALL set_mpi_pre_initialised() 
    296348#if defined key_iomput 
    297349!      IF( Agrif_Root() ) THEN 
     
    305357! RSRH simplify initialisaton for test 
    306358      IF( lk_oasis ) THEN 
    307           CALL mpi_init(nerror) 
     359          IF (.NOT. mpi_pre_initialised) THEN 
     360              CALL mpi_init(nerror) 
     361          ENDIF 
    308362          CALL oasis_init_comp ( ncomp_id, "toyoce", nerror, .TRUE. ) 
    309363!          CALL cpl_init( "toyoce", ilocal_comm )  
Note: See TracChangeset for help on using the changeset viewer.