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

Changeset 13311


Ignore:
Timestamp:
2020-07-16T15:27:24+02:00 (4 years ago)
Author:
frrh
Message:

Save dev changes for concurrent LFRIC + GO8 running

Location:
NEMO/branches/UKMO/NEMO_4.0.1_NGMS_couple_pkg/src/OCE
Files:
4 edited

Legend:

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

    r11913 r13311  
    686686      ! leave other components deadlocked. 
    687687 
    688       CALL oasis_abort(nproc,"mppstop","NEMO initiated abort") 
     688! RSRH No!  
     689      IF(ll_abort) THEN 
     690         !CALL mpi_abort( MPI_COMM_WORLD ) 
     691         CALL oasis_abort(nproc,"mppstop","NEMO initiated abort") 
     692      ELSE 
     693         CALL mppsync 
     694         CALL mpi_finalize( info ) 
     695      ENDIF 
     696      IF( ll_abort ) STOP 123 
    689697 
    690698 
  • NEMO/branches/UKMO/NEMO_4.0.1_NGMS_couple_pkg/src/OCE/SBC/cpl_oasis3.F90

    r11914 r13311  
    9595CONTAINS 
    9696 
    97    SUBROUTINE cpl_init( cd_modname, kl_comm ) 
     97   SUBROUTINE cpl_init( cd_modname, kl_comm )  
     98 
    9899      !!------------------------------------------------------------------- 
    99100      !!             ***  ROUTINE cpl_init  *** 
     
    104105      !! ** Method  :   OASIS3 MPI communication  
    105106      !!-------------------------------------------------------------------- 
     107      USE sbc_oce , ONLY :   ln_cpl 
    106108      CHARACTER(len = *), INTENT(in   ) ::   cd_modname   ! model name as set in namcouple file 
    107109      INTEGER           , INTENT(  out) ::   kl_comm      ! local communicator of the model 
     
    114116      ! 1st Initialize the OASIS system for the application 
    115117      !------------------------------------------------------------------ 
    116       CALL oasis_init_comp ( ncomp_id, TRIM(cd_modname), nerror ) 
     118      CALL oasis_init_comp ( ncomp_id, TRIM(cd_modname), nerror, ln_cpl ) 
    117119      IF ( nerror /= OASIS_Ok ) & 
    118120         CALL oasis_abort (ncomp_id, 'cpl_init', 'Failure in oasis_init_comp') 
     
    530532      !!---------------------------------------------------------------------- 
    531533      ! 
    532       DEALLOCATE( exfld ) 
     534      IF (ALLOCATED(exfld)) DEALLOCATE( exfld ) 
     535 
    533536      IF (nstop == 0) THEN 
    534537         CALL oasis_terminate( nerror )          
     
    545548   !!---------------------------------------------------------------------- 
    546549 
    547    SUBROUTINE oasis_init_comp(k1,cd1,k2) 
     550   SUBROUTINE oasis_init_comp(k1,cd1,k2,l1) 
    548551      CHARACTER(*), INTENT(in   ) ::  cd1 
    549552      INTEGER     , INTENT(  out) ::  k1,k2 
     
    554557   SUBROUTINE oasis_abort(k1,cd1,cd2) 
    555558      INTEGER     , INTENT(in   ) ::  k1 
    556       CHARACTER(*), INTENT(in   ) ::  cd1,cd2 
     559      CHARACTER(*), INTENT(in   ) ::  cd1,cd2      
     560      LOGICAL     , OPTIONAL,  INTENT(in   ) ::  l1 
    557561      WRITE(numout,*) 'oasis_abort: Error you sould not be there...', cd1, cd2 
    558562   END SUBROUTINE oasis_abort 
  • NEMO/branches/UKMO/NEMO_4.0.1_NGMS_couple_pkg/src/OCE/SBC/sbccpl.F90

    r11914 r13311  
    466466      !                                                      ! ------------------------- ! 
    467467      srcv(jpr_rnf   )%clname = 'O_Runoff' 
    468       IF( TRIM( sn_rcv_rnf%cldes ) == 'coupled' ) THEN 
    469          srcv(jpr_rnf)%laction = .TRUE. 
    470          l_rnfcpl              = .TRUE.                      ! -> no need to read runoffs in sbcrnf 
    471          ln_rnf                = nn_components /= jp_iam_sas ! -> force to go through sbcrnf if not sas 
    472          IF(lwp) WRITE(numout,*) 
    473          IF(lwp) WRITE(numout,*) '   runoffs received from oasis -> force ln_rnf = ', ln_rnf 
    474       ENDIF 
     468      IF (ln_cpl) THEN ! Don't perform this code if coupling is not active! 
     469         IF( TRIM( sn_rcv_rnf%cldes ) == 'coupled' ) THEN 
     470            srcv(jpr_rnf)%laction = .TRUE. 
     471            l_rnfcpl              = .TRUE.                      ! -> no need to read runoffs in sbcrnf 
     472            ln_rnf                = nn_components /= jp_iam_sas ! -> force to go through sbcrnf if not sas 
     473            IF(lwp) WRITE(numout,*) 
     474            IF(lwp) WRITE(numout,*) '   runoffs received from oasis -> force ln_rnf = ', ln_rnf 
     475         ENDIF 
     476      ENDIF  
    475477      ! 
    476478      srcv(jpr_cal)%clname = 'OCalving'   ;  IF( TRIM( sn_rcv_cal%cldes) == 'coupled' )   srcv(jpr_cal)%laction = .TRUE. 
     
    543545      !                                                      ! ------------------------- ! 
    544546      srcv(jpr_co2 )%clname = 'O_AtmCO2'    
    545       IF( TRIM(sn_rcv_co2%cldes   ) == 'coupled' )  THEN 
    546          srcv(jpr_co2 )%laction = .TRUE. 
    547          l_co2cpl = .TRUE. 
    548          IF(lwp) WRITE(numout,*) 
    549          IF(lwp) WRITE(numout,*) '   Atmospheric pco2 received from oasis ' 
    550          IF(lwp) WRITE(numout,*) 
     547      IF (ln_cpl) THEN ! Not needed if we're not coupling 
     548         IF( TRIM(sn_rcv_co2%cldes   ) == 'coupled' )  THEN 
     549            srcv(jpr_co2 )%laction = .TRUE. 
     550            l_co2cpl = .TRUE. 
     551            IF(lwp) WRITE(numout,*) 
     552            IF(lwp) WRITE(numout,*) '   Atmospheric pco2 received from oasis ' 
     553            IF(lwp) WRITE(numout,*) 
     554         ENDIF 
    551555      ENDIF 
    552556      ! 
     
    10321036      ! ================================ ! 
    10331037 
    1034       CALL cpl_define(jprcv, jpsnd, nn_cplmodel) 
     1038      ! If ln_cpl is false, clearly we don't want to call cpl_dfine! 
     1039      if (ln_cpl) CALL cpl_define(jprcv, jpsnd, nn_cplmodel) 
    10351040       
    10361041      IF (ln_usecplmask) THEN  
  • NEMO/branches/UKMO/NEMO_4.0.1_NGMS_couple_pkg/src/OCE/nemogcm.F90

    r11913 r13311  
    4141   !!   nemo_alloc    : dynamical allocation 
    4242   !!---------------------------------------------------------------------- 
     43   USE mod_oasis ! RSRH temp 
    4344   USE step_oce       ! module used in the ocean time stepping module (step.F90) 
    4445   USE phycst         ! physical constant                  (par_cst routine) 
     
    130131      !!              Madec, 2008, internal report, IPSL. 
    131132      !!---------------------------------------------------------------------- 
    132       INTEGER ::   istp   ! time step index 
     133      INTEGER ::   istp, nerror   ! time step index 
    133134      REAL(wp)::   zstptiming   ! elapsed time for 1 time step 
    134135      !!---------------------------------------------------------------------- 
     
    200201            ENDIF 
    201202             
    202             IF (lk_oasis) THEN 
    203                CALL sbc_cpl_snd( istp )  ! Coupling to atmos 
    204             ENDIF 
     203            ! RSRH. You can compile with OASIS but not want to do any 
     204            ! coupling. We need to cater for that properly! 
     205            IF (ln_cpl) CALL sbc_cpl_snd( istp )  ! Coupling to atmos 
     206 
    205207            CALL stp        ( istp )  
    206208            istp = istp + 1 
     
    239241      IF( ln_timing )   CALL timing_finalize 
    240242      ! 
     243      write(numout,*) "RSRH calling nemo_closefile " , lk_oasis; flush(numout) 
    241244      CALL nemo_closefile 
     245      write(numout,*) "RSRH done closefiles " , lk_oasis; flush(numout) 
    242246      ! 
    243247#if defined key_iomput 
    244                                     CALL xios_finalize  ! end mpp communications with xios 
    245       IF( lk_oasis     )            CALL cpl_finalize   ! end coupling and mpp communications with OASIS 
     248      CALL xios_finalize()  ! end mpp communications with xios 
     249 
     250      IF (lk_oasis)  CALL oasis_terminate(nerror) 
     251      CALL mppstop ! RSRH temp for development 
     252      !IF( lk_oasis     )            CALL cpl_finalize()   ! end coupling and mpp communications with OASIS 
    246253#else 
    247       IF    ( lk_oasis ) THEN   ;   CALL cpl_finalize   ! end coupling and mpp communications with OASIS 
    248       ELSEIF( lk_mpp   ) THEN   ;   CALL mppstop      ! end mpp communications 
     254      IF    ( lk_oasis ) THEN    
     255          CALL cpl_finalize()   ! end coupling and mpp communications with OASIS 
     256      ELSEIF( lk_mpp   ) THEN  
     257          CALL mppstop      ! end mpp communications 
    249258      ENDIF 
    250259#endif 
    251260      ! 
    252261      IF(lwm) THEN 
    253          IF( nstop == 0 ) THEN   ;   STOP 0 
    254          ELSE                    ;   STOP 123 
     262         IF( nstop == 0 ) THEN    
     263                STOP 0 
     264         ELSE         
     265                STOP 123 
    255266         ENDIF 
    256267      ENDIF 
     
    265276      !! ** Purpose :   initialization of the NEMO GCM 
    266277      !!---------------------------------------------------------------------- 
    267       INTEGER ::   ios, ilocal_comm   ! local integers 
     278      INTEGER ::   ios, ilocal_comm, nerror, ncomp_id, llmpi_init, ierr  ! local integers 
    268279      !! 
    269280      NAMELIST/namctl/ ln_ctl   , sn_cfctl, nn_print, nn_ictls, nn_ictle,   & 
     
    281292      ! 
    282293#if defined key_iomput 
    283       IF( Agrif_Root() ) THEN 
    284          IF( lk_oasis ) THEN 
    285             CALL cpl_init( "toyoce", ilocal_comm )                     ! nemo local communicator given by oasis 
    286             CALL xios_initialize( "not used"       , local_comm =ilocal_comm )   ! send nemo communicator to xios 
    287          ELSE 
    288             CALL xios_initialize( "for_xios_mpi_id", return_comm=ilocal_comm )   ! nemo local communicator given by xios 
    289          ENDIF 
     294!      IF( Agrif_Root() ) THEN 
     295!         IF( lk_oasis ) THEN 
     296!            CALL cpl_init( "toyoce", ilocal_comm )                     ! nemo local communicator given by oasis 
     297!            CALL xios_initialize( "not used"       , local_comm =ilocal_comm )   ! send nemo communicator to xios 
     298!         ELSE 
     299!            CALL xios_initialize( "for_xios_mpi_id", return_comm=ilocal_comm )   ! nemo local communicator given by xios 
     300!         ENDIF 
     301!      ENDIF 
     302! RSRH simplify initialisaton for test 
     303      IF( lk_oasis ) THEN 
     304          CALL mpi_init(nerror) 
     305          CALL oasis_init_comp ( ncomp_id, "toyoce", nerror, .FALSE. ) 
     306!          CALL cpl_init( "toyoce", ilocal_comm )  
     307          CALL oasis_get_localcomm ( ilocal_comm , nerror ) 
     308          CALL xios_initialize( "toyoce", local_comm =ilocal_comm ) 
    290309      ENDIF 
    291310      CALL mpp_start( ilocal_comm ) 
     
    330349      lwp = (narea == 1) .OR. ln_ctl    ! control of all listing output print 
    331350      ! 
     351WRITE(numout,*) "RSRH NEMO start local com=",ilocal_comm ; flush(numout)  
     352WRITE(numout,*) "RSRH NEMO my rank=",mpprank ; flush(numout)  
    332353      IF(lwp) THEN                      ! open listing units 
    333354         ! 
     
    335356            &            CALL ctl_opn( numout, 'ocean.output', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE., narea ) 
    336357         ! 
     358 
     359WRITE(numout,*) "RSRH NEMO start local com=",ilocal_comm ; flush(numout)  
     360WRITE(numout,*) "RSRH NEMO my rank=",mpprank ; flush(numout)  
     361 
    337362         WRITE(numout,*) 
    338363         WRITE(numout,*) '   CNRS - NERC - Met OFFICE - MERCATOR-ocean - CMCC' 
     
    625650      ! 
    626651      CALL iom_close                                 ! close all input/output files managed by iom_* 
     652 
     653write(numout,*) "RSRH after iom_close";flush(numout) 
    627654      ! 
    628655      IF( numstp          /= -1 )   CLOSE( numstp          )   ! time-step file 
     
    640667      IF( numdct_salt     /= -1 )   CLOSE( numdct_salt     )   ! salt transports 
    641668      ! 
    642       numout = 6                                     ! redefine numout in case it is used after this point... 
     669!      numout = 6                                     ! redefine numout in case it is used after this point... 
    643670      ! 
    644671   END SUBROUTINE nemo_closefile 
Note: See TracChangeset for help on using the changeset viewer.