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 @ 107

Last change on this file since 107 was 107, checked in by opalod, 20 years ago

CT : UPDATE068 : Add binary output possibilities with the dimg output format

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