source: LMDZ4/trunk/libf/dyn3dpar/nxgrarot_p.F @ 630

Last change on this file since 630 was 630, checked in by Laurent Fairhead, 19 years ago

Import d'une version parallele de la dynamique YM
LF

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 2.3 KB
Line 
1      SUBROUTINE nxgrarot_p (klevel,xcov, ycov, lr, grx, gry )
2c   ***********************************************************
3c
4c    Auteur :  P.Le Van 
5c
6c                                 lr
7c      calcul de  ( nXgrad (rot) )   du vect. v  ....
8c
9c       xcov et ycov  etant les compos. covariantes de  v
10c   ***********************************************************
11c     xcov , ycov et lr  sont des arguments  d'entree pour le s-prog
12c      grx   et  gry     sont des arguments de sortie pour le s-prog
13c
14c
15      USE parallel
16      USE times
17      USE write_field_p
18      IMPLICIT NONE
19c
20c
21#include "dimensions.h"
22#include "paramet.h"
23#include "comdissipn.h"
24#include "logic.h"
25c
26      INTEGER klevel
27      REAL xcov( ip1jmp1,klevel ), ycov( ip1jm,klevel )
28      REAL  grx( ip1jmp1,klevel ),  gry( ip1jm,klevel )
29c
30      REAL rot(ip1jm,llm)
31
32      INTEGER l,ij,iter,lr
33c
34      EXTERNAL    filtreg
35      EXTERNAL       SCOPY, rotat, nXgrad
36      INTEGER ijb,ije,jjb,jje
37c
38c
39c      CALL SCOPY ( ip1jmp1*klevel, xcov, 1, grx, 1 )
40c      CALL SCOPY (  ip1jm*klevel, ycov, 1, gry, 1 )
41c
42      ijb=ij_begin
43      ije=ij_end
44      grx(ijb:ije,1:klevel)=xcov(ijb:ije,1:klevel)
45     
46      if(pole_sud) ije=ij_end-iip1
47      gry(ijb:ije,1:klevel)=ycov(ijb:ije,1:klevel)
48     
49      DO 10 iter = 1,lr
50      call suspend_timer(timer_dissip)
51      call exchange_Hallo(grx,ip1jmp1,llm,0,1)
52      call resume_timer(timer_dissip)
53      CALL  rotat_p (klevel,grx, gry, rot )
54c      call write_field3d_p('rot',reshape(rot,(/iip1,jjm,llm/)))
55     
56      jjb=jj_begin
57      jje=jj_end
58      if (pole_sud) jje=jj_end-1
59      CALL filtreg_p( rot,jjb,jje, jjm, klevel, 2,1, .false.,2)
60     
61      call suspend_timer(timer_dissip)
62      call exchange_Hallo(rot,ip1jm,llm,1,0)
63      call resume_timer(timer_dissip)
64     
65      CALL nxgrad_p (klevel,rot, grx, gry )
66c
67      DO 5  l = 1, klevel
68      if(pole_sud) ije=ij_end-iip1
69      DO 2 ij = ijb, ije
70      gry( ij,l ) = - gry( ij,l ) * crot
71   2  CONTINUE
72      if(pole_sud) ije=ij_end
73      DO 3 ij = ijb, ije
74      grx( ij,l ) = - grx( ij,l ) * crot
75   3  CONTINUE
76   5  CONTINUE
77
78c      call write_field3d_p('grx',reshape(grx,(/iip1,jjp1,llm/)))
79c      call write_field3d_p('gry',reshape(gry,(/iip1,jjm,llm/)))
80c      stop
81  10  CONTINUE
82      RETURN
83      END
Note: See TracBrowser for help on using the repository browser.