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 7351 for branches/2016/dev_INGV_UKMO_2016/NEMOGCM/NEMO/OPA_SRC/IOM – NEMO

Ignore:
Timestamp:
2016-11-28T17:04:10+01:00 (7 years ago)
Author:
emanuelaclementi
Message:

ticket #1805 step 3: /2016/dev_INGV_UKMO_2016 aligned to the trunk at revision 7161

Location:
branches/2016/dev_INGV_UKMO_2016/NEMOGCM/NEMO/OPA_SRC/IOM
Files:
2 deleted
5 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_INGV_UKMO_2016/NEMOGCM/NEMO/OPA_SRC/IOM/in_out_manager.F90

    r5518 r7351  
    1313   !!---------------------------------------------------------------------- 
    1414   USE par_oce       ! ocean parameter 
    15    USE lib_print     ! formated print library 
    1615   USE nc4interface  ! NetCDF4 interface 
    1716 
     
    3736   INTEGER       ::   nn_itend         !: index of the last time step 
    3837   INTEGER       ::   nn_date0         !: initial calendar date aammjj 
     38   INTEGER       ::   nn_time0         !: initial time of day in hhmm 
    3939   INTEGER       ::   nn_leapy         !: Leap year calendar flag (0/1 or 30) 
    4040   INTEGER       ::   nn_istate        !: initial state output flag (0/1) 
     
    4242   INTEGER       ::   nn_stock         !: restart file frequency 
    4343   INTEGER, DIMENSION(10) :: nn_stocklist  !: restart dump times 
    44    LOGICAL       ::   ln_dimgnnn       !: type of dimgout. (F): 1 file for all proc 
    45                                                        !:                  (T): 1 file per proc 
    4644   LOGICAL       ::   ln_mskland       !: mask land points in NetCDF outputs (costly: + ~15%) 
    4745   LOGICAL       ::   ln_cfmeta        !: output additional data to netCDF files required for compliance with the CF metadata standard 
     
    9997   LOGICAL ::   ln_ctl       !: run control for debugging 
    10098   INTEGER ::   nn_timing    !: run control for timing 
     99   INTEGER ::   nn_diacfl    !: flag whether to create CFL diagnostics 
    101100   INTEGER ::   nn_print     !: level of print (0 no print) 
    102101   INTEGER ::   nn_ictls     !: Start i indice for the SUM control 
  • branches/2016/dev_INGV_UKMO_2016/NEMOGCM/NEMO/OPA_SRC/IOM/iom.F90

    r5836 r7351  
    88   !!            3.0  ! 2007-07  (D. Storkey) Changes to iom_gettime 
    99   !!            3.4  ! 2012-12  (R. Bourdalle-Badie and G. Reffray)  add C1D case   
     10   !!            3.6  ! 2014-15  DIMG format removed 
    1011   !!-------------------------------------------------------------------- 
    1112 
     
    2324   USE lbclnk          ! lateal boundary condition / mpp exchanges 
    2425   USE iom_def         ! iom variables definitions 
    25    USE iom_ioipsl      ! NetCDF format with IOIPSL library 
    2626   USE iom_nf90        ! NetCDF format with native NetCDF library 
    27    USE iom_rstdimg     ! restarts access direct format "dimg" style... 
    2827   USE in_out_manager  ! I/O manager 
    2928   USE lib_mpp           ! MPP library 
     
    115114      CASE (30)   ;   CALL xios_set_context_attr(TRIM(clname), calendar_type= "D360") 
    116115      END SELECT 
    117       WRITE(cldate,"(i4.4,'-',i2.2,'-',i2.2,' 00:00:00')") nyear,nmonth,nday  
     116      WRITE(cldate,"(i4.4,'-',i2.2,'-',i2.2,' ',i2.2,':',i2.2,':00')") nyear,nmonth,nday,nhour,nminute 
    118117      CALL xios_set_context_attr(TRIM(clname), start_date=cldate ) 
    119118 
     
    246245      CHARACTER(LEN=256)    ::   clname    ! the name of the file based on cdname [[+clcpu]+clcpu] 
    247246      CHARACTER(LEN=256)    ::   cltmpn    ! tempory name to store clname (in writting mode) 
    248       CHARACTER(LEN=10)     ::   clsuffix  ! ".nc" or ".dimg" 
     247      CHARACTER(LEN=10)     ::   clsuffix  ! ".nc"  
    249248      CHARACTER(LEN=15)     ::   clcpu     ! the cpu number (max jpmax_digits digits) 
    250249      CHARACTER(LEN=256)    ::   clinfo    ! info character 
     
    309308      ! which suffix should we use? 
    310309      SELECT CASE (iolib) 
    311       CASE (jpioipsl ) ;   clsuffix = '.nc' 
    312310      CASE (jpnf90   ) ;   clsuffix = '.nc' 
    313       CASE (jprstdimg) ;   clsuffix = '.dimg' 
    314311      CASE DEFAULT     ;   clsuffix = '' 
    315          CALL ctl_stop( TRIM(clinfo), 'accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     312         CALL ctl_stop( TRIM(clinfo), 'accepted IO library is only jpnf90 (jpioipsl option has been removed) ' ) 
    316313      END SELECT 
    317314      ! Add the suffix if needed 
     
    326323      IF( .NOT.llok ) THEN 
    327324         ! we try to add the cpu number to the name 
    328          IF( iolib == jprstdimg ) THEN   ;   WRITE(clcpu,*) narea 
    329          ELSE                            ;   WRITE(clcpu,*) narea-1 
    330          ENDIF 
     325         WRITE(clcpu,*) narea-1 
     326 
    331327         clcpu  = TRIM(ADJUSTL(clcpu)) 
    332328         iln = INDEX(clname,TRIM(clsuffix), back = .TRUE.) 
     
    375371         END SELECT 
    376372      ENDIF 
    377       ! Open the NetCDF or RSTDIMG file 
     373      ! Open the NetCDF file 
    378374      ! ============= 
    379375      ! do we have some free file identifier? 
     
    399395      IF( istop == nstop ) THEN   ! no error within this routine 
    400396         SELECT CASE (iolib) 
    401          CASE (jpioipsl )   ;   CALL iom_ioipsl_open(  clname, kiomid, llwrt, llok, idompar ) 
    402397         CASE (jpnf90   )   ;   CALL iom_nf90_open(    clname, kiomid, llwrt, llok, idompar ) 
    403          CASE (jprstdimg)   ;   CALL iom_rstdimg_open( clname, kiomid, llwrt, llok, idompar ) 
    404398         CASE DEFAULT 
    405             CALL ctl_stop( TRIM(clinfo)//' accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     399            CALL ctl_stop( TRIM(clinfo)//' accepted IO library is only jpnf90 (jpioipsl option has been removed) ' ) 
    406400         END SELECT 
    407401      ENDIF 
     
    438432            IF( iom_file(jf)%nfid > 0 ) THEN 
    439433               SELECT CASE (iom_file(jf)%iolib) 
    440                CASE (jpioipsl )   ;   CALL iom_ioipsl_close(  jf ) 
    441434               CASE (jpnf90   )   ;   CALL iom_nf90_close(    jf ) 
    442                CASE (jprstdimg)   ;   CALL iom_rstdimg_close( jf ) 
    443435               CASE DEFAULT 
    444                   CALL ctl_stop( TRIM(clinfo)//' accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     436                  CALL ctl_stop( TRIM(clinfo)//' accepted IO library is only jpnf90 (jpioipsl option has been removed)' ) 
    445437               END SELECT 
    446438               iom_file(jf)%nfid       = 0          ! free the id  
     
    497489               IF( iiv <= jpmax_vars ) THEN 
    498490                  SELECT CASE (iom_file(kiomid)%iolib) 
    499                   CASE (jpioipsl )   ;   iom_varid = iom_ioipsl_varid( kiomid, cdvar, iiv, kdimsz ) 
    500491                  CASE (jpnf90   )   ;   iom_varid = iom_nf90_varid  ( kiomid, cdvar, iiv, kdimsz, kndims ) 
    501                   CASE (jprstdimg)   ;   iom_varid = -1   ! all variables are listed in iom_file 
    502                   CASE DEFAULT    
    503                      CALL ctl_stop( TRIM(clinfo)//' accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     492                  CASE DEFAULT 
     493                     CALL ctl_stop( TRIM(clinfo)//' accepted IO library is only jpnf90 (jpioipsl option has been removed)' ) 
    504494                  END SELECT 
    505495               ELSE 
     
    559549                                 &                         'Use ncwa -a to suppress the unnecessary dimensions' ) 
    560550            SELECT CASE (iom_file(kiomid)%iolib) 
    561             CASE (jpioipsl )   ;   CALL iom_ioipsl_get(  kiomid, idvar, pvar, itime ) 
    562551            CASE (jpnf90   )   ;   CALL iom_nf90_get(    kiomid, idvar, pvar, itime ) 
    563             CASE (jprstdimg)   ;   CALL iom_rstdimg_get( kiomid, idvar, pvar ) 
    564             CASE DEFAULT     
    565                CALL ctl_stop( 'iom_g0d: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     552            CASE DEFAULT 
     553               CALL ctl_stop( 'iom_g0d: accepted IO library is only jpnf90 (jpioipsl option has been removed)' ) 
    566554            END SELECT 
    567555         ENDIF 
     
    673661      CHARACTER(LEN=256)             ::   clname      ! file name 
    674662      CHARACTER(LEN=1)               ::   clrankpv, cldmspc      !  
     663      LOGICAL                        ::   ll_depth_spec ! T => if kstart, kcount present then *only* use values for 3rd spatial dimension. 
    675664      !--------------------------------------------------------------------- 
    676665      ! 
     
    685674      IF( PRESENT(kcount) .AND. (.NOT. PRESENT(kstart)) ) CALL ctl_stop(trim(clinfo), 'kcount present needs kstart present') 
    686675      IF( PRESENT(kstart) .AND. (.NOT. PRESENT(kcount)) ) CALL ctl_stop(trim(clinfo), 'kstart present needs kcount present') 
    687       IF( PRESENT(kstart) .AND. idom /= jpdom_unknown   ) CALL ctl_stop(trim(clinfo), 'kstart present needs kdom = jpdom_unknown') 
     676      IF( PRESENT(kstart) .AND. idom /= jpdom_unknown .AND.  idom /= jpdom_autoglo_xy  ) & 
     677     &           CALL ctl_stop(trim(clinfo), 'kstart present needs kdom = jpdom_unknown or kdom = jpdom_autoglo_xy') 
    688678 
    689679      luse_jattr = .false. 
     
    694684      IF( luse_jattr ) THEN 
    695685         SELECT CASE (iom_file(kiomid)%iolib) 
    696          CASE (jpioipsl, jprstdimg ) 
    697              CALL ctl_warn(trim(clinfo), 'lrowattr present and true but this only works with netcdf (jpnf90)') 
    698              luse_jattr = .false. 
    699686         CASE (jpnf90   )    
    700687             ! Ok 
    701688         CASE DEFAULT     
    702             CALL ctl_stop( TRIM(clinfo)//' accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     689            CALL ctl_stop( TRIM(clinfo)//' accepted IO library is only jpnf90 (jpioipsl option has been removed)' ) 
    703690         END SELECT 
    704691      ENDIF 
     
    718705         ! update idom definition... 
    719706         ! Identify the domain in case of jpdom_auto(glo/dta) definition 
     707         IF( idom == jpdom_autoglo_xy ) THEN 
     708            ll_depth_spec = .TRUE. 
     709            idom = jpdom_autoglo 
     710         ELSE 
     711            ll_depth_spec = .FALSE. 
     712         ENDIF 
    720713         IF( idom == jpdom_autoglo .OR. idom == jpdom_autodta ) THEN             
    721714            IF( idom == jpdom_autoglo ) THEN   ;   idom = jpdom_global  
     
    771764         istart(idmspc+1) = itime 
    772765 
    773          IF(              PRESENT(kstart)      ) THEN ; istart(1:idmspc) = kstart(1:idmspc) ; icnt(1:idmspc) = kcount(1:idmspc) 
     766         IF( PRESENT(kstart) .AND. .NOT. ll_depth_spec ) THEN ; istart(1:idmspc) = kstart(1:idmspc) ; icnt(1:idmspc) = kcount(1:idmspc) 
    774767         ELSE 
    775             IF(           idom == jpdom_unknown ) THEN                                       ; icnt(1:idmspc) = idimsz(1:idmspc) 
     768            IF(           idom == jpdom_unknown ) THEN                                                ; icnt(1:idmspc) = idimsz(1:idmspc) 
    776769            ELSE  
    777770               IF( .NOT. PRESENT(pv_r1d) ) THEN   !   not a 1D array 
     
    796789                  ENDIF 
    797790                  IF( PRESENT(pv_r3d) ) THEN 
    798                      IF( idom == jpdom_data ) THEN   ; icnt(3) = jpkdta 
    799                      ELSE                            ; icnt(3) = jpk 
     791                     IF( idom == jpdom_data ) THEN                                  ; icnt(3) = jpkdta 
     792                     ELSE IF( ll_depth_spec .AND. PRESENT(kstart) ) THEN            ; istart(3) = kstart(3); icnt(3) = kcount(3) 
     793                     ELSE                                                           ; icnt(3) = jpk 
    800794                     ENDIF 
    801795                  ENDIF 
     
    866860       
    867861         SELECT CASE (iom_file(kiomid)%iolib) 
    868          CASE (jpioipsl )   ;   CALL iom_ioipsl_get(  kiomid, idvar, inbdim, istart, icnt, ix1, ix2, iy1, iy2,   & 
    869             &                                         pv_r1d, pv_r2d, pv_r3d ) 
    870862         CASE (jpnf90   )   ;   CALL iom_nf90_get(    kiomid, idvar, inbdim, istart, icnt, ix1, ix2, iy1, iy2,   & 
    871863            &                                         pv_r1d, pv_r2d, pv_r3d ) 
    872          CASE (jprstdimg)   ;   CALL iom_rstdimg_get( kiomid, idom, idvar, ix1, ix2, iy1, iy2,   & 
    873             &                                         pv_r1d, pv_r2d, pv_r3d ) 
    874          CASE DEFAULT     
    875             CALL ctl_stop( TRIM(clinfo)//' accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     864         CASE DEFAULT 
     865            CALL ctl_stop( TRIM(clinfo)//' accepted IO library is only jpnf90 (jpioipsl option has been removed)' ) 
    876866         END SELECT 
    877867 
     
    956946                  IF( iom_file(kiomid)%dimsz(1,idvar) <= size(ptime) ) THEN 
    957947                     SELECT CASE (iom_file(kiomid)%iolib) 
    958                      CASE (jpioipsl )   ;   CALL iom_ioipsl_gettime( kiomid, idvar, ptime, cdunits, cdcalendar ) 
    959948                     CASE (jpnf90   )   ;   CALL iom_nf90_gettime(   kiomid, idvar, ptime, cdunits, cdcalendar ) 
    960                      CASE (jprstdimg)   ;   CALL ctl_stop( TRIM(clinfo)//' case IO library == jprstdimg not coded...' ) 
    961                      CASE DEFAULT     
    962                         CALL ctl_stop( TRIM(clinfo)//' accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     949                     CASE DEFAULT 
     950                        CALL ctl_stop( TRIM(clinfo)//' accepted IO library is only jpnf90 (jpioipsl option has been removed)' ) 
    963951                     END SELECT 
    964952                  ELSE 
     
    991979         IF( iom_file(kiomid)%nfid > 0 ) THEN 
    992980            SELECT CASE (iom_file(kiomid)%iolib) 
    993             CASE (jpioipsl )   ;   CALL ctl_stop('iom_getatt: only nf90 available') 
    994981            CASE (jpnf90   )   ;   CALL iom_nf90_getatt( kiomid, cdatt, pvar ) 
    995             CASE (jprstdimg)   ;   CALL ctl_stop('iom_getatt: only nf90 available') 
    996             CASE DEFAULT     
    997                CALL ctl_stop( 'iom_g0d_att: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     982            CASE DEFAULT 
     983               CALL ctl_stop( 'iom_g0d_att: accepted IO library is only jpnf90' ) 
    998984            END SELECT 
    999985         ENDIF 
     
    10171003            ivid = iom_varid( kiomid, cdvar, ldstop = .FALSE. ) 
    10181004            SELECT CASE (iom_file(kiomid)%iolib) 
    1019             CASE (jpioipsl )   ;   CALL iom_ioipsl_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r0d = pvar ) 
    10201005            CASE (jpnf90   )   ;   CALL iom_nf90_rstput(   kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r0d = pvar ) 
    1021             CASE (jprstdimg)   ;   IF( kt == kwrite )    CALL iom_rstdimg_rstput( kiomid, cdvar, ivid, pvar ) 
    1022             CASE DEFAULT      
    1023                CALL ctl_stop( 'iom_rp0d: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     1006            CASE DEFAULT 
     1007               CALL ctl_stop( 'iom_rp0d: accepted IO library is only jpnf90 (jpioipsl option has been removed)' ) 
    10241008            END SELECT 
    10251009         ENDIF 
     
    10391023            ivid = iom_varid( kiomid, cdvar, ldstop = .FALSE. ) 
    10401024            SELECT CASE (iom_file(kiomid)%iolib) 
    1041             CASE (jpioipsl )   ;   CALL iom_ioipsl_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r1d = pvar ) 
    10421025            CASE (jpnf90   )   ;   CALL iom_nf90_rstput(   kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r1d = pvar ) 
    1043             CASE (jprstdimg)   ;   IF( kt == kwrite )    CALL iom_rstdimg_rstput( kiomid, cdvar, ivid, pv_r1d = pvar ) 
    1044             CASE DEFAULT      
    1045                CALL ctl_stop( 'iom_rp1d: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     1026            CASE DEFAULT 
     1027               CALL ctl_stop( 'iom_rp1d: accepted IO library is only jpnf90 (jpioipsl option has been removed)' ) 
    10461028            END SELECT 
    10471029         ENDIF 
     
    10611043            ivid = iom_varid( kiomid, cdvar, ldstop = .FALSE. ) 
    10621044            SELECT CASE (iom_file(kiomid)%iolib) 
    1063             CASE (jpioipsl )   ;   CALL iom_ioipsl_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r2d = pvar ) 
    10641045            CASE (jpnf90   )   ;   CALL iom_nf90_rstput(   kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r2d = pvar ) 
    1065             CASE (jprstdimg)   ;   IF( kt == kwrite )   CALL iom_rstdimg_rstput( kiomid, cdvar, ivid, pv_r2d = pvar )  
    1066             CASE DEFAULT      
    1067                CALL ctl_stop( 'iom_rp2d: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     1046            CASE DEFAULT 
     1047               CALL ctl_stop( 'iom_rp2d: accepted IO library is only jpnf90 (jpioipsl option has been removed)' ) 
    10681048            END SELECT 
    10691049         ENDIF 
     
    10831063            ivid = iom_varid( kiomid, cdvar, ldstop = .FALSE. ) 
    10841064            SELECT CASE (iom_file(kiomid)%iolib) 
    1085             CASE (jpioipsl )   ;   CALL iom_ioipsl_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r3d = pvar ) 
    10861065            CASE (jpnf90   )   ;   CALL iom_nf90_rstput(   kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r3d = pvar ) 
    1087             CASE (jprstdimg)   ;   IF( kt == kwrite )   CALL iom_rstdimg_rstput( kiomid, cdvar, ivid, pv_r3d = pvar ) 
    1088             CASE DEFAULT      
    1089                CALL ctl_stop( 'iom_rp3d: accepted IO library are only jpioipsl and jprstdimg' ) 
     1066            CASE DEFAULT 
     1067               CALL ctl_stop( 'iom_rp3d: accepted IO library is only jpnf90 (jpioipsl option has been removed)' ) 
    10901068            END SELECT 
    10911069         ENDIF 
     
    16451623            idx = INDEX(clname,'@startdate@') + INDEX(clname,'@STARTDATE@') 
    16461624            DO WHILE ( idx /= 0 )  
    1647                cldate = iom_sdate( fjulday - rdttra(1) / rday ) 
     1625               cldate = iom_sdate( fjulday - rdt / rday ) 
    16481626               clname = clname(1:idx-1)//TRIM(cldate)//clname(idx+11:LEN_TRIM(clname)) 
    16491627               idx = INDEX(clname,'@startdate@') + INDEX(clname,'@STARTDATE@') 
     
    16521630            idx = INDEX(clname,'@startdatefull@') + INDEX(clname,'@STARTDATEFULL@') 
    16531631            DO WHILE ( idx /= 0 )  
    1654                cldate = iom_sdate( fjulday - rdttra(1) / rday, ldfull = .TRUE. ) 
     1632               cldate = iom_sdate( fjulday - rdt / rday, ldfull = .TRUE. ) 
    16551633               clname = clname(1:idx-1)//TRIM(cldate)//clname(idx+15:LEN_TRIM(clname)) 
    16561634               idx = INDEX(clname,'@startdatefull@') + INDEX(clname,'@STARTDATEFULL@') 
     
    16591637            idx = INDEX(clname,'@enddate@') + INDEX(clname,'@ENDDATE@') 
    16601638            DO WHILE ( idx /= 0 )  
    1661                cldate = iom_sdate( fjulday + rdttra(1) / rday * REAL( nitend - nit000, wp ), ld24 = .TRUE. ) 
     1639               cldate = iom_sdate( fjulday + rdt / rday * REAL( nitend - nit000, wp ), ld24 = .TRUE. ) 
    16621640               clname = clname(1:idx-1)//TRIM(cldate)//clname(idx+9:LEN_TRIM(clname)) 
    16631641               idx = INDEX(clname,'@enddate@') + INDEX(clname,'@ENDDATE@') 
     
    16661644            idx = INDEX(clname,'@enddatefull@') + INDEX(clname,'@ENDDATEFULL@') 
    16671645            DO WHILE ( idx /= 0 )  
    1668                cldate = iom_sdate( fjulday + rdttra(1) / rday * REAL( nitend - nit000, wp ), ld24 = .TRUE., ldfull = .TRUE. ) 
     1646               cldate = iom_sdate( fjulday + rdt / rday * REAL( nitend - nit000, wp ), ld24 = .TRUE., ldfull = .TRUE. ) 
    16691647               clname = clname(1:idx-1)//TRIM(cldate)//clname(idx+13:LEN_TRIM(clname)) 
    16701648               idx = INDEX(clname,'@enddatefull@') + INDEX(clname,'@ENDDATEFULL@') 
  • branches/2016/dev_INGV_UKMO_2016/NEMOGCM/NEMO/OPA_SRC/IOM/iom_def.F90

    r4205 r7351  
    99   !!--------------------------------------------------------------------------------- 
    1010   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
    11    !! $Id$  
     11   !! $Id$ 
    1212   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    1313   !!--------------------------------------------------------------------------------- 
     
    2626   INTEGER, PARAMETER, PUBLIC ::   jpdom_unknown       = 7   !: No dimension checking 
    2727   INTEGER, PARAMETER, PUBLIC ::   jpdom_autoglo       = 8   !:  
    28    INTEGER, PARAMETER, PUBLIC ::   jpdom_autodta       = 9   !:  
     28   INTEGER, PARAMETER, PUBLIC ::   jpdom_autoglo_xy    = 9   !: Automatically set horizontal dimensions only 
     29   INTEGER, PARAMETER, PUBLIC ::   jpdom_autodta       = 10  !:  
    2930 
    30    INTEGER, PARAMETER, PUBLIC ::   jpioipsl    = 100      !: Use ioipsl (fliocom only) library 
    3131   INTEGER, PARAMETER, PUBLIC ::   jpnf90      = 101      !: Use nf90 library 
    32    INTEGER, PARAMETER, PUBLIC ::   jprstdimg   = 102      !: Use restart dimgs (fortran direct acces) library 
    33 #if defined key_dimgout 
    34    INTEGER, PARAMETER, PUBLIC ::   jprstlib  = jprstdimg  !: restarts io library 
    35 #else 
     32 
    3633   INTEGER, PARAMETER, PUBLIC ::   jprstlib  = jpnf90     !: restarts io library 
    37 #endif 
    3834 
    3935   INTEGER, PARAMETER, PUBLIC ::   jp_r8    = 200      !: write REAL(8) 
     
    5450      CHARACTER(LEN=240)                        ::   name     !: name of the file 
    5551      INTEGER                                   ::   nfid     !: identifier of the file (0 if closed) 
    56       INTEGER                                   ::   iolib    !: library used to read the file (jpioipsl, jpnf90 or jprstdimg) 
     52      INTEGER                                   ::   iolib    !: library used to read the file (jpnf90 or new formats, 
     53                                                              !: jpioipsl option has been removed) 
    5754      INTEGER                                   ::   nvars    !: number of identified varibles in the file 
    5855      INTEGER                                   ::   iduld    !: id of the unlimited dimension 
     56      INTEGER                                   ::   lenuld   !: length of the unlimited dimension (number of records in file) 
    5957      INTEGER                                   ::   irec     !: writing record position   
    6058      CHARACTER(LEN=32)                         ::   uldname  !: name of the unlimited dimension 
  • branches/2016/dev_INGV_UKMO_2016/NEMOGCM/NEMO/OPA_SRC/IOM/iom_nf90.F90

    r5341 r7351  
    154154         CALL iom_nf90_check(NF90_Inquire(if90id, unlimitedDimId = iom_file(kiomid)%iduld), clinfo) 
    155155         IF ( iom_file(kiomid)%iduld .GE. 0 ) THEN 
    156            CALL iom_nf90_check(NF90_Inquire_Dimension(if90id, iom_file(kiomid)%iduld,   & 
    157         &                                               name = iom_file(kiomid)%uldname), clinfo) 
     156           CALL iom_nf90_check(NF90_Inquire_Dimension(if90id, iom_file(kiomid)%iduld,     &  
     157        &                                               name = iom_file(kiomid)%uldname,  & 
     158        &                                               len  = iom_file(kiomid)%lenuld ), clinfo ) 
    158159         ENDIF 
    159160         IF(lwp) WRITE(numout,*) '                   ---> '//TRIM(cdname)//' OK' 
  • branches/2016/dev_INGV_UKMO_2016/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90

    r5836 r7351  
    2727   USE in_out_manager  ! I/O manager 
    2828   USE iom             ! I/O module 
    29  
     29   USE diurnal_bulk 
     30    
    3031   IMPLICIT NONE 
    3132   PRIVATE 
     
    3738 
    3839   !! * Substitutions 
    39 #  include "domzgr_substitute.h90" 
    4040#  include "vectopt_loop_substitute.h90" 
    4141   !!---------------------------------------------------------------------- 
     
    9595               WRITE(numout,*) 
    9696               SELECT CASE ( jprstlib ) 
    97                CASE ( jprstdimg )   ;   WRITE(numout,*)                            & 
    98                    '             open ocean restart binary file: ',TRIM(clpath)//clname 
    9997               CASE DEFAULT         ;   WRITE(numout,*)                            & 
    10098                   '             open ocean restart NetCDF file: ',TRIM(clpath)//clname 
     
    126124      !!---------------------------------------------------------------------- 
    127125 
    128                      CALL iom_rstput( kt, nitrst, numrow, 'rdt'    , rdt       )   ! dynamics time step 
    129                      CALL iom_rstput( kt, nitrst, numrow, 'rdttra1', rdttra(1) )   ! surface tracer time step 
    130  
     126                     CALL iom_rstput( kt, nitrst, numrow, 'rdt'    , rdt       )   ! dynamics and tracer time step 
     127 
     128      IF ( .NOT. ln_diurnal_only ) THEN 
    131129                     CALL iom_rstput( kt, nitrst, numrow, 'ub'     , ub        )     ! before fields 
    132130                     CALL iom_rstput( kt, nitrst, numrow, 'vb'     , vb        ) 
     
    141139                     CALL iom_rstput( kt, nitrst, numrow, 'sshn'   , sshn      ) 
    142140                     CALL iom_rstput( kt, nitrst, numrow, 'rhop'   , rhop      ) 
     141 
     142                  ! extra variable needed for the ice sheet coupling 
     143                  IF ( ln_iscpl ) THEN  
     144                     CALL iom_rstput( kt, nitrst, numrow, 'tmask'  , tmask     ) ! need to extrapolate T/S 
     145                     CALL iom_rstput( kt, nitrst, numrow, 'umask'  , umask     ) ! need to correct barotropic velocity 
     146                     CALL iom_rstput( kt, nitrst, numrow, 'vmask'  , vmask     ) ! need to correct barotropic velocity 
     147                     CALL iom_rstput( kt, nitrst, numrow, 'smask'  , ssmask    ) ! need to correct barotropic velocity 
     148                     CALL iom_rstput( kt, nitrst, numrow, 'e3t_n', e3t_n(:,:,:) )   ! need to compute temperature correction 
     149                     CALL iom_rstput( kt, nitrst, numrow, 'e3u_n', e3u_n(:,:,:) )   ! need to compute bt conservation 
     150                     CALL iom_rstput( kt, nitrst, numrow, 'e3v_n', e3v_n(:,:,:) )   ! need to compute bt conservation 
     151                     CALL iom_rstput( kt, nitrst, numrow, 'gdepw_n', gdepw_n(:,:,:) ) ! need to compute extrapolation if vvl 
     152                  END IF 
     153      ENDIF 
     154       
     155      IF (ln_diurnal) CALL iom_rstput( kt, nitrst, numrow, 'Dsst', x_dsst    )   
     156 
    143157      IF( kt == nitrst ) THEN 
    144158         CALL iom_close( numrow )     ! close the restart file (only at last time step) 
     
    175189            SELECT CASE ( jprstlib ) 
    176190            CASE ( jpnf90    )   ;   WRITE(numout,*) 'rst_read : read oce NetCDF restart file' 
    177             CASE ( jprstdimg )   ;   WRITE(numout,*) 'rst_read : read oce binary restart file' 
    178191            END SELECT 
    179192            IF ( snc4set%luse )      WRITE(numout,*) 'rst_read : configured with NetCDF4 support' 
     
    183196         clpath = TRIM(cn_ocerst_indir) 
    184197         IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath) // '/' 
    185          IF ( jprstlib == jprstdimg ) THEN 
    186            ! eventually read netcdf file (monobloc)  for restarting on different number of processors 
    187            ! if {cn_ocerst_in}.nc exists, then set jlibalt to jpnf90 
    188            INQUIRE( FILE = TRIM(cn_ocerst_indir)//'/'//TRIM(cn_ocerst_in)//'.nc', EXIST = llok ) 
    189            IF ( llok ) THEN ; jlibalt = jpnf90  ; ELSE ; jlibalt = jprstlib ; ENDIF 
    190          ENDIF 
    191198         CALL iom_open( TRIM(clpath)//cn_ocerst_in, numror, kiolib = jlibalt ) 
    192199      ENDIF 
     
    202209      !! ** Method  :   Read in restart.nc file fields which are necessary for restart 
    203210      !!---------------------------------------------------------------------- 
    204       REAL(wp) ::   zrdt, zrdttra1 
     211      REAL(wp) ::   zrdt 
    205212      INTEGER  ::   jk 
    206       LOGICAL  ::   llok 
    207213      !!---------------------------------------------------------------------- 
    208214 
     
    214220         IF( zrdt /= rdt )   neuler = 0 
    215221      ENDIF 
    216       IF( iom_varid( numror, 'rdttra1', ldstop = .FALSE. ) > 0 )   THEN 
    217          CALL iom_get( numror, 'rdttra1', zrdttra1 ) 
    218          IF( zrdttra1 /= rdttra(1) )   neuler = 0 
    219       ENDIF 
    220       !  
     222 
     223      ! Diurnal DSST  
     224      IF( ln_diurnal ) CALL iom_get( numror, jpdom_autoglo, 'Dsst' , x_dsst  )  
     225      IF ( ln_diurnal_only ) THEN  
     226         IF(lwp) WRITE( numout, * ) & 
     227         &   "rst_read:- ln_diurnal_only set, setting rhop=rau0"  
     228         rhop = rau0 
     229         CALL iom_get( numror, jpdom_autoglo, 'tn'     , tsn(:,:,1,jp_tem) )  
     230         RETURN  
     231      ENDIF   
     232       
    221233      IF( iom_varid( numror, 'ub', ldstop = .FALSE. ) > 0 ) THEN 
    222234         CALL iom_get( numror, jpdom_autoglo, 'ub'     , ub      )   ! before fields 
     
    237249         CALL iom_get( numror, jpdom_autoglo, 'rhop'   , rhop    )   ! now    potential density 
    238250      ELSE 
    239          CALL eos    ( tsn, rhd, rhop, fsdept_n(:,:,:) )    
     251         CALL eos( tsn, rhd, rhop, gdept_n(:,:,:) )    
    240252      ENDIF 
    241253      ! 
     
    246258         sshb (:,:)     = sshn (:,:) 
    247259         ! 
    248          IF( lk_vvl ) THEN 
     260         IF( .NOT.ln_linssh ) THEN 
    249261            DO jk = 1, jpk 
    250                fse3t_b(:,:,jk) = fse3t_n(:,:,jk) 
     262               e3t_b(:,:,jk) = e3t_n(:,:,jk) 
    251263            END DO 
    252264         ENDIF 
Note: See TracChangeset for help on using the changeset viewer.