/[lmdze]/trunk/libf/dyn3d/inter_barxy.f90
ViewVC logotype

Diff of /trunk/libf/dyn3d/inter_barxy.f90

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

revision 3 by guez, Wed Feb 27 13:16:39 2008 UTC revision 24 by guez, Wed Mar 3 13:23:49 2010 UTC
# Line 16  contains Line 16  contains
16    
17      ! Author: P. Le Van      ! Author: P. Le Van
18    
19      use nrutil, only: assert_eq, assert      use numer_rec, only: assert_eq, assert
   
20      use dimens_m, only: iim, jjm      use dimens_m, only: iim, jjm
21      use comgeom, only: aire_2d, apoln, apols      use comgeom, only: aire_2d, apoln, apols
22    
# Line 115  contains Line 114  contains
114      !      ( L'indice 1 correspond a l'interface mailLE 1 / maille 2)      !      ( L'indice 1 correspond a l'interface mailLE 1 / maille 2)
115      !      ( Les abscisses sont exprimées en degres)      !      ( Les abscisses sont exprimées en degres)
116    
117      use nrutil, only: assert_eq      use numer_rec, only: assert_eq
118    
119      IMPLICIT NONE      IMPLICIT NONE
120    
# Line 300  contains Line 299  contains
299      ! Version unidimensionnelle, en latitude.      ! Version unidimensionnelle, en latitude.
300      ! L'indice 1 correspond à l'interface maille 1 -- maille 2.      ! L'indice 1 correspond à l'interface maille 1 -- maille 2.
301    
302      use nrutil, only: assert      use numer_rec, only: assert
303    
304      IMPLICIT NONE      IMPLICIT NONE
305    
# Line 349  contains Line 348  contains
348            dym        = 0.            dym        = 0.
349            jmod       = jmod + 1            jmod       = jmod + 1
350         ELSE         ELSE
351            ! yjmod(jmod) == yjdat(jdat)            ! {yjmod(jmod) == yjdat(jdat)}
352            dy         = yjmod(jmod) - y0            dy         = yjmod(jmod) - y0
353            dym        = dym + dy            dym        = dym + dy
354            inter_bary(jmod) = (inter_bary(jmod) + dy * fdat(jdat)) / dym            inter_bary(jmod) = (inter_bary(jmod) + dy * fdat(jdat)) / dym
# Line 377  contains Line 376  contains
376      ! reverses their order.      ! reverses their order.
377      ! Finally, the procedure adds 90° as the last value of the array.      ! Finally, the procedure adds 90° as the last value of the array.
378    
379      use nrutil, only: assert_eq      use numer_rec, only: assert_eq
380      use comconst, only: pi      use comconst, only: pi
381    
382      IMPLICIT NONE      IMPLICIT NONE

Legend:
Removed from v.3  
changed lines
  Added in v.24

  ViewVC Help
Powered by ViewVC 1.1.21