source: LMDZ4/branches/LMDZ4-dev/libf/bibio/nf95_put_var_m.f90 @ 1155

Last change on this file since 1155 was 1155, checked in by jghattas, 15 years ago

Correction pour compilation en double precision :
Enleve kind=FourByteReal? pour les arguments. Les arguments restent REAL, donc le precision choisi pendant la compilation (double ou simple).

Lionel+Josefine

File size: 5.8 KB
Line 
1! $Id$
2module nf95_put_var_m
3
4  implicit none
5
6  interface nf95_put_var
7     module procedure nf95_put_var_1D_FourByteReal, &
8          nf95_put_var_2D_FourByteReal, nf95_put_var_3D_FourByteReal, &
9          nf95_put_var_4D_FourByteReal
10!!$     module procedure nf95_put_var_1D_FourByteReal, &
11!!$          nf95_put_var_2D_FourByteReal, nf95_put_var_3D_FourByteReal, &
12!!$          nf95_put_var_4D_FourByteReal, nf90_put_var_1D_EightByteReal, &
13!!$          nf90_put_var_3D_EightByteReal
14  end interface
15
16  private
17  public nf95_put_var
18
19contains
20
21  subroutine nf95_put_var_1D_FourByteReal(ncid, varid, values, start, count, &
22       stride, map, ncerr)
23
24    use netcdf, only: nf90_put_var
25    use handle_err_m, only: handle_err
26
27    integer,                         intent(in) :: ncid, varid
28    real, intent(in) :: values(:)
29    integer, dimension(:), optional, intent(in) :: start, count, stride, map
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_put_var(ncid, varid, values, start, count, stride, &
38         map)
39    if (present(ncerr)) then
40       ncerr = ncerr_not_opt
41    else
42       call handle_err("nf95_put_var_1D_FourByteReal", ncerr_not_opt, ncid, &
43            varid)
44    end if
45
46  end subroutine nf95_put_var_1D_FourByteReal
47
48  !***********************
49
50  subroutine nf95_put_var_2D_FourByteReal(ncid, varid, values, start, count, &
51       stride, map, ncerr)
52
53    use netcdf, only: nf90_put_var
54    use handle_err_m, only: handle_err
55
56    integer,                         intent( in) :: ncid, varid
57    real, intent( in) :: values(:, :)
58    integer, dimension(:), optional, intent( in) :: start, count, stride, map
59    integer, intent(out), optional:: ncerr
60
61    ! Variable local to the procedure:
62    integer ncerr_not_opt
63
64    !-------------------
65
66    ncerr_not_opt = nf90_put_var(ncid, varid, values, start, count, stride, &
67         map)
68    if (present(ncerr)) then
69       ncerr = ncerr_not_opt
70    else
71       call handle_err("nf95_put_var_2D_FourByteReal", ncerr_not_opt, ncid, &
72            varid)
73    end if
74
75  end subroutine nf95_put_var_2D_FourByteReal
76
77  !***********************
78
79  subroutine nf95_put_var_3D_FourByteReal(ncid, varid, values, start, count, &
80       stride, map, ncerr)
81
82    use netcdf, only: nf90_put_var
83    use handle_err_m, only: handle_err
84
85    integer,                         intent( in) :: ncid, varid
86    real, intent( in) :: values(:, :, :)
87    integer, dimension(:), optional, intent( in) :: start, count, stride, map
88    integer, intent(out), optional:: ncerr
89
90    ! Variable local to the procedure:
91    integer ncerr_not_opt
92
93    !-------------------
94
95    ncerr_not_opt = nf90_put_var(ncid, varid, values, start, count, stride, &
96         map)
97    if (present(ncerr)) then
98       ncerr = ncerr_not_opt
99    else
100       call handle_err("nf95_put_var_3D_FourByteReal", ncerr_not_opt, ncid, &
101            varid)
102    end if
103
104  end subroutine nf95_put_var_3D_FourByteReal
105
106  !***********************
107
108  subroutine nf95_put_var_4D_FourByteReal(ncid, varid, values, start, count, &
109       stride, map, ncerr)
110
111    use netcdf, only: nf90_put_var
112    use handle_err_m, only: handle_err
113
114    integer,                         intent( in) :: ncid, varid
115    real, intent( in) :: values(:, :, :, :)
116    integer, dimension(:), optional, intent( in) :: start, count, stride, map
117    integer, intent(out), optional:: ncerr
118
119    ! Variable local to the procedure:
120    integer ncerr_not_opt
121
122    !-------------------
123
124    ncerr_not_opt = nf90_put_var(ncid, varid, values, start, count, stride, &
125         map)
126    if (present(ncerr)) then
127       ncerr = ncerr_not_opt
128    else
129       call handle_err("nf95_put_var_4D_FourByteReal", ncerr_not_opt, ncid, &
130            varid)
131    end if
132
133  end subroutine nf95_put_var_4D_FourByteReal
134
135  !***********************
136
137!!$  subroutine nf90_put_var_1D_EightByteReal(ncid, varid, values, start, count, &
138!!$       stride, map, ncerr)
139!!$
140!!$    use typesizes, only: eightByteReal
141!!$    use netcdf, only: nf90_put_var
142!!$    use handle_err_m, only: handle_err
143!!$
144!!$    integer,                         intent( in) :: ncid, varid
145!!$    real (kind = EightByteReal),     intent( in) :: values(:)
146!!$    integer, dimension(:), optional, intent( in) :: start, count, stride, map
147!!$    integer, intent(out), optional:: ncerr
148!!$
149!!$    ! Variable local to the procedure:
150!!$    integer ncerr_not_opt
151!!$
152!!$    !-------------------
153!!$
154!!$    ncerr_not_opt = nf90_put_var(ncid, varid, values, start, count, stride, &
155!!$         map)
156!!$    if (present(ncerr)) then
157!!$       ncerr = ncerr_not_opt
158!!$    else
159!!$       call handle_err("nf95_put_var_1D_eightByteReal", ncerr_not_opt, ncid, &
160!!$            varid)
161!!$    end if
162!!$
163!!$  end subroutine nf90_put_var_1D_EightByteReal
164!!$
165!!$  !***********************
166!!$
167!!$  subroutine nf90_put_var_3D_EightByteReal(ncid, varid, values, start, count, &
168!!$       stride, map, ncerr)
169!!$
170!!$    use typesizes, only: eightByteReal
171!!$    use netcdf, only: nf90_put_var
172!!$    use handle_err_m, only: handle_err
173!!$
174!!$    integer,                         intent( in) :: ncid, varid
175!!$    real (kind = EightByteReal),     intent( in) :: values(:, :, :)
176!!$    integer, dimension(:), optional, intent( in) :: start, count, stride, map
177!!$    integer, intent(out), optional:: ncerr
178!!$
179!!$    ! Variable local to the procedure:
180!!$    integer ncerr_not_opt
181!!$
182!!$    !-------------------
183!!$
184!!$    ncerr_not_opt = nf90_put_var(ncid, varid, values, start, count, stride, &
185!!$         map)
186!!$    if (present(ncerr)) then
187!!$       ncerr = ncerr_not_opt
188!!$    else
189!!$       call handle_err("nf95_put_var_3D_eightByteReal", ncerr_not_opt, ncid, &
190!!$            varid)
191!!$    end if
192!!$
193!!$  end subroutine nf90_put_var_3D_EightByteReal
194
195end module nf95_put_var_m
Note: See TracBrowser for help on using the repository browser.