/[lmdze]/trunk/libf/regr1_lint.f90
ViewVC logotype

Annotation of /trunk/libf/regr1_lint.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 13 - (hide annotations)
Fri Jul 25 19:59:34 2008 UTC (15 years, 11 months ago) by guez
File size: 2559 byte(s)
-- Minor change of behaviour:

"etat0" does not compute "rugsrel" nor "radpas". Deleted arguments
"radpas" and "rugsrel" of "phyredem". Deleted argument "rugsrel" of
"phyetat0". "startphy.nc" does not contain the variable "RUGSREL". In
"physiq", "rugoro" is set to 0 if not "ok_orodr". The whole program
"etat0_lim" does not use "clesphys2".

-- Minor modification of input/output:

Created subroutine "read_clesphys2". Variables of "clesphys2" are read
in "read_clesphys2" instead of "conf_gcm". "printflag" does not print
variables of "clesphys2".

-- Should not change any result at run time:

References to module "numer_rec" instead of individual modules of
"Numer_rec_Lionel".

Deleted argument "clesphy0" of "calfis", "physiq", "conf_gcm",
"leapfrog", "phyetat0". Deleted variable "clesphy0" in
"gcm". "phyetat0" does not modify variables of "clesphys2".

The program unit "gcm" does not modify "itau_phy".

Added some "intent" attributes.

"regr11_lint" does not call "polint".

1 guez 9 module regr1_lint_m
2    
3     implicit none
4    
5     interface regr1_lint
6     ! Each procedure regrids by linear interpolation.
7     ! The regridding operation is done on the first dimension of the
8     ! input array.
9     ! The difference betwwen the procedures is the rank of the first argument.
10     module procedure regr11_lint, regr12_lint
11     end interface
12    
13     private
14     public regr1_lint
15    
16     contains
17    
18     function regr11_lint(vs, xs, xt) result(vt)
19    
20     ! "vs" has rank 1.
21    
22 guez 13 use numer_rec, only: assert_eq, hunt !!, polint
23 guez 9
24     real, intent(in):: vs(:)
25     ! (values of the function at source points "xs")
26    
27     real, intent(in):: xs(:)
28     ! (abscissas of points in source grid, in strictly monotonic order)
29    
30     real, intent(in):: xt(:)
31     ! (abscissas of points in target grid)
32    
33     real vt(size(xt)) ! values of the function on the target grid
34    
35     ! Variables local to the procedure:
36     integer is, it, ns
37     integer is_b ! "is" bound between 1 and "ns - 1"
38    
39     !--------------------------------------
40    
41     ns = assert_eq(size(vs), size(xs), "regr11_lint ns")
42    
43     is = -1 ! go immediately to bisection on first call to "hunt"
44    
45     do it = 1, size(xt)
46     call hunt(xs, xt(it), is)
47     is_b = min(max(is, 1), ns - 1)
48 guez 13 !! call polint(xs(is_b:is_b+1), vs(is_b:is_b+1), xt(it), vt(it))
49     vt(it) = ((xs(is_b+1) - xt(it)) * vs(is_b) &
50     + (xt(it) - xs(is_b)) * vs(is_b+1)) / (xs(is_b+1) - xs(is_b))
51 guez 9 end do
52    
53     end function regr11_lint
54    
55     !*********************************************************
56    
57     function regr12_lint(vs, xs, xt) result(vt)
58    
59     ! "vs" has rank 2.
60    
61 guez 13 use numer_rec, only: assert_eq, hunt
62 guez 9
63     real, intent(in):: vs(:, :)
64     ! (values of the function at source points "xs")
65    
66     real, intent(in):: xs(:)
67     ! (abscissas of points in source grid, in strictly monotonic order)
68    
69     real, intent(in):: xt(:)
70     ! (abscissas of points in target grid)
71    
72     real vt(size(xt), size(vs, 2)) ! values of the function on the target grid
73    
74     ! Variables local to the procedure:
75     integer is, it, ns
76     integer is_b ! "is" bound between 1 and "ns - 1"
77    
78     !--------------------------------------
79    
80     ns = assert_eq(size(vs, 1), size(xs), "regr12_lint ns")
81    
82     is = -1 ! go immediately to bisection on first call to "hunt"
83    
84     do it = 1, size(xt)
85     call hunt(xs, xt(it), is)
86     is_b = min(max(is, 1), ns - 1)
87     vt(it, :) = ((xs(is_b+1) - xt(it)) * vs(is_b, :) &
88     + (xt(it) - xs(is_b)) * vs(is_b+1, :)) / (xs(is_b+1) - xs(is_b))
89     end do
90    
91     end function regr12_lint
92    
93     end module regr1_lint_m

  ViewVC Help
Powered by ViewVC 1.1.21