GCC Code Coverage Report


Directory: ./
File: phys/iostart.f90
Date: 2022-01-11 19:19:34
Exec Total Coverage
Lines: 120 177 67.8%
Branches: 99 208 47.6%

Line Branch Exec Source
1 MODULE iostart
2
3 PRIVATE
4 INTEGER,SAVE :: nid_start
5 INTEGER,SAVE :: nid_restart
6
7 INTEGER,SAVE :: idim1,idim2,idim3,idim4
8 INTEGER,PARAMETER :: length=100
9
10 INTERFACE get_field
11 MODULE PROCEDURE Get_field_r1,Get_field_r2,Get_field_r3
12 END INTERFACE get_field
13
14 INTERFACE get_var
15 MODULE PROCEDURE get_var_r0,Get_var_r1,Get_var_r2,Get_var_r3
16 END INTERFACE get_var
17
18 INTERFACE put_field
19 MODULE PROCEDURE put_field_r1,put_field_r2,put_field_r3
20 END INTERFACE put_field
21
22 INTERFACE put_var
23 MODULE PROCEDURE put_var_r0,put_var_r1,put_var_r2,put_var_r3
24 END INTERFACE put_var
25
26 PUBLIC get_field,get_var,put_field,put_var
27 PUBLIC Open_startphy,close_startphy,open_restartphy,close_restartphy, enddef_restartphy
28
29 CONTAINS
30
31 1 SUBROUTINE Open_startphy(filename)
32 USE netcdf
33 USE mod_phys_lmdz_para
34 IMPLICIT NONE
35 CHARACTER(LEN=*) :: filename
36 INTEGER :: ierr
37
38
2/4
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 1 times.
✗ Branch 3 not taken.
1 IF (is_mpi_root .AND. is_omp_root) THEN
39 1 ierr = NF90_OPEN (filename, NF90_NOWRITE,nid_start)
40
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr.NE.NF90_NOERR) THEN
41 write(6,*)' Pb d''ouverture du fichier '//filename
42 write(6,*)' ierr = ', ierr
43 CALL abort_physic("", "", 1)
44 ENDIF
45 ENDIF
46
47 1 END SUBROUTINE Open_startphy
48
49 1 SUBROUTINE Close_startphy
50 USE netcdf
51 USE mod_phys_lmdz_para
52 IMPLICIT NONE
53 INTEGER :: ierr
54
55
2/4
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 1 times.
✗ Branch 3 not taken.
1 IF (is_mpi_root .AND. is_omp_root) THEN
56 1 ierr = NF90_CLOSE (nid_start)
57 ENDIF
58
59 1 END SUBROUTINE close_startphy
60
61
62 FUNCTION Inquire_Field(Field_name)
63 USE netcdf
64 USE mod_phys_lmdz_para
65 IMPLICIT NONE
66 CHARACTER(LEN=*) :: Field_name
67 LOGICAL :: inquire_field
68 INTEGER :: varid
69 INTEGER :: ierr
70
71 IF (is_mpi_root .AND. is_omp_root) THEN
72 ierr=NF90_INQ_VARID(nid_start,Field_name,varid)
73 IF (ierr==NF90_NOERR) THEN
74 Inquire_field=.TRUE.
75 ELSE
76 Inquire_field=.FALSE.
77 ENDIF
78 ENDIF
79
80 CALL bcast(Inquire_field)
81
82 END FUNCTION Inquire_Field
83
84
85
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 7 times.
7 SUBROUTINE Get_Field_r1(field_name,field,found)
86 IMPLICIT NONE
87 CHARACTER(LEN=*),INTENT(IN) :: Field_name
88 REAL,INTENT(INOUT) :: Field(:)
89 LOGICAL,INTENT(OUT),OPTIONAL :: found
90
91
1/2
✗ Branch 2 not taken.
✓ Branch 3 taken 7 times.
7 CALL Get_field_rgen(field_name,field,1,found)
92
93 7 END SUBROUTINE Get_Field_r1
94
95
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 344 times.
344 SUBROUTINE Get_Field_r2(field_name,field,found)
96 IMPLICIT NONE
97 CHARACTER(LEN=*),INTENT(IN) :: Field_name
98 REAL,INTENT(INOUT) :: Field(:,:)
99 LOGICAL,INTENT(OUT),OPTIONAL :: found
100
101
1/2
✗ Branch 2 not taken.
✓ Branch 3 taken 344 times.
344 CALL Get_field_rgen(field_name,field,size(field,2),found)
102
103
104 344 END SUBROUTINE Get_Field_r2
105
106 SUBROUTINE Get_Field_r3(field_name,field,found)
107 IMPLICIT NONE
108 CHARACTER(LEN=*),INTENT(IN) :: Field_name
109 REAL,INTENT(INOUT) :: Field(:,:,:)
110 LOGICAL,INTENT(OUT),OPTIONAL :: found
111
112 CALL Get_field_rgen(field_name,field,size(field,2)*size(field,3),found)
113
114 END SUBROUTINE Get_Field_r3
115
116 351 SUBROUTINE Get_field_rgen(field_name,field,field_size,found)
117 USE netcdf
118 USE dimphy
119 USE geometry_mod
120 USE mod_grid_phy_lmdz
121 USE mod_phys_lmdz_para
122 IMPLICIT NONE
123 CHARACTER(LEN=*) :: Field_name
124 INTEGER :: field_size
125 REAL :: field(klon,field_size)
126 LOGICAL,OPTIONAL :: found
127
128 351 REAL,ALLOCATABLE :: field_glo(:,:)
129 REAL,ALLOCATABLE :: field_glo_tmp(:,:)
130 351 INTEGER,ALLOCATABLE :: ind_cell_glo_glo(:)
131 LOGICAL :: tmp_found
132 INTEGER :: varid
133 INTEGER :: ierr,i
134
135
1/2
✓ Branch 0 taken 351 times.
✗ Branch 1 not taken.
351 IF (is_master) THEN
136
2/4
✓ Branch 0 taken 351 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 351 times.
351 ALLOCATE(ind_cell_glo_glo(klon_glo))
137
4/8
✓ Branch 0 taken 351 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 351 times.
✗ Branch 3 not taken.
✗ Branch 4 not taken.
✓ Branch 5 taken 351 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 351 times.
702 ALLOCATE(field_glo(klon_glo,field_size))
138
3/6
✓ Branch 0 taken 351 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 351 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 351 times.
702 ALLOCATE(field_glo_tmp(klon_glo,field_size))
139 ELSE
140 ALLOCATE(ind_cell_glo_glo(0))
141 ALLOCATE(field_glo(0,0))
142 ENDIF
143
144 351 CALL gather(ind_cell_glo,ind_cell_glo_glo)
145
146
1/2
✓ Branch 0 taken 351 times.
✗ Branch 1 not taken.
351 IF (is_master) THEN
147
148 351 ierr=NF90_INQ_VARID(nid_start,Field_name,varid)
149
150
2/2
✓ Branch 0 taken 322 times.
✓ Branch 1 taken 29 times.
351 IF (ierr==NF90_NOERR) THEN
151 322 CALL body(field_glo_tmp)
152 322 tmp_found=.TRUE.
153 ELSE
154 29 tmp_found=.FALSE.
155 ENDIF
156
157 ENDIF
158
159 351 CALL bcast(tmp_found)
160
161
2/2
✓ Branch 0 taken 322 times.
✓ Branch 1 taken 29 times.
351 IF (tmp_found) THEN
162
1/2
✓ Branch 0 taken 322 times.
✗ Branch 1 not taken.
322 IF (is_master) THEN
163
2/2
✓ Branch 0 taken 320068 times.
✓ Branch 1 taken 322 times.
320390 DO i=1,klon_glo
164
2/2
✓ Branch 0 taken 1159998 times.
✓ Branch 1 taken 320068 times.
1480388 field_glo(i,:)=field_glo_tmp(ind_cell_glo_glo(i),:)
165 ENDDO
166 ENDIF
167 322 CALL scatter(field_glo,field)
168 ENDIF
169
170
5/8
✓ Branch 0 taken 349 times.
✓ Branch 1 taken 2 times.
✓ Branch 2 taken 351 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 351 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 351 times.
✗ Branch 7 not taken.
702 IF (PRESENT(found)) THEN
171 349 found=tmp_found
172 ELSE
173
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 2 times.
2 IF (.NOT. tmp_found) THEN
174 PRINT*, 'phyetat0: Le champ <'//field_name//'> est absent'
175 call abort_physic("", "", 1)
176 ENDIF
177 ENDIF
178
179
180 CONTAINS
181
182 322 SUBROUTINE body(field_glo)
183 REAL :: field_glo(klon_glo*field_size)
184 322 ierr=NF90_GET_VAR(nid_start,varid,field_glo)
185
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 322 times.
322 IF (ierr/=NF90_NOERR) THEN
186 ! La variable exist dans le fichier mais la lecture a echouee.
187 PRINT*, 'phyetat0: Lecture echouee pour <'//field_name//'>'
188
189 IF (field_name=='CLWCON' .OR. field_name=='RNEBCON' .OR. field_name=='RATQS') THEN
190 ! Essaye de lire le variable sur surface uniqument, comme fait avant
191 field_glo(:)=0.
192 ierr=NF90_GET_VAR(nid_start,varid,field_glo(1:klon_glo))
193 IF (ierr/=NF90_NOERR) THEN
194 PRINT*, 'phyetat0: Lecture echouee aussi en 2D pour <'//field_name//'>'
195 call abort_physic("", "", 1)
196 ELSE
197 PRINT*, 'phyetat0: La variable <'//field_name//'> lu sur surface seulement'!, selon ancien format, le reste mis a zero'
198 END IF
199 ELSE
200 call abort_physic("", "", 1)
201 ENDIF
202 ENDIF
203
204 322 END SUBROUTINE body
205
206 END SUBROUTINE Get_field_rgen
207
208
209 SUBROUTINE get_var_r0(var_name,var,found)
210 IMPLICIT NONE
211 CHARACTER(LEN=*),INTENT(IN) :: var_name
212 REAL,INTENT(INOUT) :: var
213 LOGICAL,OPTIONAL,INTENT(OUT) :: found
214
215 REAL :: varout(1)
216
217 CALL Get_var_rgen(var_name,varout,size(varout),found)
218 var=varout(1)
219
220 END SUBROUTINE get_var_r0
221
222
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 SUBROUTINE get_var_r1(var_name,var,found)
223 IMPLICIT NONE
224 CHARACTER(LEN=*),INTENT(IN) :: var_name
225 REAL,INTENT(INOUT) :: var(:)
226 LOGICAL,OPTIONAL,INTENT(OUT) :: found
227
228
1/2
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
1 CALL Get_var_rgen(var_name,var,size(var),found)
229
230 1 END SUBROUTINE get_var_r1
231
232 SUBROUTINE get_var_r2(var_name,var,found)
233 IMPLICIT NONE
234 CHARACTER(LEN=*),INTENT(IN) :: var_name
235 REAL,INTENT(OUT) :: var(:,:)
236 LOGICAL,OPTIONAL,INTENT(OUT) :: found
237
238 CALL Get_var_rgen(var_name,var,size(var),found)
239
240 END SUBROUTINE get_var_r2
241
242 SUBROUTINE get_var_r3(var_name,var,found)
243 IMPLICIT NONE
244 CHARACTER(LEN=*),INTENT(IN) :: var_name
245 REAL,INTENT(INOUT) :: var(:,:,:)
246 LOGICAL,OPTIONAL,INTENT(OUT) :: found
247
248 CALL Get_var_rgen(var_name,var,size(var),found)
249
250 END SUBROUTINE get_var_r3
251
252 1 SUBROUTINE Get_var_rgen(var_name,var,var_size,found)
253 USE netcdf
254 USE dimphy
255 USE mod_grid_phy_lmdz
256 USE mod_phys_lmdz_para
257 IMPLICIT NONE
258 CHARACTER(LEN=*) :: var_name
259 INTEGER :: var_size
260 REAL :: var(var_size)
261 LOGICAL,OPTIONAL :: found
262
263 LOGICAL :: tmp_found
264 INTEGER :: varid
265 INTEGER :: ierr
266
267
2/4
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 1 times.
✗ Branch 3 not taken.
1 IF (is_mpi_root .AND. is_omp_root) THEN
268
269 1 ierr=NF90_INQ_VARID(nid_start,var_name,varid)
270
271
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ierr==NF90_NOERR) THEN
272 1 ierr=NF90_GET_VAR(nid_start,varid,var)
273
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr/=NF90_NOERR) THEN
274 PRINT*, 'phyetat0: Lecture echouee pour <'//var_name//'>'
275 call abort_physic("", "", 1)
276 ENDIF
277 1 tmp_found=.TRUE.
278 ELSE
279 tmp_found=.FALSE.
280 ENDIF
281
282 ENDIF
283
284 1 CALL bcast(tmp_found)
285
286
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (tmp_found) THEN
287 1 CALL bcast(var)
288 ENDIF
289
290
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (PRESENT(found)) THEN
291 found=tmp_found
292 ELSE
293
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (.NOT. tmp_found) THEN
294 PRINT*, 'phyetat0: La variable champ <'//var_name//'> est absente'
295 call abort_physic("", "", 1)
296 ENDIF
297 ENDIF
298
299 1 END SUBROUTINE Get_var_rgen
300
301
302 1 SUBROUTINE open_restartphy(filename)
303 USE netcdf
304 USE mod_phys_lmdz_para, ONLY: is_master
305 USE mod_grid_phy_lmdz, ONLY: klon_glo
306 USE dimphy, ONLY: klev, klevp1
307 USE print_control_mod, ONLY: lunout
308 IMPLICIT NONE
309 CHARACTER(LEN=*),INTENT(IN) :: filename
310 INTEGER :: ierr
311
312
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (is_master) THEN
313 ierr = NF90_CREATE(filename, IOR(NF90_CLOBBER,NF90_64BIT_OFFSET), &
314 1 nid_restart)
315
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr/=NF90_NOERR) THEN
316 write(lunout,*)'open_restartphy: problem creating file '//trim(filename)
317 write(lunout,*)trim(nf90_strerror(ierr))
318 CALL abort_physic("open_restartphy", trim(nf90_strerror(ierr)), 1)
319 ENDIF
320
321 1 ierr = NF90_PUT_ATT (nid_restart, NF90_GLOBAL, "title","Fichier redemmarage physique")
322
323 1 ierr = NF90_DEF_DIM (nid_restart, "index", length, idim1)
324 1 ierr = NF90_DEF_DIM (nid_restart, "points_physiques", klon_glo, idim2)
325 1 ierr = NF90_DEF_DIM (nid_restart, "horizon_vertical", klon_glo*klev, idim3)
326 1 ierr = NF90_DEF_DIM (nid_restart, "horizon_klevp1", klon_glo*klevp1, idim4)
327
328 ! ierr = NF90_ENDDEF(nid_restart)
329 ENDIF
330
331 1 END SUBROUTINE open_restartphy
332
333 1 SUBROUTINE enddef_restartphy
334 USE netcdf
335 USE mod_phys_lmdz_para
336 IMPLICIT NONE
337 INTEGER :: ierr
338
339
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (is_master) ierr = NF90_ENDDEF(nid_restart)
340
341 1 END SUBROUTINE enddef_restartphy
342
343 1 SUBROUTINE close_restartphy
344 USE netcdf
345 USE mod_phys_lmdz_para
346 IMPLICIT NONE
347 INTEGER :: ierr
348
349
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (is_master) ierr = NF90_CLOSE (nid_restart)
350
351 1 END SUBROUTINE close_restartphy
352
353
354
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 364 times.
364 SUBROUTINE put_field_r1(pass, field_name,title,field)
355 IMPLICIT NONE
356 INTEGER, INTENT(IN) :: pass
357 CHARACTER(LEN=*),INTENT(IN) :: field_name
358 CHARACTER(LEN=*),INTENT(IN) :: title
359 REAL,INTENT(IN) :: field(:)
360
1/2
✗ Branch 2 not taken.
✓ Branch 3 taken 364 times.
364 CALL put_field_rgen(pass, field_name,title,field,1)
361
362 364 END SUBROUTINE put_field_r1
363
364
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 60 times.
60 SUBROUTINE put_field_r2(pass, field_name,title,field)
365 IMPLICIT NONE
366 INTEGER, INTENT(IN) :: pass
367 CHARACTER(LEN=*),INTENT(IN) :: field_name
368 CHARACTER(LEN=*),INTENT(IN) :: title
369 REAL,INTENT(IN) :: field(:,:)
370
371
1/2
✗ Branch 2 not taken.
✓ Branch 3 taken 60 times.
60 CALL put_field_rgen(pass, field_name,title,field,size(field,2))
372
373 60 END SUBROUTINE put_field_r2
374
375 SUBROUTINE put_field_r3(pass, field_name,title,field)
376 IMPLICIT NONE
377 INTEGER, INTENT(IN) :: pass
378 CHARACTER(LEN=*),INTENT(IN) :: field_name
379 CHARACTER(LEN=*),INTENT(IN) :: title
380 REAL,INTENT(IN) :: field(:,:,:)
381
382 CALL put_field_rgen(pass, field_name,title,field,size(field,2)*size(field,3))
383
384 END SUBROUTINE put_field_r3
385
386 424 SUBROUTINE put_field_rgen(pass, field_name,title,field,field_size)
387 USE netcdf
388 USE dimphy
389 USE geometry_mod
390 USE mod_grid_phy_lmdz
391 USE mod_phys_lmdz_para
392 IMPLICIT NONE
393 INTEGER, INTENT(IN) :: pass
394 CHARACTER(LEN=*),INTENT(IN) :: field_name
395 CHARACTER(LEN=*),INTENT(IN) :: title
396 INTEGER,INTENT(IN) :: field_size
397 REAL,INTENT(IN) :: field(klon,field_size)
398
399 ! REAL :: field_glo(klon_glo,field_size)
400 ! REAL :: field_glo_tmp(klon_glo,field_size)
401 424 REAL ,ALLOCATABLE :: field_glo(:,:)
402 424 REAL ,ALLOCATABLE :: field_glo_tmp(:,:)
403 424 INTEGER,ALLOCATABLE :: ind_cell_glo_glo(:)
404 ! INTEGER :: ind_cell_glo_glo(klon_glo)
405 INTEGER :: ierr,i
406 INTEGER :: nvarid
407 INTEGER :: idim
408
409 ! first pass : definition
410
2/2
✓ Branch 0 taken 212 times.
✓ Branch 1 taken 212 times.
424 IF (pass==1) THEN
411
412
1/2
✓ Branch 0 taken 212 times.
✗ Branch 1 not taken.
212 IF (is_master) THEN
413
414
2/2
✓ Branch 0 taken 182 times.
✓ Branch 1 taken 30 times.
212 IF (field_size==1) THEN
415 182 idim=idim2
416
2/2
✓ Branch 0 taken 19 times.
✓ Branch 1 taken 11 times.
30 ELSE IF (field_size==klev) THEN
417 19 idim=idim3
418
1/2
✓ Branch 0 taken 11 times.
✗ Branch 1 not taken.
11 ELSE IF (field_size==klevp1) THEN
419 11 idim=idim4
420 ELSE
421 PRINT *, "erreur phyredem : probleme de dimension"
422 CALL abort_physic("", "", 1)
423 ENDIF
424
425 ! ierr = NF90_REDEF (nid_restart)
426
2/2
✓ Branch 0 taken 212 times.
✓ Branch 1 taken 212 times.
424 ierr = NF90_DEF_VAR (nid_restart, field_name, NF90_DOUBLE,(/ idim /),nvarid)
427
2/2
✓ Branch 0 taken 210 times.
✓ Branch 1 taken 2 times.
212 IF (LEN_TRIM(title) > 0) ierr = NF90_PUT_ATT (nid_restart,nvarid,"title", title)
428 ! ierr = NF90_ENDDEF(nid_restart)
429 ENDIF
430
431 ! second pass : write
432
1/2
✓ Branch 0 taken 212 times.
✗ Branch 1 not taken.
212 ELSE IF (pass==2) THEN
433
434
1/2
✓ Branch 0 taken 212 times.
✗ Branch 1 not taken.
212 IF (is_master) THEN
435
2/4
✓ Branch 0 taken 212 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 212 times.
212 ALLOCATE(ind_cell_glo_glo(klon_glo))
436
4/8
✓ Branch 0 taken 212 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 212 times.
✗ Branch 3 not taken.
✗ Branch 4 not taken.
✓ Branch 5 taken 212 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 212 times.
424 ALLOCATE(field_glo(klon_glo,field_size))
437
3/6
✓ Branch 0 taken 212 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 212 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 212 times.
424 ALLOCATE(field_glo_tmp(klon_glo,field_size))
438 ELSE
439 ALLOCATE(ind_cell_glo_glo(0))
440 ALLOCATE(field_glo_tmp(0,0))
441 ENDIF
442
443 212 CALL gather(ind_cell_glo,ind_cell_glo_glo)
444
445 212 CALL gather(field,field_glo_tmp)
446
447
1/2
✓ Branch 0 taken 212 times.
✗ Branch 1 not taken.
212 IF (is_master) THEN
448
449
2/2
✓ Branch 0 taken 210728 times.
✓ Branch 1 taken 212 times.
210940 DO i=1,klon_glo
450
2/2
✓ Branch 0 taken 1354822 times.
✓ Branch 1 taken 210728 times.
1565762 field_glo(ind_cell_glo_glo(i),:)=field_glo_tmp(i,:)
451 ENDDO
452
453 212 ierr = NF90_INQ_VARID(nid_restart, field_name, nvarid)
454
2/2
✓ Branch 0 taken 212 times.
✓ Branch 1 taken 212 times.
424 ierr = NF90_PUT_VAR(nid_restart,nvarid,RESHAPE(field_glo,(/klon_glo*field_size/)))
455 ENDIF
456 ENDIF
457
458
6/6
✓ Branch 0 taken 212 times.
✓ Branch 1 taken 212 times.
✓ Branch 2 taken 212 times.
✓ Branch 3 taken 212 times.
✓ Branch 4 taken 212 times.
✓ Branch 5 taken 212 times.
424 END SUBROUTINE put_field_rgen
459
460
461 SUBROUTINE put_var_r0(pass, var_name,title,var)
462 IMPLICIT NONE
463 INTEGER, INTENT(IN) :: pass
464 CHARACTER(LEN=*),INTENT(IN) :: var_name
465 CHARACTER(LEN=*),INTENT(IN) :: title
466 REAL,INTENT(IN) :: var
467 REAL :: varin(1)
468
469 varin(1)=var
470
471 CALL put_var_rgen(pass, var_name,title,varin,size(varin))
472
473 END SUBROUTINE put_var_r0
474
475
476
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 2 times.
2 SUBROUTINE put_var_r1(pass, var_name,title,var)
477 IMPLICIT NONE
478 INTEGER, INTENT(IN) :: pass
479 CHARACTER(LEN=*),INTENT(IN) :: var_name
480 CHARACTER(LEN=*),INTENT(IN) :: title
481 REAL,INTENT(IN) :: var(:)
482
483
1/2
✗ Branch 2 not taken.
✓ Branch 3 taken 2 times.
2 CALL put_var_rgen(pass, var_name,title,var,size(var))
484
485 2 END SUBROUTINE put_var_r1
486
487 SUBROUTINE put_var_r2(pass, var_name,title,var)
488 IMPLICIT NONE
489 INTEGER, INTENT(IN) :: pass
490 CHARACTER(LEN=*),INTENT(IN) :: var_name
491 CHARACTER(LEN=*),INTENT(IN) :: title
492 REAL,INTENT(IN) :: var(:,:)
493
494 CALL put_var_rgen(pass, var_name,title,var,size(var))
495
496 END SUBROUTINE put_var_r2
497
498 SUBROUTINE put_var_r3(pass, var_name,title,var)
499 IMPLICIT NONE
500 INTEGER, INTENT(IN) :: pass
501 CHARACTER(LEN=*),INTENT(IN) :: var_name
502 CHARACTER(LEN=*),INTENT(IN) :: title
503 REAL,INTENT(IN) :: var(:,:,:)
504
505 CALL put_var_rgen(pass, var_name,title,var,size(var))
506
507 END SUBROUTINE put_var_r3
508
509 2 SUBROUTINE put_var_rgen(pass, var_name,title,var,var_size)
510 USE netcdf
511 USE dimphy
512 USE mod_phys_lmdz_para
513 IMPLICIT NONE
514 INTEGER, INTENT(IN) :: pass
515 CHARACTER(LEN=*),INTENT(IN) :: var_name
516 CHARACTER(LEN=*),INTENT(IN) :: title
517 INTEGER,INTENT(IN) :: var_size
518 REAL,INTENT(IN) :: var(var_size)
519
520 INTEGER :: ierr
521 INTEGER :: nvarid
522
523
1/2
✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
2 IF (is_master) THEN
524
525
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 2 times.
2 IF (var_size/=length) THEN
526 PRINT *, "erreur phyredem : probleme de dimension"
527 call abort_physic("", "", 1)
528 ENDIF
529
530 ! first pass : definition
531
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
2 IF (pass==1) THEN
532
533 ! ierr = NF90_REDEF (nid_restart)
534
535
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
2 ierr = NF90_DEF_VAR (nid_restart, var_name, NF90_DOUBLE,(/ idim1 /),nvarid)
536
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (LEN_TRIM(title)>0) ierr = NF90_PUT_ATT (nid_restart,nvarid,"title", title)
537 ! ierr = NF90_ENDDEF(nid_restart)
538
539 ! second pass : write
540
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 ELSE IF (pass==2) THEN
541 1 ierr = NF90_INQ_VARID(nid_restart, var_name, nvarid)
542 1 ierr = NF90_PUT_VAR(nid_restart,nvarid,var)
543 ENDIF
544 ENDIF
545
546 2 END SUBROUTINE put_var_rgen
547
548 END MODULE iostart
549