/[lmdze]/trunk/libf/phylmd/Mobidic/regr_pr_o3.f90
ViewVC logotype

Diff of /trunk/libf/phylmd/Mobidic/regr_pr_o3.f90

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

revision 18 by guez, Fri Jul 25 19:59:34 2008 UTC revision 19 by guez, Thu Aug 7 15:46:20 2008 UTC
# Line 9  contains Line 9  contains
9      ! "regr_pr_o3" stands for "regrid pressure ozone".      ! "regr_pr_o3" stands for "regrid pressure ozone".
10      ! This procedure reads Mobidic ozone mole fraction from      ! This procedure reads Mobidic ozone mole fraction from
11      ! "coefoz_LMDZ.nc" at the initial day and regrids it in pressure.      ! "coefoz_LMDZ.nc" at the initial day and regrids it in pressure.
12        ! Ozone mole fraction from "coefoz_LMDZ.nc" is a 2D latitude --
13        ! pressure variable.
14        ! The target horizontal LMDZ grid is the "scalar" grid: "rlonv", "rlatu".
15        ! The target vertical LMDZ grid is the grid of layer boundaries.
16        ! We assume that the input variable is already on the LMDZ "rlatu"
17        ! latitude grid.
18        ! The input variable does not depend on longitude, but the
19        ! pressure at LMDZ layers does.
20        ! Therefore, the values on the LMDZ grid do depend on longitude.
21      ! Regridding is by averaging, assuming a step function.      ! Regridding is by averaging, assuming a step function.
22      ! We assume that, in the input file, the pressure levels are in hPa      ! We assume that, in the input file, the pressure levels are in
23      ! and strictly increasing.      ! hPa and strictly increasing.
24    
25      use conf_gcm_m, only: dayref      use conf_gcm_m, only: dayref
26      use dimens_m, only: iim, jjm, llm      use dimens_m, only: iim, jjm, llm
27      use netcdf95, only: nf95_open, nf95_close, nf95_inq_varid, handle_err, &      use netcdf95, only: nf95_open, nf95_close, nf95_inq_varid, handle_err, &
28           nf95_get_coord           nf95_get_coord
29      use netcdf, only:  nf90_nowrite, nf90_get_var      use netcdf, only:  nf90_nowrite, nf90_get_var
     use regr_pr, only: regr_pr_av  
30      use numer_rec, only: assert      use numer_rec, only: assert
31        use grid_change, only: dyn_phy
32        use regr1_step_av_m, only: regr1_step_av
33        use pressure_var, only: p3d
34    
35      real, intent(out):: o3_mob_regr(:, :, :) ! (iim + 1, jjm + 1, llm)      real, intent(out):: o3_mob_regr(:, :, :) ! (iim + 1, jjm + 1, llm)
36      ! (ozone mole fraction from Mobidic adapted to the LMDZ grid)      ! (ozone mole fraction from Mobidic adapted to the LMDZ grid)
# Line 37  contains Line 48  contains
48    
49      integer ncid, varid, ncerr ! for NetCDF      integer ncid, varid, ncerr ! for NetCDF
50      integer n_plev ! number of pressure levels in Mobidic data      integer n_plev ! number of pressure levels in Mobidic data
51      integer j      integer i, j
52    
53      real, allocatable:: r_mob(:, :)! (jjm + 1, n_plev)      real, allocatable:: r_mob(:, :)! (jjm + 1, n_plev)
54      ! (ozone mole fraction from Mobidic at day "dayref")      ! (ozone mole fraction from Mobidic at day "dayref")
# Line 78  contains Line 89  contains
89    
90      call nf95_close(ncid)      call nf95_close(ncid)
91    
92      o3_mob_regr = regr_pr_av(r_mob, press_in_edg)      ! Regrid in pressure by averaging a step function of pressure.
93        do j = 1, jjm + 1
94           do i = 1, iim
95              if (dyn_phy(i, j)) then
96                 o3_mob_regr(i, j, llm:1:-1) &
97                      = regr1_step_av(r_mob(j, :), press_in_edg, &
98                      p3d(i, j, llm+1:1:-1))
99                 ! (invert order of indices because "p3d" is decreasing)
100              end if
101           end do
102        end do
103    
104        ! Duplicate pole values on all longitudes:
105        o3_mob_regr(2:, 1, :) = spread(o3_mob_regr(1, 1, :), dim=1, ncopies=iim)
106        o3_mob_regr(2:, jjm + 1, :) &
107             = spread(o3_mob_regr(1, jjm + 1, :), dim=1, ncopies=iim)
108    
109        ! Duplicate first longitude to last longitude:
110        o3_mob_regr(iim + 1, 2:jjm, :) = o3_mob_regr(1, 2:jjm, :)
111    
112    end subroutine regr_pr_o3    end subroutine regr_pr_o3
113    

Legend:
Removed from v.18  
changed lines
  Added in v.19

  ViewVC Help
Powered by ViewVC 1.1.21