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 5407 for trunk/NEMOGCM/NEMO/OPA_SRC/IOM – NEMO

Ignore:
Timestamp:
2015-06-11T21:13:22+02:00 (9 years ago)
Author:
smasson
Message:

merge dev_r5218_CNRS17_coupling into the trunk

Location:
trunk/NEMOGCM/NEMO/OPA_SRC/IOM
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/OPA_SRC/IOM/in_out_manager.F90

    r5363 r5407  
    149149   LOGICAL       ::   lwp      = .FALSE.    !: boolean : true on the 1st processor only .OR. ln_ctl 
    150150   LOGICAL       ::   lsp_area = .TRUE.     !: to make a control print over a specific area 
     151   CHARACTER(lc) ::   cxios_context         !: context name used in xios 
    151152 
    152153   !!---------------------------------------------------------------------- 
  • trunk/NEMOGCM/NEMO/OPA_SRC/IOM/iom.F90

    r5385 r5407  
    121121      CALL set_scalar 
    122122 
    123       IF( TRIM(cdname) == "nemo" ) THEN   
     123      IF( TRIM(cdname) == TRIM(cxios_context) ) THEN   
    124124         CALL set_grid( "T", glamt, gphit )  
    125125         CALL set_grid( "U", glamu, gphiu ) 
     
    129129      ENDIF 
    130130 
    131       IF( TRIM(cdname) == "nemo_crs" ) THEN   
     131      IF( TRIM(cdname) == TRIM(cxios_context)//"_crs" ) THEN   
    132132         CALL dom_grid_crs   ! Save the parent grid information  & Switch to coarse grid domain 
    133133         ! 
     
    12121212      CALL iom_swap( cdname )   ! swap to cdname context 
    12131213      CALL xios_update_calendar(kt) 
    1214       IF( cdname /= "nemo" ) CALL iom_swap( "nemo" )   ! return back to nemo context 
     1214      IF( cdname /= TRIM(cxios_context) ) CALL iom_swap( TRIM(cxios_context) )   ! return back to nemo context 
    12151215      ! 
    12161216   END SUBROUTINE iom_setkt 
     
    12221222         CALL iom_swap( cdname )   ! swap to cdname context 
    12231223         CALL xios_context_finalize() ! finalize the context 
    1224          IF( cdname /= "nemo" ) CALL iom_swap( "nemo" )   ! return back to nemo context 
     1224         IF( cdname /= TRIM(cxios_context) ) CALL iom_swap( TRIM(cxios_context) )   ! return back to nemo context 
    12251225      ENDIF 
    12261226      ! 
     
    12911291         CASE ('T', 'W') 
    12921292            icnr = -1 ; jcnr = -1 
    1293             IF( TRIM(cdname) == "nemo_crs" ) THEN 
     1293            IF( TRIM(cdname) == TRIM(cxios_context)//"_crs" ) THEN 
    12941294               z_cnr(:,:,1) = gphif_crs ; z_cnr(:,:,2) = glamf_crs 
    12951295               z_pnt(:,:,1) = gphit_crs ; z_pnt(:,:,2) = glamt_crs 
     
    13001300         CASE ('U') 
    13011301            icnr =  0 ; jcnr = -1 
    1302             IF( TRIM(cdname) == "nemo_crs" ) THEN 
     1302            IF( TRIM(cdname) == TRIM(cxios_context)//"_crs" ) THEN 
    13031303               z_cnr(:,:,1) = gphiv_crs ; z_cnr(:,:,2) = glamv_crs 
    13041304               z_pnt(:,:,1) = gphiu_crs ; z_pnt(:,:,2) = glamu_crs 
     
    13091309         CASE ('V') 
    13101310            icnr = -1 ; jcnr =  0 
    1311             IF( TRIM(cdname) == "nemo_crs" ) THEN 
     1311            IF( TRIM(cdname) == TRIM(cxios_context)//"_crs" ) THEN 
    13121312               z_cnr(:,:,1) = gphiu_crs ; z_cnr(:,:,2) = glamu_crs 
    13131313               z_pnt(:,:,1) = gphiv_crs ; z_pnt(:,:,2) = glamv_crs 
  • trunk/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90

    r5341 r5407  
    2424   USE trdmxl_oce      ! ocean active mixed layer tracers trends variables 
    2525   USE divcur          ! hor. divergence and curl      (div & cur routines) 
    26    USE sbc_ice, ONLY : lk_lim3 
    2726 
    2827   IMPLICIT NONE 
     
    135134                     CALL iom_rstput( kt, nitrst, numrow, 'sshb'   , sshb      ) 
    136135                     ! 
    137       IF( lk_lim3 )  CALL iom_rstput( kt, nitrst, numrow, 'fse3t_b', fse3t_b(:,:,:) ) 
    138                      ! 
    139136                     CALL iom_rstput( kt, nitrst, numrow, 'un'     , un        )     ! now fields 
    140137                     CALL iom_rstput( kt, nitrst, numrow, 'vn'     , vn        ) 
     
    148145                     CALL iom_rstput( kt, nitrst, numrow, 'rhd'    , rhd       ) 
    149146#endif 
    150                   IF( lk_lim3 ) THEN 
    151                      CALL iom_rstput( kt, nitrst, numrow, 'fraqsr_1lev'  , fraqsr_1lev     ) !clem modif 
    152                   ENDIF 
    153147      IF( kt == nitrst ) THEN 
    154148         CALL iom_close( numrow )     ! close the restart file (only at last time step) 
     
    236230         CALL iom_get( numror, jpdom_autoglo, 'hdivb'  , hdivb   ) 
    237231         CALL iom_get( numror, jpdom_autoglo, 'sshb'   , sshb    ) 
    238          IF( lk_lim3 )   CALL iom_get( numror, jpdom_autoglo, 'fse3t_b', fse3t_b(:,:,:) ) 
    239232      ELSE 
    240233         neuler = 0 
     
    279272         ENDIF 
    280273 
    281          IF( lk_lim3 .AND. .NOT. lk_vvl ) THEN 
    282             DO jk = 1, jpk 
    283                fse3t_b(:,:,jk) = fse3t_n(:,:,jk) 
    284             END DO 
    285          ENDIF 
    286  
    287       ENDIF 
    288       ! 
    289       IF( lk_lim3 ) THEN 
    290          CALL iom_get( numror, jpdom_autoglo, 'fraqsr_1lev' , fraqsr_1lev ) 
    291274      ENDIF 
    292275      ! 
Note: See TracChangeset for help on using the changeset viewer.