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_3 – NEMO

source: trunk/NEMO/LIM_SRC_3/limrst_dimg.h90 @ 869

Last change on this file since 869 was 869, checked in by rblod, 16 years ago

Parallelisation of LIM3. This commit seems to ensure the reproducibility mono/mpp. See ticket #77.

File size: 9.7 KB
Line 
1   !!----------------------------------------------------------------------
2   !!                     *** limrst_dimg.h90  ***
3   !!----------------------------------------------------------------------
4   !!   LIM 2.0,  UCL-LOCEAN-IPSL (2005)
5   !! $Header: /home/opalod/NEMOCVSROOT/NEMO/LIM_SRC/limrst_dimg.h90,v 1.2 2005/03/27 18:34:42 opalod Exp $
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       ! 0. Initializations
42       ! ------------------
43
44       IF(lwp) THEN
45          WRITE(numout,*) ' '
46          WRITE(numout,*) ' lim_rst_write: output done in inum = ',   &
47               inum,' at it= ',kt,' date= ',ndastp
48          WRITE(numout,*) ' -------'
49       ENDIF
50
51       ! Open direct access file, with reclength for 2D wp fields
52       irecl8= jpi * jpj * wp
53       WRITE(clres,'(a,".",i3.3)') TRIM(ccfile),narea
54       OPEN(inum,FILE=clres,FORM='UNFORMATTED', ACCESS='DIRECT', RECL=irecl8 )
55
56
57      it0      = kt
58     
59      zinfo(1) = FLOAT( nfice )   ! iteration number
60      zinfo(2) = FLOAT( it0 )        ! time-step in second
61
62      ! Write in inum
63
64      zmoment(:,:,1)  = sxice (:,:)
65      zmoment(:,:,2)  = syice (:,:)
66      zmoment(:,:,3)  = sxxice(:,:)
67      zmoment(:,:,4)  = syyice(:,:)
68      zmoment(:,:,5)  = sxyice(:,:)
69      zmoment(:,:,6)  = sxsn  (:,:)
70      zmoment(:,:,7)  = sysn  (:,:)
71      zmoment(:,:,8)  = sxxsn (:,:)
72      zmoment(:,:,9)  = syysn (:,:)
73      zmoment(:,:,10) = sxysn (:,:)
74      zmoment(:,:,11) = sxa   (:,:)
75      zmoment(:,:,12) = sya   (:,:)
76      zmoment(:,:,13) = sxxa  (:,:)
77      zmoment(:,:,14) = syya  (:,:)
78      zmoment(:,:,15) = sxya  (:,:)
79      zmoment(:,:,16) = sxc0  (:,:)
80      zmoment(:,:,17) = syc0  (:,:)
81      zmoment(:,:,18) = sxxc0 (:,:)
82      zmoment(:,:,19) = syyc0 (:,:)
83      zmoment(:,:,20) = sxyc0 (:,:)
84      zmoment(:,:,21) = sxc1  (:,:)
85      zmoment(:,:,22) = syc1  (:,:)
86      zmoment(:,:,23) = sxxc1 (:,:)
87      zmoment(:,:,24) = syyc1 (:,:)
88      zmoment(:,:,25) = sxyc1 (:,:)
89      zmoment(:,:,26) = sxc2  (:,:)
90      zmoment(:,:,27) = syc2  (:,:)
91      zmoment(:,:,28) = sxxc2 (:,:)
92      zmoment(:,:,29) = syyc2 (:,:)
93      zmoment(:,:,30) = sxyc2 (:,:)
94      zmoment(:,:,31) = sxst  (:,:)
95      zmoment(:,:,32) = syst  (:,:)
96      zmoment(:,:,33) = sxxst (:,:)
97      zmoment(:,:,34) = syyst (:,:)
98      zmoment(:,:,35) = sxyst (:,:)
99
100      WRITE(inum,REC=1) irecl8, nfice, it0, &
101          &              ndastp, adatrj, jpi, jpj, jpk,  &
102          &              jpni, jpnj, jpnij, narea, jpiglo, jpjglo, &
103          &              nlcit, nlcjt, nldit, nldjt, nleit, nlejt, nimppt, njmppt
104
105      irec= 2
106      WRITE(inum,REC=irec)  ht_i(:,:,1)          ! prognostic variables
107      irec = irec + 1
108      WRITE(inum,REC=irec)  ht_s(:,:,1)
109      irec = irec + 1
110      WRITE(inum,REC=irec)  frld(:,:)
111      irec = irec + 1
112!     WRITE(inum,REC=irec)  sist(:,:)
113!     irec = irec + 1
114      WRITE(inum,REC=irec)  t_su(:,:,1)
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! MV 2005
125      DO jf=1, nlay_s
126      WRITE(inum,REC=irec)  t_s(:,:,jf,1)
127      irec = irec + 1
128      END DO
129! END MV 2005
130! MV 2005
131      DO jf=1, nlay_i
132      WRITE(inum,REC=irec)  t_i(:,:,jf,1)
133      irec = irec + 1
134      END DO
135! END MV 2005
136      WRITE(inum,REC=irec)  u_ice(:,:)
137      irec = irec + 1
138      WRITE(inum,REC=irec)  v_ice(:,:)
139      irec = irec + 1
140      WRITE(inum,REC=irec)  gtaux(:,:)
141      irec = irec + 1
142      WRITE(inum,REC=irec)  gtauy(:,:)
143      irec = irec + 1
144! MV 2005
145!     WRITE(inum,REC=irec)  qstoif(:,:)
146!     irec = irec + 1
147! END MV 2005
148      WRITE(inum,REC=irec)  fsbbq(:,:)
149      irec = irec + 1
150      DO jf=1,35
151      WRITE(inum,REC=irec)  zmoment(:,:,jf)
152      irec = irec + 1
153      END DO
154 
155      CLOSE(inum)
156     
157   END SUBROUTINE lim_rst_write
158
159
160   SUBROUTINE lim_rst_read(kt )
161      !!-----------------------------------------------------------------------
162      !!  restart from a state defined in a binary file
163      !!-----------------------------------------------------------------------
164      !! * Arguments
165      USE par_ice
166      INTEGER ,INTENT(out)  ::   kt        ! number of iteration
167
168      !- dummy variables :
169
170      INTEGER :: ji, jj, jf
171      INTEGER :: inum=71, it0, it1, ifice, irecl8, irec
172
173      REAL(wp),DIMENSION(jpi,jpj,35) ::  zmoment
174      REAL(wp),DIMENSION(2) :: zinfo
175
176      CHARACTER(len=45)  ::   ccfile = 'restart_ice_in',clres
177      !!-----------------------------------------------------------------------
178
179      !Initialisations
180
181       ! Open direct access file, with reclength for 2D wp fields
182       WRITE(clres,'(a,".",i3.3)') TRIM(ccfile),narea
183       OPEN(inum,FILE=clres,FORM='UNFORMATTED', ACCESS='DIRECT', RECL=8)
184       READ(inum,REC=1) irecl8
185       CLOSE(inum)
186
187       OPEN(inum,FILE=clres,FORM='UNFORMATTED', ACCESS='DIRECT', RECL=irecl8)
188       READ(inum,REC=1) irecl8, ifice, it1
189     
190
191      !Read inumrst
192
193      it0          = nit000
194
195
196      IF (lwp) THEN
197      WRITE(numout,*)
198      WRITE(numout,*) 'lim_rst_fdir :  READ restart file name ', ccfile, ' at time step : ', it1
199      WRITE(numout,*) '~~~~~~~~~~~~'
200      END IF
201
202
203      !Control of date
204     
205      IF( ( it0 - it1 ) /= 1 .AND. ABS( nrstdt ) == 1 ) THEN
206         IF (lwp) THEN
207         WRITE(numout,cform_err)
208         WRITE(numout,*) ' ===>>>> : problem with nit000 for the restart'
209         WRITE(numout,*) ' we stop. verify the file or rerun with the value  0 for the'
210         WRITE(numout,*) ' control of time parameter  nrstdt'
211         END IF
212         nstop = nstop + 1
213      ENDIF
214
215
216      irec = 2
217      READ(inum,REC=irec)  ht_i(:,:,1)    ! prognostic variables
218      irec = irec +1
219      READ(inum,REC=irec)  ht_s(:,:,1)
220      irec = irec +1
221      READ(inum,REC=irec)  frld(:,:)
222      irec = irec +1
223!     READ(inum,REC=irec)  sist(:,:)
224!     irec = irec +1
225!RB bug
226      READ(inum,REC=irec)  t_su(:,:)
227      irec = irec +1
228# if defined key_coupled
229      READ(inum,REC=irec)  albege(:,:)
230      irec = irec +1
231# endif
232!     DO jf = 1, jplayersp1
233!     READ(inum,REC=irec)  tbif(:,:,jf)
234!     irec = irec +1
235!     END DO
236! MV 2005
237      DO jf = 1, nlay_s
238      READ(inum,REC=irec)  t_s(:,:,jf,1)
239      irec = irec +1
240      END DO
241      DO jf = 1, nlay_i
242      READ(inum,REC=irec)  t_i(:,:,jf)
243      irec = irec +1
244      END DO
245! MV 2005
246      READ(inum,REC=irec)  u_ice(:,:)
247      irec = irec +1
248      READ(inum,REC=irec)  v_ice(:,:)
249      irec = irec +1
250      READ(inum,REC=irec)  gtaux(:,:)
251      irec = irec +1
252      READ(inum,REC=irec)  gtauy(:,:)
253      irec = irec +1
254! MV 2005
255!     READ(inum,REC=irec)  qstoif(:,:)
256!     irec = irec +1
257! END MV 2005
258      READ(inum,REC=irec)  fsbbq(:,:)
259      irec = irec +1
260      DO jf = 1, 35
261      READ(inum,REC=irec)  zmoment(:,:,jf)
262      irec = irec +1
263      END DO
264 
265      CLOSE(inum)
266
267      kt = it1
268            sxice(:,:)  = zmoment(:,:,1)
269            syice(:,:)  = zmoment(:,:,2)
270            sxxice(:,:) = zmoment(:,:,3)
271            syyice(:,:) = zmoment(:,:,4)
272            sxyice(:,:) = zmoment(:,:,5)
273            sxsn(:,:)   = zmoment(:,:,6)
274            sysn(:,:)   = zmoment(:,:,7)
275            sxxsn(:,:)  = zmoment(:,:,8)
276            syysn(:,:)  = zmoment(:,:,9)
277            sxysn(:,:)  = zmoment(:,:,10)
278            sxa(:,:)    = zmoment(:,:,11)
279            sya(:,:)    = zmoment(:,:,12)
280            sxxa(:,:)   = zmoment(:,:,13)
281            syya(:,:)   = zmoment(:,:,14)
282            sxya(:,:)   = zmoment(:,:,15)
283            sxc0(:,:)   = zmoment(:,:,16)
284            syc0(:,:)   = zmoment(:,:,17)
285            sxxc0(:,:)  = zmoment(:,:,18)
286            syyc0(:,:)  = zmoment(:,:,19)
287            sxyc0(:,:)  = zmoment(:,:,20)
288            sxc1(:,:)   = zmoment(:,:,21)
289            syc1(:,:)   = zmoment(:,:,22)
290            sxxc1(:,:)  = zmoment(:,:,23)
291            syyc1(:,:)  = zmoment(:,:,24)
292            sxyc1(:,:)  = zmoment(:,:,25)
293            sxc2(:,:)   = zmoment(:,:,26)
294            syc2(:,:)   = zmoment(:,:,27)
295            sxxc2(:,:)  = zmoment(:,:,28)
296            syyc2(:,:)  = zmoment(:,:,29)
297            sxyc2(:,:)  = zmoment(:,:,30)
298            sxst(:,:)   = zmoment(:,:,31)
299            syst(:,:)   = zmoment(:,:,32)
300            sxxst(:,:)  = zmoment(:,:,33)
301            syyst(:,:)  = zmoment(:,:,34)
302            sxyst(:,:)  = zmoment(:,:,35)
303     
304   END SUBROUTINE lim_rst_read
Note: See TracBrowser for help on using the repository browser.