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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 10 - (hide annotations)
Fri Apr 18 14:45:53 2008 UTC (16 years, 1 month ago) by guez
File size: 5026 byte(s)
Added NetCDF directory "/home/guez/include" in "g95.mk" and
"nag_tools.mk".

Added some "intent" attributes in "PVtheta", "advtrac", "caladvtrac",
"calfis", "diagedyn", "dissip", "vlspltqs", "aeropt", "ajsec",
"calltherm", "clmain", "cltrac", "cltracrn", "concvl", "conema3",
"conflx", "fisrtilp", "newmicro", "nuage", "diagcld1", "diagcld2",
"drag_noro", "lift_noro", "SUGWD", "physiq", "phytrac", "radlwsw", "thermcell".

Removed the case "ierr == 0" in "abort_gcm"; moved call to "histclo"
and messages for end of run from "abort_gcm" to "gcm"; replaced call
to "abort_gcm" in "leapfrog" by exit from outer loop.

In "calfis": removed argument "pp" and variable "unskap"; changed
"pksurcp" from scalar to rank 2; use "pressure_var"; rewrote
computation of "zplev", "zplay", "ztfi", "pcvgt" using "dyn_phy";
added computation of "pls".

Removed unused variable in "dynredem0".

In "exner_hyb": changed "dellta" from scalar to rank 1; replaced call
to "ssum" by call to "sum"; removed variables "xpn" and "xps";
replaced some loops by array expressions.

In "leapfrog": use "pressure_var"; deleted variables "p", "longcles".

Converted common blocks "YOECUMF", "YOEGWD" to modules.

Removed argument "pplay" in "cvltr", "diagetpq", "nflxtr".

Created module "raddimlw" from include file "raddimlw.h".

Corrected call to "new_unit" in "test_disvert".

1 guez 7 module regr_pr_coefoz
2 guez 3
3     implicit none
4    
5     contains
6    
7 guez 7 subroutine regr_pr_av_coefoz(ncid, name, julien, press_in_edg, v3)
8 guez 3
9 guez 7 ! "regr_pr_av_coefoz" stands for "regrid pressure averaging
10 guez 10 ! coefficient ozone".
11 guez 7 ! 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 guez 10 ! Regridding in pressure is done by averaging a step function.
16 guez 3
17     use dimens_m, only: iim, jjm, llm
18     use dimphy, only: klon
19 guez 7 use netcdf95, only: nf95_inq_varid, handle_err
20     use netcdf, only: nf90_get_var
21 guez 3 use grid_change, only: dyn_phy
22 guez 7 use regr_pr, only: regr_pr_av
23     use nrutil, only: assert
24 guez 3
25     integer, intent(in):: ncid ! NetCDF ID of the file
26     character(len=*), intent(in):: name ! of the NetCDF variable
27 guez 7 integer, intent(in):: julien ! jour julien, 1 <= julien <= 360
28 guez 3
29 guez 7 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 guez 3 ! (ozone parameter from Mobidic on the "physics" grid)
102 guez 7 ! ("v3(i, k)" is at longitude "xlon(i)", latitude
103 guez 3 ! "xlat(i)", middle of layer "k".)
104    
105     ! Variables local to the procedure:
106     integer varid, ncerr
107 guez 7 integer k
108 guez 3
109 guez 7 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 v2(iim + 1, jjm + 1, llm)
114 guez 3 ! (ozone parameter from Mobidic on the "dynamics" grid)
115 guez 7 ! "v2(i, j, k)" is at longitude "rlonv(i)", latitude
116 guez 3 ! "rlatu(j)", middle of layer "k".)
117    
118     !--------------------------------------------
119    
120 guez 7 call assert(shape(v3) == (/klon, llm/), "regr_pr_int_coefoz")
121    
122 guez 3 call nf95_inq_varid(ncid, name, varid)
123    
124 guez 7 ! 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 guez 3 ! Latitudes are in increasing order in the input file while
128 guez 7 ! "rlatu" is in decreasing order so we need to invert order:
129     v1(:, 1:) = v1(jjm+1:1:-1, 1:)
130 guez 3
131 guez 7 ! Complete "v1" with the value at 0 pressure:
132     v1(:, 0) = top_value
133 guez 3
134 guez 7 ! 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 subroutine regr_pr_int_coefoz
140    
141     end module regr_pr_coefoz

  ViewVC Help
Powered by ViewVC 1.1.21