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

Changeset 15544


Ignore:
Timestamp:
2021-11-26T16:52:40+01:00 (2 years ago)
Author:
vsmart
Message:

Merge changes for running from the Fortran cap

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

Legend:

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

    r15261 r15544  
    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 ) 
     
    693709      ELSE 
    694710         CALL mppsync 
    695          CALL mpi_finalize( info ) 
     711         IF (.NOT. mpi_pre_initialised) THEN 
     712             CALL mpi_finalize( info ) 
     713         ENDIF 
    696714      ENDIF 
    697715      IF( ll_abort ) STOP 123 
  • NEMO/branches/UKMO/NEMO_4.0.1_NGMS_couple_stage3_spmd2/src/OCE/nemogcm.F90

    r15261 r15544  
    102102 
    103103   PUBLIC   nemo_gcm    ! called by model.F90 
     104   PUBLIC   nemo_gcm_init ! called by nemo_gcm or external subroutine 
     105   PUBLIC   nemo_gcm_run ! called by nemo_gcm or external subroutine 
     106   PUBLIC   nemo_gcm_finalise ! called by nemo_gcm or external subroutine 
    104107   PUBLIC   nemo_init   ! needed by AGRIF 
    105108   PUBLIC   nemo_alloc  ! needed by TAM 
     
    126129      !!              curvilinear mesh on the sphere. 
    127130      !! 
    128       !! ** Method  : - model general initialization 
    129       !!              - launch the time-stepping (stp routine) 
    130       !!              - finalize the run by closing files and communications 
     131      !! ** Method  : - calls nemo_gcm_init, nemo_gcm_run, nemo_gcm_finalise 
    131132      !! 
    132133      !! References : Madec, Delecluse, Imbard, and Levy, 1997:  internal report, IPSL. 
    133134      !!              Madec, 2008, internal report, IPSL. 
    134135      !!---------------------------------------------------------------------- 
    135       INTEGER ::   istp, nerror   ! time step index 
    136       REAL(wp)::   zstptiming   ! elapsed time for 1 time step 
    137       !!---------------------------------------------------------------------- 
    138       ! 
     136      CALL nemo_gcm_init 
     137      CALL nemo_gcm_run 
     138      CALL nemo_gcm_finalise 
     139   END SUBROUTINE nemo_gcm 
     140 
     141   SUBROUTINE nemo_gcm_init 
     142      !!---------------------------------------------------------------------- 
     143      !!                     ***  ROUTINE nemo_gcm_init  *** 
     144      !! 
     145      !! ** Purpose :   NEMO solves the primitive equations on an orthogonal 
     146      !!              curvilinear mesh on the sphere. 
     147      !! 
     148      !! ** Method  : - model general initialization 
     149      !! 
     150      !! References : Madec, Delecluse, Imbard, and Levy, 1997:  internal report, IPSL. 
     151      !!              Madec, 2008, internal report, IPSL. 
     152      !!---------------------------------------------------------------------- 
    139153#if defined key_agrif 
    140154      CALL Agrif_Init_Grids()      ! AGRIF: set the meshes 
     
    153167# endif 
    154168#endif 
     169   END SUBROUTINE nemo_gcm_init 
     170 
     171   SUBROUTINE nemo_gcm_run 
     172      !!---------------------------------------------------------------------- 
     173      !!                     ***  ROUTINE nemo_gcm_run  *** 
     174      !! 
     175      !! ** Purpose :   NEMO solves the primitive equations on an orthogonal 
     176      !!              curvilinear mesh on the sphere. 
     177      !! 
     178      !! ** Method  : - launch the time-stepping (stp routine) 
     179      !! 
     180      !! References : Madec, Delecluse, Imbard, and Levy, 1997:  internal report, IPSL. 
     181      !!              Madec, 2008, internal report, IPSL. 
     182      !!---------------------------------------------------------------------- 
     183      INTEGER ::   istp   ! time step index 
     184      REAL(wp)::   zstptiming   ! elapsed time for 1 time step 
     185      !!---------------------------------------------------------------------- 
     186      ! 
    155187      ! check that all process are still there... If some process have an error, 
    156188      ! they will never enter in step and other processes will wait until the end of the cpu time! 
     
    252284      CALL nemo_closefile 
    253285      ! 
     286   END SUBROUTINE nemo_gcm_run 
     287 
     288   SUBROUTINE nemo_gcm_finalise 
     289      !!---------------------------------------------------------------------- 
     290      !!                     ***  ROUTINE nemo_gcm_finalise  *** 
     291      !! 
     292      !! ** Purpose :   NEMO solves the primitive equations on an orthogonal 
     293      !!              curvilinear mesh on the sphere. 
     294      !! 
     295      !! ** Method  : - finalize the run by closing files and communications 
     296      !! 
     297      !! References : Madec, Delecluse, Imbard, and Levy, 1997:  internal report, IPSL. 
     298      !!              Madec, 2008, internal report, IPSL. 
     299      !!---------------------------------------------------------------------- 
     300      integer :: nerror 
     301      !!---------------------------------------------------------------------- 
     302      ! 
    254303#if defined key_iomput 
    255304      CALL xios_finalize()  ! end mpp communications with xios 
     
    274323#endif 
    275324      ! 
    276       IF(lwm) THEN 
    277          IF( nstop == 0 ) THEN    
    278                 STOP 0 
    279          ELSE         
    280                 STOP 123 
     325      IF (.NOT. mpi_pre_initialised) THEN 
     326         IF(lwm) THEN 
     327            IF( nstop == 0 ) THEN    
     328                  STOP 0 
     329            ELSE         
     330                  STOP 123 
     331            ENDIF 
    281332         ENDIF 
    282333      ENDIF 
    283334      ! 
    284    END SUBROUTINE nemo_gcm 
     335   END SUBROUTINE nemo_gcm_finalise 
    285336 
    286337 
     
    306357      !                             !-------------------------------------------------! 
    307358      ! 
    308  
     359      CALL set_mpi_pre_initialised() 
    309360#if defined key_iomput 
    310361      IF( Agrif_Root() ) THEN 
     
    316367#if defined key_oasis3 
    317368      IF( lk_oasis ) THEN 
    318           CALL mpi_init(nerror) 
     369          IF (.NOT. mpi_pre_initialised) THEN 
     370              CALL mpi_init(nerror) 
     371          ENDIF 
    319372          CALL oasis_init_comp ( ncomp_id, "toyoce", nerror, .TRUE. ) 
    320373          CALL oasis_get_localcomm ( ilocal_comm , nerror ) 
Note: See TracChangeset for help on using the changeset viewer.