/[lmdze]/trunk/libf/dyn3d/regr_coefoz.f90
ViewVC logotype

Diff of /trunk/libf/dyn3d/regr_coefoz.f90

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

revision 3 by guez, Wed Feb 27 13:16:39 2008 UTC revision 4 by guez, Thu Feb 28 18:05:06 2008 UTC
# Line 1  Line 1 
1  module regr_coefoz_m  module regr_coefoz_m
2    
3    ! This module is clean: no C preprocessor directive, no include line.    ! This module is clean: no C preprocessor directive, no include line.
4      ! Author: Lionel GUEZ
5    
6    implicit none    implicit none
7    
# Line 33  contains Line 34  contains
34    
35      ! We assume that in the input file the latitude is in degrees      ! We assume that in the input file the latitude is in degrees
36      ! and the pressure level is in hPa, and that both are strictly      ! and the pressure level is in hPa, and that both are strictly
37      ! monotonic.      ! monotonic (as all NetCDF coordinate variables should be).
38    
39      use dimens_m, only: iim, jjm, llm      use dimens_m, only: iim, jjm, llm
40      use comgeom, only: rlatv      use comgeom, only: rlatv
# Line 85  contains Line 86  contains
86      integer, parameter:: n_o3_param = 8 ! number of ozone parameters      integer, parameter:: n_o3_param = 8 ! number of ozone parameters
87    
88      character(len=11) name_in(n_o3_param)      character(len=11) name_in(n_o3_param)
89        ! (name of NetCDF variable in the input file)
90    
91      character(len=9) name_out(n_o3_param)      character(len=9) name_out(n_o3_param)
92        ! (name of NetCDF variable in the output file)
93    
94      logical:: stepav_choice(n_o3_param) = .true.      logical:: stepav_choice(n_o3_param) = .true.
95      ! (vertical regridding by step avergage, otherwise linear interpolation)      ! (vertical regridding by step average, otherwise linear interpolation)
96    
97      real top_value(n_o3_param)      real top_value(n_o3_param)
98      ! (value at 0 pressure, only used for linear interpolation)      ! (value at 0 pressure, only used for linear interpolation)
99    
100      integer varid_in(n_o3_param), varid_out(n_o3_param), ncerr ! for NetCDF      integer varid_in(n_o3_param), varid_out(n_o3_param), ncerr ! for NetCDF
101    
102      real, allocatable:: v_regr_lat(:, :, :)      real, allocatable:: v_regr_lat(:, :, :) ! (jjm + 1, 0:n_plev, 12)
103      ! (mean of "v" over a latitude interval)      ! (mean of a variable "v" over a latitude interval)
104      ! First dimension is latitude interval.      ! First dimension is latitude interval.
105      ! The latitude interval for "v_regr_lat(j,:, :)" contains "rlatu(j)".      ! The latitude interval for "v_regr_lat(j,:, :)" contains "rlatu(j)".
106      ! If "j" is between 2 and "jjm" then the interval is:      ! If "j" is between 2 and "jjm" then the interval is:
# Line 159  contains Line 163  contains
163    
164      latitude => coordin(ncid_in, "latitude")      latitude => coordin(ncid_in, "latitude")
165      ! Convert from degrees to rad, because "rlatv" is in rad:      ! Convert from degrees to rad, because "rlatv" is in rad:
166      latitude(:) = latitude(:) / 180. * pi      latitude = latitude / 180. * pi
167      n_lat = size(latitude)      n_lat = size(latitude)
168      ! We need to supply the latitudes to "stepav" in      ! We need to supply the latitudes to "stepav" in
169      ! increasing order, so invert order if necessary:      ! increasing order, so invert order if necessary:
170      decr_lat = latitude(1) > latitude(n_lat)      decr_lat = latitude(1) > latitude(n_lat)
171      if (decr_lat) latitude(:) = latitude(n_lat:1:-1)      if (decr_lat) latitude = latitude(n_lat:1:-1)
172    
173      ! Compute edges of latitude intervals:      ! Compute edges of latitude intervals:
174      allocate(lat_in_edg(n_lat + 1))      allocate(lat_in_edg(n_lat + 1))
# Line 174  contains Line 178  contains
178      deallocate(latitude) ! pointer      deallocate(latitude) ! pointer
179    
180      plev => coordin(ncid_in, "plev")      plev => coordin(ncid_in, "plev")
181      ! Convert from hPa to Pa because "p3d" is in Pa:      ! Convert from hPa to Pa because "p3d" and "pls" are in Pa:
182      plev(:) = plev(:) * 100.      plev = plev * 100.
183      n_plev = size(plev)      n_plev = size(plev)
184      ! We need to supply the pressure levels to "stepav" in      ! We need to supply the pressure levels to "stepav" in
185      ! increasing order, so invert order if necessary:      ! increasing order, so invert order if necessary:
186      decr_plev = plev(1) > plev(n_plev)      decr_plev = plev(1) > plev(n_plev)
187      if (decr_plev) plev(:) = plev(n_plev:1:-1)      if (decr_plev) plev = plev(n_plev:1:-1)
188    
189      ! Compute edges of pressure intervals:      ! Compute edges of pressure intervals:
190      allocate(press_in_edg(n_plev + 1))      allocate(press_in_edg(n_plev + 1))
# Line 213  contains Line 217  contains
217         ! equivalent to weighting by cosine of latitude:         ! equivalent to weighting by cosine of latitude:
218         v_regr_lat(jjm+1:1:-1, 1:, :) = regr1_step_av(o3_par_in, &         v_regr_lat(jjm+1:1:-1, 1:, :) = regr1_step_av(o3_par_in, &
219              xs=sin(lat_in_edg), xt=sin((/- pi / 2, rlatv(jjm:1:-1), pi / 2/)))              xs=sin(lat_in_edg), xt=sin((/- pi / 2, rlatv(jjm:1:-1), pi / 2/)))
220         ! (invert order of indices because "rlatu" is decreasing)         ! (invert order of indices in "v_regr_lat" because "rlatu" is
221           ! decreasing)
222    
223         ! Regrid in pressure at each horizontal position:         ! Regrid in pressure at each horizontal position:
224    
# Line 293  contains Line 298  contains
298    subroutine prepare_out(ncid_in, varid_in, name_out, ncid_out, varid_out)    subroutine prepare_out(ncid_in, varid_in, name_out, ncid_out, varid_out)
299    
300      ! This subroutine creates the NetCDF output file, defines      ! This subroutine creates the NetCDF output file, defines
301      ! dimensions and variables, writes coordinate variables and "pls".      ! dimensions and variables, and writes coordinate variables and "pls".
302    
303      use dimens_m, only: iim, jjm, llm      use dimens_m, only: iim, jjm, llm
304      use comgeom, only: rlatu, rlonv      use comgeom, only: rlatu, rlonv
# Line 392  contains Line 397  contains
397      ! (convert from rad to degrees and sort in increasing order)      ! (convert from rad to degrees and sort in increasing order)
398      call handle_err("nf90_put_var", ncerr, ncid_out)      call handle_err("nf90_put_var", ncerr, ncid_out)
399    
400      ncerr = nf90_put_var(ncid_out, varid_rlonv, rlonv(:) / pi * 180.)      ncerr = nf90_put_var(ncid_out, varid_rlonv, rlonv / pi * 180.)
401      ! (convert from rad to degrees)      ! (convert from rad to degrees)
402      call handle_err("nf90_put_var", ncerr, ncid_out)      call handle_err("nf90_put_var", ncerr, ncid_out)
403    

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

  ViewVC Help
Powered by ViewVC 1.1.21