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

Diff of /trunk/libf/regr1_step_av.f90

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 13 by guez, Fri Jul 25 19:59:34 2008 UTC revision 36 by guez, Thu Dec 2 17:11:04 2010 UTC
# Line 1  Line 1 
1  module regr1_step_av_m  module regr1_step_av_m
2    
3      ! Author: Lionel GUEZ
4    
5    implicit none    implicit none
6    
7    interface regr1_step_av    interface regr1_step_av
# Line 13  module regr1_step_av_m Line 15  module regr1_step_av_m
15       ! extrapolation is allowed.       ! extrapolation is allowed.
16       ! The difference between the procedures is the rank of the first argument.       ! The difference between the procedures is the rank of the first argument.
17    
18       module procedure regr11_step_av, regr12_step_av, regr13_step_av       module procedure regr11_step_av, regr12_step_av, regr13_step_av, &
19              regr14_step_av
20    end interface    end interface
21    
22    private    private
# Line 25  contains Line 28  contains
28    
29      ! "vs" has rank 1.      ! "vs" has rank 1.
30    
31      use numer_rec, only: assert_eq, assert, locate      use nr_util, only: assert_eq, assert
32        use numer_rec, only: locate
33    
34      real, intent(in):: vs(:) ! values of steps on the source grid      real, intent(in):: vs(:) ! values of steps on the source grid
35      ! (Step "is" is between "xs(is)" and "xs(is + 1)".)      ! (Step "is" is between "xs(is)" and "xs(is + 1)".)
# Line 82  contains Line 86  contains
86    
87      ! "vs" has rank 2.      ! "vs" has rank 2.
88    
89      use numer_rec, only: assert_eq, assert, locate      use nr_util, only: assert_eq, assert
90        use numer_rec, only: locate
91    
92      real, intent(in):: vs(:, :) ! values of steps on the source grid      real, intent(in):: vs(:, :) ! values of steps on the source grid
93      ! (Step "is" is between "xs(is)" and "xs(is + 1)".)      ! (Step "is" is between "xs(is)" and "xs(is + 1)".)
# Line 140  contains Line 145  contains
145    
146      ! "vs" has rank 3.      ! "vs" has rank 3.
147    
148      use numer_rec, only: assert_eq, assert, locate      use nr_util, only: assert_eq, assert
149        use numer_rec, only: locate
150    
151      real, intent(in):: vs(:, :, :) ! values of steps on the source grid      real, intent(in):: vs(:, :, :) ! values of steps on the source grid
152      ! (Step "is" is between "xs(is)" and "xs(is + 1)".)      ! (Step "is" is between "xs(is)" and "xs(is + 1)".)
# Line 193  contains Line 199  contains
199    
200    end function regr13_step_av    end function regr13_step_av
201    
202      !********************************************
203    
204      function regr14_step_av(vs, xs, xt) result(vt)
205    
206        ! "vs" has rank 4.
207    
208        use nr_util, only: assert_eq, assert
209        use numer_rec, only: locate
210    
211        real, intent(in):: vs(:, :, :, :) ! values of steps on the source grid
212        ! (Step "is" is between "xs(is)" and "xs(is + 1)".)
213    
214        real, intent(in):: xs(:)
215        ! (edges of steps on the source grid, in strictly increasing order)
216    
217        real, intent(in):: xt(:)
218        ! (edges of cells of the target grid, in strictly increasing order)
219    
220        real vt(size(xt) - 1, size(vs, 2), size(vs, 3), size(vs, 4))
221        ! (average values on the target grid)
222        ! (Cell "it" is between "xt(it)" and "xt(it + 1)".)
223    
224        ! Variables local to the procedure:
225        integer is, it, ns, nt
226        real left_edge
227    
228        !---------------------------------------------
229    
230        ns = assert_eq(size(vs, 1), size(xs) - 1, "regr14_step_av ns")
231        nt = size(xt) - 1
232    
233        ! Quick check on sort order:
234        call assert(xs(1) < xs(2), "regr14_step_av xs bad order")
235        call assert(xt(1) < xt(2), "regr14_step_av xt bad order")
236    
237        call assert(xs(1) <= xt(1) .and. xt(nt + 1) <= xs(ns + 1), &
238             "regr14_step_av extrapolation")
239    
240        is = locate(xs, xt(1)) ! 1 <= is <= ns, because we forbid extrapolation
241        do it = 1, nt
242           ! 1 <= is <= ns
243           ! xs(is) <= xt(it) < xs(is + 1)
244           ! Compute "vt(it, :, :, :)":
245           left_edge = xt(it)
246           vt(it, :, :, :) = 0.
247           do while (xs(is + 1) < xt(it + 1))
248              ! 1 <= is <= ns - 1
249              vt(it, :, :, :) = vt(it, :, :, :) + (xs(is + 1) - left_edge) &
250                   * vs(is, :, :, :)
251              is = is + 1
252              left_edge = xs(is)
253           end do
254           ! 1 <= is <= ns
255           vt(it, :, :, :) = (vt(it, :, :, :) + (xt(it + 1) - left_edge) &
256                * vs(is, :, :, :)) / (xt(it + 1) - xt(it))
257           if (xs(is + 1) == xt(it + 1)) is = is + 1
258           ! 1 <= is <= ns .or. it == nt
259        end do
260    
261      end function regr14_step_av
262    
263  end module regr1_step_av_m  end module regr1_step_av_m

Legend:
Removed from v.13  
changed lines
  Added in v.36

  ViewVC Help
Powered by ViewVC 1.1.21