/[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

trunk/libf/phylmd/o3_mob_ph_m.f90 revision 7 by guez, Mon Mar 31 12:24:17 2008 UTC trunk/libf/phylmd/Mobidic/regr_pr_coefoz.f90 revision 19 by guez, Thu Aug 7 15:46:20 2008 UTC
# Line 1  Line 1 
1  module regr_pr_coefoz  module regr_pr_coefoz
2    
3      ! Both procedures of this module read a single Mobidic ozone
4      ! coefficient from "coefoz_LMDZ.nc", at the current day, regrid this
5      ! coefficient in pressure to the LMDZ vertical grid and pack it to the LMDZ
6      ! horizontal "physics" grid.
7      ! The input data is a 2D latitude -- pressure field.
8      ! The target horizontal LMDZ grid is the "scalar" grid: "rlonv", "rlatu".
9      ! We assume that the input data is already on the LMDZ "rlatu"
10      ! latitude grid.
11    
12    implicit none    implicit none
13    
14  contains  contains
15    
16    subroutine regr_pr_av_coefoz(ncid, name, julien, press_in_edg, v3)    subroutine regr_pr_av_coefoz(ncid, name, julien, v3)
17    
18      ! "regr_pr_av_coefoz" stands for "regrid pressure averaging      ! "regr_pr_av_coefoz" stands for "regrid pressure averaging
19      ! coefficients ozone".      ! coefficient ozone".
20      ! This procedure reads a single Mobidic ozone coefficient from      ! The target vertical LMDZ grid is the grid of layer boundaries.
21      !"coefoz_LMDZ.nc", at the current day, regrids this parameter in      ! The input data does not depend on longitude, but the pressure
22      ! pressure to the LMDZ vertical grid and packs it to the LMDZ      ! at LMDZ layers does.
23      ! horizontal "physics" grid.      ! Therefore, the values on the LMDZ grid do depend on longitude.
24      ! Regridding is by averaging a step function.      ! Regridding in pressure is done by averaging a step function.
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 regr_pr, only: regr_pr_av      use numer_rec, only: assert
32      use nrutil, only: assert      use press_coefoz_m, only: press_in_edg
33        use regr1_step_av_m, only: regr1_step_av
34        use pressure_var, only: p3d
35    
36      integer, intent(in):: ncid ! NetCDF ID of the file      integer, intent(in):: ncid ! NetCDF ID of the file
37      character(len=*), intent(in):: name ! of the NetCDF variable      character(len=*), intent(in):: name ! of the NetCDF variable
38      integer, intent(in):: julien ! jour julien, 1 <= julien <= 360      integer, intent(in):: julien ! jour julien, 1 <= julien <= 360
39    
     real, intent(in):: press_in_edg(:)  
     ! (edges of pressure intervals for Mobidic data, in Pa, in  
     ! strictly increasing order)  
   
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
# Line 37  contains Line 44  contains
44    
45      ! Variables local to the procedure:      ! Variables local to the procedure:
46      integer varid, ncerr      integer varid, ncerr
47      integer k      integer i, j, k
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 45  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 parameter from Mobidic on the "dynamics" grid)      ! (ozone coefficient from Mobidic 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)", middle of layer "k".)
58    
# Line 63  contains Line 70  contains
70      v1 = v1(jjm+1:1:-1, :)      v1 = v1(jjm+1:1:-1, :)
71    
72      ! Regrid in pressure at each horizontal position:      ! Regrid in pressure at each horizontal position:
73      v2 = regr_pr_av(v1, press_in_edg)      do j = 1, jjm + 1
74           do i = 1, iim
75              if (dyn_phy(i, j)) then
76                 v2(i, j, llm:1:-1) &
77                      = regr1_step_av(v1(j, :), press_in_edg, &
78                      p3d(i, j, llm+1:1:-1))
79                 ! (invert order of indices because "p3d" is decreasing)
80              end if
81           end do
82        end do
83    
84      forall (k = 1:llm) v3(:, k) = pack(v2(:, :, k), dyn_phy)      forall (k = 1:llm) v3(:, k) = pack(v2(:, :, k), dyn_phy)
85    
# Line 71  contains Line 87  contains
87    
88    !***************************************************************    !***************************************************************
89    
90    subroutine regr_pr_int_coefoz(ncid, name, julien, plev, top_value, v3)    subroutine regr_pr_int_coefoz(ncid, name, julien, top_value, v3)
91    
92      ! This procedure reads a single Mobidic ozone coefficient from      ! "regr_pr_int_coefoz" stands for "regrid pressure interpolation
93      !"coefoz_LMDZ.nc", at the current day, regrids this parameter in      ! coefficient ozone".
94      ! pressure to the LMDZ vertical grid and packs it to the LMDZ      ! The target vertical LMDZ grid is the grid of mid-layers.
95      ! horizontal "physics" grid.      ! The input data does not depend on longitude, but the pressure
96        ! at LMDZ mid-layers does.
97        ! Therefore, the values on the LMDZ grid do depend on longitude.
98      ! Regridding is by linear interpolation.      ! Regridding is by linear interpolation.
99    
100      use dimens_m, only: iim, jjm, llm      use dimens_m, only: iim, jjm, llm
# Line 84  contains Line 102  contains
102      use netcdf95, only: nf95_inq_varid, handle_err      use netcdf95, only: nf95_inq_varid, handle_err
103      use netcdf, only: nf90_get_var      use netcdf, only: nf90_get_var
104      use grid_change, only: dyn_phy      use grid_change, only: dyn_phy
105      use regr_pr, only: regr_pr_int      use numer_rec, only: assert
106      use nrutil, only: assert      use press_coefoz_m, only: plev
107        use regr1_lint_m, only: regr1_lint
108        use pressure_var, only: pls
109    
110      integer, intent(in):: ncid ! NetCDF ID of the file      integer, intent(in):: ncid ! NetCDF ID of the file
111      character(len=*), intent(in):: name ! of the NetCDF variable      character(len=*), intent(in):: name ! of the NetCDF variable
112      integer, intent(in):: julien ! jour julien, 1 <= julien <= 360      integer, intent(in):: julien ! jour julien, 1 <= julien <= 360
113    
     real, intent(in):: plev(:)  
     ! (pressure levels of Mobidic data, in Pa, in strictly increasing order)  
   
114      real, intent(in):: top_value      real, intent(in):: top_value
115      ! (extra value of ozone coefficient at 0 pressure)      ! (extra value of ozone coefficient at 0 pressure)
116    
117      real, intent(out):: v3(:, :) ! (klon, llm)      real, intent(out):: v3(:, :) ! (klon, llm)
118      ! (ozone parameter from Mobidic on the "physics" grid)      ! (ozone coefficient from Mobidic on the "physics" grid)
119      ! ("v3(i, k)" is at longitude "xlon(i)", latitude      ! ("v3(i, k)" is at longitude "xlon(i)", latitude
120      ! "xlat(i)", middle of layer "k".)      ! "xlat(i)", middle of layer "k".)
121    
122      ! Variables local to the procedure:      ! Variables local to the procedure:
123      integer varid, ncerr      integer varid, ncerr
124      integer k      integer i, j, k
125    
126      real  v1(jjm + 1, 0:size(plev))      real  v1(jjm + 1, 0:size(plev))
127      ! (ozone coefficient from "coefoz_LMDZ.nc" at day "julien")      ! (ozone coefficient from "coefoz_LMDZ.nc" at day "julien")
128      ! ("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)".)
129    
130      real v2(iim + 1, jjm + 1, llm)      real v2(iim + 1, jjm + 1, llm)
131      ! (ozone parameter from Mobidic on the "dynamics" grid)      ! (ozone coefficient from Mobidic on the "dynamics" grid)
132      ! "v2(i, j, k)" is at longitude "rlonv(i)", latitude      ! "v2(i, j, k)" is at longitude "rlonv(i)", latitude
133      ! "rlatu(j)", middle of layer "k".)      ! "rlatu(j)", middle of layer "k".)
134    
# Line 132  contains Line 149  contains
149      v1(:, 0) = top_value      v1(:, 0) = top_value
150    
151      ! Regrid in pressure at each horizontal position:      ! Regrid in pressure at each horizontal position:
152      v2 = regr_pr_int(v1, (/0., plev/))      do j = 1, jjm + 1
153           do i = 1, iim
154              if (dyn_phy(i, j)) then
155                 v2(i, j, llm:1:-1) &
156                      = regr1_lint(v1(j, :), (/0., plev/), pls(i, j, llm:1:-1))
157                 ! (invert order of indices because "pls" is decreasing)
158              end if
159           end do
160        end do
161    
162      forall (k = 1:llm) v3(:, k) = pack(v2(:, :, k), dyn_phy)      forall (k = 1:llm) v3(:, k) = pack(v2(:, :, k), dyn_phy)
163    

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

  ViewVC Help
Powered by ViewVC 1.1.21