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

Changeset 9679


Ignore:
Timestamp:
2018-05-29T16:37:04+02:00 (6 years ago)
Author:
dancopsey
Message:

Merge in r8183 version of this branch (dev_r8183_GC_couple_pkg [8730:8734])

Location:
branches/UKMO/dev_merge_2017_GC_couple_pkg/NEMOGCM/NEMO/OPA_SRC
Files:
9 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_merge_2017_GC_couple_pkg/NEMOGCM/NEMO/OPA_SRC/DIA/diawri.F90

    r9677 r9679  
    10321032      ENDIF 
    10331033#endif 
     1034 
     1035      IF (cdfile_name == "output.abort") THEN 
     1036         CALL ctl_stop('STOP', 'NEMO abort from dia_wri_state') 
     1037      END IF 
     1038        
    10341039      !  
    10351040   END SUBROUTINE dia_wri_state 
  • branches/UKMO/dev_merge_2017_GC_couple_pkg/NEMOGCM/NEMO/OPA_SRC/LBC/lib_mpp.F90

    r9677 r9679  
    974974 
    975975   SUBROUTINE mppstop 
     976    
     977   USE mod_oasis      ! coupling routines 
     978 
    976979      !!---------------------------------------------------------------------- 
    977980      !!                  ***  routine mppstop  *** 
     
    983986      !!---------------------------------------------------------------------- 
    984987      ! 
     988       
     989#if defined key_oasis3 
     990      ! If we're trying to shut down cleanly then we need to consider the fact 
     991      ! that this could be part of an MPMD configuration - we don't want to 
     992      ! leave other components deadlocked. 
     993 
     994      CALL oasis_abort(nproc,"mppstop","NEMO initiated abort") 
     995 
     996 
     997#else 
     998       
    985999      CALL mppsync 
    9861000      CALL mpi_finalize( info ) 
     1001#endif 
     1002 
    9871003      ! 
    9881004   END SUBROUTINE mppstop 
     
    19511967         ENDIF 
    19521968         CALL FLUSH( kout )  
    1953          STOP 'ctl_opn bad opening' 
     1969         CALL ctl_stop ('STOP', 'NEMO abort ctl_opn bad opening') 
    19541970      ENDIF 
    19551971      ! 
  • branches/UKMO/dev_merge_2017_GC_couple_pkg/NEMOGCM/NEMO/OPA_SRC/SBC/cpl_oasis3.F90

    r9677 r9679  
    4242   PUBLIC   cpl_freq 
    4343   PUBLIC   cpl_finalize 
     44#if defined key_mpp_mpi 
     45   INCLUDE 'mpif.h' 
     46#endif 
     47    
     48   INTEGER, PARAMETER         :: localRoot  = 0 
     49   LOGICAL                    :: commRank            ! true for ranks doing OASIS communication 
     50#if defined key_cpl_rootexchg 
     51   LOGICAL                    :: rootexchg =.true.   ! logical switch  
     52#else 
     53   LOGICAL                    :: rootexchg =.false.  ! logical switch  
     54#endif  
    4455 
    4556   INTEGER, PUBLIC            ::   OASIS_Rcv  = 1    !: return code if received field 
     
    8394 
    8495   REAL(wp), DIMENSION(:,:), ALLOCATABLE ::   exfld   ! Temporary buffer for receiving 
    85  
     96   INTEGER, PUBLIC :: localComm  
     97       
    8698   !!---------------------------------------------------------------------- 
    8799   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     
    121133      IF ( nerror /= OASIS_Ok ) & 
    122134         CALL oasis_abort (ncomp_id, 'cpl_init','Failure in oasis_get_localcomm' ) 
     135      localComm = kl_comm  
    123136      ! 
    124137   END SUBROUTINE cpl_init 
     
    373386            IF( srcv(kid)%nid(jc,jm) /= -1 ) THEN 
    374387 
    375                CALL oasis_get ( srcv(kid)%nid(jc,jm), kstep, exfld, kinfo )          
     388               CALL oasis_get ( srcv(kid)%nid(jc,jm), kstep, exfld, kinfo )    
    376389                
    377390               llaction =  kinfo == OASIS_Recvd   .OR. kinfo == OASIS_FromRest .OR.   & 
     
    463476         CALL oasis_get_freqs(id, mop, 1, itmp, info) 
    464477#else 
    465          CALL oasis_get_freqs(id,      1, itmp, info) 
    466 #endif 
    467          cpl_freq = itmp(1) 
     478!         CALL oasis_get_freqs(id,      1, itmp, info) 
     479         cpl_freq = namflddti( id ) 
     480#endif 
    468481      ENDIF 
    469482      ! 
  • branches/UKMO/dev_merge_2017_GC_couple_pkg/NEMOGCM/NEMO/OPA_SRC/SBC/geo2ocean.F90

    r9677 r9679  
    3434   PRIVATE 
    3535 
     36   PUBLIC   repcmo    ! called in sbccpl 
    3637   PUBLIC   rot_rep   ! called in sbccpl, fldread, and cyclone 
    3738   PUBLIC   geo2oce   ! called in sbccpl 
     
    5859   !!---------------------------------------------------------------------- 
    5960CONTAINS 
     61 
     62   SUBROUTINE repcmo ( pxu1, pyu1, pxv1, pyv1,   & 
     63                       px2 , py2 , kchoix  ) 
     64      !!---------------------------------------------------------------------- 
     65      !!                  ***  ROUTINE repcmo  *** 
     66      !! 
     67      !! ** Purpose :   Change vector componantes from a geographic grid to a 
     68      !!      stretched coordinates grid. 
     69      !! 
     70      !! ** Method  :   Initialization of arrays at the first call. 
     71      !! 
     72      !! ** Action  : - px2 : first  componante (defined at u point) 
     73      !!              - py2 : second componante (defined at v point) 
     74      !!---------------------------------------------------------------------- 
     75      REAL(wp), INTENT(in   ), DIMENSION(jpi,jpj) ::   pxu1, pyu1   ! geographic vector componantes at u-point 
     76      REAL(wp), INTENT(in   ), DIMENSION(jpi,jpj) ::   pxv1, pyv1   ! geographic vector componantes at v-point 
     77      REAL(wp), INTENT(  out), DIMENSION(jpi,jpj) ::   px2          ! i-componante (defined at u-point) 
     78      REAL(wp), INTENT(  out), DIMENSION(jpi,jpj) ::   py2          ! j-componante (defined at v-point) 
     79      !!---------------------------------------------------------------------- 
     80      INTEGER, INTENT( IN ) ::   & 
     81         kchoix   ! type of transformation 
     82                  ! = 1 change from geographic to model grid. 
     83                  ! =-1 change from model to geographic grid 
     84      !!---------------------------------------------------------------------- 
     85  
     86      SELECT CASE (kchoix) 
     87      CASE ( 1) 
     88        ! Change from geographic to stretched coordinate 
     89        ! ---------------------------------------------- 
     90      
     91        CALL rot_rep( pxu1, pyu1, 'U', 'en->i',px2 ) 
     92        CALL rot_rep( pxv1, pyv1, 'V', 'en->j',py2 ) 
     93      CASE (-1) 
     94       ! Change from stretched to geographic coordinate 
     95       ! ---------------------------------------------- 
     96      
     97       CALL rot_rep( pxu1, pyu1, 'U', 'ij->e',px2 ) 
     98       CALL rot_rep( pxv1, pyv1, 'V', 'ij->n',py2 ) 
     99     END SELECT 
     100      
     101   END SUBROUTINE repcmo 
    60102 
    61103   SUBROUTINE rot_rep ( pxin, pyin, cd_type, cdtodo, prot ) 
  • branches/UKMO/dev_merge_2017_GC_couple_pkg/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90

    r9677 r9679  
    219219      ALLOCATE( a_i(jpi,jpj,1) , STAT=ierr(2) )  ! used in sbcice_if.F90 (done here as there is no sbc_ice_if_init) 
    220220#endif 
    221       ALLOCATE( xcplmask(jpi,jpj,0:nn_cplmodel) , STAT=ierr(3) ) 
     221      !ALLOCATE( xcplmask(jpi,jpj,0:nn_cplmodel) , STAT=ierr(3) ) 
     222      ! Hardwire only two models as nn_cplmodel has not been read in 
     223      ! from the namelist yet. 
     224      ALLOCATE( xcplmask(jpi,jpj,0:2) , STAT=ierr(3) )    
    222225      ! 
    223226      IF( .NOT. ln_apr_dyn ) ALLOCATE( ssh_ib(jpi,jpj), ssh_ibb(jpi,jpj), apr(jpi, jpj), STAT=ierr(4) )  
     
    331334 
    332335      !                                   ! allocate sbccpl arrays 
    333       IF( sbc_cpl_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_cpl_alloc : unable to allocate arrays' ) 
     336      !IF( sbc_cpl_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_cpl_alloc : unable to allocate arrays' ) 
    334337      
    335338      ! ================================ ! 
     
    395398         srcv(jpr_otx2:jpr_otz2)%clgrid  = 'V'        !           and           V-point 
    396399         srcv(jpr_itx1:jpr_itz1)%clgrid  = 'F'        ! ice components given at F-point 
    397          srcv(jpr_otx1:jpr_otz2)%laction = .TRUE.     ! receive oce components on grid 1 & 2 
     400         !srcv(jpr_otx1:jpr_otz2)%laction = .TRUE.     ! receive oce components on grid 1 & 2 
     401! Currently needed for HadGEM3 - but shouldn't affect anyone else for the moment 
     402         srcv(jpr_otx1)%laction = .TRUE.  
     403         srcv(jpr_oty1)%laction = .TRUE. 
     404! 
    398405         srcv(jpr_itx1:jpr_itz1)%laction = .TRUE.     ! receive ice components on grid 1 only 
    399406      CASE( 'T,I' )  
     
    11001107      LOGICAL  ::   llnewtx, llnewtau      ! update wind stress components and module?? 
    11011108      INTEGER  ::   ji, jj, jn             ! dummy loop indices 
    1102       INTEGER  ::   isec                   ! number of seconds since nit000 (assuming rdt did not change since nit000) 
     1109      INTEGER  ::   isec                   ! number of seconds since nit000 (assuming rdttra did not change since nit000) 
     1110      INTEGER  ::   ikchoix 
    11031111      REAL(wp) ::   zcumulneg, zcumulpos   ! temporary scalars      
    11041112      REAL(wp) ::   zcoef                  ! temporary scalar 
     
    11061114      REAL(wp) ::   zcdrag = 1.5e-3        ! drag coefficient 
    11071115      REAL(wp) ::   zzx, zzy               ! temporary variables 
    1108       REAL(wp), DIMENSION(jpi,jpj) ::   ztx, zty, zmsk, zemp, zqns, zqsr 
     1116      REAL(wp), DIMENSION(jpi,jpj) ::   ztx, zty, zmsk, zemp, zqns, zqsr, ztx2, zty2 
    11091117      !!---------------------------------------------------------------------- 
    11101118      ! 
     
    11451153            IF( TRIM( sn_rcv_tau%clvor ) == 'eastward-northward' ) THEN   ! 2 components oriented along the local grid 
    11461154               !                                                       ! (geographical to local grid -> rotate the components) 
    1147                CALL rot_rep( frcv(jpr_otx1)%z3(:,:,1), frcv(jpr_oty1)%z3(:,:,1), srcv(jpr_otx1)%clgrid, 'en->i', ztx )    
    1148                IF( srcv(jpr_otx2)%laction ) THEN 
    1149                   CALL rot_rep( frcv(jpr_otx2)%z3(:,:,1), frcv(jpr_oty2)%z3(:,:,1), srcv(jpr_otx2)%clgrid, 'en->j', zty )    
    1150                ELSE 
    1151                   CALL rot_rep( frcv(jpr_otx1)%z3(:,:,1), frcv(jpr_oty1)%z3(:,:,1), srcv(jpr_otx1)%clgrid, 'en->j', zty )   
     1155               IF( srcv(jpr_otx1)%clgrid == 'U' .AND. (.NOT. srcv(jpr_otx2)%laction) ) THEN 
     1156                  ! Temporary code for HadGEM3 - will be removed eventually. 
     1157        ! Only applies when we have only taux on U grid and tauy on V grid 
     1158             DO jj=2,jpjm1 
     1159                DO ji=2,jpim1 
     1160                     ztx(ji,jj)=0.25*vmask(ji,jj,1)                & 
     1161                        *(frcv(jpr_otx1)%z3(ji,jj,1)+frcv(jpr_otx1)%z3(ji-1,jj,1)    & 
     1162                        +frcv(jpr_otx1)%z3(ji,jj+1,1)+frcv(jpr_otx1)%z3(ji-1,jj+1,1)) 
     1163                     zty(ji,jj)=0.25*umask(ji,jj,1)                & 
     1164                        *(frcv(jpr_oty1)%z3(ji,jj,1)+frcv(jpr_oty1)%z3(ji+1,jj,1)    & 
     1165                        +frcv(jpr_oty1)%z3(ji,jj-1,1)+frcv(jpr_oty1)%z3(ji+1,jj-1,1)) 
     1166                ENDDO 
     1167             ENDDO 
     1168                    
     1169             ikchoix = 1 
     1170             CALL repcmo (frcv(jpr_otx1)%z3(:,:,1),zty,ztx,frcv(jpr_oty1)%z3(:,:,1),ztx2,zty2,ikchoix) 
     1171             CALL lbc_lnk (ztx2,'U', -1. ) 
     1172             CALL lbc_lnk (zty2,'V', -1. ) 
     1173             frcv(jpr_otx1)%z3(:,:,1)=ztx2(:,:) 
     1174             frcv(jpr_oty1)%z3(:,:,1)=zty2(:,:) 
     1175          ELSE 
     1176             CALL rot_rep( frcv(jpr_otx1)%z3(:,:,1), frcv(jpr_oty1)%z3(:,:,1), srcv(jpr_otx1)%clgrid, 'en->i', ztx )    
     1177             frcv(jpr_otx1)%z3(:,:,1) = ztx(:,:)      ! overwrite 1st component on the 1st grid 
     1178             IF( srcv(jpr_otx2)%laction ) THEN 
     1179                CALL rot_rep( frcv(jpr_otx2)%z3(:,:,1), frcv(jpr_oty2)%z3(:,:,1), srcv(jpr_otx2)%clgrid, 'en->j', zty )    
     1180             ELSE 
     1181                CALL rot_rep( frcv(jpr_otx1)%z3(:,:,1), frcv(jpr_oty1)%z3(:,:,1), srcv(jpr_otx1)%clgrid, 'en->j', zty )  
     1182             ENDIF 
     1183          frcv(jpr_oty1)%z3(:,:,1) = zty(:,:)      ! overwrite 2nd component on the 2nd grid   
    11521184               ENDIF 
    1153                frcv(jpr_otx1)%z3(:,:,1) = ztx(:,:)      ! overwrite 1st component on the 1st grid 
    1154                frcv(jpr_oty1)%z3(:,:,1) = zty(:,:)      ! overwrite 2nd component on the 2nd grid 
    11551185            ENDIF 
    11561186            !                               
     
    21132143      ! 
    21142144      INTEGER ::   ji, jj, jl   ! dummy loop indices 
     2145      INTEGER ::   ikchoix 
    21152146      INTEGER ::   isec, info   ! local integer 
    21162147      REAL(wp) ::   zumax, zvmax 
     
    23742405         !                                                  j+1   j     -----V---F 
    23752406         ! surface velocity always sent from T point                     !       | 
    2376          !                                                        j      |   T   U 
     2407         ! [except for HadGEM3]                                   j      |   T   U 
    23772408         !                                                               |       | 
    23782409         !                                                   j    j-1   -I-------| 
     
    23862417            SELECT CASE( TRIM( sn_snd_crt%cldes ) ) 
    23872418            CASE( 'oce only'             )      ! C-grid ==> T 
    2388                DO jj = 2, jpjm1 
    2389                   DO ji = fs_2, fs_jpim1   ! vector opt. 
    2390                      zotx1(ji,jj) = 0.5 * ( un(ji,jj,1) + un(ji-1,jj  ,1) ) 
    2391                      zoty1(ji,jj) = 0.5 * ( vn(ji,jj,1) + vn(ji  ,jj-1,1) )  
     2419               IF ( TRIM( sn_snd_crt%clvgrd ) == 'T' ) THEN 
     2420                  DO jj = 2, jpjm1 
     2421                     DO ji = fs_2, fs_jpim1   ! vector opt. 
     2422                        zotx1(ji,jj) = 0.5 * ( un(ji,jj,1) + un(ji-1,jj  ,1) ) 
     2423                        zoty1(ji,jj) = 0.5 * ( vn(ji,jj,1) + vn(ji  ,jj-1,1) )  
     2424                     END DO 
    23922425                  END DO 
    2393                END DO 
     2426               ELSE 
     2427! Temporarily Changed for UKV 
     2428                  DO jj = 2, jpjm1 
     2429                     DO ji = 2, jpim1 
     2430                        zotx1(ji,jj) = un(ji,jj,1) 
     2431                        zoty1(ji,jj) = vn(ji,jj,1) 
     2432                     END DO 
     2433                  END DO 
     2434               ENDIF  
    23942435            CASE( 'weighted oce and ice' )    
    23952436               SELECT CASE ( cp_ice_msh ) 
     
    24502491                  END DO 
    24512492               CASE( 'F' )                      ! Ocean on C grid, Ice on F-point (B-grid) ==> T 
    2452                   DO jj = 2, jpjm1 
    2453                      DO ji = 2, jpim1   ! NO vector opt. 
    2454                         zotx1(ji,jj) = 0.5  * ( un(ji,jj,1)      + un(ji-1,jj  ,1) ) * zfr_l(ji,jj)   &    
    2455                            &         + 0.25 * ( u_ice(ji-1,jj-1) + u_ice(ji,jj-1)                     & 
    2456                            &                  + u_ice(ji-1,jj  ) + u_ice(ji,jj  )  ) *  fr_i(ji,jj) 
    2457                         zoty1(ji,jj) = 0.5  * ( vn(ji,jj,1)      + vn(ji  ,jj-1,1) ) * zfr_l(ji,jj)   &  
    2458                            &         + 0.25 * ( v_ice(ji-1,jj-1) + v_ice(ji,jj-1)                     & 
    2459                            &                  + v_ice(ji-1,jj  ) + v_ice(ji,jj  )  ) *  fr_i(ji,jj) 
     2493                  IF ( TRIM( sn_snd_crt%clvgrd ) == 'T' ) THEN 
     2494                     DO jj = 2, jpjm1 
     2495                        DO ji = 2, jpim1   ! NO vector opt. 
     2496                           zotx1(ji,jj) = 0.5  * ( un(ji,jj,1)      + un(ji-1,jj,1) ) * zfr_l(ji,jj)   &    
     2497                                &         + 0.25 * ( u_ice(ji-1,jj-1) + u_ice(ji,jj-1)                     & 
     2498                                &                  + u_ice(ji-1,jj  ) + u_ice(ji,jj  )  ) *  fr_i(ji,jj) 
     2499                           zoty1(ji,jj) = 0.5  * ( vn(ji,jj,1)      + vn(ji,jj-1,1) ) * zfr_l(ji,jj)   & 
     2500                                &         + 0.25 * ( v_ice(ji-1,jj-1) + v_ice(ji,jj-1)                     & 
     2501                                &                  + v_ice(ji-1,jj  ) + v_ice(ji,jj  )  ) *  fr_i(ji,jj) 
     2502                        END DO 
    24602503                     END DO 
    2461                   END DO 
     2504#if defined key_cice 
     2505                  ELSE 
     2506! Temporarily Changed for HadGEM3 
     2507                     DO jj = 2, jpjm1 
     2508                        DO ji = 2, jpim1   ! NO vector opt. 
     2509                           zotx1(ji,jj) = (1.0-fr_iu(ji,jj)) * un(ji,jj,1)             & 
     2510                                &              + fr_iu(ji,jj) * 0.5 * ( u_ice(ji,jj-1) + u_ice(ji,jj) )  
     2511                           zoty1(ji,jj) = (1.0-fr_iv(ji,jj)) * vn(ji,jj,1)             & 
     2512                                &              + fr_iv(ji,jj) * 0.5 * ( v_ice(ji-1,jj) + v_ice(ji,jj) )  
     2513                        END DO 
     2514                     END DO 
     2515#endif 
     2516                  ENDIF 
    24622517               END SELECT 
    24632518            END SELECT 
     
    24692524         IF( TRIM( sn_snd_crt%clvor ) == 'eastward-northward' ) THEN             ! Rotation of the components 
    24702525            !                                                                     ! Ocean component 
    2471             CALL rot_rep( zotx1, zoty1, ssnd(jps_ocx1)%clgrid, 'ij->e', ztmp1 )       ! 1st component  
    2472             CALL rot_rep( zotx1, zoty1, ssnd(jps_ocx1)%clgrid, 'ij->n', ztmp2 )       ! 2nd component  
    2473             zotx1(:,:) = ztmp1(:,:)                                                   ! overwrite the components  
    2474             zoty1(:,:) = ztmp2(:,:) 
    2475             IF( ssnd(jps_ivx1)%laction ) THEN                                     ! Ice component 
    2476                CALL rot_rep( zitx1, zity1, ssnd(jps_ivx1)%clgrid, 'ij->e', ztmp1 )    ! 1st component  
    2477                CALL rot_rep( zitx1, zity1, ssnd(jps_ivx1)%clgrid, 'ij->n', ztmp2 )    ! 2nd component  
    2478                zitx1(:,:) = ztmp1(:,:)                                                ! overwrite the components  
    2479                zity1(:,:) = ztmp2(:,:) 
    2480             ENDIF 
     2526            IF ( TRIM( sn_snd_crt%clvgrd ) == 'T' ) THEN 
     2527               CALL rot_rep( zotx1, zoty1, ssnd(jps_ocx1)%clgrid, 'ij->e', ztmp1 )       ! 1st component 
     2528               CALL rot_rep( zotx1, zoty1, ssnd(jps_ocx1)%clgrid, 'ij->n', ztmp2 )       ! 2nd component 
     2529               zotx1(:,:) = ztmp1(:,:)                                                   ! overwrite the components 
     2530               zoty1(:,:) = ztmp2(:,:) 
     2531               IF( ssnd(jps_ivx1)%laction ) THEN                                  ! Ice component 
     2532                  CALL rot_rep( zitx1, zity1, ssnd(jps_ivx1)%clgrid, 'ij->e', ztmp1 )    ! 1st component 
     2533                  CALL rot_rep( zitx1, zity1, ssnd(jps_ivx1)%clgrid, 'ij->n', ztmp2 )    ! 2nd component 
     2534                  zitx1(:,:) = ztmp1(:,:)                                                ! overwrite the components 
     2535                  zity1(:,:) = ztmp2(:,:) 
     2536               ENDIF 
     2537            ELSE 
     2538               ! Temporary code for HadGEM3 - will be removed eventually. 
     2539               ! Only applies when we want uvel on U grid and vvel on V grid 
     2540               ! Rotate U and V onto geographic grid before sending. 
     2541 
     2542               DO jj=2,jpjm1 
     2543                  DO ji=2,jpim1 
     2544                     ztmp1(ji,jj)=0.25*vmask(ji,jj,1)                  & 
     2545                          *(zotx1(ji,jj)+zotx1(ji-1,jj)    & 
     2546                          +zotx1(ji,jj+1)+zotx1(ji-1,jj+1)) 
     2547                     ztmp2(ji,jj)=0.25*umask(ji,jj,1)                  & 
     2548                          *(zoty1(ji,jj)+zoty1(ji+1,jj)    & 
     2549                          +zoty1(ji,jj-1)+zoty1(ji+1,jj-1)) 
     2550                  ENDDO 
     2551               ENDDO 
     2552                
     2553               ! Ensure any N fold and wrap columns are updated 
     2554               CALL lbc_lnk(ztmp1, 'V', -1.0) 
     2555               CALL lbc_lnk(ztmp2, 'U', -1.0) 
     2556                
     2557               ikchoix = -1 
     2558               CALL repcmo (zotx1,ztmp2,ztmp1,zoty1,zotx1,zoty1,ikchoix) 
     2559           ENDIF 
    24812560         ENDIF 
    24822561         ! 
  • branches/UKMO/dev_merge_2017_GC_couple_pkg/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_cice.F90

    r9677 r9679  
    269269      ENDIF 
    270270      ! 
     271      ! 
     272      ! In coupled mode get extra fields from CICE for passing back to atmosphere 
     273  
     274      IF ( ksbc == jp_purecpl ) CALL cice_sbc_hadgam(nit000) 
     275      !  
    271276   END SUBROUTINE cice_sbc_init 
    272277 
     
    669674      ENDIF 
    670675 
     676      IF( kt == nit000 )  THEN 
     677         IF(lwp) WRITE(numout,*)'cice_sbc_hadgam' 
     678         IF( sbc_cpl_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_cpl_alloc : unable to allocate arrays' ) 
     679      ENDIF 
     680 
    671681      !                                         ! =========================== ! 
    672682      !                                         !   Prepare Coupling fields   ! 
  • branches/UKMO/dev_merge_2017_GC_couple_pkg/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r9677 r9679  
    283283      !                             !* OASIS initialization 
    284284      ! 
    285       IF( lk_oasis )   CALL sbc_cpl_init( nn_ice )   ! Must be done before: (1) first time step 
    286       !                                              !                      (2) the use of nn_fsbc 
     285      IF( lk_oasis ) THEN 
     286         IF( sbc_cpl_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_cpl_alloc : unable to allocate arrays' )  
     287         CALL sbc_cpl_init( nn_ice )   ! Must be done before: (1) first time step 
     288                                       !                      (2) the use of nn_fsbc 
     289      ENDIF 
    287290      !     nn_fsbc initialization if OPA-SAS coupling via OASIS 
    288291      !     SAS time-step has to be declared in OASIS (mandatory) -> nn_fsbc has to be modified accordingly 
  • branches/UKMO/dev_merge_2017_GC_couple_pkg/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r9677 r9679  
    8686   USE lbcnfd  , ONLY : isendto, nsndto, nfsloop, nfeloop   ! Setup of north fold exchanges  
    8787   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
     88   USE sbccpl  
    8889#if defined key_iomput 
    8990   USE xios           ! xIOserver 
     
    185186         ! 
    186187         DO WHILE( istp <= nitend .AND. nstop == 0 ) 
    187             CALL stp_diurnal( istp )   ! time step only the diurnal SST  
     188            IF ( .NOT. ln_diurnal_only ) THEN  
     189               IF (lk_oasis) CALL sbc_cpl_snd( istp )  ! Coupling to atmos 
     190               CALL stp( istp )                 ! standard time stepping  
     191               ! We don't couple on the final timestep because 
     192               ! our restart file has already been written 
     193               ! and contains all the necessary data for a 
     194               ! restart. sbc_cpl_snd could be called here 
     195               ! but it would require 
     196               ! a) A test to ensure it was not performed 
     197               !    on the very last time-step 
     198               ! b) the presence of another call to 
     199               !    sbc_cpl_snd call prior to the main DO loop 
     200               ! This solution produces identical results 
     201               ! with fewer lines of code.  
     202            ELSE 
     203               CALL stp_diurnal( istp )   ! time step only the diurnal SST  
     204            ENDIF 
    188205            istp = istp + 1 
    189206         END DO 
     
    284301      IF( Agrif_Root() ) THEN 
    285302         IF( lk_oasis ) THEN 
    286             CALL cpl_init( "oceanx", ilocal_comm )                               ! nemo local communicator given by oasis 
     303            CALL cpl_init( "toyoce", ilocal_comm )                     ! nemo local communicator given by oasis 
    287304            CALL xios_initialize( "not used"       ,local_comm= ilocal_comm )    ! send nemo communicator to xios 
    288305         ELSE 
     
    295312      IF( lk_oasis ) THEN 
    296313         IF( Agrif_Root() ) THEN 
    297             CALL cpl_init( "oceanx", ilocal_comm )          ! nemo local communicator given by oasis 
     314            CALL cpl_init( "toyoce", ilocal_comm )                      ! nemo local communicator given by oasis 
    298315         ENDIF 
    299316         ! Nodes selection (control print return in cltxt) 
     
    445462      ! 
    446463      IF(lwp) WRITE(numout,cform_aaa)           ! Flag AAAAAAA 
     464       
     465      IF (nstop > 0) THEN 
     466        CALL CTL_STOP('STOP','Critical errors in NEMO initialisation') 
     467      END IF 
     468       
    447469      ! 
    448470      IF( ln_timing    )   CALL timing_stop( 'nemo_init') 
  • branches/UKMO/dev_merge_2017_GC_couple_pkg/NEMOGCM/NEMO/OPA_SRC/step.F90

    r9677 r9679  
    319319         IF(lwm)                        CALL FLUSH    ( numond )   ! flush output namelist oce 
    320320         IF(lwm .AND. numoni /= -1 )    CALL FLUSH    ( numoni )   ! flush output namelist ice (if exist) 
     321                               CALL ctl_stop('STOP','NEMO failure in stp') 
    321322      ENDIF 
    322323 
     
    324325      ! Coupled mode 
    325326      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    326 !!gm why lk_oasis and not lk_cpl ???? 
    327       IF( lk_oasis   )   CALL sbc_cpl_snd( kstp )     ! coupled mode : field exchanges 
     327      !IF( lk_oasis         )   CALL sbc_cpl_snd( kstp )     ! coupled mode : field exchanges 
    328328      ! 
    329329#if defined key_iomput 
Note: See TracChangeset for help on using the changeset viewer.