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

source: trunk/NEMOGCM/NEMO/LIM_SRC_3/limrst.F90 @ 7795

Last change on this file since 7795 was 7753, checked in by mocavero, 7 years ago

Reverting trunk to remove OpenMP

  • Property svn:keywords set to Id
File size: 24.6 KB
RevLine 
[825]1MODULE limrst
[835]2   !!======================================================================
3   !!                     ***  MODULE  limrst  ***
4   !! Ice restart :  write the ice restart file
5   !!======================================================================
[2528]6   !! History:   -   ! 2005-04 (M. Vancoppenolle) Original code
7   !!           3.0  ! 2008-03 (C. Ethe) restart files in using IOM interface
[2715]8   !!           4.0  ! 2011-02 (G. Madec) dynamical allocation
[2528]9   !!----------------------------------------------------------------------
[825]10#if defined key_lim3
[835]11   !!----------------------------------------------------------------------
12   !!   'key_lim3' :                                   LIM sea-ice model
13   !!----------------------------------------------------------------------
[3625]14   !!   lim_rst_opn   : open ice restart file
15   !!   lim_rst_write : write of the restart file
16   !!   lim_rst_read  : read  the restart file
[835]17   !!----------------------------------------------------------------------
[3625]18   USE ice            ! sea-ice variables
[4205]19   USE oce     , ONLY :  snwice_mass, snwice_mass_b
[3625]20   USE dom_oce        ! ocean domain
21   USE sbc_oce        ! Surface boundary condition: ocean fields
22   USE sbc_ice        ! Surface boundary condition: ice fields
23   USE in_out_manager ! I/O manager
24   USE iom            ! I/O library
25   USE lib_mpp        ! MPP library
26   USE wrk_nemo       ! work arrays
27   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
[5123]28   USE limctl
[921]29
[835]30   IMPLICIT NONE
31   PRIVATE
[921]32
[2528]33   PUBLIC   lim_rst_opn    ! routine called by icestep.F90
34   PUBLIC   lim_rst_write  ! routine called by icestep.F90
[5123]35   PUBLIC   lim_rst_read   ! routine called by sbc_lim_init
[825]36
[835]37   LOGICAL, PUBLIC ::   lrst_ice         !: logical to control the ice restart write
38   INTEGER, PUBLIC ::   numrir, numriw   !: logical unit for ice restart (read and write)
[825]39
[835]40   !!----------------------------------------------------------------------
[4161]41   !! NEMO/LIM3 4.0 , UCL - NEMO Consortium (2011)
[1156]42   !! $Id$
[2528]43   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
[835]44   !!----------------------------------------------------------------------
45CONTAINS
[825]46
[835]47   SUBROUTINE lim_rst_opn( kt )
48      !!----------------------------------------------------------------------
49      !!                    ***  lim_rst_opn  ***
50      !!
51      !! ** purpose  :   output of sea-ice variable in a netcdf file
52      !!----------------------------------------------------------------------
53      INTEGER, INTENT(in) ::   kt       ! number of iteration
54      !
[7646]55      CHARACTER(len=20)   ::   clkt     ! ocean time-step define as a character
56      CHARACTER(len=50)   ::   clname   ! ice output restart file name
[5341]57      CHARACTER(len=256)  ::   clpath   ! full path to ice output restart file
[835]58      !!----------------------------------------------------------------------
59      !
60      IF( kt == nit000 )   lrst_ice = .FALSE.   ! default definition
[921]61
[2528]62      ! in order to get better performances with NetCDF format, we open and define the ice restart file
63      ! one ice time step before writing the data (-> at nitrst - 2*nn_fsbc + 1), except if we write ice
64      ! restart files every ice time step or if an ice restart file was writen at nitend - 2*nn_fsbc + 1
65      IF( kt == nitrst - 2*nn_fsbc + 1 .OR. nstock == nn_fsbc    &
66         &                             .OR. ( kt == nitend - nn_fsbc + 1 .AND. .NOT. lrst_ice ) ) THEN
[5341]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
[835]71            ENDIF
[5341]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.
[835]90         ENDIF
91      ENDIF
92      !
[7646]93      IF( ln_limctl )   CALL lim_prt( kt, iiceprt, jiceprt, 1, ' - Beginning the time step - ' )   ! control print
[835]94   END SUBROUTINE lim_rst_opn
[825]95
[2528]96
[835]97   SUBROUTINE lim_rst_write( kt )
98      !!----------------------------------------------------------------------
99      !!                    ***  lim_rst_write  ***
100      !!
101      !! ** purpose  :   output of sea-ice variable in a netcdf file
102      !!----------------------------------------------------------------------
103      INTEGER, INTENT(in) ::   kt     ! number of iteration
[2528]104      !!
105      INTEGER ::   ji, jj, jk ,jl   ! dummy loop indices
106      INTEGER ::   iter
[7646]107      CHARACTER(len=25) ::   znam
108      CHARACTER(len=2)  ::   zchar, zchar1
[3294]109      REAL(wp), POINTER, DIMENSION(:,:) :: z2d
[835]110      !!----------------------------------------------------------------------
[921]111
[3294]112      CALL wrk_alloc( jpi, jpj, z2d )
[2715]113
[888]114      iter = kt + nn_fsbc - 1   ! ice restarts are written at kt == nitrst - nn_fsbc + 1
[825]115
[835]116      IF( iter == nitrst ) THEN
117         IF(lwp) WRITE(numout,*)
118         IF(lwp) WRITE(numout,*) 'lim_rst_write : write ice restart file  kt =', kt
119         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~'         
120      ENDIF
[825]121
[835]122      ! Write in numriw (if iter == nitrst)
123      ! ------------------
124      !                                                                        ! calendar control
[2528]125      CALL iom_rstput( iter, nitrst, numriw, 'nn_fsbc', REAL( nn_fsbc, wp ) )      ! time-step
126      CALL iom_rstput( iter, nitrst, numriw, 'kt_ice' , REAL( iter   , wp ) )      ! date
[825]127
[835]128      ! Prognostic variables
129      DO jl = 1, jpl 
[7646]130         WRITE(zchar,'(I2.2)') jl
[835]131         znam = 'v_i'//'_htc'//zchar
[7753]132         z2d(:,:) = v_i(:,:,jl)
[835]133         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
134         znam = 'v_s'//'_htc'//zchar
[7753]135         z2d(:,:) = v_s(:,:,jl)
[835]136         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
137         znam = 'smv_i'//'_htc'//zchar
[7753]138         z2d(:,:) = smv_i(:,:,jl)
[835]139         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
140         znam = 'oa_i'//'_htc'//zchar
[7753]141         z2d(:,:) = oa_i(:,:,jl)
[835]142         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
143         znam = 'a_i'//'_htc'//zchar
[7753]144         z2d(:,:) = a_i(:,:,jl)
[835]145         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
146         znam = 't_su'//'_htc'//zchar
[7753]147         z2d(:,:) = t_su(:,:,jl)
[835]148         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
149      END DO
[5341]150
[835]151      DO jl = 1, jpl 
[7646]152         WRITE(zchar,'(I2.2)') jl
[835]153         znam = 'tempt_sl1'//'_htc'//zchar
[7753]154         z2d(:,:) = e_s(:,:,1,jl)
[835]155         CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
156      END DO
[825]157
[835]158      DO jl = 1, jpl 
[7646]159         WRITE(zchar,'(I2.2)') jl
[835]160         DO jk = 1, nlay_i 
[7646]161            WRITE(zchar1,'(I2.2)') jk
[835]162            znam = 'tempt'//'_il'//zchar1//'_htc'//zchar
[7753]163            z2d(:,:) = e_i(:,:,jk,jl)
[835]164            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
165         END DO
[825]166      END DO
167
[4205]168      CALL iom_rstput( iter, nitrst, numriw, 'u_ice'        , u_ice      )
169      CALL iom_rstput( iter, nitrst, numriw, 'v_ice'        , v_ice      )
170      CALL iom_rstput( iter, nitrst, numriw, 'stress1_i'    , stress1_i  )
171      CALL iom_rstput( iter, nitrst, numriw, 'stress2_i'    , stress2_i  )
172      CALL iom_rstput( iter, nitrst, numriw, 'stress12_i'   , stress12_i )
[5123]173      CALL iom_rstput( iter, nitrst, numriw, 'snwice_mass'  , snwice_mass )
174      CALL iom_rstput( iter, nitrst, numriw, 'snwice_mass_b', snwice_mass_b )
[825]175
[7646]176      ! In case Prather scheme is used for advection, write second order moments
177      ! ------------------------------------------------------------------------
178      IF( nn_limadv == -1 ) THEN
179         
180         DO jl = 1, jpl 
181            WRITE(zchar,'(I2.2)') jl
182            znam = 'sxice'//'_htc'//zchar
[7753]183            z2d(:,:) = sxice(:,:,jl)
[835]184            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
[7646]185            znam = 'syice'//'_htc'//zchar
[7753]186            z2d(:,:) = syice(:,:,jl)
[838]187            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
[7646]188            znam = 'sxxice'//'_htc'//zchar
[7753]189            z2d(:,:) = sxxice(:,:,jl)
[835]190            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
[7646]191            znam = 'syyice'//'_htc'//zchar
[7753]192            z2d(:,:) = syyice(:,:,jl)
[835]193            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
[7646]194            znam = 'sxyice'//'_htc'//zchar
[7753]195            z2d(:,:) = sxyice(:,:,jl)
[835]196            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
[7646]197            znam = 'sxsn'//'_htc'//zchar
[7753]198            z2d(:,:) = sxsn(:,:,jl)
[7646]199            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
200            znam = 'sysn'//'_htc'//zchar
[7753]201            z2d(:,:) = sysn(:,:,jl)
[7646]202            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
203            znam = 'sxxsn'//'_htc'//zchar
[7753]204            z2d(:,:) = sxxsn(:,:,jl)
[7646]205            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
206            znam = 'syysn'//'_htc'//zchar
[7753]207            z2d(:,:) = syysn(:,:,jl)
[7646]208            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
209            znam = 'sxysn'//'_htc'//zchar
[7753]210            z2d(:,:) = sxysn(:,:,jl)
[7646]211            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
212            znam = 'sxa'//'_htc'//zchar
[7753]213            z2d(:,:) = sxa(:,:,jl)
[7646]214            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
215            znam = 'sya'//'_htc'//zchar
[7753]216            z2d(:,:) = sya(:,:,jl)
[7646]217            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
218            znam = 'sxxa'//'_htc'//zchar
[7753]219            z2d(:,:) = sxxa(:,:,jl)
[7646]220            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
221            znam = 'syya'//'_htc'//zchar
[7753]222            z2d(:,:) = syya(:,:,jl)
[7646]223            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
224            znam = 'sxya'//'_htc'//zchar
[7753]225            z2d(:,:) = sxya(:,:,jl)
[7646]226            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
227            znam = 'sxc0'//'_htc'//zchar
[7753]228            z2d(:,:) = sxc0(:,:,jl)
[7646]229            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
230            znam = 'syc0'//'_htc'//zchar
[7753]231            z2d(:,:) = syc0(:,:,jl)
[7646]232            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
233            znam = 'sxxc0'//'_htc'//zchar
[7753]234            z2d(:,:) = sxxc0(:,:,jl)
[7646]235            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
236            znam = 'syyc0'//'_htc'//zchar
[7753]237            z2d(:,:) = syyc0(:,:,jl)
[7646]238            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
239            znam = 'sxyc0'//'_htc'//zchar
[7753]240            z2d(:,:) = sxyc0(:,:,jl)
[7646]241            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
242            znam = 'sxsal'//'_htc'//zchar
[7753]243            z2d(:,:) = sxsal(:,:,jl)
[7646]244            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
245            znam = 'sysal'//'_htc'//zchar
[7753]246            z2d(:,:) = sysal(:,:,jl)
[7646]247            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
248            znam = 'sxxsal'//'_htc'//zchar
[7753]249            z2d(:,:) = sxxsal(:,:,jl)
[7646]250            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
251            znam = 'syysal'//'_htc'//zchar
[7753]252            z2d(:,:) = syysal(:,:,jl)
[7646]253            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
254            znam = 'sxysal'//'_htc'//zchar
[7753]255            z2d(:,:) = sxysal(:,:,jl)
[7646]256            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
257            znam = 'sxage'//'_htc'//zchar
[7753]258            z2d(:,:) = sxage(:,:,jl)
[7646]259            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
260            znam = 'syage'//'_htc'//zchar
[7753]261            z2d(:,:) = syage(:,:,jl)
[7646]262            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
263            znam = 'sxxage'//'_htc'//zchar
[7753]264            z2d(:,:) = sxxage(:,:,jl)
[7646]265            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
266            znam = 'syyage'//'_htc'//zchar
[7753]267            z2d(:,:) = syyage(:,:,jl)
[7646]268            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
269            znam = 'sxyage'//'_htc'//zchar
[7753]270            z2d(:,:) = sxyage(:,:,jl)
[7646]271            CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
[835]272         END DO
[825]273
[7646]274         CALL iom_rstput( iter, nitrst, numriw, 'sxopw ' ,  sxopw  )
275         CALL iom_rstput( iter, nitrst, numriw, 'syopw ' ,  syopw  )
276         CALL iom_rstput( iter, nitrst, numriw, 'sxxopw' ,  sxxopw )
277         CALL iom_rstput( iter, nitrst, numriw, 'syyopw' ,  syyopw )
278         CALL iom_rstput( iter, nitrst, numriw, 'sxyopw' ,  sxyopw )
279         
280         DO jl = 1, jpl 
281            WRITE(zchar,'(I2.2)') jl
282            DO jk = 1, nlay_i 
283               WRITE(zchar1,'(I2.2)') jk
284               znam = 'sxe'//'_il'//zchar1//'_htc'//zchar
[7753]285               z2d(:,:) = sxe(:,:,jk,jl)
[7646]286               CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
287               znam = 'sye'//'_il'//zchar1//'_htc'//zchar
[7753]288               z2d(:,:) = sye(:,:,jk,jl)
[7646]289               CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
290               znam = 'sxxe'//'_il'//zchar1//'_htc'//zchar
[7753]291               z2d(:,:) = sxxe(:,:,jk,jl)
[7646]292               CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
293               znam = 'syye'//'_il'//zchar1//'_htc'//zchar
[7753]294               z2d(:,:) = syye(:,:,jk,jl)
[7646]295               CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
296               znam = 'sxye'//'_il'//zchar1//'_htc'//zchar
[7753]297               z2d(:,:) = sxye(:,:,jk,jl)
[7646]298               CALL iom_rstput( iter, nitrst, numriw, znam , z2d )
299            END DO
300         END DO
301
302      ENDIF
303     
304      ! close restart file
305      ! ------------------
[835]306      IF( iter == nitrst ) THEN
[7646]307         CALL iom_close( numriw )
[835]308         lrst_ice = .FALSE.
309      ENDIF
310      !
[3294]311      CALL wrk_dealloc( jpi, jpj, z2d )
[2715]312      !
[921]313   END SUBROUTINE lim_rst_write
314
[2528]315
[835]316   SUBROUTINE lim_rst_read
317      !!----------------------------------------------------------------------
318      !!                    ***  lim_rst_read  ***
319      !!
320      !! ** purpose  :   read of sea-ice variable restart in a netcdf file
321      !!----------------------------------------------------------------------
[5128]322      INTEGER :: ji, jj, jk, jl
[835]323      REAL(wp) ::   zfice, ziter
[3294]324      REAL(wp), POINTER, DIMENSION(:,:) ::   z2d
[7646]325      CHARACTER(len=25) ::   znam
326      CHARACTER(len=2)  ::   zchar, zchar1
[2528]327      INTEGER           ::   jlibalt = jprstlib
328      LOGICAL           ::   llok
[835]329      !!----------------------------------------------------------------------
[921]330
[3294]331      CALL wrk_alloc( jpi, jpj, z2d )
[2715]332
[825]333      IF(lwp) THEN
334         WRITE(numout,*)
[835]335         WRITE(numout,*) 'lim_rst_read : read ice NetCDF restart file'
[2715]336         WRITE(numout,*) '~~~~~~~~~~~~~'
[825]337      ENDIF
338
[5341]339      CALL iom_open ( TRIM(cn_icerst_indir)//'/'//cn_icerst_in, numrir, kiolib = jprstlib )
[835]340
[888]341      CALL iom_get( numrir, 'nn_fsbc', zfice )
342      CALL iom_get( numrir, 'kt_ice' , ziter )   
[835]343      IF(lwp) WRITE(numout,*) '   read ice restart file at time step    : ', ziter
344      IF(lwp) WRITE(numout,*) '   in any case we force it to nit000 - 1 : ', nit000 - 1
345
[825]346      !Control of date
[921]347
[4161]348      IF( ( nit000 - NINT(ziter) ) /= 1 .AND. ABS( nrstdt ) == 1 )   &
[835]349         &     CALL ctl_stop( 'lim_rst_read ===>>>> : problem with nit000 in ice restart',  &
350         &                   '   verify the file or rerun with the value 0 for the',        &
351         &                   '   control of time parameter  nrstdt' )
[4161]352      IF( NINT(zfice) /= nn_fsbc          .AND. ABS( nrstdt ) == 1 )   &
[888]353         &     CALL ctl_stop( 'lim_rst_read ===>>>> : problem with nn_fsbc in ice restart',  &
354         &                   '   verify the file or rerun with the value 0 for the',         &
[835]355         &                   '   control of time parameter  nrstdt' )
[825]356
[7646]357      ! Prognostic variables
[835]358      DO jl = 1, jpl 
[7646]359         WRITE(zchar,'(I2.2)') jl
[835]360         znam = 'v_i'//'_htc'//zchar
361         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
362         v_i(:,:,jl) = z2d(:,:)
363         znam = 'v_s'//'_htc'//zchar
364         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
365         v_s(:,:,jl) = z2d(:,:) 
366         znam = 'smv_i'//'_htc'//zchar
367         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
368         smv_i(:,:,jl) = z2d(:,:)
369         znam = 'oa_i'//'_htc'//zchar
370         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
371         oa_i(:,:,jl) = z2d(:,:)
372         znam = 'a_i'//'_htc'//zchar
373         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
374         a_i(:,:,jl) = z2d(:,:)
375         znam = 't_su'//'_htc'//zchar
376         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
377         t_su(:,:,jl) = z2d(:,:)
378      END DO
[825]379
[919]380      DO jl = 1, jpl 
[7646]381         WRITE(zchar,'(I2.2)') jl
[835]382         znam = 'tempt_sl1'//'_htc'//zchar
383         CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
384         e_s(:,:,1,jl) = z2d(:,:)
[825]385      END DO
[921]386
[835]387      DO jl = 1, jpl 
[7646]388         WRITE(zchar,'(I2.2)') jl
[835]389         DO jk = 1, nlay_i 
[7646]390            WRITE(zchar1,'(I2.2)') jk
[835]391            znam = 'tempt'//'_il'//zchar1//'_htc'//zchar
392            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
393            e_i(:,:,jk,jl) = z2d(:,:)
394         END DO
395      END DO
[825]396
[835]397      CALL iom_get( numrir, jpdom_autoglo, 'u_ice'     , u_ice      )
398      CALL iom_get( numrir, jpdom_autoglo, 'v_ice'     , v_ice      )
399      CALL iom_get( numrir, jpdom_autoglo, 'stress1_i' , stress1_i  )
400      CALL iom_get( numrir, jpdom_autoglo, 'stress2_i' , stress2_i  )
401      CALL iom_get( numrir, jpdom_autoglo, 'stress12_i', stress12_i )
[5123]402      CALL iom_get( numrir, jpdom_autoglo, 'snwice_mass'  , snwice_mass )
403      CALL iom_get( numrir, jpdom_autoglo, 'snwice_mass_b', snwice_mass_b )
[825]404
[7646]405      ! In case Prather scheme is used for advection, read second order moments
406      ! ------------------------------------------------------------------------
407      IF( nn_limadv == -1 ) THEN
[825]408
[7646]409         DO jl = 1, jpl 
410            WRITE(zchar,'(I2.2)') jl
411            znam = 'sxice'//'_htc'//zchar
[835]412            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
[7646]413            sxice(:,:,jl) = z2d(:,:)
414            znam = 'syice'//'_htc'//zchar
[838]415            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
[7646]416            syice(:,:,jl) = z2d(:,:)
417            znam = 'sxxice'//'_htc'//zchar
[835]418            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
[7646]419            sxxice(:,:,jl) = z2d(:,:)
420            znam = 'syyice'//'_htc'//zchar
[835]421            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
[7646]422            syyice(:,:,jl) = z2d(:,:)
423            znam = 'sxyice'//'_htc'//zchar
[835]424            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
[7646]425            sxyice(:,:,jl) = z2d(:,:)
426            znam = 'sxsn'//'_htc'//zchar
427            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
428            sxsn(:,:,jl) = z2d(:,:)
429            znam = 'sysn'//'_htc'//zchar
430            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
431            sysn(:,:,jl) = z2d(:,:)
432            znam = 'sxxsn'//'_htc'//zchar
433            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
434            sxxsn(:,:,jl) = z2d(:,:)
435            znam = 'syysn'//'_htc'//zchar
436            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
437            syysn(:,:,jl) = z2d(:,:)
438            znam = 'sxysn'//'_htc'//zchar
439            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
440            sxysn(:,:,jl) = z2d(:,:)
441            znam = 'sxa'//'_htc'//zchar
442            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
443            sxa(:,:,jl) = z2d(:,:)
444            znam = 'sya'//'_htc'//zchar
445            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
446            sya(:,:,jl) = z2d(:,:)
447            znam = 'sxxa'//'_htc'//zchar
448            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
449            sxxa(:,:,jl) = z2d(:,:)
450            znam = 'syya'//'_htc'//zchar
451            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
452            syya(:,:,jl) = z2d(:,:)
453            znam = 'sxya'//'_htc'//zchar
454            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
455            sxya(:,:,jl) = z2d(:,:)
456            znam = 'sxc0'//'_htc'//zchar
457            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
458            sxc0(:,:,jl) = z2d(:,:)
459            znam = 'syc0'//'_htc'//zchar
460            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
461            syc0(:,:,jl) = z2d(:,:)
462            znam = 'sxxc0'//'_htc'//zchar
463            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
464            sxxc0(:,:,jl) = z2d(:,:)
465            znam = 'syyc0'//'_htc'//zchar
466            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
467            syyc0(:,:,jl) = z2d(:,:)
468            znam = 'sxyc0'//'_htc'//zchar
469            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
470            sxyc0(:,:,jl) = z2d(:,:)
471            znam = 'sxsal'//'_htc'//zchar
472            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
473            sxsal(:,:,jl) = z2d(:,:)
474            znam = 'sysal'//'_htc'//zchar
475            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
476            sysal(:,:,jl) = z2d(:,:)
477            znam = 'sxxsal'//'_htc'//zchar
478            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
479            sxxsal(:,:,jl) = z2d(:,:)
480            znam = 'syysal'//'_htc'//zchar
481            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
482            syysal(:,:,jl) = z2d(:,:)
483            znam = 'sxysal'//'_htc'//zchar
484            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
485            sxysal(:,:,jl) = z2d(:,:)
486            znam = 'sxage'//'_htc'//zchar
487            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
488            sxage(:,:,jl) = z2d(:,:)
489            znam = 'syage'//'_htc'//zchar
490            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
491            syage(:,:,jl) = z2d(:,:)
492            znam = 'sxxage'//'_htc'//zchar
493            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
494            sxxage(:,:,jl) = z2d(:,:)
495            znam = 'syyage'//'_htc'//zchar
496            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
497            syyage(:,:,jl) = z2d(:,:)
498            znam = 'sxyage'//'_htc'//zchar
499            CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
500            sxyage(:,:,jl)= z2d(:,:)
[835]501         END DO
[7646]502
503         CALL iom_get( numrir, jpdom_autoglo, 'sxopw ' ,  sxopw  )
504         CALL iom_get( numrir, jpdom_autoglo, 'syopw ' ,  syopw  )
505         CALL iom_get( numrir, jpdom_autoglo, 'sxxopw' ,  sxxopw )
506         CALL iom_get( numrir, jpdom_autoglo, 'syyopw' ,  syyopw )
507         CALL iom_get( numrir, jpdom_autoglo, 'sxyopw' ,  sxyopw )
508
509         DO jl = 1, jpl 
510            WRITE(zchar,'(I2.2)') jl
511            DO jk = 1, nlay_i 
512               WRITE(zchar1,'(I2.2)') jk
513               znam = 'sxe'//'_il'//zchar1//'_htc'//zchar
514               CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
515               sxe(:,:,jk,jl) = z2d(:,:)
516               znam = 'sye'//'_il'//zchar1//'_htc'//zchar
517               CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
518               sye(:,:,jk,jl) = z2d(:,:)
519               znam = 'sxxe'//'_il'//zchar1//'_htc'//zchar
520               CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
521               sxxe(:,:,jk,jl) = z2d(:,:)
522               znam = 'syye'//'_il'//zchar1//'_htc'//zchar
523               CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
524               syye(:,:,jk,jl) = z2d(:,:)
525               znam = 'sxye'//'_il'//zchar1//'_htc'//zchar
526               CALL iom_get( numrir, jpdom_autoglo, znam , z2d )
527               sxye(:,:,jk,jl) = z2d(:,:)
528            END DO
529         END DO
530         !
531      END IF
532     
[4688]533      ! clem: I do not understand why the following IF is needed
[5123]534      !       I suspect something inconsistent in the main code with option nn_icesal=1
535      IF( nn_icesal == 1 ) THEN
[4688]536         DO jl = 1, jpl 
[5123]537            sm_i(:,:,jl) = rn_icesal
[4688]538            DO jk = 1, nlay_i 
[5123]539               s_i(:,:,jk,jl) = rn_icesal
[4688]540            END DO
541         END DO
542      ENDIF
543      !
[4205]544      !CALL iom_close( numrir ) !clem: closed in sbcice_lim.F90
[2528]545      !
[3294]546      CALL wrk_dealloc( jpi, jpj, z2d )
[2715]547      !
[921]548   END SUBROUTINE lim_rst_read
549
[825]550#else
551   !!----------------------------------------------------------------------
552   !!   Default option :       Empty module            NO LIM sea-ice model
553   !!----------------------------------------------------------------------
554CONTAINS
555   SUBROUTINE lim_rst_read             ! Empty routine
556   END SUBROUTINE lim_rst_read
557   SUBROUTINE lim_rst_write            ! Empty routine
558   END SUBROUTINE lim_rst_write
559#endif
560
561   !!======================================================================
562END MODULE limrst
Note: See TracBrowser for help on using the repository browser.