/[lmdze]/trunk/Sources/dyn3d/divergf.f
ViewVC logotype

Diff of /trunk/Sources/dyn3d/divergf.f

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

trunk/libf/dyn3d/divergf.f revision 55 by guez, Mon Dec 12 13:25:01 2011 UTC trunk/dyn3d/divergf.f revision 82 by guez, Wed Mar 5 14:57:53 2014 UTC
# Line 1  Line 1 
1  !  module divergf_m
2  ! $Header: /home/cvsroot/LMDZ4/libf/dyn3d/divergf.F,v 1.1.1.1 2004/05/19 12:53:05 lmdzadmin Exp $  
3  !    IMPLICIT NONE
4        SUBROUTINE divergf(klevel,x,y,div)  
5  c  contains
6  c     P. Le Van  
7  c    SUBROUTINE divergf(klevel, x, y, div)
8  c  *********************************************************************  
9  c  ... calcule la divergence a tous les niveaux d'1 vecteur de compos.      ! From libf/dyn3d/divergf.F, version 1.1.1.1 2004/05/19 12:53:05
10  c     x et y...  
11  c              x et y  etant des composantes covariantes   ...      ! P. Le Van
12  c  *********************************************************************      ! Calcule la divergence à tous les niveaux d'un vecteur de
13        use dimens_m      ! composantes x et y. x et y sont des composantes covariantes.
14        use paramet_m  
15        use comgeom      USE comgeom, ONLY: apoln, apols, cuvsurcv, cvusurcu, unsaire
16        use filtreg_m, only: filtreg      USE dimens_m, ONLY: iim
17        IMPLICIT NONE      USE filtreg_m, ONLY: filtreg
18  c      USE paramet_m, ONLY: iip1, iip2, ip1jm, ip1jmi1, ip1jmp1, jjp1
19  c      x  et  y  sont des arguments  d'entree pour le s-prog  
20  c        div      est  un argument  de sortie pour le s-prog      INTEGER, intent(in):: klevel
21  c      REAL, intent(in):: x(ip1jmp1, klevel), y(ip1jm, klevel)
22  c      real, intent(out):: div(ip1jmp1, klevel) ! in (unit of x, y) m-2
23  c   ---------------------------------------------------------------------  
24  c      ! Variables locales :
25  c    ATTENTION : pendant ce s-pg , ne pas toucher au COMMON/scratch/  .  
26  c      INTEGER l, ij
27  c   ---------------------------------------------------------------------      REAL aiy1(iim) , aiy2(iim)
28  c      REAL sumypn, sumyps
29  c    ..........          variables en arguments    ...................  
30  c      !------------------------------------------------------------
31        INTEGER, intent(in):: klevel  
32        REAL x( ip1jmp1,klevel ),y( ip1jm,klevel ),div( ip1jmp1,klevel )      DO l = 1, klevel
33        INTEGER   l,ij         DO ij = iip2, ip1jm - 1
34  c            div(ij + 1, l) = cvusurcu(ij+1) * x(ij+1, l) &
35  c    ...............     variables  locales   .........................                 - cvusurcu(ij) * x(ij , l) + cuvsurcv(ij-iim) * y(ij-iim, l) &
36                   - cuvsurcv(ij+1) * y(ij+1, l)
37        REAL aiy1( iip1 ) , aiy2( iip1 )         ENDDO
38        REAL sumypn,sumyps  
39  c    ...................................................................         DO ij = iip2, ip1jm, iip1
40  c            div(ij, l) = div(ij + iim, l)
41        REAL      SSUM         ENDDO
42  c  
43  c         ! Calcul aux pôles
44        DO 10 l = 1,klevel  
45  c         DO ij = 1, iim
46          DO  ij = iip2, ip1jm - 1            aiy1(ij) = cuvsurcv(ij) * y(ij , l)
47           div( ij + 1, l )     =              aiy2(ij) = cuvsurcv(ij+ ip1jmi1) * y(ij+ ip1jmi1, l)
48       *   cvusurcu( ij+1 ) * x( ij+1,l ) - cvusurcu( ij ) * x( ij , l) +         ENDDO
49       *   cuvsurcv(ij-iim) * y(ij-iim,l) - cuvsurcv(ij+1) * y(ij+1,l)         sumypn = SUM(aiy1) / apoln
50          ENDDO         sumyps = SUM(aiy2) / apols
51  c  
52  c     ....  correction pour  div( 1,j,l)  ......         DO ij = 1, iip1
53  c     ....   div(1,j,l)= div(iip1,j,l) ....            div(ij , l) = - sumypn
54  c            div(ij + ip1jm, l) = sumyps
55  CDIR$ IVDEP         ENDDO
56          DO  ij = iip2,ip1jm,iip1      end DO
57           div( ij,l ) = div( ij + iim,l )  
58          ENDDO      CALL filtreg(div, jjp1, klevel, 2, 2, .TRUE.)
59  c  
60  c     ....  calcul  aux poles  .....      DO l = 1, klevel
61  c         DO ij = iip2, ip1jm
62          DO  ij  = 1,iim            div(ij, l) = div(ij, l) * unsaire(ij)
63           aiy1(ij) =    cuvsurcv(    ij       ) * y(     ij     , l )         ENDDO
64           aiy2(ij) =    cuvsurcv( ij+ ip1jmi1 ) * y( ij+ ip1jmi1, l )      ENDDO
65          ENDDO  
66          sumypn = SSUM ( iim,aiy1,1 ) / apoln    END SUBROUTINE divergf
67          sumyps = SSUM ( iim,aiy2,1 ) / apols  
68  c  end module divergf_m
         DO  ij = 1,iip1  
          div(     ij    , l ) = - sumypn  
          div( ij + ip1jm, l ) =   sumyps  
         ENDDO  
   10  CONTINUE  
 c  
   
         CALL filtreg( div, jjp1, klevel, 2, 2, .TRUE., 1 )  
         
 c  
         DO l = 1, klevel  
            DO ij = iip2,ip1jm  
             div(ij,l) = div(ij,l) * unsaire(ij)  
           ENDDO  
         ENDDO  
 c  
        RETURN  
        END  

Legend:
Removed from v.55  
changed lines
  Added in v.82

  ViewVC Help
Powered by ViewVC 1.1.21