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

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

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

trunk/libf/phylmd/Mobidic/regr_pr_o3.f90 revision 10 by guez, Fri Apr 18 14:45:53 2008 UTC trunk/phylmd/Mobidic/regr_pr_o3.f90 revision 328 by guez, Thu Jun 13 14:40:06 2019 UTC
# Line 4  module regr_pr_o3_m Line 4  module regr_pr_o3_m
4    
5  contains  contains
6    
7    subroutine regr_pr_o3(o3_mob_regr)    subroutine regr_pr_o3(p3d, o3_mob_regr)
8    
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 dimensions, only: iim, jjm, llm
26      use dimens_m, only: iim, jjm, llm      use dynetat0_chosen_m, only: day_ref
27      use netcdf95, only: nf95_open, nf95_close, nf95_inq_varid, handle_err, &      use grid_change, only: dyn_phy
28           nf95_get_coord      use netcdf, only:  nf90_nowrite
29      use netcdf, only:  nf90_nowrite, nf90_get_var      use netcdf95, only: nf95_open, nf95_close, nf95_inq_varid, nf95_get_var, &
30      use regr_pr, only: regr_pr_av           nf95_gw_var
31      use nrutil, only: assert      use nr_util, only: assert
32        use numer_rec_95, only: regr1_step_av
33    
34        REAL, intent(in):: p3d(:, :, :) ! (iim + 1, jjm + 1, llm+1)
35        ! pressure at layer interfaces, in Pa
36        ! ("p3d(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)",
37        ! for interface "l")
38    
39      real, intent(out):: o3_mob_regr(:, :, :) ! (iim + 1, jjm + 1, llm)      real, intent(out):: o3_mob_regr(:, :, :) ! (iim + 1, jjm + 1, llm)
40      ! (ozone mole fraction from Mobidic adapted to the LMDZ grid)      ! (ozone mole fraction from Mobidic adapted to the LMDZ grid)
# Line 28  contains Line 43  contains
43    
44      ! Variables local to the procedure:      ! Variables local to the procedure:
45    
46      real, pointer:: plev(:)      real, allocatable:: plev(:)
47      ! (pressure levels of Mobidic data, in Pa, in strictly increasing order)      ! (pressure levels of Mobidic data, in Pa, in strictly increasing order)
48    
49      real, allocatable:: press_in_edg(:)      real, allocatable:: press_in_edg(:)
50      ! (edges of pressure intervals for Mobidic data, in Pa, in strictly      ! (edges of pressure intervals for Mobidic data, in Pa, in strictly
51      ! increasing order)      ! increasing order)
52    
53      integer ncid, varid, ncerr ! for NetCDF      integer ncid, varid ! for NetCDF
54      integer n_plev ! number of pressure levels in Mobidic data      integer n_plev ! number of pressure levels in Mobidic data
55      integer j      integer i, j
56    
57      real, allocatable:: r_mob(:, :)! (jjm + 1, n_plev)      real, allocatable:: r_mob(:, :)! (jjm + 1, n_plev)
58      ! (ozone mole fraction from Mobidic at day "dayref")      ! (ozone mole fraction from Mobidic at day "day_ref")
59      ! (r_mob(j, k) is at latitude "rlatu(j)" and pressure level "plev(k)".)      ! (r_mob(j, k) is at latitude "rlatu(j)" and pressure level "plev(k)".)
60    
61      !------------------------------------------------------------      !------------------------------------------------------------
62    
63      print *, "Call sequence information: regr_pr_o3"      print *, "Call sequence information: regr_pr_o3"
64      call assert(shape(o3_mob_regr) == (/iim + 1, jjm + 1, llm/), "regr_pr_o3")  
65        call assert(shape(o3_mob_regr) == (/iim + 1, jjm + 1, llm/), &
66             "regr_pr_o3 o3_mob_regr")
67        call assert(shape(p3d) == (/iim + 1, jjm + 1, llm + 1/), &
68             "regr_pr_o3 p3d")
69    
70      call nf95_open("coefoz_LMDZ.nc", nf90_nowrite, ncid)      call nf95_open("coefoz_LMDZ.nc", nf90_nowrite, ncid)
71    
72      call nf95_get_coord(ncid, "plev", plev)      call nf95_inq_varid(ncid, "plev", varid)
73        call nf95_gw_var(ncid, varid, plev)
74      ! Convert from hPa to Pa because "regr_pr_av" requires so:      ! Convert from hPa to Pa because "regr_pr_av" requires so:
75      plev = plev * 100.      plev = plev * 100.
76      n_plev = size(plev)      n_plev = size(plev)
# Line 64  contains Line 84  contains
84      ! (infinity, but any value guaranteed to be greater than the      ! (infinity, but any value guaranteed to be greater than the
85      ! surface pressure would do)      ! surface pressure would do)
86    
     deallocate(plev) ! pointer  
   
87      call nf95_inq_varid(ncid, "r_Mob", varid)      call nf95_inq_varid(ncid, "r_Mob", varid)
88      allocate(r_mob(jjm + 1, n_plev))      allocate(r_mob(jjm + 1, n_plev))
89    
90      ! Get data at the right day from the input file:      ! Get data at the right day from the input file:
91      ncerr = nf90_get_var(ncid, varid, r_mob, start=(/1, 1, dayref/))      call nf95_get_var(ncid, varid, r_mob, start=(/1, 1, day_ref/))
     call handle_err("nf90_get_var r_Mob", ncerr)  
92      ! Latitudes are in increasing order in the input file while      ! Latitudes are in increasing order in the input file while
93      ! "rlatu" is in decreasing order so we need to invert order:      ! "rlatu" is in decreasing order so we need to invert order:
94      r_mob = r_mob(jjm+1:1:-1, :)      r_mob = r_mob(jjm+1:1:-1, :)
95    
96      call nf95_close(ncid)      call nf95_close(ncid)
97    
98      o3_mob_regr = regr_pr_av(r_mob, press_in_edg)      ! Regrid in pressure by averaging a step function of pressure:
99        do j = 1, jjm + 1
100           do i = 1, iim
101              if (dyn_phy(i, j)) then
102                 o3_mob_regr(i, j, llm:1:-1) &
103                      = regr1_step_av(r_mob(j, :), press_in_edg, &
104                      p3d(i, j, llm+1:1:-1))
105                 ! (invert order of indices because "p3d" is decreasing)
106              end if
107           end do
108        end do
109    
110        ! Duplicate pole values on all longitudes:
111        o3_mob_regr(2:, 1, :) = spread(o3_mob_regr(1, 1, :), dim=1, ncopies=iim)
112        o3_mob_regr(2:, jjm + 1, :) &
113             = spread(o3_mob_regr(1, jjm + 1, :), dim=1, ncopies=iim)
114    
115        ! Duplicate first longitude to last longitude:
116        o3_mob_regr(iim + 1, 2:jjm, :) = o3_mob_regr(1, 2:jjm, :)
117    
118    end subroutine regr_pr_o3    end subroutine regr_pr_o3
119    

Legend:
Removed from v.10  
changed lines
  Added in v.328

  ViewVC Help
Powered by ViewVC 1.1.21