/[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 18 - (hide annotations)
Thu Aug 7 12:29:13 2008 UTC (15 years, 11 months ago) by guez
File size: 4752 byte(s)
In module "regr_pr", rewrote scanning of horizontal positions as a
single set of loops, using a mask.

Added some "intent" attributes.

In "dynredem0", replaced calls to Fortran 77 interface of NetCDF by
calls to NetCDF95. Removed calls to "nf_redef", regrouped all writing
operations. In "dynredem1", replaced some calls to Fortran 77
interface of NetCDF by calls to Fortran 90 interface.

Renamed variable "nqmax" to "nq_phys".

In "physiq", if "nq >= 5" then "wo" is computed from the
parameterization of "Cariolle".

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

  ViewVC Help
Powered by ViewVC 1.1.21