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 835 for trunk/NEMO – NEMO

Changeset 835 for trunk/NEMO


Ignore:
Timestamp:
2008-03-10T15:14:15+01:00 (16 years ago)
Author:
ctlod
Message:

Use IOM interface to build sea-ice restart files, see ticket:#74

Location:
trunk/NEMO/LIM_SRC_3
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/LIM_SRC_3/iceini.F90

    r834 r835  
    4949      !                                   !  north and south hemisphere 
    5050   !!---------------------------------------------------------------------- 
    51    !!   LIM 2.0,  UCL-LOCEAN-IPSL (2005)  
    5251   !!   LIM 3.0,  UCL-ASTR-LOCEAN-IPSL (2008)  
    5352   !! $Header: /home/opalod/NEMOCVSROOT/NEMO/LIM_SRC/iceini.F90,v 1.4 2005/03/27 18:34:41 opalod Exp $  
     
    9695                                      ! variables 
    9796      ELSE 
    98          CALL lim_rst_read( numit )   ! start from a restart file 
     97!CT start 
     98         CALL lim_rst_read            ! start from a restart file 
     99!CT end 
    99100         numit = nit000 - 1 
    100101         CALL lim_var_agg(1)          ! aggregate ice variables 
  • trunk/NEMO/LIM_SRC_3/icestp.F90

    r834 r835  
    125125 
    126126      IF(lwp) WRITE(numout,*) ' ~~~ LIM-@ ~~~      ' 
    127       IF(lwp) WRITE(numout,*) ' Time step : ', numit 
     127      IF(lwp) WRITE(numout,*) ' Time step : ', kt 
    128128 
    129129!------------------------------------------------------------------------------- 
     
    150150      !------------------------ 
    151151 
    152       IF ( MOD( kt-1, nfice ) == 0 ) THEN 
     152      IF( MOD( kt-1, nfice ) == 0 ) THEN 
    153153          
    154154         !------------------- 
     
    268268!---------------------------------------------------------------------------- 
    269269 
     270         !                                                           !-----------------------! 
     271         CALL lim_rst_opn( kt )                                      ! Open Ice restart file ! 
     272         !                                                           !-----------------------! 
     273 
    270274         !+++++ 
    271275         WRITE(numout,*) ' - Beginning the time step - ' 
     
    278282        !--------------------------- 
    279283 
    280         !                            !--------------------! 
    281         CALL lim_dyn                 !  Ice dynamics      !  ( rheology/dynamics ) 
    282         !                            !--------------------! 
    283  
    284         !                            !--------------------! 
    285         CALL lim_trp                 !  Ice transport     ! 
    286         !                            !--------------------! 
     284        !                                                            !--------------------! 
     285        CALL lim_dyn                                                 !  Ice dynamics      !  ( rheology/dynamics ) 
     286        !                                                            !--------------------! 
     287 
     288        !                                                            !--------------------! 
     289        CALL lim_trp                                                 !  Ice transport     ! 
     290        !                                                            !--------------------! 
    287291    
    288292        CALL lim_var_agg(1)  ! aggregate categories, requested 
     
    302306        !+++++ 
    303307 
    304         !                            !------------------------------------------------! 
    305         CALL lim_itd_me              !  Mechanical redistribution ! (ridging/rafting) 
    306         !                            !------------------------------------------------! 
     308        !                                                            !------------------------------------------------! 
     309        CALL lim_itd_me                                              !  Mechanical redistribution ! (ridging/rafting) ! 
     310        !                                                            !------------------------------------------------! 
    307311 
    308312        !------------------------- 
     
    314318        CALL lim_var_bv      ! bulk brine volume (diag) 
    315319 
    316         !                            !--------------------------------! 
    317         CALL lim_thd                 !  Heat diffusion, growth, melt  ! 
    318         !                            !--------------------------------! 
     320        !                                                            !--------------------------------! 
     321        CALL lim_thd                                                 !  Heat diffusion, growth, melt  ! 
     322        !                                                            !--------------------------------! 
    319323      
    320         !                            !---------------------! 
    321         !                            !  Ice natural aging  ! 
    322         !                            !---------------------! 
     324        !                                                            !---------------------! 
     325        !                                                            !  Ice natural aging  ! 
     326        !                                                            !---------------------! 
    323327 
    324328        oa_i(:,:,:) = oa_i(:,:,:) + a_i(:,:,:) * rdt_ice / 86400.00 
     
    332336 
    333337 
    334         !                            !-------------------------------------------! 
    335         CALL lim_itd_th              !  Remap ice categories, lateral accretion  ! 
    336         !                            !-------------------------------------------! 
     338        !                                                            !-------------------------------------------! 
     339        CALL lim_itd_th                                              !  Remap ice categories, lateral accretion  ! 
     340        !                                                            !-------------------------------------------! 
    337341 
    338342!---------------------------------------------------------------------------- 
     
    341345 
    342346        CALL lim_var_agg(1)   ! requested by limupdate 
    343         !                            !-------------------------! 
    344         CALL lim_update              ! Global variables update ! 
    345         !                            !-------------------------! 
     347        !                                                            !-------------------------! 
     348        CALL lim_update                                              ! Global variables update ! 
     349        !                                                            !-------------------------! 
    346350 
    347351        CALL lim_var_glo2eqv ! equivalent variables (outputs) 
     
    360364!---------------------------------------------------------------------------- 
    361365 
    362         !                        !------------------------------! 
    363         CALL lim_flx             ! Ice/Ocean Mass & Heat fluxes ! 
    364         !                        !------------------------------! 
     366        !                                                            !------------------------------! 
     367        CALL lim_flx                                                 ! Ice/Ocean Mass & Heat fluxes ! 
     368        !                                                            !------------------------------! 
    365369 
    366370        !+++++ 
     
    375379 
    376380         IF( MOD( numit, ninfo ) == 0 .OR. ntmoy == 1 )  THEN         
    377          !                        !-------------------------------! 
    378          CALL lim_dia             ! Ice Diagnostics in evolu file ! 
    379          ENDIF                    !-------------------------------! 
    380  
    381          !                        !----------------------------! 
    382          CALL lim_wri( 1 )        ! Ice outputs in icemod file ! 
    383          !                        !----------------------------! 
    384  
    385          IF( MOD( numit, nstock ) == 0 .OR. numit == nlast ) THEN 
    386                  WRITE(numout,*) ' Ice restart is called ' 
    387          !                           !------------------! 
    388          CALL lim_rst_write( numit ) ! Ice restart file ! 
    389          !                           !------------------! 
    390          ENDIF 
     381         !                                                           !-------------------------------! 
     382         CALL lim_dia                                                ! Ice Diagnostics in evolu file ! 
     383         ENDIF                                                       !-------------------------------! 
     384 
     385         !                                                           !----------------------------! 
     386         CALL lim_wri( 1 )                                           ! Ice outputs in icemod file ! 
     387         !                                                           !----------------------------! 
     388 
     389         !                                                           !------------------! 
     390         IF( lrst_ice ) CALL lim_rst_write( kt )                     ! Ice restart file ! 
     391         !                                                           !------------------! 
    391392 
    392393         CALL lim_var_glo2eqv 
  • trunk/NEMO/LIM_SRC_3/limrst.F90

    r834 r835  
    11MODULE limrst 
    2 !!====================================================================== 
    3 !!                     ***  MODULE  limrst  *** 
    4 !! Ice restart :  write the ice restart file 
    5 !!====================================================================== 
     2   !!====================================================================== 
     3   !!                     ***  MODULE  limrst  *** 
     4   !! Ice restart :  write the ice restart file 
     5   !!====================================================================== 
    66#if defined key_lim3 
    7 !!---------------------------------------------------------------------- 
    8 !!   'key_lim3' :                                    LIM3 sea-ice model 
    9 !!---------------------------------------------------------------------- 
    10 !!   lim_rst_write   : write of the restart file  
    11 !!   lim_rst_read    : read  the restart file  
    12 !!---------------------------------------------------------------------- 
    13 !! * Modules used 
    14 USE par_ice 
    15 USE in_out_manager 
    16 USE ice 
    17 USE ioipsl 
    18 USE dom_oce 
    19 USE ice_oce         ! ice variables 
    20 USE daymod 
    21 !USE limvar 
    22  
    23 IMPLICIT NONE 
    24 PRIVATE 
    25  
    26 !! * Accessibility 
    27 PUBLIC lim_rst_write  ! routine called by lim_step.F90 
    28 PUBLIC lim_rst_read   ! routine called by lim_init.F90 
    29  
    30         !!---------------------------------------------------------------------- 
    31 !!   LIM 2.0,  UCL-LOCEAN-IPSL (2005) 
    32         !! $Header: /home/opalod/NEMOCVSROOT/NEMO/LIM_SRC/limrst.F90,v 1.6 2005/03/27 18:34:42 opalod Exp $ 
    33         !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt 
    34         !!---------------------------------------------------------------------- 
    35  
    36         CONTAINS 
    37  
    38 # if ( defined key_mpp_mpi || defined key_mpp_shmem ) && defined key_dimgout 
    39    !!---------------------------------------------------------------------- 
    40    !!   'key_mpp_mpi'     OR 
    41    !!   'key_mpp_shmem' 
    42    !!   'key_dimgout' :                           clipper type restart file 
    43    !!                 :                     can be used in mpp 
    44    !!---------------------------------------------------------------------- 
    45 #  include "limrst_dimg.h90" 
    46  
    47 # else 
    48    !!---------------------------------------------------------------------- 
    49    !!   Default option                                          NetCDF file 
    50    !!---------------------------------------------------------------------- 
    51  
    52 SUBROUTINE lim_rst_write( niter ) 
    53    !!---------------------------------------------------------------------- 
    54    !!                    ***  lim_rst_write  *** 
    55    !! 
    56    !! ** purpose  :   output of sea-ice variable in a netcdf file 
    57    !! 
    58    !!---------------------------------------------------------------------- 
    59    ! Arguments 
    60    INTEGER  ::    niter        ! number of iteration 
    61  
    62    !- dummy variables : 
    63    LOGICAL :: & 
    64    llbon 
    65    INTEGER :: & 
    66    ji, jj, jk , jl 
    67    INTEGER :: & 
    68    inumwrs, it0, itime 
    69    REAL(wp), DIMENSION(1) :: & 
    70    zdept 
    71    REAL(wp), DIMENSION(2) :: & 
    72    zinfo 
    73    REAL(wp),DIMENSION(jpi,jpj,40*jpl+5*(nlay_i-1)) :: & 
    74    zmoment 
    75    REAL(wp) :: & 
    76    zsec, zdate0, zdt 
    77         REAL(wp), DIMENSION(jpi,jpj,jpl) :: & 
    78         zheatcon 
    79  
    80         CHARACTER(len=7), DIMENSION(jpk) :: zheatnam 
    81         CHARACTER(len=1)                 :: zchar 
    82  
    83    CHARACTER(len=45)  ::  & 
    84    ccfile = 'restart_ice_out.nc' 
    85  
    86    inumwrs  = 61 
    87         INQUIRE ( FILE = ccfile, EXIST = llbon ) 
    88    IF( llbon ) THEN 
    89    OPEN ( UNIT = inumwrs , FILE = ccfile, STATUS = 'old' ) 
    90    CLOSE( inumwrs , STATUS = 'delete' ) 
    91    ENDIF 
    92  
    93         WRITE(numout,*) 'lim_rst_write : Writes the restart file' 
    94         WRITE(numout,*) '~~~~~~~~~~~~~' 
    95         WRITE(numout,*)  
    96  
    97  
    98    it0      = niter 
    99    zinfo(1) = FLOAT( nfice  )  ! coupling frequency OPA ICELLN  nfice 
    100    zinfo(2) = FLOAT( it0   )   ! iteration number 
    101  
    102    zsec     = 0. 
    103    itime    = 0 
    104    zdept(1) = 0. 
    105    zdt      = rdt_ice * nstock 
    106  
    107         WRITE(numout,*) 'Phase 1 successfull ?' 
    108    ! Write in inumwrs 
    109  
    110         WRITE(numout,*) ' jl, MOMENT FIELD NO ' 
    111         DO jl = 1, jpl 
    112         WRITE(numout,*) jl, 6*5*(jl-1) + 1, 6*5*(jl-1) + 30 
    113    DO jj = 1, jpj              ! 3D array: 10 time faster than 35 restput 
    114    DO ji = 1, jpi 
    115         zmoment(ji,jj,6*5*(jl-1)+1) = sxice(ji,jj,jl) 
    116         zmoment(ji,jj,6*5*(jl-1)+2) = syice(ji,jj,jl) 
    117         zmoment(ji,jj,6*5*(jl-1)+3) = sxxice(ji,jj,jl) 
    118         zmoment(ji,jj,6*5*(jl-1)+4) = syyice(ji,jj,jl) 
    119         zmoment(ji,jj,6*5*(jl-1)+5) = sxyice(ji,jj,jl) 
    120         zmoment(ji,jj,6*5*(jl-1)+6) = sxsn(ji,jj,jl) 
    121         zmoment(ji,jj,6*5*(jl-1)+7) = sysn(ji,jj,jl) 
    122         zmoment(ji,jj,6*5*(jl-1)+8) = sxxsn(ji,jj,jl) 
    123         zmoment(ji,jj,6*5*(jl-1)+9) = syysn(ji,jj,jl) 
    124         zmoment(ji,jj,6*5*(jl-1)+10)= sxysn(ji,jj,jl) 
    125         zmoment(ji,jj,6*5*(jl-1)+11)= sxa(ji,jj,jl) 
    126         zmoment(ji,jj,6*5*(jl-1)+12)= sya(ji,jj,jl) 
    127         zmoment(ji,jj,6*5*(jl-1)+13)= sxxa(ji,jj,jl) 
    128         zmoment(ji,jj,6*5*(jl-1)+14)= syya(ji,jj,jl) 
    129         zmoment(ji,jj,6*5*(jl-1)+15)= sxya(ji,jj,jl) 
    130         zmoment(ji,jj,6*5*(jl-1)+16)= sxc0(ji,jj,jl) 
    131         zmoment(ji,jj,6*5*(jl-1)+17)= syc0(ji,jj,jl) 
    132         zmoment(ji,jj,6*5*(jl-1)+18)= sxxc0(ji,jj,jl) 
    133         zmoment(ji,jj,6*5*(jl-1)+19)= syyc0(ji,jj,jl) 
    134         zmoment(ji,jj,6*5*(jl-1)+20)= sxyc0(ji,jj,jl) 
    135         zmoment(ji,jj,6*5*(jl-1)+21)= sxsal(ji,jj,jl) 
    136         zmoment(ji,jj,6*5*(jl-1)+22)= sysal(ji,jj,jl) 
    137         zmoment(ji,jj,6*5*(jl-1)+23)= sxxsal(ji,jj,jl) 
    138         zmoment(ji,jj,6*5*(jl-1)+24)= syysal(ji,jj,jl) 
    139         zmoment(ji,jj,6*5*(jl-1)+25)= sxysal(ji,jj,jl) 
    140         zmoment(ji,jj,6*5*(jl-1)+26)= sxage(ji,jj,jl) 
    141         zmoment(ji,jj,6*5*(jl-1)+27)= syage(ji,jj,jl) 
    142         zmoment(ji,jj,6*5*(jl-1)+28)= sxxage(ji,jj,jl) 
    143         zmoment(ji,jj,6*5*(jl-1)+29)= syyage(ji,jj,jl) 
    144         zmoment(ji,jj,6*5*(jl-1)+30)= sxyage(ji,jj,jl) 
    145         END DO  
    146         END DO 
    147         END DO 
    148  
    149         WRITE(numout,*) ' jk, jl, MOMENT FIELD NO ' 
    150         DO jl = 1, jpl 
    151         DO jk = 1, nlay_i  
    152         WRITE(numout,*) jk, jl, 5*(6*jpl+(jk-1)+2*(jl-1))+1, 5*(6*jpl+(jk-1)+2*(jl-1))+5 
    153         DO jj = 1, jpj              ! 3D array: 10 time faster than 35 restput 
    154         DO ji = 1, jpi 
    155         zmoment(ji,jj,5*(6*jpl+(jk-1)+2*(jl-1))+1)= sxe(ji,jj,jk,jl) 
    156         zmoment(ji,jj,5*(6*jpl+(jk-1)+2*(jl-1))+2)= sye(ji,jj,jk,jl) 
    157         zmoment(ji,jj,5*(6*jpl+(jk-1)+2*(jl-1))+3)= sxxe(ji,jj,jk,jl) 
    158         zmoment(ji,jj,5*(6*jpl+(jk-1)+2*(jl-1))+4)= syye(ji,jj,jk,jl) 
    159         zmoment(ji,jj,5*(6*jpl+(jk-1)+2*(jl-1))+5)= sxye(ji,jj,jk,jl) 
    160         END DO 
    161         END DO 
    162         END DO 
    163         END DO 
    164  
    165         WRITE(numout,*) ' openw , MOMENT FIELD NO ' 
    166         WRITE(numout,*) 40*jpl + 5*nlay_i - 9, 40*jpl + 5*nlay_i - 5 
    167         DO jj = 1, jpj              ! 3D array: 10 time faster than 35 restput 
    168         DO ji = 1, jpi 
    169            zmoment(ji,jj,40*jpl + 5*nlay_i - 10 + 1)= sxopw(ji,jj) 
    170            zmoment(ji,jj,40*jpl + 5*nlay_i - 10 + 2)= syopw(ji,jj) 
    171            zmoment(ji,jj,40*jpl + 5*nlay_i - 10 + 3)= sxxopw(ji,jj) 
    172            zmoment(ji,jj,40*jpl + 5*nlay_i - 10 + 4)= syyopw(ji,jj) 
    173            zmoment(ji,jj,40*jpl + 5*nlay_i - 10 + 5)= sxyopw(ji,jj) 
    174         END DO 
    175         END DO 
    176         WRITE(numout,*) ' Done ... ' 
    177  
    178         CALL ymds2ju( nyear, nmonth, nday, zsec, zdate0 ) 
    179         CALL restini( 'NONE', jpi, jpj, glamt, gphit, 1 , zdept, ccfile, itime, zdate0, zdt, inumwrs ) 
    180  
    181         CALL restput( inumwrs, 'info'   ,   1,   1,   2 , 0, zinfo   )  ! restart informations 
    182         CALL restput( inumwrs, 'v_i '   , jpi, jpj, jpl , 0, v_i  ) 
    183         CALL restput( inumwrs, 'v_s '   , jpi, jpj, jpl , 0, v_s  ) 
    184         CALL restput( inumwrs, 'smv_i'  , jpi, jpj, jpl , 0, smv_i ) 
    185         CALL restput( inumwrs, 'oa_i'   , jpi, jpj, jpl , 0, oa_i ) 
    186         CALL restput( inumwrs, 'a_i '   , jpi, jpj, jpl , 0, a_i  ) 
    187         CALL restput( inumwrs, 't_su'   , jpi, jpj, jpl , 0, t_su ) 
    188  
    189 !     CALL restput( inumwrs, 'sist'   , jpi, jpj, 1 , 0, sist    ) 
     7   !!---------------------------------------------------------------------- 
     8   !!   'key_lim3' :                                   LIM sea-ice model 
     9   !!---------------------------------------------------------------------- 
     10   !!   lim_rst_opn     : open ice restart file 
     11   !!   lim_rst_write   : write of the restart file  
     12   !!   lim_rst_read    : read  the restart file  
     13   !!---------------------------------------------------------------------- 
     14   !! * Modules used 
     15   USE ice 
     16   USE par_ice 
     17   USE in_out_manager 
     18   USE dom_oce 
     19   USE ice_oce         ! ice variables 
     20   USE daymod 
     21   USE iom 
     22    
     23   IMPLICIT NONE 
     24   PRIVATE 
     25    
     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 
     30 
     31   LOGICAL, PUBLIC ::   lrst_ice         !: logical to control the ice restart write  
     32   INTEGER, PUBLIC ::   numrir, numriw   !: logical unit for ice restart (read and write) 
     33 
     34   !!---------------------------------------------------------------------- 
     35   !!   LIM 2.0,  UCL-LOCEAN-IPSL (2005) 
     36   !! $Id:$ 
     37   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     38   !!---------------------------------------------------------------------- 
     39 
     40CONTAINS 
     41 
     42   SUBROUTINE lim_rst_opn( kt ) 
     43      !!---------------------------------------------------------------------- 
     44      !!                    ***  lim_rst_opn  *** 
     45      !! 
     46      !! ** purpose  :   output of sea-ice variable in a netcdf file 
     47      !!---------------------------------------------------------------------- 
     48      INTEGER, INTENT(in) ::   kt       ! number of iteration 
     49      ! 
     50      CHARACTER(LEN=20)   ::   clkt     ! ocean time-step deine as a character 
     51      CHARACTER(LEN=50)   ::   clname   ! ice output restart file name 
     52      !!---------------------------------------------------------------------- 
     53      ! 
     54      IF( kt == nit000 )   lrst_ice = .FALSE.   ! default definition 
     55       
     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*nfice + 1) 
     58      ! except if we write ice restart files every ice time step or if an ice restart file was writen at nitend - 2*nfice + 1 
     59      IF( kt == nitrst - 2*nfice + 1 .OR. nstock == nfice .OR. ( kt == nitend - nfice + 1 .AND. .NOT. lrst_ice ) ) THEN 
     60         ! beware of the format used to write kt (default is i8.8, that should be large enough...) 
     61         IF( nitrst > 99999999 ) THEN   ;   WRITE(clkt, *       ) nitrst 
     62         ELSE                           ;   WRITE(clkt, '(i8.8)') nitrst 
     63         ENDIF 
     64         ! create the file 
     65         clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_restart_ice" 
     66         IF(lwp) THEN 
     67            WRITE(numout,*) 
     68            SELECT CASE ( jprstlib ) 
     69            CASE ( jprstdimg )   ;   WRITE(numout,*) '             open ice restart binary file: '//clname 
     70            CASE DEFAULT         ;   WRITE(numout,*) '             open ice restart NetCDF file: '//clname 
     71            END SELECT 
     72            IF( kt == nitrst - 2*nfice + 1 ) THEN    
     73               WRITE(numout,*)         '             kt = nitrst - 2*nfice + 1 = ', kt,' date= ', ndastp 
     74            ELSE   ;   WRITE(numout,*) '             kt = '                       , kt,' date= ', ndastp 
     75            ENDIF 
     76         ENDIF 
     77 
     78         CALL iom_open( clname, numriw, ldwrt = .TRUE., kiolib = jprstlib ) 
     79         lrst_ice = .TRUE. 
     80      ENDIF 
     81      ! 
     82   END SUBROUTINE lim_rst_opn 
     83 
     84   SUBROUTINE lim_rst_write( kt ) 
     85      !!---------------------------------------------------------------------- 
     86      !!                    ***  lim_rst_write  *** 
     87      !! 
     88      !! ** purpose  :   output of sea-ice variable in a netcdf file 
     89      !! 
     90      !!---------------------------------------------------------------------- 
     91      ! Arguments : 
     92      INTEGER, INTENT(in) ::   kt     ! number of iteration 
     93 
     94      ! Local variables : 
     95      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 
     100      !!---------------------------------------------------------------------- 
     101    
     102      iter = kt + nfice - 1   ! ice restarts are written at kt == nitrst - nfice + 1 
     103 
     104      IF( iter == nitrst ) THEN 
     105         IF(lwp) WRITE(numout,*) 
     106         IF(lwp) WRITE(numout,*) 'lim_rst_write : write ice restart file  kt =', kt 
     107         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~'          
     108      ENDIF 
     109 
     110      ! Write in numriw (if iter == nitrst) 
     111      ! ------------------  
     112      !                                                                        ! calendar control 
     113      CALL iom_rstput( iter, nitrst, numriw, 'nfice' , REAL( nfice, wp) )      ! time-step  
     114      CALL iom_rstput( iter, nitrst, numriw, 'kt_ice', REAL( iter , wp) )      ! date 
     115 
     116      ! Prognostic variables  
     117      DO jl = 1, jpl  
     118         WRITE(zchar,'(I1)') jl 
     119         znam = 'v_i'//'_htc'//zchar 
     120         z2d(:,:) = v_i(:,:,jl) 
     121         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     122         znam = 'v_s'//'_htc'//zchar 
     123         z2d(:,:) = v_s(:,:,jl) 
     124         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     125         znam = 'smv_i'//'_htc'//zchar 
     126         z2d(:,:) = smv_i(:,:,jl) 
     127         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     128         znam = 'oa_i'//'_htc'//zchar 
     129         z2d(:,:) = oa_i(:,:,jl) 
     130         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     131         znam = 'a_i'//'_htc'//zchar 
     132         z2d(:,:) = a_i(:,:,jl) 
     133         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     134         znam = 't_su'//'_htc'//zchar 
     135         z2d(:,:) = t_su(:,:,jl) 
     136         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     137      END DO 
    190138# if defined key_coupled 
    191       CALL restput( inumwrs, 'albege' , jpi, jpj, 1 , 0, albege ) 
     139      CALL iom_rstput( iter, nitrst, numriw, 'albege', albege(:,:) ) 
    192140# endif 
    193       zheatcon(:,:,:) = e_s(:,:,1,:) 
    194       CALL restput( inumwrs, 'tempts1'    , jpi, jpj, jpl, 0, zheatcon) ! snow 
    195                   ! heat content 
    196  
    197       DO jk = 1, nlay_i  
    198          WRITE(zchar,'(I1)') jk 
    199          zheatnam(jk) = 'tempti'//zchar 
    200          zheatcon(:,:,:) = e_i(:,:,jk,:) 
    201          CALL restput( inumwrs, zheatnam(jk) , jpi, jpj, jpl, 0, zheatcon ) 
    202       END DO 
    203  
    204       CALL restput( inumwrs, 'u_ice'  , jpi, jpj, 1 , 0, u_ice   ) 
    205       CALL restput( inumwrs, 'v_ice'  , jpi, jpj, 1 , 0, v_ice   ) 
    206       CALL restput( inumwrs, 'gtaux'  , jpi, jpj, 1 , 0, gtaux  ) 
    207       CALL restput( inumwrs, 'gtauy'  , jpi, jpj, 1 , 0, gtauy  ) 
    208 ! MV 2005 
    209       CALL restput( inumwrs, 'fsbbq'  , jpi, jpj, 1 , 0, fsbbq   ) 
    210       WRITE(numout,*) ' Done 2 ... ' 
    211       CALL restput( inumwrs, 'str1_i' , jpi, jpj, 1 , 0, stress1_i ) 
    212       CALL restput( inumwrs, 'str2_i' , jpi, jpj, 1 , 0, stress2_i ) 
    213       CALL restput( inumwrs, 'str12i' , jpi, jpj, 1 , 0, stress12_i ) 
    214       CALL restput( inumwrs, 'moment' , jpi, jpj, 40*jpl+5*(nlay_i-1) , 0, zmoment ) 
    215       WRITE(numout,*) ' Done 3 ... ' 
    216        
    217       CALL restclo( inumwrs ) 
    218  
    219 !+++++++++++ CHECK EVERYTHING ++++++++++ 
    220             WRITE(numout,*) 
    221             WRITE(numout,*) ' lim_rst_write : CHUKCHI SEA POINT ' 
    222             WRITE(numout,*) ' ~~~~~~~~~~' 
    223             WRITE(numout,*) ' ~~~ Arctic' 
    224  
    225             ji = jiindex 
    226             jj = jjindex 
    227  
    228             WRITE(numout,*) ' ji, jj ', ji, jj 
    229             WRITE(numout,*) ' ICE VARIABLES ' 
    230             WRITE(numout,*) ' open water ', ato_i(ji,jj) 
    231             DO jl = 1, jpl 
    232                WRITE(numout,*) ' *** CATEGORY NUMBER *** ', jl 
    233                WRITE(numout,*) ' ' 
    234                WRITE(numout,*) ' a_i        : ', a_i(ji,jj,jl)      
    235                WRITE(numout,*) ' v_i        : ', v_i(ji,jj,jl)  
    236                WRITE(numout,*) ' v_s        : ', v_s(ji,jj,jl)     
    237                WRITE(numout,*) ' e_s        : ', e_s(ji,jj,1,jl)/1.0e9 
    238                WRITE(numout,*) ' e_i1       : ', e_i(ji,jj,1,jl)/1.0e9       
    239                WRITE(numout,*) ' e_i2       : ', e_i(ji,jj,2,jl)/1.0e9       
    240                WRITE(numout,*) ' smv_i      : ', smv_i(ji,jj,jl)   
    241                WRITE(numout,*) ' oa_i       : ', oa_i(ji,jj,jl) 
    242                WRITE(numout,*) ' t_su       : ', t_su(ji,jj,jl) 
    243             END DO 
    244  
    245             WRITE(numout,*) ' MOMENTS OF ADVECTION ' 
    246  
    247             WRITE(numout,*) ' open water ' 
    248             WRITE(numout,*) ' sxopw  ', sxopw(ji,jj) 
    249             WRITE(numout,*) ' syopw  ', syopw(ji,jj) 
    250             WRITE(numout,*) ' sxxopw ', sxxopw(ji,jj) 
    251             WRITE(numout,*) ' syyopw ', syyopw(ji,jj) 
    252             WRITE(numout,*) ' sxyopw ', sxyopw(ji,jj) 
    253             DO jl = 1, jpl 
    254                WRITE(numout,*) ' jl, ice volume content ', jl 
    255                WRITE(numout,*) ' sxice  ', sxice(ji,jj,jl) 
    256                WRITE(numout,*) ' syice  ', syice(ji,jj,jl) 
    257                WRITE(numout,*) ' sxxice ', sxxice(ji,jj,jl) 
    258                WRITE(numout,*) ' syyice ', syyice(ji,jj,jl) 
    259                WRITE(numout,*) ' sxyice ', sxyice(ji,jj,jl) 
    260                WRITE(numout,*) ' jl, snow volume content ', jl 
    261                WRITE(numout,*) ' sxsn   ', sxsn(ji,jj,jl) 
    262                WRITE(numout,*) ' sysn   ', sysn(ji,jj,jl) 
    263                WRITE(numout,*) ' sxxsn  ', sxxsn(ji,jj,jl) 
    264                WRITE(numout,*) ' syysn  ', syysn(ji,jj,jl) 
    265                WRITE(numout,*) ' sxysn  ', sxysn(ji,jj,jl) 
    266                WRITE(numout,*) ' jl, ice area in category ', jl 
    267                WRITE(numout,*) ' sxa    ', sxa (ji,jj,jl) 
    268                WRITE(numout,*) ' sya    ', sya (ji,jj,jl) 
    269                WRITE(numout,*) ' sxxa   ', sxxa (ji,jj,jl) 
    270                WRITE(numout,*) ' syya   ', syya (ji,jj,jl) 
    271                WRITE(numout,*) ' sxya   ', sxya (ji,jj,jl) 
    272                WRITE(numout,*) ' jl, snow temp ', jl 
    273                WRITE(numout,*) ' sxc0   ', sxc0(ji,jj,jl) 
    274                WRITE(numout,*) ' syc0   ', syc0(ji,jj,jl) 
    275                WRITE(numout,*) ' sxxc0  ', sxxc0(ji,jj,jl) 
    276                WRITE(numout,*) ' syyc0  ', syyc0(ji,jj,jl) 
    277                WRITE(numout,*) ' sxyc0  ', sxyc0(ji,jj,jl) 
    278                WRITE(numout,*) ' jl, ice salinity ', jl 
    279                WRITE(numout,*) ' sxsal  ', sxsal(ji,jj,jl) 
    280                WRITE(numout,*) ' sysal  ', sysal(ji,jj,jl) 
    281                WRITE(numout,*) ' sxxsal ', sxxsal(ji,jj,jl) 
    282                WRITE(numout,*) ' syysal ', syysal(ji,jj,jl) 
    283                WRITE(numout,*) ' sxysal ', sxysal(ji,jj,jl) 
    284                WRITE(numout,*) ' jl, ice age      ', jl 
    285                WRITE(numout,*) ' sxage  ', sxage(ji,jj,jl) 
    286                WRITE(numout,*) ' syage  ', syage(ji,jj,jl) 
    287                WRITE(numout,*) ' sxxage ', sxxage(ji,jj,jl) 
    288                WRITE(numout,*) ' syyage ', syyage(ji,jj,jl) 
    289                WRITE(numout,*) ' sxyage ', sxyage(ji,jj,jl) 
    290             END DO 
    291             DO jl = 1, jpl 
    292                DO jk = 1, nlay_i 
    293                   WRITE(numout,*) ' jk, jl, ice heat content', jk, jl 
    294                   WRITE(numout,*) ' sxe    ', sxe(ji,jj,jk,jl) 
    295                   WRITE(numout,*) ' sye    ', sye(ji,jj,jk,jl) 
    296                   WRITE(numout,*) ' sxxe   ', sxxe(ji,jj,jk,jl) 
    297                   WRITE(numout,*) ' syye   ', syye(ji,jj,jk,jl) 
    298                   WRITE(numout,*) ' sxye   ', sxye(ji,jj,jk,jl) 
     141      DO jl = 1, jpl  
     142         WRITE(zchar,'(I1)') jl 
     143         znam = 'tempt_sl1'//'_htc'//zchar 
     144         z2d(:,:) = e_s(:,:,1,jl) 
     145         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     146      END DO 
     147 
     148      DO jl = 1, jpl  
     149         WRITE(zchar,'(I1)') jl 
     150         DO jk = 1, nlay_i  
     151            WRITE(zchar1,'(I1)') jk 
     152            znam = 'tempt'//'_il'//zchar1//'_htc'//zchar 
     153            z2d(:,:) = e_i(:,:,jk,jl) 
     154            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     155         END DO 
     156      END DO 
     157 
     158      CALL iom_rstput( iter, nitrst, numriw, 'u_ice'     , u_ice      ) 
     159      CALL iom_rstput( iter, nitrst, numriw, 'v_ice'     , v_ice      ) 
     160      CALL iom_rstput( iter, nitrst, numriw, 'gtaux'     , gtaux      ) 
     161      CALL iom_rstput( iter, nitrst, numriw, 'gtauy'     , gtauy      ) 
     162      CALL iom_rstput( iter, nitrst, numriw, 'fsbbq'     , fsbbq      ) 
     163      CALL iom_rstput( iter, nitrst, numriw, 'stress1_i' , stress1_i  ) 
     164      CALL iom_rstput( iter, nitrst, numriw, 'stress2_i' , stress2_i  ) 
     165      CALL iom_rstput( iter, nitrst, numriw, 'stress12_i', stress12_i ) 
     166 
     167      DO jl = 1, jpl  
     168         WRITE(zchar,'(I1)') jl 
     169         znam = 'sxice'//'_htc'//zchar 
     170         z2d(:,:) = sxice(:,:,jl) 
     171         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     172         znam = 'syice'//'_htc'//zchar 
     173         z2d(:,:) = syice(:,:,jl) 
     174         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     175         znam = 'sxxice'//'_htc'//zchar 
     176         z2d(:,:) = sxxice(:,:,jl) 
     177         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     178         znam = 'syyice'//'_htc'//zchar 
     179         z2d(:,:) = syyice(:,:,jl) 
     180         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     181         znam = 'sxsn'//'_htc'//zchar 
     182         z2d(:,:) = sxsn(:,:,jl) 
     183         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     184         znam = 'sysn'//'_htc'//zchar 
     185         z2d(:,:) = sysn(:,:,jl) 
     186         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     187         znam = 'sxxsn'//'_htc'//zchar 
     188         z2d(:,:) = sxxsn(:,:,jl) 
     189         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     190         znam = 'syysn'//'_htc'//zchar 
     191         z2d(:,:) = syysn(:,:,jl) 
     192         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     193         znam = 'sxysn'//'_htc'//zchar 
     194         z2d(:,:) = sxysn(:,:,jl) 
     195         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     196         znam = 'sxa'//'_htc'//zchar 
     197         z2d(:,:) = sxa(:,:,jl) 
     198         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     199         znam = 'sya'//'_htc'//zchar 
     200         z2d(:,:) = sya(:,:,jl) 
     201         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     202         znam = 'sxxa'//'_htc'//zchar 
     203         z2d(:,:) = sxxa(:,:,jl) 
     204         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     205         znam = 'syya'//'_htc'//zchar 
     206         z2d(:,:) = syya(:,:,jl) 
     207         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     208         znam = 'sxya'//'_htc'//zchar 
     209         z2d(:,:) = sxya(:,:,jl) 
     210         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     211         znam = 'sxc0'//'_htc'//zchar 
     212         z2d(:,:) = sxc0(:,:,jl) 
     213         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     214         znam = 'syc0'//'_htc'//zchar 
     215         z2d(:,:) = syc0(:,:,jl) 
     216         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     217         znam = 'sxxc0'//'_htc'//zchar 
     218         z2d(:,:) = sxxc0(:,:,jl) 
     219         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     220         znam = 'syyc0'//'_htc'//zchar 
     221         z2d(:,:) = syyc0(:,:,jl) 
     222         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     223         znam = 'sxyc0'//'_htc'//zchar 
     224         z2d(:,:) = sxyc0(:,:,jl) 
     225         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     226         znam = 'sxsal'//'_htc'//zchar 
     227         z2d(:,:) = sxsal(:,:,jl) 
     228         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     229         znam = 'sysal'//'_htc'//zchar 
     230         z2d(:,:) = sysal(:,:,jl) 
     231         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     232         znam = 'sxxsal'//'_htc'//zchar 
     233         z2d(:,:) = sxxsal(:,:,jl) 
     234         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     235         znam = 'syysal'//'_htc'//zchar 
     236         z2d(:,:) = syysal(:,:,jl) 
     237         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     238         znam = 'sxysal'//'_htc'//zchar 
     239         z2d(:,:) = sxysal(:,:,jl) 
     240         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     241         znam = 'sxage'//'_htc'//zchar 
     242         z2d(:,:) = sxage(:,:,jl) 
     243         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     244         znam = 'syage'//'_htc'//zchar 
     245         z2d(:,:) = syage(:,:,jl) 
     246         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     247         znam = 'sxxage'//'_htc'//zchar 
     248         z2d(:,:) = sxxage(:,:,jl) 
     249         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     250         znam = 'syyage'//'_htc'//zchar 
     251         z2d(:,:) = syyage(:,:,jl) 
     252         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     253         znam = 'sxyage'//'_htc'//zchar 
     254         z2d(:,:) = sxyage(:,:,jl) 
     255         CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     256      END DO 
     257 
     258      CALL iom_rstput( iter, nitrst, numriw, 'sxopw ' ,  sxopw  ) 
     259      CALL iom_rstput( iter, nitrst, numriw, 'syopw ' ,  syopw  ) 
     260      CALL iom_rstput( iter, nitrst, numriw, 'sxxopw' ,  sxxopw ) 
     261      CALL iom_rstput( iter, nitrst, numriw, 'syyopw' ,  syyopw ) 
     262      CALL iom_rstput( iter, nitrst, numriw, 'sxyopw' ,  sxyopw ) 
     263 
     264      DO jl = 1, jpl  
     265         WRITE(zchar,'(I1)') jl 
     266         DO jk = 1, nlay_i  
     267            WRITE(zchar1,'(I1)') jk 
     268            znam = 'sxe'//'_il'//zchar1//'_htc'//zchar 
     269            z2d(:,:) = sxe(:,:,jk,jl) 
     270            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     271            znam = 'sxxe'//'_il'//zchar1//'_htc'//zchar 
     272            z2d(:,:) = sxxe(:,:,jk,jl) 
     273            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     274            znam = 'syye'//'_il'//zchar1//'_htc'//zchar 
     275            z2d(:,:) = syye(:,:,jk,jl) 
     276            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     277            znam = 'sxye'//'_il'//zchar1//'_htc'//zchar 
     278            z2d(:,:) = sxye(:,:,jk,jl) 
     279            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     280         END DO 
     281      END DO 
     282 
     283      IF( iter == nitrst ) THEN 
     284         CALL iom_close( numriw )                         ! close the restart file 
     285         lrst_ice = .FALSE. 
     286      ENDIF 
     287      ! 
     288    
     289   !+++++++++++ CHECK EVERYTHING ++++++++++ 
     290               WRITE(numout,*) 
     291               WRITE(numout,*) ' lim_rst_write : CHUKCHI SEA POINT ' 
     292               WRITE(numout,*) ' ~~~~~~~~~~' 
     293               WRITE(numout,*) ' ~~~ Arctic' 
     294    
     295               ji = jiindex 
     296               jj = jjindex 
     297    
     298               WRITE(numout,*) ' ji, jj ', ji, jj 
     299               WRITE(numout,*) ' ICE VARIABLES ' 
     300               WRITE(numout,*) ' open water ', ato_i(ji,jj) 
     301               DO jl = 1, jpl 
     302                  WRITE(numout,*) ' *** CATEGORY NUMBER *** ', jl 
     303                  WRITE(numout,*) ' ' 
     304                  WRITE(numout,*) ' a_i        : ', a_i(ji,jj,jl)      
     305                  WRITE(numout,*) ' v_i        : ', v_i(ji,jj,jl)  
     306                  WRITE(numout,*) ' v_s        : ', v_s(ji,jj,jl)     
     307                  WRITE(numout,*) ' e_s        : ', e_s(ji,jj,1,jl)/1.0e9 
     308                  WRITE(numout,*) ' e_i1       : ', e_i(ji,jj,1,jl)/1.0e9       
     309                  WRITE(numout,*) ' e_i2       : ', e_i(ji,jj,2,jl)/1.0e9       
     310                  WRITE(numout,*) ' smv_i      : ', smv_i(ji,jj,jl)   
     311                  WRITE(numout,*) ' oa_i       : ', oa_i(ji,jj,jl) 
     312                  WRITE(numout,*) ' t_su       : ', t_su(ji,jj,jl) 
    299313               END DO 
    300             END DO 
    301  
    302             DO jl = 1, 40*jpl+5*(nlay_i-1)  
    303                WRITE(numout,*) ' zmoment No ', jl,' = ', zmoment(ji,jj,jl) 
    304             END DO 
    305  
    306 !+++++++++++ END CHECK +++++++++++++++++ 
    307  
    308    END SUBROUTINE lim_rst_write 
    309  
    310  
    311    SUBROUTINE lim_rst_read( niter ) 
    312       !----------------------------------------------------------------------- 
    313       !  restart from a state defined in a binary file 
    314       !----------------------------------------------------------------------- 
    315       ! Arguments 
    316       INTEGER  ::   niter        ! number of iteration 
    317  
    318       !- dummy variables : 
    319       CHARACTER(len=45)  ::  & 
    320          ccfile = 'restart_ice_in.nc' 
    321       INTEGER :: & 
    322         ji, jj, jk, jl, index 
    323       INTEGER :: & 
    324          inumrst, it0, it1, itime, ibvar, ifice 
    325       LOGICAL :: & 
    326          llog 
    327       REAL(wp),DIMENSION(jpi,jpj) :: & 
    328          zlamt, zphit 
    329       REAL(wp),DIMENSION(jpi,jpj,40*jpl+5*(nlay_i-1)) :: & 
    330          zmoment 
    331       REAL(wp),DIMENSION(1) :: & 
    332          zdept 
    333       REAL(wp),DIMENSION(2) :: & 
    334          zinfo 
    335       REAL(wp) :: & 
    336          zdate0, zdt 
     314    
     315               WRITE(numout,*) ' MOMENTS OF ADVECTION ' 
     316    
     317               WRITE(numout,*) ' open water ' 
     318               WRITE(numout,*) ' sxopw  ', sxopw(ji,jj) 
     319               WRITE(numout,*) ' syopw  ', syopw(ji,jj) 
     320               WRITE(numout,*) ' sxxopw ', sxxopw(ji,jj) 
     321               WRITE(numout,*) ' syyopw ', syyopw(ji,jj) 
     322               WRITE(numout,*) ' sxyopw ', sxyopw(ji,jj) 
     323               DO jl = 1, jpl 
     324                  WRITE(numout,*) ' jl, ice volume content ', jl 
     325                  WRITE(numout,*) ' sxice  ', sxice(ji,jj,jl) 
     326                  WRITE(numout,*) ' syice  ', syice(ji,jj,jl) 
     327                  WRITE(numout,*) ' sxxice ', sxxice(ji,jj,jl) 
     328                  WRITE(numout,*) ' syyice ', syyice(ji,jj,jl) 
     329                  WRITE(numout,*) ' sxyice ', sxyice(ji,jj,jl) 
     330                  WRITE(numout,*) ' jl, snow volume content ', jl 
     331                  WRITE(numout,*) ' sxsn   ', sxsn(ji,jj,jl) 
     332                  WRITE(numout,*) ' sysn   ', sysn(ji,jj,jl) 
     333                  WRITE(numout,*) ' sxxsn  ', sxxsn(ji,jj,jl) 
     334                  WRITE(numout,*) ' syysn  ', syysn(ji,jj,jl) 
     335                  WRITE(numout,*) ' sxysn  ', sxysn(ji,jj,jl) 
     336                  WRITE(numout,*) ' jl, ice area in category ', jl 
     337                  WRITE(numout,*) ' sxa    ', sxa (ji,jj,jl) 
     338                  WRITE(numout,*) ' sya    ', sya (ji,jj,jl) 
     339                  WRITE(numout,*) ' sxxa   ', sxxa (ji,jj,jl) 
     340                  WRITE(numout,*) ' syya   ', syya (ji,jj,jl) 
     341                  WRITE(numout,*) ' sxya   ', sxya (ji,jj,jl) 
     342                  WRITE(numout,*) ' jl, snow temp ', jl 
     343                  WRITE(numout,*) ' sxc0   ', sxc0(ji,jj,jl) 
     344                  WRITE(numout,*) ' syc0   ', syc0(ji,jj,jl) 
     345                  WRITE(numout,*) ' sxxc0  ', sxxc0(ji,jj,jl) 
     346                  WRITE(numout,*) ' syyc0  ', syyc0(ji,jj,jl) 
     347                  WRITE(numout,*) ' sxyc0  ', sxyc0(ji,jj,jl) 
     348                  WRITE(numout,*) ' jl, ice salinity ', jl 
     349                  WRITE(numout,*) ' sxsal  ', sxsal(ji,jj,jl) 
     350                  WRITE(numout,*) ' sysal  ', sysal(ji,jj,jl) 
     351                  WRITE(numout,*) ' sxxsal ', sxxsal(ji,jj,jl) 
     352                  WRITE(numout,*) ' syysal ', syysal(ji,jj,jl) 
     353                  WRITE(numout,*) ' sxysal ', sxysal(ji,jj,jl) 
     354                  WRITE(numout,*) ' jl, ice age      ', jl 
     355                  WRITE(numout,*) ' sxage  ', sxage(ji,jj,jl) 
     356                  WRITE(numout,*) ' syage  ', syage(ji,jj,jl) 
     357                  WRITE(numout,*) ' sxxage ', sxxage(ji,jj,jl) 
     358                  WRITE(numout,*) ' syyage ', syyage(ji,jj,jl) 
     359                  WRITE(numout,*) ' sxyage ', sxyage(ji,jj,jl) 
     360               END DO 
     361               DO jl = 1, jpl 
     362                  DO jk = 1, nlay_i 
     363                     WRITE(numout,*) ' jk, jl, ice heat content', jk, jl 
     364                     WRITE(numout,*) ' sxe    ', sxe(ji,jj,jk,jl) 
     365                     WRITE(numout,*) ' sye    ', sye(ji,jj,jk,jl) 
     366                     WRITE(numout,*) ' sxxe   ', sxxe(ji,jj,jk,jl) 
     367                     WRITE(numout,*) ' syye   ', syye(ji,jj,jk,jl) 
     368                     WRITE(numout,*) ' sxye   ', sxye(ji,jj,jk,jl) 
     369                  END DO 
     370               END DO 
     371    
     372   !+++++++++++ END CHECK +++++++++++++++++ 
     373    
     374      END SUBROUTINE lim_rst_write 
     375    
     376   SUBROUTINE lim_rst_read 
     377      !!---------------------------------------------------------------------- 
     378      !!                    ***  lim_rst_read  *** 
     379      !! 
     380      !! ** purpose  :   read of sea-ice variable restart in a netcdf file 
     381      !!---------------------------------------------------------------------- 
     382      ! Local variables 
     383      INTEGER :: ji, jj, jk, jl, index 
     384      REAL(wp) ::   zfice, ziter 
    337385      REAL(wp) :: & !parameters for the salinity profile 
    338386         zs_inf, z_slope_s, zsmax, zsmin, zalpha, zindb 
    339       REAL(wp), DIMENSION(nlay_i) :: & 
    340          zs_zero  
    341       REAL(wp), DIMENSION(jpi,jpj,jpl) :: & 
    342          zheatcon 
    343       CHARACTER(len=7), DIMENSION(jpk) :: zheatnam 
    344       CHARACTER(len=1)                 :: zchar 
    345       CHARACTER ( len = 10 ) ::  & 
    346          clvnames(60)        
    347  
    348 !     !Read inumrst 
    349 !     INQUIRE ( FILE = ccfile , EXIST = llbon) 
    350 !     IF( .NOT. llbon ) THEN 
    351 !        IF(lwp)WRITE(numout,cform_err) 
    352 !        IF(lwp)WRITE(numout,*) 'lim_rst_read : ===>>>> : Le fichier restart ',ccfile,' n''existe pas' 
    353 !        nstop = nstop + 1 
    354 !     ENDIF 
    355  
    356       !Initialisations 
    357       inumrst    = 71 
    358       it0        = nit000 
    359       itime      = 0 
    360       llog       = .FALSE. 
    361       zlamt(:,:) = 0. 
    362       zphit(:,:) = 0. 
    363       zdept(1)   = 0. 
    364  
    365       CALL restini(ccfile , jpi, jpj, zlamt, zphit, 1 , zdept, ccfile, itime, zdate0, zdt, inumrst )       
    366       CALL ioget_vname( inumrst, ibvar, clvnames ) 
    367  
    368       CALL restget    ( inumrst,'info', 1, 1 , 2, 0, llog, zinfo ) 
    369   
    370       ifice   = INT( zinfo(1) ) 
    371       it1     = INT( zinfo(2) ) 
    372  
     387      REAL(wp), DIMENSION(nlay_i) :: zs_zero  
     388      REAL(wp), DIMENSION(jpi,jpj) :: z2d 
     389      CHARACTER(len=15) :: znam 
     390      CHARACTER(len=1) :: zchar, zchar1 
     391      !!---------------------------------------------------------------------- 
     392    
    373393      IF(lwp) THEN 
    374394         WRITE(numout,*) 
    375          WRITE(numout,*) 'lim_rst_read : READ restart file name ', ccfile,' at time step : ', it1 
    376          WRITE(numout,*) '~~~~~~~~~~~~   number of variables   : ', ibvar 
    377          WRITE(numout,*) '               NetCDF variables      : ', clvnames(1:ibvar) 
     395         WRITE(numout,*) 'lim_rst_read : read ice NetCDF restart file' 
     396         WRITE(numout,*) '~~~~~~~~~~~~~~' 
    378397      ENDIF 
    379398 
    380        
     399      CALL iom_open ( 'restart_ice_in', numrir, kiolib = jprstlib ) 
     400 
     401      CALL iom_get( numrir, 'nfice' , zfice ) 
     402      CALL iom_get( numrir, 'kt_ice', ziter )     
     403      IF(lwp) WRITE(numout,*) '   read ice restart file at time step    : ', ziter 
     404      IF(lwp) WRITE(numout,*) '   in any case we force it to nit000 - 1 : ', nit000 - 1 
     405 
    381406      !Control of date 
    382407       
    383       IF( ( it0 - it1 ) /= 1 .AND. ABS( nrstdt ) == 1 ) THEN 
    384          IF(lwp) THEN 
    385             WRITE(numout,cform_err) 
    386             WRITE(numout,*) 'lim_rst_read ===>>>> : problem with nit000 for the restart' 
    387             WRITE(numout,*) '   we stop. verify the file or rerun with the value  0 for the' 
    388             WRITE(numout,*) '   control of time parameter  nrstdt' 
    389             nstop = nstop + 1 
    390          ENDIF 
    391       ENDIF 
    392  
    393       CALL restget( inumrst, 'v_i '   , jpi, jpj, jpl , 0, llog, v_i     ) 
    394       CALL restget( inumrst, 'v_s '   , jpi, jpj, jpl , 0, llog, v_s     ) 
    395       CALL restget( inumrst, 'smv_i'  , jpi, jpj, jpl , 0, llog, smv_i  ) 
    396       CALL restget( inumrst, 'oa_i '  , jpi, jpj, jpl , 0, llog, oa_i     ) 
    397       CALL restget( inumrst, 'a_i '   , jpi, jpj, jpl , 0, llog, a_i   ) 
    398       CALL restget( inumrst, 't_su'   , jpi, jpj, jpl , 0, llog, t_su  ) 
     408      IF( ( nit000 - INT(ziter) ) /= 1 .AND. ABS( nrstdt ) == 1 )   & 
     409         &     CALL ctl_stop( 'lim_rst_read ===>>>> : problem with nit000 in ice restart',  & 
     410         &                   '   verify the file or rerun with the value 0 for the',        & 
     411         &                   '   control of time parameter  nrstdt' ) 
     412      IF( INT(zfice) /= nfice          .AND. ABS( nrstdt ) == 1 )   & 
     413         &     CALL ctl_stop( 'lim_rst_read ===>>>> : problem with nfice in ice restart',  & 
     414         &                   '   verify the file or rerun with the value 0 for the',        & 
     415         &                   '   control of time parameter  nrstdt' ) 
     416 
     417      DO jl = 1, jpl  
     418         WRITE(zchar,'(I1)') jl 
     419         znam = 'v_i'//'_htc'//zchar 
     420         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     421         v_i(:,:,jl) = z2d(:,:) 
     422         znam = 'v_s'//'_htc'//zchar 
     423         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     424         v_s(:,:,jl) = z2d(:,:)  
     425         znam = 'smv_i'//'_htc'//zchar 
     426         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     427         smv_i(:,:,jl) = z2d(:,:) 
     428         znam = 'oa_i'//'_htc'//zchar 
     429         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     430         oa_i(:,:,jl) = z2d(:,:) 
     431         znam = 'a_i'//'_htc'//zchar 
     432         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     433         a_i(:,:,jl) = z2d(:,:) 
     434         znam = 't_su'//'_htc'//zchar 
     435         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     436         t_su(:,:,jl) = z2d(:,:) 
     437      END DO 
    399438 
    400439      ! we first with bulk ice salinity 
     
    408447         END DO 
    409448      END DO 
    410  
     449    
    411450      DO jk = 1, nlay_i 
    412451         s_i(:,:,jk,:) = sm_i(:,:,:) 
    413452      END DO 
    414  
     453    
    415454      ! Salinity profile 
    416       !-------------------------------------- 
     455      !----------------- 
    417456      WRITE(numout,*) ' num_sal - will restart understand salinity profile ', num_sal 
    418  
     457    
    419458      num_sal = 2 
    420       IF (num_sal.eq.2) THEN 
    421 !        CALL lim_var_salprof 
     459      IF(num_sal.eq.2) THEN 
     460   !     CALL lim_var_salprof 
    422461         DO jl = 1, jpl 
    423          DO jk = 1, nlay_i 
    424          DO jj = 1, jpj 
    425          DO ji = 1, jpi 
    426             zs_inf        = sm_i(ji,jj,jl) 
    427             z_slope_s     = 2.0*sm_i(ji,jj,jl)/MAX(0.01,ht_i(ji,jj,jl)) 
    428                             !- slope of the salinity profile 
    429             zs_zero(jk)   = z_slope_s * ( FLOAT(jk)-1.0/2.0 ) * & 
    430                                          ht_i(ji,jj,jl) / FLOAT(nlay_i) 
    431             zsmax = 4.5 
    432             zsmin = 3.5 
    433             IF ( sm_i(ji,jj,jl) .LT. zsmin ) THEN 
    434                zalpha = 1.0 
    435             ELSEIF ( sm_i(ji,jj,jl) .LT.zsmax ) THEN 
    436                zalpha = sm_i(ji,jj,jl) / (zsmin-zsmax) + zsmax / (zsmax-zsmin) 
    437             ELSE 
    438                zalpha = 0.0 
    439             ENDIF 
    440             s_i(ji,jj,jk,jl) = zalpha*zs_zero(jk) + ( 1.0 - zalpha )*zs_inf 
    441          END DO 
    442          END DO 
    443          END DO 
    444          END DO 
    445          WRITE(numout,*) ' RESTART UNDERSTOOD SALINITY PROFILE ' 
    446       ENDIF 
    447        
    448 # if defined key_coupled  
    449       CALL restget( inumrst, 'albege' , jpi, jpj, 1 , 0, llog, albege  ) 
    450 # endif 
    451       CALL restget( inumrst, 'tempts1', jpi, jpj, jpl , 0, llog, zheatcon ) 
    452       e_s(:,:,1,:) = zheatcon(:,:,:) 
    453  
    454       DO jk = 1, nlay_i  
    455          WRITE(zchar,'(I1)') jk 
    456          WRITE(numout,*)  'zchar : ', zchar 
    457          zheatnam(jk) = 'tempti'//zchar 
    458          WRITE(numout,*)  'zheatnam(jk) : ', zheatnam(jk) 
    459          CALL restget( inumrst, zheatnam(jk), jpi, jpj, jpl , 0, llog, zheatcon ) 
    460          e_i(:,:,jk,:) = zheatcon(:,:,:) 
    461       END DO 
    462  
    463       CALL restget( inumrst, 'u_ice'  , jpi, jpj, 1 , 0, llog, u_ice   ) 
    464       CALL restget( inumrst, 'v_ice'  , jpi, jpj, 1 , 0, llog, v_ice   ) 
    465       CALL restget( inumrst, 'gtaux'  , jpi, jpj, 1 , 0, llog, gtaux   ) 
    466       CALL restget( inumrst, 'gtauy'  , jpi, jpj, 1 , 0, llog, gtauy   ) 
    467       CALL restget( inumrst, 'fsbbq'  , jpi, jpj, 1 , 0, llog, fsbbq   ) 
    468       !---- 
    469       stress1_i(:,:) = 0.0 
    470       stress2_i(:,:) = 0.0 
    471       stress12_i(:,:) = 0.0 
    472 !     CALL restget( inumwrs, 'str1_i' , jpi, jpj, 1 , 0, stress1_i ) 
    473 !     CALL restget( inumwrs, 'str2_i' , jpi, jpj, 1 , 0, stress2_i ) 
    474 !     CALL restget( inumwrs, 'str12i' , jpi, jpj, 1 , 0, stress12_i ) 
    475       !---- 
    476       CALL restget( inumrst, 'moment' , jpi, jpj, 40*jpl+5*(nlay_i-1), 0, llog, zmoment ) 
    477       WRITE(numout,*) 'MOMENT DIMENSION ', (40*jpl+5*(nlay_i-1)) 
    478  
    479       CALL restclo( inumrst ) 
    480  
    481       niter = it1 
    482  
    483         WRITE(numout,*) ' jl, FIELD No ' 
    484         DO jl = 1, jpl 
    485         WRITE(numout,*) jl, 6*5*(jl-1)+1, 6*5*(jl-1)+30 
    486    DO jj = 1, jpj              ! 3D array: 10 time faster than 35 restput 
    487    DO ji = 1, jpi 
    488         sxice(ji,jj,jl) = zmoment(ji,jj,6*5*(jl-1)+1) 
    489         syice(ji,jj,jl) = zmoment(ji,jj,6*5*(jl-1)+2) 
    490         sxxice(ji,jj,jl)= zmoment(ji,jj,6*5*(jl-1)+3) 
    491         syyice(ji,jj,jl)= zmoment(ji,jj,6*5*(jl-1)+4) 
    492         sxyice(ji,jj,jl)= zmoment(ji,jj,6*5*(jl-1)+5) 
    493         sxsn(ji,jj,jl)  = zmoment(ji,jj,6*5*(jl-1)+6) 
    494         sysn(ji,jj,jl)  = zmoment(ji,jj,6*5*(jl-1)+7) 
    495         sxxsn(ji,jj,jl) = zmoment(ji,jj,6*5*(jl-1)+8) 
    496         syysn(ji,jj,jl) = zmoment(ji,jj,6*5*(jl-1)+9) 
    497         sxysn(ji,jj,jl) = zmoment(ji,jj,6*5*(jl-1)+10) 
    498         sxa(ji,jj,jl)   = zmoment(ji,jj,6*5*(jl-1)+11) 
    499         sya(ji,jj,jl)   = zmoment(ji,jj,6*5*(jl-1)+12) 
    500         sxxa(ji,jj,jl)  = zmoment(ji,jj,6*5*(jl-1)+13) 
    501         syya(ji,jj,jl)  = zmoment(ji,jj,6*5*(jl-1)+14) 
    502         sxya(ji,jj,jl)  = zmoment(ji,jj,6*5*(jl-1)+15) 
    503         sxc0(ji,jj,jl)  = zmoment(ji,jj,6*5*(jl-1)+16) 
    504         syc0(ji,jj,jl)  = zmoment(ji,jj,6*5*(jl-1)+17) 
    505         sxxc0(ji,jj,jl) = zmoment(ji,jj,6*5*(jl-1)+18) 
    506         syyc0(ji,jj,jl) = zmoment(ji,jj,6*5*(jl-1)+19) 
    507         sxyc0(ji,jj,jl) = zmoment(ji,jj,6*5*(jl-1)+20) 
    508         sxsal(ji,jj,jl) = zmoment(ji,jj,6*5*(jl-1)+21) 
    509         sysal(ji,jj,jl) = zmoment(ji,jj,6*5*(jl-1)+22) 
    510         sxxsal(ji,jj,jl)= zmoment(ji,jj,6*5*(jl-1)+23) 
    511         syysal(ji,jj,jl)= zmoment(ji,jj,6*5*(jl-1)+24) 
    512         sxysal(ji,jj,jl)= zmoment(ji,jj,6*5*(jl-1)+25) 
    513         sxage(ji,jj,jl) = zmoment(ji,jj,6*5*(jl-1)+26) 
    514         syage(ji,jj,jl) = zmoment(ji,jj,6*5*(jl-1)+27) 
    515         sxxage(ji,jj,jl)= zmoment(ji,jj,6*5*(jl-1)+28) 
    516         syyage(ji,jj,jl)= zmoment(ji,jj,6*5*(jl-1)+29) 
    517         sxyage(ji,jj,jl)= zmoment(ji,jj,6*5*(jl-1)+30) 
    518         END DO  
    519         END DO 
    520         END DO 
    521  
    522         WRITE(numout,*) ' jk, jl, FIELD No ' 
    523         DO jl = 1, jpl 
    524         DO jk = 1, nlay_i  
    525         WRITE(numout,*) 5*(6*jpl+(jk-1)+2*(jl-1))+1, 5*(6*jpl+(jk-1)+2*(jl-1))+5 
    526    DO jj = 1, jpj              ! 3D array: 10 time faster than 35 restput 
    527    DO ji = 1, jpi 
    528         sxe(ji,jj,jk,jl) = zmoment(ji,jj,5*(6*jpl+(jk-1)+2*(jl-1))+1) 
    529         sye(ji,jj,jk,jl) = zmoment(ji,jj,5*(6*jpl+(jk-1)+2*(jl-1))+2) 
    530         sxxe(ji,jj,jk,jl)= zmoment(ji,jj,5*(6*jpl+(jk-1)+2*(jl-1))+3) 
    531         syye(ji,jj,jk,jl)= zmoment(ji,jj,5*(6*jpl+(jk-1)+2*(jl-1))+4) 
    532         sxye(ji,jj,jk,jl)= zmoment(ji,jj,5*(6*jpl+(jk-1)+2*(jl-1))+5) 
    533    END DO 
    534    END DO 
    535         END DO 
    536         END DO 
    537         WRITE(numout,*) 40*jpl+5*nlay_i-10 + 1, 40*jpl+5*nlay_i - 10 + 5 
    538    DO jj = 1, jpj              ! 3D array: 10 time faster than 35 restput 
    539    DO ji = 1, jpi 
    540         sxopw(ji,jj) = zmoment(ji,jj,40*jpl + 5*nlay_i - 10 + 1) 
    541         syopw(ji,jj) = zmoment(ji,jj,40*jpl + 5*nlay_i - 10 + 2) 
    542         sxxopw(ji,jj)= zmoment(ji,jj,40*jpl + 5*nlay_i - 10 + 3) 
    543         syyopw(ji,jj)= zmoment(ji,jj,40*jpl + 5*nlay_i - 10 + 4) 
    544         sxyopw(ji,jj)= zmoment(ji,jj,40*jpl + 5*nlay_i - 10 + 5) 
    545         END DO 
    546         END DO 
    547  
    548 !+++++++++++ CHECK EVERYTHING ++++++++++ 
    549  
    550             WRITE(numout,*) 
    551             WRITE(numout,*) ' lim_rst_read  : CHUKCHI SEA POINT ' 
    552             WRITE(numout,*) ' ~~~~~~~~~~' 
    553             WRITE(numout,*) ' ~~~ Arctic' 
    554  
    555             index = 1 
    556             ji = 24 
    557             jj = 24 
    558             WRITE(numout,*) ' ji, jj ', ji, jj 
    559             WRITE(numout,*) ' ICE VARIABLES ' 
    560             WRITE(numout,*) ' open water ', ato_i(ji,jj) 
    561  
    562             DO jl = 1, jpl 
    563                WRITE(numout,*) ' *** CATEGORY NUMBER *** ', jl 
    564                WRITE(numout,*) ' ' 
    565                WRITE(numout,*) ' a_i        : ', a_i(ji,jj,jl)      
    566                WRITE(numout,*) ' v_i        : ', v_i(ji,jj,jl)  
    567                WRITE(numout,*) ' v_s        : ', v_s(ji,jj,jl)     
    568                WRITE(numout,*) ' e_i1       : ', e_i(ji,jj,1,jl)/1.0e9       
    569                WRITE(numout,*) ' e_i2       : ', e_i(ji,jj,2,jl)/1.0e9       
    570                WRITE(numout,*) ' e_s        : ', e_s(ji,jj,1,jl)       
    571                WRITE(numout,*) ' smv_i      : ', smv_i(ji,jj,jl)   
    572                WRITE(numout,*) ' oa_i       : ', oa_i(ji,jj,jl) 
    573                WRITE(numout,*) ' t_su       : ', t_su(ji,jj,jl) 
    574             END DO 
    575  
    576             WRITE(numout,*) ' open water ' 
    577             WRITE(numout,*) ' sxopw  ', sxopw(ji,jj) 
    578             WRITE(numout,*) ' syopw  ', syopw(ji,jj) 
    579             WRITE(numout,*) ' sxxopw ', sxxopw(ji,jj) 
    580             WRITE(numout,*) ' syyopw ', syyopw(ji,jj) 
    581             WRITE(numout,*) ' sxyopw ', sxyopw(ji,jj) 
    582             DO jl = 1, jpl 
    583                WRITE(numout,*) ' jl, ice volume content ', jl 
    584                WRITE(numout,*) ' sxice  ', sxice(ji,jj,jl) 
    585                WRITE(numout,*) ' syice  ', syice(ji,jj,jl) 
    586                WRITE(numout,*) ' sxxice ', sxxice(ji,jj,jl) 
    587                WRITE(numout,*) ' syyice ', syyice(ji,jj,jl) 
    588                WRITE(numout,*) ' sxyice ', sxyice(ji,jj,jl) 
    589                WRITE(numout,*) ' jl, snow volume content ', jl 
    590                WRITE(numout,*) ' sxsn   ', sxsn(ji,jj,jl) 
    591                WRITE(numout,*) ' sysn   ', sysn(ji,jj,jl) 
    592                WRITE(numout,*) ' sxxsn  ', sxxsn(ji,jj,jl) 
    593                WRITE(numout,*) ' syysn  ', syysn(ji,jj,jl) 
    594                WRITE(numout,*) ' sxysn  ', sxysn(ji,jj,jl) 
    595                WRITE(numout,*) ' jl, ice area in category ', jl 
    596                WRITE(numout,*) ' sxa    ', sxa (ji,jj,jl) 
    597                WRITE(numout,*) ' sya    ', sya (ji,jj,jl) 
    598                WRITE(numout,*) ' sxxa   ', sxxa (ji,jj,jl) 
    599                WRITE(numout,*) ' syya   ', syya (ji,jj,jl) 
    600                WRITE(numout,*) ' sxya   ', sxya (ji,jj,jl) 
    601                WRITE(numout,*) ' jl, snow temp ', jl 
    602                WRITE(numout,*) ' sxc0   ', sxc0(ji,jj,jl) 
    603                WRITE(numout,*) ' syc0   ', syc0(ji,jj,jl) 
    604                WRITE(numout,*) ' sxxc0  ', sxxc0(ji,jj,jl) 
    605                WRITE(numout,*) ' syyc0  ', syyc0(ji,jj,jl) 
    606                WRITE(numout,*) ' sxyc0  ', sxyc0(ji,jj,jl) 
    607                WRITE(numout,*) ' jl, ice salinity ', jl 
    608                WRITE(numout,*) ' sxsal  ', sxsal(ji,jj,jl) 
    609                WRITE(numout,*) ' sysal  ', sysal(ji,jj,jl) 
    610                WRITE(numout,*) ' sxxsal ', sxxsal(ji,jj,jl) 
    611                WRITE(numout,*) ' syysal ', syysal(ji,jj,jl) 
    612                WRITE(numout,*) ' sxysal ', sxysal(ji,jj,jl) 
    613                WRITE(numout,*) ' jl, ice age      ', jl 
    614                WRITE(numout,*) ' sxage  ', sxage(ji,jj,jl) 
    615                WRITE(numout,*) ' syage  ', syage(ji,jj,jl) 
    616                WRITE(numout,*) ' sxxage ', sxxage(ji,jj,jl) 
    617                WRITE(numout,*) ' syyage ', syyage(ji,jj,jl) 
    618                WRITE(numout,*) ' sxyage ', sxyage(ji,jj,jl) 
    619             END DO 
    620             DO jl = 1, jpl 
    621                DO jk = 1, nlay_i 
    622                   WRITE(numout,*) ' jk, jl, ice heat content', jk, jl 
    623                   WRITE(numout,*) ' sxe    ', sxe(ji,jj,jk,jl) 
    624                   WRITE(numout,*) ' sye    ', sye(ji,jj,jk,jl) 
    625                   WRITE(numout,*) ' sxxe   ', sxxe(ji,jj,jk,jl) 
    626                   WRITE(numout,*) ' syye   ', syye(ji,jj,jk,jl) 
    627                   WRITE(numout,*) ' sxye   ', sxye(ji,jj,jk,jl) 
     462            DO jk = 1, nlay_i 
     463               DO jj = 1, jpj 
     464                  DO ji = 1, jpi 
     465                     zs_inf        = sm_i(ji,jj,jl) 
     466                     z_slope_s     = 2.0*sm_i(ji,jj,jl)/MAX(0.01,ht_i(ji,jj,jl)) 
     467                                     !- slope of the salinity profile 
     468                     zs_zero(jk)   = z_slope_s * ( FLOAT(jk)-1.0/2.0 ) * & 
     469                                                  ht_i(ji,jj,jl) / FLOAT(nlay_i) 
     470                     zsmax = 4.5 
     471                     zsmin = 3.5 
     472                     IF( sm_i(ji,jj,jl) .LT. zsmin ) THEN 
     473                        zalpha = 1.0 
     474                     ELSEIF( sm_i(ji,jj,jl) .LT.zsmax ) THEN 
     475                        zalpha = sm_i(ji,jj,jl) / (zsmin-zsmax) + zsmax / (zsmax-zsmin) 
     476                     ELSE 
     477                        zalpha = 0.0 
     478                     ENDIF 
     479                     s_i(ji,jj,jk,jl) = zalpha*zs_zero(jk) + ( 1.0 - zalpha )*zs_inf 
     480                  END DO 
    628481               END DO 
    629482            END DO 
    630  
    631             DO jl = 1, 40*jpl+5*(nlay_i-1)  
    632                WRITE(numout,*) ' zmoment No ', jl,' = ', zmoment(ji,jj,jl) 
    633             END DO 
    634  
    635 !+++++++++++ END CHECK +++++++++++++++++ 
    636  
    637    END SUBROUTINE lim_rst_read 
    638  
     483         END DO 
     484      ENDIF 
     485          
     486# if defined key_coupled  
     487      CALL iom_get( numrir, jpdom_autoglo, 'albege'   , albege ) 
    639488# endif 
    640  
     489      DO jl = 1, jpl  
     490         WRITE(zchar,'(I1)') jl 
     491         znam = 'tempt_sl1'//'_htc'//zchar 
     492         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     493         e_s(:,:,1,jl) = z2d(:,:) 
     494      END DO 
     495    
     496      DO jl = 1, jpl  
     497         WRITE(zchar,'(I1)') jl 
     498         DO jk = 1, nlay_i  
     499            WRITE(zchar1,'(I1)') jk 
     500            znam = 'tempt'//'_il'//zchar1//'_htc'//zchar 
     501            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     502            e_i(:,:,jk,jl) = z2d(:,:) 
     503         END DO 
     504      END DO 
     505 
     506      CALL iom_get( numrir, jpdom_autoglo, 'u_ice'     , u_ice      ) 
     507      CALL iom_get( numrir, jpdom_autoglo, 'v_ice'     , v_ice      ) 
     508      CALL iom_get( numrir, jpdom_autoglo, 'gtaux'     , gtaux      ) 
     509      CALL iom_get( numrir, jpdom_autoglo, 'gtauy'     , gtauy      ) 
     510      CALL iom_get( numrir, jpdom_autoglo, 'fsbbq'     , fsbbq      ) 
     511      CALL iom_get( numrir, jpdom_autoglo, 'stress1_i' , stress1_i  ) 
     512      CALL iom_get( numrir, jpdom_autoglo, 'stress2_i' , stress2_i  ) 
     513      CALL iom_get( numrir, jpdom_autoglo, 'stress12_i', stress12_i ) 
     514 
     515      DO jl = 1, jpl  
     516         WRITE(zchar,'(I1)') jl 
     517         znam = 'sxice'//'_htc'//zchar 
     518         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     519         sxice(:,:,jl) = z2d(:,:) 
     520         znam = 'syice'//'_htc'//zchar 
     521         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     522         syice(:,:,jl) = z2d(:,:) 
     523         znam = 'sxxice'//'_htc'//zchar 
     524         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     525         sxxice(:,:,jl) = z2d(:,:) 
     526         znam = 'syyice'//'_htc'//zchar 
     527         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     528         syyice(:,:,jl) = z2d(:,:) 
     529         znam = 'sxsn'//'_htc'//zchar 
     530         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     531         sxsn(:,:,jl) = z2d(:,:) 
     532         znam = 'sysn'//'_htc'//zchar 
     533         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     534         sysn(:,:,jl) = z2d(:,:) 
     535         znam = 'sxxsn'//'_htc'//zchar 
     536         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     537         sxxsn(:,:,jl) = z2d(:,:) 
     538         znam = 'syysn'//'_htc'//zchar 
     539         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     540         syysn(:,:,jl) = z2d(:,:) 
     541         znam = 'sxysn'//'_htc'//zchar 
     542         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     543         sxysn(:,:,jl) = z2d(:,:) 
     544         znam = 'sxa'//'_htc'//zchar 
     545         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     546         sxa(:,:,jl) = z2d(:,:) 
     547         znam = 'sya'//'_htc'//zchar 
     548         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     549         sya(:,:,jl) = z2d(:,:) 
     550         znam = 'sxxa'//'_htc'//zchar 
     551         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     552         sxxa(:,:,jl) = z2d(:,:) 
     553         znam = 'syya'//'_htc'//zchar 
     554         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     555         syya(:,:,jl) = z2d(:,:) 
     556         znam = 'sxya'//'_htc'//zchar 
     557         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     558         sxya(:,:,jl) = z2d(:,:) 
     559         znam = 'sxc0'//'_htc'//zchar 
     560         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     561         sxc0(:,:,jl) = z2d(:,:) 
     562         znam = 'syc0'//'_htc'//zchar 
     563         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     564         syc0(:,:,jl) = z2d(:,:) 
     565         znam = 'sxxc0'//'_htc'//zchar 
     566         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     567         sxxc0(:,:,jl) = z2d(:,:) 
     568         znam = 'syyc0'//'_htc'//zchar 
     569         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     570         syyc0(:,:,jl) = z2d(:,:) 
     571         znam = 'sxyc0'//'_htc'//zchar 
     572         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     573         sxyc0(:,:,jl) = z2d(:,:) 
     574         znam = 'sxsal'//'_htc'//zchar 
     575         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     576         sxsal(:,:,jl) = z2d(:,:) 
     577         znam = 'sysal'//'_htc'//zchar 
     578         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     579         sysal(:,:,jl) = z2d(:,:) 
     580         znam = 'sxxsal'//'_htc'//zchar 
     581         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     582         sxxsal(:,:,jl) = z2d(:,:) 
     583         znam = 'syysal'//'_htc'//zchar 
     584         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     585         syysal(:,:,jl) = z2d(:,:) 
     586         znam = 'sxysal'//'_htc'//zchar 
     587         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     588         sxysal(:,:,jl) = z2d(:,:) 
     589         znam = 'sxage'//'_htc'//zchar 
     590         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     591         sxage(:,:,jl) = z2d(:,:) 
     592         znam = 'syage'//'_htc'//zchar 
     593         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     594         syage(:,:,jl) = z2d(:,:) 
     595         znam = 'sxxage'//'_htc'//zchar 
     596         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     597         sxxage(:,:,jl) = z2d(:,:) 
     598         znam = 'syyage'//'_htc'//zchar 
     599         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     600         syyage(:,:,jl) = z2d(:,:) 
     601         znam = 'sxyage'//'_htc'//zchar 
     602         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     603         sxyage(:,:,jl)= z2d(:,:) 
     604      END DO 
     605 
     606      CALL iom_get( numrir, jpdom_autoglo, 'sxopw ' ,  sxopw  ) 
     607      CALL iom_get( numrir, jpdom_autoglo, 'syopw ' ,  syopw  ) 
     608      CALL iom_get( numrir, jpdom_autoglo, 'sxxopw' ,  sxxopw ) 
     609      CALL iom_get( numrir, jpdom_autoglo, 'syyopw' ,  syyopw ) 
     610      CALL iom_get( numrir, jpdom_autoglo, 'sxyopw' ,  sxyopw ) 
     611 
     612      DO jl = 1, jpl  
     613         WRITE(zchar,'(I1)') jl 
     614         DO jk = 1, nlay_i  
     615            WRITE(zchar1,'(I1)') jk 
     616            znam = 'sxe'//'_il'//zchar1//'_htc'//zchar 
     617            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     618            sxe(:,:,jk,jl) = z2d(:,:) 
     619            znam = 'sxxe'//'_il'//zchar1//'_htc'//zchar 
     620            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     621            sxxe(:,:,jk,jl) = z2d(:,:) 
     622            znam = 'syye'//'_il'//zchar1//'_htc'//zchar 
     623            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     624            syye(:,:,jk,jl) = z2d(:,:) 
     625            znam = 'sxye'//'_il'//zchar1//'_htc'//zchar 
     626            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     627            sxye(:,:,jk,jl) = z2d(:,:) 
     628         END DO 
     629      END DO 
     630 
     631      !---- 
     632!CT start 
     633!      stress1_i(:,:) = 0.0 
     634!      stress2_i(:,:) = 0.0 
     635!      stress12_i(:,:) = 0.0 
     636!CT end 
     637      !---- 
     638      CALL iom_close( numrir ) 
     639 
     640   !+++++++++++ CHECK EVERYTHING ++++++++++ 
     641    
     642               WRITE(numout,*) 
     643               WRITE(numout,*) ' lim_rst_read  : CHUKCHI SEA POINT ' 
     644               WRITE(numout,*) ' ~~~~~~~~~~' 
     645               WRITE(numout,*) ' ~~~ Arctic' 
     646    
     647               index = 1 
     648               ji = 24 
     649               jj = 24 
     650               WRITE(numout,*) ' ji, jj ', ji, jj 
     651               WRITE(numout,*) ' ICE VARIABLES ' 
     652               WRITE(numout,*) ' open water ', ato_i(ji,jj) 
     653    
     654               DO jl = 1, jpl 
     655                  WRITE(numout,*) ' *** CATEGORY NUMBER *** ', jl 
     656                  WRITE(numout,*) ' ' 
     657                  WRITE(numout,*) ' a_i        : ', a_i(ji,jj,jl)      
     658                  WRITE(numout,*) ' v_i        : ', v_i(ji,jj,jl)  
     659                  WRITE(numout,*) ' v_s        : ', v_s(ji,jj,jl)     
     660                  WRITE(numout,*) ' e_i1       : ', e_i(ji,jj,1,jl)/1.0e9       
     661                  WRITE(numout,*) ' e_i2       : ', e_i(ji,jj,2,jl)/1.0e9       
     662                  WRITE(numout,*) ' e_s        : ', e_s(ji,jj,1,jl)       
     663                  WRITE(numout,*) ' smv_i      : ', smv_i(ji,jj,jl)   
     664                  WRITE(numout,*) ' oa_i       : ', oa_i(ji,jj,jl) 
     665                  WRITE(numout,*) ' t_su       : ', t_su(ji,jj,jl) 
     666               END DO 
     667    
     668               WRITE(numout,*) ' open water ' 
     669               WRITE(numout,*) ' sxopw  ', sxopw(ji,jj) 
     670               WRITE(numout,*) ' syopw  ', syopw(ji,jj) 
     671               WRITE(numout,*) ' sxxopw ', sxxopw(ji,jj) 
     672               WRITE(numout,*) ' syyopw ', syyopw(ji,jj) 
     673               WRITE(numout,*) ' sxyopw ', sxyopw(ji,jj) 
     674               DO jl = 1, jpl 
     675                  WRITE(numout,*) ' jl, ice volume content ', jl 
     676                  WRITE(numout,*) ' sxice  ', sxice(ji,jj,jl) 
     677                  WRITE(numout,*) ' syice  ', syice(ji,jj,jl) 
     678                  WRITE(numout,*) ' sxxice ', sxxice(ji,jj,jl) 
     679                  WRITE(numout,*) ' syyice ', syyice(ji,jj,jl) 
     680                  WRITE(numout,*) ' sxyice ', sxyice(ji,jj,jl) 
     681                  WRITE(numout,*) ' jl, snow volume content ', jl 
     682                  WRITE(numout,*) ' sxsn   ', sxsn(ji,jj,jl) 
     683                  WRITE(numout,*) ' sysn   ', sysn(ji,jj,jl) 
     684                  WRITE(numout,*) ' sxxsn  ', sxxsn(ji,jj,jl) 
     685                  WRITE(numout,*) ' syysn  ', syysn(ji,jj,jl) 
     686                  WRITE(numout,*) ' sxysn  ', sxysn(ji,jj,jl) 
     687                  WRITE(numout,*) ' jl, ice area in category ', jl 
     688                  WRITE(numout,*) ' sxa    ', sxa (ji,jj,jl) 
     689                  WRITE(numout,*) ' sya    ', sya (ji,jj,jl) 
     690                  WRITE(numout,*) ' sxxa   ', sxxa (ji,jj,jl) 
     691                  WRITE(numout,*) ' syya   ', syya (ji,jj,jl) 
     692                  WRITE(numout,*) ' sxya   ', sxya (ji,jj,jl) 
     693                  WRITE(numout,*) ' jl, snow temp ', jl 
     694                  WRITE(numout,*) ' sxc0   ', sxc0(ji,jj,jl) 
     695                  WRITE(numout,*) ' syc0   ', syc0(ji,jj,jl) 
     696                  WRITE(numout,*) ' sxxc0  ', sxxc0(ji,jj,jl) 
     697                  WRITE(numout,*) ' syyc0  ', syyc0(ji,jj,jl) 
     698                  WRITE(numout,*) ' sxyc0  ', sxyc0(ji,jj,jl) 
     699                  WRITE(numout,*) ' jl, ice salinity ', jl 
     700                  WRITE(numout,*) ' sxsal  ', sxsal(ji,jj,jl) 
     701                  WRITE(numout,*) ' sysal  ', sysal(ji,jj,jl) 
     702                  WRITE(numout,*) ' sxxsal ', sxxsal(ji,jj,jl) 
     703                  WRITE(numout,*) ' syysal ', syysal(ji,jj,jl) 
     704                  WRITE(numout,*) ' sxysal ', sxysal(ji,jj,jl) 
     705                  WRITE(numout,*) ' jl, ice age      ', jl 
     706                  WRITE(numout,*) ' sxage  ', sxage(ji,jj,jl) 
     707                  WRITE(numout,*) ' syage  ', syage(ji,jj,jl) 
     708                  WRITE(numout,*) ' sxxage ', sxxage(ji,jj,jl) 
     709                  WRITE(numout,*) ' syyage ', syyage(ji,jj,jl) 
     710                  WRITE(numout,*) ' sxyage ', sxyage(ji,jj,jl) 
     711               END DO 
     712               DO jl = 1, jpl 
     713                  DO jk = 1, nlay_i 
     714                     WRITE(numout,*) ' jk, jl, ice heat content', jk, jl 
     715                     WRITE(numout,*) ' sxe    ', sxe(ji,jj,jk,jl) 
     716                     WRITE(numout,*) ' sye    ', sye(ji,jj,jk,jl) 
     717                     WRITE(numout,*) ' sxxe   ', sxxe(ji,jj,jk,jl) 
     718                     WRITE(numout,*) ' syye   ', syye(ji,jj,jk,jl) 
     719                     WRITE(numout,*) ' sxye   ', sxye(ji,jj,jk,jl) 
     720                  END DO 
     721               END DO 
     722    
     723   !+++++++++++ END CHECK +++++++++++++++++ 
     724    
     725      END SUBROUTINE lim_rst_read 
     726    
     727    
    641728#else 
    642729   !!---------------------------------------------------------------------- 
Note: See TracChangeset for help on using the changeset viewer.