1 | MODULE limrst |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE limrst *** |
---|
4 | !! Ice restart : write the ice restart file |
---|
5 | !!====================================================================== |
---|
6 | !! History: - ! 2005-04 (M. Vancoppenolle) Original code |
---|
7 | !! 3.0 ! 2008-03 (C. Ethe) restart files in using IOM interface |
---|
8 | !! 4.0 ! 2011-02 (G. Madec) dynamical allocation |
---|
9 | !!---------------------------------------------------------------------- |
---|
10 | #if defined key_lim3 |
---|
11 | !!---------------------------------------------------------------------- |
---|
12 | !! 'key_lim3' : LIM sea-ice model |
---|
13 | !!---------------------------------------------------------------------- |
---|
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 |
---|
17 | !!---------------------------------------------------------------------- |
---|
18 | USE ice ! sea-ice variables |
---|
19 | USE oce , ONLY : snwice_mass, snwice_mass_b |
---|
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) |
---|
28 | USE limctl |
---|
29 | |
---|
30 | IMPLICIT NONE |
---|
31 | PRIVATE |
---|
32 | |
---|
33 | PUBLIC lim_rst_opn ! routine called by icestep.F90 |
---|
34 | PUBLIC lim_rst_write ! routine called by icestep.F90 |
---|
35 | PUBLIC lim_rst_read ! routine called by sbc_lim_init |
---|
36 | |
---|
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) |
---|
39 | |
---|
40 | !!---------------------------------------------------------------------- |
---|
41 | !! NEMO/LIM3 4.0 , UCL - NEMO Consortium (2011) |
---|
42 | !! $Id$ |
---|
43 | !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) |
---|
44 | !!---------------------------------------------------------------------- |
---|
45 | CONTAINS |
---|
46 | |
---|
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 | ! |
---|
55 | CHARACTER(len=20) :: clkt ! ocean time-step define as a character |
---|
56 | CHARACTER(len=50) :: clname ! ice output restart file name |
---|
57 | CHARACTER(len=256) :: clpath ! full path to ice output restart file |
---|
58 | !!---------------------------------------------------------------------- |
---|
59 | ! |
---|
60 | IF( kt == nit000 ) lrst_ice = .FALSE. ! default definition |
---|
61 | |
---|
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 |
---|
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 |
---|
71 | ENDIF |
---|
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 ( jprstdimg ) |
---|
80 | WRITE(numout,*) ' open ice restart binary file: ',TRIM(clpath)//clname |
---|
81 | CASE DEFAULT |
---|
82 | WRITE(numout,*) ' open ice restart NetCDF file: ',TRIM(clpath)//clname |
---|
83 | END SELECT |
---|
84 | IF( kt == nitrst - 2*nn_fsbc + 1 ) THEN |
---|
85 | WRITE(numout,*) ' kt = nitrst - 2*nn_fsbc + 1 = ', kt,' date= ', ndastp |
---|
86 | ELSE ; WRITE(numout,*) ' kt = ' , kt,' date= ', ndastp |
---|
87 | ENDIF |
---|
88 | ENDIF |
---|
89 | ! |
---|
90 | CALL iom_open( TRIM(clpath)//TRIM(clname), numriw, ldwrt = .TRUE., kiolib = jprstlib ) |
---|
91 | lrst_ice = .TRUE. |
---|
92 | ENDIF |
---|
93 | ENDIF |
---|
94 | ! |
---|
95 | IF( ln_limctl ) CALL lim_prt( kt, iiceprt, jiceprt, 1, ' - Beginning the time step - ' ) ! control print |
---|
96 | END SUBROUTINE lim_rst_opn |
---|
97 | |
---|
98 | |
---|
99 | SUBROUTINE lim_rst_write( kt ) |
---|
100 | !!---------------------------------------------------------------------- |
---|
101 | !! *** lim_rst_write *** |
---|
102 | !! |
---|
103 | !! ** purpose : output of sea-ice variable in a netcdf file |
---|
104 | !!---------------------------------------------------------------------- |
---|
105 | INTEGER, INTENT(in) :: kt ! number of iteration |
---|
106 | !! |
---|
107 | INTEGER :: ji, jj, jk ,jl ! dummy loop indices |
---|
108 | INTEGER :: iter |
---|
109 | CHARACTER(len=25) :: znam |
---|
110 | CHARACTER(len=2) :: zchar, zchar1 |
---|
111 | REAL(wp), POINTER, DIMENSION(:,:) :: z2d |
---|
112 | !!---------------------------------------------------------------------- |
---|
113 | |
---|
114 | CALL wrk_alloc( jpi, jpj, z2d ) |
---|
115 | |
---|
116 | iter = kt + nn_fsbc - 1 ! ice restarts are written at kt == nitrst - nn_fsbc + 1 |
---|
117 | |
---|
118 | IF( iter == nitrst ) THEN |
---|
119 | IF(lwp) WRITE(numout,*) |
---|
120 | IF(lwp) WRITE(numout,*) 'lim_rst_write : write ice restart file kt =', kt |
---|
121 | IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~' |
---|
122 | ENDIF |
---|
123 | |
---|
124 | ! Write in numriw (if iter == nitrst) |
---|
125 | ! ------------------ |
---|
126 | ! ! calendar control |
---|
127 | CALL iom_rstput( iter, nitrst, numriw, 'nn_fsbc', REAL( nn_fsbc, wp ) ) ! time-step |
---|
128 | CALL iom_rstput( iter, nitrst, numriw, 'kt_ice' , REAL( iter , wp ) ) ! date |
---|
129 | |
---|
130 | ! Prognostic variables |
---|
131 | DO jl = 1, jpl |
---|
132 | WRITE(zchar,'(I2.2)') jl |
---|
133 | znam = 'v_i'//'_htc'//zchar |
---|
134 | z2d(:,:) = v_i(:,:,jl) |
---|
135 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
136 | znam = 'v_s'//'_htc'//zchar |
---|
137 | z2d(:,:) = v_s(:,:,jl) |
---|
138 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
139 | znam = 'smv_i'//'_htc'//zchar |
---|
140 | z2d(:,:) = smv_i(:,:,jl) |
---|
141 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
142 | znam = 'oa_i'//'_htc'//zchar |
---|
143 | z2d(:,:) = oa_i(:,:,jl) |
---|
144 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
145 | znam = 'a_i'//'_htc'//zchar |
---|
146 | z2d(:,:) = a_i(:,:,jl) |
---|
147 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
148 | znam = 't_su'//'_htc'//zchar |
---|
149 | z2d(:,:) = t_su(:,:,jl) |
---|
150 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
151 | END DO |
---|
152 | |
---|
153 | ! MV MP 2016 |
---|
154 | IF ( ln_limMP ) THEN |
---|
155 | DO jl = 1, jpl |
---|
156 | znam = 'a_ip'//'_htc'//zchar |
---|
157 | z2d(:,:) = a_ip(:,:,jl) |
---|
158 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
159 | znam = 'v_ip'//'_htc'//zchar |
---|
160 | z2d(:,:) = v_ip(:,:,jl) |
---|
161 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
162 | END DO |
---|
163 | ENDIF |
---|
164 | ! END MV MP 2016 |
---|
165 | |
---|
166 | DO jl = 1, jpl |
---|
167 | WRITE(zchar,'(I2.2)') jl |
---|
168 | znam = 'tempt_sl1'//'_htc'//zchar |
---|
169 | z2d(:,:) = e_s(:,:,1,jl) |
---|
170 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
171 | END DO |
---|
172 | |
---|
173 | DO jl = 1, jpl |
---|
174 | WRITE(zchar,'(I2.2)') jl |
---|
175 | DO jk = 1, nlay_i |
---|
176 | WRITE(zchar1,'(I2.2)') jk |
---|
177 | znam = 'tempt'//'_il'//zchar1//'_htc'//zchar |
---|
178 | z2d(:,:) = e_i(:,:,jk,jl) |
---|
179 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
180 | END DO |
---|
181 | END DO |
---|
182 | |
---|
183 | CALL iom_rstput( iter, nitrst, numriw, 'u_ice' , u_ice ) |
---|
184 | CALL iom_rstput( iter, nitrst, numriw, 'v_ice' , v_ice ) |
---|
185 | CALL iom_rstput( iter, nitrst, numriw, 'stress1_i' , stress1_i ) |
---|
186 | CALL iom_rstput( iter, nitrst, numriw, 'stress2_i' , stress2_i ) |
---|
187 | CALL iom_rstput( iter, nitrst, numriw, 'stress12_i' , stress12_i ) |
---|
188 | CALL iom_rstput( iter, nitrst, numriw, 'snwice_mass' , snwice_mass ) |
---|
189 | CALL iom_rstput( iter, nitrst, numriw, 'snwice_mass_b', snwice_mass_b ) |
---|
190 | |
---|
191 | ! In case Prather scheme is used for advection, write second order moments |
---|
192 | ! ------------------------------------------------------------------------ |
---|
193 | IF( nn_limadv == -1 ) THEN |
---|
194 | |
---|
195 | DO jl = 1, jpl |
---|
196 | WRITE(zchar,'(I2.2)') jl |
---|
197 | znam = 'sxice'//'_htc'//zchar |
---|
198 | z2d(:,:) = sxice(:,:,jl) |
---|
199 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
200 | znam = 'syice'//'_htc'//zchar |
---|
201 | z2d(:,:) = syice(:,:,jl) |
---|
202 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
203 | znam = 'sxxice'//'_htc'//zchar |
---|
204 | z2d(:,:) = sxxice(:,:,jl) |
---|
205 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
206 | znam = 'syyice'//'_htc'//zchar |
---|
207 | z2d(:,:) = syyice(:,:,jl) |
---|
208 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
209 | znam = 'sxyice'//'_htc'//zchar |
---|
210 | z2d(:,:) = sxyice(:,:,jl) |
---|
211 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
212 | znam = 'sxsn'//'_htc'//zchar |
---|
213 | z2d(:,:) = sxsn(:,:,jl) |
---|
214 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
215 | znam = 'sysn'//'_htc'//zchar |
---|
216 | z2d(:,:) = sysn(:,:,jl) |
---|
217 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
218 | znam = 'sxxsn'//'_htc'//zchar |
---|
219 | z2d(:,:) = sxxsn(:,:,jl) |
---|
220 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
221 | znam = 'syysn'//'_htc'//zchar |
---|
222 | z2d(:,:) = syysn(:,:,jl) |
---|
223 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
224 | znam = 'sxysn'//'_htc'//zchar |
---|
225 | z2d(:,:) = sxysn(:,:,jl) |
---|
226 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
227 | znam = 'sxa'//'_htc'//zchar |
---|
228 | z2d(:,:) = sxa(:,:,jl) |
---|
229 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
230 | znam = 'sya'//'_htc'//zchar |
---|
231 | z2d(:,:) = sya(:,:,jl) |
---|
232 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
233 | znam = 'sxxa'//'_htc'//zchar |
---|
234 | z2d(:,:) = sxxa(:,:,jl) |
---|
235 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
236 | znam = 'syya'//'_htc'//zchar |
---|
237 | z2d(:,:) = syya(:,:,jl) |
---|
238 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
239 | znam = 'sxya'//'_htc'//zchar |
---|
240 | z2d(:,:) = sxya(:,:,jl) |
---|
241 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
242 | znam = 'sxc0'//'_htc'//zchar |
---|
243 | z2d(:,:) = sxc0(:,:,jl) |
---|
244 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
245 | znam = 'syc0'//'_htc'//zchar |
---|
246 | z2d(:,:) = syc0(:,:,jl) |
---|
247 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
248 | znam = 'sxxc0'//'_htc'//zchar |
---|
249 | z2d(:,:) = sxxc0(:,:,jl) |
---|
250 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
251 | znam = 'syyc0'//'_htc'//zchar |
---|
252 | z2d(:,:) = syyc0(:,:,jl) |
---|
253 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
254 | znam = 'sxyc0'//'_htc'//zchar |
---|
255 | z2d(:,:) = sxyc0(:,:,jl) |
---|
256 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
257 | znam = 'sxsal'//'_htc'//zchar |
---|
258 | z2d(:,:) = sxsal(:,:,jl) |
---|
259 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
260 | znam = 'sysal'//'_htc'//zchar |
---|
261 | z2d(:,:) = sysal(:,:,jl) |
---|
262 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
263 | znam = 'sxxsal'//'_htc'//zchar |
---|
264 | z2d(:,:) = sxxsal(:,:,jl) |
---|
265 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
266 | znam = 'syysal'//'_htc'//zchar |
---|
267 | z2d(:,:) = syysal(:,:,jl) |
---|
268 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
269 | znam = 'sxysal'//'_htc'//zchar |
---|
270 | z2d(:,:) = sxysal(:,:,jl) |
---|
271 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
272 | znam = 'sxage'//'_htc'//zchar |
---|
273 | z2d(:,:) = sxage(:,:,jl) |
---|
274 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
275 | znam = 'syage'//'_htc'//zchar |
---|
276 | z2d(:,:) = syage(:,:,jl) |
---|
277 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
278 | znam = 'sxxage'//'_htc'//zchar |
---|
279 | z2d(:,:) = sxxage(:,:,jl) |
---|
280 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
281 | znam = 'syyage'//'_htc'//zchar |
---|
282 | z2d(:,:) = syyage(:,:,jl) |
---|
283 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
284 | znam = 'sxyage'//'_htc'//zchar |
---|
285 | z2d(:,:) = sxyage(:,:,jl) |
---|
286 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
287 | END DO |
---|
288 | |
---|
289 | CALL iom_rstput( iter, nitrst, numriw, 'sxopw ' , sxopw ) |
---|
290 | CALL iom_rstput( iter, nitrst, numriw, 'syopw ' , syopw ) |
---|
291 | CALL iom_rstput( iter, nitrst, numriw, 'sxxopw' , sxxopw ) |
---|
292 | CALL iom_rstput( iter, nitrst, numriw, 'syyopw' , syyopw ) |
---|
293 | CALL iom_rstput( iter, nitrst, numriw, 'sxyopw' , sxyopw ) |
---|
294 | |
---|
295 | DO jl = 1, jpl |
---|
296 | WRITE(zchar,'(I2.2)') jl |
---|
297 | DO jk = 1, nlay_i |
---|
298 | WRITE(zchar1,'(I2.2)') jk |
---|
299 | znam = 'sxe'//'_il'//zchar1//'_htc'//zchar |
---|
300 | z2d(:,:) = sxe(:,:,jk,jl) |
---|
301 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
302 | znam = 'sye'//'_il'//zchar1//'_htc'//zchar |
---|
303 | z2d(:,:) = sye(:,:,jk,jl) |
---|
304 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
305 | znam = 'sxxe'//'_il'//zchar1//'_htc'//zchar |
---|
306 | z2d(:,:) = sxxe(:,:,jk,jl) |
---|
307 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
308 | znam = 'syye'//'_il'//zchar1//'_htc'//zchar |
---|
309 | z2d(:,:) = syye(:,:,jk,jl) |
---|
310 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
311 | znam = 'sxye'//'_il'//zchar1//'_htc'//zchar |
---|
312 | z2d(:,:) = sxye(:,:,jk,jl) |
---|
313 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
314 | END DO |
---|
315 | END DO |
---|
316 | ! MV MP 2016 |
---|
317 | IF ( ln_limMP ) THEN |
---|
318 | DO jl = 1, jpl |
---|
319 | znam = 'sxap'//'_htc'//zchar |
---|
320 | z2d(:,:) = sxap(:,:,jl) |
---|
321 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
322 | znam = 'syap'//'_htc'//zchar |
---|
323 | z2d(:,:) = syap(:,:,jl) |
---|
324 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
325 | znam = 'sxxap'//'_htc'//zchar |
---|
326 | z2d(:,:) = sxxap(:,:,jl) |
---|
327 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
328 | znam = 'syyap'//'_htc'//zchar |
---|
329 | z2d(:,:) = syyap(:,:,jl) |
---|
330 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
331 | znam = 'sxyap'//'_htc'//zchar |
---|
332 | z2d(:,:) = sxyap(:,:,jl) |
---|
333 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
334 | |
---|
335 | znam = 'sxvp'//'_htc'//zchar |
---|
336 | z2d(:,:) = sxvp(:,:,jl) |
---|
337 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
338 | znam = 'syvp'//'_htc'//zchar |
---|
339 | z2d(:,:) = syvp(:,:,jl) |
---|
340 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
341 | znam = 'sxxvp'//'_htc'//zchar |
---|
342 | z2d(:,:) = sxxvp(:,:,jl) |
---|
343 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
344 | znam = 'syyvp'//'_htc'//zchar |
---|
345 | z2d(:,:) = syyvp(:,:,jl) |
---|
346 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
347 | znam = 'sxyvp'//'_htc'//zchar |
---|
348 | z2d(:,:) = sxyvp(:,:,jl) |
---|
349 | CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) |
---|
350 | END DO |
---|
351 | ENDIF |
---|
352 | |
---|
353 | ENDIF |
---|
354 | |
---|
355 | ! close restart file |
---|
356 | ! ------------------ |
---|
357 | IF( iter == nitrst ) THEN |
---|
358 | CALL iom_close( numriw ) |
---|
359 | lrst_ice = .FALSE. |
---|
360 | ENDIF |
---|
361 | ! |
---|
362 | CALL wrk_dealloc( jpi, jpj, z2d ) |
---|
363 | ! |
---|
364 | END SUBROUTINE lim_rst_write |
---|
365 | |
---|
366 | |
---|
367 | SUBROUTINE lim_rst_read |
---|
368 | !!---------------------------------------------------------------------- |
---|
369 | !! *** lim_rst_read *** |
---|
370 | !! |
---|
371 | !! ** purpose : read of sea-ice variable restart in a netcdf file |
---|
372 | !!---------------------------------------------------------------------- |
---|
373 | INTEGER :: ji, jj, jk, jl |
---|
374 | REAL(wp) :: zfice, ziter |
---|
375 | REAL(wp), POINTER, DIMENSION(:,:) :: z2d |
---|
376 | CHARACTER(len=25) :: znam |
---|
377 | CHARACTER(len=2) :: zchar, zchar1 |
---|
378 | INTEGER :: jlibalt = jprstlib |
---|
379 | LOGICAL :: llok |
---|
380 | !!---------------------------------------------------------------------- |
---|
381 | |
---|
382 | CALL wrk_alloc( jpi, jpj, z2d ) |
---|
383 | |
---|
384 | IF(lwp) THEN |
---|
385 | WRITE(numout,*) |
---|
386 | WRITE(numout,*) 'lim_rst_read : read ice NetCDF restart file' |
---|
387 | WRITE(numout,*) '~~~~~~~~~~~~~' |
---|
388 | ENDIF |
---|
389 | |
---|
390 | IF ( jprstlib == jprstdimg ) THEN |
---|
391 | ! eventually read netcdf file (monobloc) for restarting on different number of processors |
---|
392 | ! if {cn_icerst_in}.nc exists, then set jlibalt to jpnf90 |
---|
393 | INQUIRE( FILE = TRIM(cn_icerst_indir)//'/'//TRIM(cn_icerst_in)//'.nc', EXIST = llok ) |
---|
394 | IF ( llok ) THEN ; jlibalt = jpnf90 ; ELSE ; jlibalt = jprstlib ; ENDIF |
---|
395 | ENDIF |
---|
396 | |
---|
397 | CALL iom_open ( TRIM(cn_icerst_indir)//'/'//cn_icerst_in, numrir, kiolib = jprstlib ) |
---|
398 | |
---|
399 | CALL iom_get( numrir, 'nn_fsbc', zfice ) |
---|
400 | CALL iom_get( numrir, 'kt_ice' , ziter ) |
---|
401 | IF(lwp) WRITE(numout,*) ' read ice restart file at time step : ', ziter |
---|
402 | IF(lwp) WRITE(numout,*) ' in any case we force it to nit000 - 1 : ', nit000 - 1 |
---|
403 | |
---|
404 | !Control of date |
---|
405 | |
---|
406 | IF( ( nit000 - NINT(ziter) ) /= 1 .AND. ABS( nrstdt ) == 1 ) & |
---|
407 | & CALL ctl_stop( 'lim_rst_read ===>>>> : problem with nit000 in ice restart', & |
---|
408 | & ' verify the file or rerun with the value 0 for the', & |
---|
409 | & ' control of time parameter nrstdt' ) |
---|
410 | IF( NINT(zfice) /= nn_fsbc .AND. ABS( nrstdt ) == 1 ) & |
---|
411 | & CALL ctl_stop( 'lim_rst_read ===>>>> : problem with nn_fsbc in ice restart', & |
---|
412 | & ' verify the file or rerun with the value 0 for the', & |
---|
413 | & ' control of time parameter nrstdt' ) |
---|
414 | |
---|
415 | ! Prognostic variables |
---|
416 | DO jl = 1, jpl |
---|
417 | WRITE(zchar,'(I2.2)') jl |
---|
418 | znam = 'v_i'//'_htc'//zchar |
---|
419 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
420 | v_i(:,:,jl) = z2d(:,:) |
---|
421 | znam = 'v_s'//'_htc'//zchar |
---|
422 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
423 | v_s(:,:,jl) = z2d(:,:) |
---|
424 | znam = 'smv_i'//'_htc'//zchar |
---|
425 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
426 | smv_i(:,:,jl) = z2d(:,:) |
---|
427 | znam = 'oa_i'//'_htc'//zchar |
---|
428 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
429 | oa_i(:,:,jl) = z2d(:,:) |
---|
430 | znam = 'a_i'//'_htc'//zchar |
---|
431 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
432 | a_i(:,:,jl) = z2d(:,:) |
---|
433 | znam = 't_su'//'_htc'//zchar |
---|
434 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
435 | t_su(:,:,jl) = z2d(:,:) |
---|
436 | END DO |
---|
437 | |
---|
438 | ! MV MP 2016 |
---|
439 | IF ( ln_limMP ) THEN |
---|
440 | DO jl = 1, jpl |
---|
441 | znam = 'a_ip'//'_htc'//zchar |
---|
442 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
443 | a_ip(:,:,jl) = z2d(:,:) |
---|
444 | znam = 'v_ip'//'_htc'//zchar |
---|
445 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
446 | v_ip(:,:,jl) = z2d(:,:) |
---|
447 | END DO |
---|
448 | ENDIF |
---|
449 | |
---|
450 | DO jl = 1, jpl |
---|
451 | WRITE(zchar,'(I2.2)') jl |
---|
452 | znam = 'tempt_sl1'//'_htc'//zchar |
---|
453 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
454 | e_s(:,:,1,jl) = z2d(:,:) |
---|
455 | END DO |
---|
456 | |
---|
457 | DO jl = 1, jpl |
---|
458 | WRITE(zchar,'(I2.2)') jl |
---|
459 | DO jk = 1, nlay_i |
---|
460 | WRITE(zchar1,'(I2.2)') jk |
---|
461 | znam = 'tempt'//'_il'//zchar1//'_htc'//zchar |
---|
462 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
463 | e_i(:,:,jk,jl) = z2d(:,:) |
---|
464 | END DO |
---|
465 | END DO |
---|
466 | |
---|
467 | CALL iom_get( numrir, jpdom_autoglo, 'u_ice' , u_ice ) |
---|
468 | CALL iom_get( numrir, jpdom_autoglo, 'v_ice' , v_ice ) |
---|
469 | CALL iom_get( numrir, jpdom_autoglo, 'stress1_i' , stress1_i ) |
---|
470 | CALL iom_get( numrir, jpdom_autoglo, 'stress2_i' , stress2_i ) |
---|
471 | CALL iom_get( numrir, jpdom_autoglo, 'stress12_i', stress12_i ) |
---|
472 | CALL iom_get( numrir, jpdom_autoglo, 'snwice_mass' , snwice_mass ) |
---|
473 | CALL iom_get( numrir, jpdom_autoglo, 'snwice_mass_b', snwice_mass_b ) |
---|
474 | |
---|
475 | ! In case Prather scheme is used for advection, read second order moments |
---|
476 | ! ------------------------------------------------------------------------ |
---|
477 | IF( nn_limadv == -1 ) THEN |
---|
478 | |
---|
479 | DO jl = 1, jpl |
---|
480 | WRITE(zchar,'(I2.2)') jl |
---|
481 | znam = 'sxice'//'_htc'//zchar |
---|
482 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
483 | sxice(:,:,jl) = z2d(:,:) |
---|
484 | znam = 'syice'//'_htc'//zchar |
---|
485 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
486 | syice(:,:,jl) = z2d(:,:) |
---|
487 | znam = 'sxxice'//'_htc'//zchar |
---|
488 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
489 | sxxice(:,:,jl) = z2d(:,:) |
---|
490 | znam = 'syyice'//'_htc'//zchar |
---|
491 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
492 | syyice(:,:,jl) = z2d(:,:) |
---|
493 | znam = 'sxyice'//'_htc'//zchar |
---|
494 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
495 | sxyice(:,:,jl) = z2d(:,:) |
---|
496 | znam = 'sxsn'//'_htc'//zchar |
---|
497 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
498 | sxsn(:,:,jl) = z2d(:,:) |
---|
499 | znam = 'sysn'//'_htc'//zchar |
---|
500 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
501 | sysn(:,:,jl) = z2d(:,:) |
---|
502 | znam = 'sxxsn'//'_htc'//zchar |
---|
503 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
504 | sxxsn(:,:,jl) = z2d(:,:) |
---|
505 | znam = 'syysn'//'_htc'//zchar |
---|
506 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
507 | syysn(:,:,jl) = z2d(:,:) |
---|
508 | znam = 'sxysn'//'_htc'//zchar |
---|
509 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
510 | sxysn(:,:,jl) = z2d(:,:) |
---|
511 | znam = 'sxa'//'_htc'//zchar |
---|
512 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
513 | sxa(:,:,jl) = z2d(:,:) |
---|
514 | znam = 'sya'//'_htc'//zchar |
---|
515 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
516 | sya(:,:,jl) = z2d(:,:) |
---|
517 | znam = 'sxxa'//'_htc'//zchar |
---|
518 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
519 | sxxa(:,:,jl) = z2d(:,:) |
---|
520 | znam = 'syya'//'_htc'//zchar |
---|
521 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
522 | syya(:,:,jl) = z2d(:,:) |
---|
523 | znam = 'sxya'//'_htc'//zchar |
---|
524 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
525 | sxya(:,:,jl) = z2d(:,:) |
---|
526 | znam = 'sxc0'//'_htc'//zchar |
---|
527 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
528 | sxc0(:,:,jl) = z2d(:,:) |
---|
529 | znam = 'syc0'//'_htc'//zchar |
---|
530 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
531 | syc0(:,:,jl) = z2d(:,:) |
---|
532 | znam = 'sxxc0'//'_htc'//zchar |
---|
533 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
534 | sxxc0(:,:,jl) = z2d(:,:) |
---|
535 | znam = 'syyc0'//'_htc'//zchar |
---|
536 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
537 | syyc0(:,:,jl) = z2d(:,:) |
---|
538 | znam = 'sxyc0'//'_htc'//zchar |
---|
539 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
540 | sxyc0(:,:,jl) = z2d(:,:) |
---|
541 | znam = 'sxsal'//'_htc'//zchar |
---|
542 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
543 | sxsal(:,:,jl) = z2d(:,:) |
---|
544 | znam = 'sysal'//'_htc'//zchar |
---|
545 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
546 | sysal(:,:,jl) = z2d(:,:) |
---|
547 | znam = 'sxxsal'//'_htc'//zchar |
---|
548 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
549 | sxxsal(:,:,jl) = z2d(:,:) |
---|
550 | znam = 'syysal'//'_htc'//zchar |
---|
551 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
552 | syysal(:,:,jl) = z2d(:,:) |
---|
553 | znam = 'sxysal'//'_htc'//zchar |
---|
554 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
555 | sxysal(:,:,jl) = z2d(:,:) |
---|
556 | znam = 'sxage'//'_htc'//zchar |
---|
557 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
558 | sxage(:,:,jl) = z2d(:,:) |
---|
559 | znam = 'syage'//'_htc'//zchar |
---|
560 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
561 | syage(:,:,jl) = z2d(:,:) |
---|
562 | znam = 'sxxage'//'_htc'//zchar |
---|
563 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
564 | sxxage(:,:,jl) = z2d(:,:) |
---|
565 | znam = 'syyage'//'_htc'//zchar |
---|
566 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
567 | syyage(:,:,jl) = z2d(:,:) |
---|
568 | znam = 'sxyage'//'_htc'//zchar |
---|
569 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
570 | sxyage(:,:,jl)= z2d(:,:) |
---|
571 | END DO |
---|
572 | ! MV MP 2016 |
---|
573 | IF ( ln_limMP ) THEN |
---|
574 | DO jl = 1, jpl |
---|
575 | znam = 'sxap'//'_htc'//zchar |
---|
576 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
577 | sxap(:,:,jl) = z2d(:,:) |
---|
578 | znam = 'syap'//'_htc'//zchar |
---|
579 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
580 | syap(:,:,jl) = z2d(:,:) |
---|
581 | znam = 'sxxap'//'_htc'//zchar |
---|
582 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
583 | sxxap(:,:,jl) = z2d(:,:) |
---|
584 | znam = 'syyap'//'_htc'//zchar |
---|
585 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
586 | syyap(:,:,jl) = z2d(:,:) |
---|
587 | znam = 'sxyap'//'_htc'//zchar |
---|
588 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
589 | sxyap(:,:,jl) = z2d(:,:) |
---|
590 | |
---|
591 | znam = 'sxvp'//'_htc'//zchar |
---|
592 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
593 | sxvp(:,:,jl) = z2d(:,:) |
---|
594 | znam = 'syvp'//'_htc'//zchar |
---|
595 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
596 | syvp(:,:,jl) = z2d(:,:) |
---|
597 | znam = 'sxxvp'//'_htc'//zchar |
---|
598 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
599 | sxxvp(:,:,jl) = z2d(:,:) |
---|
600 | znam = 'syyvp'//'_htc'//zchar |
---|
601 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
602 | syyvp(:,:,jl) = z2d(:,:) |
---|
603 | znam = 'sxyvp'//'_htc'//zchar |
---|
604 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
605 | sxyvp(:,:,jl) = z2d(:,:) |
---|
606 | END DO |
---|
607 | ENDIF |
---|
608 | ! END MV MP 2016 |
---|
609 | |
---|
610 | CALL iom_get( numrir, jpdom_autoglo, 'sxopw ' , sxopw ) |
---|
611 | CALL iom_get( numrir, jpdom_autoglo, 'syopw ' , syopw ) |
---|
612 | CALL iom_get( numrir, jpdom_autoglo, 'sxxopw' , sxxopw ) |
---|
613 | CALL iom_get( numrir, jpdom_autoglo, 'syyopw' , syyopw ) |
---|
614 | CALL iom_get( numrir, jpdom_autoglo, 'sxyopw' , sxyopw ) |
---|
615 | |
---|
616 | DO jl = 1, jpl |
---|
617 | WRITE(zchar,'(I2.2)') jl |
---|
618 | DO jk = 1, nlay_i |
---|
619 | WRITE(zchar1,'(I2.2)') jk |
---|
620 | znam = 'sxe'//'_il'//zchar1//'_htc'//zchar |
---|
621 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
622 | sxe(:,:,jk,jl) = z2d(:,:) |
---|
623 | znam = 'sye'//'_il'//zchar1//'_htc'//zchar |
---|
624 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
625 | sye(:,:,jk,jl) = z2d(:,:) |
---|
626 | znam = 'sxxe'//'_il'//zchar1//'_htc'//zchar |
---|
627 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
628 | sxxe(:,:,jk,jl) = z2d(:,:) |
---|
629 | znam = 'syye'//'_il'//zchar1//'_htc'//zchar |
---|
630 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
631 | syye(:,:,jk,jl) = z2d(:,:) |
---|
632 | znam = 'sxye'//'_il'//zchar1//'_htc'//zchar |
---|
633 | CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) |
---|
634 | sxye(:,:,jk,jl) = z2d(:,:) |
---|
635 | END DO |
---|
636 | END DO |
---|
637 | ! |
---|
638 | END IF |
---|
639 | |
---|
640 | ! clem: I do not understand why the following IF is needed |
---|
641 | ! I suspect something inconsistent in the main code with option nn_icesal=1 |
---|
642 | IF( nn_icesal == 1 ) THEN |
---|
643 | DO jl = 1, jpl |
---|
644 | sm_i(:,:,jl) = rn_icesal |
---|
645 | DO jk = 1, nlay_i |
---|
646 | s_i(:,:,jk,jl) = rn_icesal |
---|
647 | END DO |
---|
648 | END DO |
---|
649 | ENDIF |
---|
650 | ! |
---|
651 | !CALL iom_close( numrir ) !clem: closed in sbcice_lim.F90 |
---|
652 | ! |
---|
653 | CALL wrk_dealloc( jpi, jpj, z2d ) |
---|
654 | ! |
---|
655 | END SUBROUTINE lim_rst_read |
---|
656 | |
---|
657 | #else |
---|
658 | !!---------------------------------------------------------------------- |
---|
659 | !! Default option : Empty module NO LIM sea-ice model |
---|
660 | !!---------------------------------------------------------------------- |
---|
661 | CONTAINS |
---|
662 | SUBROUTINE lim_rst_read ! Empty routine |
---|
663 | END SUBROUTINE lim_rst_read |
---|
664 | SUBROUTINE lim_rst_write ! Empty routine |
---|
665 | END SUBROUTINE lim_rst_write |
---|
666 | #endif |
---|
667 | |
---|
668 | !!====================================================================== |
---|
669 | END MODULE limrst |
---|