source: trunk/SOURCES/Netcdf-routines/io_netcdf_GRISLI.f90 @ 22

Last change on this file since 22 was 10, checked in by dumas, 9 years ago

Modification chemin dirnameinp et dirsource pour lancer GRISLI depuis le répertoire RESULTATS/ma_simule. Lecture du fichier param dans le repertoire de la simulation avec nom standard type hemin40_param_list.dat. Pour le moment seule la version Hemin-40 est utilisable.

File size: 63.9 KB
Line 
1!> \file io_netcdf_GRISLI.f90
2!! NetCDF Fortran 90 read/write interface
3!<
4
5!> \namespace io_netcdf_grisli
6!! NetCDF Fortran 90 read/write interface
7!! @note Use input/output functions provided by unidata                                                                   
8!!                                                                               
9!! @note Glossary of variables
10!! @note varname   =  name of variable to trait
11!! @note file,file_in,file_out      =  netcdf file name
12!! @note tabvar    =  array containing values of the required variable
13!! @note typevar   =  type of the variable to trait
14!! @note dimIDs    =  array containing dimensions of variables 
15!! @note dim'i'    =  dimensions of variables
16!! @note varid,varid_in,varid_out = variables identificator
17!! @note ncid,ncid_in,ncid_out = netcdf file identificator
18!! @note time      = time corresponding to the values to read/write 
19!! @note level     = level corresponding to the values to read/write 
20!! @note dimval    = value of the required dimension
21!! @note dimname   = name of dimension to retrieve
22!!
23!! http://my.unidata.ucar.edu/content/software/netcdf/docs/netcdf-f90/index.html 
24!!                                                                               
25!<
26
27module io_netcdf_grisli
28  !     
29  use netcdf     
30  use runparam,only:dirsource 
31  !> \interface Read_Ncdf_var
32  !! Interfaces of functions and subroutines to read netcdf variables
33  !!\author ...
34  !!\date 2010
35  !!
36  !<
37  integer :: ncdf_type = 0                    ! pour changer eventuellement de netcdf
38
39  interface Read_Ncdf_var
40     module procedure Read_Ncdf_var1d_Real,   &  ! Reading a 1d real variable
41          Read_Ncdf_var2d_Real,               &  ! Reading a 2d real variable
42          Read_Ncdf_var2d_Real_bis,           &  ! Reading a 2d real var with selection of data
43          Read_Ncdf_var3d_Real,               &  ! Reading a 3d real variable
44          Read_Ncdf_var4d_Real,               &  ! Reading a 4d real variable
45          Read_Ncdf_var1d_Int,                &  ! Reading a 1d integer variable
46          Read_Ncdf_var2d_Int,                &  ! Reading a 2d integer variable
47          Read_Ncdf_var3d_Int,                &  ! Reading a 3d integer variable
48          Read_Ncdf_var4d_Int,                &  ! Reading a 4d integer variable
49          Read_Ncdf_var3d_Real_t,             &  ! Reading a 2d variable depending on time
50          Read_Ncdf_var4d_Real_t,             &  ! Reading a 3d variable depending on time
51          Read_Ncdf_var4d_Real_nt                ! Reading a 2d variable  at a time t and a level n
52  end interface
53  !************************************************************************************************************
54
55  !> \interface Write_Ncdf_var
56  !! Interfaces of functions and  subroutine to write netcdf variables
57  !!\author ...
58  !!\date 2010
59  !!
60  !<
61  interface Write_Ncdf_var
62     module procedure Write_Ncdf_var1d_Real,  &  ! Writing a 1d real (simple/double) variable
63          Write_Ncdf_var2d_Real,              &  ! Writing a 2d real (simple/double) variable
64          Write_Ncdf_var3d_Real,              &  ! Writing a 3d real (simple/double) variable
65          Write_Ncdf_var4d_Real,              &  ! Writing a 4d real (simple/double) variable
66          Write_Ncdf_var1d_Int,               &  ! Writing a 1d integer variable
67          Write_Ncdf_var2d_Int,               &  ! Writing a 2d integer variable
68          Write_Ncdf_var3d_Int,               &  ! Writing a 3d integer variable
69          Write_Ncdf_var4d_Int,               &  ! Writing a 4d integer variable
70          Write_Ncdf_var1d_Int_t,             &  ! Writing a 1d integer variable depending on time
71          Write_Ncdf_var1d_Realbis_t,         &  ! Writing a 1d real (simple/double) variable depending on time
72          Write_Ncdf_var1d_Real_t,            &  ! Writing a 1d real (simple/double) variable depending on time
73          Write_Ncdf_var2d_Int_t,             &  ! Writing a 2d integer variable depending on time     
74          Write_Ncdf_var2d_Real_t,            &  ! Writing a 2d real (simple/double) variable depending on time
75          Write_Ncdf_var3d_Real_t,            &  ! Writing a 3d real (simple/double) variable depending on time
76          Write_Ncdf_var4d_Real_t,            &  ! Writing a 4d real (simple/double) variable depending on time
77          Write_Ncdf_var4d_Real_nt               ! Writing a 2d variable  at a time t and a level n                                                     
78
79  end interface
80  !*************************************************************************************************************
81
82  !> \interface Copy_Ncdf_att
83  !! Interfaces of functions and subroutines to copy netcdf variables
84  !!\author ...
85  !!\date 2010
86  !!
87  !<
88  interface Copy_Ncdf_att
89     module procedure Copy_Ncdf_att_latlon,Copy_Ncdf_att_var
90  end interface
91
92contains
93
94! subroutine pour lire netcdf_type
95  subroutine lect_netcdf_type
96
97    implicit none
98    ! open(22,file='../SOURCES/Fichiers-parametres/netcdf_type.dat')
99    open(22,file=trim(dirsource)//'/Fichiers-parametres/netcdf_type.dat')
100    read(22,'(i3)') ncdf_type
101    close(22)
102    write(6,*) ' lecture de ncdft_type',ncdf_type 
103    return
104  end subroutine lect_netcdf_type
105
106  !> Subroutine to retrieve values of a given 1D real variable
107  !! @param[in]  varname : name of variable to retrieve
108  !! @param[in]  file    : netcdf file name                               
109  !! @param[out] tabvar  : array containing values of the required variable
110  !! @return tabvar
111
112  subroutine Read_Ncdf_var1d_Real(varname,file,tabvar)
113    !     
114    implicit none
115    !       
116    Character(*),intent(in) :: varname,file
117    Real*8, dimension(:), pointer :: tabvar
118    !
119    !local variables
120    !
121    Integer, dimension(1) :: dimID   
122    Integer :: dim1                 
123    Integer :: status,ncid           
124    Integer :: varid             
125    !
126    status = nf90_open(file,NF90_NOWRITE,ncid)
127         
128    if (status/=nf90_noerr) then   
129       write(*,*)"unable to open netcdf file : ",file
130       stop
131    endif
132    !     
133    status = nf90_inq_varid(ncid,varname,varid)
134
135    if (status/=nf90_noerr) then   
136       write(*,*)"pb de nom de variable :", varname, file
137       stop
138    endif
139
140!  recupere l'identite des dimensions de la variable
141    status = nf90_inquire_variable(ncid,varid,dimids=dimID)
142
143!  recupere la taille de la  dimension de la variable
144    status = nf90_inquire_dimension(ncid,dimID(1),len=dim1)
145    !               
146    if(.not. associated(tabvar)) then
147       Allocate(tabvar(dim1)) 
148    else
149       if( any(shape(tabvar)/=(/dim1/)) ) then           
150          deallocate(tabvar)   
151          Allocate(tabvar(dim1))     
152       endif
153    endif
154           
155!  lit la variable
156    status=nf90_get_var(ncid,varid,tabvar)     
157     
158! referme le fichier
159    status = nf90_close(ncid)
160    !
161  end subroutine Read_Ncdf_var1d_Real
162
163
164
165  !> Subroutine to retrieve values of a given 2D real variable
166  !! @param[in]  varname : name of variable to retrieve
167  !! @param[in]  file    : netcdf file name                               
168  !! @param[out] tabvar  : array containing values of the required variable
169  !! @return tabvar
170
171  subroutine Read_Ncdf_var2d_Real(varname,file,tabvar)
172    !     
173    implicit none
174    !       
175    Character(*),intent(in) :: varname,file
176    Real*8, dimension(:,:), pointer :: tabvar
177    !local variables
178    Integer, dimension(10) :: dimIDS
179    Integer :: dim1,dim2
180    Integer :: status,ncid
181    Integer :: varid             
182    !
183    status = nf90_open(file,NF90_NOWRITE,ncid)
184    !     
185    if (status/=nf90_noerr) then   
186       write(*,*)"unable to open netcdf file : ",file
187       stop
188    endif
189    !     
190    status = nf90_inq_varid(ncid,varname,varid)
191    status=nf90_inquire_variable(ncid,varid,dimids=dimIDS)
192    status=nf90_inquire_dimension(ncid,dimIDS(1),len=dim1)
193    status=nf90_inquire_dimension(ncid,dimIDS(2),len=dim2)
194    !               
195    if(.not. associated(tabvar)) then
196       Allocate(tabvar(dim1,dim2)) 
197    else
198       if( any(shape(tabvar)/=(/dim1,dim2/)) ) then           
199          tabvar => null()
200          Allocate(tabvar(dim1,dim2))     
201       endif
202    endif
203    !       
204    status=nf90_get_var(ncid,varid,tabvar)     
205    !     
206    status = nf90_close(ncid)
207    !     
208  end subroutine Read_Ncdf_var2d_Real
209
210
211
212  !> Subroutine to retrieve values of a given 2D real variable
213  !! @param[in]  varname : name of variable to retrieve
214  !! @param[in]  file    : netcdf file name                               
215  !! @param[out] tabvar  : array containing values of the required variable
216  !! @param[in]  strt    : array of integers specifiying the index in the 
217  !!              variable from which the first (or only) of the 
218  !!              data values will be read. The elements of start
219  !!              correspond, in order, to the variable's dimensions                                     
220  !! @param[in]  cnt     : A vector of integers specifying the number of   
221  !!               indices selected along each dimension.         
222  !! @return tabvar
223
224
225  subroutine Read_Ncdf_var2d_Real_bis(varname,file,tabvar,strt,cnt)
226    !     
227    implicit none
228    !       
229    Character(*),intent(in) :: varname,file
230    Real*8, dimension(:,:), pointer :: tabvar
231    !local variables
232    Integer, dimension(10) :: dimIDS
233    Integer, dimension(2) :: strt,cnt
234    Integer :: dim1,dim2
235    Integer :: status,ncid
236    Integer :: varid             
237    !
238    status = nf90_open(file,NF90_NOWRITE,ncid)
239    !     
240    if (status/=nf90_noerr) then   
241       write(*,*)"unable to open netcdf file : ",file
242       stop
243    endif
244    !     
245    dim1 = cnt(1) 
246    dim2 = cnt(2)
247    !     
248    status = nf90_inq_varid(ncid,varname,varid)
249    status=nf90_inquire_variable(ncid,varid,dimids=dimIDS)
250    !               
251    if(.not. associated(tabvar)) then
252       Allocate(tabvar(dim1,dim2)) 
253    else
254       if( any(shape(tabvar)/=(/dim1,dim2/)) ) then           
255          deallocate(tabvar)   
256          Allocate(tabvar(dim1,dim2))     
257       endif
258    endif
259    !       
260    status=nf90_get_var(ncid,varid,tabvar,start = strt,count = cnt)     
261    !     
262    status = nf90_close(ncid)
263    !     
264  end subroutine Read_Ncdf_var2d_Real_bis
265
266
267  !> Subroutine to retrieve values of a given 3D real variable
268  !! @param[in]  varname : name of variable to retrieve
269  !! @param[in]  file    : netcdf file name                               
270  !! @param[out] tabvar  : array containing values of the required variable
271  !! @return tabvar
272  subroutine Read_Ncdf_var3d_Real(varname,file,tabvar)
273    !     
274    implicit none
275    !       
276    Character(*),intent(in) :: varname,file
277    Real*8, dimension(:,:,:), pointer :: tabvar
278    !
279    !local variables
280    !
281    Integer, dimension(10) :: dimIDS
282    Integer :: dim1,dim2,dim3
283    Integer :: status,ncid
284    Integer :: varid             
285    !
286    status = nf90_open(file,NF90_NOWRITE,ncid)
287    !     
288    if (status/=nf90_noerr) then   
289       write(*,*)"unable to open netcdf file : ",file
290       stop
291    endif
292    !     
293    status = nf90_inq_varid(ncid,varname,varid)
294    status=nf90_inquire_variable(ncid,varid,dimids=dimIDS)
295    status=nf90_inquire_dimension(ncid,dimIDS(1),len=dim1)
296    status=nf90_inquire_dimension(ncid,dimIDS(2),len=dim2) 
297    status=nf90_inquire_dimension(ncid,dimIDS(3),len=dim3)
298    !               
299    if(.not. associated(tabvar)) then
300       Allocate(tabvar(dim1,dim2,dim3)) 
301    else
302       if( any(shape(tabvar) /= (/dim1,dim2,dim3/)) ) then           
303          deallocate(tabvar)   
304          Allocate(tabvar(dim1,dim2,dim3))     
305       endif
306    endif
307    !     
308    status=nf90_get_var(ncid,varid,tabvar) 
309    if (status/=nf90_noerr) then   
310       write(*,*)"unable to retrieve netcdf variable : ",trim(varname)
311       stop
312    endif
313    !     
314    status = nf90_close(ncid)
315    !     
316  end subroutine Read_Ncdf_var3d_Real
317
318
319  !> Subroutine to retrieve values of a given 4D real variable
320  !! @param[in]  varname : name of variable to retrieve
321  !! @param[in]  file    : netcdf file name                               
322  !! @param[out] tabvar  : array containing values of the required variable
323  !! @return tabvar
324  subroutine Read_Ncdf_var4d_Real(varname,file,tabvar)
325    !     
326    implicit none
327    !       
328    Character(*),intent(in) :: varname,file
329    Real*8, dimension(:,:,:,:), pointer :: tabvar
330    !
331    !local variables
332    !
333    Integer, dimension(10) :: dimIDS
334    Integer :: dim1,dim2,dim3,dim4
335    Integer :: status,ncid
336    Integer :: varid             
337    !
338    status = nf90_open(file,NF90_NOWRITE,ncid)
339    !     
340    if (status/=nf90_noerr) then   
341       write(*,*)"unable to open netcdf file : ",file
342       stop
343    endif
344    !     
345    status = nf90_inq_varid(ncid,varname,varid)
346    status=nf90_inquire_variable(ncid,varid,dimids=dimIDS)
347    status=nf90_inquire_dimension(ncid,dimIDS(1),len=dim1)
348    status=nf90_inquire_dimension(ncid,dimIDS(2),len=dim2) 
349    status=nf90_inquire_dimension(ncid,dimIDS(3),len=dim3)   
350    status=nf90_inquire_dimension(ncid,dimIDS(4),len=dim4)       
351    !               
352    if(.not. associated(tabvar)) then
353       Allocate(tabvar(dim1,dim2,dim3,dim4)) 
354    else
355       if( any(shape(tabvar) /= (/dim1,dim2,dim3,dim4/)) ) then           
356          deallocate(tabvar)   
357          Allocate(tabvar(dim1,dim2,dim3,dim4))     
358       endif
359    endif
360   
361    status=nf90_get_var(ncid,varid,tabvar)     
362    !     
363    status = nf90_close(ncid)
364    !     
365  end subroutine Read_Ncdf_var4d_Real
366
367  !> Subroutine to retrieve values of a given 1D integer variable
368  !! @param[in]  varname : name of variable to retrieve
369  !! @param[in]  file    : netcdf file name                               
370  !! @param[out] tabvar  : array containing values of the required variable
371  !! @return tabvar
372  subroutine Read_Ncdf_var1d_Int(varname,file,tabvar)
373    !     
374    implicit none
375    !       
376    Character(*),intent(in) :: varname,file
377    Integer, dimension(:), pointer :: tabvar
378    !
379    !local variables
380    !
381    Integer,dimension(10) :: dimID
382    Integer :: dim1
383    Integer :: status,ncid
384    Integer :: varid             
385    !
386    status = nf90_open(file,NF90_NOWRITE,ncid)
387    !     
388    if (status/=nf90_noerr) then   
389       write(*,*)"unable to open netcdf file : ",file
390       stop
391    endif
392    !     
393    status = nf90_inq_varid(ncid,varname,varid)
394    status=nf90_inquire_variable(ncid,varid,dimids=dimID)
395    status=nf90_inquire_dimension(ncid,dimID(1),len=dim1)         
396    !               
397    if(.not. associated(tabvar)) then
398       Allocate(tabvar(dim1)) 
399    else
400       if( any(shape(tabvar) /= (/dim1/)) ) then           
401          deallocate(tabvar)   
402          Allocate(tabvar(dim1))     
403       endif
404    endif
405   
406    status=nf90_get_var(ncid,varid,tabvar)     
407    !     
408    status = nf90_close(ncid)
409    !     
410  end subroutine Read_Ncdf_var1d_Int
411
412
413  !> Subroutine to retrieve values of a given 2D integer variable
414  !! @param[in]  varname : name of variable to retrieve
415  !! @param[in]  file    : netcdf file name                               
416  !! @param[out] tabvar  : array containing values of the required variable
417  !! @return tabvar
418  subroutine Read_Ncdf_var2d_Int(varname,file,tabvar)
419    !     
420    implicit none
421    !       
422    Character(*),intent(in) :: varname,file
423    Integer, dimension(:,:), pointer :: tabvar
424    !local variables
425    Integer, dimension(10) :: dimIDS
426    Integer :: dim1,dim2
427    Integer :: status,ncid
428    Integer :: varid             
429    !
430    status = nf90_open(file,NF90_NOWRITE,ncid)
431    !     
432    if (status/=nf90_noerr) then   
433       write(*,*)"unable to open netcdf file : ",file
434       stop
435    endif
436    !     
437    status = nf90_inq_varid(ncid,varname,varid)
438    status=nf90_inquire_variable(ncid,varid,dimids=dimIDS)
439    status=nf90_inquire_dimension(ncid,dimIDS(1),len=dim1)
440    status=nf90_inquire_dimension(ncid,dimIDS(2),len=dim2)     
441    !               
442    if(.not. associated(tabvar)) then
443       Allocate(tabvar(dim1,dim2)) 
444    else
445       if( any(shape(tabvar) /= (/dim1,dim2/)) ) then           
446          deallocate(tabvar)   
447          Allocate(tabvar(dim1,dim2))     
448       endif
449    endif
450   
451    status=nf90_get_var(ncid,varid,tabvar)     
452    !     
453    status = nf90_close(ncid)
454    !     
455  end subroutine Read_Ncdf_var2d_Int
456
457  !> Subroutine to retrieve values of a given 3D integer variable
458  !! @param[in]  varname : name of variable to retrieve
459  !! @param[in]  file    : netcdf file name                               
460  !! @param[out] tabvar  : array containing values of the required variable
461  !! @return tabvar
462  subroutine Read_Ncdf_var3d_Int(varname,file,tabvar)
463    !     
464    implicit none
465    !       
466    Character(*),intent(in) :: varname,file
467    Integer, dimension(:,:,:), pointer :: tabvar
468    !
469    !local variables
470    !
471    Integer, dimension(10) :: dimIDS
472    Integer :: dim1,dim2,dim3
473    Integer :: status,ncid
474    Integer :: varid             
475    !
476    status = nf90_open(file,NF90_NOWRITE,ncid)
477    !     
478    if (status/=nf90_noerr) then   
479       write(*,*)"unable to open netcdf file : ",file
480       stop
481    endif
482    !     
483    status = nf90_inq_varid(ncid,varname,varid)
484    status=nf90_inquire_variable(ncid,varid,dimids=dimIDS)
485    status=nf90_inquire_dimension(ncid,dimIDS(1),len=dim1)
486    status=nf90_inquire_dimension(ncid,dimIDS(2),len=dim2) 
487    status=nf90_inquire_dimension(ncid,dimIDS(3),len=dim3)         
488    !               
489    if(.not. associated(tabvar)) then
490       Allocate(tabvar(dim1,dim2,dim3)) 
491    else
492       if( any(shape(tabvar) /= (/dim1,dim2,dim3/)) ) then           
493          deallocate(tabvar)   
494          Allocate(tabvar(dim1,dim2,dim3))     
495       endif
496    endif
497    !
498    status=nf90_get_var(ncid,varid,tabvar)     
499    !     
500    status = nf90_close(ncid)
501    !     
502  end subroutine Read_Ncdf_var3d_Int
503
504  !> Subroutine to retrieve values of a given 4D integer variable
505  !! @param[in]  varname : name of variable to retrieve
506  !! @param[in]  file    : netcdf file name                               
507  !! @param[out] tabvar  : array containing values of the required variable
508  !! @return tabvar
509
510  subroutine Read_Ncdf_var4d_Int(varname,file,tabvar)
511    !     
512    implicit none
513    !       
514    Character(*),intent(in) :: varname,file
515    Integer, dimension(:,:,:,:), pointer :: tabvar
516    !
517    !local variables
518    !
519    Integer, dimension(10) :: dimIDS
520    Integer :: dim1,dim2,dim3,dim4
521    Integer :: status,ncid
522    Integer :: varid             
523    !
524    status = nf90_open(file,NF90_NOWRITE,ncid)
525    !     
526    if (status/=nf90_noerr) then   
527       write(*,*)"unable to open netcdf file : ",file
528       stop
529    endif
530    !     
531    status = nf90_inq_varid(ncid,varname,varid)
532    status=nf90_inquire_variable(ncid,varid,dimids=dimIDS)
533    status=nf90_inquire_dimension(ncid,dimIDS(1),len=dim1)
534    status=nf90_inquire_dimension(ncid,dimIDS(2),len=dim2) 
535    status=nf90_inquire_dimension(ncid,dimIDS(3),len=dim3)   
536    status=nf90_inquire_dimension(ncid,dimIDS(4),len=dim4)       
537    !               
538    if(.not. associated(tabvar)) then
539       Allocate(tabvar(dim1,dim2,dim3,dim4)) 
540    else
541       if( any(shape(tabvar) /= (/dim1,dim2,dim3,dim4/)) ) then           
542          deallocate(tabvar)   
543          Allocate(tabvar(dim1,dim2,dim3,dim4))     
544       endif
545    endif
546   
547    status=nf90_get_var(ncid,varid,tabvar)     
548    !     
549    status = nf90_close(ncid)
550    !     
551  end subroutine Read_Ncdf_var4d_Int
552
553
554  !> Subroutine to retrieve values of a given 4D real variable
555  !! @param[in]  varname : name of variable to retrieve
556  !! @param[in]  file    : netcdf file name                               
557  !! @param[out] tabvar  : array containing values of the required variable
558  !! @param[in]  time    : time corresponding to the values to read
559  !! @param[in]  level   : level corresponding to the values to read
560  !! @return tabvar
561
562  subroutine Read_Ncdf_var4d_Real_nt(varname,file,tabvar,time,level)     
563    implicit none
564    !       
565    Character(*),intent(in) :: varname,file
566    Integer,intent(in) :: time,level
567    Real*8, dimension(:,:,:,:), pointer :: tabvar
568    !
569    !local variables
570    !
571    Integer, dimension(4) :: dimIDS
572    Integer :: dim1,dim2
573    Integer :: status,ncid
574    Integer :: varid             
575    !
576    status = nf90_open(file,NF90_NOWRITE,ncid)
577    !     
578    if (status/=nf90_noerr) then   
579       write(*,*)"unable to open netcdf file : ",file
580       stop
581    endif
582    !     
583    status = nf90_inq_varid(ncid,varname,varid)
584    !       
585    status=nf90_inquire_variable(ncid,varid,dimids=dimIDS)
586    status=nf90_inquire_dimension(ncid,dimIDS(1),len=dim1)
587    status=nf90_inquire_dimension(ncid,dimIDS(2),len=dim2)
588    !
589    if(.not. associated(tabvar)) then
590       Allocate(tabvar(dim1,dim2,1,1)) 
591    else
592       if( any(shape(tabvar) /= (/dim1,dim2,1,1/)) ) then           
593          deallocate(tabvar)   
594          Allocate(tabvar(dim1,dim2,1,1))     
595       endif
596    endif
597    !
598    status=nf90_get_var(ncid,varid,tabvar,start=(/1,1,level,time/))
599    !                                             
600    if (status/=nf90_noerr) then   
601       write(*,*)"unable to retrieve netcdf variable : ",trim(varname)
602       stop
603    endif
604    !     
605    status = nf90_close(ncid)
606    !     
607  end subroutine Read_Ncdf_var4d_Real_nt
608
609
610  !> Subroutine to retrieve values of a given 3D real variable withe time dependent
611  !! @param[in]  varname : name of variable to retrieve
612  !! @param[in]  file    : netcdf file name                               
613  !! @param[out] tabvar  : array containing values of the required variable
614  !! @param[in]  time    : time corresponding to the values to read
615  !! @return tabvar
616  subroutine Read_Ncdf_var4d_Real_t(varname,file,tabvar,time)   
617    implicit none
618    !       
619    Character(*),intent(in) :: varname,file
620    Integer,intent(in) :: time
621    Real*8, dimension(:,:,:,:), pointer :: tabvar
622    !
623    !local variables
624    !
625    Integer, dimension(4) :: dimIDS
626    Integer :: dim1,dim2,dim3
627    Integer :: status,ncid
628    Integer :: varid             
629    !
630    status = nf90_open(file,NF90_NOWRITE,ncid)
631    !     
632    if (status/=nf90_noerr) then   
633       write(*,*)"unable to open netcdf file : ",file
634       stop
635    endif
636    !     
637    status = nf90_inq_varid(ncid,varname,varid)
638    !       
639    status=nf90_inquire_variable(ncid,varid,dimids=dimIDS)
640    status=nf90_inquire_dimension(ncid,dimIDS(1),len=dim1)
641    status=nf90_inquire_dimension(ncid,dimIDS(2),len=dim2)
642    status=nf90_inquire_dimension(ncid,dimIDS(3),len=dim3)
643    !
644    if(.not. associated(tabvar)) Allocate(tabvar(dim1,dim2,dim3,1)) 
645    status=nf90_get_var(ncid,varid,tabvar,start=(/1,1,1,time/))
646
647    if (status/=nf90_noerr) then   
648       write(*,*)"unable to retrieve netcdf variable : ",trim(varname)
649       stop
650    endif
651    !     
652    status = nf90_close(ncid)
653    !     
654  end subroutine Read_Ncdf_var4d_Real_t
655
656  !> Subroutine to read a 3D real variable in a given file for time t
657  !! @param[in]  varname : name of variable to retrieve
658  !! @param[in]  file    : netcdf file name                               
659  !! @param[out] tabvar  : array containing values of the required variable
660  !! @param[in]  time    : time corresponding to the values to read
661  !! @return tabvar
662
663
664  subroutine Read_Ncdf_var3d_Real_t(varname,file,tabvar,time)   
665    implicit none
666    !       
667    Character(*),intent(in) :: varname,file
668    Integer,intent(in) :: time
669    Real*8, dimension(:,:,:), pointer :: tabvar
670    !
671    !local variables
672    !
673    Integer, dimension(3) :: dimIDS
674    Integer :: dim1,dim2
675    Integer :: status,ncid
676    Integer :: varid             
677    !
678    status = nf90_open(file,NF90_NOWRITE,ncid)
679    !     
680    if (status/=nf90_noerr) then   
681       write(*,*)"unable to open netcdf file : ",file
682       stop
683    endif
684    !     
685    status = nf90_inq_varid(ncid,varname,varid)
686    !       
687    status=nf90_inquire_variable(ncid,varid,dimids=dimIDS)
688    status=nf90_inquire_dimension(ncid,dimIDS(1),len=dim1)
689    status=nf90_inquire_dimension(ncid,dimIDS(2),len=dim2)
690    !
691    if(.not. associated(tabvar)) then
692       Allocate(tabvar(dim1,dim2,1)) 
693    else
694       if( any(shape(tabvar) /= (/dim1,dim2,1/)) ) then           
695          deallocate(tabvar)   
696          Allocate(tabvar(dim1,dim2,1))     
697       endif
698    endif
699
700    status=nf90_get_var(ncid,varid,tabvar,start=(/1,1,time/))
701
702    if (status/=nf90_noerr) then   
703       write(*,*)"unable to retrieve netcdf variable : ",trim(varname)
704       stop
705    endif
706    !     
707    status = nf90_close(ncid)
708    !     
709  end subroutine Read_Ncdf_var3d_Real_t
710
711  !> Subroutine to write a 1D real variable in a given file
712  !!@param[in]     varname : name of variable to store                           
713  !!@param[in]     dimname : name of dimensions of the given variable       
714  !!@param[in]     file    : netcdf file name                               
715  !!@param[in]     tabvar  : values of the variable to write                 
716  !!@param[in]     typevar : type of the variable to write                   
717
718  subroutine Write_Ncdf_var1d_Real(varname,dimname,file,tabvar,typevar)
719    !     
720    implicit none
721    !       
722    Character(*),intent(in) :: varname,file,dimname,typevar
723    Real*8, dimension(:), pointer :: tabvar
724    !
725    ! local variables
726    !
727    Integer :: dimid
728    Integer :: status,ncid
729    Integer :: varid             
730    !
731    status = nf90_open(file,NF90_WRITE,ncid)       
732    if (status/=nf90_noerr) then   
733       write(*,*)"unable to open netcdf file : ",file
734       stop
735    endif
736   
737
738    status = nf90_inq_dimid(ncid,dimname, dimid)
739
740    status = nf90_inq_varid(ncid,varname,varid)
741!    write(6,*) 'varid status',status,'no error :',nf90_NoErr,' varid :',varid,'  varname: ',varname
742!    write(6,*)  'erreur',trim(nf90_strerror(status))
743
744    status = nf90_redef(ncid)
745
746    select case(TRIM(typevar))
747    case('double')
748       status = nf90_def_var(ncid,varname,nf90_double,(/dimid/),varid)
749
750    case('float')
751       status = nf90_def_var(ncid,varname,nf90_float,(/dimid/),varid) 
752    end select
753 
754    status = nf90_enddef(ncid)
755    status = nf90_put_var(ncid,varid,tabvar) 
756
757    !     
758    status = nf90_close(ncid)
759    !
760  end subroutine Write_Ncdf_var1d_Real
761
762  !> Subroutine to write a 2D real variable in a given file
763  !!@param[in]     varname : name of variable to store                           
764  !!@param[in]     dimname : name of dimensions of the given variable       
765  !!@param[in]     file    : netcdf file name                               
766  !!@param[in]     tabvar  : values of the variable to write                 
767  !!@param[in]     typevar : type of the variable to write                   
768 
769
770  subroutine Write_Ncdf_var2d_Real(varname,dimname,file,tabvar,typevar)
771    !     
772    !      implicit none
773    !       
774    Character(*),intent(in) :: varname,file,typevar
775    Character(*), dimension(2) :: dimname
776    Real*8, dimension(:,:), pointer :: tabvar
777    !
778    ! local variables
779    !
780    Integer :: dimid1,dimid2
781    Integer :: status,ncid
782    Integer :: varid             
783    !
784    status = nf90_open(file,NF90_WRITE,ncid)       
785    if (status/=nf90_noerr) then   
786       write(*,*)"unable to open netcdf file : ",file
787       stop
788    endif
789    !     
790    status = nf90_inq_dimid(ncid,dimname(1), dimid1)
791    status = nf90_inq_dimid(ncid,dimname(2), dimid2)
792   
793    status = nf90_inq_varid(ncid,varname,varid)
794    status = nf90_redef(ncid)
795   
796    select case(TRIM(typevar))
797    case('double')
798       status = nf90_def_var(ncid,varname,nf90_double,     &
799            (/dimid1,dimid2/),varid)
800    case('float')
801       status = nf90_def_var(ncid,varname,nf90_float,     &
802            (/dimid1,dimid2/),varid)     
803    end select
804    !
805    status = nf90_enddef(ncid)
806    status = nf90_put_var(ncid,varid,tabvar)     
807    !     
808    status = nf90_close(ncid)
809    !
810  end subroutine Write_Ncdf_var2d_Real
811
812  !> Subroutine to write a 3D real variable in a given file
813  !!@param[in]     varname : name of variable to store                           
814  !!@param[in]     dimname : name of dimensions of the given variable       
815  !!@param[in]     file    : netcdf file name                               
816  !!@param[in]     tabvar  : values of the variable to write                 
817  !!@param[in]     typevar : type of the variable to write                   
818
819  subroutine Write_Ncdf_var3d_Real(varname,dimname,file,tabvar,typevar)
820    !     
821    implicit none
822    !       
823    Character(*),intent(in) :: varname,file,typevar
824    Character(*),dimension(3),intent(in) :: dimname
825    Real*8, dimension(:,:,:), pointer :: tabvar
826    !
827    ! local variables
828    !
829    Integer :: dimid1,dimid2,dimid3
830    Integer :: status,ncid
831    Integer :: varid             
832    !
833    status = nf90_open(file,NF90_WRITE,ncid)       
834    if (status/=nf90_noerr) then   
835       write(*,*)"unable to open netcdf file : ",file
836       stop
837    endif
838    !     
839    status = nf90_inq_dimid(ncid,dimname(1), dimid1)
840    status = nf90_inq_dimid(ncid,dimname(2), dimid2)
841    status = nf90_inq_dimid(ncid,dimname(3), dimid3)
842    status = nf90_inq_varid(ncid,varname,varid)
843    status = nf90_redef(ncid)
844
845    select case(TRIM(typevar))
846    case('double')
847       status = nf90_def_var(ncid,varname,nf90_double,     &
848            (/dimid1,dimid2,dimid3/),varid)
849    case('float')
850       status = nf90_def_var(ncid,varname,nf90_float,     &
851            (/dimid1,dimid2,dimid3/),varid)   
852    end select
853    !
854    status = nf90_enddef(ncid)
855    status = nf90_put_var(ncid,varid,tabvar)     
856    !     
857    status = nf90_close(ncid)
858    !
859  end subroutine Write_Ncdf_var3d_Real
860
861  !> Subroutine to write a 4D real variable in a given file
862  !!@param[in]     varname : name of variable to store                           
863  !!@param[in]     dimname : name of dimensions of the given variable       
864  !!@param[in]     file    : netcdf file name                               
865  !!@param[in]     tabvar  : values of the variable to write                 
866  !!@param[in]     typevar : type of the variable to write                   
867
868  subroutine Write_Ncdf_var4d_Real(varname,dimname,file,tabvar,typevar)
869    !     
870    implicit none
871    !       
872    Character(*),intent(in) :: varname,file,typevar
873    Character(*),dimension(4),intent(in) :: dimname
874    Real*8, dimension(:,:,:,:), pointer :: tabvar
875    !
876    ! local variables
877    !
878    Integer :: dimid1,dimid2,dimid3,dimid4
879    Integer :: status,ncid
880    Integer :: varid             
881    !
882    status = nf90_open(file,NF90_WRITE,ncid)       
883    if (status/=nf90_noerr) then   
884       write(*,*)"unable to open netcdf file : ",file
885       stop
886    endif
887    !
888    status = nf90_inq_varid(ncid,varname,varid)
889    !     
890    if(status/=nf90_noerr) then
891       !     
892       status = nf90_inq_dimid(ncid,dimname(1), dimid1)
893       status = nf90_inq_dimid(ncid,dimname(2), dimid2)
894       status = nf90_inq_dimid(ncid,dimname(3), dimid3)
895       status = nf90_inq_dimid(ncid,dimname(4), dimid4)
896       status = nf90_redef(ncid)
897       !     
898       select case(TRIM(typevar))
899       case('double')
900          status = nf90_def_var(ncid,varname,nf90_double,     &
901               (/dimid1,dimid2,dimid3,dimid4/),varid)
902       case('float')
903          status = nf90_def_var(ncid,varname,nf90_float,     &
904               (/dimid1,dimid2,dimid3,dimid4/),varid)   
905       end select
906       !
907       status = nf90_enddef(ncid)
908    endif
909    !         
910    status = nf90_put_var(ncid,varid,tabvar)     
911    !     
912    status = nf90_close(ncid)
913    !
914  end subroutine Write_Ncdf_var4d_Real
915
916
917  !> Subroutine to write a 1D integer variable in a given file
918  !!@param[in]     varname : name of variable to store                           
919  !!@param[in]     dimname : name of dimensions of the given variable       
920  !!@param[in]     file    : netcdf file name                               
921  !!@param[in]     tabvar  : values of the variable to write                             
922
923
924  subroutine Write_Ncdf_var1d_Int(varname,dimname,file,tabvar)
925    !     
926    implicit none
927    !       
928    Character(*),intent(in) :: varname,file,dimname
929    Integer, dimension(:), pointer :: tabvar
930    !
931    ! local variables
932    !
933    Integer :: dimid
934    Integer :: status,ncid
935    Integer :: varid             
936    !
937    status = nf90_open(file,NF90_WRITE,ncid)       
938    if (status/=nf90_noerr) then   
939       write(*,*)"unable to open netcdf file : ",file
940       stop
941    endif
942    !     
943    status = nf90_inq_dimid(ncid,dimname, dimid)
944    status = nf90_inq_varid(ncid,varname,varid)
945    status = nf90_redef(ncid)
946    status = nf90_def_var(ncid,varname,nf90_int,(/dimid/),varid)
947    status = nf90_enddef(ncid)
948    status = nf90_put_var(ncid,varid,tabvar)     
949    !     
950    status = nf90_close(ncid)
951    !
952  end subroutine Write_Ncdf_var1d_Int
953
954  !> Subroutine to write a 2D integer variable in a given file
955  !!@param[in]     varname : name of variable to store                           
956  !!@param[in]     dimname : name of dimensions of the given variable       
957  !!@param[in]     file    : netcdf file name                               
958  !!@param[in]    tabvar  : values of the variable to write                             
959
960  subroutine Write_Ncdf_var2d_Int(varname,dimname,file,tabvar)
961    !     
962    implicit none
963    !       
964    Character(*),intent(in) :: varname,file
965    Character(*), dimension(2) :: dimname
966    Integer, dimension(:,:), pointer :: tabvar
967    !
968    ! local variables
969    !
970    Integer :: dimid1,dimid2
971    Integer :: status,ncid
972    Integer :: varid             
973    !
974    status = nf90_open(file,NF90_WRITE,ncid)       
975    if (status/=nf90_noerr) then   
976       write(*,*)"unable to open netcdf file : ",file
977       stop
978    endif
979    !     
980    status = nf90_inq_dimid(ncid,dimname(1), dimid1)
981    status = nf90_inq_dimid(ncid,dimname(2), dimid2)
982    status = nf90_inq_varid(ncid,varname,varid)
983    status = nf90_redef(ncid)
984    status = nf90_def_var(ncid,varname,nf90_int,     &
985         (/dimid1,dimid2/),varid)
986    status = nf90_enddef(ncid)
987    status = nf90_put_var(ncid,varid,tabvar)     
988    !     
989    status = nf90_close(ncid)
990    !
991  end subroutine Write_Ncdf_var2d_Int
992
993  !> Subroutine to write a 3D integer variable in a given file
994  !!@param[in]     varname : name of variable to store                           
995  !!@param[in]     dimname : name of dimensions of the given variable       
996  !!@param[in]     file    : netcdf file name                               
997  !!@param[in]     tabvar  : values of the variable to write                             
998
999  subroutine Write_Ncdf_var3d_Int(varname,dimname,file,tabvar)
1000    !     
1001    implicit none
1002    !       
1003    Character(*),intent(in) :: varname,file
1004    Character(*),dimension(3),intent(in) :: dimname
1005    Integer, dimension(:,:,:), pointer :: tabvar
1006    !
1007    ! local variables
1008    !
1009    Integer :: dimid1,dimid2,dimid3
1010    Integer :: status,ncid
1011    Integer :: varid             
1012    !
1013    status = nf90_open(file,NF90_WRITE,ncid)       
1014    if (status/=nf90_noerr) then   
1015       write(*,*)"unable to open netcdf file : ",file
1016       stop
1017    endif
1018    !     
1019    status = nf90_inq_dimid(ncid,dimname(1), dimid1)
1020    status = nf90_inq_dimid(ncid,dimname(2), dimid2)
1021    status = nf90_inq_dimid(ncid,dimname(3), dimid3)
1022    status = nf90_inq_varid(ncid,varname,varid)
1023    status = nf90_redef(ncid)
1024    status = nf90_def_var(ncid,varname,nf90_int,     &
1025         (/dimid1,dimid2,dimid3/),varid)
1026    status = nf90_enddef(ncid)
1027    status = nf90_put_var(ncid,varid,tabvar)     
1028    !     
1029    status = nf90_close(ncid)
1030    !
1031  end subroutine Write_Ncdf_var3d_Int
1032
1033  !> Subroutine to write a 4D integer variable in a given file
1034  !!@param[in]     varname : name of variable to store                           
1035  !!@param[in]     dimname : name of dimensions of the given variable       
1036  !!@param[in]     file    : netcdf file name                               
1037  !!@param[in]    tabvar  : values of the variable to write                             
1038
1039
1040  subroutine Write_Ncdf_var4d_Int(varname,dimname,file,tabvar)
1041    !     
1042    implicit none
1043    !       
1044    Character(*),intent(in) :: varname,file
1045    Character(*),dimension(4),intent(in) :: dimname
1046    Integer, dimension(:,:,:,:), pointer :: tabvar
1047    !
1048    ! local variables
1049    !
1050    Integer :: dimid1,dimid2,dimid3,dimid4
1051    Integer :: status,ncid
1052    Integer :: varid             
1053    !
1054    status = nf90_open(file,NF90_WRITE,ncid)       
1055    if (status/=nf90_noerr) then   
1056       write(*,*)"unable to open netcdf file : ",file
1057       stop
1058    endif
1059    !     
1060    status = nf90_inq_dimid(ncid,dimname(1), dimid1)
1061    status = nf90_inq_dimid(ncid,dimname(2), dimid2)
1062    status = nf90_inq_dimid(ncid,dimname(3), dimid3)
1063    status = nf90_inq_dimid(ncid,dimname(4), dimid4)
1064    status = nf90_inq_varid(ncid,varname,varid)
1065    status = nf90_redef(ncid)
1066    status = nf90_def_var(ncid,varname,nf90_int,     &
1067         (/dimid1,dimid2,dimid3,dimid4/),varid)
1068    status = nf90_enddef(ncid)
1069    status = nf90_put_var(ncid,varid,tabvar)     
1070    !     
1071    status = nf90_close(ncid)
1072    !
1073  end subroutine Write_Ncdf_var4d_Int
1074
1075  !> Subroutine to write a 2D real variable with time dependent in a given file
1076  !!@param[in]     varname : name of variable to store                           
1077  !!@param[in]     dimname : name of dimensions of the given variable       
1078  !!@param[in]     file    : netcdf file name                               
1079  !!@param[in]     tabvar  : values of the variable to write
1080  !!@param[in]     time    : time corresponding to the values to write
1081  !!@param[inout]  idef    :
1082  !!@param[in]     typevar : type of the variable to write
1083  !!@return idef
1084  subroutine Write_Ncdf_var2d_Real_t(varname,dimname,file,tabvar,time,idef,typevar)
1085    !     
1086    implicit none
1087    !       
1088    Character(*),intent(in) :: varname,file,typevar
1089    Character(*),dimension(3),intent(in) :: dimname
1090    Integer :: time
1091    Integer,intent(inout) :: idef 
1092    Real*8, dimension(:,:), pointer :: tabvar
1093    !
1094    ! local variables
1095    !
1096    Integer :: dimid1,dimid2,dimid3
1097    Integer :: status,ncid
1098    Integer :: varid             
1099    !
1100    status = nf90_open(file,NF90_WRITE,ncid)       
1101    if (status/=nf90_noerr) then   
1102       write(*,*)"unable to open netcdf file : ",file
1103       stop
1104    endif
1105    !     
1106    if(time==1 .OR. idef==0) then
1107       !     
1108       status = nf90_inq_dimid(ncid,dimname(1), dimid1)
1109       status = nf90_inq_dimid(ncid,dimname(2), dimid2)
1110       status = nf90_inq_dimid(ncid,dimname(3), dimid3)
1111       status = nf90_redef(ncid)
1112       !     
1113       select case(TRIM(typevar))
1114       case('double')
1115          status = nf90_def_var(ncid,varname,nf90_double,     &
1116               (/dimid1,dimid2,dimid3/),varid) 
1117       case('float')
1118          status = nf90_def_var(ncid,varname,nf90_float,     &
1119               (/dimid1,dimid2,dimid3/),varid)   
1120       end select
1121       !
1122       status = nf90_enddef(ncid)
1123       idef = 1
1124    else
1125       status = nf90_inq_varid(ncid, varname, varid)
1126    endif
1127    !     
1128    status = nf90_put_var(ncid,varid,tabvar,start=(/1,1,time/))
1129    if (status/=nf90_noerr) then   
1130       write(*,*)"unable to store variable ",varname, &
1131            " in file ",file
1132       stop
1133    endif
1134    !     
1135    status = nf90_close(ncid)
1136    !
1137  end subroutine Write_Ncdf_var2d_Real_t
1138
1139  !> Subroutine to write a 2D integer variable with time dependent in a given file
1140  !!@param[in]     varname : name of variable to store                           
1141  !!@param[in]     dimname : name of dimensions of the given variable       
1142  !!@param[in]     file    : netcdf file name                               
1143  !!@param[in]     tabvar  : values of the variable to write
1144  !!@param[in]     time    : time corresponding to the values to write
1145  !!@param[inout]  idef    :
1146  !!@return idef
1147
1148  subroutine Write_Ncdf_var2d_Int_t(varname,dimname,file,tabvar,time,idef)
1149    !     
1150    implicit none
1151    !       
1152    Character(*),intent(in) :: varname,file
1153    Character(*),dimension(3),intent(in) :: dimname
1154    Integer :: time
1155    Integer,intent(inout) :: idef
1156    Integer, dimension(:,:), pointer :: tabvar
1157    !
1158    ! local variables
1159    !
1160    Integer :: dimid1,dimid2,dimid3
1161    Integer :: status,ncid
1162    Integer :: varid             
1163    !
1164    status = nf90_open(file,NF90_WRITE,ncid)       
1165    if (status/=nf90_noerr) then   
1166       write(*,*)"unable to open netcdf file : ",file
1167       stop
1168    endif
1169    !     
1170    if(time==1 .OR. idef==0 ) then
1171       !     
1172       status = nf90_inq_dimid(ncid,dimname(1), dimid1)
1173       status = nf90_inq_dimid(ncid,dimname(2), dimid2)
1174       status = nf90_inq_dimid(ncid,dimname(3), dimid3)
1175       status = nf90_redef(ncid)
1176       !     
1177       status = nf90_def_var(ncid,varname,nf90_int,     &
1178            (/dimid1,dimid2,dimid3/),varid) 
1179       !
1180       status = nf90_enddef(ncid)
1181       idef=1
1182    else
1183       status = nf90_inq_varid(ncid, varname, varid)
1184    endif
1185    !     
1186    status = nf90_put_var(ncid,varid,tabvar,start=(/1,1,time/))
1187    if (status/=nf90_noerr) then   
1188       write(*,*)"unable to store variable ",varname, &
1189            " in file ",file
1190       stop
1191    endif
1192    !     
1193    status = nf90_close(ncid)
1194    !
1195  end subroutine Write_Ncdf_var2d_Int_t
1196
1197
1198  !> Subroutine to write a 1D real variable with time dependent in a given file
1199  !!@param[in]     varname : name of variable to store                           
1200  !!@param[in]     dimname : name of dimensions of the given variable       
1201  !!@param[in]     file    : netcdf file name                               
1202  !!@param[in]     tabvar  : values of the variable to write
1203  !!@param[in]     time    : time corresponding to the values to write
1204  !!@param[inou]   idef    :
1205  !!@param[in]     typevar : type of the variable to write
1206  !!@return idef
1207
1208
1209  subroutine Write_Ncdf_var1d_Real_t(varname,dimname,file,tabvar,time,idef,typevar)
1210    !     
1211    implicit none
1212    !       
1213    Character(*),intent(in) :: varname,file,typevar
1214    Character(*),dimension(2),intent(in) :: dimname
1215    Integer :: time
1216    Integer,intent(inout) :: idef
1217    Real*8, dimension(:) :: tabvar
1218    !
1219    ! local variables
1220    !
1221    Integer :: dimid1,dimid2
1222    Integer :: status,ncid
1223    Integer :: varid             
1224    !
1225    status = nf90_open(file,NF90_WRITE,ncid)       
1226    if (status/=nf90_noerr) then   
1227       write(*,*)"unable to open netcdf file : ",file
1228       stop
1229    endif
1230    !     
1231    if(time==1 .OR. idef==0) then
1232       !     
1233       status = nf90_inq_dimid(ncid,dimname(1), dimid1)
1234       status = nf90_inq_dimid(ncid,dimname(2), dimid2)
1235       status = nf90_redef(ncid)
1236       !     
1237       select case(TRIM(typevar))
1238       case('double')
1239          status = nf90_def_var(ncid,varname,nf90_double,     &
1240               (/dimid1,dimid2/),varid) 
1241       case('float')
1242          status = nf90_def_var(ncid,varname,nf90_float,     &
1243               (/dimid1,dimid2/),varid)   
1244       end select
1245       !
1246       status = nf90_enddef(ncid)
1247       idef=1
1248    else
1249       status = nf90_inq_varid(ncid, varname, varid)
1250    endif
1251    !     
1252
1253    status = nf90_put_var(ncid,varid,tabvar,start=(/1,time/))
1254    if (status/=nf90_noerr) then   
1255       write(*,*)"unable to store variable ",varname, &
1256            " in file ",file
1257       stop
1258    endif
1259    !     
1260    status = nf90_close(ncid)
1261    !
1262  end subroutine Write_Ncdf_var1d_Real_t
1263
1264  !> Subroutine to write a 1D real variable with time dependent in a given file
1265  !!@param[in]     varname : name of variable to store                           
1266  !!@param[in]     dimname : name of dimensions of the given variable       
1267  !!@param[in]     file    : netcdf file name                               
1268  !!@param[in]     tabvar  : values of the variable to write
1269  !!@param[in]     time    : time corresponding to the values to write
1270  !!@param[inout]  idef    :
1271  !!@param[in]     typevar : type of the variable to write
1272  !!@return idef
1273
1274  subroutine Write_Ncdf_var1d_Realbis_t(varname,dimname,file,tabvar,time,idef,typevar)
1275    !     
1276    implicit none
1277    !       
1278    Character(*),intent(in) :: varname,file,typevar
1279    Character(*),intent(in) :: dimname                           
1280    Integer :: time
1281    Integer,intent(inout) :: idef
1282    Real*8, dimension(:), pointer :: tabvar
1283    !
1284    ! local variables
1285    !
1286    Integer :: dimid1
1287    Integer :: status,ncid
1288    Integer :: varid             
1289    !
1290    status = nf90_open(file,NF90_WRITE,ncid)       
1291    if (status/=nf90_noerr) then   
1292       write(*,*)"unable to open netcdf file : ",file
1293       stop
1294    endif
1295    !     
1296    if(time==1 .OR. idef==0) then
1297       !     
1298       status = nf90_inq_dimid(ncid,dimname, dimid1)
1299       status = nf90_redef(ncid)
1300       !     
1301       select case(TRIM(typevar))
1302       case('double')
1303          status = nf90_def_var(ncid,varname,nf90_double,     &
1304               (/dimid1/),varid) 
1305       case('float')
1306          status = nf90_def_var(ncid,varname,nf90_float,     &
1307               (/dimid1/),varid)   
1308       end select
1309       !
1310       status = nf90_enddef(ncid)
1311       idef=1
1312    else
1313       status = nf90_inq_varid(ncid, varname, varid)
1314    endif
1315    !     
1316
1317    status = nf90_put_var(ncid,varid,tabvar,start=(/time/))
1318    if (status/=nf90_noerr) then   
1319       write(*,*)"unable to store variable ",varname, &
1320            " in file ",file
1321       stop
1322    endif
1323    !     
1324    status = nf90_close(ncid)
1325    !
1326  end subroutine Write_Ncdf_var1d_Realbis_t
1327
1328
1329  !> Subroutine to write a 1D integer variable with time dependent in a given file
1330  !!@param[in]     varname : name of variable to store                           
1331  !!@param[in]     dimname : name of dimensions of the given variable       
1332  !!@param[in]     file    : netcdf file name                               
1333  !!@param[in]     tabvar  : values of the variable to write
1334  !!@param[in]     time    : time corresponding to the values to write
1335  !!@param[inout]  idef    :
1336  !!@param[in]     typevar : type of the variable to write
1337  !!@return idef
1338  subroutine Write_Ncdf_var1d_Int_t(varname,dimname,file,tabvar,time,idef,typevar)
1339    !     
1340    implicit none
1341    !       
1342    Character(*),intent(in) :: varname,file,typevar
1343    Character(*),dimension(2),intent(in) :: dimname
1344    Integer :: time
1345    Integer,intent(inout) :: idef
1346    !Integer, dimension(:), pointer :: tabvar
1347    Integer, dimension(:) :: tabvar
1348    !
1349    ! local variables
1350    !
1351    Integer :: dimid1,dimid2
1352    Integer :: status,ncid
1353    Integer :: varid             
1354    !
1355    status = nf90_open(file,NF90_WRITE,ncid)       
1356    if (status/=nf90_noerr) then   
1357       write(*,*)"unable to open netcdf file : ",file
1358       stop
1359    endif
1360    !     
1361    if(time==1 .OR. idef==0) then
1362       !     
1363       status = nf90_inq_dimid(ncid,dimname(1), dimid1)
1364       status = nf90_inq_dimid(ncid,dimname(2), dimid2)
1365       status = nf90_redef(ncid)
1366
1367       !     
1368
1369       status = nf90_def_var(ncid,varname,nf90_double,     &
1370            (/dimid1,dimid2/),varid) 
1371
1372       !
1373       status = nf90_enddef(ncid)
1374       idef=1
1375    else
1376       status = nf90_inq_varid(ncid, varname, varid)
1377    endif
1378    !     
1379    status = nf90_put_var(ncid,varid,tabvar,start=(/1,time/))
1380    if (status/=nf90_noerr) then   
1381       write(*,*)"unable to store variable ",varname, &
1382            " in file ",file
1383       stop
1384    endif
1385    !     
1386    status = nf90_close(ncid)
1387    !
1388  end subroutine Write_Ncdf_var1d_Int_t
1389
1390  !> Subroutine to write a 2D real variable with time dependent in a given file
1391  !!@param[in]     varname : name of variable to store                           
1392  !!@param[in]     dimname : name of dimensions of the given variable       
1393  !!@param[in]     file    : netcdf file name                               
1394  !!@param[in]     tabvar  : values of the variable to write
1395  !!@param[in]     time    : time corresponding to the values to write
1396  !!@param[inout]  idef    :
1397  !!@param[in]     typevar : type of the variable to write
1398  !!@return idef
1399  subroutine Write_Ncdf_var3d_Real_t(varname,dimname,file,tabvar,time,idef,typevar)
1400    !     
1401    implicit none
1402    !       
1403    Character(*),intent(in) :: varname,file,typevar
1404    Character(*),dimension(4),intent(in) :: dimname
1405    Integer :: time
1406    Integer,intent(inout) :: idef
1407    Real*8, dimension(:,:,:), pointer :: tabvar
1408    !
1409    ! local variables
1410    !
1411    Integer :: dimid1,dimid2,dimid3,dimid4
1412    Integer :: status,ncid
1413    Integer :: varid             
1414    !
1415    status = nf90_open(file,NF90_WRITE,ncid)       
1416    if (status/=nf90_noerr) then   
1417       write(*,*)"unable to open netcdf file : ",file
1418       stop
1419    endif
1420    !     
1421    if(time==1 .OR. idef==0) then
1422       !     
1423       status = nf90_inq_dimid(ncid,dimname(1), dimid1)
1424       status = nf90_inq_dimid(ncid,dimname(2), dimid2)
1425       status = nf90_inq_dimid(ncid,dimname(3), dimid3)
1426       status = nf90_inq_dimid(ncid,dimname(4), dimid4)
1427       status = nf90_redef(ncid)
1428       !     
1429       select case(TRIM(typevar))
1430       case('double')
1431          status = nf90_def_var(ncid,varname,nf90_double,     &
1432               (/dimid1,dimid2,dimid3,dimid4/),varid) 
1433       case('float')
1434          status = nf90_def_var(ncid,varname,nf90_float,     &
1435               (/dimid1,dimid2,dimid3,dimid4/),varid)   
1436       end select
1437       !
1438       status = nf90_enddef(ncid)
1439       idef=1
1440    else
1441       status = nf90_inq_varid(ncid, varname, varid)
1442    endif
1443    !     
1444    status = nf90_put_var(ncid,varid,tabvar,start=(/1,1,1,time/))
1445    if (status/=nf90_noerr) then   
1446       write(*,*)"unable to store variable ",varname, &
1447            " in file ",file
1448       stop
1449    endif
1450    !     
1451    status = nf90_close(ncid)
1452    !
1453  end subroutine Write_Ncdf_var3d_Real_t
1454
1455  !> Subroutine to write a 3D real variable with time dependent in a given file
1456  !!@param[in]     varname : name of variable to store                           
1457  !!@param[in]     dimname : name of dimensions of the given variable       
1458  !!@param[in]     file    : netcdf file name                               
1459  !!@param[in]     tabvar  : values of the variable to write
1460  !!@param[in]     time    : time corresponding to the values to write
1461  !!@param[inout]  idef    :
1462  !!@param[in]     typevar : type of the variable to write
1463  !!@return idef
1464  subroutine Write_Ncdf_var4d_Real_t(varname,dimname,file,tabvar,time,idef,typevar)
1465    !     
1466    implicit none
1467    !       
1468    Character(*),intent(in) :: varname,file,typevar
1469    Character(*),dimension(4),intent(in) :: dimname
1470    Integer :: time
1471    Integer,intent(inout) :: idef
1472    Real*8, dimension(:,:,:,:), pointer :: tabvar
1473    !
1474    ! local variables
1475    !
1476    Integer :: dimid1,dimid2,dimid3,dimid4
1477    Integer :: status,ncid
1478    Integer :: varid             
1479    !
1480    status = nf90_open(file,NF90_WRITE,ncid)       
1481    if (status/=nf90_noerr) then   
1482       write(*,*)"unable to open netcdf file : ",file
1483       stop
1484    endif
1485    !     
1486    if(time==1 .OR. idef==0) then
1487       !     
1488       status = nf90_inq_dimid(ncid,dimname(1), dimid1)
1489       status = nf90_inq_dimid(ncid,dimname(2), dimid2)
1490       status = nf90_inq_dimid(ncid,dimname(3), dimid3)
1491       status = nf90_inq_dimid(ncid,dimname(4), dimid4)
1492       status = nf90_redef(ncid)
1493       !     
1494       select case(TRIM(typevar))
1495       case('double')
1496          status = nf90_def_var(ncid,TRIM(varname),nf90_double,     &
1497               (/dimid1,dimid2,dimid3,dimid4/),varid) 
1498       case('float')
1499          status = nf90_def_var(ncid,TRIM(varname),nf90_float,     &
1500               (/dimid1,dimid2,dimid3,dimid4/),varid)   
1501       end select
1502       !
1503       status = nf90_enddef(ncid)
1504       idef=1
1505    else
1506       status = nf90_inq_varid(ncid, varname, varid)
1507    endif
1508    !   
1509    status = nf90_put_var(ncid,varid,tabvar,start=(/1,1,1,time/))
1510    if (status/=nf90_noerr) then   
1511       write(*,*)"unable to store variable ",varname, &
1512            " in file ",file
1513       stop
1514    endif
1515    !   
1516    status = nf90_close(ncid)
1517    !
1518  end subroutine Write_Ncdf_var4d_Real_t
1519
1520
1521  !> Subroutine to write a 3D real variable with time dependent in a given file
1522  !!@param[in]     varname : name of variable to store                           
1523  !!@param[in]     dimname : name of dimensions of the given variable       
1524  !!@param[in]     file    : netcdf file name                               
1525  !!@param[in]     tabvar  : values of the variable to write
1526  !!@param[in]     time    : time corresponding to the values to write
1527  !!@param[in]     level   : level corresponding to the values to read
1528  !!@param[inout]  idef    :
1529  !!@param[in]     typevar : type of the variable to write
1530  !!@return idef
1531
1532  subroutine Write_Ncdf_var4d_Real_nt(varname,dimname,file,tabvar,time,level,idef,typevar)
1533    !     
1534    implicit none
1535    !       
1536    Character(*),intent(in) :: varname,file,typevar
1537    Character(*),dimension(4),intent(in) :: dimname
1538    Integer :: time,level
1539    Integer,intent(inout) :: idef
1540    Real*8, dimension(:,:,:,:), pointer :: tabvar
1541    !
1542    ! local variables
1543    !
1544    Integer :: dimid1,dimid2,dimid3,dimid4
1545    Integer :: status,ncid
1546    Integer :: varid             
1547    !
1548    status = nf90_open(file,NF90_WRITE,ncid)       
1549    if (status/=nf90_noerr) then   
1550       write(*,*)"unable to open netcdf file : ",file
1551       stop
1552    endif
1553    !     
1554    if((time==1.and.level==1) .OR. idef==0 ) then
1555       !     
1556       status = nf90_inq_dimid(ncid,dimname(1), dimid1)
1557       status = nf90_inq_dimid(ncid,dimname(2), dimid2)
1558       status = nf90_inq_dimid(ncid,dimname(3), dimid3)
1559       status = nf90_inq_dimid(ncid,dimname(4), dimid4)
1560       status = nf90_redef(ncid)
1561       !     
1562       select case(TRIM(typevar))
1563       case('double')
1564          status = nf90_def_var(ncid,TRIM(varname),nf90_double,     &
1565               (/dimid1,dimid2,dimid3,dimid4/),varid) 
1566       case('float')
1567          status = nf90_def_var(ncid,TRIM(varname),nf90_float,     &
1568               (/dimid1,dimid2,dimid3,dimid4/),varid)   
1569       end select
1570       !
1571       status = nf90_enddef(ncid)
1572       idef=1
1573    else
1574       status = nf90_inq_varid(ncid, varname, varid)
1575    endif
1576    !   
1577    status = nf90_put_var(ncid,varid,tabvar,start=(/1,1,level,time/))
1578    if (status/=nf90_noerr) then   
1579       write(*,*)"unable to store variable ",varname, &
1580            " in file ",file
1581       stop
1582    endif
1583    !   
1584    status = nf90_close(ncid)
1585    !
1586  end subroutine Write_Ncdf_var4d_Real_nt
1587
1588  !> Subroutine  to retrieve names of all variables included in a given file
1589  !!@param[in]     filename    : netcdf file name                   
1590  !!@param[out]    tabvarname  : array containing various variables names       
1591  !!@return tabvarname
1592
1593  subroutine Read_Ncdf_VarName(filename,tabvarname)
1594    !     
1595    Character(*),intent(in) :: filename
1596    Character*20,dimension(:),pointer :: tabvarname
1597    Integer :: nDimensions,nVariables
1598    Integer :: nAttributes,unlimitedDimId,i
1599    Integer :: ncid,status
1600    !     
1601    status = nf90_open(filename,NF90_NOWRITE,ncid)
1602    if (status/=nf90_noerr) then   
1603       write(*,*)"unable to open netcdf file : ",filename
1604       stop
1605    endif
1606    !     
1607    status = nf90_inquire(ncid,nDimensions,nVariables,nAttributes, &
1608         unlimitedDimId) 
1609    !
1610    Allocate(tabvarname(nVariables))
1611    !
1612    Do i=1,nVariables
1613       status = nf90_inquire_variable(ncid,i,tabvarname(i))
1614    End do
1615
1616  end subroutine Read_Ncdf_Varname
1617
1618
1619  !> Subroutine copy a netcdf varaiable  included in a given file to an other file                 
1620  !!@param[in]    varname  : array containing various variables names       
1621  !!@param[in]    filein   : netcdf entry file name   
1622  !!@param[in]    fileout  : netcdf result file name
1623  !!@return
1624
1625  subroutine Copy_Ncdf_att_var(varname,filein,fileout)
1626    !     
1627    Character(*),intent(in) :: filein,fileout
1628    Character(*),intent(in) :: varname
1629    Integer :: ncid_in,ncid_out,status,varid_in,varid_out
1630    !     
1631    !      print *,'filein = ',filein,fileout
1632    status = nf90_open(filein,NF90_NOWRITE,ncid_in)
1633    if (status/=nf90_noerr) then   
1634       write(*,*)"unable to open input netcdf file : ",filein
1635       stop
1636    endif
1637    !                                                                             
1638    status = nf90_open(fileout,NF90_WRITE,ncid_out)
1639    if (status/=nf90_noerr) then   
1640       write(*,*)"unable to open output netcdf file : ",fileout
1641       stop
1642    endif
1643   
1644    !      print *,'ici1'
1645    status = nf90_inq_varid(ncid_in,varname,varid_in)
1646    status = nf90_inq_varid(ncid_out,varname,varid_out)
1647    !
1648    status = nf90_redef(ncid_out)
1649    !     
1650    status = nf90_copy_att(ncid_in,varid_in,'units',ncid_out,varid_out)
1651    status = nf90_copy_att(ncid_in,varid_in,'valid_min',ncid_out,varid_out)
1652    status = nf90_copy_att(ncid_in,varid_in,'valid_max',ncid_out,varid_out) 
1653    status = nf90_copy_att(ncid_in,varid_in,'long_name',ncid_out,varid_out)
1654    status = nf90_copy_att(ncid_in,varid_in,'calendar',ncid_out,varid_out)
1655    status = nf90_copy_att(ncid_in,varid_in,'title',ncid_out,varid_out)     
1656    status = nf90_copy_att(ncid_in,varid_in,'time_origin',ncid_out,varid_out) 
1657    status = nf90_copy_att(ncid_in,varid_in,'positive',ncid_out,varid_out)                 
1658    status = nf90_copy_att(ncid_in,varid_in,'tstep_sec',ncid_out,varid_out)         
1659    status = nf90_copy_att(ncid_in,varid_in,'nav_model',ncid_out,varid_out)   
1660    status = nf90_copy_att(ncid_in,varid_in,'Minvalue=',ncid_out,varid_out)
1661    status = nf90_copy_att(ncid_in,varid_in,'Maxvalue=',ncid_out,varid_out) 
1662    status = nf90_copy_att(ncid_in,varid_in,'short_name',ncid_out,varid_out)
1663    status = nf90_copy_att(ncid_in,varid_in,'online_operation',ncid_out,varid_out)
1664    status = nf90_copy_att(ncid_in,varid_in,'axis',ncid_out,varid_out)           
1665    status = nf90_copy_att(ncid_in,varid_in,'interval_operation',ncid_out,varid_out)
1666    status = nf90_copy_att(ncid_in,varid_in,'interval_write',ncid_out,varid_out) 
1667    status = nf90_copy_att(ncid_in,varid_in,'associate',ncid_out,varid_out)
1668    status = nf90_copy_att(ncid_in,varid_in,'actual_range',ncid_out,varid_out) 
1669    status = nf90_copy_att(ncid_in,varid_in,'longitude',ncid_out,varid_out)
1670    status = nf90_copy_att(ncid_in,varid_in,'latitude',ncid_out,varid_out)
1671    status = nf90_copy_att(ncid_in,varid_in,'scale_factor',ncid_out,varid_out)
1672    status = nf90_copy_att(ncid_in,varid_in,'add_offset',ncid_out,varid_out)
1673    status = nf90_copy_att(ncid_in,varid_in,'missing_value',ncid_out,varid_out) 
1674    !     
1675    status = nf90_enddef(ncid_out) 
1676    !
1677    status = nf90_close(ncid_in)
1678    status = nf90_close(ncid_out)
1679    !      print *,'ici2'
1680    !
1681  end subroutine Copy_Ncdf_att_var
1682
1683  !> Subroutine copy a netcdf varaiable  included in a given file to an other file at latlon                 
1684  !!@param[in]    varname  : array containing various variables names       
1685  !!@param[in]    filein   : netcdf entry file name   
1686  !!@param[in]    fileout  : netcdf result file name
1687  !!@param[in]    min      :
1688  !!@param[in]    max      :
1689  !!@return
1690
1691
1692  subroutine Copy_Ncdf_att_latlon(varname,filein,fileout,min,max)
1693    !     
1694    Character(*),intent(in) :: filein,fileout
1695    Character(*),intent(in) :: varname
1696    real*8 :: min,max
1697    Integer :: ncid_in,ncid_out,status,varid_in,varid_out
1698    !     
1699    status = nf90_open(filein,NF90_NOWRITE,ncid_in)
1700    if (status/=nf90_noerr) then   
1701       write(*,*)"unable to open netcdf file : ",filein
1702       stop
1703    endif
1704    !                                                                             
1705    status = nf90_open(fileout,NF90_WRITE,ncid_out)
1706    if (status/=nf90_noerr) then   
1707       write(*,*)"unable to open netcdf file : ",fileout
1708       stop
1709    endif
1710   
1711    status = nf90_inq_varid(ncid_in,varname,varid_in)
1712    status = nf90_inq_varid(ncid_out,varname,varid_out)
1713    !
1714    status = nf90_redef(ncid_out)
1715    !     
1716    select case (varname)
1717       !     
1718    case('nav_lon')     
1719       status = nf90_copy_att(ncid_in,varid_in,'units',ncid_out,varid_out) 
1720       status = nf90_put_att(ncid_out,varid_out,'valid_min',real(min,4))
1721       status = nf90_put_att(ncid_out,varid_out,'valid_max',real(max,4))
1722       status = nf90_copy_att(ncid_in,varid_in,'long_name',ncid_out,varid_out)
1723       status = nf90_copy_att(ncid_in,varid_in,'nav_model',ncid_out,varid_out)
1724       status = nf90_copy_att(ncid_in,varid_in,'title',ncid_out,varid_out)
1725       !
1726    case('nav_lat')
1727       status = nf90_copy_att(ncid_in,varid_in,'units',ncid_out,varid_out) 
1728       status = nf90_put_att(ncid_out,varid_out,'valid_min',real(min,4))
1729       status = nf90_put_att(ncid_out,varid_out,'valid_max',real(max,4))
1730       status = nf90_copy_att(ncid_in,varid_in,'long_name',ncid_out,varid_out)
1731       status = nf90_copy_att(ncid_in,varid_in,'nav_model',ncid_out,varid_out)
1732       status = nf90_copy_att(ncid_in,varid_in,'title',ncid_out,varid_out) 
1733       !
1734    end select
1735    !     
1736    status = nf90_enddef(ncid_out) 
1737    !
1738    status = nf90_close(ncid_in)
1739    status = nf90_close(ncid_out)
1740  end subroutine Copy_Ncdf_att_latlon
1741
1742  !> Subroutine to retrieve value of a given dimension             
1743  !!@param[in]    dimname : name of dimension to retrieve     
1744  !!@param[in]    file    : netcdf file name       
1745  !!@param[out]   dimval  : value of the required dimension
1746  !!@return       dimval
1747
1748  subroutine Read_Ncdf_dim(dimname,file,dimval)   
1749    !     
1750    implicit none
1751    !           
1752    Character(*),intent(in) :: dimname,file   
1753    Integer    :: dimval
1754    !           
1755    ! local variables
1756    !
1757    integer ncid,status,dimid
1758    !     
1759    status = nf90_open(file,NF90_NOWRITE,ncid)
1760    if (status/=nf90_noerr) then   
1761       write(*,*)"unable to open netcdf file : ",file
1762       stop
1763    endif
1764    !     
1765    status = nf90_inq_dimid(ncid,dimname,dimid)
1766    status = nf90_inquire_dimension(ncid,dimid,len=dimval)                                                               
1767    !     
1768    status = nf90_close(ncid)
1769    !     
1770  end subroutine Read_Ncdf_dim
1771
1772  !> Subroutine   to write a dimension in a given file           
1773  !!@param[in]    dimname : name of dimension to retrieve     
1774  !!@param[in]    file    : netcdf file name       
1775  !!@param[out]   dimval  : value of the required dimension
1776  !!@return       dimval
1777
1778  subroutine Write_Ncdf_dim(dimname,file,dimval)   
1779    !     
1780    implicit none
1781    !           
1782    Character(*),intent(in) :: dimname,file   
1783    Integer    :: dimval
1784    !     
1785    ! local variables
1786    !
1787    integer ncid,status,dimid
1788    !     
1789    status = nf90_open(file,NF90_WRITE,ncid)
1790    if (status/=nf90_noerr) then   
1791       write(*,*)"unable to open netcdf file : ",file
1792       stop
1793    endif
1794    !     
1795    status = nf90_redef(ncid)
1796    If(dimval.eq.0) then
1797       status = nf90_def_dim(ncid,dimname,nf90_unlimited,dimid)       
1798    Else
1799       status = nf90_def_dim(ncid,dimname,dimval,dimid) 
1800    End If
1801    status = nf90_enddef(ncid)
1802    !     
1803    status = nf90_close(ncid)
1804    !     
1805  end subroutine Write_Ncdf_dim
1806
1807  !> Function   to get the dimension of a given vriable in a given file           
1808  !!@param[in]    varname : name of variable to retrieve dimension     
1809  !!@param[in]    filename    : netcdf file name       
1810  !!@return       
1811
1812  Integer function Get_NbDims( varname , filename )
1813    !
1814    Character(*),intent(in) :: varname,filename
1815    Integer :: status,ncid,varid   
1816    !     
1817    status = nf90_open(TRIM(filename),NF90_NOWRITE,ncid)
1818    if (status/=nf90_noerr) then   
1819       write(*,*)"unable to open netcdf file : ",TRIM(filename)
1820       stop
1821    endif
1822    status = nf90_inq_varid(ncid,TRIM(varname),varid)     
1823    status = nf90_inquire_variable(ncid, varid , ndims = Get_NbDims)
1824    !
1825    return
1826    !
1827  end function Get_NbDims
1828
1829 
1830  !> Function   to test exitence dimension in a given file           
1831  !!@param[in]    varname : name of variable to retrieve dimension     
1832  !!@param[in]    filename    : netcdf file name       
1833  !!@return       
1834
1835  !   function Get_NbDims_Existence
1836  !**************************************************************         
1837  !
1838  Logical function Dims_Existence( dimname , filename )
1839    !
1840    Character(*),intent(in) :: dimname,filename
1841    Integer :: status,ncid,dimid   
1842    !     
1843    status = nf90_open(TRIM(filename),NF90_NOWRITE,ncid)
1844    if (status/=nf90_noerr) then   
1845       write(*,*)"unable to open netcdf file : ",TRIM(filename)
1846       stop
1847    endif
1848    status = nf90_inq_dimid(ncid,dimname,dimid)
1849    !     
1850    if (status/=nf90_noerr) then
1851       Dims_Existence = .false.
1852    else
1853       Dims_Existence = .true.
1854    endif
1855    !
1856    return
1857    !
1858  end function Dims_Existence
1859  !
1860  !**************************************************************
1861  !**************************************************************
1862
1863end module io_netcdf_grisli
1864
1865
1866
1867
1868
1869
Note: See TracBrowser for help on using the repository browser.