source: LMDZ6/trunk/tools/netcdf95/Variables/nf95_def_var.f90 @ 4918

Last change on this file since 4918 was 4918, checked in by Laurent Fairhead, 4 weeks ago

Reintegrated NetCDF95 in LMDZ so that it is compiled and made available by the makelmdz_fcm script.
The makelmdz_fcm creates the libnetcdf95 library and copies it in the tools/netcdf/lib directory, copying
the mod files in the tools/netcdf/include library.

File size: 2.9 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  use netcdf, only: nf90_def_var
10  use nf95_abort_m, only: nf95_abort
11  use nf95_constants, only: nf95_noerr
12
13  implicit none
14
15  interface nf95_def_var
16    module procedure nf95_def_var_oneDim, nf95_def_var_ManyDims
17  end interface
18
19  private
20  public nf95_def_var, nf95_def_var_scalar
21
22contains
23
24  subroutine nf95_def_var_scalar(ncid, name, xtype, varid, ncerr)
25
26    integer,               intent( in) :: ncid
27    character (len = *),   intent( in) :: name
28    integer,               intent( in) :: xtype
29    integer,               intent(out) :: varid
30    integer, intent(out), optional:: ncerr
31
32    ! Variable local to the procedure:
33    integer ncerr_not_opt
34
35    !-------------------
36
37    ncerr_not_opt = nf90_def_var(ncid, name, xtype, varid)
38    if (present(ncerr)) then
39       ncerr = ncerr_not_opt
40    else
41       if (ncerr_not_opt /= nf95_noerr) call &
42            nf95_abort("nf95_def_var_scalar, name =  " // name, ncerr_not_opt, &
43            ncid)
44    end if
45
46  end subroutine nf95_def_var_scalar
47
48  !***********************
49
50  subroutine nf95_def_var_oneDim(ncid, name, xtype, dimids, varid, ncerr)
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       if (ncerr_not_opt /= nf95_noerr) call &
69            nf95_abort("nf95_def_var_oneDim, name =  " // name, ncerr_not_opt, &
70            ncid)
71    end if
72
73  end subroutine nf95_def_var_oneDim
74
75  !***********************
76
77  subroutine nf95_def_var_ManyDims(ncid, name, xtype, dimids, varid, ncerr)
78
79    integer,               intent( in) :: ncid
80    character (len = *),   intent( in) :: name
81    integer,               intent( in) :: xtype
82    integer, dimension(:), intent( in) :: dimids
83    integer,               intent(out) :: varid
84    integer, intent(out), optional:: ncerr
85
86    ! Variable local to the procedure:
87    integer ncerr_not_opt
88
89    !-------------------
90
91    ncerr_not_opt = nf90_def_var(ncid, name, xtype, dimids, varid)
92    if (present(ncerr)) then
93       ncerr = ncerr_not_opt
94    else
95       if (ncerr_not_opt /= nf95_noerr) call &
96            nf95_abort("nf95_def_var_ManyDims, name = " // name, &
97            ncerr_not_opt, ncid)
98    end if
99
100  end subroutine nf95_def_var_ManyDims
101
102end module nf95_def_var_m
Note: See TracBrowser for help on using the repository browser.