source: LMDZ6/trunk/libf/dyn3d/groupe.f90 @ 5273

Last change on this file since 5273 was 5272, checked in by abarral, 2 days ago

Turn paramet.h into a module

  • 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
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 2.4 KB
Line 
1!
2! $Header$
3!
4subroutine groupe(pext,pbaru,pbarv,pbarum,pbarvm,wm)
5
6  use comconst_mod, only: ngroup
7
8  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
9USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
10          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
11implicit none
12
13  !   sous-programme servant a fitlrer les champs de flux de masse aux
14  !   poles en "regroupant" les mailles 2 par 2 puis 4 par 4 etc. au fur
15  !   et a mesure qu'on se rapproche du pole.
16  !
17  !   en entree: pext, pbaru et pbarv
18  !
19  !   en sortie:  pbarum,pbarvm et wm.
20  !
21  !   remarque, le wm est recalcule a partir des pbaru pbarv et on n'a donc
22  !   pas besoin de w en entree.
23
24
25
26  include "comgeom2.h"
27
28  ! integer ngroup
29  ! parameter (ngroup=3)
30
31
32  real :: pbaru(iip1,jjp1,llm),pbarv(iip1,jjm,llm)
33  real :: pext(iip1,jjp1,llm)
34
35  real :: pbarum(iip1,jjp1,llm),pbarvm(iip1,jjm,llm)
36  real :: wm(iip1,jjp1,llm)
37
38  real :: zconvm(iip1,jjp1,llm),zconvmm(iip1,jjp1,llm)
39
40  real :: uu
41
42  integer :: i,j,l
43
44  logical :: firstcall,groupe_ok
45  save firstcall,groupe_ok
46
47  data firstcall/.true./
48  data groupe_ok/.true./
49
50  if (iim==1) then
51     groupe_ok=.false.
52  endif
53
54  if (firstcall) then
55     if (groupe_ok) then
56        if(mod(iim,2**ngroup).ne.0) &
57              CALL abort_gcm('groupe','probleme du nombre de point',1)
58     endif
59     firstcall=.false.
60  endif
61
62
63  !   Champs 1D
64
65  call convflu(pbaru,pbarv,llm,zconvm)
66
67  call scopy(ijp1llm,zconvm,1,zconvmm,1)
68  call scopy(ijmllm,pbarv,1,pbarvm,1)
69
70  if (groupe_ok) then
71  call groupeun(jjp1,llm,zconvmm)
72  call groupeun(jjm,llm,pbarvm)
73
74  !   Champs 3D
75  do l=1,llm
76     do j=2,jjm
77        uu=pbaru(iim,j,l)
78        do i=1,iim
79           uu=uu+pbarvm(i,j,l)-pbarvm(i,j-1,l)-zconvmm(i,j,l)
80           pbarum(i,j,l)=uu
81  ! zconvm(i,j,l ) =  xflu(i-1,j,l)-xflu(i,j,l)+
82  !    *                      yflu(i,j,l)-yflu(i,j-1,l)
83        enddo
84        pbarum(iip1,j,l)=pbarum(1,j,l)
85     enddo
86  enddo
87
88  else
89     pbarum(:,:,:)=pbaru(:,:,:)
90     pbarvm(:,:,:)=pbarv(:,:,:)
91  endif
92
93  !    integration de la convergence de masse de haut  en bas ......
94  do l=1,llm
95     do j=1,jjp1
96        do i=1,iip1
97           zconvmm(i,j,l)=zconvmm(i,j,l)
98        enddo
99     enddo
100  enddo
101  do  l = llm-1,1,-1
102      do j=1,jjp1
103         do i=1,iip1
104            zconvmm(i,j,l)=zconvmm(i,j,l)+zconvmm(i,j,l+1)
105         enddo
106      enddo
107  enddo
108
109  CALL vitvert(zconvmm,wm)
110
111  return
112end subroutine groupe
113
Note: See TracBrowser for help on using the repository browser.