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

Changeset 15424


Ignore:
Timestamp:
2021-10-21T14:28:46+02:00 (2 years ago)
Author:
jcastill
Message:

Compiling code

Location:
NEMO/branches/UKMO/r14075_coupling_sequence/src/OCE
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/UKMO/r14075_coupling_sequence/src/OCE/IOM/iom.F90

    r14075 r15424  
    926926      CHARACTER(LEN=1)                                ::   cldmspc   ! 
    927927      LOGICAL                                         ::   llxios 
     928      REAL(wp)        , DIMENSION(1)                  ::   pvartmp 
    928929      ! 
    929930      llxios = .FALSE. 
     
    953954         IF(lwp) WRITE(numout,*) 'XIOS RST READ (0D): ', trim(cdvar) 
    954955         CALL iom_swap( TRIM(crxios_context) ) 
    955          CALL xios_recv_field( trim(cdvar), pvar) 
     956         pvartmp(:) = pvar  
     957         CALL xios_recv_field( trim(cdvar), pvartmp) 
    956958         CALL iom_swap( TRIM(cxios_context) ) 
    957959#else 
  • NEMO/branches/UKMO/r14075_coupling_sequence/src/OCE/LBC/lib_mpp.F90

    r14075 r15424  
    673673      !! 
    674674      !!---------------------------------------------------------------------- 
     675#if defined key_oasis3  
     676      USE mod_oasis      ! coupling routines  
     677#endif 
     678 
    675679      LOGICAL, OPTIONAL, INTENT(in) :: ld_abort    ! source process number 
    676680      LOGICAL ::   ll_abort 
     
    684688         CALL mpi_abort( MPI_COMM_WORLD ) 
    685689      ELSE 
     690#if defined key_oasis3    
     691         ! If we're trying to shut down cleanly then we need to consider the fact    
     692         ! that this could be part of an MPMD configuration - we don't want to    
     693         ! leave other components deadlocked.    
     694         CALL oasis_abort(nproc,"mppstop","NEMO initiated abort")    
     695#else 
    686696         CALL mppsync 
    687697         CALL mpi_finalize( info ) 
    688       ENDIF 
    689 #endif 
    690       IF( ll_abort ) STOP 123 
     698#endif  
     699      ENDIF  
     700#endif  
     701      IF( ll_abort ) CALL ctl_stop ('STOP', 'NEMO abort mppstop') 
    691702      ! 
    692703   END SUBROUTINE mppstop 
  • NEMO/branches/UKMO/r14075_coupling_sequence/src/OCE/SBC/sbccpl.F90

    r14075 r15424  
    236236      ALLOCATE( a_i(jpi,jpj,1) , STAT=ierr(2) )  ! used in sbcice_if.F90 (done here as there is no sbc_ice_if_init) 
    237237#endif 
    238       ALLOCATE( xcplmask(jpi,jpj,0:nn_cplmodel) , STAT=ierr(3) ) 
     238      !ALLOCATE( xcplmask(jpi,jpj,nn_cplmodel) , STAT=ierr(3) )      
     239      ! Hardwire three models as nn_cplmodel has not been read in from the namelist yet.      
     240      ALLOCATE( xcplmask(jpi,jpj,0:3) , STAT=ierr(3) ) 
    239241#if defined key_si3 || defined key_cice 
    240242      ALLOCATE( a_i_last_couple(jpi,jpj,jpl) , STAT=ierr(4) ) 
     
    354356 
    355357      !                                   ! allocate sbccpl arrays 
    356       IF( sbc_cpl_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_cpl_alloc : unable to allocate arrays' ) 
     358!      IF( sbc_cpl_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_cpl_alloc : unable to allocate arrays' ) 
    357359      
    358360      ! ================================ ! 
  • NEMO/branches/UKMO/r14075_coupling_sequence/src/OCE/SBC/sbcice_cice.F90

    r14075 r15424  
    269269      ENDIF 
    270270      ! 
     271      ! In coupled mode get extra fields from CICE for passing back to atmosphere    
     272      IF ( ksbc == jp_purecpl ) CALL cice_sbc_hadgam(nit000)    
     273      ! 
    271274   END SUBROUTINE cice_sbc_init 
    272275 
     
    664667      !!--------------------------------------------------------------------- 
    665668      ! 
    666       IF( kt == nit000 )  THEN 
    667          IF(lwp) WRITE(numout,*)'cice_sbc_hadgam' 
    668          IF( sbc_cpl_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_cpl_alloc : unable to allocate arrays' ) 
    669       ENDIF 
    670  
    671669      !                                         ! =========================== ! 
    672670      !                                         !   Prepare Coupling fields   ! 
  • NEMO/branches/UKMO/r14075_coupling_sequence/src/OCE/SBC/sbcmod.F90

    r14075 r15424  
    303303      !                             !* OASIS initialization 
    304304      ! 
    305       IF( lk_oasis )   CALL sbc_cpl_init( nn_ice )   ! Must be done before: (1) first time step 
    306       !                                              !                      (2) the use of nn_fsbc 
     305      IF( lk_oasis ) THEN    
     306         IF( sbc_cpl_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_cpl_alloc : unable to allocate arrays' )     
     307         CALL sbc_cpl_init( nn_ice )   ! Must be done before: (1) first time step    
     308                                       ! (2) the use of nn_fsbc    
     309      ENDIF 
    307310      !     nn_fsbc initialization if OPA-SAS coupling via OASIS 
    308311      !     SAS time-step has to be declared in OASIS (mandatory) -> nn_fsbc has to be modified accordingly 
  • NEMO/branches/UKMO/r14075_coupling_sequence/src/OCE/nemogcm.F90

    r14075 r15424  
    8787   USE lbcnfd  , ONLY : isendto, nsndto, nfsloop, nfeloop   ! Setup of north fold exchanges  
    8888   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
     89   USE sbccpl 
    8990#if defined key_iomput 
    9091   USE xios           ! xIOserver 
     
    192193            ENDIF 
    193194             
     195            IF (lk_oasis) CALL sbc_cpl_snd( istp )  ! Coupling to atmos 
    194196            CALL stp        ( istp )  
     197            ! We don't couple on the final timestep because    
     198            ! our restart file has already been written    
     199            ! and contains all the necessary data for a    
     200            ! restart. sbc_cpl_snd could be called here    
     201            ! but it would require    
     202            ! a) A test to ensure it was not performed    
     203            !    on the very last time-step    
     204            ! b) the presence of another call to    
     205            !    sbc_cpl_snd call prior to the main DO loop    
     206            ! This solution produces identical results    
     207            ! with fewer lines of code. 
    195208            istp = istp + 1 
    196209 
     
    499512      ! 
    500513      IF(lwp) WRITE(numout,cform_aaa)           ! Flag AAAAAAA 
     514      !  
     515      IF (nstop > 0) THEN    
     516        CALL CTL_STOP('STOP','Critical errors in NEMO initialisation')    
     517      END IF 
    501518      ! 
    502519      IF( ln_timing    )   CALL timing_stop( 'nemo_init') 
  • NEMO/branches/UKMO/r14075_coupling_sequence/src/OCE/step.F90

    r14075 r15424  
    286286      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    287287                         CALL stp_ctl      ( kstp ) 
     288 
     289      IF( nstop > 0  ) THEN  
     290                         CALL ctl_stop('STOP','NEMO failure in stp')  
     291      ENDIF 
    288292                          
    289293#if defined key_agrif 
     
    311315      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    312316!!gm why lk_oasis and not lk_cpl ???? 
    313       IF( lk_oasis .AND. nstop == 0 )   CALL sbc_cpl_snd( kstp )     ! coupled mode : field exchanges 
     317!      IF( lk_oasis .AND. nstop == 0 )   CALL sbc_cpl_snd( kstp )     ! coupled mode : field exchanges 
    314318      ! 
    315319#if defined key_iomput 
Note: See TracChangeset for help on using the changeset viewer.