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 tags/nemo_v1_13_dev4/NEMO/LIM_SRC – NEMO

source: tags/nemo_v1_13_dev4/NEMO/LIM_SRC/limrst.F90 @ 5712

Last change on this file since 5712 was 473, checked in by opalod, 18 years ago

nemo_v1_update_060: SM: IOM + 301 levels + CORE + begining of ctl_stop

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 10.1 KB
Line 
1MODULE limrst
2   !!======================================================================
3   !!                     ***  MODULE  limrst  ***
4   !! Ice restart :  write the ice restart file
5   !!======================================================================
6#if defined key_ice_lim
7   !!----------------------------------------------------------------------
8   !!   'key_ice_lim' :                                   LIM 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 in_out_manager
15   USE ice
16   USE ioipsl
17   USE dom_oce
18   USE ice_oce         ! ice variables
19   USE daymod
20
21   IMPLICIT NONE
22   PRIVATE
23
24   !! * Accessibility
25   PUBLIC lim_rst_write  ! routine called by lim_step.F90
26   PUBLIC lim_rst_read   ! routine called by lim_init.F90
27
28   !!----------------------------------------------------------------------
29   !!   LIM 2.0,  UCL-LOCEAN-IPSL (2005)
30   !! $Header$
31   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
32   !!----------------------------------------------------------------------
33
34CONTAINS
35
36# if ( defined key_mpp_mpi || defined key_mpp_shmem ) && defined key_dimgout
37   !!----------------------------------------------------------------------
38   !!   'key_mpp_mpi'     OR
39   !!   'key_mpp_shmem'
40   !!   'key_dimgout' :                           clipper type restart file
41   !!                 :                     can be used in mpp
42   !!----------------------------------------------------------------------
43#  include "limrst_dimg.h90"
44
45# else
46   !!----------------------------------------------------------------------
47   !!   Default option                                          NetCDF file
48   !!----------------------------------------------------------------------
49
50   SUBROUTINE lim_rst_write( niter )
51      !!----------------------------------------------------------------------
52      !!                    ***  lim_rst_write  ***
53      !!
54      !! ** purpose  :   output of sea-ice variable in a netcdf file
55      !!
56      !!----------------------------------------------------------------------
57      ! Arguments
58      INTEGER  ::    niter        ! number of iteration
59
60      !- dummy variables :
61      LOGICAL :: &
62         llbon
63      INTEGER :: &
64         ji, jj
65      INTEGER :: &
66         inumwrs, it0, itime
67      REAL(wp), DIMENSION(1) :: &
68         zdept
69      REAL(wp), DIMENSION(2) :: &
70         zinfo
71      REAL(wp),DIMENSION(jpi,jpj,35) :: &
72         zmoment
73      REAL(wp) :: &
74         zsec, zdate0, zdt
75
76      CHARACTER(len=45)  ::  ccfile
77
78      ccfile = 'restart_ice_out.nc'
79
80#if defined key_agrif
81      if ( .NOT. Agrif_Root() ) then
82         ccfile= TRIM(Agrif_CFixed())//'_'//TRIM(ccfile)
83      endif
84#endif
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
94      it0      = niter
95      zinfo(1) = FLOAT( nfice  )  ! coupling frequency OPA ICELLN  nfice
96      zinfo(2) = FLOAT( it0   )   ! iteration number
97
98      zsec     = 0.e0
99      itime    = 0
100      zdept(1) = 0.e0
101      zdt      = rdt_ice * nstock
102
103      ! Write in inumwrs
104
105      DO jj = 1, jpj              ! 3D array: 10 time faster than 35 restput
106         DO ji = 1, jpi
107            zmoment(ji,jj,1)  = sxice(ji,jj)
108            zmoment(ji,jj,2)  = syice(ji,jj)
109            zmoment(ji,jj,3)  = sxxice(ji,jj)
110            zmoment(ji,jj,4)  = syyice(ji,jj)
111            zmoment(ji,jj,5)  = sxyice(ji,jj)
112            zmoment(ji,jj,6)  = sxsn(ji,jj)
113            zmoment(ji,jj,7)  = sysn(ji,jj)
114            zmoment(ji,jj,8)  = sxxsn(ji,jj)
115            zmoment(ji,jj,9)  = syysn(ji,jj)
116            zmoment(ji,jj,10) = sxysn(ji,jj)
117            zmoment(ji,jj,11) = sxa(ji,jj)
118            zmoment(ji,jj,12) = sya(ji,jj)
119            zmoment(ji,jj,13) = sxxa(ji,jj)
120            zmoment(ji,jj,14) = syya(ji,jj)
121            zmoment(ji,jj,15) = sxya(ji,jj)
122            zmoment(ji,jj,16) = sxc0(ji,jj)
123            zmoment(ji,jj,17) = syc0(ji,jj)
124            zmoment(ji,jj,18) = sxxc0(ji,jj)
125            zmoment(ji,jj,19) = syyc0(ji,jj)
126            zmoment(ji,jj,20) = sxyc0(ji,jj)
127            zmoment(ji,jj,21) = sxc1(ji,jj)
128            zmoment(ji,jj,22) = syc1(ji,jj)
129            zmoment(ji,jj,23) = sxxc1(ji,jj)
130            zmoment(ji,jj,24) = syyc1(ji,jj)
131            zmoment(ji,jj,25) = sxyc1(ji,jj)
132            zmoment(ji,jj,26) = sxc2(ji,jj)
133            zmoment(ji,jj,27) = syc2(ji,jj)
134            zmoment(ji,jj,28) = sxxc2(ji,jj)
135            zmoment(ji,jj,29) = syyc2(ji,jj)
136            zmoment(ji,jj,30) = sxyc2(ji,jj)
137            zmoment(ji,jj,31) = sxst(ji,jj)
138            zmoment(ji,jj,32) = syst(ji,jj)
139            zmoment(ji,jj,33) = sxxst(ji,jj)
140            zmoment(ji,jj,34) = syyst(ji,jj)
141            zmoment(ji,jj,35) = sxyst(ji,jj)
142         END DO
143      END DO
144
145      CALL ymds2ju( nyear, nmonth, nday, zsec, zdate0 )
146      CALL restini( 'NONE', jpi, jpj, glamt, gphit, 1 , zdept, ccfile, itime, zdate0, zdt, &
147         &         inumwrs, domain_id=nidom )
148     
149      CALL restput( inumwrs, 'info'   ,   1,   1, 2 , 0, zinfo   )  ! restart informations
150       
151      CALL restput( inumwrs, 'hicif'  , jpi, jpj, 1 , 0, hicif   )  ! prognostic variables
152      CALL restput( inumwrs, 'hsnif'  , jpi, jpj, 1 , 0, hsnif   )
153      CALL restput( inumwrs, 'frld'   , jpi, jpj, 1 , 0, frld    )
154      CALL restput( inumwrs, 'sist'   , jpi, jpj, 1 , 0, sist    )
155# if defined key_coupled
156      CALL restput( inumwrs, 'albege' , jpi, jpj, 1 , 0, albege  )
157# endif
158      CALL restput( inumwrs, 'tbif'   , jpi, jpj, 3 , 0, tbif    )
159      CALL restput( inumwrs, 'u_ice'  , jpi, jpj, 1 , 0, u_ice   )
160      CALL restput( inumwrs, 'v_ice'  , jpi, jpj, 1 , 0, v_ice   )
161      CALL restput( inumwrs, 'gtaux'  , jpi, jpj, 1 , 0, gtaux  )
162      CALL restput( inumwrs, 'gtauy'  , jpi, jpj, 1 , 0, gtauy  )
163      CALL restput( inumwrs, 'qstoif' , jpi, jpj, 1 , 0, qstoif  )
164      CALL restput( inumwrs, 'fsbbq'  , jpi, jpj, 1 , 0, fsbbq   )
165      CALL restput( inumwrs, 'moment' , jpi, jpj, 35, 0, zmoment )
166
167     
168      CALL restclo( inumwrs )
169
170   END SUBROUTINE lim_rst_write
171
172
173   SUBROUTINE lim_rst_read( niter )
174      !-----------------------------------------------------------------------
175      !  restart from a state defined in a binary file
176      !-----------------------------------------------------------------------
177      !! * Modules used
178      USE iom
179      ! Arguments
180      INTEGER  ::   niter        ! number of iteration
181
182      !- dummy variables :
183      INTEGER :: &
184         inum, it1, ifice
185      REAL(wp),DIMENSION(jpi,jpj,35) :: &
186         zmoment
187      REAL(wp),DIMENSION(1, 1, 2) :: &
188         zinfo
189
190      CALL iom_open ( 'restart_ice_in', inum )
191
192      CALL iom_get (inum, jpdom_unknown, 'info', zinfo)
193      ifice   = INT( zinfo(1, 1, 1) ) ! not used ...
194      it1     = INT( zinfo(1, 1, 2) )
195
196      IF(lwp) WRITE(numout,*) 'lim_rst_read : READ restart file at time step : ', it1
197
198      !Control of date
199     
200      IF( ( nit000 - it1 ) /= 1 .AND. ABS( nrstdt ) == 1 ) &
201           CALL ctl_stop( 'lim_rst_read ===>>>> : problem with nit000 for the restart',  &
202      &                   '   verify the file or rerun with the value 0 for the',        &
203      &                   '   control of time parameter  nrstdt' )
204
205      CALL iom_get( inum, jpdom_local, 'hicif' , hicif )   
206      CALL iom_get( inum, jpdom_local, 'hsnif' , hsnif )   
207      CALL iom_get( inum, jpdom_local, 'frld'  , frld )   
208      CALL iom_get( inum, jpdom_local, 'sist'  , sist )   
209# if defined key_coupled 
210      CALL iom_get( inum, jpdom_local, 'albege', albege )   
211# endif
212      CALL iom_get( inum, jpdom_unknown, 'tbif', tbif )   
213      CALL iom_get( inum, jpdom_local, 'u_ice' , u_ice )   
214      CALL iom_get( inum, jpdom_local, 'v_ice' , v_ice )   
215      CALL iom_get( inum, jpdom_local, 'gtaux' , gtaux )   
216      CALL iom_get( inum, jpdom_local, 'gtauy' , gtauy )   
217      CALL iom_get( inum, jpdom_local, 'qstoif', qstoif )   
218      CALL iom_get( inum, jpdom_local, 'fsbbq' , fsbbq )   
219      CALL iom_get( inum, jpdom_unknown, 'moment', zmoment )   
220      sxice(:,:)  = zmoment(:,:,1)
221      syice(:,:)  = zmoment(:,:,2)
222      sxxice(:,:) = zmoment(:,:,3)
223      syyice(:,:) = zmoment(:,:,4)
224      sxyice(:,:) = zmoment(:,:,5)
225      sxsn(:,:)   = zmoment(:,:,6)
226      sysn(:,:)   = zmoment(:,:,7)
227      sxxsn(:,:)  = zmoment(:,:,8)
228      syysn(:,:)  = zmoment(:,:,9)
229      sxysn(:,:)  = zmoment(:,:,10)
230      sxa(:,:)    = zmoment(:,:,11)
231      sya(:,:)    = zmoment(:,:,12)
232      sxxa(:,:)   = zmoment(:,:,13)
233      syya(:,:)   = zmoment(:,:,14)
234      sxya(:,:)   = zmoment(:,:,15)
235      sxc0(:,:)   = zmoment(:,:,16)
236      syc0(:,:)   = zmoment(:,:,17)
237      sxxc0(:,:)  = zmoment(:,:,18)
238      syyc0(:,:)  = zmoment(:,:,19)
239      sxyc0(:,:)  = zmoment(:,:,20)
240      sxc1(:,:)   = zmoment(:,:,21)
241      syc1(:,:)   = zmoment(:,:,22)
242      sxxc1(:,:)  = zmoment(:,:,23)
243      syyc1(:,:)  = zmoment(:,:,24)
244      sxyc1(:,:)  = zmoment(:,:,25)
245      sxc2(:,:)   = zmoment(:,:,26)
246      syc2(:,:)   = zmoment(:,:,27)
247      sxxc2(:,:)  = zmoment(:,:,28)
248      syyc2(:,:)  = zmoment(:,:,29)
249      sxyc2(:,:)  = zmoment(:,:,30)
250      sxst(:,:)   = zmoment(:,:,31)
251      syst(:,:)   = zmoment(:,:,32)
252      sxxst(:,:)  = zmoment(:,:,33)
253      syyst(:,:)  = zmoment(:,:,34)
254      sxyst(:,:)  = zmoment(:,:,35)
255     
256      CALL iom_close( inum )
257     
258      niter = it1
259
260   END SUBROUTINE lim_rst_read
261
262# endif
263
264#else
265   !!----------------------------------------------------------------------
266   !!   Default option :       Empty module            NO LIM sea-ice model
267   !!----------------------------------------------------------------------
268CONTAINS
269   SUBROUTINE lim_rst_read             ! Empty routine
270   END SUBROUTINE lim_rst_read
271   SUBROUTINE lim_rst_write            ! Empty routine
272   END SUBROUTINE lim_rst_write
273#endif
274
275   !!======================================================================
276END MODULE limrst
Note: See TracBrowser for help on using the repository browser.