source: LMDZ6/trunk/libf/dyn3dmem/groupe_loc.f90 @ 5308

Last change on this file since 5308 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: 2.8 KB
RevLine 
[5246]1subroutine groupe_loc(pext,pbaru,pbarv,pbarum,pbarvm,wm)
[5281]2  USE comgeom2_mod_h
[5246]3  USE parallel_lmdz
4  USE Write_field_loc
5  USE groupe_mod
6  USE comconst_mod, ONLY: ngroup
[5258]7  USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_DEBUGIO
[5271]8  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
[5285]9USE paramet_mod_h
[5271]10implicit none
[1632]11
[5246]12  !   sous-programme servant a fitlrer les champs de flux de masse aux
13  !   poles en "regroupant" les mailles 2 par 2 puis 4 par 4 etc. au fur
14  !   et a mesure qu'on se rapproche du pole.
15  !
16  !   en entree: pext, pbaru et pbarv
17  !
18  !   en sortie:  pbarum,pbarvm et wm.
19  !
20  !   remarque, le wm est recalcule a partir des pbaru pbarv et on n'a donc
21  !   pas besoin de w en entree.
[1632]22
[5271]23
[5272]24
[1632]25
[5246]26  ! integer ngroup
27  ! parameter (ngroup=3)
[1632]28
29
[5246]30  real :: pbaru(iip1,jjb_u:jje_u,llm),pbarv(iip1,jjb_v:jje_v,llm)
31  real :: pext(iip1,jjb_u:jje_u,llm)
[1632]32
[5246]33  real :: pbarum(iip1,jjb_u:jje_u,llm),pbarvm(iip1,jjb_v:jje_v,llm)
34  real :: wm(iip1,jjb_u:jje_u,llm)
[1632]35
36
[5246]37  real :: uu
[1632]38
[5246]39  integer :: i,j,l
[1632]40
[5246]41  logical :: firstcall
42  save firstcall
43!$OMP THREADPRIVATE(firstcall)
[1632]44
[5246]45  integer :: ijb,ije,jjb,jje
[1632]46
[5246]47  !   Champs 1D
[1632]48
[5246]49  call convflu_loc(pbaru,pbarv,llm,zconvm)
[1632]50
[5246]51  !
52  !  call scopy(ijp1llm,zconvm,1,zconvmm,1)
53  !  call scopy(ijmllm,pbarv,1,pbarvm,1)
[1632]54
[5246]55  jjb=jj_begin
56  jje=jj_end
[1632]57
[5246]58!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
59  do l=1,llm
60    zconvmm(:,jjb:jje,l)=zconvm(:,jjb:jje,l)
61  enddo
62!$OMP END DO NOWAIT
63
64  call groupeun_loc(jjp1,llm,jjb_u,jje_u,jjb,jje,zconvmm)
65
66  jjb=jj_begin-1
67  jje=jj_end
68  if (pole_nord) jjb=jj_begin
69  if (pole_sud)  jje=jj_end-1
70!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
71  do l=1,llm
72    pbarvm(:,jjb:jje,l)=pbarv(:,jjb:jje,l)
73  enddo
74!$OMP END DO NOWAIT
75
[5258]76IF (CPPKEY_DEBUGIO) THEN
[5246]77  CALL WriteField_v('pbarvm',reshape(pbarvm,(/ip1jm,llm/)))
[5258]78END IF
[5246]79  call groupeun_loc(jjm,llm,jjb_v,jje_v,jjb,jje,pbarvm)
[5258]80IF (CPPKEY_DEBUGIO) THEN
[5246]81  CALL WriteField_v('pbarvm',reshape(pbarvm,(/ip1jm,llm/)))
[5258]82END IF
[5246]83  !   Champs 3D
84
85  jjb=jj_begin
86  jje=jj_end
87  if (pole_nord) jjb=jj_begin+1
88  if (pole_sud)  jje=jj_end-1
89
90!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
91  do l=1,llm
92     do j=jjb,jje
93        uu=pbaru(iim,j,l)
94        do i=1,iim
95           uu=uu+pbarvm(i,j,l)-pbarvm(i,j-1,l)-zconvmm(i,j,l)
96           pbarum(i,j,l)=uu
97  ! zconvm(i,j,l ) =  xflu(i-1,j,l)-xflu(i,j,l)+
98  !    *                      yflu(i,j,l)-yflu(i,j-1,l)
99        enddo
100        pbarum(iip1,j,l)=pbarum(1,j,l)
101     enddo
102  enddo
103!$OMP END DO NOWAIT
104  !    integration de la convergence de masse de haut  en bas ......
105
106  jjb=jj_begin
107  jje=jj_end
108
109!$OMP BARRIER
110!$OMP MASTER
111  do  l = llm-1,1,-1
112      do j=jjb,jje
113         do i=1,iip1
114            zconvmm(i,j,l)=zconvmm(i,j,l)+zconvmm(i,j,l+1)
[1632]115         enddo
116      enddo
[5246]117  enddo
[1632]118
[5246]119  if (.not. pole_sud) then
120    zconvmm(:,jj_end+1,:)=0
121  !ym   wm(:,jj_end+1,:)=0
122  endif
[1632]123
[5246]124!$OMP END MASTER
125!$OMP BARRIER
[1632]126
[5246]127  CALL vitvert_loc(zconvmm,wm)
[1632]128
[5246]129  return
130end subroutine groupe_loc
[1632]131
Note: See TracBrowser for help on using the repository browser.