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 2528 for trunk/NEMOGCM/NEMO/LIM_SRC_3/limrst.F90 – NEMO

Ignore:
Timestamp:
2010-12-27T18:33:53+01:00 (13 years ago)
Author:
rblod
Message:

Update NEMOGCM from branch nemo_v3_3_beta

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/LIM_SRC_3/limrst.F90

    r2477 r2528  
    44   !! Ice restart :  write the ice restart file 
    55   !!====================================================================== 
     6   !! History:   -   ! 2005-04 (M. Vancoppenolle) Original code 
     7   !!           3.0  ! 2008-03 (C. Ethe) restart files in using IOM interface 
     8   !!---------------------------------------------------------------------- 
    69#if defined key_lim3 
    710   !!---------------------------------------------------------------------- 
     
    1215   !!   lim_rst_read    : read  the restart file  
    1316   !!---------------------------------------------------------------------- 
    14    !! * Modules used 
    15    USE ice 
    16    USE par_ice 
    17    USE in_out_manager 
    18    USE dom_oce 
    19    USE sbc_oce         ! Surface boundary condition: ocean fields 
    20    USE sbc_ice         ! Surface boundary condition: ice fields 
    21    USE iom 
     17   USE ice              ! sea-ice variables 
     18   USE par_ice          ! sea-ice parameters 
     19   USE dom_oce          ! ocean domain 
     20   USE sbc_oce          ! Surface boundary condition: ocean fields 
     21   USE sbc_ice          ! Surface boundary condition: ice fields 
     22   USE in_out_manager   ! I/O manager 
     23   USE iom              ! I/O library 
    2224 
    2325   IMPLICIT NONE 
    2426   PRIVATE 
    2527 
    26    !! * Accessibility 
    27    PUBLIC lim_rst_opn    ! routine called by icestep.F90 
    28    PUBLIC lim_rst_write  ! routine called by icestep.F90 
    29    PUBLIC lim_rst_read   ! routine called by iceinit.F90 
     28   PUBLIC   lim_rst_opn    ! routine called by icestep.F90 
     29   PUBLIC   lim_rst_write  ! routine called by icestep.F90 
     30   PUBLIC   lim_rst_read   ! routine called by iceini.F90 
    3031 
    3132   LOGICAL, PUBLIC ::   lrst_ice         !: logical to control the ice restart write  
     
    3334 
    3435   !!---------------------------------------------------------------------- 
    35    !!   LIM 3.0,  UCL-LOCEAN-IPSL (2008) 
     36   !! NEMO/LIM3 3.3 , UCL - NEMO Consortium (2010) 
    3637   !! $Id$ 
    37    !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    38    !!---------------------------------------------------------------------- 
    39  
     38   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     39   !!---------------------------------------------------------------------- 
    4040CONTAINS 
    4141 
     
    4848      INTEGER, INTENT(in) ::   kt       ! number of iteration 
    4949      ! 
    50       CHARACTER(LEN=20)   ::   clkt     ! ocean time-step deine as a character 
     50      CHARACTER(LEN=20)   ::   clkt     ! ocean time-step define as a character 
    5151      CHARACTER(LEN=50)   ::   clname   ! ice output restart file name 
    5252      !!---------------------------------------------------------------------- 
     
    5454      IF( kt == nit000 )   lrst_ice = .FALSE.   ! default definition 
    5555 
    56       ! to get better performances with NetCDF format: 
    57       ! we open and define the ice restart file one ice time step before writing the data (-> at nitrst - 2*nn_fsbc + 1) 
    58       ! except if we write ice restart files every ice time step or if an ice restart file was writen at nitend - 2*nn_fsbc + 1 
    59       IF( kt == nitrst - 2*nn_fsbc + 1 .OR. nstock == nn_fsbc .OR. ( kt == nitend - nn_fsbc + 1 .AND. .NOT. lrst_ice ) ) THEN 
     56      ! in order to get better performances with NetCDF format, we open and define the ice restart file  
     57      ! one ice time step before writing the data (-> at nitrst - 2*nn_fsbc + 1), except if we write ice  
     58      ! restart files every ice time step or if an ice restart file was writen at nitend - 2*nn_fsbc + 1 
     59      IF( kt == nitrst - 2*nn_fsbc + 1 .OR. nstock == nn_fsbc    & 
     60         &                             .OR. ( kt == nitend - nn_fsbc + 1 .AND. .NOT. lrst_ice ) ) THEN 
    6061         ! beware of the format used to write kt (default is i8.8, that should be large enough...) 
    6162         IF( nitrst > 99999999 ) THEN   ;   WRITE(clkt, *       ) nitrst 
     
    7576            ENDIF 
    7677         ENDIF 
    77  
     78         ! 
    7879         CALL iom_open( clname, numriw, ldwrt = .TRUE., kiolib = jprstlib ) 
    7980         lrst_ice = .TRUE. 
     
    8283   END SUBROUTINE lim_rst_opn 
    8384 
     85 
    8486   SUBROUTINE lim_rst_write( kt ) 
    8587      !!---------------------------------------------------------------------- 
     
    8789      !! 
    8890      !! ** purpose  :   output of sea-ice variable in a netcdf file 
     91      !!---------------------------------------------------------------------- 
     92      INTEGER, INTENT(in) ::   kt     ! number of iteration 
    8993      !! 
    90       !!---------------------------------------------------------------------- 
    91       ! Arguments : 
    92       INTEGER, INTENT(in) ::   kt     ! number of iteration 
    93  
    94       ! Local variables : 
     94      INTEGER ::   ji, jj, jk ,jl   ! dummy loop indices 
     95      INTEGER ::   iter 
     96      CHARACTER(len=15) ::   znam 
     97      CHARACTER(len=1)  ::   zchar, zchar1 
    9598      REAL(wp), DIMENSION(jpi,jpj) :: z2d 
    96       INTEGER :: ji, jj, jk ,jl 
    97       INTEGER :: iter 
    98       CHARACTER(len=15) :: znam 
    99       CHARACTER(len=1)  :: zchar, zchar1 
    10099      !!---------------------------------------------------------------------- 
    101100 
     
    111110      ! ------------------  
    112111      !                                                                        ! calendar control 
    113       CALL iom_rstput( iter, nitrst, numriw, 'nn_fsbc', REAL( nn_fsbc, wp) )      ! time-step  
    114       CALL iom_rstput( iter, nitrst, numriw, 'kt_ice' , REAL( iter , wp) )        ! date 
     112      CALL iom_rstput( iter, nitrst, numriw, 'nn_fsbc', REAL( nn_fsbc, wp ) )      ! time-step  
     113      CALL iom_rstput( iter, nitrst, numriw, 'kt_ice' , REAL( iter   , wp ) )      ! date 
    115114 
    116115      ! Prognostic variables  
     
    288287      ENDIF 
    289288      ! 
    290  
    291289   END SUBROUTINE lim_rst_write 
     290 
    292291 
    293292   SUBROUTINE lim_rst_read 
     
    297296      !! ** purpose  :   read of sea-ice variable restart in a netcdf file 
    298297      !!---------------------------------------------------------------------- 
    299       ! Local variables 
    300298      INTEGER :: ji, jj, jk, jl, indx 
    301299      REAL(wp) ::   zfice, ziter 
    302       REAL(wp) :: & !parameters for the salinity profile 
    303          zs_inf, z_slope_s, zsmax, zsmin, zalpha, zindb 
    304       REAL(wp), DIMENSION(nlay_i) :: zs_zero  
    305       REAL(wp), DIMENSION(jpi,jpj) :: z2d 
    306       CHARACTER(len=15) :: znam 
    307       CHARACTER(len=1)  :: zchar, zchar1 
    308       INTEGER           :: jlibalt = jprstlib 
    309       LOGICAL           :: llok 
     300      REAL(wp) ::   zs_inf, z_slope_s, zsmax, zsmin, zalpha, zindb   ! local scalars used for the salinity profile 
     301      REAL(wp), DIMENSION(nlay_i)  ::   zs_zero  
     302      REAL(wp), DIMENSION(jpi,jpj) ::   z2d 
     303      CHARACTER(len=15) ::   znam 
     304      CHARACTER(len=1)  ::   zchar, zchar1 
     305      INTEGER           ::   jlibalt = jprstlib 
     306      LOGICAL           ::   llok 
    310307      !!---------------------------------------------------------------------- 
    311308 
     
    384381      END DO 
    385382 
    386       ! Salinity profile 
    387       !----------------- 
    388       IF( num_sal == 2 ) THEN 
    389          !     CALL lim_var_salprof 
     383      IF( num_sal == 2 ) THEN      ! Salinity profile 
    390384         DO jl = 1, jpl 
    391385            DO jk = 1, nlay_i 
     
    393387                  DO ji = 1, jpi 
    394388                     zs_inf        = sm_i(ji,jj,jl) 
    395                      z_slope_s     = 2.0*sm_i(ji,jj,jl)/MAX(0.01,ht_i(ji,jj,jl)) 
     389                     z_slope_s     = 2._wp * sm_i(ji,jj,jl) / MAX( 0.01_wp , ht_i(ji,jj,jl) ) 
    396390                     !- slope of the salinity profile 
    397                      zs_zero(jk)   = z_slope_s * ( FLOAT(jk)-1.0/2.0 ) * & 
    398                         ht_i(ji,jj,jl) / FLOAT(nlay_i) 
    399                      zsmax = 4.5 
    400                      zsmin = 3.5 
     391                     zs_zero(jk)   = z_slope_s * ( REAL(jk,wp) - 0.5_wp ) * ht_i(ji,jj,jl) / REAL(nlay_i,wp) 
     392                     zsmax = 4.5_wp 
     393                     zsmin = 3.5_wp 
    401394                     IF( sm_i(ji,jj,jl) .LT. zsmin ) THEN 
    402                         zalpha = 1.0 
     395                        zalpha = 1._wp 
    403396                     ELSEIF( sm_i(ji,jj,jl) .LT.zsmax ) THEN 
    404                         zalpha = sm_i(ji,jj,jl) / (zsmin-zsmax) + zsmax / (zsmax-zsmin) 
     397                        zalpha = sm_i(ji,jj,jl) / ( zsmin - zsmax ) + zsmax / ( zsmax - zsmin ) 
    405398                     ELSE 
    406                         zalpha = 0.0 
     399                        zalpha = 0._wp 
    407400                     ENDIF 
    408                      s_i(ji,jj,jk,jl) = zalpha*zs_zero(jk) + ( 1.0 - zalpha )*zs_inf 
     401                     s_i(ji,jj,jk,jl) = zalpha * zs_zero(jk) + ( 1._wp - zalpha ) * zs_inf 
    409402                  END DO 
    410403               END DO 
     
    558551         END DO 
    559552      END DO 
    560  
     553      ! 
    561554      CALL iom_close( numrir ) 
    562  
     555      ! 
    563556   END SUBROUTINE lim_rst_read 
    564  
    565557 
    566558#else 
Note: See TracChangeset for help on using the changeset viewer.