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

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

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

revision 19 by guez, Thu Aug 7 15:46:20 2008 UTC revision 36 by guez, Thu Dec 2 17:11:04 2010 UTC
# Line 21  contains Line 21  contains
21      ! The input data does not depend on longitude, but the pressure      ! The input data does not depend on longitude, but the pressure
22      ! at LMDZ layers does.      ! at LMDZ layers does.
23      ! Therefore, the values on the LMDZ grid do depend on longitude.      ! Therefore, the values on the LMDZ grid do depend on longitude.
24      ! Regridding in pressure is done by averaging a step function.      ! Regridding in pressure is done by averaging a step function of pressure.
25    
26      use dimens_m, only: iim, jjm, llm      use dimens_m, only: iim, jjm, llm
27      use dimphy, only: klon      use dimphy, only: klon
28      use netcdf95, only: nf95_inq_varid, handle_err      use netcdf95, only: nf95_inq_varid, handle_err
29      use netcdf, only: nf90_get_var      use netcdf, only: nf90_get_var
30      use grid_change, only: dyn_phy      use grid_change, only: dyn_phy
31      use numer_rec, only: assert      use nr_util, only: assert
32      use press_coefoz_m, only: press_in_edg      use press_coefoz_m, only: press_in_edg
33      use regr1_step_av_m, only: regr1_step_av      use regr1_step_av_m, only: regr1_step_av
34      use pressure_var, only: p3d      use pressure_var, only: p3d
# Line 40  contains Line 40  contains
40      real, intent(out):: v3(:, :) ! (klon, llm)      real, intent(out):: v3(:, :) ! (klon, llm)
41      ! (ozone coefficient from Mobidic on the "physics" grid)      ! (ozone coefficient from Mobidic on the "physics" grid)
42      ! ("v3(i, k)" is at longitude "xlon(i)", latitude      ! ("v3(i, k)" is at longitude "xlon(i)", latitude
43      ! "xlat(i)", middle of layer "k".)      ! "xlat(i)", in layer "k".)
44    
45      ! Variables local to the procedure:      ! Variables local to the procedure:
46      integer varid, ncerr  
47      integer i, j, k      integer varid, ncerr ! for NetCDF
48    
49      real  v1(jjm + 1, size(press_in_edg) - 1)      real  v1(jjm + 1, size(press_in_edg) - 1)
50      ! (ozone coefficient from "coefoz_LMDZ.nc" at day "julien")      ! (ozone coefficient from "coefoz_LMDZ.nc" at day "julien")
# Line 52  contains Line 52  contains
52      ! pressure interval "[press_in_edg(k), press_in_edg(k+1)]".)      ! pressure interval "[press_in_edg(k), press_in_edg(k+1)]".)
53    
54      real v2(iim + 1, jjm + 1, llm)      real v2(iim + 1, jjm + 1, llm)
55      ! (ozone coefficient from Mobidic on the "dynamics" grid)      ! (ozone coefficient on the "dynamics" grid)
56      ! "v2(i, j, k)" is at longitude "rlonv(i)", latitude      ! ("v2(i, j, k)" is at longitude "rlonv(i)", latitude
57      ! "rlatu(j)", middle of layer "k".)      ! "rlatu(j)" and for pressure interval "[p3d(i, j, k+1), p3d(i, j, k)]".)
58    
59        integer i, j, k
60    
61      !--------------------------------------------      !--------------------------------------------
62    
# Line 65  contains Line 67  contains
67      ! Get data at the right day from the input file:      ! Get data at the right day from the input file:
68      ncerr = nf90_get_var(ncid, varid, v1, start=(/1, 1, julien/))      ncerr = nf90_get_var(ncid, varid, v1, start=(/1, 1, julien/))
69      call handle_err("regr_pr_av_coefoz nf90_get_var " // name, ncerr, ncid)      call handle_err("regr_pr_av_coefoz nf90_get_var " // name, ncerr, ncid)
70      ! Latitudes are in increasing order in the input file while      ! Latitudes are in ascending order in the input file while
71      ! "rlatu" is in decreasing order so we need to invert order:      ! "rlatu" is in descending order so we need to invert order:
72      v1 = v1(jjm+1:1:-1, :)      v1 = v1(jjm+1:1:-1, :)
73    
74      ! Regrid in pressure at each horizontal position:      ! Regrid in pressure at each horizontal position:
# Line 76  contains Line 78  contains
78               v2(i, j, llm:1:-1) &               v2(i, j, llm:1:-1) &
79                    = regr1_step_av(v1(j, :), press_in_edg, &                    = regr1_step_av(v1(j, :), press_in_edg, &
80                    p3d(i, j, llm+1:1:-1))                    p3d(i, j, llm+1:1:-1))
81               ! (invert order of indices because "p3d" is decreasing)               ! (invert order of indices because "p3d" is in descending order)
82            end if            end if
83         end do         end do
84      end do      end do
# Line 102  contains Line 104  contains
104      use netcdf95, only: nf95_inq_varid, handle_err      use netcdf95, only: nf95_inq_varid, handle_err
105      use netcdf, only: nf90_get_var      use netcdf, only: nf90_get_var
106      use grid_change, only: dyn_phy      use grid_change, only: dyn_phy
107      use numer_rec, only: assert      use nr_util, only: assert
108      use press_coefoz_m, only: plev      use press_coefoz_m, only: plev
109      use regr1_lint_m, only: regr1_lint      use regr1_lint_m, only: regr1_lint
110      use pressure_var, only: pls      use pressure_var, only: pls
# Line 120  contains Line 122  contains
122      ! "xlat(i)", middle of layer "k".)      ! "xlat(i)", middle of layer "k".)
123    
124      ! Variables local to the procedure:      ! Variables local to the procedure:
125      integer varid, ncerr  
126      integer i, j, k      integer varid, ncerr ! for NetCDF
127    
128      real  v1(jjm + 1, 0:size(plev))      real  v1(jjm + 1, 0:size(plev))
129      ! (ozone coefficient from "coefoz_LMDZ.nc" at day "julien")      ! (ozone coefficient from "coefoz_LMDZ.nc" at day "julien")
130      ! ("v1(j, k >=1)" is at latitude "rlatu(j)" and pressure "plev(k)".)      ! ("v1(j, k >=1)" is at latitude "rlatu(j)" and pressure "plev(k)".)
131    
132      real v2(iim + 1, jjm + 1, llm)      real v2(iim + 1, jjm + 1, llm)
133      ! (ozone coefficient from Mobidic on the "dynamics" grid)      ! (ozone coefficient on the "dynamics" grid)
134      ! "v2(i, j, k)" is at longitude "rlonv(i)", latitude      ! "v2(i, j, k)" is at longitude "rlonv(i)", latitude
135      ! "rlatu(j)", middle of layer "k".)      ! "rlatu(j)" and pressure "pls(i, j, k)".)
136    
137        integer i, j, k
138    
139      !--------------------------------------------      !--------------------------------------------
140    
# Line 141  contains Line 145  contains
145      ! Get data at the right day from the input file:      ! Get data at the right day from the input file:
146      ncerr = nf90_get_var(ncid, varid, v1(:, 1:), start=(/1, 1, julien/))      ncerr = nf90_get_var(ncid, varid, v1(:, 1:), start=(/1, 1, julien/))
147      call handle_err("regr_pr_int_coefoz nf90_get_var " // name, ncerr, ncid)      call handle_err("regr_pr_int_coefoz nf90_get_var " // name, ncerr, ncid)
148      ! Latitudes are in increasing order in the input file while      ! Latitudes are in ascending order in the input file while
149      ! "rlatu" is in decreasing order so we need to invert order:      ! "rlatu" is in descending order so we need to invert order:
150      v1(:, 1:) = v1(jjm+1:1:-1, 1:)      v1(:, 1:) = v1(jjm+1:1:-1, 1:)
151    
152      ! Complete "v1" with the value at 0 pressure:      ! Complete "v1" with the value at 0 pressure:
# Line 154  contains Line 158  contains
158            if (dyn_phy(i, j)) then            if (dyn_phy(i, j)) then
159               v2(i, j, llm:1:-1) &               v2(i, j, llm:1:-1) &
160                    = regr1_lint(v1(j, :), (/0., plev/), pls(i, j, llm:1:-1))                    = regr1_lint(v1(j, :), (/0., plev/), pls(i, j, llm:1:-1))
161               ! (invert order of indices because "pls" is decreasing)               ! (invert order of indices because "pls" is in descending order)
162            end if            end if
163         end do         end do
164      end do      end do

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

  ViewVC Help
Powered by ViewVC 1.1.21