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 6225 for branches/2014/dev_r4704_NOC5_MPP_BDY_UPDATE/NEMOGCM/NEMO/LIM_SRC_3/limrst.F90 – NEMO

Ignore:
Timestamp:
2016-01-08T10:35:19+01:00 (8 years ago)
Author:
jamesharle
Message:

Update MPP_BDY_UPDATE branch to be consistent with head of trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_r4704_NOC5_MPP_BDY_UPDATE/NEMOGCM/NEMO/LIM_SRC_3/limrst.F90

    r4688 r6225  
    1818   USE ice            ! sea-ice variables 
    1919   USE oce     , ONLY :  snwice_mass, snwice_mass_b 
    20    USE par_ice        ! sea-ice parameters 
    2120   USE dom_oce        ! ocean domain 
    2221   USE sbc_oce        ! Surface boundary condition: ocean fields 
     
    2726   USE wrk_nemo       ! work arrays 
    2827   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)   
     28   USE limctl 
    2929 
    3030   IMPLICIT NONE 
     
    3333   PUBLIC   lim_rst_opn    ! routine called by icestep.F90 
    3434   PUBLIC   lim_rst_write  ! routine called by icestep.F90 
    35    PUBLIC   lim_rst_read   ! routine called by iceini.F90 
     35   PUBLIC   lim_rst_read   ! routine called by sbc_lim_init 
    3636 
    3737   LOGICAL, PUBLIC ::   lrst_ice         !: logical to control the ice restart write  
     
    5555      CHARACTER(LEN=20)   ::   clkt     ! ocean time-step define as a character 
    5656      CHARACTER(LEN=50)   ::   clname   ! ice output restart file name 
     57      CHARACTER(len=256)  ::   clpath   ! full path to ice output restart file  
    5758      !!---------------------------------------------------------------------- 
    5859      ! 
     
    6465      IF( kt == nitrst - 2*nn_fsbc + 1 .OR. nstock == nn_fsbc    & 
    6566         &                             .OR. ( kt == nitend - nn_fsbc + 1 .AND. .NOT. lrst_ice ) ) THEN 
    66          ! beware of the format used to write kt (default is i8.8, that should be large enough...) 
    67          IF( nitrst > 99999999 ) THEN   ;   WRITE(clkt, *       ) nitrst 
    68          ELSE                           ;   WRITE(clkt, '(i8.8)') nitrst 
     67         IF( nitrst <= nitend .AND. nitrst > 0 ) THEN 
     68            ! beware of the format used to write kt (default is i8.8, that should be large enough...) 
     69            IF( nitrst > 99999999 ) THEN   ;   WRITE(clkt, *       ) nitrst 
     70            ELSE                           ;   WRITE(clkt, '(i8.8)') nitrst 
     71            ENDIF 
     72            ! create the file 
     73            clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_"//TRIM(cn_icerst_out) 
     74            clpath = TRIM(cn_icerst_outdir)  
     75            IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath)//'/' 
     76            IF(lwp) THEN 
     77               WRITE(numout,*) 
     78               SELECT CASE ( jprstlib ) 
     79               CASE DEFAULT 
     80                  WRITE(numout,*) '             open ice restart NetCDF file: ',TRIM(clpath)//clname 
     81               END SELECT 
     82               IF( kt == nitrst - 2*nn_fsbc + 1 ) THEN    
     83                  WRITE(numout,*)         '             kt = nitrst - 2*nn_fsbc + 1 = ', kt,' date= ', ndastp 
     84               ELSE   ;   WRITE(numout,*) '             kt = '                         , kt,' date= ', ndastp 
     85               ENDIF 
     86            ENDIF 
     87            ! 
     88            CALL iom_open( TRIM(clpath)//TRIM(clname), numriw, ldwrt = .TRUE., kiolib = jprstlib ) 
     89            lrst_ice = .TRUE. 
    6990         ENDIF 
    70          ! create the file 
    71          clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_"//TRIM(cn_icerst_out) 
    72          IF(lwp) THEN 
    73             WRITE(numout,*) 
    74             SELECT CASE ( jprstlib ) 
    75             CASE ( jprstdimg )   ;   WRITE(numout,*) '             open ice restart binary file: '//clname 
    76             CASE DEFAULT         ;   WRITE(numout,*) '             open ice restart NetCDF file: '//clname 
    77             END SELECT 
    78             IF( kt == nitrst - 2*nn_fsbc + 1 ) THEN    
    79                WRITE(numout,*)         '             kt = nitrst - 2*nn_fsbc + 1 = ', kt,' date= ', ndastp 
    80             ELSE   ;   WRITE(numout,*) '             kt = '                         , kt,' date= ', ndastp 
    81             ENDIF 
    82          ENDIF 
    83          ! 
    84          CALL iom_open( clname, numriw, ldwrt = .TRUE., kiolib = jprstlib ) 
    85          lrst_ice = .TRUE. 
    8691      ENDIF 
    8792      ! 
     93      IF( ln_icectl )   CALL lim_prt( kt, iiceprt, jiceprt, 1, ' - Beginning the time step - ' )   ! control print 
    8894   END SUBROUTINE lim_rst_opn 
    8995 
     
    142148         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    143149      END DO 
    144        
     150 
    145151      DO jl = 1, jpl  
    146152         WRITE(zchar,'(I1)') jl 
     
    165171      CALL iom_rstput( iter, nitrst, numriw, 'stress2_i'    , stress2_i  ) 
    166172      CALL iom_rstput( iter, nitrst, numriw, 'stress12_i'   , stress12_i ) 
    167       CALL iom_rstput( iter, nitrst, numriw, 'snwice_mass'  , snwice_mass )   !clem modif 
    168       CALL iom_rstput( iter, nitrst, numriw, 'snwice_mass_b', snwice_mass_b ) !clem modif 
     173      CALL iom_rstput( iter, nitrst, numriw, 'snwice_mass'  , snwice_mass ) 
     174      CALL iom_rstput( iter, nitrst, numriw, 'snwice_mass_b', snwice_mass_b ) 
    169175 
    170176      DO jl = 1, jpl  
     
    306312      !! ** purpose  :   read of sea-ice variable restart in a netcdf file 
    307313      !!---------------------------------------------------------------------- 
    308       INTEGER :: ji, jj, jk, jl, indx 
     314      INTEGER :: ji, jj, jk, jl 
    309315      REAL(wp) ::   zfice, ziter 
    310       REAL(wp) ::   zs_inf, z_slope_s, zsmax, zsmin, zalpha, zindb   ! local scalars used for the salinity profile 
    311       REAL(wp), POINTER, DIMENSION(:)  ::   zs_zero  
    312316      REAL(wp), POINTER, DIMENSION(:,:) ::   z2d 
    313317      CHARACTER(len=15) ::   znam 
     
    317321      !!---------------------------------------------------------------------- 
    318322 
    319       CALL wrk_alloc( nlay_i, zs_zero ) 
    320323      CALL wrk_alloc( jpi, jpj, z2d ) 
    321324 
     
    326329      ENDIF 
    327330 
    328       IF ( jprstlib == jprstdimg ) THEN 
    329         ! eventually read netcdf file (monobloc)  for restarting on different number of processors 
    330         ! if {cn_icerst_in}.nc exists, then set jlibalt to jpnf90 
    331         INQUIRE( FILE = TRIM(cn_icerst_in)//'.nc', EXIST = llok ) 
    332         IF ( llok ) THEN ; jlibalt = jpnf90  ; ELSE ; jlibalt = jprstlib ; ENDIF 
    333       ENDIF 
    334  
    335       CALL iom_open ( cn_icerst_in, numrir, kiolib = jprstlib ) 
     331      CALL iom_open ( TRIM(cn_icerst_indir)//'/'//cn_icerst_in, numrir, kiolib = jprstlib ) 
    336332 
    337333      CALL iom_get( numrir, 'nn_fsbc', zfice ) 
     
    395391      CALL iom_get( numrir, jpdom_autoglo, 'stress2_i' , stress2_i  ) 
    396392      CALL iom_get( numrir, jpdom_autoglo, 'stress12_i', stress12_i ) 
    397       CALL iom_get( numrir, jpdom_autoglo, 'snwice_mass'  , snwice_mass )   !clem modif 
    398       CALL iom_get( numrir, jpdom_autoglo, 'snwice_mass_b', snwice_mass_b ) !clem modif 
     393      CALL iom_get( numrir, jpdom_autoglo, 'snwice_mass'  , snwice_mass ) 
     394      CALL iom_get( numrir, jpdom_autoglo, 'snwice_mass_b', snwice_mass_b ) 
    399395 
    400396      DO jl = 1, jpl  
     
    521517      ! 
    522518      ! clem: I do not understand why the following IF is needed 
    523       !       I suspect something inconsistent in the main code with option num_sal=1 
    524       IF( num_sal == 1 ) THEN 
     519      !       I suspect something inconsistent in the main code with option nn_icesal=1 
     520      IF( nn_icesal == 1 ) THEN 
    525521         DO jl = 1, jpl  
    526             sm_i(:,:,jl) = bulk_sal 
     522            sm_i(:,:,jl) = rn_icesal 
    527523            DO jk = 1, nlay_i  
    528                s_i(:,:,jk,jl) = bulk_sal 
     524               s_i(:,:,jk,jl) = rn_icesal 
    529525            END DO 
    530526         END DO 
     
    533529      !CALL iom_close( numrir ) !clem: closed in sbcice_lim.F90 
    534530      ! 
    535       CALL wrk_dealloc( nlay_i, zs_zero ) 
    536531      CALL wrk_dealloc( jpi, jpj, z2d ) 
    537532      ! 
Note: See TracChangeset for help on using the changeset viewer.