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

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

Convert fixed-form to free-form sources .F -> .{f,F}90
(WIP: some .F remain, will be handled in subsequent commits)

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