source: LMDZ6/trunk/libf/dyn3dmem/nxgraro2_loc.f90 @ 5300

Last change on this file since 5300 was 5285, checked in by abarral, 4 days ago

As discussed internally, remove generic ONLY: ... for new _mod_h modules

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 3.4 KB
Line 
1 SUBROUTINE nxgraro2_loc(klevel,xcov,ycov,lr,grx_out,gry_out)
2  !
3  !  P.Le Van .
4  !   ***********************************************************
5  !                             lr
6  !  calcul de  ( nxgrad (rot) )   du vect. v  ....
7  !
8  !   xcov et ycov  etant les compos. covariantes de  v
9  !   ***********************************************************
10  ! xcov , ycov et lr  sont des arguments  d'entree pour le s-prog
11  !  grx   et  gry     sont des arguments de sortie pour le s-prog
12  !
13  !
14  USE comdissipn_mod_h
15  USE write_Field_p
16  USE parallel_lmdz
17  USE times
18  USE mod_hallo
19  USE mod_filtreg_p
20  USE nxgraro2_mod
21  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
22USE paramet_mod_h
23IMPLICIT NONE
24  !
25
26
27  !
28  !    ......  variables en arguments  .......
29  !
30  INTEGER :: klevel
31  REAL :: xcov( ijb_u:ije_u,klevel ), ycov( ijb_v:ije_v,klevel )
32  REAL :: grx_out( ijb_u:ije_u,klevel ),gry_out(ijb_v:ije_v,klevel)
33  !
34  !    ......   variables locales     ........
35  !
36  REAL :: signe, nugradrs
37  INTEGER :: l,ij,iter,lr
38  Type(Request),SAVE :: Request_dissip
39!$OMP THREADPRIVATE(Request_dissip)
40  !    ........................................................
41  !
42  INTEGER :: ijb,ije,jjb,jje
43
44  !
45  !
46  signe    = (-1.)**lr
47  nugradrs = signe * crot
48  !
49  !  CALL SCOPY ( ip1jmp1* klevel, xcov, 1, grx, 1 )
50  !  CALL SCOPY (  ip1jm * klevel, ycov, 1, gry, 1 )
51
52  ijb=ij_begin
53  ije=ij_end
54
55!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
56  DO    l = 1, klevel
57    grx(ijb:ije,l)=xcov(ijb:ije,l)
58  ENDDO
59!$OMP END DO NOWAIT
60
61!$OMP BARRIER
62   call Register_Hallo_u(grx,llm,0,1,1,0,Request_dissip)
63   call SendRequest(Request_dissip)
64!$OMP BARRIER
65   call WaitRequest(Request_dissip)
66!$OMP BARRIER
67
68  ijb=ij_begin
69  ije=ij_end
70  if(pole_sud) ije=ij_end-iip1
71
72!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
73  DO    l = 1, klevel
74    gry(ijb:ije,l)=ycov(ijb:ije,l)
75  ENDDO
76!$OMP END DO NOWAIT
77
78  !
79  CALL     rotatf_loc ( klevel, grx, gry, rot )
80   ! call write_field3d_p('rot1',reshape(rot,(/iip1,jjm,llm/)))
81
82!$OMP BARRIER
83   call Register_Hallo_v(rot,llm,1,1,1,1,Request_dissip)
84   call SendRequest(Request_dissip)
85!$OMP BARRIER
86   call WaitRequest(Request_dissip)
87!$OMP BARRIER
88
89  CALL laplacien_rot_loc ( klevel, rot, rot,grx,gry      )
90    ! call write_field3d_p('rot2',reshape(rot,(/iip1,jjm,llm/)))
91  !
92  !    .....   Iteration de l'operateur laplacien_rotgam  .....
93  !
94  DO  iter = 1, lr -2
95!$OMP BARRIER
96   call Register_Hallo_v(rot,llm,1,1,1,1,Request_dissip)
97   call SendRequest(Request_dissip)
98!$OMP BARRIER
99   call WaitRequest(Request_dissip)
100!$OMP BARRIER
101
102    CALL laplacien_rotgam_loc( klevel, rot, rot )
103  ENDDO
104
105    ! call write_field3d_p('rot3',reshape(rot,(/iip1,jjm,llm/)))
106
107  !
108  !
109  jjb=jj_begin
110  jje=jj_end
111  if (pole_sud) jje=jj_end-1
112
113  CALL filtreg_p( rot, jjb_v,jje_v, jjb,jje,jjm, &
114        klevel, 2,1, .FALSE.,1)
115!$OMP BARRIER
116   call Register_Hallo_v(rot,llm,1,0,0,1,Request_dissip)
117   call SendRequest(Request_dissip)
118!$OMP BARRIER
119   call WaitRequest(Request_dissip)
120!$OMP BARRIER
121
122  CALL nxgrad_loc ( klevel, rot, grx, gry )
123
124  !
125  ijb=ij_begin
126  ije=ij_end
127
128!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
129  DO    l = 1, klevel
130
131     if(pole_sud) ije=ij_end-iip1
132     DO  ij = ijb, ije
133      gry_out( ij,l ) = gry( ij,l ) * nugradrs
134     ENDDO
135
136     if(pole_sud) ije=ij_end
137     DO  ij = ijb, ije
138      grx_out( ij,l ) = grx( ij,l ) * nugradrs
139     ENDDO
140
141  ENDDO
142!$OMP END DO NOWAIT
143  !
144  RETURN
145END SUBROUTINE nxgraro2_loc
Note: See TracBrowser for help on using the repository browser.