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 5955 for branches/NERC/dev_r5589_is_oce_cpl/NEMOGCM/NEMO/OPA_SRC/IOM – NEMO

Ignore:
Timestamp:
2015-11-30T17:43:24+01:00 (9 years ago)
Author:
mathiot
Message:

ice sheet coupling: merged in head of trunk (r5936)

Location:
branches/NERC/dev_r5589_is_oce_cpl/NEMOGCM/NEMO/OPA_SRC/IOM
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • branches/NERC/dev_r5589_is_oce_cpl/NEMOGCM/NEMO/OPA_SRC/IOM/iom.F90

    r5426 r5955  
    129129         ! 
    130130         IF( ln_cfmeta ) THEN   ! Add additional grid metadata 
    131             CALL iom_set_domain_attr("grid_T", area = e12t(nldi:nlei, nldj:nlej)) 
    132             CALL iom_set_domain_attr("grid_U", area = e12u(nldi:nlei, nldj:nlej)) 
    133             CALL iom_set_domain_attr("grid_V", area = e12v(nldi:nlei, nldj:nlej)) 
    134             CALL iom_set_domain_attr("grid_W", area = e12t(nldi:nlei, nldj:nlej)) 
     131            CALL iom_set_domain_attr("grid_T", area = e1e2t(nldi:nlei, nldj:nlej)) 
     132            CALL iom_set_domain_attr("grid_U", area = e1e2u(nldi:nlei, nldj:nlej)) 
     133            CALL iom_set_domain_attr("grid_V", area = e1e2v(nldi:nlei, nldj:nlej)) 
     134            CALL iom_set_domain_attr("grid_W", area = e1e2t(nldi:nlei, nldj:nlej)) 
    135135            CALL set_grid_bounds( "T", glamf, gphif, glamt, gphit ) 
    136136            CALL set_grid_bounds( "U", glamv, gphiv, glamu, gphiu ) 
     
    903903               IF( zofs /= 0. )   pv_r1d(:) = pv_r1d(:) + zofs 
    904904            ELSEIF( PRESENT(pv_r2d) ) THEN 
    905 !CDIR COLLAPSE 
    906905               IF( zscf /= 1.)   pv_r2d(:,:) = pv_r2d(:,:) * zscf 
    907 !CDIR COLLAPSE 
    908906               IF( zofs /= 0.)   pv_r2d(:,:) = pv_r2d(:,:) + zofs 
    909907            ELSEIF( PRESENT(pv_r3d) ) THEN 
    910 !CDIR COLLAPSE 
    911908               IF( zscf /= 1.)   pv_r3d(:,:,:) = pv_r3d(:,:,:) * zscf 
    912 !CDIR COLLAPSE 
    913909               IF( zofs /= 0.)   pv_r3d(:,:,:) = pv_r3d(:,:,:) + zofs 
    914910            ENDIF 
     
    11961192      CHARACTER(LEN=*),OPTIONAL , INTENT(in) ::   freq_op 
    11971193      CHARACTER(LEN=*),OPTIONAL , INTENT(in) ::   freq_offset 
    1198       IF ( xios_is_valid_field     (cdid) )   CALL xios_set_field_attr     ( cdid, freq_op=freq_op, freq_offset=freq_offset ) 
    1199       IF ( xios_is_valid_fieldgroup(cdid) )   CALL xios_set_fieldgroup_attr( cdid, freq_op=freq_op, freq_offset=freq_offset ) 
     1194      IF ( xios_is_valid_field     (cdid) )   CALL xios_set_field_attr       & 
     1195    &     ( cdid, freq_op=freq_op, freq_offset=freq_offset ) 
     1196      IF ( xios_is_valid_fieldgroup(cdid) )   CALL xios_set_fieldgroup_attr  & 
     1197    &                    ( cdid, freq_op=freq_op, freq_offset=freq_offset ) 
    12001198      CALL xios_solve_inheritance() 
    12011199   END SUBROUTINE iom_set_field_attr 
     
    16731671            END DO 
    16741672 
     1673            IF( jn == 1 .AND. TRIM(Agrif_CFixed()) /= '0' )   clname = TRIM(Agrif_CFixed())//"_"//TRIM(clname) 
    16751674            IF( jn == 1 )   CALL iom_set_file_attr( cdid, name        = clname ) 
    16761675            IF( jn == 2 )   CALL iom_set_file_attr( cdid, name_suffix = clname ) 
     
    17201719      ENDIF 
    17211720       
     1721!$AGRIF_DO_NOT_TREAT       
     1722! Should be fixed in the conv 
    17221723      IF( llfull ) THEN  
    17231724         clfmt = TRIM(clfmt)//",'_',i2.2,':',i2.2,':',i2.2" 
     
    17301731         WRITE(iom_sdate, '('//TRIM(clfmt)//')') iyear, imonth, iday                          ! date of the end of run 
    17311732      ENDIF 
     1733!$AGRIF_END_DO_NOT_TREAT       
    17321734 
    17331735   END FUNCTION iom_sdate 
  • branches/NERC/dev_r5589_is_oce_cpl/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90

    r5779 r5955  
    99   !!            3.3  !  2010-04  (M. Leclair, G. Madec)  modified LF-RA 
    1010   !!            - -  !  2010-10  (C. Ethe, G. Madec) TRC-TRA merge (T-S in 4D) 
     11   !!            3.7  !  2014-01  (G. Madec) suppression of curl and hdiv from the restart 
     12   !!             -   !  2014-12  (G. Madec) remove KPP scheme 
    1113   !!---------------------------------------------------------------------- 
    1214 
     
    1820   USE oce             ! ocean dynamics and tracers  
    1921   USE dom_oce         ! ocean space and time domain 
     22   USE sbc_ice         ! only lk_lim3  
    2023   USE phycst          ! physical constants 
     24   USE eosbn2          ! equation of state            (eos bn2 routine) 
     25   USE trdmxl_oce      ! ocean active mixed layer tracers trends variables 
     26   ! 
    2127   USE in_out_manager  ! I/O manager 
    2228   USE iom             ! I/O module 
    23    USE eosbn2          ! equation of state            (eos bn2 routine) 
    24    USE trdmxl_oce      ! ocean active mixed layer tracers trends variables 
    25    USE divcur          ! hor. divergence and curl      (div & cur routines) 
    2629 
    2730   IMPLICIT NONE 
     
    130133                     CALL iom_rstput( kt, nitrst, numrow, 'tb'     , tsb(:,:,:,jp_tem) ) 
    131134                     CALL iom_rstput( kt, nitrst, numrow, 'sb'     , tsb(:,:,:,jp_sal) ) 
    132                      CALL iom_rstput( kt, nitrst, numrow, 'rotb'   , rotb      ) 
    133                      CALL iom_rstput( kt, nitrst, numrow, 'hdivb'  , hdivb     ) 
    134135                     CALL iom_rstput( kt, nitrst, numrow, 'sshb'   , sshb      ) 
    135136                     ! 
     
    138139                     CALL iom_rstput( kt, nitrst, numrow, 'tn'     , tsn(:,:,:,jp_tem) ) 
    139140                     CALL iom_rstput( kt, nitrst, numrow, 'sn'     , tsn(:,:,:,jp_sal) ) 
    140                      CALL iom_rstput( kt, nitrst, numrow, 'rotn'   , rotn      ) 
    141                      CALL iom_rstput( kt, nitrst, numrow, 'hdivn'  , hdivn     ) 
    142141                     CALL iom_rstput( kt, nitrst, numrow, 'sshn'   , sshn      ) 
    143142                     CALL iom_rstput( kt, nitrst, numrow, 'rhop'   , rhop      ) 
    144 #if defined key_zdfkpp 
    145                      CALL iom_rstput( kt, nitrst, numrow, 'rhd'    , rhd       ) 
    146 #endif 
    147143 
    148144                  IF ( ln_iscpl ) THEN  
     
    208204   END SUBROUTINE rst_read_open 
    209205 
     206 
    210207   SUBROUTINE rst_read 
    211208      !!----------------------------------------------------------------------  
     
    237234         CALL iom_get( numror, jpdom_autoglo, 'tb'     , tsb(:,:,:,jp_tem) ) 
    238235         CALL iom_get( numror, jpdom_autoglo, 'sb'     , tsb(:,:,:,jp_sal) ) 
    239          CALL iom_get( numror, jpdom_autoglo, 'rotb'   , rotb    ) 
    240          CALL iom_get( numror, jpdom_autoglo, 'hdivb'  , hdivb   ) 
    241236         CALL iom_get( numror, jpdom_autoglo, 'sshb'   , sshb    ) 
    242237      ELSE 
     
    249244      CALL iom_get( numror, jpdom_autoglo, 'sn'     , tsn(:,:,:,jp_sal) ) 
    250245      CALL iom_get( numror, jpdom_autoglo, 'sshn'   , sshn    ) 
    251       IF( iom_varid( numror, 'rotn', ldstop = .FALSE. ) > 0 ) THEN 
    252          CALL iom_get( numror, jpdom_autoglo, 'rotn'   , rotn    ) 
    253          CALL iom_get( numror, jpdom_autoglo, 'hdivn'  , hdivn   ) 
    254       ELSE 
    255          CALL div_cur( 0 )                              ! Horizontal divergence & Relative vorticity 
    256       ENDIF 
    257246      IF( iom_varid( numror, 'rhop', ldstop = .FALSE. ) > 0 ) THEN 
    258247         CALL iom_get( numror, jpdom_autoglo, 'rhop'   , rhop    )   ! now    potential density 
     
    260249         CALL eos    ( tsn, rhd, rhop, fsdept_n(:,:,:) )    
    261250      ENDIF 
    262 #if defined key_zdfkpp 
    263       IF( iom_varid( numror, 'rhd', ldstop = .FALSE. ) > 0 ) THEN 
    264          CALL iom_get( numror, jpdom_autoglo, 'rhd'    , rhd     )   ! now    in situ density anomaly 
    265       ELSE 
    266          CALL eos( tsn, rhd, fsdept_n(:,:,:) )   ! compute rhd 
    267       ENDIF 
    268 #endif 
    269251      ! 
    270252      IF( neuler == 0 ) THEN                                  ! Euler restart (neuler=0) 
     
    272254         ub   (:,:,:)   = un   (:,:,:) 
    273255         vb   (:,:,:)   = vn   (:,:,:) 
    274          rotb (:,:,:)   = rotn (:,:,:) 
    275          hdivb(:,:,:)   = hdivn(:,:,:) 
    276256         sshb (:,:)     = sshn (:,:) 
    277  
     257         ! 
    278258         IF( lk_vvl ) THEN 
    279259            DO jk = 1, jpk 
     
    281261            END DO 
    282262         ENDIF 
    283  
     263         ! 
    284264      ENDIF 
    285265      ! 
Note: See TracChangeset for help on using the changeset viewer.