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_dimg.h90 in trunk/NEMO/LIM_SRC – NEMO

source: trunk/NEMO/LIM_SRC/limrst_dimg.h90 @ 391

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

RB:nemo_v1_update_038: first integration of AGRIF :

add agrif to ice files

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 9.1 KB
Line 
1   !!----------------------------------------------------------------------
2   !!                     *** limrst_dimg.h90  ***
3   !!----------------------------------------------------------------------
4   !!   LIM 2.0,  UCL-LOCEAN-IPSL (2005)
5   !! $Header$
6   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
7   !!----------------------------------------------------------------------
8
9   SUBROUTINE lim_rst_write( kt )
10      !!-----------------------------------------------------------------------
11      !!                  ***  ROUTINE lim_rst_write  ***
12      !!
13      !! ** Purpose : Write restart fields for the LIM in mpp.
14      !!    one file per process, in the same manner as the ocean.
15      !! 
16      !! ** Methode : Each nstock time step, save  which are necessary
17      !!      for restart
18      !!      Record #1 hold general information on the state of the run
19      !!      Data fields (either 3D or 2D ) starts ar record #2
20      !!
21      !! History :
22      !!   9.0   : 04-05 (J.M. Molines ) from limrst_fdir.h90
23      !!-----------------------------------------------------------------------
24      !! * Arguments
25      USE par_ice
26      INTEGER, INTENT(in)  ::   kt        ! number of iteration
27
28      !- dummy variables :
29      INTEGER :: ji, jj, jf
30      INTEGER :: inum=61, it0, irecl8, irec
31
32      REAL(wp),DIMENSION(jpi,jpj,35) ::  zmoment
33      REAL(wp),DIMENSION(2)          :: zinfo
34
35      CHARACTER(len=45)  ::   ccfile = 'restart_ice_out', clres
36      !!-----------------------------------------------------------------------
37           
38      !! This routine is called from icestep if it is the right time to use it.
39      !! no additional check is necessary.
40
41       
42       ! 0. Initializations
43       ! ------------------
44
45       IF(lwp) THEN
46          WRITE(numout,*) ' '
47          WRITE(numout,*) ' lim_rst_write: output done in inum = ',   &
48               inum,' at it= ',kt,' date= ',ndastp
49          WRITE(numout,*) ' -------'
50       ENDIF
51
52       ! Open direct access file, with reclength for 2D wp fields
53       irecl8= jpi * jpj * wp
54       WRITE(clres,'(a,".",i3.3)') TRIM(ccfile),narea
55       CALL ctlopn(inum,clres,'UNKNOWN','UNFORMATTED','DIRECT',irecl8,numout,lwp,0)
56!!       OPEN(inum,FILE=clres,FORM='UNFORMATTED', ACCESS='DIRECT', RECL=irecl8 )
57
58
59      it0      = kt
60     
61      zinfo(1) = FLOAT( nfice )   ! iteration number
62      zinfo(2) = FLOAT( it0 )        ! time-step in second
63
64      ! Write in inum
65
66      zmoment(:,:,1)  = sxice (:,:)
67      zmoment(:,:,2)  = syice (:,:)
68      zmoment(:,:,3)  = sxxice(:,:)
69      zmoment(:,:,4)  = syyice(:,:)
70      zmoment(:,:,5)  = sxyice(:,:)
71      zmoment(:,:,6)  = sxsn  (:,:)
72      zmoment(:,:,7)  = sysn  (:,:)
73      zmoment(:,:,8)  = sxxsn (:,:)
74      zmoment(:,:,9)  = syysn (:,:)
75      zmoment(:,:,10) = sxysn (:,:)
76      zmoment(:,:,11) = sxa   (:,:)
77      zmoment(:,:,12) = sya   (:,:)
78      zmoment(:,:,13) = sxxa  (:,:)
79      zmoment(:,:,14) = syya  (:,:)
80      zmoment(:,:,15) = sxya  (:,:)
81      zmoment(:,:,16) = sxc0  (:,:)
82      zmoment(:,:,17) = syc0  (:,:)
83      zmoment(:,:,18) = sxxc0 (:,:)
84      zmoment(:,:,19) = syyc0 (:,:)
85      zmoment(:,:,20) = sxyc0 (:,:)
86      zmoment(:,:,21) = sxc1  (:,:)
87      zmoment(:,:,22) = syc1  (:,:)
88      zmoment(:,:,23) = sxxc1 (:,:)
89      zmoment(:,:,24) = syyc1 (:,:)
90      zmoment(:,:,25) = sxyc1 (:,:)
91      zmoment(:,:,26) = sxc2  (:,:)
92      zmoment(:,:,27) = syc2  (:,:)
93      zmoment(:,:,28) = sxxc2 (:,:)
94      zmoment(:,:,29) = syyc2 (:,:)
95      zmoment(:,:,30) = sxyc2 (:,:)
96      zmoment(:,:,31) = sxst  (:,:)
97      zmoment(:,:,32) = syst  (:,:)
98      zmoment(:,:,33) = sxxst (:,:)
99      zmoment(:,:,34) = syyst (:,:)
100      zmoment(:,:,35) = sxyst (:,:)
101
102      WRITE(inum,REC=1) irecl8, nfice, it0, &
103          &              ndastp, adatrj, jpi, jpj, jpk,  &
104          &              jpni, jpnj, jpnij, narea, jpiglo, jpjglo, &
105          &              nlcit, nlcjt, nldit, nldjt, nleit, nlejt, nimppt, njmppt
106
107      irec= 2
108      WRITE(inum,REC=irec)  hicif(:,:)          ! prognostic variables
109      irec = irec + 1
110      WRITE(inum,REC=irec)  hsnif(:,:)
111      irec = irec + 1
112      WRITE(inum,REC=irec)  frld(:,:)
113      irec = irec + 1
114      WRITE(inum,REC=irec)  sist(:,:)
115      irec = irec + 1
116# if defined key_coupled
117      WRITE(inum,REC=irec)  albege(:,:)
118      irec = irec + 1
119# endif
120      DO jf=1, jplayersp1
121      WRITE(inum,REC=irec)  tbif(:,:,jf)
122      irec = irec + 1
123      END DO
124      WRITE(inum,REC=irec)  u_ice(:,:)
125      irec = irec + 1
126      WRITE(inum,REC=irec)  v_ice(:,:)
127      irec = irec + 1
128      WRITE(inum,REC=irec)  gtaux(:,:)
129      irec = irec + 1
130      WRITE(inum,REC=irec)  gtauy(:,:)
131      irec = irec + 1
132      WRITE(inum,REC=irec)  qstoif(:,:)
133      irec = irec + 1
134      WRITE(inum,REC=irec)  fsbbq(:,:)
135      irec = irec + 1
136      DO jf=1,35
137      WRITE(inum,REC=irec)  zmoment(:,:,jf)
138      irec = irec + 1
139      END DO
140 
141      CLOSE(inum)
142     
143   END SUBROUTINE lim_rst_write
144
145
146   SUBROUTINE lim_rst_read(kt )
147      !!-----------------------------------------------------------------------
148      !!  restart from a state defined in a binary file
149      !!-----------------------------------------------------------------------
150      !! * Arguments
151      USE par_ice
152      INTEGER ,INTENT(out)  ::   kt        ! number of iteration
153
154      !- dummy variables :
155
156      INTEGER :: ji, jj, jf
157      INTEGER :: inum=71, it0, it1, ifice, irecl8, irec
158
159      REAL(wp),DIMENSION(jpi,jpj,35) ::  zmoment
160      REAL(wp),DIMENSION(2) :: zinfo
161
162      CHARACTER(len=45)  ::   ccfile = 'restart_ice_in',clres
163      !!-----------------------------------------------------------------------
164
165      !Initialisations
166
167       ! Open direct access file, with reclength for 2D wp fields
168       WRITE(clres,'(a,".",i3.3)') TRIM(ccfile),narea
169       CALL ctlopn(inum,clres,'UNKNOWN','UNFORMATTED','DIRECT',8,numout,lwp,1)
170   !!!    OPEN(inum,FILE=clres,FORM='UNFORMATTED', ACCESS='DIRECT', RECL=8)
171       READ(inum,REC=1) irecl8
172       CLOSE(inum)
173
174       OPEN(inum,FILE=clres,FORM='UNFORMATTED', ACCESS='DIRECT', RECL=irecl8)
175       READ(inum,REC=1) irecl8, ifice, it1
176     
177
178      !Read inumrst
179
180      it0          = nit000
181
182
183      IF (lwp) THEN
184      WRITE(numout,*)
185      WRITE(numout,*) 'lim_rst_fdir :  READ restart file name ', ccfile, ' at time step : ', it1
186      WRITE(numout,*) '~~~~~~~~~~~~'
187      END IF
188
189
190      !Control of date
191     
192      IF( ( it0 - it1 ) /= 1 .AND. ABS( nrstdt ) == 1 ) THEN
193         IF (lwp) THEN
194         WRITE(numout,cform_err)
195         WRITE(numout,*) ' ===>>>> : problem with nit000 for the restart'
196         WRITE(numout,*) ' we stop. verify the file or rerun with the value  0 for the'
197         WRITE(numout,*) ' control of time parameter  nrstdt'
198         END IF
199         nstop = nstop + 1
200      ENDIF
201
202
203      irec = 2
204      READ(inum,REC=irec)  hicif(:,:)    ! prognostic variables
205      irec = irec +1
206      READ(inum,REC=irec)  hsnif(:,:)
207      irec = irec +1
208      READ(inum,REC=irec)  frld(:,:)
209      irec = irec +1
210      READ(inum,REC=irec)  sist(:,:)
211      irec = irec +1
212# if defined key_coupled
213      READ(inum,REC=irec)  albege(:,:)
214      irec = irec +1
215# endif
216      DO jf = 1, jplayersp1
217      READ(inum,REC=irec)  tbif(:,:,jf)
218      irec = irec +1
219      END DO
220      READ(inum,REC=irec)  u_ice(:,:)
221      irec = irec +1
222      READ(inum,REC=irec)  v_ice(:,:)
223      irec = irec +1
224      READ(inum,REC=irec)  gtaux(:,:)
225      irec = irec +1
226      READ(inum,REC=irec)  gtauy(:,:)
227      irec = irec +1
228      READ(inum,REC=irec)  qstoif(:,:)
229      irec = irec +1
230      READ(inum,REC=irec)  fsbbq(:,:)
231      irec = irec +1
232      DO jf = 1, 35
233      READ(inum,REC=irec)  zmoment(:,:,jf)
234      irec = irec +1
235      END DO
236 
237      CLOSE(inum)
238
239      kt = it1
240            sxice(:,:)  = zmoment(:,:,1)
241            syice(:,:)  = zmoment(:,:,2)
242            sxxice(:,:) = zmoment(:,:,3)
243            syyice(:,:) = zmoment(:,:,4)
244            sxyice(:,:) = zmoment(:,:,5)
245            sxsn(:,:)   = zmoment(:,:,6)
246            sysn(:,:)   = zmoment(:,:,7)
247            sxxsn(:,:)  = zmoment(:,:,8)
248            syysn(:,:)  = zmoment(:,:,9)
249            sxysn(:,:)  = zmoment(:,:,10)
250            sxa(:,:)    = zmoment(:,:,11)
251            sya(:,:)    = zmoment(:,:,12)
252            sxxa(:,:)   = zmoment(:,:,13)
253            syya(:,:)   = zmoment(:,:,14)
254            sxya(:,:)   = zmoment(:,:,15)
255            sxc0(:,:)   = zmoment(:,:,16)
256            syc0(:,:)   = zmoment(:,:,17)
257            sxxc0(:,:)  = zmoment(:,:,18)
258            syyc0(:,:)  = zmoment(:,:,19)
259            sxyc0(:,:)  = zmoment(:,:,20)
260            sxc1(:,:)   = zmoment(:,:,21)
261            syc1(:,:)   = zmoment(:,:,22)
262            sxxc1(:,:)  = zmoment(:,:,23)
263            syyc1(:,:)  = zmoment(:,:,24)
264            sxyc1(:,:)  = zmoment(:,:,25)
265            sxc2(:,:)   = zmoment(:,:,26)
266            syc2(:,:)   = zmoment(:,:,27)
267            sxxc2(:,:)  = zmoment(:,:,28)
268            syyc2(:,:)  = zmoment(:,:,29)
269            sxyc2(:,:)  = zmoment(:,:,30)
270            sxst(:,:)   = zmoment(:,:,31)
271            syst(:,:)   = zmoment(:,:,32)
272            sxxst(:,:)  = zmoment(:,:,33)
273            syyst(:,:)  = zmoment(:,:,34)
274            sxyst(:,:)  = zmoment(:,:,35)
275     
276   END SUBROUTINE lim_rst_read
Note: See TracBrowser for help on using the repository browser.