/[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 3 by guez, Wed Feb 27 13:16:39 2008 UTC trunk/libf/phylmd/Mobidic/regr_pr_coefoz.f90 revision 47 by guez, Fri Jul 1 15:00:48 2011 UTC
# Line 1  Line 1 
1  module o3_Mob_ph_m  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    function o3_Mob_ph(ncid, name)    subroutine regr_pr_av_coefoz(ncid, name, julien, v3)
17    
18      ! This function reads a single Mobidic ozone parameter from a file and      ! "regr_pr_av_coefoz" stands for "regrid pressure averaging
19      ! packs it on the "physics" grid.      ! coefficient ozone".
20        ! The target vertical LMDZ grid is the grid of layer boundaries.
21        ! The input data does not depend on longitude, but the pressure
22        ! at LMDZ layers does.
23        ! Therefore, the values on the LMDZ grid do depend on longitude.
24        ! 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, nf90_get_var, handle_err      use netcdf95, only: nf95_inq_varid, handle_err
29        use netcdf, only: nf90_get_var
30      use grid_change, only: dyn_phy      use grid_change, only: dyn_phy
31        use nr_util, only: assert
32        use press_coefoz_m, only: press_in_edg
33        use l_util, 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
39    
40        real, intent(out):: v3(:, :) ! (klon, llm)
41        ! (ozone coefficient from Mobidic on the "physics" grid)
42        ! ("v3(i, k)" is at longitude "xlon(i)", latitude
43        ! "xlat(i)", in layer "k".)
44    
45        ! Variables local to the procedure:
46    
47        integer varid, ncerr ! for NetCDF
48    
49        real  v1(jjm + 1, size(press_in_edg) - 1)
50        ! (ozone coefficient from "coefoz_LMDZ.nc" at day "julien")
51        ! ("v1(j, k)" is at latitude "rlatu(j)" and for
52        ! pressure interval "[press_in_edg(k), press_in_edg(k+1)]".)
53    
54        real v2(iim + 1, jjm + 1, llm)
55        ! (ozone coefficient on the "dynamics" grid)
56        ! ("v2(i, j, k)" is at longitude "rlonv(i)", latitude
57        ! "rlatu(j)" and for pressure interval "[p3d(i, j, k+1), p3d(i, j, k)]".)
58    
59        integer i, j, k
60    
61        !--------------------------------------------
62    
63        call assert(shape(v3) == (/klon, llm/), "regr_pr_av_coefoz")
64    
65        call nf95_inq_varid(ncid, name, varid)
66    
67        ! Get data at the right day from the input file:
68        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)
70        ! Latitudes are in ascending order in the input file while
71        ! "rlatu" is in descending order so we need to invert order:
72        v1 = v1(jjm+1:1:-1, :)
73    
74        ! Regrid in pressure at each horizontal position:
75        do j = 1, jjm + 1
76           do i = 1, iim
77              if (dyn_phy(i, j)) then
78                 v2(i, j, llm:1:-1) &
79                      = regr1_step_av(v1(j, :), press_in_edg, &
80                      p3d(i, j, llm+1:1:-1))
81                 ! (invert order of indices because "p3d" is in descending order)
82              end if
83           end do
84        end do
85    
86        forall (k = 1:llm) v3(:, k) = pack(v2(:, :, k), dyn_phy)
87    
88      end subroutine regr_pr_av_coefoz
89    
90      !***************************************************************
91    
92      subroutine regr_pr_int_coefoz(ncid, name, julien, top_value, v3)
93    
94        ! "regr_pr_int_coefoz" stands for "regrid pressure interpolation
95        ! coefficient ozone".
96        ! The target vertical LMDZ grid is the grid of mid-layers.
97        ! The input data does not depend on longitude, but the pressure
98        ! at LMDZ mid-layers does.
99        ! Therefore, the values on the LMDZ grid do depend on longitude.
100        ! Regridding is by linear interpolation.
101    
102      real o3_Mob_ph(klon, llm, 12)      use dimens_m, only: iim, jjm, llm
103      ! (ozone parameter from Mobidic on the "physics" grid)      use dimphy, only: klon
104      ! (Third dimension is the number of the month in the year.      use netcdf95, only: nf95_inq_varid, handle_err
105      ! "o3_Mob_ph(i, k, month)" is at longitude "xlon(i)", latitude      use netcdf, only: nf90_get_var
106        use grid_change, only: dyn_phy
107        use nr_util, only: assert
108        use press_coefoz_m, only: plev
109        use l_util, only: regr1_lint
110        use pressure_var, only: pls
111    
112        integer, intent(in):: ncid ! NetCDF ID of the file
113        character(len=*), intent(in):: name ! of the NetCDF variable
114        integer, intent(in):: julien ! jour julien, 1 <= julien <= 360
115    
116        real, intent(in):: top_value
117        ! (extra value of ozone coefficient at 0 pressure)
118    
119        real, intent(out):: v3(:, :) ! (klon, llm)
120        ! (ozone coefficient from Mobidic on the "physics" grid)
121        ! ("v3(i, k)" is at longitude "xlon(i)", latitude
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:
     integer varid, ncerr  
     integer k, month  
125    
126      real o3_Mob_dyn(iim + 1, jjm + 1, llm, 12)      integer varid, ncerr ! for NetCDF
127      ! (ozone parameter from Mobidic on the "dynamics" grid)  
128      ! Fourth dimension is the number of the month in the year.      real  v1(jjm + 1, 0:size(plev))
129      ! "o3_Mob_dyn(i, j, k, month)" is at longitude "rlonv(i)", latitude      ! (ozone coefficient from "coefoz_LMDZ.nc" at day "julien")
130      ! "rlatu(j)", middle of layer "k".)      ! ("v1(j, k >=1)" is at latitude "rlatu(j)" and pressure "plev(k)".)
131    
132        real v2(iim + 1, jjm + 1, llm)
133        ! (ozone coefficient on the "dynamics" grid)
134        ! "v2(i, j, k)" is at longitude "rlonv(i)", latitude
135        ! "rlatu(j)" and pressure "pls(i, j, k)".)
136    
137        integer i, j, k
138    
139      !--------------------------------------------      !--------------------------------------------
140    
141        call assert(shape(v3) == (/klon, llm/), "regr_pr_int_coefoz")
142    
143      call nf95_inq_varid(ncid, name, varid)      call nf95_inq_varid(ncid, name, varid)
     ncerr = nf90_get_var(ncid, varid, o3_Mob_dyn)  
     call handle_err("o3_Mob_ph nf90_get_var " // name, ncerr, ncid)  
144    
145      ! Latitudes are in increasing order in the input file while      ! Get data at the right day from the input file:
146      ! "rlatu" is in decreasing order, so invert:      ncerr = nf90_get_var(ncid, varid, v1(:, 1:), start=(/1, 1, julien/))
147      o3_Mob_dyn = o3_Mob_dyn(:, jjm+1:1:-1, :, :)      call handle_err("regr_pr_int_coefoz nf90_get_var " // name, ncerr, ncid)
148      forall (k = 1:llm, month = 1:12) &      ! Latitudes are in ascending order in the input file while
149           o3_Mob_ph(:, k, month) = pack(o3_Mob_dyn(:, :, k, month), dyn_phy)      ! "rlatu" is in descending order so we need to invert order:
150        v1(:, 1:) = v1(jjm+1:1:-1, 1:)
151    
152        ! Complete "v1" with the value at 0 pressure:
153        v1(:, 0) = top_value
154    
155        ! Regrid in pressure at each horizontal position:
156        do j = 1, jjm + 1
157           do i = 1, iim
158              if (dyn_phy(i, j)) then
159                 v2(i, j, llm:1:-1) &
160                      = regr1_lint(v1(j, :), (/0., plev/), pls(i, j, llm:1:-1))
161                 ! (invert order of indices because "pls" is in descending order)
162              end if
163           end do
164        end do
165    
166        forall (k = 1:llm) v3(:, k) = pack(v2(:, :, k), dyn_phy)
167    
168    end function o3_Mob_ph    end subroutine regr_pr_int_coefoz
169    
170  end module o3_Mob_ph_m  end module regr_pr_coefoz

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

  ViewVC Help
Powered by ViewVC 1.1.21