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

Changeset 6558


Ignore:
Timestamp:
2016-05-18T14:16:20+02:00 (8 years ago)
Author:
frrh
Message:

Add changes as per dev_r5107_hadgem3_mct@6355

Location:
branches/UKMO/dev_r5518_hadgem3_mct/NEMOGCM/NEMO/OPA_SRC
Files:
13 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_hadgem3_mct/NEMOGCM/NEMO/OPA_SRC/DIA/diadimg.F90

    r6557 r6558  
    124124 
    125125    CASE DEFAULT 
    126        IF(lwp) WRITE(numout,*) ' E R R O R : bad cd_type in dia_wri_dimg ' 
    127        STOP 'dia_wri_dimg' 
     126     
     127       WRITE(numout,*) 'dia_wri_dimg : E R R O R : bad cd_type in dia_wri_dimg' 
     128       CALL ctl_stop( 'STOP', 'dia_wri_dimg :bad cd_type in dia_wri_dimg ' ) 
    128129 
    129130    END SELECT 
  • branches/UKMO/dev_r5518_hadgem3_mct/NEMOGCM/NEMO/OPA_SRC/DIA/diawri.F90

    r6557 r6558  
    10621062      ENDIF 
    10631063#endif 
     1064 
     1065      IF (cdfile_name == "output.abort") THEN 
     1066         CALL ctl_stop('STOP', 'NEMO abort from dia_wri_state') 
     1067      END IF 
    10641068        
    10651069!     IF( nn_timing == 1 )   CALL timing_stop('dia_wri_state') ! not sure this works for routines not called in first timestep 
  • branches/UKMO/dev_r5518_hadgem3_mct/NEMOGCM/NEMO/OPA_SRC/DIA/diawri_dimg.h90

    r6557 r6558  
    112112    IF( inbsel >  jpk ) THEN 
    113113       IF(lwp) WRITE(numout,*)  ' STOP inbsel =',inbsel,' is larger than jpk=',jpk 
    114        STOP 
     114       CALL ctl_stop('STOP', 'NEMO aborted from dia_wri') 
    115115    ENDIF 
    116116 
  • branches/UKMO/dev_r5518_hadgem3_mct/NEMOGCM/NEMO/OPA_SRC/DOM/dommsk.F90

    r6557 r6558  
    526526      IF(lwp) WRITE(numout,*) 'dom_msk_nsa : noslip accurate boundary condition' 
    527527      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~   using Schchepetkin and O Brian scheme' 
    528       IF( lk_mpp )   CALL ctl_stop( ' mpp version is not yet implemented' ) 
     528      IF( lk_mpp )   CALL ctl_stop('STOP', ' mpp version is not yet implemented' ) 
    529529 
    530530      ! mask for second order calculation of vorticity 
     
    548548         WRITE(numout,*) ' symetric boundary conditions need special' 
    549549         WRITE(numout,*) ' treatment not implemented. we stop.' 
    550          STOP 
     550         CALL ctl_stop('STOP', 'NEMO abort from dom_msk_nsa') 
    551551      ENDIF 
    552552       
  • branches/UKMO/dev_r5518_hadgem3_mct/NEMOGCM/NEMO/OPA_SRC/DYN/dynldf_bilapg.F90

    r6557 r6558  
    465465            END DO 
    466466         ELSE 
    467             IF(lwp)WRITE(numout,*) ' ldfguv: kahm= 1 or 2, here =', kahm 
    468             IF(lwp)WRITE(numout,*) '         We stop' 
    469             STOP 'ldfguv' 
     467             
     468            WRITE(numout,*) ' ldfguv: kahm= 1 or 2, here =', kahm 
     469            WRITE(numout,*) '         We stop' 
     470            CALL ctl_stop('STOP', 'ldfguv: Unexpected kahm value') 
     471 
    470472         ENDIF 
    471473         !                                             ! =============== 
  • branches/UKMO/dev_r5518_hadgem3_mct/NEMOGCM/NEMO/OPA_SRC/LBC/lib_mpp.F90

    r6557 r6558  
    6262   USE lbcnfd         ! north fold treatment 
    6363   USE in_out_manager ! I/O manager 
     64   USE mod_oasis      ! coupling routines 
    6465 
    6566   IMPLICIT NONE 
     
    20062007 
    20072008   SUBROUTINE mppstop 
     2009    
     2010 
    20082011      !!---------------------------------------------------------------------- 
    20092012      !!                  ***  routine mppstop  *** 
     
    20152018      !!---------------------------------------------------------------------- 
    20162019      ! 
     2020       
     2021#if defined key_oasis3 || defined key_oasis3mct 
     2022      ! If we're trying to shut down cleanly then we need to consider the fact 
     2023      ! that this could be part of an MPMD configuration - we don't want to 
     2024      ! leave other components deadlocked. 
     2025 
     2026      CALL oasis_abort(nproc,"mppstop","NEMO initiated abort") 
     2027 
     2028 
     2029#else 
     2030       
    20172031      CALL mppsync 
    20182032      CALL mpi_finalize( info ) 
     2033#endif 
     2034 
    20192035      ! 
    20202036   END SUBROUTINE mppstop 
     
    37843800            WRITE(kout,*) 
    37853801         ENDIF 
    3786          STOP 'ctl_opn bad opening' 
     3802         CALL ctl_stop ('STOP', 'NEMO abort ctl_opn bad opening') 
    37873803      ENDIF 
    37883804 
  • branches/UKMO/dev_r5518_hadgem3_mct/NEMOGCM/NEMO/OPA_SRC/SBC/cpl_oasis3.F90

    r6557 r6558  
    2424   !!   cpl_finalize : finalize the coupled mode communication 
    2525   !!---------------------------------------------------------------------- 
    26 #if defined key_oasis3 
     26#if defined key_oasis3 || defined key_oasis3mct 
    2727   USE mod_oasis                    ! OASIS3-MCT module 
    2828#endif 
     
    3131   USE in_out_manager               ! I/O manager 
    3232   USE lbclnk                       ! ocean lateral boundary conditions (or mpp link) 
     33    
     34#if defined key_cpl_rootexchg 
     35   USE lib_mpp, only : mppsync 
     36   USE lib_mpp, only : mppscatter,mppgather 
     37#endif  
    3338 
    3439   IMPLICIT NONE 
     
    4146   PUBLIC   cpl_freq 
    4247   PUBLIC   cpl_finalize 
     48#if defined key_mpp_mpi 
     49   INCLUDE 'mpif.h' 
     50#endif 
     51    
     52   INTEGER, PARAMETER         :: localRoot  = 0 
     53   LOGICAL                    :: commRank            ! true for ranks doing OASIS communication 
     54#if defined key_cpl_rootexchg 
     55   LOGICAL                    :: rootexchg =.true.   ! logical switch  
     56#else 
     57   LOGICAL                    :: rootexchg =.false.  ! logical switch  
     58#endif  
    4359 
    4460   INTEGER, PUBLIC            ::   OASIS_Rcv  = 1    !: return code if received field 
     
    4662   INTEGER                    ::   ncomp_id          ! id returned by oasis_init_comp 
    4763   INTEGER                    ::   nerror            ! return error code 
    48 #if ! defined key_oasis3 
     64#if ! defined key_oasis3 && ! defined key_oasis3mct 
    4965   ! OASIS Variables not used. defined only for compilation purpose 
    5066   INTEGER                    ::   OASIS_Out         = -1 
     
    8298 
    8399   REAL(wp), DIMENSION(:,:), ALLOCATABLE ::   exfld   ! Temporary buffer for receiving 
    84  
     100   REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::   tbuf  ! Temporary buffer for sending / receiving  
     101   INTEGER, PUBLIC :: localComm  
     102       
    85103   !!---------------------------------------------------------------------- 
    86104   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     
    120138      IF ( nerror /= OASIS_Ok ) & 
    121139         CALL oasis_abort (ncomp_id, 'cpl_init','Failure in oasis_get_localcomm' ) 
     140      localComm = kl_comm  
    122141      ! 
    123142   END SUBROUTINE cpl_init 
     
    148167      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~~~~' 
    149168      IF(lwp) WRITE(numout,*) 
     169       
     170      commRank = .false. 
     171      IF ( rootexchg ) THEN 
     172         IF ( nproc == localRoot ) commRank = .true. 
     173      ELSE 
     174         commRank = .true. 
     175      ENDIF 
    150176 
    151177      ncplmodel = kcplmodel 
     
    172198      ishape(:,2) = (/ 1, nlej-nldj+1 /) 
    173199      ! 
    174       ! ... Allocate memory for data exchange 
    175       ! 
    176       ALLOCATE(exfld(nlei-nldi+1, nlej-nldj+1), stat = nerror) 
    177       IF( nerror > 0 ) THEN 
    178          CALL oasis_abort ( ncomp_id, 'cpl_define', 'Failure in allocating exfld')   ;   RETURN 
    179       ENDIF 
    180200      ! 
    181201      ! ----------------------------------------------------------------- 
    182202      ! ... Define the partition  
    183203      ! ----------------------------------------------------------------- 
     204       
     205      IF ( rootexchg ) THEN 
     206      
     207      paral(1) = 2              ! box partitioning 
     208      paral(2) = 0              ! NEMO lower left corner global offset      
     209      paral(3) = jpiglo         ! local extent in i  
     210      paral(4) = jpjglo         ! local extent in j 
     211      paral(5) = jpiglo         ! global extent in x 
     212 
     213      ELSE  
    184214       
    185215      paral(1) = 2                                              ! box partitioning 
     
    196226      ENDIF 
    197227       
    198       CALL oasis_def_partition ( id_part, paral, nerror ) 
     228      ENDIF 
     229      IF ( commRank )  CALL oasis_def_partition ( id_part, paral, nerror, jpiglo*jpjglo ) 
     230      
     231      ! ... Allocate memory for data exchange 
     232      ! 
     233      ALLOCATE(exfld(paral(3), paral(4)), stat = nerror) 
     234      IF( nerror > 0 ) THEN 
     235         CALL oasis_abort ( ncomp_id, 'cpl_define', 'Failure in allocating exfld')   ;   RETURN 
     236      ENDIF 
     237      IF ( rootexchg ) THEN 
     238! Should possibly use one of the work arrays for tbuf really 
     239         ALLOCATE(tbuf(jpi, jpj, jpnij), stat = nerror) 
     240         IF( nerror > 0 ) THEN 
     241             CALL oasis_abort ( ncomp_id, 'cpl_define', 'Failure in allocating tbuf') ; RETURN 
     242         ENDIF 
     243       ENDIF              
     244       ! 
     245       IF (commRank ) THEN 
    199246      ! 
    200247      ! ... Announce send variables.  
     
    241288            END DO 
    242289         ENDIF 
    243       END DO 
     290      END DO       
    244291      ! 
    245292      ! ... Announce received variables.  
     
    288335         ENDIF 
    289336      END DO 
     337      ! 
     338      ENDIF  ! commRank=true  
    290339       
    291340      !------------------------------------------------------------------ 
     
    293342      !------------------------------------------------------------------ 
    294343       
    295       CALL oasis_enddef(nerror) 
    296       IF( nerror /= OASIS_Ok )   CALL oasis_abort ( ncomp_id, 'cpl_define', 'Failure in oasis_enddef') 
     344      IF ( commRank ) THEN      
     345       
     346         CALL oasis_enddef(nerror) 
     347         IF( nerror /= OASIS_Ok )   CALL oasis_abort ( ncomp_id, 'cpl_define', 'Failure in oasis_enddef') 
     348      ENDIF 
    297349      ! 
    298350   END SUBROUTINE cpl_define 
     
    311363      REAL(wp), DIMENSION(:,:,:), INTENT(in   ) ::   pdata 
    312364      !! 
    313       INTEGER                                   ::   jc,jm     ! local loop index 
     365      INTEGER                                   ::   jn,jc,jm     ! local loop index 
    314366      !!-------------------------------------------------------------------- 
    315367      ! 
     
    320372         
    321373            IF( ssnd(kid)%nid(jc,jm) /= -1 ) THEN 
    322                CALL oasis_put ( ssnd(kid)%nid(jc,jm), kstep, pdata(nldi:nlei, nldj:nlej,jc), kinfo ) 
     374               IF ( rootexchg ) THEN 
     375                  ! 
     376                  ! collect data on the local root process 
     377                  ! 
     378                  CALL mppgather (pdata(:,:,jc),localRoot,tbuf)  
     379                  CALL mppsync  
     380            
     381                  IF ( nproc == localRoot ) THEN 
     382                                
     383                     DO jn = 1, jpnij 
     384                        exfld(nimppt(jn)-1+nldit(jn):nimppt(jn)+nleit(jn)-1,njmppt(jn)-1+nldjt(jn):njmppt(jn)+nlejt(jn)-1)= & 
     385                          tbuf(nldit(jn):nleit(jn),nldjt(jn):nlejt(jn),jn) 
     386                     ENDDO 
     387                
     388                     ! snd data to OASIS3 
     389                     CALL oasis_put ( ssnd(kid)%nid(jc,jm), kstep, exfld, kinfo ) 
     390            
     391                  ENDIF 
     392            
     393               ELSE 
     394 
     395                   ! snd data to OASIS3 
     396                   CALL oasis_put ( ssnd(kid)%nid(jc,jm), kstep, pdata(nldi:nlei, nldj:nlej,jc), kinfo ) 
     397               ENDIF 
    323398                
    324399               IF ( ln_ctl ) THEN         
     
    358433      INTEGER                   , INTENT(  out) ::   kinfo     ! OASIS3 info argument 
    359434      !! 
    360       INTEGER                                   ::   jc,jm     ! local loop index 
     435      INTEGER                                   ::   jn,jc,jm     ! local loop index 
    361436      LOGICAL                                   ::   llaction, llfisrt 
    362437      !!-------------------------------------------------------------------- 
     
    372447 
    373448            IF( srcv(kid)%nid(jc,jm) /= -1 ) THEN 
    374  
    375                CALL oasis_get ( srcv(kid)%nid(jc,jm), kstep, exfld, kinfo )          
     449                
     450               ! 
     451               ! receive data from OASIS3 
     452               ! 
     453               IF ( commRank )  CALL oasis_get ( srcv(kid)%nid(jc,jm), kstep, exfld, kinfo ) 
     454        
     455               IF ( rootexchg )  CALL MPI_BCAST ( kinfo, 1, MPI_INTEGER, localRoot, localComm, nerror )                       
    376456                
    377457               llaction =  kinfo == OASIS_Recvd   .OR. kinfo == OASIS_FromRest .OR.   & 
     
    384464                  kinfo = OASIS_Rcv 
    385465                  IF( llfisrt ) THEN  
    386                      pdata(nldi:nlei,nldj:nlej,jc) =                                 exfld(:,:) * pmask(nldi:nlei,nldj:nlej,jm) 
     466                      
     467                     IF ( rootexchg ) THEN 
     468            
     469                        ! distribute data to processes 
     470                        ! 
     471                        IF ( nproc == localRoot ) THEN 
     472 
     473                           DO jn = 1, jpnij 
     474                              tbuf(nldit(jn):nleit(jn),nldjt(jn):nlejt(jn),jn)=          & 
     475                              exfld(nimppt(jn)-1+nldit(jn):nimppt(jn)+nleit(jn)-1,njmppt(jn)-1+nldjt(jn):njmppt(jn)+nlejt(jn)-1) 
     476                              ! NOTE: we are missing combining this with pmask (see else below) 
     477                           ENDDO 
     478                
     479                        ENDIF 
     480 
     481                        CALL mppscatter (tbuf,localRoot,pdata(:,:,jc))  
     482                        CALL mppsync 
     483 
     484                     ELSE 
     485            
     486                        pdata(nldi:nlei, nldj:nlej, jc) = exfld(:,:) * pmask(nldi:nlei,nldj:nlej,jm) 
     487                
     488                     ENDIF 
     489                      
    387490                     llfisrt = .FALSE. 
    388491                  ELSE 
     
    462565#if defined key_oa3mct_v3 
    463566         CALL oasis_get_freqs(id, mop, 1, itmp, info) 
    464 #else 
     567#endif 
     568#if defined key_oasis3 
    465569         CALL oasis_get_freqs(id,      1, itmp, info) 
    466570#endif 
    467571         cpl_freq = itmp(1) 
     572#if defined key_oasis3mct 
     573         cpl_freq = namflddti( id ) 
     574#endif 
    468575      ENDIF 
    469576      ! 
     
    481588      ! 
    482589      DEALLOCATE( exfld ) 
     590      IF ( rootexchg ) DEALLOCATE ( tbuf ) 
    483591      IF (nstop == 0) THEN 
    484592         CALL oasis_terminate( nerror )          
     
    489597   END SUBROUTINE cpl_finalize 
    490598 
    491 #if ! defined key_oasis3 
     599#if ! defined key_oasis3 && ! defined key_oasis3mct 
    492600 
    493601   !!---------------------------------------------------------------------- 
  • branches/UKMO/dev_r5518_hadgem3_mct/NEMOGCM/NEMO/OPA_SRC/SBC/sbc_oce.F90

    r6557 r6558  
    3535   LOGICAL , PUBLIC ::   ln_blk_core    !: CORE bulk formulation 
    3636   LOGICAL , PUBLIC ::   ln_blk_mfs     !: MFS  bulk formulation 
    37 #if defined key_oasis3 
     37#if defined key_oasis3 || defined key_oasis3mct 
    3838   LOGICAL , PUBLIC ::   lk_oasis = .TRUE.  !: OASIS used 
    3939#else 
  • branches/UKMO/dev_r5518_hadgem3_mct/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90

    r6557 r6558  
    4141   USE timing          ! Timing 
    4242   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
     43#if defined key_oasis3 || defined key_oasis3mct 
     44   USE mod_oasis                    ! OASIS3-MCT module 
     45#endif 
    4346   USE eosbn2 
    4447   USE sbcrnf   , ONLY : l_rnfcpl 
  • branches/UKMO/dev_r5518_hadgem3_mct/NEMOGCM/NEMO/OPA_SRC/TRA/traldf_bilapg.F90

    r6557 r6558  
    330330               END DO 
    331331            ELSE 
    332                IF(lwp) WRITE(numout,*) ' ldfght: kaht= 1 or 2, here =', kaht 
    333                IF(lwp) WRITE(numout,*) '         We stop' 
    334                STOP 'ldfght' 
     332               WRITE(numout,*) ' ldfght: kaht= 1 or 2, here =', kaht 
     333               WRITE(numout,*) '         We stop' 
     334               CALL ctl_stop( 'STOP', 'ldfght : unexpected kaht value') 
    335335            ENDIF 
    336336            !                                             ! =============== 
  • branches/UKMO/dev_r5518_hadgem3_mct/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r6557 r6558  
    277277      IF( Agrif_Root() ) THEN 
    278278         IF( lk_oasis ) THEN 
    279             CALL cpl_init( "oceanx", ilocal_comm )                     ! nemo local communicator given by oasis 
     279            CALL cpl_init( "toyoce", ilocal_comm )                     ! nemo local communicator given by oasis 
    280280            CALL xios_initialize( "not used",local_comm=ilocal_comm )    ! send nemo communicator to xios 
    281281         ELSE 
     
    288288      IF( lk_oasis ) THEN 
    289289         IF( Agrif_Root() ) THEN 
    290             CALL cpl_init( "oceanx", ilocal_comm )                      ! nemo local communicator given by oasis 
     290            CALL cpl_init( "toyoce", ilocal_comm )                      ! nemo local communicator given by oasis 
    291291         ENDIF 
    292292         ! Nodes selection (control print return in cltxt) 
     
    461461      IF( lk_asminc     )   CALL asm_inc_init   ! Initialize assimilation increments 
    462462      IF(lwp) WRITE(numout,*) 'Euler time step switch is ', neuler 
     463       
     464      IF (nstop > 0) THEN 
     465        CALL CTL_STOP('STOP','Critical errors in NEMO initialisation') 
     466      END IF 
     467 
    463468      ! 
    464469   END SUBROUTINE nemo_init 
  • branches/UKMO/dev_r5518_hadgem3_mct/NEMOGCM/NEMO/OPA_SRC/step.F90

    r6557 r6558  
    346346                               CALL ctl_stop( 'step: indic < 0' ) 
    347347                               CALL dia_wri_state( 'output.abort', kstp ) 
     348                               CALL ctl_stop('STOP','NEMO failure in stp') 
    348349      ENDIF 
    349350      IF( kstp == nit000   )   THEN 
  • branches/UKMO/dev_r5518_hadgem3_mct/NEMOGCM/NEMO/OPA_SRC/wrk_nemo.F90

    r6557 r6558  
    7272   !!---------------------------------------------------------------------- 
    7373   USE par_oce        ! ocean parameters 
     74   USE lib_mpp 
    7475 
    7576   IMPLICIT NONE 
     
    483484         &      .AND. SUM( tree(ii)%ishape ) /= 0 ) 
    484485         ii = ii + 1 
    485          IF (ii > jparray) STOP   ! increase the value of jparray (should not be needed as already very big!) 
     486         IF (ii > jparray) CALL ctl_stop('STOP', 'NEMO aborted wrk_allocbase') 
     487                           ! increase the value of jparray (should not be needed as already very big!) 
    486488      END DO 
    487489       
Note: See TracChangeset for help on using the changeset viewer.