source: LMDZ5/trunk/tools/Max_diff_nc_with_lib/NetCDF95/nf95_def_var.f90 @ 1907

Last change on this file since 1907 was 1907, checked in by lguez, 10 years ago

Added a copyright property to every file of the distribution, except
for the fcm files (which have their own copyright). Use svn propget on
a file to see the copyright. For instance:

$ svn propget copyright libf/phylmd/physiq.F90
Name of program: LMDZ
Creation date: 1984
Version: LMDZ5
License: CeCILL version 2
Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
See the license file in the root directory

Also added the files defining the CeCILL version 2 license, in French
and English, at the top of the LMDZ tree.

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 2.8 KB
Line 
1module nf95_def_var_m
2
3  ! The generic procedure name "nf90_def_var" applies to
4  ! "nf90_def_var_Scalar" but we cannot apply the generic procedure name
5  ! "nf95_def_var" to "nf95_def_var_scalar" because of the additional
6  ! optional argument.
7  ! "nf95_def_var_scalar" cannot be distinguished from "nf95_def_var_oneDim".
8
9  implicit none
10
11  interface nf95_def_var
12    module procedure nf95_def_var_oneDim, nf95_def_var_ManyDims
13  end interface
14
15  private
16  public nf95_def_var, nf95_def_var_scalar
17
18contains
19
20  subroutine nf95_def_var_scalar(ncid, name, xtype, varid, ncerr)
21
22    use netcdf, only: nf90_def_var
23    use handle_err_m, only: handle_err
24
25    integer,               intent( in) :: ncid
26    character (len = *),   intent( in) :: name
27    integer,               intent( in) :: xtype
28    integer,               intent(out) :: varid
29    integer, intent(out), optional:: ncerr
30
31    ! Variable local to the procedure:
32    integer ncerr_not_opt
33
34    !-------------------
35
36    ncerr_not_opt = nf90_def_var(ncid, name, xtype, varid)
37    if (present(ncerr)) then
38       ncerr = ncerr_not_opt
39    else
40       call handle_err("nf95_def_var_scalar " // name, ncerr_not_opt, ncid)
41    end if
42
43  end subroutine nf95_def_var_scalar
44
45  !***********************
46
47  subroutine nf95_def_var_oneDim(ncid, name, xtype, dimids, varid, ncerr)
48
49    use netcdf, only: nf90_def_var
50    use handle_err_m, only: handle_err
51
52    integer,               intent( in) :: ncid
53    character (len = *),   intent( in) :: name
54    integer,               intent( in) :: xtype
55    integer,               intent( in) :: dimids
56    integer,               intent(out) :: varid
57    integer, intent(out), optional:: ncerr
58
59    ! Variable local to the procedure:
60    integer ncerr_not_opt
61
62    !-------------------
63
64    ncerr_not_opt = nf90_def_var(ncid, name, xtype, dimids, varid)
65    if (present(ncerr)) then
66       ncerr = ncerr_not_opt
67    else
68       call handle_err("nf95_def_var_oneDim " // name, ncerr_not_opt, ncid)
69    end if
70
71  end subroutine nf95_def_var_oneDim
72
73  !***********************
74
75  subroutine nf95_def_var_ManyDims(ncid, name, xtype, dimids, varid, ncerr)
76
77    use netcdf, only: nf90_def_var
78    use handle_err_m, only: handle_err
79
80    integer,               intent( in) :: ncid
81    character (len = *),   intent( in) :: name
82    integer,               intent( in) :: xtype
83    integer, dimension(:), intent( in) :: dimids
84    integer,               intent(out) :: varid
85    integer, intent(out), optional:: ncerr
86
87    ! Variable local to the procedure:
88    integer ncerr_not_opt
89
90    !-------------------
91
92    ncerr_not_opt = nf90_def_var(ncid, name, xtype, dimids, varid)
93    if (present(ncerr)) then
94       ncerr = ncerr_not_opt
95    else
96       call handle_err("nf95_def_var_ManyDims " // name, ncerr_not_opt, ncid)
97    end if
98
99  end subroutine nf95_def_var_ManyDims
100
101end module nf95_def_var_m
Note: See TracBrowser for help on using the repository browser.