/[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 6 by guez, Wed Feb 27 13:16:39 2008 UTC revision 7 by guez, Mon Mar 31 12:24:17 2008 UTC
# Line 1  Line 1 
1  module o3_Mob_ph_m  module regr_pr_coefoz
2    
3    implicit none    implicit none
4    
5  contains  contains
6    
7    function o3_Mob_ph(ncid, name)    subroutine regr_pr_av_coefoz(ncid, name, julien, press_in_edg, v3)
8    
9      ! This function reads a single Mobidic ozone parameter from a file and      ! "regr_pr_av_coefoz" stands for "regrid pressure averaging
10      ! packs it on the "physics" grid.      ! coefficients ozone".
11        ! This procedure reads a single Mobidic ozone coefficient from
12        !"coefoz_LMDZ.nc", at the current day, regrids this parameter in
13        ! pressure to the LMDZ vertical grid and packs it to the LMDZ
14        ! horizontal "physics" grid.
15        ! Regridding is by averaging a step function.
16    
17      use dimens_m, only: iim, jjm, llm      use dimens_m, only: iim, jjm, llm
18      use dimphy, only: klon      use dimphy, only: klon
19      use netcdf95, only: nf95_inq_varid, nf90_get_var, handle_err      use netcdf95, only: nf95_inq_varid, handle_err
20        use netcdf, only: nf90_get_var
21      use grid_change, only: dyn_phy      use grid_change, only: dyn_phy
22        use regr_pr, only: regr_pr_av
23        use nrutil, only: assert
24    
25      integer, intent(in):: ncid ! NetCDF ID of the file      integer, intent(in):: ncid ! NetCDF ID of the file
26      character(len=*), intent(in):: name ! of the NetCDF variable      character(len=*), intent(in):: name ! of the NetCDF variable
27        integer, intent(in):: julien ! jour julien, 1 <= julien <= 360
28    
29      real o3_Mob_ph(klon, llm, 12)      real, intent(in):: press_in_edg(:)
30        ! (edges of pressure intervals for Mobidic data, in Pa, in
31        ! strictly increasing order)
32    
33        real, intent(out):: v3(:, :) ! (klon, llm)
34        ! (ozone coefficient from Mobidic on the "physics" grid)
35        ! ("v3(i, k)" is at longitude "xlon(i)", latitude
36        ! "xlat(i)", middle of layer "k".)
37    
38        ! Variables local to the procedure:
39        integer varid, ncerr
40        integer k
41    
42        real  v1(jjm + 1, size(press_in_edg) - 1)
43        ! (ozone coefficient from "coefoz_LMDZ.nc" at day "julien")
44        ! ("v1(j, k)" is at latitude "rlatu(j)" and for
45        ! pressure interval "[press_in_edg(k), press_in_edg(k+1)]".)
46    
47        real v2(iim + 1, jjm + 1, llm)
48        ! (ozone parameter from Mobidic on the "dynamics" grid)
49        ! "v2(i, j, k)" is at longitude "rlonv(i)", latitude
50        ! "rlatu(j)", middle of layer "k".)
51    
52        !--------------------------------------------
53    
54        call assert(shape(v3) == (/klon, llm/), "regr_pr_av_coefoz")
55    
56        call nf95_inq_varid(ncid, name, varid)
57    
58        ! Get data at the right day from the input file:
59        ncerr = nf90_get_var(ncid, varid, v1, start=(/1, 1, julien/))
60        call handle_err("regr_pr_av_coefoz nf90_get_var " // name, ncerr, ncid)
61        ! Latitudes are in increasing order in the input file while
62        ! "rlatu" is in decreasing order so we need to invert order:
63        v1 = v1(jjm+1:1:-1, :)
64    
65        ! Regrid in pressure at each horizontal position:
66        v2 = regr_pr_av(v1, press_in_edg)
67    
68        forall (k = 1:llm) v3(:, k) = pack(v2(:, :, k), dyn_phy)
69    
70      end subroutine regr_pr_av_coefoz
71    
72      !***************************************************************
73    
74      subroutine regr_pr_int_coefoz(ncid, name, julien, plev, top_value, v3)
75    
76        ! This procedure reads a single Mobidic ozone coefficient from
77        !"coefoz_LMDZ.nc", at the current day, regrids this parameter in
78        ! pressure to the LMDZ vertical grid and packs it to the LMDZ
79        ! horizontal "physics" grid.
80        ! Regridding is by linear interpolation.
81    
82        use dimens_m, only: iim, jjm, llm
83        use dimphy, only: klon
84        use netcdf95, only: nf95_inq_varid, handle_err
85        use netcdf, only: nf90_get_var
86        use grid_change, only: dyn_phy
87        use regr_pr, only: regr_pr_int
88        use nrutil, only: assert
89    
90        integer, intent(in):: ncid ! NetCDF ID of the file
91        character(len=*), intent(in):: name ! of the NetCDF variable
92        integer, intent(in):: julien ! jour julien, 1 <= julien <= 360
93    
94        real, intent(in):: plev(:)
95        ! (pressure levels of Mobidic data, in Pa, in strictly increasing order)
96    
97        real, intent(in):: top_value
98        ! (extra value of ozone coefficient at 0 pressure)
99    
100        real, intent(out):: v3(:, :) ! (klon, llm)
101      ! (ozone parameter from Mobidic on the "physics" grid)      ! (ozone parameter from Mobidic on the "physics" grid)
102      ! (Third dimension is the number of the month in the year.      ! ("v3(i, k)" is at longitude "xlon(i)", latitude
     ! "o3_Mob_ph(i, k, month)" is at longitude "xlon(i)", latitude  
103      ! "xlat(i)", middle of layer "k".)      ! "xlat(i)", middle of layer "k".)
104    
105      ! Variables local to the procedure:      ! Variables local to the procedure:
106      integer varid, ncerr      integer varid, ncerr
107      integer k, month      integer k
108    
109        real  v1(jjm + 1, 0:size(plev))
110        ! (ozone coefficient from "coefoz_LMDZ.nc" at day "julien")
111        ! ("v1(j, k >=1)" is at latitude "rlatu(j)" and pressure "plev(k)".)
112    
113      real o3_Mob_dyn(iim + 1, jjm + 1, llm, 12)      real v2(iim + 1, jjm + 1, llm)
114      ! (ozone parameter from Mobidic on the "dynamics" grid)      ! (ozone parameter from Mobidic on the "dynamics" grid)
115      ! Fourth dimension is the number of the month in the year.      ! "v2(i, j, k)" is at longitude "rlonv(i)", latitude
     ! "o3_Mob_dyn(i, j, k, month)" is at longitude "rlonv(i)", latitude  
116      ! "rlatu(j)", middle of layer "k".)      ! "rlatu(j)", middle of layer "k".)
117    
118      !--------------------------------------------      !--------------------------------------------
119    
120        call assert(shape(v3) == (/klon, llm/), "regr_pr_int_coefoz")
121    
122      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)  
123    
124        ! Get data at the right day from the input file:
125        ncerr = nf90_get_var(ncid, varid, v1(:, 1:), start=(/1, 1, julien/))
126        call handle_err("regr_pr_int_coefoz nf90_get_var " // name, ncerr, ncid)
127      ! Latitudes are in increasing order in the input file while      ! Latitudes are in increasing order in the input file while
128      ! "rlatu" is in decreasing order, so invert:      ! "rlatu" is in decreasing order so we need to invert order:
129      o3_Mob_dyn = o3_Mob_dyn(:, jjm+1:1:-1, :, :)      v1(:, 1:) = v1(jjm+1:1:-1, 1:)
130      forall (k = 1:llm, month = 1:12) &  
131           o3_Mob_ph(:, k, month) = pack(o3_Mob_dyn(:, :, k, month), dyn_phy)      ! Complete "v1" with the value at 0 pressure:
132        v1(:, 0) = top_value
133    
134        ! Regrid in pressure at each horizontal position:
135        v2 = regr_pr_int(v1, (/0., plev/))
136    
137        forall (k = 1:llm) v3(:, k) = pack(v2(:, :, k), dyn_phy)
138    
139    end function o3_Mob_ph    end subroutine regr_pr_int_coefoz
140    
141  end module o3_Mob_ph_m  end module regr_pr_coefoz

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

  ViewVC Help
Powered by ViewVC 1.1.21