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

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

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

trunk/libf/dyn3d/nxgraro2.f revision 26 by guez, Tue Mar 9 15:27:15 2010 UTC trunk/Sources/dyn3d/Dissipation/nxgraro2.f revision 137 by guez, Wed May 6 15:51:03 2015 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 )  
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_v_m, ONLY: filtreg_v
16  c      use nr_util, only: assert, assert_eq
17        use dimens_m      use rotatf_m, only: rotatf
18        use paramet_m  
19              use inidissip_m      ! Composantes covariantes de v :
20        IMPLICIT NONE      REAL, intent(in):: xcov(:, :, :) ! (iim + 1, jjm + 1, :)
21  c      REAL, intent(in):: ycov(:, :, :) ! (iim + 1, jjm, :)
22  c  
23  c    ......  variables en arguments  .......      integer, intent(in):: lr
24  c      REAL, intent(out):: grx(:, :, :) ! (iim + 1, jjm + 1, :)
25        INTEGER klevel      REAL, intent(out):: gry(:, :, :) ! (iim + 1, jjm, :)
26        REAL xcov( ip1jmp1,klevel ), ycov( ip1jm,klevel )      real, intent(in):: crot
27        REAL  grx( ip1jmp1,klevel ),  gry( ip1jm,klevel )  
28  c      ! Variables locales
29  c    ......   variables locales     ........  
30  c      INTEGER klevel, iter
31        REAL rot(ip1jm,llm) , signe, nugradrs      REAL rot(iim + 1, jjm, size(xcov, 3)) , nugradrs
32        INTEGER l,ij,iter  
33        integer, intent(in):: lr      !----------------------------------------------------------
34  c    ........................................................  
35  c      call assert((/size(xcov, 1), size(ycov, 1), size(grx, 1), size(gry, 1)/) &
36  c           == iim + 1, "nxgraro2 iim")
37  c      call assert((/size(xcov, 2) - 1, size(ycov, 2), size(grx, 2) - 1, &
38        signe    = (-1.)**lr           size(gry, 2)/) == jjm, "nxgraro2 jjm")
39        nugradrs = signe * crot      klevel = assert_eq(size(xcov, 3), size(ycov, 3), size(grx, 3), &
40  c           size(gry, 3), "nxgraro2 klevel")
41        CALL SCOPY ( ip1jmp1* klevel, xcov, 1, grx, 1 )  
42        CALL SCOPY (  ip1jm * klevel, ycov, 1, gry, 1 )      grx = xcov
43  c      gry = ycov
44        CALL     rotatf     ( klevel, grx, gry, rot )  
45  c      CALL rotatf(klevel, grx, gry, rot)
46        CALL laplacien_rot ( klevel, rot, rot,grx,gry      )      CALL laplacien_rot(klevel, rot, rot, grx, gry)
47    
48  c      ! ItĂ©ration de l'opĂ©rateur laplacien_rotgam
49  c    .....   Iteration de l'operateur laplacien_rotgam  .....      DO iter = 1, lr - 2
50  c         CALL laplacien_rotgam(klevel, rot, rot)
51        DO  iter = 1, lr -2      ENDDO
52          CALL laplacien_rotgam ( klevel, rot, rot )  
53        ENDDO      CALL filtreg_v(rot, intensive = .true.)
54  c      CALL nxgrad(klevel, rot, grx, gry)
55  c  
56        CALL filtreg( rot, jjm, klevel, 2,1, .FALSE.,1)      nugradrs = (-1.)**lr * crot
57        CALL nxgrad ( klevel, rot, grx, gry )      grx = grx * nugradrs
58  c      gry = gry * nugradrs
59        DO    l = 1, klevel  
60           DO  ij = 1, ip1jm    END SUBROUTINE nxgraro2
61            gry( ij,l ) = gry( ij,l ) * nugradrs  
62           ENDDO  end module nxgraro2_m
          DO  ij = 1, ip1jmp1  
           grx( ij,l ) = grx( ij,l ) * nugradrs  
          ENDDO  
       ENDDO  
 c  
       RETURN  
       END  

Legend:
Removed from v.26  
changed lines
  Added in v.137

  ViewVC Help
Powered by ViewVC 1.1.21