/[lmdze]/trunk/libf/bibio/regr_pr.f90
ViewVC logotype

Annotation of /trunk/libf/bibio/regr_pr.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 12 - (hide annotations)
Mon Jul 21 16:05:07 2008 UTC (15 years, 10 months ago) by guez
File size: 5400 byte(s)
-- Minor modification of input/output:

Created procedure "read_logic". Variables of module "logic" are read
by "read_logic" instead of "conf_gcm". Variable "offline" of module
"conf_gcm" is read from namelist instead of "*.def".

Deleted arguments "dtime", "co2_ppm_etat0", "solaire_etat0",
"tabcntr0" and local variables "radpas", "tab_cntrl" of
"phyetat0". "phyetat0" does not read "controle" in "startphy.nc" any
longer. "phyetat0" now reads global attribute "itau_phy" from
"startphy.nc". "phyredem" does not create variable "controle" in
"startphy.nc" any longer. "phyredem" now writes global attribute
"itau_phy" of "startphy.nc". Deleted argument "tabcntr0" of
"printflag". Removed diagnostic messages written by "printflag" for
comparison of the variable "controle" of "startphy.nc" and the
variables read from "*.def" or namelist input.

-- Removing unwanted functionality:

Removed variable "lunout" from module "iniprint", replaced everywhere
by standard output.

Removed case "ocean == 'couple'" in "clmain", "interfsurf_hq" and
"physiq". Removed procedure "interfoce_cpl".

-- Should not change anything at run time:

Automated creation of graphs in documentation. More documentation on
input files.

Converted Fortran files to free format: "phyredem.f90", "printflag.f90".

Split module "clesphy" into "clesphys" and "clesphys2".

Removed variables "conser", "leapf", "forward", "apphys", "apdiss" and
"statcl" from module "logic". Added arguments "conser" to "advect",
"leapf" to "integrd". Added local variables "forward", "leapf",
"apphys", "conser", "apdiss" in "leapfrog".

Added intent attributes.

Deleted arguments "dtime" of "phyredem", "pdtime" of "flxdtdq", "sh"
of "phytrac", "dt" of "yamada".

Deleted local variables "dtime", "co2_ppm_etat0", "solaire_etat0",
"length", "tabcntr0" in "physiq". Replaced all references to "dtime"
by references to "pdtphys".

1 guez 7 module regr_pr
2    
3     implicit none
4    
5     contains
6    
7     function regr_pr_av(v, press_in)
8    
9     ! "regr_pr_av" stands for "regrid pressure averaging".
10     ! This function regrids a 2D latitude -- pressure variable to the
11     ! LMDZ 3D grid.
12 guez 10 ! The target horizontal LMDZ grid is the "scalar" grid: "rlonv", "rlatu".
13     ! The target vertical LMDZ grid is the grid of layer boundaries.
14 guez 7 ! We assume that the variable is already on the LMDZ "rlatu" latitude grid.
15     ! There only remains to regrid in pressure at each horizontal
16     ! position.
17     ! The input variable does not depend on longitude, but the pressure
18 guez 10 ! at LMDZ layers does.
19 guez 7 ! Therefore, the values on the LMDZ grid do depend on longitude.
20     ! The variable is regridded by averaging.
21    
22     use dimens_m, only: iim, jjm, llm
23     use nrutil, only: assert
24     use regr1_step_av_m, only: regr1_step_av
25 guez 10 use pressure_var, only: p3d
26 guez 7
27     real, intent(in):: v(:, :)
28     ! ("v(j, l)" is at latitude "rlatu(j)" and for pressure interval
29     ! "[press_in(l), press_in(l+1)]".)
30    
31     real, intent(in):: press_in(:)
32     ! (edges of pressure intervals, on input grid, in Pa, in strictly
33     ! increasing order)
34    
35     real regr_pr_av(iim + 1, jjm + 1, llm)
36     ! (variable adapted to the LMDZ grid
37     ! "regr_pr_av(i, j, l)" is at longitude "rlonv(i)", latitude
38 guez 10 ! "rlatu(j)" and in pressure interval "[p3d(i, j, l+1), p3d(i, j, l)]")
39 guez 7
40     ! Variables local to the procedure:
41     integer i, j
42    
43     !---------------------------------------------
44    
45     call assert(size(v, 1) == jjm + 1, "regr_pr_av 1")
46     call assert(size(press_in) == size(v, 2) + 1, "regr_pr_av 2")
47    
48     ! Regrid in pressure by averaging a step function of pressure.
49    
50     ! Poles ("p3d" does not depend on longitude):
51     do j = 1, jjm + 1, jjm
52     ! Average on pressure, only for first longitude:
53     regr_pr_av(1, j, llm:1:-1) &
54     = regr1_step_av(v(j, :), press_in, p3d(1, j, llm+1:1:-1))
55     ! (invert order of indices because "p3d" is decreasing)
56     end do
57    
58     ! Latitudes other than poles ("p3d" depends on longitude):
59     do j = 2, jjm
60     ! Average on pressure at each longitude:
61     do i = 1, iim
62     regr_pr_av(i, j, llm:1:-1) &
63 guez 12 = regr1_step_av(v(j, :), press_in, p3d(i, j, llm+1:1:-1))
64 guez 7 ! (invert order of indices because "p3d" is decreasing)
65     end do
66     end do
67    
68     ! Duplicate pole values on all longitudes:
69     regr_pr_av(2:, 1, :) = spread(regr_pr_av(1, 1, :), dim=1, ncopies=iim)
70     regr_pr_av(2:, jjm + 1, :) &
71     = spread(regr_pr_av(1, jjm + 1, :), dim=1, ncopies=iim)
72    
73     ! Duplicate first longitude to last longitude:
74     regr_pr_av(iim + 1, 2:jjm, :) = regr_pr_av(1, 2:jjm, :)
75    
76     end function regr_pr_av
77    
78     !************************************************************
79    
80     function regr_pr_int(v, press_in)
81    
82     ! "regr_pr_int" stands for "regrid pressure interpolation".
83     ! This function regrids a 2D latitude -- pressure variable to the
84     ! LMDZ 3D grid.
85 guez 10 ! The target horizontal LMDZ grid is the "scalar" grid: "rlonv", "rlatu".
86     ! The target vertical LMDZ grid is the grid of mid-layers.
87 guez 7 ! We assume that the variable is already on the LMDZ latitude grid.
88     ! There only remains to regrid in pressure at each horizontal
89     ! position.
90     ! The input variable does not depend on longitude, but the pressure
91     ! at LMDZ mid-layers does.
92     ! Therefore, the values on the LMDZ grid do depend on longitude.
93     ! The variable is regridded by interpolation.
94    
95     use dimens_m, only: iim, jjm, llm
96     use nrutil, only: assert
97     use regr1_lint_m, only: regr1_lint
98 guez 10 use pressure_var, only: pls
99 guez 7
100     real, intent(in):: v(:, :)
101     ! ("v(j, l)" is at latitude "rlatu(j)" and pressure level "press_in(l)".)
102    
103     real, intent(in):: press_in(:)
104     ! (pressure levels on input grid, in Pa, in strictly increasing order)
105    
106     real regr_pr_int(iim + 1, jjm + 1, llm)
107     ! (variable adapted to the LMDZ grid
108     ! "regr_pr_int(i, j, l)" is at longitude "rlonv(i)", latitude
109     ! "rlatu(j)" and pressure level "pls(i, j, l)")
110    
111     ! Variables local to the procedure:
112     integer i, j
113    
114     !---------------------------------------------
115    
116     call assert(size(v, 1) == jjm + 1, "regr_pr_int 1")
117     call assert(size(press_in) == size(v, 2), "regr_pr_int 2")
118    
119     ! Regrid in pressure by linear interpolation
120    
121     ! Poles ("pls" does not depend on longitude):
122     do j = 1, jjm + 1, jjm
123     ! Interpolate in pressure, only for first longitude:
124     regr_pr_int(1, j, llm:1:-1) &
125     = regr1_lint(v(j, :), press_in, pls(1, j, llm:1:-1))
126     ! (invert order of indices because "pls" is decreasing)
127     end do
128    
129     ! Latitudes other than poles ("pls" depends on longitude):
130     do j = 2, jjm
131     ! Average on pressure at each longitude:
132     do i = 1, iim
133     regr_pr_int(i, j, llm:1:-1) &
134     = regr1_lint(v(j, :), press_in, pls(i, j, llm:1:-1))
135     ! (invert order of indices because "pls" is decreasing)
136     end do
137     end do
138    
139     ! Duplicate pole values on all longitudes:
140     regr_pr_int(2:, 1, :) &
141     = spread(regr_pr_int(1, 1, :), dim=1, ncopies=iim)
142     regr_pr_int(2:, jjm + 1, :) &
143     = spread(regr_pr_int(1, jjm + 1, :), dim=1, ncopies=iim)
144    
145     ! Duplicate first longitude to last longitude:
146     regr_pr_int(iim + 1, 2:jjm, :) = regr_pr_int(1, 2:jjm, :)
147    
148     end function regr_pr_int
149    
150     end module regr_pr

  ViewVC Help
Powered by ViewVC 1.1.21