/[lmdze]/trunk/phylmd/Mobidic/regr_lat_time_coefoz.f
ViewVC logotype

Diff of /trunk/phylmd/Mobidic/regr_lat_time_coefoz.f

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

trunk/libf/dyn3d/regr_coefoz.f90 revision 4 by guez, Thu Feb 28 18:05:06 2008 UTC trunk/Sources/phylmd/Mobidic/regr_lat_time_coefoz.f revision 179 by guez, Fri Mar 11 18:58:19 2016 UTC
# Line 1  Line 1 
1  module regr_coefoz_m  module regr_lat_time_coefoz_m
2    
   ! This module is clean: no C preprocessor directive, no include line.  
3    ! Author: Lionel GUEZ    ! Author: Lionel GUEZ
4    
5    implicit none    implicit none
6    
7    private    private
8    public regr_coefoz    public regr_lat_time_coefoz
9    
10  contains  contains
11    
12    subroutine regr_coefoz    subroutine regr_lat_time_coefoz
13    
14      ! "regr_coefoz" stands for "regrid coefficients ozone".      ! "regr_lat_time_coefoz" stands for "regrid latitude time
15        ! coefficients ozone".
16    
17        ! This procedure reads from a NetCDF file parameters for ozone
18        ! chemistry, regrids them in latitude and time, and writes the
19        ! regridded fields to a new NetCDF file.
20    
     ! This procedure reads from a file parameters for ozone  
     ! chemistry and regrids them for LMDZ.  
21      ! The input fields depend on time, pressure level and      ! The input fields depend on time, pressure level and
22      ! latitude.      ! latitude.
23      ! We assume that the input fields are step functions      ! We assume that the input fields are step functions
24      ! of latitude.      ! of latitude.
25      ! Horizontal regridding is made by averaging on latitude, with a      ! Regridding in latitude is made by averaging, with a cosine of
26      ! cosine of latitude factor.      ! latitude factor.
27      ! The target horizontal LMDZ grid is the "scalar" grid: "rlonv", "rlatu".      ! The target LMDZ latitude grid is the "scalar" grid: "rlatu".
28      ! The values of "rlatu" are taken to be the centers of intervals.      ! The values of "rlatu" are taken to be the centers of intervals.
29      ! The target vertical LMDZ grid is the grid of mid-layers.      ! Regridding in time is by linear interpolation.
30      ! The input latitude values are different from the latitude values      ! Monthly values are processed to get daily values, on the basis
31      ! of the LMDZ "scalar" grid.      ! of a 360-day calendar.
32      ! The input data does not depend on longitude, but the pressure  
33      ! at LMDZ mid-layers does.      ! We assume that in the input file:
34      ! Therefore, the values on the LMDZ grid do depend on longitude.      ! -- the latitude is in degrees and strictly monotonic (as all
35      ! The regridded fields are written to a file.      ! NetCDF coordinate variables should be);
36        ! -- time increases from January to December (even though we do
37      ! We assume that in the input file the latitude is in degrees      ! not use values of the input time coordinate).
38      ! and the pressure level is in hPa, and that both are strictly  
39      ! monotonic (as all NetCDF coordinate variables should be).      use dimens_m, only: jjm
40        use dynetat0_m, only: rlatv
41      use dimens_m, only: iim, jjm, llm      use nr_util, only: pi
42      use comgeom, only: rlatv      use numer_rec_95, only: regr3_lint, regr1_conserv, slopes
43      use comconst, only: pi      use netcdf95, only: nf95_open, nf95_gw_var, nf95_close, &
44      use pressure_m, only: p3d, pls           nf95_inq_varid, handle_err, nf95_put_var
45      use regr1_step_av_m, only: regr1_step_av      use netcdf, only: nf90_nowrite, nf90_get_var
     use regr1_lint_m, only: regr1_lint  
     use netcdf95, only: nf95_open, nf90_nowrite, coordin, nf95_close, &  
          nf95_inq_varid, handle_err, nf90_put_var, nf90_get_var  
46    
47      ! Variables local to the procedure:      ! Variables local to the procedure:
48    
49      integer ncid_in, ncid_out ! NetCDF IDs for input and output files      integer ncid_in, ncid_out ! NetCDF IDs for input and output files
   
50      integer n_plev ! number of pressure levels in the input data      integer n_plev ! number of pressure levels in the input data
51      integer n_lat! number of latitudes in the input data      integer n_lat! number of latitudes in the input data
52    
# Line 59  contains Line 57  contains
57      ! (edges of latitude intervals for input data, in rad, in strictly      ! (edges of latitude intervals for input data, in rad, in strictly
58      ! increasing order)      ! increasing order)
59    
60      real, pointer:: plev(:)      real, pointer:: plev(:) ! pressure level of input data
     ! (pressure level of input data, converted to Pa, sorted  
     ! in strictly increasing order)  
   
     real, allocatable:: press_in_edg(:)  
     ! (edges of pressure intervals for input data, in Pa, in strictly  
     ! increasing order)  
   
61      logical decr_lat ! decreasing latitude in the input file      logical decr_lat ! decreasing latitude in the input file
     logical decr_plev ! decreasing pressure level in the input file  
62    
63      real, allocatable:: o3_par_in(:, :, :)      real, allocatable:: o3_par_in(:, :, :) ! (n_lat, n_plev, 12)
64      ! (ozone parameter from the input file)      ! (ozone parameter from the input file)
65      ! ("o3_par_in(j, l, month)" is at latitude "latitude(j)" and pressure      ! ("o3_par_in(j, l, month)" is at latitude "latitude(j)" and pressure
66      ! level "plev(l)". "month" is between 1 and 12.)      ! level "plev(l)". "month" is between 1 and 12.)
67    
68      real o3_par_out(iim + 1, jjm + 1, llm, 12)      real, allocatable:: v_regr_lat(:, :, :) ! (jjm + 1, n_plev, 0:13)
     ! (ozone parameter adapted to the LMDZ grid)  
     ! (Last dimension is month number.  
     ! "o3_par_out(i, j, l, month)" is at longitude "rlonv(i)", latitude  
     ! "rlatu(j)" and pressure level "pls(i, j, l)")  
   
     integer i, j  
     integer i_v ! index of ozone parameter  
     integer, parameter:: n_o3_param = 8 ! number of ozone parameters  
   
     character(len=11) name_in(n_o3_param)  
     ! (name of NetCDF variable in the input file)  
   
     character(len=9) name_out(n_o3_param)  
     ! (name of NetCDF variable in the output file)  
   
     logical:: stepav_choice(n_o3_param) = .true.  
     ! (vertical regridding by step average, otherwise linear interpolation)  
   
     real top_value(n_o3_param)  
     ! (value at 0 pressure, only used for linear interpolation)  
   
     integer varid_in(n_o3_param), varid_out(n_o3_param), ncerr ! for NetCDF  
   
     real, allocatable:: v_regr_lat(:, :, :) ! (jjm + 1, 0:n_plev, 12)  
69      ! (mean of a variable "v" over a latitude interval)      ! (mean of a variable "v" over a latitude interval)
70      ! First dimension is latitude interval.      ! (First dimension is latitude interval.
71      ! The latitude interval for "v_regr_lat(j,:, :)" contains "rlatu(j)".      ! The latitude interval for "v_regr_lat(j,:, :)" contains "rlatu(j)".
72      ! If "j" is between 2 and "jjm" then the interval is:      ! If "j" is between 2 and "jjm" then the interval is:
73      ! [rlatv(j), rlatv(j-1)]      ! [rlatv(j), rlatv(j-1)]
# Line 110  contains Line 76  contains
76      ! or:      ! or:
77      ! [- pi / 2, rlatv(jjm)]      ! [- pi / 2, rlatv(jjm)]
78      ! respectively.      ! respectively.
79      ! "v_regr_lat(:, l, :)" is for pressure interval      ! "v_regr_lat(:, l, :)" is for pressure level "plev(l)".
     ! "[press_in_edg(l), press_in_edg(l+1)]" or pressure level "plev(l)",  
     ! depending on the type of vertical regridding, step average or linear  
     ! interpolation.  
80      ! Last dimension is month number.)      ! Last dimension is month number.)
81    
82        real, allocatable:: o3_par_out(:, :, :) ! (jjm + 1, n_plev, 360)
83        ! (regridded ozone parameter)
84        ! ("o3_par_out(j, l, day)" is at latitude "rlatu(j)", pressure
85        ! level "plev(l)" and date "January 1st 0h" + "tmidday(day)", in a
86        ! 360-day calendar.)
87    
88        integer j
89        integer i_v ! index of ozone parameter
90        integer, parameter:: n_o3_param = 8 ! number of ozone parameters
91    
92        character(len=11) name_in(n_o3_param)
93        ! (name of NetCDF primary variable in the input file)
94    
95        character(len=9) name_out(n_o3_param)
96        ! (name of NetCDF primary variable in the output file)
97    
98        integer varid_in(n_o3_param), varid_out(n_o3_param), varid_plev, varid_time
99        integer ncerr, varid
100        ! (for NetCDF)
101    
102        real, parameter:: tmidmonth(0:13) = (/(-15. + 30. * j, j = 0, 13)/)
103        ! (time to middle of month, in days since January 1st 0h, in a
104        ! 360-day calendar)
105        ! (We add values -15 and 375 so that, for example, day 3 of the year is
106        ! interpolated between the December and the January value.)
107    
108        real, parameter:: tmidday(360) = (/(j + 0.5, j = 0, 359)/)
109        ! (time to middle of day, in days since January 1st 0h, in a
110        ! 360-day calendar)
111    
112      !---------------------------------      !---------------------------------
113    
114      print *, "Call sequence information: regr_coefoz"      print *, "Call sequence information: regr_lat_time_coefoz"
115    
116      ! Details for each ozone parameter:      ! Names of ozone parameters:
117      i_v = 0      i_v = 0
118    
119      i_v = i_v + 1      i_v = i_v + 1
# Line 132  contains Line 125  contains
125      name_out(i_v) = "a2"      name_out(i_v) = "a2"
126    
127      i_v = i_v + 1      i_v = i_v + 1
128      name_in(i_v) = "r"      name_in(i_v) = "tro3"
129      name_out(i_v) = "r_Mob"      name_out(i_v) = "r_Mob"
130    
131      i_v = i_v + 1      i_v = i_v + 1
# Line 150  contains Line 143  contains
143      i_v = i_v + 1      i_v = i_v + 1
144      name_in(i_v) = "Sigma"      name_in(i_v) = "Sigma"
145      name_out(i_v) = "Sigma_Mob"      name_out(i_v) = "Sigma_Mob"
     stepav_choice(i_v) = .false.  
     top_value(i_v) = 0.  
146    
147      i_v = i_v + 1      i_v = i_v + 1
148      name_in(i_v) = "R_Het"      name_in(i_v) = "R_Het"
149      name_out(i_v) = "R_Het"      name_out(i_v) = "R_Het"
150    
151      call nf95_open("coefoz_v2_3.nc", nf90_nowrite, ncid_in)      call nf95_open("coefoz.nc", nf90_nowrite, ncid_in)
152    
153      ! Get coordinates from the input file:      ! Get coordinates from the input file:
154    
155      latitude => coordin(ncid_in, "latitude")      call nf95_inq_varid(ncid_in, "latitude", varid)
156        call nf95_gw_var(ncid_in, varid, latitude)
157      ! Convert from degrees to rad, because "rlatv" is in rad:      ! Convert from degrees to rad, because "rlatv" is in rad:
158      latitude = latitude / 180. * pi      latitude = latitude / 180. * pi
159      n_lat = size(latitude)      n_lat = size(latitude)
160      ! We need to supply the latitudes to "stepav" in      ! We need to supply the latitudes to "regr1_step_av" in
161      ! increasing order, so invert order if necessary:      ! increasing order, so invert order if necessary:
162      decr_lat = latitude(1) > latitude(n_lat)      decr_lat = latitude(1) > latitude(n_lat)
163      if (decr_lat) latitude = latitude(n_lat:1:-1)      if (decr_lat) latitude = latitude(n_lat:1:-1)
# Line 177  contains Line 169  contains
169      lat_in_edg(n_lat + 1) = pi / 2      lat_in_edg(n_lat + 1) = pi / 2
170      deallocate(latitude) ! pointer      deallocate(latitude) ! pointer
171    
172      plev => coordin(ncid_in, "plev")      call nf95_inq_varid(ncid_in, "plev", varid)
173      ! Convert from hPa to Pa because "p3d" and "pls" are in Pa:      call nf95_gw_var(ncid_in, varid, plev)
     plev = plev * 100.  
174      n_plev = size(plev)      n_plev = size(plev)
175      ! We need to supply the pressure levels to "stepav" in      ! (We only need the pressure coordinate to copy it to the output file.)
     ! increasing order, so invert order if necessary:  
     decr_plev = plev(1) > plev(n_plev)  
     if (decr_plev) plev = plev(n_plev:1:-1)  
   
     ! Compute edges of pressure intervals:  
     allocate(press_in_edg(n_plev + 1))  
     press_in_edg(1) = 0.  
     ! We choose edges halfway in logarithm:  
     forall (j = 2:n_plev) press_in_edg(j) = sqrt(plev(j - 1) * plev(j))  
     press_in_edg(n_plev + 1) = huge(0.)  
     ! (infinity, but any value guaranteed to be greater than the  
     ! surface pressure would do)  
176    
177      ! Get the IDs of ozone parameters in the input file:      ! Get the IDs of ozone parameters in the input file:
178      do i_v = 1, n_o3_param      do i_v = 1, n_o3_param
179         call nf95_inq_varid(ncid_in, trim(name_in(i_v)), varid_in(i_v))         call nf95_inq_varid(ncid_in, trim(name_in(i_v)), varid_in(i_v))
180      end do      end do
181    
182      call prepare_out(ncid_in, varid_in, name_out, ncid_out, varid_out)      ! Create the output file and get the variable IDs:
183      allocate(o3_par_in(n_lat, n_plev, 12), v_regr_lat(jjm + 1, 0:n_plev, 12))      call prepare_out(ncid_in, varid_in, n_plev, name_out, ncid_out, &
184             varid_out, varid_plev, varid_time)
185    
186        ! Write remaining coordinate variables:
187        call nf95_put_var(ncid_out, varid_time, tmidday)
188        call nf95_put_var(ncid_out, varid_plev, plev)
189    
190        deallocate(plev) ! pointer
191    
192        allocate(o3_par_in(n_lat, n_plev, 12))
193        allocate(v_regr_lat(jjm + 1, n_plev, 0:13))
194        allocate(o3_par_out(jjm + 1, n_plev, 360))
195    
196      do i_v = 1, n_o3_param      do i_v = 1, n_o3_param
197         ! Process ozone parameter "name_in(i_v)"         ! Process ozone parameter "name_in(i_v)"
# Line 210  contains Line 200  contains
200         call handle_err("nf90_get_var", ncerr, ncid_in)         call handle_err("nf90_get_var", ncerr, ncid_in)
201    
202         if (decr_lat) o3_par_in = o3_par_in(n_lat:1:-1, :, :)         if (decr_lat) o3_par_in = o3_par_in(n_lat:1:-1, :, :)
        if (decr_plev) o3_par_in = o3_par_in(:, n_plev:1:-1, :)  
203    
204         ! Regrid in latitude:         ! Regrid in latitude:
205         ! We average with respect to sine of latitude, which is         ! We average with respect to sine of latitude, which is
206         ! equivalent to weighting by cosine of latitude:         ! equivalent to weighting by cosine of latitude:
207         v_regr_lat(jjm+1:1:-1, 1:, :) = regr1_step_av(o3_par_in, &         call regr1_conserv(o3_par_in, &
208              xs=sin(lat_in_edg), xt=sin((/- pi / 2, rlatv(jjm:1:-1), pi / 2/)))              xs = sin(lat_in_edg), xt = (/- 1., sin(rlatv(jjm:1:-1)), 1./), &
209                slope = slopes(o3_par_in, sin(lat_in_edg)), &
210                vt = v_regr_lat(jjm + 1:1:- 1, :, 1:12))
211         ! (invert order of indices in "v_regr_lat" because "rlatu" is         ! (invert order of indices in "v_regr_lat" because "rlatu" is
212         ! decreasing)         ! decreasing)
213    
214         ! Regrid in pressure at each horizontal position:         ! Duplicate January and December values, in preparation of time
215           ! interpolation:
216         if (stepav_choice(i_v)) then         v_regr_lat(:, :, 0) = v_regr_lat(:, :, 12)
217            ! Regrid in pressure by averaging a step function of pressure         v_regr_lat(:, :, 13) = v_regr_lat(:, :, 1)
   
           ! Poles ("p3d" does not depend on longitude):  
           do j = 1, jjm + 1, jjm  
              ! Average on pressure, only for first longitude:  
              o3_par_out(1, j, llm:1:-1, :) &  
                   = regr1_step_av(v_regr_lat(j, 1:, :), press_in_edg, &  
                   p3d(1, j, llm+1:1:-1))  
              ! (invert order of indices because "p3d" is decreasing)  
           end do  
   
           ! Latitudes other than poles ("p3d" depends on longitude):  
           do j = 2, jjm  
              ! Average on pressure at each longitude:  
              do i = 1, iim  
                 o3_par_out(i, j, llm:1:-1, :) &  
                      = regr1_step_av(v_regr_lat(j, 1:, :), press_in_edg, &  
                      p3d(i, j, llm+1:1:-1))  
                 ! (invert order of indices because "p3d" is decreasing)  
              end do  
           end do  
        else  
           ! Regrid in pressure by linear interpolation  
   
           ! Complete "v_regr_lat" with the value at 0 pressure:  
           v_regr_lat(:, 0, :) = top_value(i_v)  
   
           ! Poles ("pls" does not depend on longitude):  
           do j = 1, jjm + 1, jjm  
              ! Interpolate in pressure, only for first longitude:  
              o3_par_out(1, j, llm:1:-1, :) = regr1_lint(v_regr_lat(j, :, :), &  
                   xs=(/0., plev/), xt=pls(1, j, llm:1:-1))  
              ! (invert order of indices because "pls" is decreasing)  
           end do  
   
           ! Latitudes other than poles ("pls" depends on longitude):  
           do j = 2, jjm  
              ! Average on pressure at each longitude:  
              do i = 1, iim  
                 o3_par_out(i, j, llm:1:-1, :) &  
                      = regr1_lint(v_regr_lat(j, :, :), xs=(/0., plev/), &  
                      xt=pls(i, j, llm:1:-1))  
                 ! (invert order of indices because "pls" is decreasing)  
              end do  
           end do  
        end if  
   
        ! Duplicate pole values on all longitudes:  
        o3_par_out(2:, 1, :, :) &  
             = spread(o3_par_out(1, 1, :, :), dim=1, ncopies=iim)  
        o3_par_out(2:, jjm + 1, :, :) &  
             = spread(o3_par_out(1, jjm + 1, :, :), dim=1, ncopies=iim)  
218    
219         ! Duplicate first longitude to last longitude:         ! Regrid in time by linear interpolation:
220         o3_par_out(iim + 1, 2:jjm, :, :) = o3_par_out(1, 2:jjm, :, :)         o3_par_out = regr3_lint(v_regr_lat, tmidmonth, tmidday)
221    
222         ! Write to file:         ! Write to file:
223           call nf95_put_var(ncid_out, varid_out(i_v), &
224         ncerr = nf90_put_var(ncid_out, varid_out(i_v), &              o3_par_out(jjm+1:1:-1, :, :))
             o3_par_out(:,jjm+1:1:-1, :, :))  
225         ! (The order of "rlatu" is inverted in the output file)         ! (The order of "rlatu" is inverted in the output file)
        call handle_err("nf90_put_var", ncerr, ncid_out)  
226      end do      end do
227    
     deallocate(plev) ! pointer  
228      call nf95_close(ncid_out)      call nf95_close(ncid_out)
229      call nf95_close(ncid_in)      call nf95_close(ncid_in)
230    
231    end subroutine regr_coefoz    end subroutine regr_lat_time_coefoz
232    
233    !********************************************    !********************************************
234    
235    subroutine prepare_out(ncid_in, varid_in, name_out, ncid_out, varid_out)    subroutine prepare_out(ncid_in, varid_in, n_plev, name_out, ncid_out, &
236           varid_out, varid_plev, varid_time)
237    
238      ! This subroutine creates the NetCDF output file, defines      ! This subroutine creates the NetCDF output file, defines
239      ! dimensions and variables, and writes coordinate variables and "pls".      ! dimensions and variables, and writes one of the coordinate variables.
240    
241      use dimens_m, only: iim, jjm, llm      use dimens_m, only: jjm
242      use comgeom, only: rlatu, rlonv      use dynetat0_m, only: rlatu
243      use pressure_m, only: pls      use netcdf, only: nf90_clobber, nf90_float, nf90_copy_att, nf90_global
244      use comconst, only: pi      use netcdf95, only: nf95_create, nf95_def_dim, nf95_def_var, &
245      use nrutil, only: assert_eq           nf95_put_att, nf95_enddef, nf95_copy_att, nf95_put_var
246        use nr_util, only: assert_eq, pi
     use netcdf95, only: nf95_create, nf90_clobber, nf95_def_dim, &  
          nf95_def_var, nf90_float, nf90_int, nf95_put_att, nf95_enddef, &  
          nf90_put_var, handle_err, nf90_copy_att, nf95_copy_att, nf90_global  
247    
248      integer, intent(in):: ncid_in, varid_in(:)      integer, intent(in):: ncid_in, varid_in(:), n_plev
249      character(len=*), intent(in):: name_out(:) ! of NetCDF variables      character(len=*), intent(in):: name_out(:) ! of NetCDF variables
250      integer, intent(out):: ncid_out, varid_out(:)      integer, intent(out):: ncid_out, varid_out(:), varid_plev, varid_time
251    
252      ! Variables local to the procedure:      ! Variables local to the procedure:
253      integer ncerr      integer ncerr
254      integer dimid_rlonv, dimid_rlatu, dimid_sigs, dimid_month      integer dimid_rlatu, dimid_plev, dimid_time
255      integer varid_rlonv, varid_rlatu, varid_sigs, varid_month      integer varid_rlatu
     integer varid_pls  
256      integer i, n_o3_param      integer i, n_o3_param
257    
258      !---------------------------      !---------------------------
# Line 330  contains Line 264  contains
264      call nf95_create("coefoz_LMDZ.nc", nf90_clobber, ncid_out)      call nf95_create("coefoz_LMDZ.nc", nf90_clobber, ncid_out)
265    
266      ! Dimensions:      ! Dimensions:
267      call nf95_def_dim(ncid_out, "month", 12, dimid_month)      call nf95_def_dim(ncid_out, "time", 360, dimid_time)
268      call nf95_def_dim(ncid_out, "sigs", llm, dimid_sigs)      call nf95_def_dim(ncid_out, "plev", n_plev, dimid_plev)
269      call nf95_def_dim(ncid_out, "rlatu", jjm + 1, dimid_rlatu)      call nf95_def_dim(ncid_out, "rlatu", jjm + 1, dimid_rlatu)
     call nf95_def_dim(ncid_out, "rlonv", iim + 1, dimid_rlonv)  
   
     ! Coordinate variables:  
270    
271      call nf95_def_var(ncid_out, "month", nf90_float, dimid_month, varid_month)      ! Define coordinate variables:
     call nf95_put_att(ncid_out, varid_month, "units", &  
          "calendar_month as %m.%f")  
     call nf95_put_att(ncid_out, varid_month, "long_name", "seasonal phase")  
272    
273      call nf95_def_var(ncid_out, "sigs", nf90_int, dimid_sigs, varid_sigs)      call nf95_def_var(ncid_out, "time", nf90_float, dimid_time, varid_time)
274      call nf95_put_att(ncid_out, varid_sigs, "long_name", "s-layer index")      call nf95_put_att(ncid_out, varid_time, "units", "days since 2000-1-1")
275        call nf95_put_att(ncid_out, varid_time, "calendar", "360_day")
276        call nf95_put_att(ncid_out, varid_time, "standard_name", "time")
277    
278        call nf95_def_var(ncid_out, "plev", nf90_float, dimid_plev, varid_plev)
279        call nf95_put_att(ncid_out, varid_plev, "units", "millibar")
280        call nf95_put_att(ncid_out, varid_plev, "standard_name", "air_pressure")
281        call nf95_put_att(ncid_out, varid_plev, "long_name", "air pressure")
282    
283      call nf95_def_var(ncid_out, "rlatu", nf90_float, dimid_rlatu, varid_rlatu)      call nf95_def_var(ncid_out, "rlatu", nf90_float, dimid_rlatu, varid_rlatu)
284      call nf95_put_att(ncid_out, varid_rlatu, "units", "degrees_north")      call nf95_put_att(ncid_out, varid_rlatu, "units", "degrees_north")
285      call nf95_put_att(ncid_out, varid_rlatu, "long_name", "latitude")      call nf95_put_att(ncid_out, varid_rlatu, "standard_name", "latitude")
286    
287      call nf95_def_var(ncid_out, "rlonv", nf90_float, dimid_rlonv, varid_rlonv)      ! Define primary variables:
     call nf95_put_att(ncid_out, varid_rlonv, "units", "degrees_east")  
     call nf95_put_att(ncid_out, varid_rlonv, "long_name", "longitude")  
   
     ! Primary variables:  
   
     call nf95_def_var(ncid_out, "pls", nf90_float, &  
          (/dimid_rlonv, dimid_rlatu, dimid_sigs/), varid_pls)  
     call nf95_put_att(ncid_out, varid_pls, "units", "millibar")  
     call nf95_put_att(ncid_out, varid_pls, "long_name", &  
          "pressure at LMDZ mid-layers")  
288    
289      do i = 1, n_o3_param      do i = 1, n_o3_param
290         call nf95_def_var(ncid_out, name_out(i), nf90_float, &         call nf95_def_var(ncid_out, name_out(i), nf90_float, &
291              (/dimid_rlonv, dimid_rlatu, dimid_sigs, dimid_month/),&              (/dimid_rlatu, dimid_plev, dimid_time/), varid_out(i))
292              & varid_out(i))  
293         ! The following commands may fail. That is OK. It should just         ! The following commands may fail. That is OK. It should just
294         ! mean that the attribute is not defined in the input file.         ! mean that the attribute is not defined in the input file.
295    
296         ncerr = nf90_copy_att(ncid_in, varid_in(i), "long_name",&         ncerr = nf90_copy_att(ncid_in, varid_in(i), "long_name",&
297              & ncid_out, varid_out(i))              & ncid_out, varid_out(i))
298         call handle_err_copy_att("long_name")         call handle_err_copy_att("long_name")
299    
300         ncerr = nf90_copy_att(ncid_in, varid_in(i), "units", ncid_out,&         ncerr = nf90_copy_att(ncid_in, varid_in(i), "units", ncid_out,&
301              & varid_out(i))              & varid_out(i))
302         call handle_err_copy_att("units")         call handle_err_copy_att("units")
303    
304         ncerr = nf90_copy_att(ncid_in, varid_in(i), "standard_name", ncid_out,&         ncerr = nf90_copy_att(ncid_in, varid_in(i), "standard_name", ncid_out,&
305              & varid_out(i))              & varid_out(i))
306         call handle_err_copy_att("standard_name")         call handle_err_copy_att("standard_name")
307      end do      end do
308    
309      ! Global attributes:      ! Global attributes:
310        call nf95_copy_att(ncid_in, nf90_global, "Conventions", ncid_out, &
311             nf90_global)
312      call nf95_copy_att(ncid_in, nf90_global, "title", ncid_out, nf90_global)      call nf95_copy_att(ncid_in, nf90_global, "title", ncid_out, nf90_global)
313      call nf95_copy_att(ncid_in, nf90_global, "source", ncid_out, nf90_global)      call nf95_copy_att(ncid_in, nf90_global, "source", ncid_out, nf90_global)
314      call nf95_put_att(ncid_out, nf90_global, "comment", "Regridded for LMDZ")      call nf95_put_att(ncid_out, nf90_global, "comment", "Regridded for LMDZ")
315    
316      call nf95_enddef(ncid_out)      call nf95_enddef(ncid_out)
317    
318      ! Coordinate variables:      ! Write one of the coordinate variables:
319        call nf95_put_var(ncid_out, varid_rlatu, rlatu(jjm+1:1:-1) / pi * 180.)
     ncerr = nf90_put_var(ncid_out, varid_month, (/(i + 0.5, i = 1, 12)/))  
     call handle_err("nf90_put_var", ncerr, ncid_out)  
   
     ncerr = nf90_put_var(ncid_out, varid_sigs, (/(i, i = 1, llm)/))  
     call handle_err("nf90_put_var", ncerr, ncid_out)  
   
     ncerr = nf90_put_var(ncid_out, varid_rlatu, rlatu(jjm+1:1:-1) / pi * 180.)  
320      ! (convert from rad to degrees and sort in increasing order)      ! (convert from rad to degrees and sort in increasing order)
     call handle_err("nf90_put_var", ncerr, ncid_out)  
   
     ncerr = nf90_put_var(ncid_out, varid_rlonv, rlonv / pi * 180.)  
     ! (convert from rad to degrees)  
     call handle_err("nf90_put_var", ncerr, ncid_out)  
   
     ! Primary variable:  
   
     ncerr = nf90_put_var(ncid_out, varid_pls, pls(:, jjm+1:1:-1, :) / 100.)  
     ! (convert from Pa to hPa)  
     call handle_err("nf90_put_var", ncerr, ncid_out)  
321    
322    contains    contains
323    
324      subroutine handle_err_copy_att(att_name)      subroutine handle_err_copy_att(att_name)
325    
326        use netcdf95, only: nf90_noerr, nf90_strerror        use netcdf, only: nf90_noerr, nf90_strerror
327    
328        character(len=*), intent(in):: att_name        character(len=*), intent(in):: att_name
329    
# Line 427  contains Line 339  contains
339    
340    end subroutine prepare_out    end subroutine prepare_out
341    
342  end module regr_coefoz_m  end module regr_lat_time_coefoz_m

Legend:
Removed from v.4  
changed lines
  Added in v.179

  ViewVC Help
Powered by ViewVC 1.1.21