/[lmdze]/trunk/Sources/dyn3d/Dissipation/nxgraro2.f
ViewVC logotype

Diff of /trunk/Sources/dyn3d/Dissipation/nxgraro2.f

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

trunk/libf/dyn3d/Dissipation/nxgraro2.f revision 64 by guez, Wed Aug 29 14:47:17 2012 UTC trunk/libf/dyn3d/Dissipation/nxgraro2.f90 revision 65 by guez, Thu Sep 20 09:57:03 2012 UTC
# Line 1  Line 1 
1  !  module nxgraro2_m
2  ! $Header: /home/cvsroot/LMDZ4/libf/dyn3d/nxgraro2.F,v 1.1.1.1 2004/05/19 12:53:06 lmdzadmin Exp $  
3  !    IMPLICIT NONE
4         SUBROUTINE nxgraro2 (klevel,xcov, ycov, lr, grx, gry, crot )  
5  c  contains
6  c      P.Le Van .  
7  c   ***********************************************************    SUBROUTINE nxgraro2(xcov, ycov, lr, grx, gry, crot)
8  c                                 lr  
9  c      calcul de  ( nxgrad (rot) )   du vect. v  ....      ! From LMDZ4/libf/dyn3d/nxgraro2.F, version 1.1.1.1 2004/05/19 12:53:06
10  c  
11  c       xcov et ycov  etant les compos. covariantes de  v      ! P. Le Van
12  c   ***********************************************************      ! Calcul de nxgrad(rot) du vecteur v
13  c     xcov , ycov et lr  sont des arguments  d'entree pour le s-prog  
14  c      grx   et  gry     sont des arguments de sortie pour le s-prog      USE dimens_m, ONLY: iim, jjm
15  c      USE filtreg_m, ONLY: filtreg
16  c      use nr_util, only: assert, assert_eq
17        use dimens_m  
18        use paramet_m      ! Composantes covariantes de v :
19        use filtreg_m, only: filtreg      REAL, intent(in):: xcov(:, :, :) ! (iim + 1, jjm + 1, :)
20        IMPLICIT NONE      REAL, intent(in):: ycov(:, :, :) ! (iim + 1, jjm, :)
21  c  
22  c      integer, intent(in):: lr
23  c    ......  variables en arguments  .......      REAL, intent(out):: grx(:, :, :) ! (iim + 1, jjm + 1, :)
24  c      REAL, intent(out):: gry(:, :, :) ! (iim + 1, jjm, :)
25        INTEGER klevel      real, intent(in):: crot
26        REAL, intent(in):: xcov( ip1jmp1,klevel ), ycov( ip1jm,klevel )  
27        REAL, intent(out)::  grx( ip1jmp1,klevel ),  gry( ip1jm,klevel )      ! Variables locales
28        real, intent(in):: crot  
29  c      INTEGER klevel, iter
30  c    ......   variables locales     ........      REAL rot(iim + 1, jjm, size(xcov, 3)) , nugradrs
31  c  
32        REAL rot(ip1jm,llm) , signe, nugradrs      !----------------------------------------------------------
33        INTEGER l,ij,iter  
34        integer, intent(in):: lr      call assert((/size(xcov, 1), size(ycov, 1), size(grx, 1), size(gry, 1)/) &
35  c    ........................................................           == iim + 1, "nxgraro2 iim")
36  c      call assert((/size(xcov, 2) - 1, size(ycov, 2), size(grx, 2) - 1, &
37  c           size(gry, 2)/) == jjm, "nxgraro2 jjm")
38  c      klevel = assert_eq(size(xcov, 3), size(ycov, 3), size(grx, 3), &
39        signe    = (-1.)**lr           size(gry, 3), "nxgraro2 klevel")
40        nugradrs = signe * crot  
41  c      grx = xcov
42        grx = xcov      gry = ycov
43        gry = ycov  
44  c      CALL rotatf(klevel, grx, gry, rot)
45        CALL     rotatf     ( klevel, grx, gry, rot )      CALL laplacien_rot(klevel, rot, rot, grx, gry)
46  c  
47        CALL laplacien_rot ( klevel, rot, rot,grx,gry      )      ! ItĂ©ration de l'opĂ©rateur laplacien_rotgam
48        DO iter = 1, lr - 2
49  c         CALL laplacien_rotgam(klevel, rot, rot)
50  c    .....   Iteration de l'operateur laplacien_rotgam  .....      ENDDO
51  c  
52        DO  iter = 1, lr -2      CALL filtreg(rot, jjm, klevel, 2, 1, .FALSE.)
53          CALL laplacien_rotgam ( klevel, rot, rot )      CALL nxgrad(klevel, rot, grx, gry)
54        ENDDO  
55  c      nugradrs = (-1.)**lr * crot
56  c      grx = grx * nugradrs
57        CALL filtreg( rot, jjm, klevel, 2,1, .FALSE.)      gry = gry * nugradrs
58        CALL nxgrad ( klevel, rot, grx, gry )  
59  c    END SUBROUTINE nxgraro2
60        DO    l = 1, klevel  
61           DO  ij = 1, ip1jm  end module nxgraro2_m
           gry( ij,l ) = gry( ij,l ) * nugradrs  
          ENDDO  
          DO  ij = 1, ip1jmp1  
           grx( ij,l ) = grx( ij,l ) * nugradrs  
          ENDDO  
       ENDDO  
 c  
       RETURN  
       END  

Legend:
Removed from v.64  
changed lines
  Added in v.65

  ViewVC Help
Powered by ViewVC 1.1.21